Safe Haskell | None |
---|---|
Language | GHC2021 |
Synopsis
- pattern (:->) :: forall {k} f (m :: k) a. () => f m a -> a -> DSumI (f m)
- data Action (r :: EffectRow) (rInitial :: Type -> Type)
- = ExpectRequest (DSumI (Union r rInitial))
- | UnsafeForceReturn Any
- type DSumI (f :: Type -> Type) = DSum f Identity
- forgetM :: forall f (m :: Type -> Type) a. f m a -> f [] a
- type ActionsU (r :: EffectRow) (rInitial :: Type -> Type) = [Action r rInitial]
- newtype MockError' = MockErrorMessage Text
- data MockResult a
- 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
- type family AllFirstOrder (xs :: EffectRow) where ...
- 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)
- = SingleAction (Action r rInitial)
- | MultipleActions [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
- (===-) :: forall e (r :: EffectRow) (rInitial :: EffectRow) a. Member e r => e (Sem rInitial) a -> a -> ActionList r (Sem rInitial)
- data LocalReaderZone i
- 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
- 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)
- inj :: forall e (r :: EffectRow) (rInitial :: EffectRow) a. Member e r => e (Sem rInitial) a -> Union r (Sem rInitial) a
Documentation
data Action (r :: EffectRow) (rInitial :: Type -> Type) #
ExpectRequest (DSumI (Union r rInitial)) | |
UnsafeForceReturn Any | Escape hatch, use with caution, expect segfaults |
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
newtype MockError' #
Instances
IsString MockError' # | |
Defined in Polysemy.Mock fromString :: String -> MockError' # | |
Exception MockError' # | |
Defined in Polysemy.Mock toException :: MockError' -> SomeException # fromException :: SomeException -> Maybe MockError' # displayException :: MockError' -> String # | |
Show MockError' # | |
Defined in Polysemy.Mock showsPrec :: Int -> MockError' -> ShowS # show :: MockError' -> String # showList :: [MockError'] -> ShowS # | |
Eq MockError' # | |
Defined in Polysemy.Mock (==) :: MockError' -> MockError' -> Bool # (/=) :: MockError' -> MockError' -> Bool # | |
Member r effs => MockInterpret effs '[State (ActionsU effs rInitial) :: (Type -> Type) -> Type -> Type, Error MockError' :: (Type -> Type) -> Type -> Type] rInitial # | |
data MockResult a #
Instances
Show a => Show (MockResult a) # | |
Defined in Polysemy.Mock showsPrec :: Int -> MockResult a -> ShowS # show :: MockResult a -> String # showList :: [MockResult a] -> ShowS # | |
Eq a => Eq (MockResult a) # | |
Defined in Polysemy.Mock (==) :: 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 #
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 #
interpretMock :: Sem r a -> Sem '[State (ActionsU effs rInitial) :: (Type -> Type) -> Type -> Type, Error MockError' :: (Type -> Type) -> Type -> Type] a #
Instances
Member r effs => MockInterpret effs '[State (ActionsU effs rInitial) :: (Type -> Type) -> Type -> Type, Error MockError' :: (Type -> Type) -> Type -> Type] rInitial # | |
(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 # | |
type family AllFirstOrder (xs :: EffectRow) where ... #
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
SingleAction (Action r rInitial) | |
MultipleActions [ActionList r rInitial] |
Instances
Monoid (ActionList r rInitial) # | |||||
Defined in Polysemy.Mock 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) # | |||||
Defined in Polysemy.Mock (<>) :: 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) # | |||||
Defined in Polysemy.Mock
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) # | |||||
Defined in Polysemy.Mock |
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
Show i => Show (LocalReaderZone i) # | |
Defined in Polysemy.Mock showsPrec :: Int -> LocalReaderZone i -> ShowS # show :: LocalReaderZone i -> String # showList :: [LocalReaderZone i] -> ShowS # | |
Eq i => Eq (LocalReaderZone i) # | |
Defined in Polysemy.Mock (==) :: LocalReaderZone i -> LocalReaderZone i -> Bool # (/=) :: LocalReaderZone i -> LocalReaderZone i -> Bool # |
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