Copyright | (c) John Maraist 2022 |
---|---|
License | GPL3 |
Maintainer | haskell-tlt@maraist.org |
Stability | experimental |
Portability | POSIX |
Safe Haskell | Safe-Inferred |
Language | Haskell2010 |
Assertion infrastructure for the TLT
testing system. See TLT
for more information.
Synopsis
- type Assertion m = m [TestFail]
- assertFailed :: Monad m => String -> Assertion m
- assertSuccess :: Monad m => Assertion m
- (~:) :: MonadTLT m n => String -> Assertion m -> m ()
- (~::-) :: MonadTLT m n => String -> Bool -> m ()
- (~::) :: MonadTLT m n => String -> m Bool -> 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
- 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
Specifying individual 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.
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.
(~:) :: 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 -> 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.
(~::) :: 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.
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.
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