| Safe Haskell | Safe-Inferred | 
|---|---|
| Language | Haskell2010 | 
Test.Tasty.HUnit
Description
Unit testing support for tasty, inspired by the HUnit package.
Here's an example (a single tasty test case consisting of three assertions):
import Test.Tasty
import Test.Tasty.HUnit
main = defaultMain $
  testCase "Example test case" $ do
    -- assertion no. 1 (passes)
    2 + 2 @?= 4
    -- assertion no. 2 (fails)
    assertBool "the list is not empty" $ null [1]
    -- assertion no. 3 (would have failed, but won't be executed because
    -- the previous assertion has already failed)
    "foo" @?= "bar"Synopsis
- testCase :: TestName -> Assertion -> TestTree
- testCaseInfo :: TestName -> IO String -> TestTree
- testCaseSteps :: TestName -> ((String -> IO ()) -> Assertion) -> TestTree
- assertFailure :: HasCallStack => String -> IO a
- assertBool :: HasCallStack => String -> Bool -> Assertion
- assertEqual :: (Eq a, Show a, HasCallStack) => String -> a -> a -> Assertion
- (@=?) :: (Eq a, Show a, HasCallStack) => a -> a -> Assertion
- (@?=) :: (Eq a, Show a, HasCallStack) => a -> a -> Assertion
- (@?) :: (AssertionPredicable t, HasCallStack) => t -> String -> Assertion
- class AssertionPredicable t where- assertionPredicate :: t -> IO Bool
 
- type Assertion = IO ()
- data HUnitFailure = HUnitFailure (Maybe SrcLoc) String
- type HasCallStack = ?callStack :: CallStack
- assertString :: HasCallStack => String -> Assertion
- class Assertable t where
- type AssertionPredicate = IO Bool
Constructing test cases
testCaseInfo :: TestName -> IO String -> TestTree Source #
Like testCase, except in case the test succeeds, the returned string
 will be shown as the description. If the empty string is returned, it
 will be ignored.
testCaseSteps :: TestName -> ((String -> IO ()) -> Assertion) -> TestTree Source #
Create a multi-step unit test.
Example:
main = defaultMain $ testCaseSteps "Multi-step test" $ \step -> do step "Preparing..." -- do something step "Running part 1" -- do something step "Running part 2" -- do something assertFailure "BAM!" step "Running part 3" -- do something
The step calls are mere annotations. They let you see which steps were
 performed successfully, and which step failed.
You can think of step
 as putStrLn, except putStrLn would mess up the output with the
 console reporter and get lost with the others.
For the example above, the output will be
Multi-step test: FAIL
  Preparing...
  Running part 1
  Running part 2
    BAM!
1 out of 1 tests failed (0.00s)Note that:
- Tasty still treats this as a single test, even though it consists of multiple steps.
- The execution stops after the first failure. When we are looking at a failed test, we know that all displayed steps but the last one were successful, and the last one failed. The steps after the failed one are not displayed, since they didn't run.
Constructing assertions
Arguments
| :: HasCallStack | |
| => String | A message that is displayed with the assertion failure | 
| -> IO a | 
Unconditionally signals that a failure has occured. All other assertions can be expressed with the form:
   if conditionIsMet
       then return ()
       else assertFailure msg
Arguments
| :: HasCallStack | |
| => String | The message that is displayed if the assertion fails | 
| -> Bool | The condition | 
| -> Assertion | 
Asserts that the specified condition holds.
Arguments
| :: (Eq a, Show a, HasCallStack) | |
| => String | The message prefix | 
| -> a | The expected value | 
| -> a | The actual value | 
| -> Assertion | 
Asserts that the specified actual value is equal to the expected value. The output message will contain the prefix, the expected value, and the actual value.
If the prefix is the empty string (i.e., ""), then the prefix is omitted
 and only the expected and actual values are output.
Arguments
| :: (Eq a, Show a, HasCallStack) | |
| => a | The expected value | 
| -> a | The actual value | 
| -> Assertion | 
Asserts that the specified actual value is equal to the expected value (with the expected value on the left-hand side).
Arguments
| :: (Eq a, Show a, HasCallStack) | |
| => a | The actual value | 
| -> a | The expected value | 
| -> Assertion | 
Asserts that the specified actual value is equal to the expected value (with the actual value on the left-hand side).
Arguments
| :: (AssertionPredicable t, HasCallStack) | |
| => t | A value of which the asserted condition is predicated | 
| -> String | A message that is displayed if the assertion fails | 
| -> Assertion | 
An infix and flipped version of assertBool. E.g. instead of
assertBool "Non-empty list" (null [1])
you can write
null [1] @? "Non-empty list"
@? is also overloaded to accept IO Bool
do e <- doesFileExist "test" e @? "File does not exist"
you can write
doesFileExist "test" @? "File does not exist"
class AssertionPredicable t where Source #
An ad-hoc class used to overload the @? operator.
The only intended instances of this class are BoolIO Bool
You shouldn't need to interact with this class directly.
Methods
assertionPredicate :: t -> IO Bool Source #
Instances
| AssertionPredicable Bool Source # | |
| Defined in Test.Tasty.HUnit.Orig | |
| AssertionPredicable t => AssertionPredicable (IO t) Source # | |
| Defined in Test.Tasty.HUnit.Orig | |
Data types
type Assertion = IO () Source #
An assertion is simply an IO action. Assertion failure is indicated
 by throwing an exception, typically HUnitFailure.
Instead of throwing the exception directly, you should use
 functions like assertFailure and assertBool.
Test cases are composed of a sequence of one or more assertions.
data HUnitFailure Source #
Exception thrown by assertFailure etc.
Constructors
| HUnitFailure (Maybe SrcLoc) String | 
Instances
| Exception HUnitFailure Source # | |
| Defined in Test.Tasty.HUnit.Orig Methods toException :: HUnitFailure -> SomeException # fromException :: SomeException -> Maybe HUnitFailure # displayException :: HUnitFailure -> String # | |
| Show HUnitFailure Source # | |
| Defined in Test.Tasty.HUnit.Orig Methods showsPrec :: Int -> HUnitFailure -> ShowS # show :: HUnitFailure -> String # showList :: [HUnitFailure] -> ShowS # | |
| Eq HUnitFailure Source # | |
| Defined in Test.Tasty.HUnit.Orig | |
Accurate location for domain-specific assertion functions
It is common to define domain-specific assertion functions based on the standard ones, e.g.
assertNonEmpty = assertBool "List is empty" . not . null
The problem is that if a test fails, tasty-hunit will point to the
 definition site of assertNonEmpty as the source of failure, not
 its use site.
To correct this, add a HasCallStack constraint (re-exported from
 this module) to your function:
assertNonEmpty :: HasCallStack => [a] -> Assertion assertNonEmpty = assertBool "List is empty" . not . null
type HasCallStack = ?callStack :: CallStack #
Request a CallStack.
NOTE: The implicit parameter ?callStack :: CallStack is an
 implementation detail and should not be considered part of the
 CallStack API, we may decide to change the implementation in the
 future.
Since: base-4.9.0.0
Deprecated functions and types
These definitions come from HUnit, but I don't see why one would need them. If you have a valid use case for them, please contact me or file an issue for tasty. Otherwise, they will eventually be removed.
Arguments
| :: HasCallStack | |
| => String | The message that is displayed with the assertion failure | 
| -> Assertion | 
Deprecated: Why not use assertBool instead?
Signals an assertion failure if a non-empty message (i.e., a message
 other than "") is passed.
class Assertable t where Source #
Deprecated: This class or type seems dubious. If you have a good use case for it, please create an issue for tasty. Otherwise, it may be removed in a future version.
Allows the extension of the assertion mechanism.
Since an Assertion can be a sequence of Assertions and IO actions,
 there is a fair amount of flexibility of what can be achieved.  As a rule,
 the resulting Assertion should be the body of a TestCase or part of
 a TestCase; it should not be used to assert multiple, independent
 conditions.
If more complex arrangements of assertions are needed, Test and
 Testable should be used.
Instances
| Assertable String Source # | |
| Assertable () Source # | |
| Defined in Test.Tasty.HUnit.Orig | |
| Assertable Bool Source # | |
| Assertable t => Assertable (IO t) Source # | |
type AssertionPredicate = IO Bool Source #
Deprecated: This class or type seems dubious. If you have a good use case for it, please create an issue for tasty. Otherwise, it may be removed in a future version.
The result of an assertion that hasn't been evaluated yet.
Most test cases follow the following steps:
- Do some processing or an action.
- Assert certain conditions.
However, this flow is not always suitable.  AssertionPredicate allows for
 additional steps to be inserted without the initial action to be affected
 by side effects.  Additionally, clean-up can be done before the test case
 has a chance to end.  A potential work flow is:
- Write data to a file.
- Read data from a file, evaluate conditions.
- Clean up the file.
- Assert that the side effects of the read operation meet certain conditions.
- Assert that the conditions evaluated in step 2 are met.