Blame README.md

Packit bc3140
# HUnit User's Guide
Packit bc3140
Packit bc3140
HUnit is a unit testing framework for Haskell, inspired by the JUnit tool for Java. This
Packit bc3140
guide describes how to use HUnit, assuming you are familiar with Haskell, though not
Packit bc3140
necessarily with JUnit. You can obtain HUnit, including this guide, at
Packit bc3140
[https://github.com/hspec/HUnit](https://github.com/hspec/HUnit)
Packit bc3140
Packit bc3140
## Introduction
Packit bc3140
A test-centered methodology for software development is most effective when tests are
Packit bc3140
easy to create, change, and execute. The [JUnit](www.junit.org) tool
Packit bc3140
pioneered support for test-first development in [Java](http://java.sun.com).
Packit bc3140
HUnit is an adaptation of JUnit to Haskell, a general-purpose, purely functional
Packit bc3140
programming language. (To learn more about Haskell, see [www.haskell.org](http://www.haskell.org)).
Packit bc3140
Packit bc3140
With HUnit, as with JUnit, you can easily create tests, name them, group them into
Packit bc3140
suites, and execute them, with the framework checking the results automatically. Test
Packit bc3140
specification in HUnit is even more concise and flexible than in JUnit, thanks to the
Packit bc3140
nature of the Haskell language. HUnit currently includes only a text-based test
Packit bc3140
controller, but the framework is designed for easy extension. (Would anyone care to
Packit bc3140
write a graphical test controller for HUnit?)
Packit bc3140
Packit bc3140
The next section helps you get started using HUnit in simple ways. Subsequent sections
Packit bc3140
give details on [writing tests](#writing-tests) and [running tests](#running-tests).
Packit bc3140
The document concludes with a section describing HUnit's [constituent files](#constituent-files)
Packit bc3140
and a section giving [references](#references) to further information.
Packit bc3140
Packit bc3140
## Getting Started
Packit bc3140
Packit bc3140
In the Haskell module where your tests will reside, import module `Test.HUnit`:
Packit bc3140
Packit bc3140
```haskell
Packit bc3140
import Test.HUnit
Packit bc3140
```
Packit bc3140
Packit bc3140
Define test cases as appropriate:
Packit bc3140
Packit bc3140
```haskell
Packit bc3140
test1 = TestCase (assertEqual "for (foo 3)," (1,2) (foo 3))
Packit bc3140
test2 = TestCase (do (x,y) <- partA 3
Packit bc3140
                     assertEqual "for the first result of partA," 5 x
Packit bc3140
                     b <- partB y
Packit bc3140
                     assertBool ("(partB " ++ show y ++ ") failed") b)
Packit bc3140
```
Packit bc3140
Packit bc3140
Name the test cases and group them together:
Packit bc3140
Packit bc3140
```haskell
Packit bc3140
tests = TestList [TestLabel "test1" test1, TestLabel "test2" test2]
Packit bc3140
```
Packit bc3140
Packit bc3140
Run the tests as a group. At a Haskell interpreter prompt, apply the
Packit bc3140
function `runTestTT` to the collected tests. (The `TT` suggests
Packit bc3140
**T**ext orientation with output to the **T**erminal.)
Packit bc3140
Packit bc3140
```haskell
Packit bc3140
> runTestTT tests
Packit bc3140
Cases: 2  Tried: 2  Errors: 0  Failures: 0
Packit bc3140
>
Packit bc3140
```
Packit bc3140
Packit bc3140
If the tests are proving their worth, you might see:
Packit bc3140
Packit bc3140
```haskell
Packit bc3140
> runTestTT tests
Packit bc3140
### Failure in: 0:test1
Packit bc3140
for (foo 3),
Packit bc3140
expected: (1,2)
Packit bc3140
 but got: (1,3)
Packit bc3140
Cases: 2  Tried: 2  Errors: 0  Failures: 1
Packit bc3140
>
Packit bc3140
```
Packit bc3140
Packit bc3140
Isn't that easy?
Packit bc3140
Packit bc3140
You can specify tests even more succinctly using operators and
Packit bc3140
overloaded functions that HUnit provides:
Packit bc3140
Packit bc3140
```haskell
Packit bc3140
tests = test [ "test1" ~: "(foo 3)" ~: (1,2) ~=? (foo 3),
Packit bc3140
               "test2" ~: do (x, y) <- partA 3
Packit bc3140
                             assertEqual "for the first result of partA," 5 x
Packit bc3140
                             partB y @? "(partB " ++ show y ++ ") failed" ]
Packit bc3140
```
Packit bc3140
Packit bc3140
Assuming the same test failures as before, you would see:
Packit bc3140
Packit bc3140
```haskell
Packit bc3140
> runTestTT tests
Packit bc3140
### Failure in: 0:test1:(foo 3)
Packit bc3140
expected: (1,2)
Packit bc3140
 but got: (1,3)
Packit bc3140
Cases: 2  Tried: 2  Errors: 0  Failures: 1
Packit bc3140
>
Packit bc3140
```
Packit bc3140
Packit bc3140
## Writing Tests
Packit bc3140
Packit bc3140
Tests are specified compositionally. [Assertions](#assertions) are
Packit bc3140
combined to make a [test case](#test-case), and test cases are combined
Packit bc3140
into [tests](#tests). HUnit also provides [advanced
Packit bc3140
features](#advanced-features) for more convenient test specification.
Packit bc3140
Packit bc3140
### Assertions
Packit bc3140
Packit bc3140
 The basic building block of a test is an **assertion**.
Packit bc3140
Packit bc3140
```haskell
Packit bc3140
type Assertion = IO ()
Packit bc3140
```
Packit bc3140
Packit bc3140
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`.
Packit bc3140
Packit bc3140
```haskell
Packit bc3140
assertFailure :: String -> Assertion
Packit bc3140
assertFailure msg = ioError (userError ("HUnit:" ++ msg))
Packit bc3140
```
Packit bc3140
Packit bc3140
`(assertFailure msg)` raises an exception. The string argument identifies the
Packit bc3140
 failure. The failure message is prefixed by "`HUnit:`" to mark it as an HUnit
Packit bc3140
 assertion failure message. The HUnit test framework interprets such an exception as
Packit bc3140
 indicating failure of the test whose execution raised the exception. (Note: The details
Packit bc3140
 concerning the implementation of `assertFailure` are subject to change and should
Packit bc3140
 not be relied upon.)
Packit bc3140
Packit bc3140
`assertFailure` can be used directly, but it is much more common to use it
Packit bc3140
 indirectly through other assertion functions that conditionally assert failure.
Packit bc3140
Packit bc3140
```haskell
Packit bc3140
assertBool :: String -> Bool -> Assertion
Packit bc3140
assertBool msg b = unless b (assertFailure msg)
Packit bc3140
Packit bc3140
assertString :: String -> Assertion
Packit bc3140
assertString s = unless (null s) (assertFailure s)
Packit bc3140
Packit bc3140
assertEqual :: (Eq a, Show a) => String -> a -> a -> Assertion
Packit bc3140
assertEqual preface expected actual =
Packit bc3140
  unless (actual == expected) (assertFailure msg)
Packit bc3140
 where msg = (if null preface then "" else preface ++ "\n") ++
Packit bc3140
             "expected: " ++ show expected ++ "\n but got: " ++ show actual
Packit bc3140
```
Packit bc3140
Packit bc3140
With `assertBool` you give the assertion condition and failure message separately.
Packit bc3140
 With `assertString` the two are combined. With `assertEqual` you provide a
Packit bc3140
 "preface", an expected value, and an actual value; the failure message shows the two
Packit bc3140
 unequal values and is prefixed by the preface. Additional ways to create assertions are
Packit bc3140
 described later under [Avanced Features](#advanced-features)
Packit bc3140
Packit bc3140
Since assertions are `IO` computations, they may be combined--along with other
Packit bc3140
     `IO` computations--using `(>>=)`, `(>>)`, and the `do`
Packit bc3140
 notation. As long as its result is of type `(IO ())`, such a combination
Packit bc3140
 constitutes a single, collective assertion, incorporating any number of constituent
Packit bc3140
 assertions. The important features of such a collective assertion are that it fails if
Packit bc3140
 any of its constituent assertions is executed and fails, and that the first constituent
Packit bc3140
 assertion to fail terminates execution of the collective assertion. Such behavior is
Packit bc3140
 essential to specifying a test case.
Packit bc3140
Packit bc3140
### Test Case
Packit bc3140
Packit bc3140
A **test case** is the unit of test execution. That is, distinct test cases are
Packit bc3140
 executed independently. The failure of one is independent of the failure of any other.
Packit bc3140
Packit bc3140
A test case consists of a single, possibly collective, assertion. The possibly multiple
Packit bc3140
 constituent assertions in a test case's collective assertion are **not** independent.
Packit bc3140
 Their interdependence may be crucial to specifying correct operation for a test. A test
Packit bc3140
 case may involve a series of steps, each concluding in an assertion, where each step
Packit bc3140
 must succeed in order for the test case to continue. As another example, a test may
Packit bc3140
 require some "set up" to be performed that must be undone ("torn down" in JUnit
Packit bc3140
 parlance) once the test is complete. In this case, you could use Haskell's
Packit bc3140
     `IO.bracket` function to achieve the desired effect.
Packit bc3140
Packit bc3140
You can make a test case from an assertion by applying the `TestCase` constructor.
Packit bc3140
 For example, `(TestCase (return ()))` is a test case that never
Packit bc3140
 fails, and `(TestCase (assertEqual "for x," 3 x))`
Packit bc3140
 is a test case that checks that the value of `x` is 3.  Additional ways
Packit bc3140
 to create test cases are described later under [Advanced Features](#advanced-eatures).
Packit bc3140
Packit bc3140
### Tests
Packit bc3140
Packit bc3140
As soon as you have more than one test, you'll want to name them to tell them apart. As
Packit bc3140
 soon as you have more than several tests, you'll want to group them to process them more
Packit bc3140
 easily. So, naming and grouping are the two keys to managing collections of tests.
Packit bc3140
Packit bc3140
In tune with the "composite" design pattern [1], a
Packit bc3140
 **test** is defined as a package of test cases. Concretely, a test is either a single
Packit bc3140
 test case, a group of tests, or either of the first two identified by a label.
Packit bc3140
Packit bc3140
```haskell
Packit bc3140
data Test = TestCase Assertion
Packit bc3140
          | TestList [Test]
Packit bc3140
          | TestLabel String Test
Packit bc3140
```
Packit bc3140
Packit bc3140
There are three important features of this definition to note:
Packit bc3140
Packit bc3140
Packit bc3140
* A `TestList` consists of a list of tests rather than a list of test cases.
Packit bc3140
   This means that the structure of a `Test` is actually a tree. Using a
Packit bc3140
   hierarchy helps organize tests just as it helps organize files in a file system.
Packit bc3140
* A `TestLabel` is attached to a test rather than to a test case. This means
Packit bc3140
   that all nodes in the test tree, not just test case (leaf) nodes, can be labeled.
Packit bc3140
   Hierarchical naming helps organize tests just as it helps organize files in a file
Packit bc3140
   system.
Packit bc3140
* A `TestLabel` is separate from both `TestCase` and `TestList`.
Packit bc3140
   This means that labeling is optional everywhere in the tree. Why is this a good
Packit bc3140
   thing? Because of the hierarchical structure of a test, each constituent test case
Packit bc3140
   is uniquely identified by its path in the tree, ignoring all labels. Sometimes a
Packit bc3140
   test case's path (or perhaps its subpath below a certain node) is a perfectly
Packit bc3140
   adequate "name" for the test case (perhaps relative to a certain node). In this
Packit bc3140
   case, creating a label for the test case is both unnecessary and inconvenient.
Packit bc3140
Packit bc3140
Packit bc3140
The number of test cases that a test comprises can be computed with `testCaseCount`.
Packit bc3140
Packit bc3140
```haskell
Packit bc3140
testCaseCount :: Test -> Int
Packit bc3140
```
Packit bc3140
Packit bc3140
As mentioned above, a test is identified by its **path** in the test hierarchy.
Packit bc3140
Packit bc3140
```haskell
Packit bc3140
data Node  = ListItem Int | Label String
Packit bc3140
  deriving (Eq, Show, Read)
Packit bc3140
Packit bc3140
type Path = [Node]    -- Node order is from test case to root.
Packit bc3140
```
Packit bc3140
Packit bc3140
Each occurrence of `TestList` gives rise to a `ListItem` and each
Packit bc3140
 occurrence of `TestLabel` gives rise to a `Label`. The `ListItem`s
Packit bc3140
 by themselves ensure uniqueness among test case paths, while the `Label`s allow
Packit bc3140
 you to add mnemonic names for individual test cases and collections of them.
Packit bc3140
Packit bc3140
Note that the order of nodes in a path is reversed from what you might expect: The first
Packit bc3140
 node in the list is the one deepest in the tree. This order is a concession to
Packit bc3140
 efficiency: It allows common path prefixes to be shared.
Packit bc3140
Packit bc3140
The paths of the test cases that a test comprises can be computed with
Packit bc3140
 `testCasePaths`. The paths are listed in the order in which the corresponding
Packit bc3140
 test cases would be executed.
Packit bc3140
Packit bc3140
```haskell
Packit bc3140
testCasePaths :: Test -> [Path]
Packit bc3140
```
Packit bc3140
Packit bc3140
The three variants of `Test` can be constructed simply by applying
Packit bc3140
 `TestCase`, `TestList`, and `TestLabel` to appropriate arguments.
Packit bc3140
 Additional ways to create tests are described later under [Advanced Features](#advanced-features).
Packit bc3140
Packit bc3140
The design of the type `Test` provides great conciseness, flexibility, and
Packit bc3140
 convenience in specifying tests. Moreover, the nature of Haskell significantly augments
Packit bc3140
 these qualities:
Packit bc3140
Packit bc3140
* Combining assertions and other code to construct test cases is easy with the
Packit bc3140
    `IO` monad.
Packit bc3140
* Using overloaded functions and special operators (see below), specification of
Packit bc3140
    assertions and tests is extremely compact.
Packit bc3140
* Structuring a test tree by value, rather than by name as in JUnit, provides for more
Packit bc3140
    convenient, flexible, and robust test suite specification. In particular, a test
Packit bc3140
    suite can more easily be computed "on the fly" than in other test frameworks.
Packit bc3140
* Haskell's powerful abstraction facilities provide unmatched support for test
Packit bc3140
    refactoring.
Packit bc3140
Packit bc3140
### Advanced Features
Packit bc3140
Packit bc3140
HUnit provides additional features for specifying assertions and tests more conveniently
Packit bc3140
 and concisely. These facilities make use of Haskell type classes.
Packit bc3140
Packit bc3140
The following operators can be used to construct assertions.
Packit bc3140
Packit bc3140
```haskell
Packit bc3140
infix 1 @?, @=?, @?=
Packit bc3140
Packit bc3140
(@?) :: (AssertionPredicable t) => t -> String -> Assertion
Packit bc3140
pred @? msg = assertionPredicate pred >>= assertBool msg
Packit bc3140
Packit bc3140
(@=?) :: (Eq a, Show a) => a -> a -> Assertion
Packit bc3140
expected @=? actual = assertEqual "" expected actual
Packit bc3140
Packit bc3140
(@?=) :: (Eq a, Show a) => a -> a -> Assertion
Packit bc3140
actual @?= expected = assertEqual "" expected actual
Packit bc3140
```
Packit bc3140
Packit bc3140
You provide a boolean condition and failure message separately to `(@?)`, as for
Packit bc3140
     `assertBool`, but in a different order. The `(@=?)` and `(@?=)`
Packit bc3140
 operators provide shorthands for `assertEqual` when no preface is required. They
Packit bc3140
 differ only in the order in which the expected and actual values are provided. (The
Packit bc3140
 actual value--the uncertain one--goes on the "?" side of the operator.)
Packit bc3140
Packit bc3140
The `(@?)` operator's first argument is something from which an assertion
Packit bc3140
 predicate can be made, that is, its type must be `AssertionPredicable`.
Packit bc3140
Packit bc3140
```haskell
Packit bc3140
type AssertionPredicate = IO Bool
Packit bc3140
Packit bc3140
class AssertionPredicable t
Packit bc3140
 where assertionPredicate :: t -> AssertionPredicate
Packit bc3140
Packit bc3140
instance AssertionPredicable Bool
Packit bc3140
 where assertionPredicate = return
Packit bc3140
Packit bc3140
instance (AssertionPredicable t) => AssertionPredicable (IO t)
Packit bc3140
 where assertionPredicate = (>>= assertionPredicate)
Packit bc3140
```
Packit bc3140
Packit bc3140
The overloaded `assert` function in the `Assertable` type class constructs
Packit bc3140
 an assertion.
Packit bc3140
Packit bc3140
```haskell
Packit bc3140
class Assertable t
Packit bc3140
 where assert :: t -> Assertion
Packit bc3140
Packit bc3140
instance Assertable ()
Packit bc3140
 where assert = return
Packit bc3140
Packit bc3140
instance Assertable Bool
Packit bc3140
 where assert = assertBool ""
Packit bc3140
Packit bc3140
instance (ListAssertable t) => Assertable [t]
Packit bc3140
 where assert = listAssert
Packit bc3140
Packit bc3140
instance (Assertable t) => Assertable (IO t)
Packit bc3140
 where assert = (>>= assert)
Packit bc3140
```
Packit bc3140
Packit bc3140
The `ListAssertable` class allows `assert` to be applied to `[Char]`
Packit bc3140
 (that is, `String`).
Packit bc3140
Packit bc3140
```haskell
Packit bc3140
class ListAssertable t
Packit bc3140
 where listAssert :: [t] -> Assertion
Packit bc3140
Packit bc3140
instance ListAssertable Char
Packit bc3140
 where listAssert = assertString
Packit bc3140
```
Packit bc3140
Packit bc3140
With the above declarations, `(assert ())`,
Packit bc3140
 `(assert True)`, and `(assert "")` (as well as
Packit bc3140
 `IO` forms of these values, such as `(return ())`) are all
Packit bc3140
 assertions that never fail, while `(assert False)` and
Packit bc3140
     `(assert "some failure message")` (and their
Packit bc3140
     `IO` forms) are assertions that always fail. You may define additional
Packit bc3140
 instances for the type classes `Assertable`, `ListAssertable`, and
Packit bc3140
     `AssertionPredicable` if that should be useful in your application.
Packit bc3140
Packit bc3140
The overloaded `test` function in the `Testable` type class constructs a
Packit bc3140
 test.
Packit bc3140
Packit bc3140
```haskell
Packit bc3140
class Testable t
Packit bc3140
 where test :: t -> Test
Packit bc3140
Packit bc3140
instance Testable Test
Packit bc3140
 where test = id
Packit bc3140
Packit bc3140
instance (Assertable t) => Testable (IO t)
Packit bc3140
 where test = TestCase . assert
Packit bc3140
Packit bc3140
instance (Testable t) => Testable [t]
Packit bc3140
 where test = TestList . map test
Packit bc3140
```
Packit bc3140
Packit bc3140
The `test` function makes a test from either an `Assertion` (using
Packit bc3140
     `TestCase`), a list of `Testable` items (using `TestList`), or
Packit bc3140
 a `Test` (making no change).
Packit bc3140
Packit bc3140
The following operators can be used to construct tests.
Packit bc3140
Packit bc3140
```haskell
Packit bc3140
infix  1 ~?, ~=?, ~?=
Packit bc3140
infixr 0 ~:
Packit bc3140
Packit bc3140
(~?) :: (AssertionPredicable t) => t -> String -> Test
Packit bc3140
pred ~? msg = TestCase (pred @? msg)
Packit bc3140
Packit bc3140
(~=?) :: (Eq a, Show a) => a -> a -> Test
Packit bc3140
expected ~=? actual = TestCase (expected @=? actual)
Packit bc3140
Packit bc3140
(~?=) :: (Eq a, Show a) => a -> a -> Test
Packit bc3140
actual ~?= expected = TestCase (actual @?= expected)
Packit bc3140
Packit bc3140
(~:) :: (Testable t) => String -> t -> Test
Packit bc3140
label ~: t = TestLabel label (test t)
Packit bc3140
```
Packit bc3140
Packit bc3140
`(~?)`, `(~=?)`, and `(~?=)` each make an assertion, as for
Packit bc3140
 `(@?)`, `(@=?)`, and `(@?=)`, respectively, and then a test case
Packit bc3140
 from that assertion. `(~:)` attaches a label to something that is
Packit bc3140
 `Testable`. You may define additional instances for the type class
Packit bc3140
 `Testable` should that be useful.
Packit bc3140
Packit bc3140
## Running Tests
Packit bc3140
Packit bc3140
HUnit is structured to support multiple test controllers. The first
Packit bc3140
 subsection below describes the [test execution](#test-execution)
Packit bc3140
 characteristics common to all test controllers. The second subsection
Packit bc3140
 describes the text-based controller that is included with HUnit.
Packit bc3140
Packit bc3140
## Test Execution
Packit bc3140
Packit bc3140
All test controllers share a common test execution model. They differ only in how the
Packit bc3140
 results of test execution are shown.
Packit bc3140
Packit bc3140
The execution of a test (a value of type `Test`) involves the serial execution (in
Packit bc3140
 the `IO` monad) of its constituent test cases. The test cases are executed in a
Packit bc3140
 depth-first, left-to-right order. During test execution, four counts of test cases are
Packit bc3140
 maintained:
Packit bc3140
Packit bc3140
```haskell
Packit bc3140
data Counts = Counts { cases, tried, errors, failures :: Int }
Packit bc3140
  deriving (Eq, Show, Read)
Packit bc3140
```
Packit bc3140
Packit bc3140
Packit bc3140
* `cases` is the number of test cases included in the test. This number is a
Packit bc3140
    static property of a test and remains unchanged during test execution.
Packit bc3140
* `tried` is the number of test cases that have been executed so far during the
Packit bc3140
    test execution.
Packit bc3140
* `errors` is the number of test cases whose execution ended with an unexpected
Packit bc3140
    exception being raised. Errors indicate problems with test cases, as opposed to the
Packit bc3140
    code under test.
Packit bc3140
* `failures` is the number of test cases whose execution asserted failure.
Packit bc3140
    Failures indicate problems with the code under test.
Packit bc3140
Packit bc3140
Packit bc3140
Why is there no count for test case successes? The technical reason is that the counts
Packit bc3140
 are maintained such that the number of test case successes is always equal to
Packit bc3140
     `(tried - (errors + failures))`. The
Packit bc3140
 psychosocial reason is that, with test-centered development and the expectation that
Packit bc3140
 test failures will be few and short-lived, attention should be focused on the failures
Packit bc3140
 rather than the successes.
Packit bc3140
Packit bc3140
As test execution proceeds, three kinds of reporting event are communicated to the test
Packit bc3140
 controller. (What the controller does in response to the reporting events depends on the
Packit bc3140
 controller.)
Packit bc3140
Packit bc3140
* *start* -- Just prior to initiation of a test case, the path of the test case
Packit bc3140
    and the current counts (excluding the current test case) are reported.
Packit bc3140
* *error* -- When a test case terminates with an error, the error message is
Packit bc3140
    reported, along with the test case path and current counts (including the current
Packit bc3140
    test case).
Packit bc3140
* *failure* -- When a test case terminates with a failure, the failure message is
Packit bc3140
    reported, along with the test case path and current counts (including the current
Packit bc3140
    test case).
Packit bc3140
Packit bc3140
Typically, a test controller shows *error* and *failure* reports immediately
Packit bc3140
 but uses the *start* report merely to update an indication of overall test
Packit bc3140
 execution progress.
Packit bc3140
Packit bc3140
### Text-Based Controller
Packit bc3140
Packit bc3140
A text-based test controller is included with HUnit.
Packit bc3140
Packit bc3140
```haskell
Packit bc3140
runTestText :: PutText st -> Test -> IO (Counts, st)
Packit bc3140
```
Packit bc3140
Packit bc3140
`runTestText` is generalized on a *reporting scheme* given as its first
Packit bc3140
 argument. During execution of the test given as its second argument, the controller
Packit bc3140
 creates a string for each reporting event and processes it according to the reporting
Packit bc3140
 scheme. When test execution is complete, the controller returns the final counts along
Packit bc3140
 with the final state for the reporting scheme.
Packit bc3140
Packit bc3140
The strings for the three kinds of reporting event are as follows.
Packit bc3140
Packit bc3140
* A *start* report is the result of the function `showCounts` applied to
Packit bc3140
    the counts current immediately prior to initiation of the test case being started.
Packit bc3140
* An *error* report is of the form
Packit bc3140
            "`Error in:   *path*\n*message*`",
Packit bc3140
    where *path* is the path of the test case in error, as shown by
Packit bc3140
    `showPath`, and *message* is a message describing the error. If the path
Packit bc3140
    is empty, the report has the form "`Error:\n*message*`".
Packit bc3140
* A *failure* report is of the form
Packit bc3140
            "`Failure in: *path*\n*message*`", where
Packit bc3140
        *path* is the path of the test case in error, as shown by
Packit bc3140
    `showPath`, and *message* is the failure message. If the path is empty,
Packit bc3140
    the report has the form "`Failure:\n*message*`".
Packit bc3140
Packit bc3140
The function `showCounts` shows a set of counts.
Packit bc3140
Packit bc3140
```haskell
Packit bc3140
showCounts :: Counts -> String
Packit bc3140
```
Packit bc3140
Packit bc3140
The form of its result is
Packit bc3140
`Cases: *cases*  Tried: *tried*  Errors: *errors*  Failures: *failures*`
Packit bc3140
where *cases*, *tried*, *errors*, and *failures* are the count values.
Packit bc3140
Packit bc3140
The function `showPath` shows a test case path.
Packit bc3140
Packit bc3140
```haskell
Packit bc3140
 showPath :: Path -> String
Packit bc3140
```
Packit bc3140
Packit bc3140
The nodes in the path are reversed (so that the path reads from the root down to the test
Packit bc3140
 case), and the representations for the nodes are joined by '`:`' separators. The
Packit bc3140
 representation for `(ListItem *n*)` is `(show n)`. The representation
Packit bc3140
 for `(Label *label*)` is normally *label*. However, if *label*
Packit bc3140
 contains a colon or if `(show *label*)` is different from *label*
Packit bc3140
 surrounded by quotation marks--that is, if any ambiguity could exist--then `(Label
Packit bc3140
         *label*)` is represented as `(show *label*)`.
Packit bc3140
Packit bc3140
HUnit includes two reporting schemes for the text-based test controller. You may define
Packit bc3140
 others if you wish.
Packit bc3140
Packit bc3140
```haskell
Packit bc3140
putTextToHandle :: Handle -> Bool -> PutText Int
Packit bc3140
```
Packit bc3140
Packit bc3140
`putTextToHandle` writes error and failure reports, plus a report of the final
Packit bc3140
 counts, to the given handle. Each of these reports is terminated by a newline. In
Packit bc3140
 addition, if the given flag is `True`, it writes start reports to the handle as
Packit bc3140
 well. A start report, however, is not terminated by a newline. Before the next report is
Packit bc3140
 written, the start report is "erased" with an appropriate sequence of carriage return
Packit bc3140
 and space characters. Such overwriting realizes its intended effect on terminal devices.
Packit bc3140
Packit bc3140
```haskell
Packit bc3140
putTextToShowS :: PutText ShowS
Packit bc3140
```
Packit bc3140
Packit bc3140
`putTextToShowS` ignores start reports and simply accumulates error and failure
Packit bc3140
 reports, terminating them with newlines. The accumulated reports are returned (as the
Packit bc3140
 second element of the pair returned by `runTestText`) as a `ShowS`
Packit bc3140
 function (that is, one with type `(String -> String)`) whose
Packit bc3140
 first argument is a string to be appended to the accumulated report lines.
Packit bc3140
Packit bc3140
HUnit provides a shorthand for the most common use of the text-based test controller.
Packit bc3140
Packit bc3140
```haskell
Packit bc3140
runTestTT :: Test -> IO Counts
Packit bc3140
```
Packit bc3140
Packit bc3140
`runTestTT` invokes `runTestText`, specifying `(putTextToHandle stderr
Packit bc3140
True)` for the reporting scheme, and returns the final counts from the
Packit bc3140
test execution.
Packit bc3140
Packit bc3140
## References
Packit bc3140
Packit bc3140
* [1] Gamma, E., et al. Design Patterns: Elements of Reusable Object-Oriented Software, Addison-Wesley, Reading, MA, 1995: The classic book describing design patterns in an object-oriented context.
Packit bc3140
Packit bc3140
* [junit.org](http://www.junit.org): Web page for JUnit, the tool after which HUnit is modeled.
Packit bc3140
Packit bc3140
* [http://junit.sourceforge.net/doc/testinfected/testing.htm](http://junit.sourceforge.net/doc/testinfected/testing.htm): A good introduction to test-first development and the use of JUnit.
Packit bc3140
Packit bc3140
* [http://junit.sourceforge.net/doc/cookstour/cookstour.htm](http://junit.sourceforge.net/doc/cookstour/cookstour.htm): A description of the internal structure of JUnit. Makes for an interesting comparison between JUnit and HUnit.
Packit bc3140
Packit bc3140
The HUnit software and this guide were written by Dean Herington [heringto@cs.unc.edu](mailto:heringto@cs.unc.edu)