TLT-0.5.0.0: Testing in monads and transformers without explicit specs
Copyright(c) John Maraist 2022
LicenseGPL3
Maintainerhaskell-tlt@maraist.org
Stabilityexperimental
PortabilityPOSIX
Safe HaskellSafe-Inferred
LanguageHaskell2010

Test.TLT

Description

TLT is a small unit test system oriented towards examining intermediate results of computations in monad transformers. It is intended to be lightweight for the programmer, and does not require tests to be specified in some sort of formal list of tests. Rather, tests are simply commands in a monad stack which includes the transformer layer Test.TLT.

This module is a re-exporter for the various Test.TLT.* modules which define distinct portions of the TLT system. These exports are oriented towards the simple use of TLT as a test framework. When using TLT more programmatically, such as when integrating TLT into another test framework, it may be necessary to import the more internally-oriented functions of the individual modules.

Synopsis

Introduction and basic use

The basic use of TLT is a call to tlt in the main function of a program, followed by a monadic computation which asserts various properties about the results it calculates. For example:

main :: IO ()
main = tlt $ runExceptT test
  "True passes" ~::- True
  "1 and 1 make 2" ~: 2 @== return (1 + 1)

tlt :: MonadIO m => TLT m r -> m () Source #

Execute the tests specified in a TLT monad, and report the results as text output.

When using TLT from some other package (as opposed to using TLT itself as your test framework, and wishing to see its human-oriented output directly), consider using runTLT instead.

Writing tests

The two tests in the example above have the common form of one individual TLT test:

 LABLE TEST-OPERATOR EXPRESSION

There are three TEST-OPERATORs, corresponding to three different forms of EXPRESSION:

OPERATOREXPRESSION
~: The expression is an assertion written with one of the several operators below.
~:: The expression is a monadic computation returning a boolean value, where True corresponds to the test passing.
~::- The expression is a simple boolean value, where again True corresponds to the test passing.

The last two of these test-introducung operations show a pattern that recrus throughout TLT: where two operators differ only where one has a trailing hyphen, the version without the hyphen refers to a monadic computation, and the version with the hyphen refers to a pure expression.

There are a number of special forms of test, and commands for setting session options.

  • The tltFail function introduces a test which always fails. This function is useful in pattern matches, for wholly unacceptable combinations.
  • The reportAllTestResults function controls whether TLT (when invoked with tlt as described above) should display only tests which fails, or should display all passing tests as well. The former is the default, since the latter can be quite verbose.
  • The setExitAfterFailDisplay function directs tlt to exit after displaying a set of test results which include at * least one failing test. The idea of this default is that a * test suite can be broken into parts when it makes sense to * run the latter parts only when the former parts all pass.
  • The inGroup function groups several tests together as a single group. The tlt function displays the tests of a group indented, which helps to visually group related tests together.

All of these test and option forms are formally documented below.

Writing standard assertions

There are a number of pre-defined forms of assertion imported automatically from Test.TLT. Note that more operators are in pairs, with one comparison for monadic results, and one for pure values.

@==, @==-Asserts equality of two Eq values.
@/=, @/=- Asserts inequality of two Eq values.
@<, @<- Asserts a less-than relation between two Ord values.
@>, @>- Asserts a greater-than relation between twoOrd values.
@<=, @<=- Asserts a less-than-or-equal-to relation between two Ord values.
@>=, @>=- Asserts a greater-than-or-equal-to relation between two Ord values.
empty, emptyP Asserts the emptiness of a traversable structure.
nonempty, nonemptyP Asserts the non-emptiness of a traversable structure.
nothing, nothingP Asserts that a Maybe value is Nothing.

The predefined operators, along with functions for defining new Assertion operators, are documented more formally below.

Dealing with exceptions

TLT's interaction with exceptions thrown from the Except monad or from an ExceptT transformer layer is subtle. Because TLT does not have a specification of tests separate from the tests' execution, TLT will notice test failures only it actually runs them. Tests which may be viewed by the human programmer as implicitly failing because a thrown exception prevented them from running are not recorded or reported as failures. TLT provides three functions for checking for thrown exceptions. The first argument of each is a TLT monad of tests which has been declared to take an ExceptT layer.

noUncaught and noUncaught_
Both assert that no uncaught exceptions should be thrown from its argument computation, and fails if one is. The noUncaught_ function accepts any type of exception, but cannot report any details about them except that something was thrown. The noUncaught function demands that the exception type be of class Show, and does report exception details in the case of failure.
uncaught
Asserts that an uncaught exception should be thrown from its argument computation, and fails if none are thrown.
uncaughtWith
Asserts that an uncaught exception should be thrown from its argument computation, fails if none are thrown, and passes the thrown exception to its second argument for further inspection.

The declaration that a monadic value includes an ExceptT layer to be checked is made by declaring instances of the MonadTLTExcept class. The use of these exception-checking functions requires that the TLT transformer layer be contained within the ExceptT layer. The generated documentation for this class and its predefined instances, as well as the above functions, are all below.

The TLT transformer

data TLT (m :: * -> *) r Source #

Monad transformer for TLT tests. This layer stores the results from tests as they are executed.

Instances

Instances details
MonadTrans TLT Source # 
Instance details

Defined in Test.TLT.Class

Methods

lift :: Monad m => m a -> TLT m a #

Monad m => Applicative (TLT m) Source # 
Instance details

Defined in Test.TLT.Class

Methods

pure :: a -> TLT m a #

(<*>) :: TLT m (a -> b) -> TLT m a -> TLT m b #

liftA2 :: (a -> b -> c) -> TLT m a -> TLT m b -> TLT m c #

(*>) :: TLT m a -> TLT m b -> TLT m b #

(<*) :: TLT m a -> TLT m b -> TLT m a #

Functor m => Functor (TLT m) Source # 
Instance details

Defined in Test.TLT.Class

Methods

fmap :: (a -> b) -> TLT m a -> TLT m b #

(<$) :: a -> TLT m b -> TLT m a #

Monad m => Monad (TLT m) Source # 
Instance details

Defined in Test.TLT.Class

Methods

(>>=) :: TLT m a -> (a -> TLT m b) -> TLT m b #

(>>) :: TLT m a -> TLT m b -> TLT m b #

return :: a -> TLT m a #

Monad m => MonadTLT (TLT m) m Source # 
Instance details

Defined in Test.TLT.Class

Methods

liftTLT :: TLT m a -> TLT m a Source #

class (Monad m, Monad n) => MonadTLT m n | m -> n where Source #

Extending TLT operations across other monad transformers. For easiest and most flexible testing, declare the monad transformers of your application as instances of this class.

Methods

liftTLT :: TLT n a -> m a Source #

Lift TLT operations within a monad transformer stack. Note that with enough transformer types included in this class, the liftTLT function should usually be unnecessary: the commands in this module which actually configure testing, or specify a test, already liftTLT their own result. So they will all act as top-level transformers in MonadTLT.

Instances

Instances details
Monad m => MonadTLT (TLT m) m Source # 
Instance details

Defined in Test.TLT.Class

Methods

liftTLT :: TLT m a -> TLT m a Source #

MonadTLT m n => MonadTLT (ResourceT m) n Source # 
Instance details

Defined in Test.TLT.Class

Methods

liftTLT :: TLT n a -> ResourceT m a Source #

MonadTLT m n => MonadTLT (MaybeT m) n Source # 
Instance details

Defined in Test.TLT.Class

Methods

liftTLT :: TLT n a -> MaybeT m a Source #

MonadTLT m n => MonadTLT (STT s m) n Source # 
Instance details

Defined in Test.TLT.Class

Methods

liftTLT :: TLT n a -> STT s m a Source #

(MonadTLT m n, Functor f) => MonadTLT (FreeT f m) n Source # 
Instance details

Defined in Test.TLT.Class

Methods

liftTLT :: TLT n a -> FreeT f m a Source #

MonadTLT m n => MonadTLT (ExceptT e m) n Source # 
Instance details

Defined in Test.TLT.Class

Methods

liftTLT :: TLT n a -> ExceptT e m a Source #

MonadTLT m n => MonadTLT (IdentityT m) n Source # 
Instance details

Defined in Test.TLT.Class

Methods

liftTLT :: TLT n a -> IdentityT m a Source #

MonadTLT m n => MonadTLT (ReaderT r m) n Source # 
Instance details

Defined in Test.TLT.Class

Methods

liftTLT :: TLT n a -> ReaderT r m a Source #

MonadTLT m n => MonadTLT (StateT s m) n Source # 
Instance details

Defined in Test.TLT.Class

Methods

liftTLT :: TLT n a -> StateT s m a Source #

MonadTLT m n => MonadTLT (StateT s m) n Source # 
Instance details

Defined in Test.TLT.Class

Methods

liftTLT :: TLT n a -> StateT s m a Source #

(MonadTLT m n, Monoid w) => MonadTLT (WriterT w m) n Source # 
Instance details

Defined in Test.TLT.Class

Methods

liftTLT :: TLT n a -> WriterT w m a Source #

(MonadTLT m n, Monoid w) => MonadTLT (WriterT w m) n Source # 
Instance details

Defined in Test.TLT.Class

Methods

liftTLT :: TLT n a -> WriterT w m a Source #

Session options

reportAllTestResults :: MonadTLT m n => Bool -> m () Source #

This function controls whether tlt will report only tests which fail, suppressing any display of tests which pass, or else report the results of all tests. The default is the former: the idea is that no news should be good news, with the programmer bothered only with problems which need fixing.

setExitAfterFailDisplay :: MonadTLT m n => Bool -> m () Source #

This function controls whether the main tlt executable should exit after displaying test results which include at least one failing test. By default, it will exit in this situation. The idea is that a test suite can be broken into parts when it makes sense to run the latter parts only when the former parts all pass.

Tests

(~:) :: MonadTLT m n => String -> Assertion m -> m () infix 0 Source #

Label and perform a test of an Assertion.

Example
test :: Monad m => TLT m ()
test = do
  "2 is 2 as result" ~: 2 @== return 2    -- This test passes.
  "2 not 3" ~: 2 @/=- 3                   -- This test fails.

(~::) :: MonadTLT m n => String -> m Bool -> m () infix 0 Source #

Label and perform a test of a boolean value returned by a computation in the wrapped monad m.

Example
test :: Monad m => TLT m ()
test = do
  "True passes" ~::- True               -- This test passes.
  "2 is 2 as single Bool" ~::- 2 == 2   -- This test passes.
  "2 is 3!?" ~::- 2 == 2                -- This test fails.

(~::-) :: MonadTLT m n => String -> Bool -> m () infix 0 Source #

Label and perform a test of a (pure) boolean value.

Example
test :: Monad m => TLT m ()
test = do
  "True passes" ~::- return True                 -- This test passes.
  "2 is 2 as single Bool" ~::- return (2 == 2)   -- This test passes.
  "2 is 3!?" ~::- myFn 4 "Hammer"                -- Passes if myFn (which
                                                 -- must be monadic)
                                                 -- returns True.

tltFail :: MonadTLT m n => String -> String -> m () Source #

Report a failure. Useful in pattern-matching cases which are entirely not expected.

inGroup :: MonadTLT m n => String -> m a -> m a Source #

Organize the tests in the given subcomputation as a separate group within the test results we will report.

Assertions

type Assertion m = m [TestFail] Source #

An assertion is a computation (typically in the monad wrapped by TLT) which returns a list of zero of more reasons for the failure of the assertion. A successful computation returns an empty list: no reasons for failure, hence success.

About the values of pure expressions of Eq- and Ord-type

(@==-) :: (Monad m, Eq a, Show a) => a -> a -> Assertion m infix 1 Source #

Assert that two values are equal. This assertion takes an expected and an actual value; see (@==) to compare the result of a monadic computation to an expected value.

Examples
test :: Monad m => TLT m ()
test = do
  "Make sure that 2 is still equal to itself" ~: 2 @==- 2
  "Make sure that there are four lights" ~: 4 @==- length lights

(@/=-) :: (Monad m, Eq a, Show a) => a -> a -> Assertion m infix 1 Source #

Assert that two values are not equal. This assertion takes an expected and an actual value; see (@/=) to compare the result of a monadic computation to an expected value.

(@<-) :: (Monad m, Ord a, Show a) => a -> a -> Assertion m infix 1 Source #

Assert that a given boundary is strictly less than some value. This assertion takes an expected and an actual value; see (@<) to compare the result of a monadic computation to an expected value.

(@>-) :: (Monad m, Ord a, Show a) => a -> a -> Assertion m infix 1 Source #

Assert that a given boundary is strictly less than some value. This assertion takes an expected and an actual value; see (@>) to compare the result of a monadic computation to an expected value.

(@<=-) :: (Monad m, Ord a, Show a) => a -> a -> Assertion m infix 1 Source #

Assert that a given boundary is strictly less than some value. This assertion takes an expected and an actual value; see (@<=) to compare the result of a monadic computation to an expected value.

(@>=-) :: (Monad m, Ord a, Show a) => a -> a -> Assertion m infix 1 Source #

Assert that a given boundary is strictly less than some value. This assertion takes an expected and an actual value; see (@>=) to compare the result of a monadic computation to an expected value.

About monadic computations returing Eqs and Ords

(@==) :: (Monad m, Eq a, Show a) => a -> m a -> Assertion m infix 1 Source #

Assert that a calculated value is as expected. This assertion compare the result of a monadic computation to an expected value; see (@==-) to compare an actual value to the expected value.

Examples
test :: Monad m => TLT m ()
test = do
  "Make sure that 2 is still equal to itself" ~: 2 @== return 2
  "Make sure that there are four lights" ~: 4 @== countLights
                                            -- where countLights :: m Int

(@/=) :: (Monad m, Eq a, Show a) => a -> m a -> Assertion m infix 1 Source #

Assert that a calculated value differs from some known value. This assertion compares the result of a monadic computation to an expected value; see (@/=-) to compare an actual value to the expected value.

(@<) :: (Monad m, Ord a, Show a) => a -> m a -> Assertion m infix 1 Source #

Assert that a given, constant boundary is strictly less than some calculated value. This assertion compares the result of a /monadic computation/ to an expected value; see (@<-) to compare an actual value to the expected value.

(@>) :: (Monad m, Ord a, Show a) => a -> m a -> Assertion m infix 1 Source #

Assert that a given, constant boundary is strictly less than some calculated value. This assertion compares the result of a /monadic computation/ to an expected value; see (@>-) to compare an actual value to the expected value.

(@<=) :: (Monad m, Ord a, Show a) => a -> m a -> Assertion m infix 1 Source #

Assert that a given, constant boundary is strictly less than some calculated value. This assertion compares the result of a /monadic computation/ to an expected value; see (@<=-) to compare an actual value to the expected value.

(@>=) :: (Monad m, Ord a, Show a) => a -> m a -> Assertion m infix 1 Source #

Assert that a given, constant boundary is strictly less than some calculated value. This assertion compares the result of a /monadic computation/ to an expected value; see (@>=-) to compare an actual value to the expected value.

About list values

empty :: (Monad m, Traversable t) => m (t a) -> Assertion m Source #

Assert that a traversable structure (such as a list) returned from a computation is empty.

nonempty :: (Monad m, Traversable t) => m (t a) -> Assertion m Source #

Assert that a traversable structure (such as a list) returned from a computation is non-empty.

emptyP :: (Monad m, Traversable t) => t a -> Assertion m Source #

Assert that a pure traversable structure (such as a list) is empty.

nonemptyP :: (Monad m, Traversable t) => t a -> Assertion m Source #

Assert that a pure traversable structure (such as a list) is nonempty.

About Maybe values

nothing :: Monad m => m (Maybe a) -> Assertion m Source #

Assert that a Maybe result of a computation is Nothing.

nothingP :: Monad m => Maybe a -> Assertion m Source #

Assert that a Maybe value is Nothing.

Unconditional assertions

assertFailed :: Monad m => String -> Assertion m Source #

This assertion always fails with the given message.

assertSuccess :: Monad m => Assertion m Source #

This assertion always succeeds.

Building new assertions

Unary assertions

liftAssertionPure :: Monad m => (a -> Bool) -> (a -> String) -> a -> Assertion m Source #

Transform a unary function on a value (plus a generator of a failure message) into a unary function returning an Assertion for a pure given actual value.

Example

The TLT assertion emptyP (defined in Standard) is built from the Traversable predicate null

emptyP :: (Monad m, Traversable t) => t a -> Assertion m
emptyP = liftAssertionPure null
           (\ _ -> "Expected empty structure but got non-empty")

assertionPtoM :: Monad m => (a -> Assertion m) -> m a -> Assertion m Source #

Given an Assertion for a pure (actual) value, lift it to an Assertion expecting the value to be returned from a computation.

Example

The TLT assertion empty (defined in Standard) on monadic computations returning lists is defined in terms of the corresponging assertion on pure list-valued expressions.

empty :: (Monad m, Traversable t) => m (t a) -> Assertion m
empty = assertionPtoM emptyP

liftAssertionM :: Monad m => (a -> Bool) -> (a -> String) -> m a -> Assertion m Source #

Transform a unary function on an actual value (plus a generator of a failure message) into an Assertion where the value is to be returned from a subcomputation.

Binary assertions

liftAssertion2Pure :: Monad m => (a -> a -> Bool) -> (a -> a -> String) -> a -> a -> Assertion m Source #

Transform a binary function on an expected and an actual value (plus a binary generator of a failure message) into an Assertion for a pure given actual value.

Example

TLT's scalar-testing operators like @==- are defined with this function:

(@==-) :: (Monad m, Eq a, Show a) => a -> a -> Assertion m
(@==-) = liftAssertion2Pure (==) $
  \ exp actual -> "Expected " ++ show exp ++ " but got " ++ show actual

The (==) operator tests equality, and the result here allows the assertion that a value should be exactly equal to a target. The second argument formats the detail reported when the assertion fails.

assertion2PtoM :: Monad m => (a -> a -> Assertion m) -> a -> m a -> Assertion m Source #

Given an Assertion for two pure values (expected and actual), lift it to an Assertion expecting the actual value to be returned from a computation.

Examples

The TLT assertion `Test.TLT.(==)` lifts `Test.TLT.(==-)` (both defined in Standard) from expecting a pure actual result to expecting a computation returning a value to test.

(@==) :: (Monad m, Eq a, Show a) => a -> m a -> Assertion m
(@==) = assertion2PtoM (@==-)

liftAssertion2M :: Monad m => (a -> a -> Bool) -> (a -> a -> String) -> a -> m a -> Assertion m Source #

Transform a binary function on expected and actual values (plus a generator of a failure message) into an Assertion where the actual value is to be returned from a subcomputation.

Dealing with exceptions in an ExceptT layer

class (MonadTLT m nt, Monad m, MonadTLT ne nt) => MonadTLTExcept m e nt ne | m -> e, m -> ne where Source #

Enabling TLT checking of the completion of computations with- or without uncaught exceptions in a (possibly embedded) ExceptT or Except monad.

In general, it is more difficult to automatically deduce MonadTLTExcept instances than MonadTLT because runToExcept instances bodies will frequently require additional parameters to functions such as runReaderT, or values corresponding to Nothing, which are specific to a particular scenario.

Note that using MonadTLTExcept imposes the restriction that the TLT transformer layer must be wrapped within the ExceptT transformer layer.

Methods

liftTLTExcept :: ExceptT e ne a -> m a Source #

Encodes how an embedded ExceptT monad can be lifted to the top-level monad stack type m.

runToExcept :: m a -> ExceptT e ne a Source #

Runs the layers of the monad stack above the ExceptT layer, exposing that latter layer. Serves as an inverse of liftTLTExcept.

Instances

Instances details
MonadTLT m nt => MonadTLTExcept (ExceptT e m) e nt m Source #

The ExceptT instance is a base case; here the lift/run functions are simply id.

Instance details

Defined in Test.TLT.Class

Methods

liftTLTExcept :: ExceptT e m a -> ExceptT e m a Source #

runToExcept :: ExceptT e m a -> ExceptT e m a Source #

MonadTLTExcept m e nt ne => MonadTLTExcept (IdentityT m) e nt ne Source #

We can infer general instances for other monad transformer types when their run function does not take some initializing argument.

Instance details

Defined in Test.TLT.Class

Methods

liftTLTExcept :: ExceptT e ne a -> IdentityT m a Source #

runToExcept :: IdentityT m a -> ExceptT e ne a Source #

(MonadTLTExcept m e nt ne, Monoid w) => MonadTLTExcept (WriterT w m) e nt ne Source #

The runToExcept function in this case simply discards any output.

Instance details

Defined in Test.TLT.Class

Methods

liftTLTExcept :: ExceptT e ne a -> WriterT w m a Source #

runToExcept :: WriterT w m a -> ExceptT e ne a Source #

(MonadTLTExcept m e nt ne, Monoid w) => MonadTLTExcept (WriterT w m) e nt ne Source #

The runToExcept function in this case simply discards any output.

Instance details

Defined in Test.TLT.Class

Methods

liftTLTExcept :: ExceptT e ne a -> WriterT w m a Source #

runToExcept :: WriterT w m a -> ExceptT e ne a Source #

noUncaught :: (MonadTLTExcept m e nt ne, Show e) => String -> m a -> m () Source #

Ensure that a computation in ExceptT completes without an uncaught exception.

noUncaught_ :: MonadTLTExcept m e nt ne => String -> m a -> m () Source #

Ensure that a computation in ExceptT completes without an uncaught exception.

uncaught :: forall {m} {e} {nt :: Type -> Type} {ne :: Type -> Type} {a}. MonadTLTExcept m e nt ne => String -> m a -> m () Source #

Ensure that a computation in ExceptT does throw an uncaught exception.

uncaughtWith :: MonadTLTExcept m e nt ne => String -> m a -> (e -> ExceptT e ne ()) -> m () Source #

Ensure that a computation in ExceptT does throw an uncaught exception, allowing further testing of the exception.