TLT
TLT is a Haskell test framework oriented towards stacked monad
transformers. TLT has no explicit test specifications. Tests are run
where declared, with results accumulated and reported at the end.
Tests can live in an arbitrary monad transformer so long as the TLT
transformer is part of the stack. Some control of the results display
is available.
See also the TLT Haddock page for additional examples.
Overview
A TLT test is a command in the TLT
monad transformer. There is no
separation between the specification and execution of a test; TLT
makes no record of an executable test itself, only of its result. So
in the main instance for testing, the core IO
monad should be
wrapped in the TLT
transformer, and in whatever other layers are
also to be tested.
In TLT, all tests are associated with a string which names or
otherwise describes the test. Each test is introduced with one of the
~:
, ~::
, or ~::-
infix operators.
The simplest tests simply look for a True
boolean value. These
tests are introduced with ~::
or ~::-
. The difference between the
two is whether the boolean value is the result of a pure Bool
expression, or whether it is returned as the result of a computation.
In TLT, we distinguish between the two cases by including a trailing
hyphen -
to operators on pure expressions, and omitting the hyphen
from operators on monadic arguments. So these two tests will both
pass,
"2 is 2 as single Bool" ~::- 2 == 2
"2 is 2 a returned Bool" ~:: return $ 2 == 2
The ~:
operator introduces a more general form of test. The
right-hand side of ~:
should be an Assertion
formed with one of
TLT's built-in assertion operators, or returned from a package's
custom assertions. Assertion
s can give more detailed failure
information then simple Bool
s.
Syntactically, most assertions are infix operators which start with a
@
character. The value to the left of the operator is the expected
value, and the symbol to the right is (or returns) the value under
test. A hyphen or P
suffixes assertion operators which operate on
pure values; for operators without the trailing hyphen, the value
under test should is expected to be returned as the result of a
monadic computation (as with ~::
and ~::-
).
TLT provides these assertion operators:
Operator |
Meaning |
expected @== monadic |
The actual result must be equal to the given expected result. |
expected @==- expr |
|
unexpected @/= monadic |
The actual result must differ from the given unexpected result. |
unexpected @/=- expr |
|
expected @< monadic |
The actual result must be greater than the given lower bound. |
expected @<- expr |
|
expected @ monadic |
The actual result must be less than the given upper bound. |
expected @>- expr |
|
expected @<= monadic |
The actual result must be greater than or equal to the given lower bound. |
expected @<=- expr |
|
expected @>= monadic |
The actual result must be less than or equal to the given upper bound. |
expected @>=- expr |
|
empty monadic |
The actual result must be an empty Traversable structure. |
emptyP expr |
|
nonempty monadic |
The actual result must be a nonempty Traversable structure. |
nonemptyP expr |
|
nothing monadic |
The actual result must be Nothing (in a Maybe -typed value) |
nothingP expr |
|
assertFailed message |
Trivial assertions, intended for the less interesting branches of conditional and selection expressions. |
assertSuccess |
|
Note that although the assertions are in pairs of one for testing a
pure expression value, and one for testing the result returned from a
monadic computation, in all of the builtin binary assertions the
/expected/ value argument is always a pure value, not itself monadic.
The inGroup
function allows related tests to be reported as a group.
The function takes two arguments, a String
name for the group, and
the TLT
computation housing its tests. Groups have impact only in
terms of organizing the output you see in the final report of tests
run.
Finally, it is straightforward to write new Assertion
s for
project-specific test criteria: they are simply functions returning
monadic values. There are several functions in the final section of
this document which transform pure predicates into Assertion
s, or
which transform one form of Assertion
into another.
Examples
These examples are from the sample executables and test suite of
the TLT
package.
A simple example
The tests in this example are vacuous, but they show a simple
setup with both passing and failing tests.
main :: IO ()
main = do
tlt test
test :: Monad m = TLT m ()
test = do
"True passes" ~::- True
"2 is 3 as single Bool" ~::- 2 == 3
"2 is 2 as single Bool" ~::- 2 == 2
inGroup "== assertions" $ do
inGroup "pure" $ do
"2 is 3 as pure assertion" ~: 2 @==- 3
"2 is 2 as pure assertion" ~: 2 @==- 2
inGroup "monadic" $ do
"2 is 3 as result" ~: 2 @== return 3
"2 is 2 as result" ~: 2 @== return 2
inGroup "/= pure assertions" $ do
"2 not 3" ~: 2 @/=- 3
"2 not 2" ~: 2 @/=- 2
"2 not 3 as result" ~: 2 @/= return 3
"2 not 2 as result" ~: 2 @/= return 2
Running these tests should give:
Running tests:
- 2 is 3 as single Bool: FAIL Expected True but got False
- == assertions:
- pure:
- 2 is 3 as pure assertion: FAIL Expected 2 but got 3
- monadic:
- 2 is 3 as result: FAIL Expected 2 but got 3
- /= pure assertions:
- 2 not 2: FAIL Expected other than 2 but got 2
- 2 not 2 as result: FAIL Expected other than 2 but got 2
Found 5 errors in 11 tests; exiting
Note that only failing tests appear. This can be configured in the
test
command: add a call at the beginning of test
to
reportAllTestResults
to control this behavior:
test :: Monad m = TLT m ()
test = do
reportAllTestResults True
"True passes" ~::- True
...
and the output will be
Running tests:
- True passes: Pass
- 2 is 3 as single Bool: FAIL Expected True but got False
- 2 is 2 as single Bool: Pass
- == assertions:
- pure:
- 2 is 3 as pure assertion: FAIL Expected 2 but got 3
- 2 is 2 as pure assertion: Pass
- monadic:
- 2 is 3 as result: FAIL Expected 2 but got 3
- 2 is 2 as result: Pass
- /= pure assertions:
- 2 not 3: Pass
- 2 not 2: FAIL Expected other than 2 but got 2
- 2 not 3 as result: Pass
- 2 not 2 as result: FAIL Expected other than 2 but got 2
Found 5 errors in 11 tests; exiting
In the previous example TLT
was the outermost (in fact only)
monad transformer, but it can appear at any level of the test
suite's application stack. Using TLT
at other than the top
level is easiest when all of the transformers which might wrap it
are declared as instances of MonadTLT
.
Consider an application which declares two monad transformers
M1T
and M2T
. For simplicity here we take them to be just
aliases for IdentityT
:
newtype Monad m = M1T m a = M1T { unwrap1 :: IdentityT m a }
runM1T :: Monad m = M1T m a - m a
runM1T = runIdentityT . unwrap1
newtype Monad m = M2T m a = M2T { unwrap2 :: IdentityT m a }
runM2T :: Monad m = M2T m a - m a
runM2T = runIdentityT . unwrap2
And we elide the usual details of including each of them in
Functor
, Applicative
, Monad
and MonadTrans
. We can
declare instances of each in MonadTLT
,
instance MonadTLT m n = MonadTLT (M1T m) n where
liftTLT = lift . liftTLT
and similarly for M2T
. Note that this declaration does require
FlexibleInstances
(because n
does not appear in the instance
type), MultiParamTypeClasses
(because we must mention both the top
transformer m
and the monadic type n
directly wrapped by TLT
within m
), and UndecidableInstances
(because n
is not smaller in
the recursive context of MonadTLT
, which is not actually a problem
because in the definition of MonadTLT
, n
is functionally dependent
on m
, which /is/ smaller in the recursive context) in the module
where the MonadTLT
instance is declared.
Now it is convenient to test both transformers:
ttest = do
runM1T $ inGroup "M1T tests" $ m1tests
runM2T $ inGroup "M2T tests" $ m2tests
m1tests = M1T $ do
"3 is 3 as pure assertion" ~: 3 @==- 3
"4 is 4 as pure assertion" ~: 4 @==- 4
m2tests = M2T $ do
"5 is 5 as pure assertion" ~: 5 @==- 5
"6 is 6 as pure assertion" ~: 6 @==- 6
It is not necessary, for example, to harvest test declarations
from the executions of the MnT
s for assembly into an overall
test declaration.