| Safe Haskell | None |
|---|---|
| Language | Haskell2010 |
Control.Monad.Mock.TH
Description
This module provides Template Haskell functions for automatically generating
types representing typeclass methods for use with Control.Monad.Mock. The
resulting datatypes can be used with runMock or
runMockT to mock out functionality in unit tests.
The primary interface to this module is the makeAction function, which
generates an action GADT given a list of mtl-style typeclass constraints. For
example, consider a typeclass that encodes side-effectful monadic operations:
classMonadm => MonadFileSystem m where readFile ::FilePath-> mStringwriteFile ::FilePath->String-> m ()
The typeclass has an obvious, straightforward instance for IO. However, one
of the main value of using a typeclass is that a alternate, pure instance may
be provided for unit tests, which is what MockT provides. Therefore, one
might use makeAction to automatically generate the necessary datatype and
instances:
makeAction"FileSystemAction" [ts| MonadFileSystem |]
This generates three things:
- A
FileSystemActionGADT with constructors that correspond to the methods ofMonadFileSystem. - An
Actioninstance forFileSystemAction. - A
MonadFileSysteminstance for.MockTFileSystemAction m
The generated code effectively looks like this:
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_ _ =NothinginstanceMonadm => MonadFileSystem (MockTFileSystemAction m) where readFile a =mockAction"readFile" (ReadFile a) writeFile a b =mockAction"writeFile" (WriteFile a b)
This can then be used in tandem with runMock to unit-test
a function that interacts with the file system 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":->() ]
- makeAction :: String -> Cxt -> Q [Dec]
- deriveAction :: Name -> Q [Dec]
- ts :: QuasiQuoter
Documentation
makeAction :: String -> Cxt -> Q [Dec] Source #
Given a list of monadic typeclass constraints of kind * -> ,
generate a type with an ConstraintAction instance with constructors that have the
same types as the methods.
classMonadm => MonadFileSystem m where readFile ::FilePath-> mStringwriteFile ::FilePath->String-> m ()makeActionFileSystemAction [ts| MonadFileSystem |]
deriveAction :: Name -> Q [Dec] Source #
Given the name of a type of kind * -> *, generate an Action instance.
data FileSystemAction r where ReadFile ::FilePath-> FileSystemActionStringWriteFile ::FilePath->String-> FileSystemAction () deriving instanceEq(FileSystemAction r) deriving instanceShow(FileSystemAction r)deriveAction''FileSystemAction
ts :: QuasiQuoter Source #
A quasi-quoter like the built-in [t| ... |] quasi-quoter, but produces
a list of types instead of a single type. Each type should be separated by
a comma.
>>>[ts| Bool, (), String |][ConT GHC.Types.Bool,ConT GHC.Tuple.(),ConT GHC.Base.String]>>>[ts| Maybe Int, Monad m |][AppT (ConT GHC.Base.Maybe) (ConT GHC.Types.Int),AppT (ConT GHC.Base.Monad) (VarT m)]