With HUnit, as with JUnit, you can easily create tests, name them, group them into suites, and execute them, with the framework checking the results automatically. Test specification in HUnit is even more concise and flexible than in JUnit, thanks to the nature of the Haskell language. HUnit currently includes only a text-based test controller, but the framework is designed for easy extension. (Would anyone care to write a graphical test controller for HUnit?)
The next section helps you get started using HUnit in simple ways. Subsequent sections give details on writing tests and running tests. The document concludes with a section describing HUnit's constituent files and a section giving references to further information.
import HUnitDefine test cases as appropriate:
test1 = TestCase (assertEqual "for (foo 3)," (1,2) (foo 3)) test2 = TestCase (do (x,y) <- partA 3 assertEqual "for the first result of partA," 5 x b <- partB y assertBool ("(partB " ++ show y ++ ") failed") b)Name the test cases and group them together:
tests = TestList [TestLabel "test1" test1, TestLabel "test2" test2]Run the tests as a group. At a Haskell interpreter prompt, apply the function runTestTT to the collected tests. (The "TT" suggests text orientation with output to the terminal.)
> runTestTT tests Cases: 2 Tried: 2 Errors: 0 Failures: 0 >If the tests are proving their worth, you might see:
> runTestTT tests ### Failure in: 0:test1 for (foo 3), expected: (1,2) but got: (1,3) Cases: 2 Tried: 2 Errors: 0 Failures: 1 >Isn't that easy?
You can specify tests even more succinctly using operators and overloaded functions that HUnit provides:
tests = test [ "test1" ~: "(foo 3)" ~: (1,2) ~=? (foo 3), "test2" ~: do (x, y) <- partA 3 assertEqual "for the first result of partA," 5 x partB y @? "(partB " ++ show y ++ ") failed" ]Assuming the same test failures as before, you would see:
> runTestTT tests ### Failure in: 0:test1:(foo 3) expected: (1,2) but got: (1,3) Cases: 2 Tried: 2 Errors: 0 Failures: 1 >
type Assertion = IO ()An assertion is an IO computation that always produces a void result. Why is an assertion an IO computation? So that programs with real-world side effects can be tested. How does an assertion assert anything if it produces no useful result? The answer is that an assertion can signal failure by calling assertFailure.
assertFailure :: String -> Assertion assertFailure msg = ioError (userError ("HUnit:" ++ msg))(assertFailure msg) raises an exception. The string argument identifies the failure. The failure message is prefixed by "HUnit:" to mark it as an HUnit assertion failure message. The HUnit test framework interprets such an exception as indicating failure of the test whose execution raised the exception. (Note: The details concerning the implementation of assertFailure are subject to change and should not be relied upon.)
assertFailure can be used directly, but it is much more common to use it indirectly through other assertion functions that conditionally assert failure.
assertBool :: String -> Bool -> Assertion assertBool msg b = unless b (assertFailure msg) assertString :: String -> Assertion assertString s = unless (null s) (assertFailure s) assertEqual :: (Eq a, Show a) => String -> a -> a -> Assertion assertEqual preface expected actual = unless (actual == expected) (assertFailure msg) where msg = (if null preface then "" else preface ++ "\n") ++ "expected: " ++ show expected ++ "\n but got: " ++ show actualWith assertBool you give the assertion condition and failure message separately. With assertString the two are combined. With assertEqual you provide a "preface", an expected value, and an actual value; the failure message shows the two unequal values and is prefixed by the preface. Additional ways to create assertions are described later under Advanced Features.
Since assertions are IO computations, they may be combined--along with other IO computations--using (>>=), (>>), and the do notation. As long as its result is of type (IO ()), such a combination constitutes a single, collective assertion, incorporating any number of constituent assertions. The important features of such a collective assertion are that it fails if any of its constituent assertions is executed and fails, and that the first constituent assertion to fail terminates execution of the collective assertion. Such behavior is essential to specifying a test case.
A test case consists of a single, possibly collective, assertion. The possibly multiple constituent assertions in a test case's collective assertion are not independent. Their interdependence may be crucial to specifying correct operation for a test. A test case may involve a series of steps, each concluding in an assertion, where each step must succeed in order for the test case to continue. As another example, a test may require some "set up" to be performed that must be undone ("torn down" in JUnit parlance) once the test is complete. In this case, you could use Haskell's IO.bracket function to achieve the desired effect.
You can make a test case from an assertion by applying the TestCase constructor. For example, (TestCase (return ())) is a test case that never fails, and (TestCase (assertEqual "for x," 3 x)) is a test case that checks that the value of x is 3. Additional ways to create test cases are described later under Advanced Features.
In tune with the "composite" design pattern [1], a test is defined as a package of test cases. Concretely, a test is either a single test case, a group of tests, or either of the first two identified by a label.
data Test = TestCase Assertion | TestList [Test] | TestLabel String TestThere are three important features of this definition to note:
The number of test cases that a test comprises can be computed with testCaseCount.
testCaseCount :: Test -> Int
As mentioned above, a test is identified by its path in the test hierarchy.
data Node = ListItem Int | Label String deriving (Eq, Show, Read) type Path = [Node] -- Node order is from test case to root.Each occurrence of TestList gives rise to a ListItem and each occurrence of TestLabel gives rise to a Label. The ListItems by themselves ensure uniqueness among test case paths, while the Labels allow you to add mnemonic names for individual test cases and collections of them.
Note that the order of nodes in a path is reversed from what you might expect: The first node in the list is the one deepest in the tree. This order is a concession to efficiency: It allows common path prefixes to be shared.
The paths of the test cases that a test comprises can be computed with testCasePaths. The paths are listed in the order in which the corresponding test cases would be executed.
testCasePaths :: Test -> [Path]
The three variants of Test can be constructed simply by applying TestCase, TestList, and TestLabel to appropriate arguments. Additional ways to create tests are described later under Advanced Features.
The design of the type Test provides great conciseness, flexibility, and convenience in specifying tests. Moreover, the nature of Haskell significantly augments these qualities:
The following operators can be used to construct assertions.
infix 1 @?, @=?, @?= (@?) :: (AssertionPredicable t) => t -> String -> Assertion pred @? msg = assertionPredicate pred >>= assertBool msg (@=?) :: (Eq a, Show a) => a -> a -> Assertion expected @=? actual = assertEqual "" expected actual (@?=) :: (Eq a, Show a) => a -> a -> Assertion actual @?= expected = assertEqual "" expected actualYou provide a boolean condition and failure message separately to (@?), as for assertBool, but in a different order. The (@=?) and (@?=) operators provide shorthands for assertEqual when no preface is required. They differ only in the order in which the expected and actual values are provided. (The actual value--the uncertain one--goes on the "?" side of the operator.)
The (@?) operator's first argument is something from which an assertion predicate can be made, that is, its type must be AssertionPredicable.
type AssertionPredicate = IO Bool class AssertionPredicable t where assertionPredicate :: t -> AssertionPredicate instance AssertionPredicable Bool where assertionPredicate = return instance (AssertionPredicable t) => AssertionPredicable (IO t) where assertionPredicate = (>>= assertionPredicate)The overloaded assert function in the Assertable type class constructs an assertion.
class Assertable t where assert :: t -> Assertion instance Assertable () where assert = return instance Assertable Bool where assert = assertBool "" instance (ListAssertable t) => Assertable [t] where assert = listAssert instance (Assertable t) => Assertable (IO t) where assert = (>>= assert)The ListAssertable class allows assert to be applied to [Char] (that is, String).
class ListAssertable t where listAssert :: [t] -> Assertion instance ListAssertable Char where listAssert = assertStringWith the above declarations, (assert ()), (assert True), and (assert "") (as well as IO forms of these values, such as (return ())) are all assertions that never fail, while (assert False) and (assert "some failure message") (and their IO forms) are assertions that always fail. You may define additional instances for the type classes Assertable, ListAssertable, and AssertionPredicable if that should be useful in your application.
The overloaded test function in the Testable type class constructs a test.
class Testable t where test :: t -> Test instance Testable Test where test = id instance (Assertable t) => Testable (IO t) where test = TestCase . assert instance (Testable t) => Testable [t] where test = TestList . map testThe test function makes a test from either an Assertion (using TestCase), a list of Testable items (using TestList), or a Test (making no change).
The following operators can be used to construct tests.
infix 1 ~?, ~=?, ~?= infixr 0 ~: (~?) :: (AssertionPredicable t) => t -> String -> Test pred ~? msg = TestCase (pred @? msg) (~=?) :: (Eq a, Show a) => a -> a -> Test expected ~=? actual = TestCase (expected @=? actual) (~?=) :: (Eq a, Show a) => a -> a -> Test actual ~?= expected = TestCase (actual @?= expected) (~:) :: (Testable t) => String -> t -> Test label ~: t = TestLabel label (test t)(~?), (~=?), and (~?=) each make an assertion, as for (@?), (@=?), and (@?=), respectively, and then a test case from that assertion. (~:) attaches a label to something that is Testable. You may define additional instances for the type class Testable should that be useful.
The execution of a test (a value of type Test) involves the serial execution (in the IO monad) of its constituent test cases. The test cases are executed in a depth-first, left-to-right order. During test execution, four counts of test cases are maintained:
data Counts = Counts { cases, tried, errors, failures :: Int } deriving (Eq, Show, Read)
As test execution proceeds, three kinds of reporting event are communicated to the test controller. (What the controller does in response to the reporting events depends on the controller.)
runTestText :: PutText st -> Test -> IO (Counts, st)runTestText is generalized on a reporting scheme given as its first argument. During execution of the test given as its second argument, the controller creates a string for each reporting event and processes it according to the reporting scheme. When test execution is complete, the controller returns the final counts along with the final state for the reporting scheme.
The strings for the three kinds of reporting event are as follows.
The function showCounts shows a set of counts.
showCounts :: Counts -> StringThe form of its result is "Cases: cases Tried: tried Errors: errors Failures: failures" where cases, tried, errors, and failures are the count values.
The function showPath shows a test case path.
showPath :: Path -> StringThe nodes in the path are reversed (so that the path reads from the root down to the test case), and the representations for the nodes are joined by ':' separators. The representation for (ListItem n) is (show n). The representation for (Label label) is normally label. However, if label contains a colon or if (show label) is different from label surrounded by quotation marks--that is, if any ambiguity could exist--then (Label label) is represented as (show label).
HUnit includes two reporting schemes for the text-based test controller. You may define others if you wish.
putTextToHandle :: Handle -> Bool -> PutText IntputTextToHandle writes error and failure reports, plus a report of the final counts, to the given handle. Each of these reports is terminated by a newline. In addition, if the given flag is True, it writes start reports to the handle as well. A start report, however, is not terminated by a newline. Before the next report is written, the start report is "erased" with an appropriate sequence of carriage return and space characters. Such overwriting realizes its intended effect on terminal devices.
putTextToShowS :: PutText ShowSputTextToShowS ignores start reports and simply accumulates error and failure reports, terminating them with newlines. The accumulated reports are returned (as the second element of the pair returned by runTestText) as a ShowS function (that is, one with type (String -> String)) whose first argument is a string to be appended to the accumulated report lines.
HUnit provides a shorthand for the most common use of the text-based test controller.
runTestTT :: Test -> IO CountsrunTestTT invokes runTestText, specifying (putTextToHandle stderr True) for the reporting scheme, and returns the final counts from the test execution.
HUnit development is supported by
[$Revision: 1.1 $ $Date: 2002/02/21 19:09:27 $]