Safe Haskell | None |
---|---|
Language | Haskell2010 |
Synopsis
- class Mock (eff :: Effect) (m :: Type -> Type) where
- runMock :: (Mock eff m, Member (Embed m) r) => Sem (MockImpl eff m ': r) a -> Sem r (MockState eff m, a)
- evalMock :: (Mock eff m, Member (Embed m) r) => Sem (MockImpl eff m ': r) a -> Sem r a
- execMock :: (Mock eff m, Member (Embed m) r) => Sem (MockImpl eff m ': r) a -> Sem r (MockState eff m)
- class MockMany (effs :: EffectRow) m (r :: EffectRow) where
- type family MocksExist (xs :: EffectRow) m :: Constraint where ...
- type family MockChain (xs :: EffectRow) m (r :: EffectRow) :: Constraint where ...
- type family MockImpls (xs :: EffectRow) m where ...
- type family (xs :: [a]) :++: r :: [a] where ...
Documentation
class Mock (eff :: Effect) (m :: Type -> Type) where Source #
The Mock
class can be instantiated for an effect eff
and a functor m
.
Here eff
represents the effect being mocked and m
is the side-effect the mock implementation uses to keep track of MockState
.
To take the classic example of Teletype, we can mock Teletype using the Identity
functor like this:
Consder a Teletype effect defined as:
data Teletype (m :: * -> *) a where Read :: Teletype m String Write :: String -> Teletype m () makeSem ''Teletype
A simple Mock
instance which always reads Mock when Read action is called and records all Write actions.
instance Mock Teletype Identity where data MockImpl Teletype Identity m a where MockRead :: MockImpl Teletype Identity m String MockWrite :: String -> MockImpl Teletype Identity m String MockWriteCalls :: MockImpl Teletype Identity m [String] data MockState Teletype Identity = MockState {writes :: [String]} initialMockState = MockState [] mock = interpret $ case Read -> send(MockImpl Teletype Identity) MockRead Write s -> send
(MockImpl Teletype Identity) $ MockWrite s mockToState = reinterpretH $ case MockRead -> pureT Mock MockWrite s -> do (MockState w) <- get(MockState Teletype Identity) put $ MockState (w ++ [s]) pureT () MockWriteCalls -> do (MockState w) <- get
(MockState Teletype Identity) pureT w
If we have a program which uses the Teletype
effect like this:
program :: Member Teletype r => Sem r () program = do name <- read write $ "Hello " <> name
This program can be tested using hspec and our mock like this:
spec :: Spec spec = describe "program" $ do it "writes hello message" $ do let MockState w = runIdentity . runM . execMock $ mockTeletype
Identity program wshouldBe
["Hello Mock"]
One can write such tests without even using this class. This class and the library is more useful when used with the template haskell generator for the mocks. The generator will produce a different mock than written above and it can be used like this:
genMock ''Teletype mockWriteReturns :: (String -> m ()) -> Sem '[MockImpl Teletype m, Embed m] () mockWriteReturns = send . MockWriteReturns mockReadReturns :: m String -> Sem '[MockImpl Teletype m, Embed m] () mockReadReturns = send . MockReadReturns mockReadCalls :: forall m. Sem '[MockImpl Teletype m, Embed m] [()] mockReadCalls = send(MockImpl Teletype m) MockReadCalls mockWriteCalls :: forall m. Sem '[MockImpl Teletype m, Embed m] [String] mockWriteCalls = send
(MockImpl Teletype m) MockWriteCalls spec :: Spec spec = describe "program" $ do it "writes hello message" $ runMIO . evalMock do mockReadReturns $ pure Mock mockWriteReturns $ pure () mock
Teletype @IO program w <- mockWriteCalls embed $ wshouldBe
["Hello Mock"]
data MockImpl eff m :: Effect Source #
The effect which eff
should be interpreted to
The type keep information about the mock. For example, it can be used to keep record of actions called on the effect and what to return on each call
initialMockState :: MockState eff m Source #
Can be used to set default return values and initialize other attributes of the MockState
mock :: Member (MockImpl eff m) r => Sem (eff ': r) a -> Sem r a Source #
Swaps real effect for the mock one.
mockToState :: Member (Embed m) r => Sem (MockImpl eff m ': r) a -> Sem (State (MockState eff m) ': r) a Source #
Update mock state for every action on the mock
runMock :: (Mock eff m, Member (Embed m) r) => Sem (MockImpl eff m ': r) a -> Sem r (MockState eff m, a) Source #
Run a mocked effect to get MockState
and the effect value
execMock :: (Mock eff m, Member (Embed m) r) => Sem (MockImpl eff m ': r) a -> Sem r (MockState eff m) Source #
class MockMany (effs :: EffectRow) m (r :: EffectRow) where Source #
Mock many effects
mockMany :: MockChain effs m r => Sem (effs :++: r) a -> Sem r a Source #
Give a computation using a list of effects, transform it into a computation using Mocks of those effects
evalMocks :: (MocksExist effs m, Member (Embed m) r) => Sem (MockImpls effs m :++: r) a -> Sem r a Source #
Given a computation using Mock effects, evaluate the computation
type family MocksExist (xs :: EffectRow) m :: Constraint where ... Source #
Constraint to assert existence of mocks for each effect in xs
for state effect m
MocksExist '[] _ = () | |
MocksExist (x ': xs) m = (Mock x m, MocksExist xs m) |