Safe Haskell | None |
---|---|
Language | Haskell2010 |
Basic definitions for the HUnitPlus library.
This module contains what you need to create assertions and test cases and combine them into test suites.
The assertion and test definition operators are the same as those found in the HUnit library. However, an important note is that the behavior of assertions in HUnit-Plus differs from those in HUnit. HUnit-Plus assertions do not stop executing a test if they fail, and are designed so that multiple assertions can be made by a single test. HUnit-Plus contains several "abort" functions, which can be used to terminate a test immediately.
HUnit-Plus test execution handles exceptions. An uncaught exception will cause the test to report an error (along with any failures and/or errors that have occurred so far), and test execution and reporting will continue.
The data structures for describing tests are the same as those in
the Distribution.TestSuite module used by cabal's testing
facilities. This allows for easy interfacing with cabal's
detailed
testing scheme.
This gives rise to a grid possible use cases: creating a test using
the HUnit-Plus facilities vs. executing an existing
Distribution.TestSuite test which was not created by the
facilities in this module, and executing a test with HUnit-Plus vs
executing it with another test framework. The executeTest
function is designed to cope with either possible origin of a test,
and the Testable
instances are designed to produce tests which
work as expected in either possible execution environment.
- data Test :: *
- = Test TestInstance
- | Group {
- groupName :: String
- concurrently :: Bool
- groupTests :: [Test]
- | ExtraOptions [OptionDescr] Test
- data TestInstance :: * = TestInstance {}
- data TestSuite = TestSuite {
- suiteName :: !String
- suiteConcurrently :: !Bool
- suiteOptions :: [(String, String)]
- suiteTests :: [Test]
- class Testable t where
- (~=?) :: (Eq a, Show a) => a -> a -> Test
- (~?=) :: (Eq a, Show a) => a -> a -> Test
- (~:) :: Testable t => String -> t -> Test
- (~?) :: Assertable t => t -> String -> Test
- type Assertion = IO ()
- assertSuccess :: Assertion
- assertFailure :: String -> Assertion
- abortFailure :: String -> Assertion
- abortError :: String -> Assertion
- assertBool :: String -> Bool -> Assertion
- assertString :: String -> Assertion
- assertStringWithPrefix :: String -> String -> Assertion
- assertEqual :: (Eq a, Show a) => String -> a -> a -> Assertion
- class Assertable t where
- assertWithMsg :: String -> t -> Assertion
- assert :: t -> Assertion
- (@=?) :: (Eq a, Show a) => a -> a -> Assertion
- (@?=) :: (Eq a, Show a) => a -> a -> Assertion
- (@?) :: Assertable t => t -> String -> Assertion
- executeTest :: Reporter us -> State -> us -> IO Progress -> IO (Double, State, us)
- logAssert :: IO ()
- logFailure :: String -> IO ()
- logError :: String -> IO ()
- withPrefix :: String -> IO () -> IO ()
- getErrors :: IO (Maybe String)
- getFailures :: IO (Maybe String)
Test Definition
data Test :: *
Test TestInstance | |
Group | |
| |
ExtraOptions [OptionDescr] Test |
data TestInstance :: *
TestInstance | |
|
Definition for a test suite. This is intended to be a top-level
(ie. non-nestable) container for tests. Test suites have a name, a
list of options with default values (which can be overridden either
at runtime or statically using ExtraOptions
), and a set of
Test
s to be run.
Individual tests are described using definitions found in cabal's Distribution.TestSuite module, to allow for straightforward integration with cabal testing facilities.
TestSuite | |
|
Extended Test Creation
Provides a way to convert data into a Test
or set of Test
.
testNameTags :: String -> [String] -> t -> Test Source
Create a test with a given name and tag set from a Testable
value
testName :: String -> t -> Test Source
Create a test with a given name and no tags from a Testable
value
testTags :: [String] -> t -> Test Source
Create a test with a given name and no tags from a Testable
value
test :: Testable t => t -> Test Source
Create a test with a synthetic name and no tags from a Testable
value
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).
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).
:: Assertable 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
.
Assertions
assertSuccess :: Assertion Source
Signal that an assertion succeeded. This will log that an assertion has been made.
Unconditionally signal that a failure has occurred. This will not stop execution, but will record the failure, resulting in a failed test.
abortFailure :: String -> Assertion Source
Signal that a failure has occurred and stop the test immediately. Note that if an error has been logged already, the test will be reported as an error.
abortError :: String -> Assertion Source
Signal than an error has occurred and stop the test immediately.
Asserts that the specified condition holds.
Signals an assertion failure if a non-empty message (i.e., a message
other than ""
) is passed.
Signals an assertion failure if a non-empty message (i.e., a
message other than ""
) is passed. Allows a prefix to be
supplied for the assertion failure message.
:: (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.
Extended 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 not assert
multiple, independent conditions.
If more complex arrangements of assertions are needed, Test
s and
Testable
should be used.
assertWithMsg :: String -> t -> Assertion Source
Assertion with a failure message
assert :: t -> Assertion Source
Assertion with no failure message
Assertable Bool | |
Assertable () | |
Assertable Progress | |
Assertable Result | |
ListAssertable t => Assertable [t] | |
Assertable t => Assertable (IO t) |
Asserts that the specified actual value is equal to the expected value (with the expected value on the left-hand side).
Asserts that the specified actual value is equal to the expected value (with the actual value on the left-hand side).
:: Assertable t | |
=> t | A value of which the asserted condition is predicated |
-> String | A message that is displayed if the assertion fails |
-> Assertion |
Shorthand for assertBool
.
Low-level Test Functions
:: Reporter us | The reporter to use for reporting results. |
-> State | The HUnit internal state. |
-> us | The reporter state. |
-> IO Progress | The test to run. |
-> IO (Double, State, us) |
Does the actual work of executing a test. This maintains the necessary bookkeeping recording assertions and failures, It also sets up exception handlers and times the test.
logFailure :: String -> IO () Source
Record a failure, along with a message.
withPrefix :: String -> IO () -> IO () Source
Execute the given computation with a message prefix.
getFailures :: IO (Maybe String) Source
Get a combined failure message, if there is one.