test-fixture-0.3.1.0: Test monadic side-effects

Safe HaskellNone
LanguageHaskell2010

Control.Monad.TestFixture.TH

Description

This module provides a Template Haskell function for automatically generating reified typeclass dictionaries for use with Control.Monad.TestFixture. These generated dictionaries can be used with functions like unTestFixture and logTestFixture to quickly implement monadic typeclasses in a way that can be used to “stub out” functionality in unit tests.

The mkFixture function is a Template Haskell code generation tool, which generates three things:

  1. A record type that represents a reified typeclass dictionary (or set of typeclass dictionaries).
  2. A Default instance for the generated record type, which automatically fills all fields with stub implementations that will throw using unimplemented.
  3. Typeclass implementations for all of the provided typeclasses using TestFixture and the generated record type that defer to the implementations provided through the reified dictionary.

In practice, this is used for generate “fixture” types that are used within tests. For example, consider some typeclasses that encode side-effectful monadic operations:

class Monad m => DB m where
  fetchRecord :: DBRecord a => Id a -> m (Either DBError a)
  insertRecord :: DBRecord a => a -> m (Either DBError (Id a))

class Monad m => HTTP m where
  sendRequest :: HTTPRequest -> m (Either HTTPError HTTPResponse)

The typeclasses may have relatively straightforward instances for IO. However, one of the main values of them is that alternative instances may be provided in unit tests, which is what TestFixture provides. Therefore, one might use mkFixture to create some utilities for stubbing these typeclasses out:

mkFixture "Fixture" [''DB, ''HTTP]

This generates code much like the following:

data Fixture m =
  { _fetchRecord :: DBRecord a => Id a -> m (Either DBError a)
  , _insertRecord :: DBRecord a => a -> m (Either DBError (Id a))
  , _sendRequest :: HTTPRequest -> m (Either HTTPError HTTPResponse) }

instance Default (Fixture m) where
  def =
    { _fetchRecord = unimplemented "_fetchRecord"
    , _insertRecord = unimplemented "_insertRecord"
    , _sendRequest = unimplemented "_sendRequest" }

instance Monoid w => DB (TestFixture Fixture w s) where
  fetchRecord r = do
    fn <- asks _fetchRecord
    lift $ fn r
  insertRecord r = do
    fn <- asks _insertRecord
    lift $ fn r

instance Monoid w => HTTP (TestFixture Fixture w s) where
  sendRequest r = do
    fn <- asks _sendRequest
    lift $ fn r

This type can then be used in tandem with Control.Monad.TestFixture to create stubbed typeclass instances and run computations using them.

Synopsis

Documentation

mkFixture :: String -> [Name] -> Q [Dec] Source #

A Template Haskell function that generates a fixture record type with a given name that reifies the set of typeclass dictionaries provided, as described in the module documentation for Control.Monad.TestFixture.TH. For example, the following splice would create a new record type called Fixture with fields and instances for typeclasses called Foo and Bar:

mkFixture "Fixture" [''Foo, ''Bar]

def :: Default a => a #

The default value for this type.