Safe Haskell | None |
---|
This module provides assert-like functions for writing unit tests.
Hint: Do not use the assertXXX_
functions
directly. Instead, for each function assertXXX_
,
there exist a preprocessor macro assertXXX
, which provides
the Location parameter automatically. Use these macros, which
are available automatically if you add
{-# OPTIONS_GHC -F -pgmF htfpp #-}
at the top of your source file (see the Tutorial
).
- assertBool_ :: Location -> Bool -> Assertion
- assertBoolVerbose_ :: Location -> String -> Bool -> Assertion
- assertEqual_ :: (Eq a, Show a) => Location -> a -> a -> Assertion
- assertEqualVerbose_ :: (Eq a, Show a) => Location -> String -> a -> a -> Assertion
- assertEqualPretty_ :: (Eq a, Pretty a) => Location -> a -> a -> Assertion
- assertEqualPrettyVerbose_ :: (Eq a, Pretty a) => Location -> String -> a -> a -> Assertion
- assertEqualNoShow_ :: Eq a => Location -> a -> a -> Assertion
- assertEqualNoShowVerbose_ :: Eq a => Location -> String -> a -> a -> Assertion
- assertNotEqual_ :: (Eq a, Show a) => Location -> a -> a -> Assertion
- assertNotEqualVerbose_ :: (Eq a, Show a) => Location -> String -> a -> a -> Assertion
- assertNotEqualPretty_ :: (Eq a, Pretty a) => Location -> a -> a -> Assertion
- assertNotEqualPrettyVerbose_ :: (Eq a, Pretty a) => Location -> String -> a -> a -> Assertion
- assertNotEqualNoShow_ :: Eq a => Location -> a -> a -> Assertion
- assertNotEqualNoShowVerbose_ :: Eq a => Location -> String -> a -> a -> Assertion
- assertListsEqualAsSets_ :: (Eq a, Show a) => Location -> [a] -> [a] -> Assertion
- assertListsEqualAsSetsVerbose_ :: (Eq a, Show a) => Location -> String -> [a] -> [a] -> Assertion
- assertNotEmpty_ :: Location -> [a] -> Assertion
- assertNotEmptyVerbose_ :: Location -> String -> [a] -> Assertion
- assertEmpty_ :: Location -> [a] -> Assertion
- assertEmptyVerbose_ :: Location -> String -> [a] -> Assertion
- assertThrows_ :: Exception e => Location -> a -> (e -> Bool) -> Assertion
- assertThrowsVerbose_ :: Exception e => Location -> String -> a -> (e -> Bool) -> Assertion
- assertThrowsSome_ :: Location -> a -> Assertion
- assertThrowsSomeVerbose_ :: Location -> String -> a -> Assertion
- assertThrowsIO_ :: Exception e => Location -> IO a -> (e -> Bool) -> Assertion
- assertThrowsIOVerbose_ :: Exception e => Location -> String -> IO a -> (e -> Bool) -> Assertion
- assertThrowsSomeIO_ :: Location -> IO a -> Assertion
- assertThrowsSomeIOVerbose_ :: Location -> String -> IO a -> Assertion
- assertThrowsM_ :: (MonadBaseControl IO m, MonadIO m, Exception e) => Location -> m a -> (e -> Bool) -> m ()
- assertThrowsMVerbose_ :: (MonadBaseControl IO m, MonadIO m, Exception e) => Location -> String -> m a -> (e -> Bool) -> m ()
- assertThrowsSomeM_ :: (MonadBaseControl IO m, MonadIO m) => Location -> m a -> m ()
- assertThrowsSomeMVerbose_ :: (MonadBaseControl IO m, MonadIO m) => Location -> String -> m a -> m ()
- assertLeft_ :: Show b => Location -> Either a b -> IO a
- assertLeftVerbose_ :: Show b => Location -> String -> Either a b -> IO a
- assertLeftNoShow_ :: Location -> Either a b -> IO a
- assertLeftNoShowVerbose_ :: Location -> String -> Either a b -> IO a
- assertRight_ :: Show a => Location -> Either a b -> IO b
- assertRightVerbose_ :: Show a => Location -> String -> Either a b -> IO b
- assertRightNoShow_ :: Location -> Either a b -> IO b
- assertRightNoShowVerbose_ :: Location -> String -> Either a b -> IO b
- assertJust_ :: Location -> Maybe a -> IO a
- assertJustVerbose_ :: Location -> String -> Maybe a -> IO a
- assertNothing_ :: Show a => Location -> Maybe a -> Assertion
- assertNothingVerbose_ :: Show a => Location -> String -> Maybe a -> Assertion
- assertNothingNoShow_ :: Location -> Maybe a -> Assertion
- assertNothingNoShowVerbose_ :: Location -> String -> Maybe a -> Assertion
- assertFailure_ :: Location -> String -> IO a
- unitTestPending :: String -> IO a
- unitTestPending' :: String -> IO a -> IO a
- subAssert_ :: MonadBaseControl IO m => Location -> m a -> m a
- subAssertVerbose_ :: MonadBaseControl IO m => Location -> String -> m a -> m a
Assertions on Bool values
assertBool_ :: Location -> Bool -> AssertionSource
assertBoolVerbose_ :: Location -> String -> Bool -> AssertionSource
Fail if the Bool
value is False
. The String
parameter in the Verbose
variant can be used to provide extra information about the error. Do not use assertBool_
and assertBoolVerbose_
directly, use the macros assertBool
and assertBoolVerbose
instead. These macros, provided by the htfpp
preprocessor, insert the Location
parameter automatically.
Equality assertions
assertEqualVerbose_ :: (Eq a, Show a) => Location -> String -> a -> a -> AssertionSource
Fail if the two values of type a
are not equal.
The first parameter denotes the expected value. Use these two functions
of a
is an instance of Show
but not of Pretty
. The String
parameter in the Verbose
variant can be used to provide extra information about the error. Do not use assertEqual_
and assertEqualVerbose_
directly, use the macros assertEqual
and assertEqualVerbose
instead. These macros, provided by the htfpp
preprocessor, insert the Location
parameter automatically.
assertEqualPrettyVerbose_ :: (Eq a, Pretty a) => Location -> String -> a -> a -> AssertionSource
Fail if the two values of type a
are not equal.
The first parameter denotes the expected value. Use these two functions
of a
is an instance of Pretty
. The String
parameter in the Verbose
variant can be used to provide extra information about the error. Do not use assertEqualPretty_
and assertEqualPrettyVerbose_
directly, use the macros assertEqualPretty
and assertEqualPrettyVerbose
instead. These macros, provided by the htfpp
preprocessor, insert the Location
parameter automatically.
assertEqualNoShow_ :: Eq a => Location -> a -> a -> AssertionSource
assertEqualNoShowVerbose_ :: Eq a => Location -> String -> a -> a -> AssertionSource
Fail if the two values of type a
are not equal.
The first parameter denotes the expected value. Use these two functions
of a
is neither an instance of Show
nor Pretty
. Be aware that in this
case the generated error message might not be very helpful. The String
parameter in the Verbose
variant can be used to provide extra information about the error. Do not use assertEqualNoShow_
and assertEqualNoShowVerbose_
directly, use the macros assertEqualNoShow
and assertEqualNoShowVerbose
instead. These macros, provided by the htfpp
preprocessor, insert the Location
parameter automatically.
assertNotEqualVerbose_ :: (Eq a, Show a) => Location -> String -> a -> a -> AssertionSource
Fail if the two values of type a
are equal.
The first parameter denotes the expected value. Use these two functions
of a
is an instance of Show
but not of Pretty
. The String
parameter in the Verbose
variant can be used to provide extra information about the error. Do not use assertNotEqual_
and assertNotEqualVerbose_
directly, use the macros assertNotEqual
and assertNotEqualVerbose
instead. These macros, provided by the htfpp
preprocessor, insert the Location
parameter automatically.
assertNotEqualPrettyVerbose_ :: (Eq a, Pretty a) => Location -> String -> a -> a -> AssertionSource
Fail if the two values of type a
are equal.
The first parameter denotes the expected value. Use these two functions
of a
is an instance of Pretty
. The String
parameter in the Verbose
variant can be used to provide extra information about the error. Do not use assertNotEqualPretty_
and assertNotEqualPrettyVerbose_
directly, use the macros assertNotEqualPretty
and assertNotEqualPrettyVerbose
instead. These macros, provided by the htfpp
preprocessor, insert the Location
parameter automatically.
assertNotEqualNoShow_ :: Eq a => Location -> a -> a -> AssertionSource
assertNotEqualNoShowVerbose_ :: Eq a => Location -> String -> a -> a -> AssertionSource
Fail if the two values of type a
are equal.
The first parameter denotes the expected value. Use these two functions
of a
is neither an instance of Show
nor Pretty
. Be aware that in this
case the generated error message might not be very helpful. The String
parameter in the Verbose
variant can be used to provide extra information about the error. Do not use assertNotEqualNoShow_
and assertNotEqualNoShowVerbose_
directly, use the macros assertNotEqualNoShow
and assertNotEqualNoShowVerbose
instead. These macros, provided by the htfpp
preprocessor, insert the Location
parameter automatically.
Assertions on lists
assertListsEqualAsSetsVerbose_ :: (Eq a, Show a) => Location -> String -> [a] -> [a] -> AssertionSource
Fail if the two given lists are not equal
when considered as sets. The first list parameter
denotes the expected value. The String
parameter in the Verbose
variant can be used to provide extra information about the error. Do not use assertListsEqualAsSets_
and assertListsEqualAsSetsVerbose_
directly, use the macros assertListsEqualAsSets
and assertListsEqualAsSetsVerbose
instead. These macros, provided by the htfpp
preprocessor, insert the Location
parameter automatically.
assertNotEmpty_ :: Location -> [a] -> AssertionSource
assertNotEmptyVerbose_ :: Location -> String -> [a] -> AssertionSource
Fail if the given list is empty. The String
parameter in the Verbose
variant can be used to provide extra information about the error. Do not use assertNotEmpty_
and assertNotEmptyVerbose_
directly, use the macros assertNotEmpty
and assertNotEmptyVerbose
instead. These macros, provided by the htfpp
preprocessor, insert the Location
parameter automatically.
assertEmpty_ :: Location -> [a] -> AssertionSource
assertEmptyVerbose_ :: Location -> String -> [a] -> AssertionSource
Fail if the given list is a non-empty list. The String
parameter in the Verbose
variant can be used to provide extra information about the error. Do not use assertEmpty_
and assertEmptyVerbose_
directly, use the macros assertEmpty
and assertEmptyVerbose
instead. These macros, provided by the htfpp
preprocessor, insert the Location
parameter automatically.
Assertions for exceptions
assertThrowsVerbose_ :: Exception e => Location -> String -> a -> (e -> Bool) -> AssertionSource
Fail if evaluating the expression of type a
does not
throw an exception satisfying the given predicate (e -> Bool)
. The String
parameter in the Verbose
variant can be used to provide extra information about the error. Do not use assertThrows_
and assertThrowsVerbose_
directly, use the macros assertThrows
and assertThrowsVerbose
instead. These macros, provided by the htfpp
preprocessor, insert the Location
parameter automatically.
assertThrowsSome_ :: Location -> a -> AssertionSource
assertThrowsSomeVerbose_ :: Location -> String -> a -> AssertionSource
Fail if evaluating the expression of type a
does not
throw an exception. The String
parameter in the Verbose
variant can be used to provide extra information about the error. Do not use assertThrowsSome_
and assertThrowsSomeVerbose_
directly, use the macros assertThrowsSome
and assertThrowsSomeVerbose
instead. These macros, provided by the htfpp
preprocessor, insert the Location
parameter automatically.
assertThrowsIOVerbose_ :: Exception e => Location -> String -> IO a -> (e -> Bool) -> AssertionSource
Fail if executing the IO
action does not
throw an exception satisfying the given predicate (e -> Bool)
. The String
parameter in the Verbose
variant can be used to provide extra information about the error. Do not use assertThrowsIO_
and assertThrowsIOVerbose_
directly, use the macros assertThrowsIO
and assertThrowsIOVerbose
instead. These macros, provided by the htfpp
preprocessor, insert the Location
parameter automatically.
assertThrowsSomeIO_ :: Location -> IO a -> AssertionSource
assertThrowsSomeIOVerbose_ :: Location -> String -> IO a -> AssertionSource
Fail if executing the IO
action does not
throw an exception. The String
parameter in the Verbose
variant can be used to provide extra information about the error. Do not use assertThrowsSomeIO_
and assertThrowsSomeIOVerbose_
directly, use the macros assertThrowsSomeIO
and assertThrowsSomeIOVerbose
instead. These macros, provided by the htfpp
preprocessor, insert the Location
parameter automatically.
assertThrowsM_ :: (MonadBaseControl IO m, MonadIO m, Exception e) => Location -> m a -> (e -> Bool) -> m ()Source
assertThrowsMVerbose_ :: (MonadBaseControl IO m, MonadIO m, Exception e) => Location -> String -> m a -> (e -> Bool) -> m ()Source
Fail if executing the m
action does not
throw an exception satisfying the given predicate (e -> Bool)
. The String
parameter in the Verbose
variant can be used to provide extra information about the error. Do not use assertThrowsM_
and assertThrowsMVerbose_
directly, use the macros assertThrowsM
and assertThrowsMVerbose
instead. These macros, provided by the htfpp
preprocessor, insert the Location
parameter automatically.
assertThrowsSomeM_ :: (MonadBaseControl IO m, MonadIO m) => Location -> m a -> m ()Source
assertThrowsSomeMVerbose_ :: (MonadBaseControl IO m, MonadIO m) => Location -> String -> m a -> m ()Source
Fail if executing the m
action does not
throw an exception. The String
parameter in the Verbose
variant can be used to provide extra information about the error. Do not use assertThrowsSomeM_
and assertThrowsSomeMVerbose_
directly, use the macros assertThrowsSomeM
and assertThrowsSomeMVerbose
instead. These macros, provided by the htfpp
preprocessor, insert the Location
parameter automatically.
Assertions on Either values
assertLeftVerbose_ :: Show b => Location -> String -> Either a b -> IO aSource
Fail if the given Either a b
value is a Right
.
Use this function if b
is an instance of Show
The String
parameter in the Verbose
variant can be used to provide extra information about the error. Do not use assertLeft_
and assertLeftVerbose_
directly, use the macros assertLeft
and assertLeftVerbose
instead. These macros, provided by the htfpp
preprocessor, insert the Location
parameter automatically.
assertLeftNoShow_ :: Location -> Either a b -> IO aSource
assertLeftNoShowVerbose_ :: Location -> String -> Either a b -> IO aSource
Fail if the given Either a b
value is a Right
. The String
parameter in the Verbose
variant can be used to provide extra information about the error. Do not use assertLeftNoShow_
and assertLeftNoShowVerbose_
directly, use the macros assertLeftNoShow
and assertLeftNoShowVerbose
instead. These macros, provided by the htfpp
preprocessor, insert the Location
parameter automatically.
assertRightVerbose_ :: Show a => Location -> String -> Either a b -> IO bSource
Fail if the given Either a b
value is a Left
.
Use this function if a
is an instance of Show
The String
parameter in the Verbose
variant can be used to provide extra information about the error. Do not use assertRight_
and assertRightVerbose_
directly, use the macros assertRight
and assertRightVerbose
instead. These macros, provided by the htfpp
preprocessor, insert the Location
parameter automatically.
assertRightNoShow_ :: Location -> Either a b -> IO bSource
assertRightNoShowVerbose_ :: Location -> String -> Either a b -> IO bSource
Fail if the given Either a b
value is a Left
. The String
parameter in the Verbose
variant can be used to provide extra information about the error. Do not use assertRightNoShow_
and assertRightNoShowVerbose_
directly, use the macros assertRightNoShow
and assertRightNoShowVerbose
instead. These macros, provided by the htfpp
preprocessor, insert the Location
parameter automatically.
Assertions on Just values
assertJust_ :: Location -> Maybe a -> IO aSource
assertJustVerbose_ :: Location -> String -> Maybe a -> IO aSource
Fail is the given Maybe a
value is a Nothing
. The String
parameter in the Verbose
variant can be used to provide extra information about the error. Do not use assertJust_
and assertJustVerbose_
directly, use the macros assertJust
and assertJustVerbose
instead. These macros, provided by the htfpp
preprocessor, insert the Location
parameter automatically.
assertNothingVerbose_ :: Show a => Location -> String -> Maybe a -> AssertionSource
Fail is the given Maybe a
value is a Just
.
Use this function if a
is an instance of Show
. The String
parameter in the Verbose
variant can be used to provide extra information about the error. Do not use assertNothing_
and assertNothingVerbose_
directly, use the macros assertNothing
and assertNothingVerbose
instead. These macros, provided by the htfpp
preprocessor, insert the Location
parameter automatically.
assertNothingNoShow_ :: Location -> Maybe a -> AssertionSource
assertNothingNoShowVerbose_ :: Location -> String -> Maybe a -> AssertionSource
Fail is the given Maybe a
value is a Just
. The String
parameter in the Verbose
variant can be used to provide extra information about the error. Do not use assertNothingNoShow_
and assertNothingNoShowVerbose_
directly, use the macros assertNothingNoShow
and assertNothingNoShowVerbose
instead. These macros, provided by the htfpp
preprocessor, insert the Location
parameter automatically.
General failure
assertFailure_ :: Location -> String -> IO aSource
Fail with the given reason, supplying the error location and the error message.
Pending unit tests
unitTestPending :: String -> IO aSource
unitTestPending' :: String -> IO a -> IO aSource
Use unitTestPending' msg test
to mark the given test as pending
without removing it from the test suite and without deleting or commenting out the test code.
Sub assertions
subAssert_ :: MonadBaseControl IO m => Location -> m a -> m aSource
Sub assertions are a poor man's way of abstracting over assertions while still propagating location
information. Say you want to abstract over the assertion that an Int
is positive. You would write
assertIsPositive :: Int -> Assertion assertIsPositive n = assertBool (n > 0)
You can now use assertIsPositive i
for some integer i
from your unit tests, but if you call it directly
you will lose location information: if assertIsPositive i
fails you will only get the location where
assertIsPositive
is defined but not from where it has been called.
To recover the location information you simply use subAssert (assertIsPositive i)
.
In this case, if i
is not positive, you will get the location of the caller.
Note: Don't use subAssert_ directly but use the preprocessor macro subAssert
.
subAssertVerbose_ :: MonadBaseControl IO m => Location -> String -> m a -> m aSource
Same as subAssert_
but with an additional error message.