| Safe Haskell | None |
|---|---|
| Language | Haskell2010 |
Control.Monad.Mock
Description
This module provides a monad transformer that helps create “mocks” of
mtl-style typeclasses, intended for use in unit tests. A mock can be
executed by providing a sequence of expected monadic calls and their results,
and the mock will verify that the computation conforms to the expectation.
For example, imagine a MonadFileSystem typeclass, which describes a class of
monads that may perform filesystem operations:
classMonadm => MonadFileSystem m where readFile ::FilePath-> mStringwriteFile ::FilePath->String-> m ()
Using MockT, it’s possible to test computations that use MonadFileSystem
in a completely pure way:
copyFile :: MonadFileSystem m =>FilePath->FilePath-> m () copyFile a b = do x <- readFile a writeFile b x spec = describe "copyFile"$it "reads a file and writes its contents to another file"$evaluate$copyFile "foo.txt" "bar.txt"&runMock[ ReadFile "foo.txt":->"contents" , WriteFile "bar.txt" "contents":->() ]
To make the above code work, all you have to do is write a small GADT that
represents typeclass method calls and implement the Action typeclass:
data FileSystemAction r where ReadFile ::FilePath-> FileSystemActionStringWriteFile ::FilePath->String-> FileSystemAction () deriving instanceEq(FileSystemAction r) deriving instanceShow(FileSystemAction r) instanceActionFileSystemAction whereeqAction(ReadFile a) (ReadFile b) = if a==b thenJustReflelseNothingeqAction(WriteFile a b) (WriteFile c d) = if a==c && b==d thenJustReflelseNothingeqAction_ _ =Nothing
Then, just write a MonadFileSystem instance for MockT:
instanceMonadm => MonadFileSystem (MockTFileSystemAction m) where readFile a =mockAction"readFile" (ReadFile a) writeFile a b =mockAction"writeFile" (WriteFile a b)
For some Template Haskell functions that eliminate the need to write the above
boilerplate, look at makeAction from
Control.Monad.Mock.TH.
- data MockT f m a
- type Mock f = MockT f Identity
- runMockT :: forall f m a. (Action f, Monad m) => [WithResult f] -> MockT f m a -> m a
- runMock :: forall f a. Action f => [WithResult f] -> Mock f a -> a
- mockAction :: (Action f, Monad m) => String -> f r -> MockT f m r
- class Action f where
- data WithResult f where
- (:->) :: f r -> r -> WithResult f
The MockT monad transformer
A monad transformer for creating mock instances of typeclasses. In , MockT
f m af should be an Action, which should be a GADT that represents a
reified version of typeclass method calls.
Instances
| MonadBase b m => MonadBase b (MockT f m) Source # | |
| MonadBaseControl b m => MonadBaseControl b (MockT f m) Source # | |
| MonadError e m => MonadError e (MockT f m) Source # | |
| MonadReader r m => MonadReader r (MockT f m) Source # | |
| MonadState s m => MonadState s (MockT f m) Source # | |
| MonadWriter w m => MonadWriter w (MockT f m) Source # | |
| MonadTrans (MockT f) Source # | |
| MonadTransControl (MockT f) Source # | |
| Monad m => Monad (MockT f m) Source # | |
| Functor m => Functor (MockT f m) Source # | |
| Monad m => Applicative (MockT f m) Source # | |
| MonadIO m => MonadIO (MockT f m) Source # | |
| MonadThrow m => MonadThrow (MockT f m) Source # | |
| MonadCatch m => MonadCatch (MockT f m) Source # | |
| MonadMask m => MonadMask (MockT f m) Source # | |
| MonadCont m => MonadCont (MockT f m) Source # | |
| type StT (MockT f) a Source # | |
| type StM (MockT f m) a Source # | |
runMockT :: forall f m a. (Action f, Monad m) => [WithResult f] -> MockT f m a -> m a Source #
Runs a MockT computation given an expected list of calls and results. If
any method is called during the extent of the computation that is unexpected,
an exception will be thrown. Additionally, if the computation terminates
without making all of the expected calls, an exception is raised.
mockAction :: (Action f, Monad m) => String -> f r -> MockT f m r Source #
Logs a method call within a mock.
Actions and actions with results
A class of types that represent typeclass method calls. The type must be of
kind * -> *, and its type parameter should represent type of the method’s
return type.
Minimal complete definition
Methods
eqAction :: f a -> f b -> Maybe (a :~: b) Source #
Compares two Actions for equality, and produces a witness of type
equality if the two actions are, in fact, equal.
showAction :: f a -> String Source #
Converts an Action to a String, which will be used when displaying
mock failures.
The default implementation of showAction just uses Show, assuming there
is an instance forall a. . This instance can be derived by
GHC using a standalone Show (f a)deriving clause.
showAction :: ForallF Show f => f a -> String Source #
Converts an Action to a String, which will be used when displaying
mock failures.
The default implementation of showAction just uses Show, assuming there
is an instance forall a. . This instance can be derived by
GHC using a standalone Show (f a)deriving clause.
data WithResult f where Source #
Represents both an expected call (an Action) and its expected result.
Constructors
| (:->) :: f r -> r -> WithResult f |