HTF-0.15.0.0: The Haskell Test Framework
Safe HaskellNone
LanguageHaskell2010

Test.Framework.HUnitWrapper

Description

This module provides assert-like functions for writing unit tests.

Synopsis

Assertions on Bool values

assertBool :: HasCallStack => Bool -> IO () Source #

Fail if the Bool value is False.

Equality assertions

assertEqual :: (Eq a, Show a, HasCallStack) => a -> a -> IO () Source #

Fail if the two values of type a are not equal. Use if a is an instance of Show but not of Pretty.

assertEqualVerbose :: (Eq a, Show a, HasCallStack) => String -> a -> a -> IO () Source #

Fail if the two values of type a are not equal, supplying an additional message. Use if a is an instance of Show but not of Pretty.

assertEqualPretty :: (Eq a, Pretty a, HasCallStack) => a -> a -> IO () Source #

Fail if the two values of type a are not equal. Use if a is an instance of Pretty.

assertEqualPrettyVerbose :: (Eq a, Pretty a, HasCallStack) => String -> a -> a -> IO () Source #

Fail if the two values of type a are not equal, supplying an additional message. Use if a is an instance of Pretty.

assertEqualNoShow :: (Eq a, HasCallStack) => a -> a -> IO () Source #

Fail if the two values of type a are not equal. Use if a is neither an instance of Show nor of Pretty.

assertEqualNoShowVerbose :: (Eq a, HasCallStack) => String -> a -> a -> IO () Source #

Fail if the two values of type a are not equal, supplying an additional message. Use if a is neither an instance of Show nor of Pretty.

Inequality assertions

assertNotEqual :: (Eq a, Show a, HasCallStack) => a -> a -> IO () Source #

Fail if the two values of type a are equal. Use if a is an instance of Show but not of Pretty.

assertNotEqualVerbose :: (Eq a, Show a, HasCallStack) => String -> a -> a -> IO () Source #

Fail if the two values of type a are equal, supplying an additional message. Use if a is an instance of Show but not of Pretty.

assertNotEqualPretty :: (Eq a, Pretty a, HasCallStack) => a -> a -> IO () Source #

Fail if the two values of type a are equal. Use if a is an instance of Pretty.

assertNotEqualPrettyVerbose :: (Eq a, Pretty a, HasCallStack) => String -> a -> a -> IO () Source #

Fail if the two values of type a are equal, supplying an additional message. Use if a is an instance of Pretty.

assertNotEqualNoShow :: (Eq a, HasCallStack) => a -> a -> IO () Source #

Fail if the two values of type a are equal. Use if a is neither an instance of Show nor of Pretty.

assertNotEqualNoShowVerbose :: (Eq a, HasCallStack) => String -> a -> a -> IO () Source #

Fail if the two values of type a are equal, supplying an additional message. Use if a is neither an instance of Show nor of Pretty.

Assertions on lists

assertListsEqualAsSets :: (Eq a, Show a, HasCallStack) => [a] -> [a] -> IO () Source #

Fail if the two given lists are not equal when considered as sets.

assertListsEqualAsSetsVerbose :: (Eq a, Show a, HasCallStack) => String -> [a] -> [a] -> IO () Source #

Fail if the two given lists are not equal when considered as sets, supplying an additional error message.

assertNotEmpty :: HasCallStack => [a] -> IO () Source #

Fail if the given list is empty.

assertNotEmptyVerbose :: HasCallStack => String -> [a] -> IO () Source #

Fail if the given list is empty, supplying an additional error message.

assertEmpty :: HasCallStack => [a] -> IO () Source #

Fail if the given list is not empty.

assertEmptyVerbose :: HasCallStack => String -> [a] -> IO () Source #

Fail if the given list is not empty, supplying an additional error message.

assertElem :: (Eq a, Show a, HasCallStack) => a -> [a] -> IO () Source #

Fail if the element given is not contained in the list.

assertElemVerbose :: (Eq a, Show a, HasCallStack) => String -> a -> [a] -> IO () Source #

Fail if the element given is not contained in the list, supplying an additional error message.

Assertions for exceptions

assertThrows :: (HasCallStack, Exception e) => a -> (e -> Bool) -> IO () Source #

Fail if evaluating the expression of type a does not throw an exception satisfying the given predicate (e -> Bool).

assertThrowsVerbose :: (HasCallStack, Exception e) => 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), supplying an additional error message.

assertThrowsSome :: HasCallStack => a -> IO () Source #

Fail if evaluating the expression of type a does not throw any exception.

assertThrowsSomeVerbose :: HasCallStack => String -> a -> IO () Source #

Fail if evaluating the expression of type a does not throw any exception, supplying an additional error message.

assertThrowsIO :: (HasCallStack, Exception e) => IO a -> (e -> Bool) -> IO () Source #

Fail if executing the IO action does not throw an exception satisfying the given predicate (e -> Bool).

assertThrowsIOVerbose :: (HasCallStack, Exception e) => String -> IO a -> (e -> Bool) -> IO () Source #

Fail if executing the IO action does not throw an exception satisfying the given predicate (e -> Bool), supplying an additional error message.

assertThrowsSomeIO :: HasCallStack => IO a -> IO () Source #

Fail if executing the IO action does not throw any exception.

assertThrowsSomeIOVerbose :: HasCallStack => String -> IO a -> IO () Source #

Fail if executing the IO action does not throw any exception, supplying an additional error message.

assertThrowsM :: (MonadBaseControl IO m, MonadIO m, Exception e, HasCallStack) => m a -> (e -> Bool) -> m () Source #

Fail if executing the m action does not throw an exception satisfying the given predicate (e -> Bool).

assertThrowsMVerbose :: (MonadBaseControl IO m, MonadIO m, Exception e, HasCallStack) => String -> m a -> (e -> Bool) -> m () Source #

Fail if executing the m action does not throw an exception satisfying the given predicate (e -> Bool), supplying an additional error message.

assertThrowsSomeM :: (MonadBaseControl IO m, MonadIO m, HasCallStack) => m a -> m () Source #

Fail if executing the m action does not throw any exception.

assertThrowsSomeMVerbose :: (MonadBaseControl IO m, MonadIO m, HasCallStack) => String -> m a -> m () Source #

Fail if executing the m action does not throw any exception, supplying an additional error message.

Assertions on Either values

assertLeft :: (HasCallStack, Show b) => Either a b -> IO a Source #

Fail if the given Either a b value is a Right. Use this function if b is an instance of Show.

assertLeftVerbose :: (Show b, HasCallStack) => String -> Either a b -> IO a Source #

Fail if the given Either a b value is a Right, supplying an additional error message. Use this function if b is an instance of Show.

assertLeftNoShow :: HasCallStack => Either a b -> IO a Source #

Fail if the given Either a b value is a Right. Use this function if b is not an instance of Show.

assertLeftNoShowVerbose :: HasCallStack => String -> Either a b -> IO a Source #

Fail if the given Either a b value is a Right, supplying an additional error message. Use this function if b is not an instance of Show.

assertRight :: (HasCallStack, Show a) => Either a b -> IO b Source #

Fail if the given Either a b value is a Left. Use this function if a is an instance of Show.

assertRightVerbose :: (Show a, HasCallStack) => String -> Either a b -> IO b Source #

Fail if the given Either a b value is a Left, supplying an additional error message. Use this function if a is an instance of Show.

assertRightNoShow :: HasCallStack => Either a b -> IO b Source #

Fail if the given Either a b value is a Left. Use this function if a is not an instance of Show.

assertRightNoShowVerbose :: HasCallStack => String -> Either a b -> IO b Source #

Fail if the given Either a b value is a Left, supplying an additional error message. Use this function if a is not an instance of Show.

Assertions on Just values

assertJust :: HasCallStack => Maybe a -> IO a Source #

Fail if the given value is a Nothing.

assertJustVerbose :: HasCallStack => String -> Maybe a -> IO a Source #

Fail if the given value is a Nothing, supplying an additional error message.

assertNothing :: (HasCallStack, Show a) => Maybe a -> IO () Source #

Fail if the given Maybe a value is a Just. Use this function if a is an instance of Show.

assertNothingVerbose :: (Show a, HasCallStack) => String -> Maybe a -> IO () Source #

Fail if the given Maybe a value is a Just, supplying an additional error message. Use this function if a is an instance of Show.

assertNothingNoShow :: HasCallStack => Maybe a -> IO () Source #

Fail if the given Maybe a value is a Just. Use this function if a is not an instance of Show.

assertNothingNoShowVerbose :: HasCallStack => String -> Maybe a -> IO () Source #

Fail if the given Maybe a value is a Just, supplying an additional error message. Use this function if a is not an instance of Show.

General failure

assertFailure :: HasCallStack => String -> IO a Source #

Specialization of gassertFailure to IO.

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 :: (HasCallStack, MonadBaseControl IO m) => m a -> m a Source #

Use subAssert if you want location information for the call site but the function being called does not carry a HasCallStack constraint.

Generalized assertions and failures in AssertM

The following definitions generalize the the monad in which assertions are executed. Usually, assertions are executed in the IO monad. The AssertM monad (see Test.Framework.AssertM) allows you to evaluate assertions also as pure functions.

Assertions on Bool values

Equality assertions

gassertEqual :: (Eq a, Show a, AssertM m, HasCallStack) => a -> a -> m () Source #

Fail in some AssertM monad if the two values of type a are not equal. Use if a is an instance of Show but not of Pretty.

gassertEqualVerbose :: (Eq a, Show a, AssertM m, HasCallStack) => String -> a -> a -> m () Source #

Fail in some AssertM monad if the two values of type a are not equal, supplying an additional message. Use if a is an instance of Show but not of Pretty.

gassertEqualPretty :: (Eq a, Pretty a, AssertM m, HasCallStack) => a -> a -> m () Source #

Fail in some AssertM monad if the two values of type a are not equal. Use if a is an instance of Pretty.

gassertEqualPrettyVerbose :: (Eq a, Pretty a, AssertM m, HasCallStack) => String -> a -> a -> m () Source #

Fail in some AssertM monad if the two values of type a are not equal, supplying an additional message. Use if a is an instance of Pretty.

gassertEqualNoShow :: (Eq a, AssertM m, HasCallStack) => a -> a -> m () Source #

Fail in some AssertM monad if the two values of type a are not equal. Use if a is neither an instance of Show nor of Pretty.

gassertEqualNoShowVerbose :: (Eq a, AssertM m, HasCallStack) => String -> a -> a -> m () Source #

Fail in some AssertM monad if the two values of type a are not equal, supplying an additional message. Use if a is neither an instance of Show nor of Pretty.

Inequality assertions

gassertNotEqual :: (Eq a, Show a, AssertM m, HasCallStack) => a -> a -> m () Source #

Fail in some AssertM monad if the two values of type a are equal. Use if a is an instance of Show but not of Pretty.

gassertNotEqualVerbose :: (Eq a, Show a, AssertM m, HasCallStack) => String -> a -> a -> m () Source #

Fail in some AssertM monad if the two values of type a are equal, supplying an additional message. Use if a is an instance of Show but not of Pretty.

gassertNotEqualPretty :: (Eq a, Pretty a, AssertM m, HasCallStack) => a -> a -> m () Source #

Fail in some AssertM monad if the two values of type a are equal. Use if a is an instance of Pretty.

gassertNotEqualPrettyVerbose :: (Eq a, Pretty a, AssertM m, HasCallStack) => String -> a -> a -> m () Source #

Fail in some AssertM monad if the two values of type a are equal, supplying an additional message. Use if a is an instance of Pretty.

gassertNotEqualNoShow :: (Eq a, AssertM m, HasCallStack) => a -> a -> m () Source #

Fail in some AssertM monad if the two values of type a are equal. Use if a is neither an instance of Show nor of Pretty.

gassertNotEqualNoShowVerbose :: (Eq a, AssertM m, HasCallStack) => String -> a -> a -> m () Source #

Fail in some AssertM monad if the two values of type a are equal, supplying an additional message. Use if a is neither an instance of Show nor of Pretty.

Assertions on lists

gassertListsEqualAsSets :: (Eq a, Show a, AssertM m, HasCallStack) => [a] -> [a] -> m () Source #

Fail in some AssertM monad if the two given lists are not equal when considered as sets.

gassertListsEqualAsSetsVerbose :: (Eq a, Show a, AssertM m, HasCallStack) => String -> [a] -> [a] -> m () Source #

Fail in some AssertM monad if the two given lists are not equal when considered as sets, supplying an additional error message.

gassertNotEmpty :: (HasCallStack, AssertM m) => [a] -> m () Source #

Fail in some AssertM monad if the given list is empty.

gassertNotEmptyVerbose :: (AssertM m, HasCallStack) => String -> [a] -> m () Source #

Fail in some AssertM monad if the given list is empty, supplying an additional error message.

gassertEmpty :: (HasCallStack, AssertM m) => [a] -> m () Source #

Fail in some AssertM monad if the given list is not empty.

gassertEmptyVerbose :: (AssertM m, HasCallStack) => String -> [a] -> m () Source #

Fail in some AssertM monad if the given list is not empty, supplying an additional error message.

gassertElem :: (Eq a, Show a, AssertM m, HasCallStack) => a -> [a] -> m () Source #

Fail in some AssertM monad if the element given is not contained in the list.

gassertElemVerbose :: (Eq a, Show a, AssertM m, HasCallStack) => String -> a -> [a] -> m () Source #

Fail in some AssertM monad if the element given is not contained in the list, supplying an additional error message.

Assertions on Either values

gassertLeft :: (Show b, AssertM m, HasCallStack) => Either a b -> m a Source #

Fail in some AssertM monad if the given Either a b value is a Right. Use this function if b is an instance of Show.

gassertLeftVerbose :: (Show b, AssertM m, HasCallStack) => String -> Either a b -> m a Source #

Fail in some AssertM monad if the given Either a b value is a Right, supplying an additional error message. Use this function if b is an instance of Show.

gassertLeftNoShow :: (HasCallStack, AssertM m) => Either a b -> m a Source #

Fail in some AssertM monad if the given Either a b value is a Right. Use this function if b is not an instance of Show.

gassertLeftNoShowVerbose :: (HasCallStack, AssertM m) => String -> Either a b -> m a Source #

Fail in some AssertM monad if the given Either a b value is a Right, supplying an additional error message. Use this function if b is not an instance of Show.

gassertRight :: (Show a, AssertM m, HasCallStack) => Either a b -> m b Source #

Fail in some AssertM monad if the given Either a b value is a Left. Use this function if a is an instance of Show.

gassertRightVerbose :: (Show a, AssertM m, HasCallStack) => String -> Either a b -> m b Source #

Fail in some AssertM monad if the given Either a b value is a Left, supplying an additional error message. Use this function if a is an instance of Show.

gassertRightNoShow :: (HasCallStack, AssertM m) => Either a b -> m b Source #

Fail in some AssertM monad if the given Either a b value is a Left. Use this function if a is not an instance of Show.

gassertRightNoShowVerbose :: (HasCallStack, AssertM m) => String -> Either a b -> m b Source #

Fail in some AssertM monad if the given Either a b value is a Left, supplying an additional error message. Use this function if a is not an instance of Show.

Assertions on Just values

gassertJust :: (HasCallStack, AssertM m) => Maybe a -> m a Source #

Fail in some AssertM monad if the given value is a Nothing.

gassertJustVerbose :: (HasCallStack, AssertM m) => String -> Maybe a -> m a Source #

Fail in some AssertM monad if the given value is a Nothing, supplying an additional error message.

gassertNothing :: (Show a, AssertM m, HasCallStack) => Maybe a -> m () Source #

Fail in some AssertM monad if the given Maybe a value is a Just. Use this function if a is an instance of Show.

gassertNothingVerbose :: (Show a, AssertM m, HasCallStack) => String -> Maybe a -> m () Source #

Fail in some AssertM monad if the given Maybe a value is a Just, supplying an additional error message. Use this function if a is an instance of Show.

gassertNothingNoShow :: (HasCallStack, AssertM m) => Maybe a -> m () Source #

Fail in some AssertM monad if the given Maybe a value is a Just. Use this function if a is not an instance of Show.

gassertNothingNoShowVerbose :: (HasCallStack, AssertM m) => String -> Maybe a -> m () Source #

Fail in some AssertM monad if the given Maybe a value is a Just, supplying an additional error message. Use this function if a is not an instance of Show.

General failure

gassertFailure :: (HasCallStack, AssertM m) => String -> m a Source #

Fail with the given reason in some AssertM monad.

Sub assertions

gsubAssert :: (HasCallStack, AssertM m) => m a -> m a Source #

HUnit re-exports

Tests (for internal use)