Copyright | (c) John Maraist 2022 |
---|---|
License | GPL3 |
Maintainer | haskell-tlt@maraist.org |
Stability | experimental |
Portability | POSIX |
Safe Haskell | None |
Language | Haskell2010 |
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 Haddock page is the main piece of documentation; or see also the GitHub repository https://github.com/jphmrst/TLT/.
Synopsis
- data Monad m => TLT m r
- tlt :: MonadIO m => TLT m r -> m ()
- class (Monad m, Monad n) => MonadTLT m n | m -> n
- liftTLT :: MonadTLT m n => TLT n a -> m a
- tltCore :: MonadIO m => TLT m r -> m (TLTopts, [TestResult])
- reportAllTestResults :: MonadTLT m n => Bool -> m ()
- setExitAfterFailDisplay :: MonadTLT m n => Bool -> m ()
- type Assertion m = m [TestFail]
- (~:) :: MonadTLT m n => String -> Assertion m -> m ()
- (~::) :: MonadTLT m n => String -> m Bool -> m ()
- (~::-) :: MonadTLT m n => String -> Bool -> m ()
- tltFail :: MonadTLT m n => String -> String -> m ()
- inGroup :: MonadTLT m n => String -> m a -> m a
- (@==) :: (Monad m, Eq a, Show a) => a -> m a -> Assertion m
- (@/=) :: (Monad m, Eq a, Show a) => a -> m a -> Assertion m
- (@<) :: (Monad m, Ord a, Show a) => a -> m a -> Assertion m
- (@>) :: (Monad m, Ord a, Show a) => a -> m a -> Assertion m
- (@<=) :: (Monad m, Ord a, Show a) => a -> m a -> Assertion m
- (@>=) :: (Monad m, Ord a, Show a) => a -> m a -> Assertion m
- (@==-) :: (Monad m, Eq a, Show a) => a -> a -> Assertion m
- (@/=-) :: (Monad m, Eq a, Show a) => a -> a -> Assertion m
- (@<-) :: (Monad m, Ord a, Show a) => a -> a -> Assertion m
- (@>-) :: (Monad m, Ord a, Show a) => a -> a -> Assertion m
- (@<=-) :: (Monad m, Ord a, Show a) => a -> a -> Assertion m
- (@>=-) :: (Monad m, Ord a, Show a) => a -> a -> Assertion m
- empty :: (Monad m, Traversable t) => m (t a) -> Assertion m
- nonempty :: (Monad m, Traversable t) => m (t a) -> Assertion m
- emptyP :: (Monad m, Traversable t) => t a -> Assertion m
- nonemptyP :: (Monad m, Traversable t) => t a -> Assertion m
- nothing :: Monad m => m (Maybe a) -> Assertion m
- nothingP :: Monad m => Maybe a -> Assertion m
- assertFailed :: Monad m => String -> Assertion m
- assertSuccess :: Monad m => Assertion m
- liftAssertionPure :: Monad m => (a -> Bool) -> (a -> String) -> a -> Assertion m
- assertionPtoM :: Monad m => (a -> Assertion m) -> m a -> Assertion m
- liftAssertionM :: Monad m => (a -> Bool) -> (a -> String) -> m a -> Assertion m
- liftAssertion2Pure :: Monad m => (a -> a -> Bool) -> (a -> a -> String) -> a -> a -> Assertion m
- assertion2PtoM :: Monad m => (a -> a -> Assertion m) -> a -> m a -> Assertion m
- liftAssertion2M :: Monad m => (a -> a -> Bool) -> (a -> a -> String) -> a -> m a -> Assertion m
The TLT transformer
data Monad m => TLT m r Source #
Monad transformer for TLT tests. This layer stores the results from tests as they are executed.
class (Monad m, Monad n) => MonadTLT m n | m -> n 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.
Instances
MonadTLT m n => MonadTLT (MaybeT m) n Source # | |
MonadTLT m n => MonadTLT (ResourceT m) n Source # | |
Monad m => MonadTLT (TLT m) m Source # | |
MonadTLT m n => MonadTLT (STT s m) n Source # | |
MonadTLT m n => MonadTLT (IdentityT m) n Source # | |
(MonadTLT m n, Functor f) => MonadTLT (FreeT f m) n Source # | |
MonadTLT m n => MonadTLT (ReaderT r m) n Source # | |
MonadTLT m n => MonadTLT (StateT s m) n Source # | |
MonadTLT m n => MonadTLT (StateT s m) n Source # | |
(MonadTLT m n, Monoid w) => MonadTLT (WriterT w m) n Source # | |
(MonadTLT m n, Monoid w) => MonadTLT (WriterT w m) n Source # | |
liftTLT :: MonadTLT m n => 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
.
tltCore :: MonadIO m => TLT m r -> m (TLTopts, [TestResult]) Source #
Execute the tests specified in a TLT
monad without output
side-effects, returning the final options and result reports.
This function is primarily useful when calling TLT from some other
package. If you are using TLT itself as your test framework, and
wishing to see its human-oriented output directly, consider using
tlt
instead.
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 tlt
will 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.
Writing tests
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.
TLT
commands
(~:) :: 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
About the values of pure expressions of Eq
- and Ord
-type
(@==) :: (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 monadic computations returing Eq
s and Ord
s
(@==-) :: (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 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
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
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
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 (@==)
lifts (@==-)
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 (@==-)