monad-mock-0.1.1.1: A monad transformer for mocking mtl-style typeclasses

Safe HaskellNone
LanguageHaskell2010

Control.Monad.Mock

Contents

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:

class Monad m => MonadFileSystem m where
  readFile :: FilePath -> m String
  writeFile :: 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 -> FileSystemAction String
  WriteFile :: FilePath -> String -> FileSystemAction ()
deriving instance Eq (FileSystemAction r)
deriving instance Show (FileSystemAction r)

instance Action FileSystemAction where
  eqAction (ReadFile a) (ReadFile b)
    = if a == b then Just Refl else Nothing
  eqAction (WriteFile a b) (WriteFile c d)
    = if a == c && b == d then Just Refl else Nothing
  eqAction _ _ = Nothing

Then, just write a MonadFileSystem instance for MockT:

instance Monad m => MonadFileSystem (MockT FileSystemAction 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.

Synopsis

The MockT monad transformer

data MockT f m a Source #

A monad transformer for creating mock instances of typeclasses. In MockT f m a, f 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 # 

Methods

liftBase :: b α -> MockT f m α #

MonadBaseControl b m => MonadBaseControl b (MockT f m) Source # 

Associated Types

type StM (MockT f m :: * -> *) a :: * #

Methods

liftBaseWith :: (RunInBase (MockT f m) b -> b a) -> MockT f m a #

restoreM :: StM (MockT f m) a -> MockT f m a #

MonadError e m => MonadError e (MockT f m) Source # 

Methods

throwError :: e -> MockT f m a #

catchError :: MockT f m a -> (e -> MockT f m a) -> MockT f m a #

MonadReader r m => MonadReader r (MockT f m) Source # 

Methods

ask :: MockT f m r #

local :: (r -> r) -> MockT f m a -> MockT f m a #

reader :: (r -> a) -> MockT f m a #

MonadState s m => MonadState s (MockT f m) Source # 

Methods

get :: MockT f m s #

put :: s -> MockT f m () #

state :: (s -> (a, s)) -> MockT f m a #

MonadWriter w m => MonadWriter w (MockT f m) Source # 

Methods

writer :: (a, w) -> MockT f m a #

tell :: w -> MockT f m () #

listen :: MockT f m a -> MockT f m (a, w) #

pass :: MockT f m (a, w -> w) -> MockT f m a #

MonadTrans (MockT f) Source # 

Methods

lift :: Monad m => m a -> MockT f m a #

MonadTransControl (MockT f) Source # 

Associated Types

type StT (MockT f :: (* -> *) -> * -> *) a :: * #

Methods

liftWith :: Monad m => (Run (MockT f) -> m a) -> MockT f m a #

restoreT :: Monad m => m (StT (MockT f) a) -> MockT f m a #

Monad m => Monad (MockT f m) Source # 

Methods

(>>=) :: MockT f m a -> (a -> MockT f m b) -> MockT f m b #

(>>) :: MockT f m a -> MockT f m b -> MockT f m b #

return :: a -> MockT f m a #

fail :: String -> MockT f m a #

Functor m => Functor (MockT f m) Source # 

Methods

fmap :: (a -> b) -> MockT f m a -> MockT f m b #

(<$) :: a -> MockT f m b -> MockT f m a #

Monad m => Applicative (MockT f m) Source # 

Methods

pure :: a -> MockT f m a #

(<*>) :: MockT f m (a -> b) -> MockT f m a -> MockT f m b #

(*>) :: MockT f m a -> MockT f m b -> MockT f m b #

(<*) :: MockT f m a -> MockT f m b -> MockT f m a #

MonadIO m => MonadIO (MockT f m) Source # 

Methods

liftIO :: IO a -> MockT f m a #

MonadThrow m => MonadThrow (MockT f m) Source # 

Methods

throwM :: Exception e => e -> MockT f m a #

MonadCatch m => MonadCatch (MockT f m) Source # 

Methods

catch :: Exception e => MockT f m a -> (e -> MockT f m a) -> MockT f m a #

MonadMask m => MonadMask (MockT f m) Source # 

Methods

mask :: ((forall a. MockT f m a -> MockT f m a) -> MockT f m b) -> MockT f m b #

uninterruptibleMask :: ((forall a. MockT f m a -> MockT f m a) -> MockT f m b) -> MockT f m b #

MonadCont m => MonadCont (MockT f m) Source # 

Methods

callCC :: ((a -> MockT f m b) -> MockT f m a) -> MockT f m a #

type StT (MockT f) a Source # 
type StT (MockT f) a = StT (StateT [WithResult f]) a
type StM (MockT f m) a Source # 
type StM (MockT f m) a = ComposeSt (MockT f) m a

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.

runMock :: forall f a. Action f => [WithResult f] -> Mock f a -> a Source #

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

class Action f where Source #

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

eqAction

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. Show (f a). This instance can be derived by GHC using a standalone 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. Show (f a). This instance can be derived by GHC using a standalone deriving clause.

data WithResult f where Source #

Represents both an expected call (an Action) and its expected result.

Constructors

(:->) :: f r -> r -> WithResult f