polysemy-mocks-0.1.0.0: Mocking framework for polysemy effects
Safe HaskellNone
LanguageHaskell2010

Test.Polysemy.Mock

Synopsis

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 $
            mock Teletype Identity program
    w shouldBe ["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" $ runM IO . evalMock do
    mockReadReturns $ pure Mock
    mockWriteReturns $ pure ()
    mock Teletype @IO program
    w <- mockWriteCalls
    embed $ w shouldBe ["Hello Mock"]

Associated Types

data MockImpl eff m :: Effect Source #

The effect which eff should be interpreted to

data MockState eff m Source #

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

Methods

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

evalMock :: (Mock eff m, Member (Embed m) r) => Sem (MockImpl eff m ': r) a -> Sem r a Source #

Like runMock but discards the MockState

execMock :: (Mock eff m, Member (Embed m) r) => Sem (MockImpl eff m ': r) a -> Sem r (MockState eff m) Source #

Like runMock but only returns the MockState

class MockMany (effs :: EffectRow) m (r :: EffectRow) where Source #

Mock many effects

Methods

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

Instances

Instances details
MockMany ('[] :: [Effect]) r m Source # 
Instance details

Defined in Test.Polysemy.Mock

Methods

mockMany :: MockChain '[] r m => Sem ('[] :++: m) a -> Sem m a Source #

evalMocks :: (MocksExist '[] r, Member (Embed r) m) => Sem (MockImpls '[] r :++: m) a -> Sem m a Source #

(MockMany effs m r, Member (Embed m) (MockImpls effs m :++: r)) => MockMany (eff ': effs) m r Source # 
Instance details

Defined in Test.Polysemy.Mock

Methods

mockMany :: MockChain (eff ': effs) m r => Sem ((eff ': effs) :++: r) a -> Sem r a Source #

evalMocks :: (MocksExist (eff ': effs) m, Member (Embed m) r) => Sem (MockImpls (eff ': effs) m :++: r) a -> Sem r a Source #

type family MocksExist (xs :: EffectRow) m :: Constraint where ... Source #

Constraint to assert existence of mocks for each effect in xs for state effect m

Equations

MocksExist '[] _ = () 
MocksExist (x ': xs) m = (Mock x m, MocksExist xs m) 

type family MockChain (xs :: EffectRow) m (r :: EffectRow) :: Constraint where ... Source #

Equations

MockChain '[] r m = () 
MockChain (x ': xs) m r = (Mock x m, Member (MockImpl x m) (xs :++: r), MockChain xs m r) 

type family MockImpls (xs :: EffectRow) m where ... Source #

Equations

MockImpls '[] _ = '[] 
MockImpls (x ': xs) m = MockImpl x m ': MockImpls xs m 

type family (xs :: [a]) :++: r :: [a] where ... Source #

Append type level lists

Equations

'[] :++: r = r 
(x ': xs) :++: r = x ': (xs :++: r)