| Safe Haskell | None |
|---|---|
| Language | Haskell2010 |
Test.Framework.HUnitWrapper
Contents
Description
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 -> IO ()
- assertBoolVerbose_ :: Location -> String -> Bool -> IO ()
- gassertBool_ :: AssertM m => Location -> Bool -> m ()
- gassertBoolVerbose_ :: AssertM m => Location -> String -> Bool -> m ()
- assertEqual_ :: (Eq a, Show a) => Location -> a -> a -> IO ()
- assertEqualVerbose_ :: (Eq a, Show a) => Location -> String -> a -> a -> IO ()
- gassertEqual_ :: (Eq a, Show a, AssertM m) => Location -> a -> a -> m ()
- gassertEqualVerbose_ :: (Eq a, Show a, AssertM m) => Location -> String -> a -> a -> m ()
- assertEqualPretty_ :: (Eq a, Pretty a) => Location -> a -> a -> IO ()
- assertEqualPrettyVerbose_ :: (Eq a, Pretty a) => Location -> String -> a -> a -> IO ()
- gassertEqualPretty_ :: (Eq a, Pretty a, AssertM m) => Location -> a -> a -> m ()
- gassertEqualPrettyVerbose_ :: (Eq a, Pretty a, AssertM m) => Location -> String -> a -> a -> m ()
- assertEqualNoShow_ :: Eq a => Location -> a -> a -> IO ()
- assertEqualNoShowVerbose_ :: Eq a => Location -> String -> a -> a -> IO ()
- gassertEqualNoShow_ :: (Eq a, AssertM m) => Location -> a -> a -> m ()
- gassertEqualNoShowVerbose_ :: (Eq a, AssertM m) => Location -> String -> a -> a -> m ()
- assertNotEqual_ :: (Eq a, Show a) => Location -> a -> a -> IO ()
- assertNotEqualVerbose_ :: (Eq a, Show a) => Location -> String -> a -> a -> IO ()
- gassertNotEqual_ :: (Eq a, Show a, AssertM m) => Location -> a -> a -> m ()
- gassertNotEqualVerbose_ :: (Eq a, Show a, AssertM m) => Location -> String -> a -> a -> m ()
- assertNotEqualPretty_ :: (Eq a, Pretty a) => Location -> a -> a -> IO ()
- assertNotEqualPrettyVerbose_ :: (Eq a, Pretty a) => Location -> String -> a -> a -> IO ()
- gassertNotEqualPretty_ :: (Eq a, Pretty a, AssertM m) => Location -> a -> a -> m ()
- gassertNotEqualPrettyVerbose_ :: (Eq a, Pretty a, AssertM m) => Location -> String -> a -> a -> m ()
- assertNotEqualNoShow_ :: Eq a => Location -> a -> a -> IO ()
- assertNotEqualNoShowVerbose_ :: Eq a => Location -> String -> a -> a -> IO ()
- gassertNotEqualNoShow_ :: (Eq a, AssertM m) => Location -> a -> a -> m ()
- gassertNotEqualNoShowVerbose_ :: (Eq a, AssertM m) => Location -> String -> a -> a -> m ()
- assertListsEqualAsSets_ :: (Eq a, Show a) => Location -> [a] -> [a] -> IO ()
- assertListsEqualAsSetsVerbose_ :: (Eq a, Show a) => Location -> String -> [a] -> [a] -> IO ()
- gassertListsEqualAsSets_ :: (Eq a, Show a, AssertM m) => Location -> [a] -> [a] -> m ()
- gassertListsEqualAsSetsVerbose_ :: (Eq a, Show a, AssertM m) => Location -> String -> [a] -> [a] -> m ()
- assertNotEmpty_ :: Location -> [a] -> IO ()
- assertNotEmptyVerbose_ :: Location -> String -> [a] -> IO ()
- gassertNotEmpty_ :: AssertM m => Location -> [a] -> m ()
- gassertNotEmptyVerbose_ :: AssertM m => Location -> String -> [a] -> m ()
- assertEmpty_ :: Location -> [a] -> IO ()
- assertEmptyVerbose_ :: Location -> String -> [a] -> IO ()
- gassertEmpty_ :: AssertM m => Location -> [a] -> m ()
- gassertEmptyVerbose_ :: AssertM m => Location -> String -> [a] -> m ()
- assertElem_ :: (Eq a, Show a) => Location -> a -> [a] -> IO ()
- assertElemVerbose_ :: (Eq a, Show a) => Location -> String -> a -> [a] -> IO ()
- gassertElem_ :: (Eq a, Show a, AssertM m) => Location -> a -> [a] -> m ()
- gassertElemVerbose_ :: (Eq a, Show a, AssertM m) => Location -> String -> a -> [a] -> m ()
- assertThrows_ :: Exception e => Location -> a -> (e -> Bool) -> IO ()
- assertThrowsVerbose_ :: Exception e => Location -> String -> a -> (e -> Bool) -> IO ()
- assertThrowsSome_ :: Location -> a -> IO ()
- assertThrowsSomeVerbose_ :: Location -> String -> a -> IO ()
- assertThrowsIO_ :: Exception e => Location -> IO a -> (e -> Bool) -> IO ()
- assertThrowsIOVerbose_ :: Exception e => Location -> String -> IO a -> (e -> Bool) -> IO ()
- assertThrowsSomeIO_ :: Location -> IO a -> IO ()
- assertThrowsSomeIOVerbose_ :: Location -> String -> IO a -> IO ()
- 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
- gassertLeft_ :: (Show b, AssertM m) => Location -> Either a b -> m a
- gassertLeftVerbose_ :: (Show b, AssertM m) => Location -> String -> Either a b -> m a
- assertLeftNoShow_ :: Location -> Either a b -> IO a
- assertLeftNoShowVerbose_ :: Location -> String -> Either a b -> IO a
- gassertLeftNoShow_ :: AssertM m => Location -> Either a b -> m a
- gassertLeftNoShowVerbose_ :: AssertM m => Location -> String -> Either a b -> m a
- assertRight_ :: Show a => Location -> Either a b -> IO b
- assertRightVerbose_ :: Show a => Location -> String -> Either a b -> IO b
- gassertRight_ :: (Show a, AssertM m) => Location -> Either a b -> m b
- gassertRightVerbose_ :: (Show a, AssertM m) => Location -> String -> Either a b -> m b
- assertRightNoShow_ :: Location -> Either a b -> IO b
- assertRightNoShowVerbose_ :: Location -> String -> Either a b -> IO b
- gassertRightNoShow_ :: AssertM m => Location -> Either a b -> m b
- gassertRightNoShowVerbose_ :: AssertM m => Location -> String -> Either a b -> m b
- assertJust_ :: Location -> Maybe a -> IO a
- assertJustVerbose_ :: Location -> String -> Maybe a -> IO a
- gassertJust_ :: AssertM m => Location -> Maybe a -> m a
- gassertJustVerbose_ :: AssertM m => Location -> String -> Maybe a -> m a
- assertNothing_ :: Show a => Location -> Maybe a -> IO ()
- assertNothingVerbose_ :: Show a => Location -> String -> Maybe a -> IO ()
- gassertNothing_ :: (Show a, AssertM m) => Location -> Maybe a -> m ()
- gassertNothingVerbose_ :: (Show a, AssertM m) => Location -> String -> Maybe a -> m ()
- assertNothingNoShow_ :: Location -> Maybe a -> IO ()
- assertNothingNoShowVerbose_ :: Location -> String -> Maybe a -> IO ()
- gassertNothingNoShow_ :: AssertM m => Location -> Maybe a -> m ()
- gassertNothingNoShowVerbose_ :: AssertM m => Location -> String -> Maybe a -> m ()
- assertFailure_ :: Location -> String -> IO a
- gassertFailure_ :: AssertM m => Location -> String -> m 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
- gsubAssert_ :: AssertM m => Location -> m a -> m a
- gsubAssertVerbose_ :: AssertM m => Location -> String -> m a -> m a
- data HUnitFailure :: *
- hunitWrapperTests :: [(String, IO ())]
Assertions on Bool values
assertBool_ :: Location -> Bool -> IO () Source
gassertBool_ :: AssertM m => Location -> Bool -> m () Source
gassertBoolVerbose_ :: AssertM m => Location -> String -> Bool -> m () Source
Fail if the Bool value is False. The String parameter in the Verbose variants can be used to provide extra information about the error. The variants gassertBool and gassertBoolVerbose are generic assertions: they run in the IO monad and can be evaluated to a Bool value. Do not use the assertBool_, assertBoolVerbose_, gassertBool_, and gassertBoolVerbose_ functions directly, use the macros assertBool, assertBoolVerbose, gassertBool, and gassertBoolVerbose instead. These macros, provided by the htfpp preprocessor, insert the Location parameter automatically.
Equality assertions
gassertEqualVerbose_ :: (Eq a, Show a, AssertM m) => Location -> String -> a -> a -> m () Source
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 variants can be used to provide extra information about the error. The variants gassertEqual and gassertEqualVerbose are generic assertions: they run in the IO monad and can be evaluated to a Bool value. Do not use the assertEqual_, assertEqualVerbose_, gassertEqual_, and gassertEqualVerbose_ functions directly, use the macros assertEqual, assertEqualVerbose, gassertEqual, and gassertEqualVerbose instead. These macros, provided by the htfpp preprocessor, insert the Location parameter automatically.
gassertEqualPrettyVerbose_ :: (Eq a, Pretty a, AssertM m) => Location -> String -> a -> a -> m () Source
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 variants can be used to provide extra information about the error. The variants gassertEqualPretty and gassertEqualPrettyVerbose are generic assertions: they run in the IO monad and can be evaluated to a Bool value. Do not use the assertEqualPretty_, assertEqualPrettyVerbose_, gassertEqualPretty_, and gassertEqualPrettyVerbose_ functions directly, use the macros assertEqualPretty, assertEqualPrettyVerbose, gassertEqualPretty, and gassertEqualPrettyVerbose instead. These macros, provided by the htfpp preprocessor, insert the Location parameter automatically.
assertEqualNoShow_ :: Eq a => Location -> a -> a -> IO () Source
gassertEqualNoShow_ :: (Eq a, AssertM m) => Location -> a -> a -> m () Source
gassertEqualNoShowVerbose_ :: (Eq a, AssertM m) => Location -> String -> a -> a -> m () Source
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 variants can be used to provide extra information about the error. The variants gassertEqualNoShow and gassertEqualNoShowVerbose are generic assertions: they run in the IO monad and can be evaluated to a Bool value. Do not use the assertEqualNoShow_, assertEqualNoShowVerbose_, gassertEqualNoShow_, and gassertEqualNoShowVerbose_ functions directly, use the macros assertEqualNoShow, assertEqualNoShowVerbose, gassertEqualNoShow, and gassertEqualNoShowVerbose instead. These macros, provided by the htfpp preprocessor, insert the Location parameter automatically.
gassertNotEqualVerbose_ :: (Eq a, Show a, AssertM m) => Location -> String -> a -> a -> m () Source
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 variants can be used to provide extra information about the error. The variants gassertNotEqual and gassertNotEqualVerbose are generic assertions: they run in the IO monad and can be evaluated to a Bool value. Do not use the assertNotEqual_, assertNotEqualVerbose_, gassertNotEqual_, and gassertNotEqualVerbose_ functions directly, use the macros assertNotEqual, assertNotEqualVerbose, gassertNotEqual, and gassertNotEqualVerbose instead. These macros, provided by the htfpp preprocessor, insert the Location parameter automatically.
gassertNotEqualPrettyVerbose_ :: (Eq a, Pretty a, AssertM m) => Location -> String -> a -> a -> m () Source
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 variants can be used to provide extra information about the error. The variants gassertNotEqualPretty and gassertNotEqualPrettyVerbose are generic assertions: they run in the IO monad and can be evaluated to a Bool value. Do not use the assertNotEqualPretty_, assertNotEqualPrettyVerbose_, gassertNotEqualPretty_, and gassertNotEqualPrettyVerbose_ functions directly, use the macros assertNotEqualPretty, assertNotEqualPrettyVerbose, gassertNotEqualPretty, and gassertNotEqualPrettyVerbose instead. These macros, provided by the htfpp preprocessor, insert the Location parameter automatically.
assertNotEqualNoShow_ :: Eq a => Location -> a -> a -> IO () Source
gassertNotEqualNoShow_ :: (Eq a, AssertM m) => Location -> a -> a -> m () Source
gassertNotEqualNoShowVerbose_ :: (Eq a, AssertM m) => Location -> String -> a -> a -> m () Source
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 variants can be used to provide extra information about the error. The variants gassertNotEqualNoShow and gassertNotEqualNoShowVerbose are generic assertions: they run in the IO monad and can be evaluated to a Bool value. Do not use the assertNotEqualNoShow_, assertNotEqualNoShowVerbose_, gassertNotEqualNoShow_, and gassertNotEqualNoShowVerbose_ functions directly, use the macros assertNotEqualNoShow, assertNotEqualNoShowVerbose, gassertNotEqualNoShow, and gassertNotEqualNoShowVerbose 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] -> IO () Source
gassertListsEqualAsSetsVerbose_ :: (Eq a, Show a, AssertM m) => Location -> String -> [a] -> [a] -> m () Source
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 variants can be used to provide extra information about the error. The variants gassertListsEqualAsSets and gassertListsEqualAsSetsVerbose are generic assertions: they run in the IO monad and can be evaluated to a Bool value. Do not use the assertListsEqualAsSets_, assertListsEqualAsSetsVerbose_, gassertListsEqualAsSets_, and gassertListsEqualAsSetsVerbose_ functions directly, use the macros assertListsEqualAsSets, assertListsEqualAsSetsVerbose, gassertListsEqualAsSets, and gassertListsEqualAsSetsVerbose instead. These macros, provided by the htfpp preprocessor, insert the Location parameter automatically.
assertNotEmpty_ :: Location -> [a] -> IO () Source
assertNotEmptyVerbose_ :: Location -> String -> [a] -> IO () Source
gassertNotEmpty_ :: AssertM m => Location -> [a] -> m () Source
gassertNotEmptyVerbose_ :: AssertM m => Location -> String -> [a] -> m () Source
Fail if the given list is empty. The String parameter in the Verbose variants can be used to provide extra information about the error. The variants gassertNotEmpty and gassertNotEmptyVerbose are generic assertions: they run in the IO monad and can be evaluated to a Bool value. Do not use the assertNotEmpty_, assertNotEmptyVerbose_, gassertNotEmpty_, and gassertNotEmptyVerbose_ functions directly, use the macros assertNotEmpty, assertNotEmptyVerbose, gassertNotEmpty, and gassertNotEmptyVerbose instead. These macros, provided by the htfpp preprocessor, insert the Location parameter automatically.
assertEmpty_ :: Location -> [a] -> IO () Source
assertEmptyVerbose_ :: Location -> String -> [a] -> IO () Source
gassertEmpty_ :: AssertM m => Location -> [a] -> m () Source
gassertEmptyVerbose_ :: AssertM m => Location -> String -> [a] -> m () Source
Fail if the given list is a non-empty list. The String parameter in the Verbose variants can be used to provide extra information about the error. The variants gassertEmpty and gassertEmptyVerbose are generic assertions: they run in the IO monad and can be evaluated to a Bool value. Do not use the assertEmpty_, assertEmptyVerbose_, gassertEmpty_, and gassertEmptyVerbose_ functions directly, use the macros assertEmpty, assertEmptyVerbose, gassertEmpty, and gassertEmptyVerbose instead. These macros, provided by the htfpp preprocessor, insert the Location parameter automatically.
gassertElemVerbose_ :: (Eq a, Show a, AssertM m) => Location -> String -> a -> [a] -> m () Source
Fail if the given element is not in the list. The String parameter in the Verbose variants can be used to provide extra information about the error. The variants gassertElem and gassertElemVerbose are generic assertions: they run in the IO monad and can be evaluated to a Bool value. Do not use the assertElem_, assertElemVerbose_, gassertElem_, and gassertElemVerbose_ functions directly, use the macros assertElem, assertElemVerbose, gassertElem, and gassertElemVerbose instead. These macros, provided by the htfpp preprocessor, insert the Location parameter automatically.
Assertions for exceptions
assertThrowsVerbose_ :: Exception e => Location -> String -> a -> (e -> Bool) -> IO () Source
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 the assertThrows_ and assertThrowsVerbose_ functions directly, use the macros assertThrows and assertThrowsVerbose instead. These macros, provided by the htfpp preprocessor, insert the Location parameter automatically.
assertThrowsSome_ :: Location -> a -> IO () Source
assertThrowsSomeVerbose_ :: Location -> String -> a -> IO () Source
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 the assertThrowsSome_ and assertThrowsSomeVerbose_ functions 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) -> IO () Source
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 the assertThrowsIO_ and assertThrowsIOVerbose_ functions directly, use the macros assertThrowsIO and assertThrowsIOVerbose instead. These macros, provided by the htfpp preprocessor, insert the Location parameter automatically.
assertThrowsSomeIO_ :: Location -> IO a -> IO () Source
assertThrowsSomeIOVerbose_ :: Location -> String -> IO a -> IO () Source
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 the assertThrowsSomeIO_ and assertThrowsSomeIOVerbose_ functions 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 the assertThrowsM_ and assertThrowsMVerbose_ functions 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 the assertThrowsSomeM_ and assertThrowsSomeMVerbose_ functions directly, use the macros assertThrowsSomeM and assertThrowsSomeMVerbose instead. These macros, provided by the htfpp preprocessor, insert the Location parameter automatically.
Assertions on Either values
gassertLeftVerbose_ :: (Show b, AssertM m) => Location -> String -> Either a b -> m a Source
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 variants can be used to provide extra information about the error. The variants gassertLeft and gassertLeftVerbose are generic assertions: they run in the IO monad and can be evaluated to a Bool value. Do not use the assertLeft_, assertLeftVerbose_, gassertLeft_, and gassertLeftVerbose_ functions directly, use the macros assertLeft, assertLeftVerbose, gassertLeft, and gassertLeftVerbose instead. These macros, provided by the htfpp preprocessor, insert the Location parameter automatically.
assertLeftNoShow_ :: Location -> Either a b -> IO a Source
gassertLeftNoShow_ :: AssertM m => Location -> Either a b -> m a Source
gassertLeftNoShowVerbose_ :: AssertM m => Location -> String -> Either a b -> m a Source
Fail if the given Either a b value is a Right. The String parameter in the Verbose variants can be used to provide extra information about the error. The variants gassertLeftNoShow and gassertLeftNoShowVerbose are generic assertions: they run in the IO monad and can be evaluated to a Bool value. Do not use the assertLeftNoShow_, assertLeftNoShowVerbose_, gassertLeftNoShow_, and gassertLeftNoShowVerbose_ functions directly, use the macros assertLeftNoShow, assertLeftNoShowVerbose, gassertLeftNoShow, and gassertLeftNoShowVerbose instead. These macros, provided by the htfpp preprocessor, insert the Location parameter automatically.
gassertRightVerbose_ :: (Show a, AssertM m) => Location -> String -> Either a b -> m b Source
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 variants can be used to provide extra information about the error. The variants gassertRight and gassertRightVerbose are generic assertions: they run in the IO monad and can be evaluated to a Bool value. Do not use the assertRight_, assertRightVerbose_, gassertRight_, and gassertRightVerbose_ functions directly, use the macros assertRight, assertRightVerbose, gassertRight, and gassertRightVerbose instead. These macros, provided by the htfpp preprocessor, insert the Location parameter automatically.
assertRightNoShow_ :: Location -> Either a b -> IO b Source
gassertRightNoShow_ :: AssertM m => Location -> Either a b -> m b Source
gassertRightNoShowVerbose_ :: AssertM m => Location -> String -> Either a b -> m b Source
Fail if the given Either a b value is a Left. The String parameter in the Verbose variants can be used to provide extra information about the error. The variants gassertRightNoShow and gassertRightNoShowVerbose are generic assertions: they run in the IO monad and can be evaluated to a Bool value. Do not use the assertRightNoShow_, assertRightNoShowVerbose_, gassertRightNoShow_, and gassertRightNoShowVerbose_ functions directly, use the macros assertRightNoShow, assertRightNoShowVerbose, gassertRightNoShow, and gassertRightNoShowVerbose instead. These macros, provided by the htfpp preprocessor, insert the Location parameter automatically.
Assertions on Just values
assertJust_ :: Location -> Maybe a -> IO a Source
gassertJust_ :: AssertM m => Location -> Maybe a -> m a Source
gassertJustVerbose_ :: AssertM m => Location -> String -> Maybe a -> m a Source
Fail is the given Maybe a value is a Nothing. The String parameter in the Verbose variants can be used to provide extra information about the error. The variants gassertJust and gassertJustVerbose are generic assertions: they run in the IO monad and can be evaluated to a Bool value. Do not use the assertJust_, assertJustVerbose_, gassertJust_, and gassertJustVerbose_ functions directly, use the macros assertJust, assertJustVerbose, gassertJust, and gassertJustVerbose instead. These macros, provided by the htfpp preprocessor, insert the Location parameter automatically.
gassertNothingVerbose_ :: (Show a, AssertM m) => Location -> String -> Maybe a -> m () Source
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 variants can be used to provide extra information about the error. The variants gassertNothing and gassertNothingVerbose are generic assertions: they run in the IO monad and can be evaluated to a Bool value. Do not use the assertNothing_, assertNothingVerbose_, gassertNothing_, and gassertNothingVerbose_ functions directly, use the macros assertNothing, assertNothingVerbose, gassertNothing, and gassertNothingVerbose instead. These macros, provided by the htfpp preprocessor, insert the Location parameter automatically.
assertNothingNoShow_ :: Location -> Maybe a -> IO () Source
gassertNothingNoShow_ :: AssertM m => Location -> Maybe a -> m () Source
gassertNothingNoShowVerbose_ :: AssertM m => Location -> String -> Maybe a -> m () Source
Fail is the given Maybe a value is a Just. The String parameter in the Verbose variants can be used to provide extra information about the error. The variants gassertNothingNoShow and gassertNothingNoShowVerbose are generic assertions: they run in the IO monad and can be evaluated to a Bool value. Do not use the assertNothingNoShow_, assertNothingNoShowVerbose_, gassertNothingNoShow_, and gassertNothingNoShowVerbose_ functions directly, use the macros assertNothingNoShow, assertNothingNoShowVerbose, gassertNothingNoShow, and gassertNothingNoShowVerbose instead. These macros, provided by the htfpp preprocessor, insert the Location parameter automatically.
General failure
assertFailure_ :: Location -> String -> IO a Source
Specialization of gassertFailure.
gassertFailure_ :: AssertM m => Location -> String -> m a Source
Fail with the given reason, supplying the error location and the error message.
Pending unit tests
unitTestPending :: String -> IO a Source
Signals that the current unit test is pending.
unitTestPending' :: String -> IO a -> IO a Source
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 a Source
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 a Source
Same as subAssert_ but with an additional error message.
gsubAssert_ :: AssertM m => Location -> m a -> m a Source
Generic variant of subAssert_.
gsubAssertVerbose_ :: AssertM m => Location -> String -> m a -> m a Source
Generic variant of subAssertVerbose_.
HUnit re-exports
data HUnitFailure :: *
Tests (for internal use)
hunitWrapperTests :: [(String, IO ())] Source