Safe Haskell | Safe-Inferred |
---|---|
Language | Haskell2010 |
Basic definitions for the HUnit library.
This module contains what you need to create assertions and test cases and combine them into test suites.
This module also provides infrastructure for implementing test controllers (which are used to execute tests). See Test.HUnit.Text for a great example of how to implement a test controller.
Synopsis
- data Test
- (~=?) :: HasCallStack => (Eq a, Show a) => a -> a -> Test
- (~?=) :: HasCallStack => (Eq a, Show a) => a -> a -> Test
- (~:) :: HasCallStack => Testable t => String -> t -> Test
- (~?) :: HasCallStack => AssertionPredicable t => t -> String -> Test
- assertFailure :: HasCallStack => String -> IO a
- assertBool :: HasCallStack => String -> Bool -> Assertion
- assertEqual :: HasCallStack => (Eq a, Show a) => String -> a -> a -> Assertion
- assertString :: HasCallStack => String -> Assertion
- type Assertion = IO ()
- (@=?) :: HasCallStack => (Eq a, Show a) => a -> a -> Assertion
- (@?=) :: HasCallStack => (Eq a, Show a) => a -> a -> Assertion
- (@?) :: HasCallStack => AssertionPredicable t => t -> String -> Assertion
- class Assertable t where
- assert :: HasCallStack => t -> Assertion
- class ListAssertable t where
- listAssert :: HasCallStack => [t] -> Assertion
- type AssertionPredicate = IO Bool
- class AssertionPredicable t where
- assertionPredicate :: t -> AssertionPredicate
- class Testable t where
- test :: HasCallStack => t -> Test
- data State = State {}
- data Counts = Counts {}
- type Path = [Node]
- data Node
- testCasePaths :: Test -> [Path]
- testCaseCount :: Test -> Int
- type ReportStart us = State -> us -> IO us
- type ReportProblem us = Maybe SrcLoc -> String -> State -> us -> IO us
- performTest :: ReportStart us -> ReportProblem us -> ReportProblem us -> us -> Test -> IO (Counts, us)
Declaring tests
The basic structure used to create an annotated tree of test cases.
:: HasCallStack | |
=> (Eq a, Show a) | |
=> a | The expected value |
-> a | The actual value |
-> Test |
Shorthand for a test case that asserts equality (with the expected value on the left-hand side, and the actual value on the right-hand side).
:: HasCallStack | |
=> (Eq a, Show a) | |
=> a | The actual value |
-> a | The expected value |
-> Test |
Shorthand for a test case that asserts equality (with the actual value on the left-hand side, and the expected value on the right-hand side).
:: HasCallStack | |
=> AssertionPredicable t | |
=> t | A value of which the asserted condition is predicated |
-> String | A message that is displayed on test failure |
-> Test |
Creates a test case resulting from asserting the condition obtained
from the specified AssertionPredicable
.
Making assertions
:: HasCallStack | |
=> String | A message that is displayed with the assertion failure |
-> IO a |
Unconditionally signals that a failure has occurred.
:: HasCallStack | |
=> String | The message that is displayed if the assertion fails |
-> Bool | The condition |
-> Assertion |
Asserts that the specified condition holds.
:: HasCallStack | |
=> (Eq a, Show a) | |
=> 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.
:: HasCallStack | |
=> String | The message that is displayed with the assertion failure |
-> Assertion |
Signals an assertion failure if a non-empty message (i.e., a message
other than ""
) is passed.
type Assertion = IO () Source #
When an assertion is evaluated, it will output a message if and only if the assertion fails.
Test cases are composed of a sequence of one or more assertions.
:: HasCallStack | |
=> (Eq a, Show a) | |
=> 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).
:: HasCallStack | |
=> (Eq a, Show a) | |
=> 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).
:: HasCallStack | |
=> AssertionPredicable t | |
=> t | A value of which the asserted condition is predicated |
-> String | A message that is displayed if the assertion fails |
-> Assertion |
Asserts that the condition obtained from the specified
AssertionPredicable
holds.
Extending the assertion functionality
class Assertable t where Source #
Allows the extension of the assertion mechanism.
Since an Assertion
can be a sequence of Assertion
s 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
s and
Testable
should be used.
assert :: HasCallStack => t -> Assertion Source #
Instances
Assertable Bool Source # | |
Assertable () Source # | |
Defined in Test.HUnit.Base | |
ListAssertable t => Assertable [t] Source # | |
Defined in Test.HUnit.Base | |
Assertable t => Assertable (IO t) Source # | |
class ListAssertable t where Source #
A specialized form of Assertable
to handle lists.
listAssert :: HasCallStack => [t] -> Assertion Source #
Instances
ListAssertable Char Source # | |
Defined in Test.HUnit.Base listAssert :: [Char] -> Assertion Source # |
type AssertionPredicate = IO Bool Source #
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.
class AssertionPredicable t where Source #
Used to signify that a data type can be converted to an assertion predicate.
assertionPredicate :: t -> AssertionPredicate Source #
Instances
AssertionPredicable Bool Source # | |
Defined in Test.HUnit.Base | |
AssertionPredicable t => AssertionPredicable (IO t) Source # | |
Defined in Test.HUnit.Base assertionPredicate :: IO t -> AssertionPredicate Source # |
class Testable t where Source #
Provides a way to convert data into a Test
or set of Test
.
test :: HasCallStack => t -> Test Source #
Test execution
Note: the rest of the functionality in this module is intended for implementors of test controllers. If you just want to run your tests cases, simply use a test controller, such as the text-based controller in Test.HUnit.Text.
Keeps track of the remaining tests and the results of the performed tests. As each test is performed, the path is removed and the counts are updated as appropriate.
A data structure that hold the results of tests that have been performed up until this point.
Uniquely describes the location of a test within a test hierarchy. Node order is from test case to root.
type ReportStart us = State -> us -> IO us Source #
Report generator for reporting the start of a test run.
type ReportProblem us = Maybe SrcLoc -> String -> State -> us -> IO us Source #
Report generator for reporting problems that have occurred during a test run. Problems may be errors or assertion failures.
:: ReportStart us | report generator for the test run start |
-> ReportProblem us | report generator for errors during the test run |
-> ReportProblem us | report generator for assertion failures during the test run |
-> us | |
-> Test | the test to be executed |
-> IO (Counts, us) |
Performs a test run with the specified report generators.
This handles the actual running of the tests. Most developers will want
to use HUnit.Text.runTestTT
instead. A developer could use this function
to execute tests via another IO system, such as a GUI, or to output the
results in a different manner (e.g., upload XML-formatted results to a
webservice).
Note that the counts in a start report do not include the test case being started, whereas the counts in a problem report do include the test case just finished. The principle is that the counts are sampled only between test case executions. As a result, the number of test case successes always equals the difference of test cases tried and the sum of test case errors and failures.