Difference between revisions of "HUnit 1.0 User's Guide"

From HaskellWiki
Jump to navigation Jump to search
(wikified Getting Started)
m (remove stray “</p>”)
(12 intermediate revisions by 4 users not shown)
Line 5: Line 5:
 
== Introduction ==
 
== Introduction ==
   
A test-centered methodology for software development is most effective when tests are easy to create, change, and execute. The [http://www.junit.org JUnit] tool pioneered support for test-first development in [http://java.sun.com Java]. HUnit is an adaptation of JUnit to Haskell, a general-purpose, purely functional programming language. (To learn more about Haskell, see [http://www.haskell.org http://www.haskell.org].)
+
A test-centered methodology for software development is most effective when tests are easy to create, change, and execute. The [https://en.wikipedia.org/wiki/SUnit Sunit] tool pioneered support for test-first development in Smalltalk. HUnit is an adaptation of the unit testing framework to Haskell, a general-purpose, purely functional programming language. (To learn more about Haskell, see [http://www.haskell.org http://www.haskell.org].). Unit testing frameworks for various languages are referred to as [https://en.wikipedia.org/wiki/XUnit xUnit].
   
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?)
+
With HUnit, as with [https://en.wikipedia.org/wiki/XUnit xUnit], you can easily create tests, name them, group them into suites, and execute them, with the framework checking the results automatically. 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 | writing tests]] and [[#Running Tests | running tests]]. The document concludes with a section describing HUnit's [[#ConstituentFiles | constituent files]] and a section giving [[#References | references]] to further information.
 
The next section helps you get started using HUnit in simple ways. Subsequent sections give details on [[#Writing Tests | writing tests]] and [[#Running Tests | running tests]]. The document concludes with a section describing HUnit's [[#ConstituentFiles | constituent files]] and a section giving [[#References | references]] to further information.
Line 13: Line 13:
 
== Getting Started ==
 
== Getting Started ==
   
In the Haskell module where your tests will reside, import module <tt>Test.HUnit</tt>:
+
In the Haskell module where your tests will reside, import module <code>Test.HUnit</code>:
   
<pre>
+
<haskell>
import Test.HUnit
+
import Test.HUnit
</pre>
+
</haskell>
   
 
Define test cases as appropriate:
 
Define test cases as appropriate:
   
<pre>
+
<haskell>
test1 = TestCase (assertEqual "for (foo 3)," (1,2) (foo 3))
+
test1 = TestCase (assertEqual "for (foo 3)," (1,2) (foo 3))
test2 = TestCase (do (x,y) &lt;- partA 3
+
test2 = TestCase (do (x,y) <- partA 3
assertEqual "for the first result of partA," 5 x
+
assertEqual "for the first result of partA," 5 x
b &lt;- partB y
+
b <- partB y
assertBool ("(partB " ++ show y ++ ") failed") b)
+
assertBool ("(partB " ++ show y ++ ") failed") b)
</pre>
+
</haskell>
   
 
Name the test cases and group them together:
 
Name the test cases and group them together:
   
<pre>
+
<haskell>
tests = TestList [TestLabel "test1" test1, TestLabel "test2" test2]
+
tests = TestList [TestLabel "test1" test1, TestLabel "test2" test2]
</pre>
+
</haskell>
   
Run the tests as a group. At a Haskell interpreter prompt, apply the function <tt>runTestTT</tt> to the collected tests. (The "<tt>TT</tt>" suggests '''T'''ext orientation with output to the '''T'''erminal.)</p>
+
Run the tests as a group. At a Haskell interpreter prompt, apply the function <code>runTestTT</code> to the collected tests. (The "<code>TT</code>" suggests '''T'''ext orientation with output to the '''T'''erminal.)
   
<pre>
+
<haskell>
> runTestTT tests
+
> runTestTT tests
Cases: 2 Tried: 2 Errors: 0 Failures: 0
+
Cases: 2 Tried: 2 Errors: 0 Failures: 0
  +
>
>
 
</pre>
+
</haskell>
   
 
If the tests are proving their worth, you might see:
 
If the tests are proving their worth, you might see:
   
<pre>
+
<haskell>
> runTestTT tests
+
> runTestTT tests
### Failure in: 0:test1
+
### Failure in: 0:test1
for (foo 3),
+
for (foo 3),
expected: (1,2)
+
expected: (1,2)
but got: (1,3)
+
but got: (1,3)
Cases: 2 Tried: 2 Errors: 0 Failures: 1
+
Cases: 2 Tried: 2 Errors: 0 Failures: 1
  +
>
>
 
</pre>
+
</haskell>
   
 
Isn't that easy?
 
Isn't that easy?
Line 59: Line 59:
 
You can specify tests even more succinctly using operators and overloaded functions that HUnit provides:
 
You can specify tests even more succinctly using operators and overloaded functions that HUnit provides:
   
<pre>
+
<haskell>
tests = test [ "test1" ~: "(foo 3)" ~: (1,2) ~=? (foo 3),
+
tests = test [ "test1" ~: "(foo 3)" ~: (1,2) ~=? (foo 3),
"test2" ~: do (x, y) &lt;- partA 3
+
"test2" ~: do (x, y) <- partA 3
assertEqual "for the first result of partA," 5 x
+
assertEqual "for the first result of partA," 5 x
partB y @? "(partB " ++ show y ++ ") failed" ]
+
partB y @? "(partB " ++ show y ++ ") failed" ]
</pre>
+
</haskell>
   
 
Assuming the same test failures as before, you would see:
 
Assuming the same test failures as before, you would see:
   
<pre>
+
<haskell>
> runTestTT tests
+
> runTestTT tests
### Failure in: 0:test1:(foo 3)
+
### Failure in: 0:test1:(foo 3)
expected: (1,2)
+
expected: (1,2)
but got: (1,3)
+
but got: (1,3)
Cases: 2 Tried: 2 Errors: 0 Failures: 1
+
Cases: 2 Tried: 2 Errors: 0 Failures: 1
  +
>
>
 
</pre>
+
</haskell>
   
 
== Writing Tests ==
 
== Writing Tests ==
   
  +
Tests are specified compositionally. [[#Assertions | Assertions]] are combined to make a [[#Test Case | test case]], and test cases are combined into [[#Tests" | tests]]. HUnit also provides [[#Advanced Features | advanced features]] for more convenient test specification.
<p>Tests are specified compositionally. <a href="#Assertions">Assertions</a> are combined to
 
make a <a href="#TestCase">test case</a>, and test cases are combined into <a
 
href="#Tests">tests</a>. HUnit also provides <a href="#AdvancedFeatures">advanced
 
features</a> for more convenient test specification.</p>
 
   
  +
=== Assertions ===
<h3 id="Assertions">Assertions</h3>
 
   
<p>The basic building block of a test is an <b>assertion</b>.</p>
+
The basic building block of a test is an ''assertion''.
<pre>
 
type Assertion = IO ()
 
</pre>
 
<p>An assertion is an <tt>IO</tt> computation that always produces a void result. Why is an
 
assertion an <tt>IO</tt> 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 <tt>assertFailure</tt>.</p>
 
<pre>
 
assertFailure :: String -> Assertion
 
assertFailure msg = ioError (userError ("HUnit:" ++ msg))
 
</pre>
 
<p><tt>(assertFailure msg)</tt> raises an exception. The string argument identifies the
 
failure. The failure message is prefixed by "<tt>HUnit:</tt>" 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 <tt>assertFailure</tt> are subject to change and should
 
not be relied upon.)</p>
 
   
  +
<haskell>
<p><tt>assertFailure</tt> can be used directly, but it is much more common to use it
 
  +
type Assertion = IO ()
indirectly through other assertion functions that conditionally assert failure.</p>
 
  +
</haskell>
<pre>
 
assertBool :: String -> Bool -> Assertion
 
assertBool msg b = unless b (assertFailure msg)
 
   
  +
An assertion is an <code>IO</code> computation that always produces a void result. Why is an assertion an <code>IO</code> 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 <code>assertFailure</code>.
assertString :: String -> Assertion
 
assertString s = unless (null s) (assertFailure s)
 
   
  +
<haskell>
assertEqual :: (Eq a, Show a) => String -> a -> a -> Assertion
 
  +
assertFailure :: String -> Assertion
assertEqual preface expected actual =
 
  +
assertFailure msg = ioError (userError ("HUnit:" ++ msg))
unless (actual == expected) (assertFailure msg)
 
  +
</haskell>
where msg = (if null preface then "" else preface ++ "\n") ++
 
"expected: " ++ show expected ++ "\n but got: " ++ show actual
 
</pre>
 
<p>With <tt>assertBool</tt> you give the assertion condition and failure message separately.
 
With <tt>assertString</tt> the two are combined. With <tt>assertEqual</tt> 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 <a href="#AdvancedFeatures">Advanced Features</a>.</p>
 
   
  +
<code>(assertFailure msg)</code> raises an exception. The string argument identifies the failure. The failure message is prefixed by "<code>HUnit:</code>" 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 <code>assertFailure</code> are subject to change and should not be relied upon.)
<p>Since assertions are <tt>IO</tt> computations, they may be combined--along with other
 
<tt>IO</tt> computations--using <tt>(>>=)</tt>, <tt>(>>)</tt>, and the <tt>do</tt>
 
notation. As long as its result is of type <tt>(IO ())</tt>, 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.</p>
 
   
  +
<code>assertFailure</code> can be used directly, but it is much more common to use it indirectly through other assertion functions that conditionally assert failure.
<h3 id="TestCase">Test Case</h3>
 
   
  +
<haskell>
<p>A <b>test case</b> is the unit of test execution. That is, distinct test cases are
 
  +
assertBool :: String -> Bool -> Assertion
executed independently. The failure of one is independent of the failure of any other.</p>
 
  +
assertBool msg b = unless b (assertFailure msg)
   
  +
assertString :: String -> Assertion
<p>A test case consists of a single, possibly collective, assertion. The possibly multiple
 
  +
assertString s = unless (null s) (assertFailure s)
constituent assertions in a test case's collective assertion are <b>not</b> 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
 
<tt>IO.bracket</tt> function to achieve the desired effect.</p>
 
   
  +
assertEqual :: (Eq a, Show a) => String -> a -> a -> Assertion
<p>You can make a test case from an assertion by applying the <tt>TestCase</tt> constructor.
 
  +
assertEqual preface expected actual =
For example, <tt>(TestCase&nbsp;(return&nbsp;()))</tt> is a test case that never
 
  +
unless (actual == expected) (assertFailure msg)
fails, and
 
  +
where msg = (if null preface then "" else preface ++ "\n") ++
<tt>(TestCase&nbsp;(assertEqual&nbsp;"for&nbsp;x,"&nbsp;3&nbsp;x))</tt>
 
is a test case that checks that the value of <tt>x</tt> is 3.&nbsp; Additional ways
+
"expected: " ++ show expected ++ "\n but got: " ++ show actual
  +
</haskell>
to create test cases are described later under <a href="#AdvancedFeatures">Advanced
 
Features</a>.</p>
 
   
  +
With <code>assertBool</code> you give the assertion condition and failure message separately. With <code>assertString</code> the two are combined. With <code>assertEqual</code> 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 | Advanced Features]].
<h3 id="Tests">Tests</h3>
 
   
  +
Since assertions are <code>IO</code> computations, they may be combined--along with other <code>IO</code> computations--using <code>(>>=)</code>, <code>(>>)</code>, and the <code>do</code> notation. As long as its result is of type <code>(IO ())</code>, 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.
<p>As soon as you have more than one test, you'll want to name them to tell them apart. As
 
soon as you have more than several tests, you'll want to group them to process them more
 
easily. So, naming and grouping are the two keys to managing collections of tests.</p>
 
   
  +
=== Test Case ===
<p>In tune with the "composite" design pattern [<a href="#DesignPatterns">1</a>], a
 
<b>test</b> 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.</p>
 
<pre>
 
data Test = TestCase Assertion
 
| TestList [Test]
 
| TestLabel String Test
 
</pre>
 
<p>There are three important features of this definition to note:</p>
 
<ul>
 
<li>A <tt>TestList</tt> consists of a list of tests rather than a list of test cases.
 
This means that the structure of a <tt>Test</tt> is actually a tree. Using a
 
hierarchy helps organize tests just as it helps organize files in a file system.</li>
 
<li>A <tt>TestLabel</tt> is attached to a test rather than to a test case. This means
 
that all nodes in the test tree, not just test case (leaf) nodes, can be labeled.
 
Hierarchical naming helps organize tests just as it helps organize files in a file
 
system.</li>
 
<li>A <tt>TestLabel</tt> is separate from both <tt>TestCase</tt> and <tt>TestList</tt>.
 
This means that labeling is optional everywhere in the tree. Why is this a good
 
thing? Because of the hierarchical structure of a test, each constituent test case
 
is uniquely identified by its path in the tree, ignoring all labels. Sometimes a
 
test case's path (or perhaps its subpath below a certain node) is a perfectly
 
adequate "name" for the test case (perhaps relative to a certain node). In this
 
case, creating a label for the test case is both unnecessary and inconvenient.</li>
 
</ul>
 
<p>The number of test cases that a test comprises can be computed with
 
<tt>testCaseCount</tt>.</p>
 
<pre>
 
testCaseCount :: Test -> Int
 
</pre>
 
<p>As mentioned above, a test is identified by its <b>path</b> in the test hierarchy.</p>
 
<pre>
 
data Node = ListItem Int | Label String
 
deriving (Eq, Show, Read)
 
   
  +
A ''test case'' is the unit of test execution. That is, distinct test cases are executed independently. The failure of one is independent of the failure of any other.
type Path = [Node] -- Node order is from test case to root.
 
</pre>
 
<p>Each occurrence of <tt>TestList</tt> gives rise to a <tt>ListItem</tt> and each
 
occurrence of <tt>TestLabel</tt> gives rise to a <tt>Label</tt>. The <tt>ListItem</tt>s
 
by themselves ensure uniqueness among test case paths, while the <tt>Label</tt>s allow
 
you to add mnemonic names for individual test cases and collections of them.</p>
 
   
  +
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 <code>IO.bracket</code> function to achieve the desired effect.
<p>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.</p>
 
   
  +
You can make a test case from an assertion by applying the <code>TestCase</code> constructor. For example, <code>(TestCase&nbsp;(return&nbsp;()))</code> is a test case that never fails, and <code>(TestCase&nbsp;assertEqual&nbsp;"for&nbsp;x,"&nbsp;3&nbsp;x))</code> is a test case that checks that the value of <code>x</code> is 3. Additional ways to create test cases are described later under [[#Advanced Features | Advanced Features]].
<p>The paths of the test cases that a test comprises can be computed with
 
<tt>testCasePaths</tt>. The paths are listed in the order in which the corresponding
 
test cases would be executed.</p>
 
<pre>
 
testCasePaths :: Test -> [Path]
 
</pre>
 
   
  +
=== Tests ===
<p>The three variants of <tt>Test</tt> can be constructed simply by applying
 
<tt>TestCase</tt>, <tt>TestList</tt>, and <tt>TestLabel</tt> to appropriate arguments.
 
Additional ways to create tests are described later under <a href="#AdvancedFeatures"
 
>Advanced Features</a>.</p>
 
   
  +
As soon as you have more than one test, you'll want to name them to tell them apart. As soon as you have more than several tests, you'll want to group them to process them more easily. So, naming and grouping are the two keys to managing collections of tests.
<p>The design of the type <tt>Test</tt> provides great conciseness, flexibility, and
 
convenience in specifying tests. Moreover, the nature of Haskell significantly augments
 
these qualities:</p>
 
<ul>
 
<li>Combining assertions and other code to construct test cases is easy with the
 
<tt>IO</tt> monad.</li>
 
<li>Using overloaded functions and special operators (see below), specification of
 
assertions and tests is extremely compact.</li>
 
<li>Structuring a test tree by value, rather than by name as in JUnit, provides for more
 
convenient, flexible, and robust test suite specification. In particular, a test
 
suite can more easily be computed "on the fly" than in other test frameworks.</li>
 
<li>Haskell's powerful abstraction facilities provide unmatched support for test
 
refactoring.</li>
 
</ul>
 
   
  +
In tune with the "composite" design pattern [[#Design Patterns | 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.
<h3 id="AdvancedFeatures">Advanced Features</h3>
 
   
  +
<haskell>
<p>HUnit provides additional features for specifying assertions and tests more conveniently
 
  +
data Test = TestCase Assertion
and concisely. These facilities make use of Haskell type classes.</p>
 
  +
| TestList [Test]
  +
| TestLabel String Test
  +
</haskell>
   
  +
There are three important features of this definition to note:
<p>The following operators can be used to construct assertions.</p>
 
<pre>
 
infix 1 @?, @=?, @?=
 
   
  +
* A <code>TestList</code> consists of a list of tests rather than a list of test cases. This means that the structure of a <code>Test</code> is actually a tree. Using a hierarchy helps organize tests just as it helps organize files in a file system.
(@?) :: (AssertionPredicable t) => t -> String -> Assertion
 
  +
* A <code>TestLabel</code> is attached to a test rather than to a test case. This means that all nodes in the test tree, not just test case (leaf) nodes, can be labeled. Hierarchical naming helps organize tests just as it helps organize files in a file system.
pred @? msg = assertionPredicate pred >>= assertBool msg
 
  +
* A <code>TestLabel</code> is separate from both <code>TestCase</code> and <code>TestList</code>. This means that labeling is optional everywhere in the tree. Why is this a good thing? Because of the hierarchical structure of a test, each constituent test case is uniquely identified by its path in the tree, ignoring all labels. Sometimes a test case's path (or perhaps its subpath below a certain node) is a perfectly adequate "name" for the test case (perhaps relative to a certain node). In this case, creating a label for the test case is both unnecessary and inconvenient.
   
  +
The number of test cases that a test comprises can be computed with <code>testCaseCount</code>.
(@=?) :: (Eq a, Show a) => a -> a -> Assertion
 
expected @=? actual = assertEqual "" expected actual
 
   
  +
<haskell>
(@?=) :: (Eq a, Show a) => a -> a -> Assertion
 
  +
testCaseCount :: Test -> Int
actual @?= expected = assertEqual "" expected actual
 
</pre>
+
</haskell>
<p>You provide a boolean condition and failure message separately to <tt>(@?)</tt>, as for
 
<tt>assertBool</tt>, but in a different order. The <tt>(@=?)</tt> and <tt>(@?=)</tt>
 
operators provide shorthands for <tt>assertEqual</tt> 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.)</p>
 
   
  +
As mentioned above, a test is identified by its ''path'' in the test hierarchy.
<p>The <tt>(@?)</tt> operator's first argument is something from which an assertion
 
predicate can be made, that is, its type must be <tt>AssertionPredicable</tt>.</p>
 
<pre>
 
type AssertionPredicate = IO Bool
 
   
  +
<haskell>
class AssertionPredicable t
 
  +
data Node = ListItem Int | Label String
where assertionPredicate :: t -> AssertionPredicate
 
  +
deriving (Eq, Show, Read)
   
  +
type Path = [Node] -- Node order is from test case to root.
instance AssertionPredicable Bool
 
  +
</haskell>
where assertionPredicate = return
 
   
  +
Each occurrence of <code>TestList</code> gives rise to a <code>ListItem</code> and each occurrence of <code>TestLabel</code> gives rise to a <code>Label</code>. The <code>ListItem</code>s by themselves ensure uniqueness among test case paths, while the <code>Label</code>s allow you to add mnemonic names for individual test cases and collections of them.
instance (AssertionPredicable t) => AssertionPredicable (IO t)
 
where assertionPredicate = (>>= assertionPredicate)
 
</pre>
 
<p>The overloaded <tt>assert</tt> function in the <tt>Assertable</tt> type class constructs
 
an assertion.</p>
 
<pre>
 
class Assertable t
 
where assert :: t -> Assertion
 
   
  +
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.
instance Assertable ()
 
where assert = return
 
   
  +
The paths of the test cases that a test comprises can be computed with <code>testCasePaths</code>. The paths are listed in the order in which the corresponding test cases would be executed.
instance Assertable Bool
 
where assert = assertBool ""
 
   
  +
<haskell>
instance (ListAssertable t) => Assertable [t]
 
  +
testCasePaths :: Test -> [Path]
where assert = listAssert
 
  +
</haskell>
   
  +
The three variants of <code>Test</code> can be constructed simply by applying <code>TestCase</code>, <code>TestList</code>, and <code>TestLabel</code> to appropriate arguments. Additional ways to create tests are described later under [[#Advanced Features | Advanced Features]].
instance (Assertable t) => Assertable (IO t)
 
where assert = (>>= assert)
 
</pre>
 
<p>The <tt>ListAssertable</tt> class allows <tt>assert</tt> to be applied to <tt>[Char]</tt>
 
(that is, <tt>String</tt>).</p>
 
<pre>
 
class ListAssertable t
 
where listAssert :: [t] -> Assertion
 
   
  +
The design of the type <code>Test</code> provides great conciseness, flexibility, and convenience in specifying tests. Moreover, the nature of Haskell significantly augments these qualities:
instance ListAssertable Char
 
where listAssert = assertString
 
</pre>
 
<p>With the above declarations, <tt>(assert&nbsp;())</tt>,
 
<tt>(assert&nbsp;True)</tt>, and <tt>(assert&nbsp;"")</tt> (as well as
 
<tt>IO</tt> forms of these values, such as <tt>(return&nbsp;())</tt>) are all
 
assertions that never fail, while <tt>(assert&nbsp;False)</tt> and
 
<tt>(assert&nbsp;"some&nbsp;failure&nbsp;message")</tt> (and their
 
<tt>IO</tt> forms) are assertions that always fail. You may define additional
 
instances for the type classes <tt>Assertable</tt>, <tt>ListAssertable</tt>, and
 
<tt>AssertionPredicable</tt> if that should be useful in your application.</p>
 
   
  +
* Combining assertions and other code to construct test cases is easy with the <code>IO</code> monad.
<p>The overloaded <tt>test</tt> function in the <tt>Testable</tt> type class constructs a
 
  +
* Using overloaded functions and special operators (see below), specification of assertions and tests is extremely compact.
test.</p>
 
  +
*Structuring a test tree by value, rather than by name as in JUnit, provides for more convenient, flexible, and robust test suite specification. In particular, a test suite can more easily be computed "on the fly" than in other test frameworks.
<pre>
 
  +
* Haskell's powerful abstraction facilities provide unmatched support for test refactoring.
class Testable t
 
where test :: t -> Test
 
   
  +
=== Advanced Features ===
instance Testable Test
 
where test = id
 
   
  +
HUnit provides additional features for specifying assertions and tests more conveniently and concisely. These facilities make use of Haskell type classes.
instance (Assertable t) => Testable (IO t)
 
where test = TestCase . assert
 
   
  +
The following operators can be used to construct assertions.
instance (Testable t) => Testable [t]
 
where test = TestList . map test
 
</pre>
 
<p>The <tt>test</tt> function makes a test from either an <tt>Assertion</tt> (using
 
<tt>TestCase</tt>), a list of <tt>Testable</tt> items (using <tt>TestList</tt>), or
 
a <tt>Test</tt> (making no change).</p>
 
   
  +
<haskell>
<p>The following operators can be used to construct tests.</p>
 
  +
infix 1 @?, @=?, @?=
<pre>
 
infix 1 ~?, ~=?, ~?=
 
infixr 0 ~:
 
   
(~?) :: (AssertionPredicable t) => t -> String -> Test
+
(@?) :: (AssertionPredicable t) => t -> String -> Assertion
pred ~? msg = TestCase (pred @? msg)
+
pred @? msg = assertionPredicate pred >>= assertBool msg
   
(~=?) :: (Eq a, Show a) => a -> a -> Test
+
(@=?) :: (Eq a, Show a) => a -> a -> Assertion
expected ~=? actual = TestCase (expected @=? actual)
+
expected @=? actual = assertEqual "" expected actual
   
(~?=) :: (Eq a, Show a) => a -> a -> Test
+
(@?=) :: (Eq a, Show a) => a -> a -> Assertion
actual ~?= expected = TestCase (actual @?= expected)
+
actual @?= expected = assertEqual "" expected actual
  +
</haskell>
   
  +
You provide a boolean condition and failure message separately to <code>(@?)</code>, as for <code>assertBool</code>, but in a different order. The <code>(@=?)</code> and <code>(@?=)</code> operators provide shorthands for <code>assertEqual</code> 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.)
(~:) :: (Testable t) => String -> t -> Test
 
label ~: t = TestLabel label (test t)
 
</pre>
 
<p><tt>(~?)</tt>, <tt>(~=?)</tt>, and <tt>(~?=)</tt> each make an assertion, as for
 
<tt>(@?)</tt>, <tt>(@=?)</tt>, and <tt>(@?=)</tt>, respectively, and then a test case
 
from that assertion. <tt>(~:)</tt> attaches a label to something that is
 
<tt>Testable</tt>. You may define additional instances for the type class
 
<tt>Testable</tt> should that be useful.</p>
 
   
  +
The <code>(@?)</code> operator's first argument is something from which an assertion predicate can be made, that is, its type must be <code>AssertionPredicable</code>.
<h2 id="RunningTests">Running Tests</h2>
 
   
  +
<haskell>
<p>HUnit is structured to support multiple test controllers. The first subsection below
 
  +
type AssertionPredicate = IO Bool
describes the <a href="#TestExecution">test execution</a> characteristics common to all
 
test controllers. The second subsection describes the <a href="#Text-BasedController"
 
>text-based controller</a> that is included with HUnit.</p>
 
   
  +
class AssertionPredicable t
<h3 id="TestExecution">Test Execution</h3>
 
  +
where assertionPredicate :: t -> AssertionPredicate
   
  +
instance AssertionPredicable Bool
<p>All test controllers share a common test execution model. They differ only in how the
 
  +
where assertionPredicate = return
results of test execution are shown.</p>
 
   
  +
instance (AssertionPredicable t) => AssertionPredicable (IO t)
<p>The execution of a test (a value of type <tt>Test</tt>) involves the serial execution (in
 
  +
where assertionPredicate = (>>= assertionPredicate)
the <tt>IO</tt> monad) of its constituent test cases. The test cases are executed in a
 
  +
</haskell>
depth-first, left-to-right order. During test execution, four counts of test cases are
 
maintained:</p>
 
<pre>
 
data Counts = Counts { cases, tried, errors, failures :: Int }
 
deriving (Eq, Show, Read)
 
</pre>
 
<ul>
 
<li><tt>cases</tt> is the number of test cases included in the test. This number is a
 
static property of a test and remains unchanged during test execution.</li>
 
<li><tt>tried</tt> is the number of test cases that have been executed so far during the
 
test execution.</li>
 
<li><tt>errors</tt> is the number of test cases whose execution ended with an unexpected
 
exception being raised. Errors indicate problems with test cases, as opposed to the
 
code under test.</li>
 
<li><tt>failures</tt> is the number of test cases whose execution asserted failure.
 
Failures indicate problems with the code under test.</li>
 
</ul>
 
<p>Why is there no count for test case successes? The technical reason is that the counts
 
are maintained such that the number of test case successes is always equal to
 
<tt>(tried&nbsp;-&nbsp;(errors&nbsp;+&nbsp;failures))</tt>. The
 
psychosocial reason is that, with test-centered development and the expectation that
 
test failures will be few and short-lived, attention should be focused on the failures
 
rather than the successes.</p>
 
   
  +
The overloaded <code>assert</code> function in the <code>Assertable</code> type class constructs an assertion.
<p>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.)</p>
 
<ul>
 
<li><i>start</i> -- Just prior to initiation of a test case, the path of the test case
 
and the current counts (excluding the current test case) are reported.</li>
 
<li><i>error</i> -- When a test case terminates with an error, the error message is
 
reported, along with the test case path and current counts (including the current
 
test case).</li>
 
<li><i>failure</i> -- When a test case terminates with a failure, the failure message is
 
reported, along with the test case path and current counts (including the current
 
test case).</li>
 
</ul>
 
<p>Typically, a test controller shows <i>error</i> and <i>failure</i> reports immediately
 
but uses the <i>start</i> report merely to update an indication of overall test
 
execution progress.</p>
 
   
  +
<haskell>
<h3 id="Text-BasedController">Text-Based Controller</h3>
 
  +
class Assertable t
  +
where assert :: t -> Assertion
   
  +
instance Assertable ()
<p>A text-based test controller is included with HUnit.</p>
 
  +
where assert = return
<pre>
 
runTestText :: PutText st -> Test -> IO (Counts, st)
 
</pre>
 
<p><tt>runTestText</tt> is generalized on a <i>reporting scheme</i> 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.</p>
 
   
  +
instance Assertable Bool
<p>The strings for the three kinds of reporting event are as follows.</p>
 
  +
where assert = assertBool ""
<ul>
 
<li>A <i>start</i> report is the result of the function <tt>showCounts</tt> applied to
 
the counts current immediately prior to initiation of the test case being started.</li>
 
<li>An <i>error</i> report is of the form
 
"<tt>Error&nbsp;in:&nbsp;&nbsp;&nbsp;<i>path</i>\n<i>message</i></tt>",
 
where <i>path</i> is the path of the test case in error, as shown by
 
<tt>showPath</tt>, and <i>message</i> is a message describing the error. If the path
 
is empty, the report has the form "<tt>Error:\n<i>message</i></tt>".</li>
 
<li>A <i>failure</i> report is of the form
 
"<tt>Failure&nbsp;in:&nbsp;<i>path</i>\n<i>message</i></tt>", where
 
<i>path</i> is the path of the test case in error, as shown by
 
<tt>showPath</tt>, and <i>message</i> is the failure message. If the path is empty,
 
the report has the form "<tt>Failure:\n<i>message</i></tt>".</li>
 
</ul>
 
   
  +
instance (ListAssertable t) => Assertable [t]
<p>The function <tt>showCounts</tt> shows a set of counts.</p>
 
  +
where assert = listAssert
<pre>
 
showCounts :: Counts -> String
 
</pre>
 
<p>The form of its result is
 
"<tt>Cases:&nbsp;<i>cases</i>&nbsp;&nbsp;Tried:&nbsp;<i>tried</i>&nbsp;&nbsp;Errors:&nbsp;<i>errors</i>&nbsp;&nbsp;Failures:&nbsp;<i>failures</i></tt>"
 
where <i>cases</i>, <i>tried</i>, <i>errors</i>, and <i>failures</i> are the count
 
values.</p>
 
   
  +
instance (Assertable t) => Assertable (IO t)
<p>The function <tt>showPath</tt> shows a test case path.</p>
 
  +
where assert = (>>= assert)
<pre>
 
  +
</haskell>
showPath :: Path -> String
 
</pre>
 
<p>The 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 '<tt>:</tt>' separators. The
 
representation for <tt>(ListItem <i>n</i>)</tt> is <tt>(show n)</tt>. The representation
 
for <tt>(Label <i>label</i>)</tt> is normally <i>label</i>. However, if <i>label</i>
 
contains a colon or if <tt>(show <i>label</i>)</tt> is different from <i>label</i>
 
surrounded by quotation marks--that is, if any ambiguity could exist--then <tt>(Label
 
<i>label</i>)</tt> is represented as <tt>(show <i>label</i>)</tt>.</p>
 
   
  +
The <code>ListAssertable</code> class allows <code>assert</code> to be applied to <code>[Char]</code> (that is, <code>String</code>).
<p>HUnit includes two reporting schemes for the text-based test controller. You may define
 
others if you wish.</p>
 
<pre>
 
putTextToHandle :: Handle -> Bool -> PutText Int
 
</pre>
 
<p><tt>putTextToHandle</tt> 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 <tt>True</tt>, 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.</p>
 
<pre>
 
putTextToShowS :: PutText ShowS
 
</pre>
 
<p><tt>putTextToShowS</tt> 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 <tt>runTestText</tt>) as a <tt>ShowS</tt>
 
function (that is, one with type <tt>(String&nbsp;->&nbsp;String)</tt>) whose
 
first argument is a string to be appended to the accumulated report lines.</p>
 
   
  +
<haskell>
<p>HUnit provides a shorthand for the most common use of the text-based test controller.</p>
 
  +
class ListAssertable t
<pre>
 
runTestTT :: Test -> IO Counts
+
where listAssert :: [t] -> Assertion
</pre>
 
<p><tt>runTestTT</tt> invokes <tt>runTestText</tt>, specifying <tt>(putTextToHandle stderr
 
True)</tt> for the reporting scheme, and returns the final counts from the test
 
execution.</p>
 
   
  +
instance ListAssertable Char
  +
where listAssert = assertString
  +
</haskell>
   
  +
With the above declarations, <code>(assert&nbsp;())</code>, <code>(assert&nbsp;True)</code>, and <code>(assert&nbsp;"")</code> (as well as <code>IO</code> forms of these values, such as <code>(return&nbsp;())</code>) are all assertions that never fail, while <code>(assert&nbsp;False)</code> and <code>(assert&nbsp;"some&nbsp;failure&nbsp;message")</code> (and their <code>IO</code> forms) are assertions that always fail. You may define additional instances for the type classes <code>Assertable</code>, <code>ListAssertable</code>, and <code>AssertionPredicable</code> if that should be useful in your application.
<h2 id="References">References</h2>
 
   
  +
The overloaded <code>test</code> function in the <code>Testable</code> type class constructs a test.
<dl>
 
   
  +
<haskell>
<dt id="DesignPatterns">[1] Gamma, E., et al. Design Patterns: Elements of Reusable
 
  +
class Testable t
Object-Oriented Software, Addison-Wesley, Reading, MA, 1995.</dt>
 
  +
where test :: t -> Test
<dd>The classic book describing design patterns in an object-oriented context.</dd>
 
   
  +
instance Testable Test
<dt>
 
  +
where test = id
<a href="http://www.junit.org">http://www.junit.org</a>
 
</dt>
 
<dd>Web page for JUnit, the tool after which HUnit is modeled.</dd>
 
   
  +
instance (Assertable t) => Testable (IO t)
<dt>
 
  +
where test = TestCase . assert
<a href="http://junit.sourceforge.net/doc/testinfected/testing.htm">
 
http://junit.sourceforge.net/doc/testinfected/testing.htm</a>
 
</dt>
 
<dd>A good introduction to test-first development and the use of JUnit.</dd>
 
   
  +
instance (Testable t) => Testable [t]
<dt>
 
  +
where test = TestList . map test
<a href="http://junit.sourceforge.net/doc/cookstour/cookstour.htm">
 
  +
</haskell>
http://junit.sourceforge.net/doc/cookstour/cookstour.htm</a>
 
</dt>
 
<dd>A description of the internal structure of JUnit. Makes for an interesting
 
comparison between JUnit and HUnit.</dd>
 
   
  +
The <code>test</code> function makes a test from either an <code>Assertion</code> (using <code>TestCase</code>), a list of <code>Testable</code> items (using <code>TestList</code>), or a <code>Test</code> (making no change).
</dl>
 
  +
  +
The following operators can be used to construct tests.
  +
  +
<haskell>
  +
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)
  +
</haskell>
  +
  +
<code>(~?)</code>, <code>(~=?)</code>, and <code>(~?=)</code> each make an assertion, as for <code>(@?)</code>, <code>(@=?)</code>, and <code>(@?=)</code>, respectively, and then a test case from that assertion. <code>(~:)</code> attaches a label to something that is <code>Testable</code>. You may define additional instances for the type class <code>Testable</code> should that be useful.
  +
  +
== Running Tests ==
  +
  +
HUnit is structured to support multiple test controllers. The first subsection below describes the [[#Test Execution | test execution]] characteristics common to all test controllers. The second subsection describes the [[#Text-Based Controller | text-based controller]] that is included with HUnit.
  +
  +
=== Test Execution ===
  +
  +
All test controllers share a common test execution model. They differ only in how the results of test execution are shown.
  +
  +
The execution of a test (a value of type <code>Test</code>) involves the serial execution (in the <code>IO</code> 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:
  +
  +
<haskell>
  +
data Counts = Counts { cases, tried, errors, failures :: Int }
  +
deriving (Eq, Show, Read)
  +
</haskell>
  +
  +
* <code>cases</code> is the number of test cases included in the test. This number is a static property of a test and remains unchanged during test execution.
  +
* <code>tried</code> is the number of test cases that have been executed so far during the test execution.
  +
* <code>errors</code> is the number of test cases whose execution ended with an unexpected exception being raised. Errors indicate problems with test cases, as opposed to the code under test.
  +
* <code>failures</code> is the number of test cases whose execution asserted failure. Failures indicate problems with the code under test.
  +
  +
Why is there no count for test case successes? The technical reason is that the counts are maintained such that the number of test case successes is always equal to <code>(tried&nbsp;-&nbsp;(errors&nbsp;+&nbsp;failures))</code>. The psychosocial reason is that, with test-centered development and the expectation that test failures will be few and short-lived, attention should be focused on the failures rather than the successes.
  +
  +
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.)
  +
  +
; start : Just prior to initiation of a test case, the path of the test case and the current counts (excluding the current test case) are reported.
  +
; error : When a test case terminates with an error, the error message is reported, along with the test case path and current counts (including the current test case).
  +
; failure : When a test case terminates with a failure, the failure message is reported, along with the test case path and current counts (including the test case).
  +
  +
Typically, a test controller shows ''error'' and ''failure'' reports immediately but uses the ''start'' report merely to update an indication of overall test execution progress.
  +
  +
=== Text-Based Controller ===
  +
  +
A text-based test controller is included with HUnit.
  +
  +
<haskell>
  +
runTestText :: PutText st -> Test -> IO (Counts, st)
  +
</haskell>
  +
  +
<code>runTestText</code> 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.
  +
  +
* A ''start'' report is the result of the function <code>showCounts</code> applied to the counts current immediately prior to initiation of the test case being started.
  +
* An ''error'' report is of the form "<code>Error&nbsp;in:&nbsp;&nbsp;&nbsp;''path''\n''message''</code>", where ''path'' is the path of the test case in error, as shown by <code>showPath</code>, and ''message'' is a message describing the error. If the path is empty, the report has the form "<code>Error:\n''message''</code>".
  +
* A ''failure'' report is of the form "<code>Failure&nbsp;in:&nbsp;''path''\n''message''</code>", where <i>path</i> is the path of the test case in error, as shown by <code>showPath</code>, and ''message'' is the failure message. If the path is empty, the report has the form "<code>Failure:\n''message''</code>".
  +
  +
The function <code>showCounts</code> shows a set of counts.
  +
  +
<haskell>
  +
showCounts :: Counts -> String
  +
</haskell>
  +
  +
The form of its result is "<code>Cases:&nbsp;''cases''&nbsp;&nbsp;Tried:&nbsp;<i>tried</i>&nbsp;&nbsp;Errors:&nbsp;<i>errors</i>&nbsp;&nbsp;Failures:&nbsp;<i>failures</i></code>" where <i>cases</i>, <i>tried</i>, <i>errors</i>, and <i>failures</i> are the count values.
  +
  +
The function <code>showPath</code> shows a test case path.
  +
  +
<haskell>
  +
showPath :: Path -> String
  +
</haskell>
  +
  +
The 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 '<code>:</code>' separators. The representation for <code>(ListItem <i>n</i>)</code> is <code>(show n)</code>. The representation for <code>(Label <i>label</i>)</code> is normally <i>label</i>. However, if <i>label</i> contains a colon or if <code>(show <i>label</i>)</code> is different from <i>label</i> surrounded by quotation marks--that is, if any ambiguity could exist--then <code>(Label <i>label</i>)</code> is represented as <code>(show <i>label</i>)</code>.
  +
  +
HUnit includes two reporting schemes for the text-based test controller. You may define others if you wish.
  +
  +
<haskell>
  +
putTextToHandle :: Handle -> Bool -> PutText Int
  +
</haskell>
  +
  +
<code>putTextToHandle</code> 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 <code>True</code>, 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.
  +
  +
<haskell>
  +
putTextToShowS :: PutText ShowS
  +
</haskell>
  +
  +
<code>putTextToShowS</code> 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 <code>runTestText</code>) as a <code>ShowS</code> function (that is, one with type <code>(String&nbsp;->&nbsp;String)</code>) 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.
  +
  +
<haskell>
  +
runTestTT :: Test -> IO Counts
  +
</haskell>
  +
  +
<code>runTestTT</code> invokes <code>runTestText</code>, specifying <code>(putTextToHandle stderr True)</code> for the reporting scheme, and returns the final counts from the test execution.
  +
  +
== References ==
  +
  +
; [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.
  +
; [http://www.junit.org http://www.junit.org]
  +
: Web page for JUnit, the tool after which HUnit is modeled.
  +
; [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.
  +
; [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.

Revision as of 21:13, 5 June 2012

The HUnit software and this guide were written by Dean Herington (heringto@cs.unc.edu).

HUnit is a unit testing framework for Haskell, inspired by the JUnit tool for Java. This guide describes how to use HUnit, assuming you are familiar with Haskell, though not necessarily with JUnit.

Introduction

A test-centered methodology for software development is most effective when tests are easy to create, change, and execute. The Sunit tool pioneered support for test-first development in Smalltalk. HUnit is an adaptation of the unit testing framework to Haskell, a general-purpose, purely functional programming language. (To learn more about Haskell, see http://www.haskell.org.). Unit testing frameworks for various languages are referred to as xUnit.

With HUnit, as with xUnit, you can easily create tests, name them, group them into suites, and execute them, with the framework checking the results automatically. 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.

Getting Started

In the Haskell module where your tests will reside, import module Test.HUnit:

import Test.HUnit

Define 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
>

Writing Tests

Tests are specified compositionally. Assertions are combined to make a test case, and test cases are combined into tests. HUnit also provides advanced features for more convenient test specification.

Assertions

The basic building block of a test is an assertion.

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 actual

With 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.

Test Case

A test case is the unit of test execution. That is, distinct test cases are executed independently. The failure of one is independent of the failure of any other.

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.

Tests

As soon as you have more than one test, you'll want to name them to tell them apart. As soon as you have more than several tests, you'll want to group them to process them more easily. So, naming and grouping are the two keys to managing collections of tests.

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 Test

There are three important features of this definition to note:

  • A TestList consists of a list of tests rather than a list of test cases. This means that the structure of a Test is actually a tree. Using a hierarchy helps organize tests just as it helps organize files in a file system.
  • A TestLabel is attached to a test rather than to a test case. This means that all nodes in the test tree, not just test case (leaf) nodes, can be labeled. Hierarchical naming helps organize tests just as it helps organize files in a file system.
  • A TestLabel is separate from both TestCase and TestList. This means that labeling is optional everywhere in the tree. Why is this a good thing? Because of the hierarchical structure of a test, each constituent test case is uniquely identified by its path in the tree, ignoring all labels. Sometimes a test case's path (or perhaps its subpath below a certain node) is a perfectly adequate "name" for the test case (perhaps relative to a certain node). In this case, creating a label for the test case is both unnecessary and inconvenient.

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:

  • Combining assertions and other code to construct test cases is easy with the IO monad.
  • Using overloaded functions and special operators (see below), specification of assertions and tests is extremely compact.
  • Structuring a test tree by value, rather than by name as in JUnit, provides for more convenient, flexible, and robust test suite specification. In particular, a test suite can more easily be computed "on the fly" than in other test frameworks.
  • Haskell's powerful abstraction facilities provide unmatched support for test refactoring.

Advanced Features

HUnit provides additional features for specifying assertions and tests more conveniently and concisely. These facilities make use of Haskell type classes.

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 actual

You 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 = assertString

With 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 test

The 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.

Running Tests

HUnit is structured to support multiple test controllers. The first subsection below describes the test execution characteristics common to all test controllers. The second subsection describes the text-based controller that is included with HUnit.

Test Execution

All test controllers share a common test execution model. They differ only in how the results of test execution are shown.

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)
  • cases is the number of test cases included in the test. This number is a static property of a test and remains unchanged during test execution.
  • tried is the number of test cases that have been executed so far during the test execution.
  • errors is the number of test cases whose execution ended with an unexpected exception being raised. Errors indicate problems with test cases, as opposed to the code under test.
  • failures is the number of test cases whose execution asserted failure. Failures indicate problems with the code under test.

Why is there no count for test case successes? The technical reason is that the counts are maintained such that the number of test case successes is always equal to (tried - (errors + failures)). The psychosocial reason is that, with test-centered development and the expectation that test failures will be few and short-lived, attention should be focused on the failures rather than the successes.

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.)

start
Just prior to initiation of a test case, the path of the test case and the current counts (excluding the current test case) are reported.
error
When a test case terminates with an error, the error message is reported, along with the test case path and current counts (including the current test case).
failure
When a test case terminates with a failure, the failure message is reported, along with the test case path and current counts (including the test case).

Typically, a test controller shows error and failure reports immediately but uses the start report merely to update an indication of overall test execution progress.

Text-Based Controller

A text-based test controller is included with HUnit.

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.

  • A start report is the result of the function showCounts applied to the counts current immediately prior to initiation of the test case being started.
  • An error report is of the form "Error in:   path\nmessage", where path is the path of the test case in error, as shown by showPath, and message is a message describing the error. If the path is empty, the report has the form "Error:\nmessage".
  • A failure report is of the form "Failure in: path\nmessage", where path is the path of the test case in error, as shown by showPath, and message is the failure message. If the path is empty, the report has the form "Failure:\nmessage".

The function showCounts shows a set of counts.

showCounts :: Counts -> String

The 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 -> String

The 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 Int

putTextToHandle 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 ShowS

putTextToShowS 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 Counts

runTestTT invokes runTestText, specifying (putTextToHandle stderr True) for the reporting scheme, and returns the final counts from the test execution.

References

[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.
http://www.junit.org
Web page for JUnit, the tool after which HUnit is modeled.
http://junit.sourceforge.net/doc/testinfected/testing.htm
A good introduction to test-first development and the use of JUnit.
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.