Safe Haskell | Safe-Infered |
---|
This is the main testing module. Start reading here if you want to know what this package is all about.
There's a documentation section at the bottom of this page. You might want to start by reading that. Otherwise, here's a quick summary:
- You create
Test
objects to represent your tests. -
to quickly run a test interactively (e.g., during debugging activity).run_test
::Test
->IO
Bool
-
run_test_full
allows more control, including recording detailed test results to an XML log file. -
creates a test from pure code.test
::Bool
->Test
-
(
for tests with known answers.?=
) ::Eq
x => x -> x ->Test
- Tests can be annotated with
title
,argument
,temporary
,note
and so on. -
for combining multiple tests into a singletests
:: [Test
] ->Test
Test
object. Tests can be nested arbitrarily in this mannar to group related tests together. -
for tests that need to perform I/O.testIO
::IO
Bool
->Test
- The
TestM
monad supportsliftIO
and allows limited test annotations from within monadic code. -
to use thetestM
::TestM
Bool
->Test
TestM
monad. -
throws
,throwsIO
,throwsM
to test for exceptions.
- data Test
- test :: Bool -> Test
- inapplicable :: Test
- throws_ :: x -> Test
- throws :: Show x => x -> Test
- (?=) :: (Eq x, Show x) => x -> x -> Test
- (?/=) :: (Eq x, Show x) => x -> x -> Test
- (?<) :: (Ord x, Show x) => x -> x -> Test
- (?<=) :: (Ord x, Show x) => x -> x -> Test
- (?>) :: (Ord x, Show x) => x -> x -> Test
- (?>=) :: (Ord x, Show x) => x -> x -> Test
- title :: String -> Test -> Test
- argument :: Show x => String -> x -> Test -> Test
- argument_ :: String -> String -> Test -> Test
- temporary :: Show x => String -> x -> Test -> Test
- temporary_ :: String -> String -> Test -> Test
- note :: String -> Test -> Test
- testIO :: IO Bool -> Test
- testIO3 :: IO x -> (x -> IO Bool) -> (x -> IO y) -> Test
- throws_IO :: IO x -> Test
- throwsIO :: Show x => IO x -> Test
- data TestM x
- testM :: TestM Bool -> Test
- throws_M :: TestM x -> Test
- throwsM :: Show x => TestM x -> Test
- inapplicableM :: TestM Bool
- temporaryM :: Show x => String -> x -> TestM ()
- temporaryM_ :: String -> String -> TestM ()
- noteM :: String -> TestM ()
- tests :: [Test] -> Test
- alternatives :: [Test] -> Test
- run_test :: Test -> IO Bool
- run_test_full :: TestConfig -> Test -> IO Bool
- data TestConfig = TestConfig {}
- default_config :: TestConfig
Types
Pure tests
Creation
Simple tests
This test always succeeds, but writes a note in the log to say that the test case was "inapplicable".
This is generally useful if you have a test generation function which doesn't work for certain combinations of inputs. In that instance, the test still passes, but there is a note in the log letting you know it was only a "null" test.
Exceptions
Test for exceptions.
Ordinarily, any test which throws an exception is deemed to have failed. However, this test passes if evaluating the argument to WHNF causes an exception to be thrown. The test fails if no exception is thrown.
This can be useful for checking that functions reject invalid input by throwing an exception. (Of course, you cannot check that the correct exception is thrown!)
If WHNF is not enough to trigger the exception, you can wrap the
expression in some suitable forcing function. (The function
length
.
show
can sometimes be used for this purpose.)
Note that an infinite loop is not an exception (unless the loop exhausts some resource).
If an exception is not thrown, the actual value returned is not
recorded. See throws
for a function that records this
information. (Note that this requires adding a Show
constraint.)
throws :: Show x => x -> TestSource
Test for exceptions.
Ordinarily, any test which throws an exception is deemed to have failed. However, this test passes if evaluating the argument to WHNF causes an exception to be thrown. The test fails if no exception is thrown.
This can be useful for checking that functions reject invalid input by throwing an exception. (Of course, you cannot check that the correct exception is thrown!)
If WHNF is not enough to trigger the exception, you can wrap the
expression in some suitable forcing function. (The function
length
.
show
can sometimes be used for this purpose.)
Note that an infinite loop is not an exception (unless the loop exhausts some resource).
If no exception is thrown, the actual value returned is recorded.
This requires adding a Show
constraint. See throws_
for a
function without this constraint.
Comparisons
(?=) :: (Eq x, Show x) => x -> x -> TestSource
Compare two values for equality.
The right-hand value is the "target" value, and the left-hand
value (next to the ?
sign) is the "actual" value. The test
passes if both values are equal according to ==
. The test fails
if any exceptions are thrown by ==
or show
.
This operator has the same precedence as ==
(i.e., 4).
(?/=) :: (Eq x, Show x) => x -> x -> TestSource
Compare two values for inequality.
The right-hand value is the "target" value, and the left-hand
value (next to the ?
sign) is the "actual" value. The test
passes if both values are unequal according to /=
. The test fails
if any exceptions are thrown by /=
or show
.
This operator has the same precedence as /=
(i.e., 4).
(?<) :: (Ord x, Show x) => x -> x -> TestSource
Compare two values for inequality.
The right-hand value is the "target" value, and the left-hand
value (next to the ?
sign) is the "actual" value. The test
passes if the actual value is less than the target value according
to <
. The test fails if any exceptions are thrown by <
or
show
.
This operator has the same precedence as <
(i.e., 4).
(?<=) :: (Ord x, Show x) => x -> x -> TestSource
Compare two values for inequality.
The right-hand value is the "target" value, and the left-hand
value (next to the ?
sign) is the "actual" value. The test
passes if the actual value is less than or equal to the target
value according to <=
. The test fails if any exceptions are
thrown by <=
or show
.
This operator has the same precedence as <=
(i.e., 4).
(?>) :: (Ord x, Show x) => x -> x -> TestSource
Compare two values for inequality.
The right-hand value is the "target" value, and the left-hand
value (next to the ?
sign) is the "actual" value. The test
passes if the actual value is more than the target value according
to >
. The test fails if any exceptions are thrown by >
or
show
.
This operator has the same precedence as >
(i.e., 4).
(?>=) :: (Ord x, Show x) => x -> x -> TestSource
Compare two values for inequality.
The right-hand value is the "target" value, and the left-hand
value (next to the ?
sign) is the "actual" value. The test
passes if the actual value is more than or equal to the target
value according to >=
. The test fails if any exceptions are
thrown by >=
or show
.
This operator has the same precedence as >=
(i.e., 4).
Annotations
title :: String -> Test -> TestSource
Attach a title to a test.
This title is an arbitrary human-readable label. It is recorded in relation to the test, but has no other function.
argument_ :: String -> String -> Test -> TestSource
Attach an argument value note.
The first String
is the argument name, and the second is some
suitable textual representation of that argument's value.
temporary_ :: String -> String -> Test -> TestSource
Note down a temporary intermediate value computed in the process of constructing a test.
The first String
is the temporary name, and the second is some
suitable textual representation of the temporary's value.
Impure tests
In the IO
monad
testIO3 :: IO x -> (x -> IO Bool) -> (x -> IO y) -> TestSource
Create a Test
from an IO
action with seperate set-up and
clean-up phases.
The first argument is a set-up action. This might be used to initialise mutable storage or create disk structures, or just to open some handles. Its result is passed to the second argument, which then does the actual test propper. Finally, the third argument is run (again with the set-up result as argument) to do any post-test clean-up operations required. Its result is discarded.
If any of these IO
actions throw an exception, the test is
marked failed. Note that if the set-up action throws an exception,
the test and clean-up actions are not run. (If only the main test
action throws an exception, the clean-up is still run.)
throws_IO :: IO x -> TestSource
Test for exceptions in the IO
monad.
Ordinarily, any test which throws an exception is deemed to have failed. However, this test passes if evaluating the action's result to WHNF causes an exception to be thrown. The test fails if no exception is thrown.
This can be useful for checking that a function rejects invalid input by throwing an exception, or that invalid I/O operations are reported. (Of course, you cannot check that the correct exception is thrown!)
Note that the IO
action is run and its result is reduced (to
WHNF only). Note also that infinite loops are not exceptions
(unless the loop exhausts some resource).
If no exception is thrown, the actual value returned is not
recorded. See throwsIO
for a function which does record this
information. (This requires adding a Show
constraint.)
throwsIO :: Show x => IO x -> TestSource
Test for exceptions in the IO
monad.
Ordinarily, any test which throws an exception is deemed to have failed. However, this test passes if evaluating the action's result to WHNF causes an exception to be thrown. The test fails if no exception is thrown.
This can be useful for checking that a function rejects invalid input by throwing an exception, or that invalid I/O operations are reported. (Of course, you cannot check that the correct exception is thrown!)
Note that the IO
action is run and its result is reduced (to
WHNF only). Note also that infinite loops are not exceptions
(unless the loop exhausts some resource).
If no exception is thrown, the actual value returned is recorded.
This requires adding a Show
constraint; see throws_IO
for a
function without this constraint.
In the TestM
monad
Types
Creation
throws_M :: TestM x -> TestSource
Check a TestM
action for exceptions.
Ordinarily, any test which throws an exception is deemed to have failed. However, this test passes if evaluating the action's result to WHNF causes an exception to be thrown. The test fails if no exception is thrown.
This can be useful for checking that a function rejects invalid input by throwing an exception, or that invalid I/O operations are reported. (Of course, you cannot check that the correct exception is thrown!)
Note that the TestM
action is run and its result is reduced (to
WHNF only). Note also that infinite loops are not exceptions
(unless the loop exhausts some resource).
If no exception is thrown, the actual value returned is not
recorded. See throwsM
for a function that does record the value.
This requires adding a Show
constraint.
throwsM :: Show x => TestM x -> TestSource
Check a TestM
action for exceptions.
Ordinarily, any test which throws an exception is deemed to have failed. However, this test passes if evaluating the action's result to WHNF causes an exception to be thrown. The test fails if no exception is thrown.
This can be useful for checking that a function rejects invalid input by throwing an exception, or that invalid I/O operations are reported. (Of course, you cannot check that the correct exception is thrown!)
Note that the TestM
action is run and its result is reduced (to
WHNF only). Note also that infinite loops are not exceptions
(unless the loop exhausts some resource).
If no exception is thrown, the actual value returns is recorded.
This requires adding a Show
constraint. See throws_M
for a
function without this constraint.
Annotations
inapplicableM :: TestM BoolSource
Mark the current test as "inapplicable" and return True
.
(See inapplicable
.)
temporaryM_ :: String -> String -> TestM ()Source
Note down a temporary intermediate value computed in the process of constructing a test.
The first String
is the name, and the second is some suitable
textual representation of the value.
Combining tests
Combine multiple tests into a single composite test.
The composite test fails if any of its constituent tests fail.
Whether the remaining tests are run depends on the testing mode
(the cfg_FailAbort
parameter in TestConfig
).
Essentially, this takes the logical-AND of several tests. You can
achieve the same result using the normal &&
operator or the and
function, operating on plain Bool
values rather than Test
objects. However, by turning subexpressions into Test
objects and
using tests
, the result of each subexpression will be logged to
file in addition to the overall result. Depending on the context,
that may or may not be helpful. You decide which you want.
alternatives :: [Test] -> TestSource
Create a composite test which passes if at least one child test passes.
All child tests are always run, regardless of error reporting mode. No test failures are reported, unless all children fail.
Essentially, this takes the logical-OR of several tests. You can
achieve the same result using the normal ||
operator or the or
function, operating on plain Bool
values rather than Test
objects. However, by turning subexpressions into Test
objects and
using alternatives
, the result of each subexpression will be
logged to file in addition to the overall result. Depending on the
context, that may or may not be helpful. You decide which you want.
Running tests
run_test :: Test -> IO BoolSource
Execute a test.
Ordinarily, "the test" will be a composite test created with
tests
, and will actually contain multiple sub-tests within it.
A Bool
value is returned indicating whether the test was
successful or not. Test progress information is printed to
stdout
. If any test fails, detailed information for that test is
printed to stdout
, and testing aborts.
For more control, see run_test_full
.
run_test_full :: TestConfig -> Test -> IO BoolSource
Execute a test.
Ordinarily, "the test" will be a composite test created with
tests
, and will actually contain multiple sub-tests within it.
A Bool
value is returned indicating whether the test was
successful or not. Test progress information is printed to
stdout
. Various testing options can be configured using the
TestConfig
argument. In particular, it is possible to log
detailed testing data to an XML log file (the cfg_LogFile
parameter).
The related run_test
function runs a test with the
default_config
test settings, which are useful for quick
interactive testing during a debugging session.
data TestConfig Source
Configuration settings for a test run.
TestConfig | |
|
default_config :: TestConfigSource
The default test configuration, as used by run_test
.
cfg_LogFile = Nothing cfg_LogXSL = Nothing cfg_FailReport = True cfg_FailAbort = True
You can use this as a starting point if you only want to customise a few test settings. (More options may be added in future.)
Mini-guide
Tests are represented by Test
objects.
You can run such a test using
.
This is intended for quickly running a test or two interactively to
see if those code changes you just made fixed the bug or not. For
running an entire test suite, you probably want run_test
:: Test
-> IO
Bool
run_test_full
.
This uses a TestConfig
object to set testing options; in
particular, detailed test information can be written to an XML log
file. Most test annotations only affect the log file, not the
visible output on stdout
.
You can create a test in several ways. The easiest is
.
For example, a simple hard-coded test might look like
test
:: Bool
-> Test
t_null_empty :: Test t_null_empty = test $ SET.null SET.empty
You can also add a test title:
t_null_empty :: Test t_null_empty = title "null empty" $ test $ SET.null SET.empty
Running this test produces a log entry which looks something like
<test> <title>null empty</title> <pure/> <result><pass/></result> </test>
(Assuming the implementation of your SET
module isn't broken,
obviously.) I like to set the test title
to be the Haskell
expression that I'm testing (or some approximation of it), but
there's no law that says you have to do it like that. You can name
it whatever you like.
More often, you'll have a function that takes some inputs and generates a test object. For example:
p_head_member :: Ord x => [x] -> Test p_head_member xs = title "head xs `member` fromList xs" $ argument "xs" xs $ let set = SET.fromList xs in temporary "fromList xs" set $ if LIST.null xs then inapplicable else test $ head xs `SET.member` set
Running this test might produce a log entry such as
<test> <title>head xs `member` fromList xs</title> <argument><name>xs</name><value>fromList [3,1,4]</value></argument> <temporary><name>fromList xs</name><value>fromList [1,3,4]</value></temporary> <pure/> <result><pass/></result> </test>
Of course, head
is not defined on an empty list. In that case,
the code above is configured to mark the test as inapplicable
.
The resulting log entry looks like
<test> <title>head xs `member` fromList xs</title> <argument><name>xs</name><value>fromList []</value></argument> <temporary><name>fromList xs</name><value>fromList []</value></temporary> <inapplicable/> <result><pass/></result> </test>
The test is still "successul", but we have marked it so that anyone reading the log will know that this particular test "did nothing".
For tests with a known correct answer, you can also use the
(
operator. For example,
?=
) :: Eq
x => x -> x -> Test
p_size :: Ord x => [x] -> Test p_size xs = title "size (fromList xs) == length (nub xs)" $ argument "xs" xs $ temporary "fromList xs" (SET.fromList xs) $ temporary "nub xs" (LIST.nub xs) $ SET.size (SET.fromList xs) ?= LIST.length (LIST.nub xs)
Running that might produce something like
<test> <title>size (fromList xs) == length (nub xs)</title> <argument><name>xs</name><value>[3,1,4,1]</value></argument> <temporary><name>fromList xs</name><value>fromList [1,3,4]</value></temporary> <temporary><name>nub xs</name><value>[3,1,4]</value></temporary> <pure/> <compare> <equal-to-target/> <target>3</target> <actual>3</actual> </compare> <result><pass/></result> </test>
In this instance, the output indicates that size (fromList xs)
was supposed to yield 3, and the value actually produced was also
3 - and hence, the test passed. There are several similar operators
such as ?>
, ?<
and so forth for inequality testing using an
Ord
instance.
One test case probably isn't particularly useful. But using the
function, you can combine multiple tests into a single composite
tests
:: [Test
] -> Test
Test
object. You can have multiple levels of this grouping to
organise related tests together. Composite tests can of course
have titles just like any other kind of test.
Note that this package (unlike, say, QuickCheck) provides no facility for generating test data automatically. That's your problem. You can solve it in several ways. One idea might be
t_size :: Test t_size = tests $ map p_size [ [], [5], [5,5], [4,6], [1..10] ]
Because this package doesn't deal with test data generation, you are free to use any approach you like. In particular, different properties can be tested with different test data (rather than relying on the type system to select test data for you), the data can be random or deterministic, and it can even be loaded from an external disk file if you like. Hell, you can even spawn an external OS process running a reference implementation, and then compare the results from your Haskell code against that. The choice is endless.
If you want to test code that needs to perform I/O, you can use the
function. Impure tests such as this can be annotated in all the
usual ways. For example,
testIO
:: IO
Bool
-> Test
p_makedir :: FilePath -> Test p_makedir dir = title "p_makedir" $ argument "dir" dir $ testIO $ do createDirectory dir doesDirectoryExist dir
If the test involves setup and cleanup steps, or just resource
allocation and subsequent deallocation, then you can build those
into the main test body, or you can use testIO3
instead. This has
the added advantage that it handles exceptions in the test body and
still runs the cleanup stage. (We are testing code which might
well crash, after all.) The choice is entirely up to you.
While you're in the IO
monad, you unfortunately cannot use
functions such as temporary
or note
. To get around this
limitation, you can use the TestM
monad. It implements liftIO
,
so you can still perform any I/O operations you want. But it also
provides temporaryM
and noteM
, which run inside the monad. The
function lets you wrap
everything up onto a regular testM
:: TestM
Bool
-> Test
Test
object when you're done.
Some functions (e.g., head
) are supposed to throw an exception
under certain circumstances. To check that they do (rather than,
say, return gibberish data instead), you can use throws
(or
throwsIO
in the IO
monad, or throwsM
in the TestM
monad).