napkin-1.0.0
Safe HaskellNone
LanguageGHC2021

Polysemy.Mock

Synopsis

Documentation

pattern (:->) :: forall {k} f (m :: k) a. () => f m a -> a -> DSumI (f m) #

data Action (r :: EffectRow) (rInitial :: Type -> Type) #

Constructors

ExpectRequest (DSumI (Union r rInitial)) 
UnsafeForceReturn Any

Escape hatch, use with caution, expect segfaults

Instances

Instances details
Member r effs => MockInterpret effs '[State (ActionsU effs rInitial) :: (Type -> Type) -> Type -> Type, Error MockError' :: (Type -> Type) -> Type -> Type] rInitial # 
Instance details

Defined in Polysemy.Mock

Methods

interpretMock :: Sem '[State (ActionsU effs rInitial) :: (Type -> Type) -> Type -> Type, Error MockError' :: (Type -> Type) -> Type -> Type] a -> Sem '[State (ActionsU effs rInitial) :: (Type -> Type) -> Type -> Type, Error MockError' :: (Type -> Type) -> Type -> Type] a #

type DSumI (f :: Type -> Type) = DSum f Identity #

forgetM :: forall f (m :: Type -> Type) a. f m a -> f [] a #

We do only care about data in GADT, we can do unsafe coerce as long as our effect is first order

type ActionsU (r :: EffectRow) (rInitial :: Type -> Type) = [Action r rInitial] #

newtype MockError' #

Constructors

MockErrorMessage Text 

Instances

Instances details
IsString MockError' # 
Instance details

Defined in Polysemy.Mock

Exception MockError' # 
Instance details

Defined in Polysemy.Mock

Show MockError' # 
Instance details

Defined in Polysemy.Mock

Eq MockError' # 
Instance details

Defined in Polysemy.Mock

Member r effs => MockInterpret effs '[State (ActionsU effs rInitial) :: (Type -> Type) -> Type -> Type, Error MockError' :: (Type -> Type) -> Type -> Type] rInitial # 
Instance details

Defined in Polysemy.Mock

Methods

interpretMock :: Sem '[State (ActionsU effs rInitial) :: (Type -> Type) -> Type -> Type, Error MockError' :: (Type -> Type) -> Type -> Type] a -> Sem '[State (ActionsU effs rInitial) :: (Type -> Type) -> Type -> Type, Error MockError' :: (Type -> Type) -> Type -> Type] a #

data MockResult a #

Instances

Instances details
Show a => Show (MockResult a) # 
Instance details

Defined in Polysemy.Mock

Eq a => Eq (MockResult a) # 
Instance details

Defined in Polysemy.Mock

Methods

(==) :: MockResult a -> MockResult a -> Bool #

(/=) :: MockResult a -> MockResult a -> Bool #

mockSem :: forall (ra :: EffectRow) (rb :: Type -> Type) e (m :: Type -> Type) x (r :: EffectRow). (GShow (e []), GEq (e []), Member (State (ActionsU ra rb) :: (Type -> Type) -> Type -> Type) r, Member e ra, GShow (Union ra []), Member (Error MockError' :: (Type -> Type) -> Type -> Type) r) => e m x -> Sem r x #

gshow' :: forall {k} f (a :: k). GShow f => f a -> Text #

verifyU :: forall (f :: EffectRow) w (r :: Type -> Type). GShow (Union f []) => Either MockError' ([Action f r], w) -> Either MockError' w #

class Member (State (ActionsU effs rInitial) :: (Type -> Type) -> Type -> Type) r => MockInterpret (effs :: EffectRow) (r :: EffectRow) (rInitial :: Type -> Type) where #

Methods

interpretMock :: Sem r a -> Sem '[State (ActionsU effs rInitial) :: (Type -> Type) -> Type -> Type, Error MockError' :: (Type -> Type) -> Type -> Type] a #

Instances

Instances details
Member r effs => MockInterpret effs '[State (ActionsU effs rInitial) :: (Type -> Type) -> Type -> Type, Error MockError' :: (Type -> Type) -> Type -> Type] rInitial # 
Instance details

Defined in Polysemy.Mock

Methods

interpretMock :: Sem '[State (ActionsU effs rInitial) :: (Type -> Type) -> Type -> Type, Error MockError' :: (Type -> Type) -> Type -> Type] a -> Sem '[State (ActionsU effs rInitial) :: (Type -> Type) -> Type -> Type, Error MockError' :: (Type -> Type) -> Type -> Type] a #

(GShow (Union effs []), GShow (r []), GEq (r []), Member r effs, MockInterpret effs (ra ': (rs ': rw)) rInitial, Member (State (ActionsU effs rInitial) :: (Type -> Type) -> Type -> Type) (r ': (ra ': (rs ': rw))), FirstOrder r "interpretMock", Member (Error MockError' :: (Type -> Type) -> Type -> Type) (rs ': rw), Member (Error MockError' :: (Type -> Type) -> Type -> Type) (ra ': (rs ': rw))) => MockInterpret effs (r ': (ra ': (rs ': rw))) rInitial # 
Instance details

Defined in Polysemy.Mock

Methods

interpretMock :: Sem (r ': (ra ': (rs ': rw))) a -> Sem '[State (ActionsU effs rInitial) :: (Type -> Type) -> Type -> Type, Error MockError' :: (Type -> Type) -> Type -> Type] a #

type family AllFirstOrder (xs :: EffectRow) where ... #

Equations

AllFirstOrder ('[] :: [Effect]) = () 
AllFirstOrder (x ': xs) = (FirstOrder x "runMockM", AllFirstOrder xs) 

runMockM :: forall (mockedEffs :: EffectRow) a (effs :: EffectRow) (rInitial :: Type -> Type). (GShow (Union mockedEffs []), MockInterpret mockedEffs effs rInitial, effs ~ (mockedEffs ++ '[State (ActionsU mockedEffs rInitial) :: (Type -> Type) -> Type -> Type, Error MockError' :: (Type -> Type) -> Type -> Type]), AllFirstOrder mockedEffs) => ActionList mockedEffs rInitial -> Sem effs a -> MockResult a #

data ActionList (r :: EffectRow) (rInitial :: Type -> Type) #

To be used with OverloadedLists

Constructors

SingleAction (Action r rInitial) 
MultipleActions [ActionList r rInitial] 

Instances

Instances details
Monoid (ActionList r rInitial) # 
Instance details

Defined in Polysemy.Mock

Methods

mempty :: ActionList r rInitial #

mappend :: ActionList r rInitial -> ActionList r rInitial -> ActionList r rInitial #

mconcat :: [ActionList r rInitial] -> ActionList r rInitial #

Semigroup (ActionList r rInitial) # 
Instance details

Defined in Polysemy.Mock

Methods

(<>) :: ActionList r rInitial -> ActionList r rInitial -> ActionList r rInitial #

sconcat :: NonEmpty (ActionList r rInitial) -> ActionList r rInitial #

stimes :: Integral b => b -> ActionList r rInitial -> ActionList r rInitial #

IsList (ActionList r rInitial) # 
Instance details

Defined in Polysemy.Mock

Associated Types

type Item (ActionList r rInitial) 
Instance details

Defined in Polysemy.Mock

type Item (ActionList r rInitial) = ActionList r rInitial

Methods

fromList :: [Item (ActionList r rInitial)] -> ActionList r rInitial #

fromListN :: Int -> [Item (ActionList r rInitial)] -> ActionList r rInitial #

toList :: ActionList r rInitial -> [Item (ActionList r rInitial)] #

type Item (ActionList r rInitial) # 
Instance details

Defined in Polysemy.Mock

type Item (ActionList r rInitial) = ActionList r rInitial

runMockMList :: forall (mockedEffs :: EffectRow) a (effs :: EffectRow) (rInitial :: Type -> Type). (GShow (Union mockedEffs []), MockInterpret mockedEffs effs rInitial) => ActionsU mockedEffs rInitial -> Sem effs a -> MockResult a #

flattenActionList :: forall (r :: EffectRow) (rInitial :: Type -> Type). ActionList r rInitial -> [Action r rInitial] #

runMockM' :: forall (mockedEffs :: EffectRow) a (effs :: EffectRow) (rInitial :: Type -> Type). (GShow (Union mockedEffs []), MockInterpret mockedEffs effs rInitial, effs ~ (mockedEffs ++ '[State (ActionsU mockedEffs rInitial) :: (Type -> Type) -> Type -> Type, Error MockError' :: (Type -> Type) -> Type -> Type]), AllFirstOrder mockedEffs) => ActionList mockedEffs rInitial -> Sem effs a -> IO a #

expectActions :: forall (r :: EffectRow) (rInitial :: Type -> Type). [Action r rInitial] -> ActionList r rInitial #

Use when OverloadedLists are not enabled

(===-) :: forall e (r :: EffectRow) (rInitial :: EffectRow) a. Member e r => e (Sem rInitial) a -> a -> ActionList r (Sem rInitial) #

data LocalReaderZone i #

Instances

Instances details
Show i => Show (LocalReaderZone i) # 
Instance details

Defined in Polysemy.Mock

Eq i => Eq (LocalReaderZone i) # 
Instance details

Defined in Polysemy.Mock

type LocalReader i = Output (LocalReaderZone i) :: k -> Type -> Type #

runReaderMock :: forall i (r :: EffectRow) a. Member (LocalReader i :: (Type -> Type) -> Type -> Type) r => i -> Sem (Reader i ': r) a -> Sem r a #

Run (Reader i) effect while emitting calls to (LocalReaderZone i) effect when local zone is entered and leaved.

localReaderBegin :: forall i (r :: EffectRow) (rInitial :: EffectRow). Member (LocalReader i :: (Type -> Type) -> Type -> Type) r => i -> ActionList r (Sem rInitial) #

localReaderEnd :: forall i (r :: EffectRow) (rInitial :: EffectRow). Member (LocalReader i :: (Type -> Type) -> Type -> Type) r => ActionList r (Sem rInitial) #

localReader :: forall i (r :: EffectRow) (rInitial :: EffectRow). Member (LocalReader i :: (Type -> Type) -> Type -> Type) r => i -> ActionList r (Sem rInitial) -> ActionList r (Sem rInitial) #

localReaderAborted :: forall i (r :: EffectRow) (rInitial :: EffectRow). Member (LocalReader i :: (Type -> Type) -> Type -> Type) r => i -> ActionList r (Sem rInitial) -> ActionList r (Sem rInitial) #

When computation is aborted with exception localReaderEnd is not registered as local computation does not return

inj :: forall e (r :: EffectRow) (rInitial :: EffectRow) a. Member e r => e (Sem rInitial) a -> Union r (Sem rInitial) a #

Lift an effect e into a Union capable of holding it.