• Home
  • History
  • Annotate
Name Date Size #Lines LOC

..03-May-2022-

examples/H09-Sep-2001-4125

src/Test/H03-May-2022-744324

tests/H09-Sep-2001-487363

CHANGELOG.mdH A D09-Sep-2001684 4422

HUnit.cabalH A D09-Sep-20011.6 KiB6761

LICENSEH A D09-Sep-20011.5 KiB3024

README.mdH A D09-Sep-200121.6 KiB546412

Setup.lhsH A D09-Sep-200176 42

README.md

1# HUnit User's Guide
2
3HUnit is a unit testing framework for Haskell, inspired by the JUnit tool for Java. This
4guide describes how to use HUnit, assuming you are familiar with Haskell, though not
5necessarily with JUnit. You can obtain HUnit, including this guide, at
6[https://github.com/hspec/HUnit](https://github.com/hspec/HUnit)
7
8## Introduction
9A test-centered methodology for software development is most effective when tests are
10easy to create, change, and execute. The [JUnit](www.junit.org) tool
11pioneered support for test-first development in [Java](http://java.sun.com).
12HUnit is an adaptation of JUnit to Haskell, a general-purpose, purely functional
13programming language. (To learn more about Haskell, see [www.haskell.org](http://www.haskell.org)).
14
15With HUnit, as with JUnit, you can easily create tests, name them, group them into
16suites, and execute them, with the framework checking the results automatically. Test
17specification in HUnit is even more concise and flexible than in JUnit, thanks to the
18nature of the Haskell language. HUnit currently includes only a text-based test
19controller, but the framework is designed for easy extension. (Would anyone care to
20write a graphical test controller for HUnit?)
21
22The next section helps you get started using HUnit in simple ways. Subsequent sections
23give details on [writing tests](#writing-tests) and [running tests](#running-tests).
24The document concludes with a section describing HUnit's [constituent files](#constituent-files)
25and a section giving [references](#references) to further information.
26
27## Getting Started
28
29In the Haskell module where your tests will reside, import module `Test.HUnit`:
30
31```haskell
32import Test.HUnit
33```
34
35Define test cases as appropriate:
36
37```haskell
38test1 = TestCase (assertEqual "for (foo 3)," (1,2) (foo 3))
39test2 = TestCase (do (x,y) <- partA 3
40                     assertEqual "for the first result of partA," 5 x
41                     b <- partB y
42                     assertBool ("(partB " ++ show y ++ ") failed") b)
43```
44
45Name the test cases and group them together:
46
47```haskell
48tests = TestList [TestLabel "test1" test1, TestLabel "test2" test2]
49```
50
51Run the tests as a group. At a Haskell interpreter prompt, apply the
52function `runTestTT` to the collected tests. (The `TT` suggests
53**T**ext orientation with output to the **T**erminal.)
54
55```haskell
56> runTestTT tests
57Cases: 2  Tried: 2  Errors: 0  Failures: 0
58>
59```
60
61If the tests are proving their worth, you might see:
62
63```haskell
64> runTestTT tests
65### Failure in: 0:test1
66for (foo 3),
67expected: (1,2)
68 but got: (1,3)
69Cases: 2  Tried: 2  Errors: 0  Failures: 1
70>
71```
72
73Isn't that easy?
74
75You can specify tests even more succinctly using operators and
76overloaded functions that HUnit provides:
77
78```haskell
79tests = test [ "test1" ~: "(foo 3)" ~: (1,2) ~=? (foo 3),
80               "test2" ~: do (x, y) <- partA 3
81                             assertEqual "for the first result of partA," 5 x
82                             partB y @? "(partB " ++ show y ++ ") failed" ]
83```
84
85Assuming the same test failures as before, you would see:
86
87```haskell
88> runTestTT tests
89### Failure in: 0:test1:(foo 3)
90expected: (1,2)
91 but got: (1,3)
92Cases: 2  Tried: 2  Errors: 0  Failures: 1
93>
94```
95
96## Writing Tests
97
98Tests are specified compositionally. [Assertions](#assertions) are
99combined to make a [test case](#test-case), and test cases are combined
100into [tests](#tests). HUnit also provides [advanced
101features](#advanced-features) for more convenient test specification.
102
103### Assertions
104
105 The basic building block of a test is an **assertion**.
106
107```haskell
108type Assertion = IO ()
109```
110
111An 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`.
112
113```haskell
114assertFailure :: String -> Assertion
115assertFailure msg = ioError (userError ("HUnit:" ++ msg))
116```
117
118`(assertFailure msg)` raises an exception. The string argument identifies the
119 failure. The failure message is prefixed by "`HUnit:`" to mark it as an HUnit
120 assertion failure message. The HUnit test framework interprets such an exception as
121 indicating failure of the test whose execution raised the exception. (Note: The details
122 concerning the implementation of `assertFailure` are subject to change and should
123 not be relied upon.)
124
125`assertFailure` can be used directly, but it is much more common to use it
126 indirectly through other assertion functions that conditionally assert failure.
127
128```haskell
129assertBool :: String -> Bool -> Assertion
130assertBool msg b = unless b (assertFailure msg)
131
132assertString :: String -> Assertion
133assertString s = unless (null s) (assertFailure s)
134
135assertEqual :: (Eq a, Show a) => String -> a -> a -> Assertion
136assertEqual preface expected actual =
137  unless (actual == expected) (assertFailure msg)
138 where msg = (if null preface then "" else preface ++ "\n") ++
139             "expected: " ++ show expected ++ "\n but got: " ++ show actual
140```
141
142With `assertBool` you give the assertion condition and failure message separately.
143 With `assertString` the two are combined. With `assertEqual` you provide a
144 "preface", an expected value, and an actual value; the failure message shows the two
145 unequal values and is prefixed by the preface. Additional ways to create assertions are
146 described later under [Advanced Features](#advanced-features)
147
148Since assertions are `IO` computations, they may be combined--along with other
149     `IO` computations--using `(>>=)`, `(>>)`, and the `do`
150 notation. As long as its result is of type `(IO ())`, such a combination
151 constitutes a single, collective assertion, incorporating any number of constituent
152 assertions. The important features of such a collective assertion are that it fails if
153 any of its constituent assertions is executed and fails, and that the first constituent
154 assertion to fail terminates execution of the collective assertion. Such behavior is
155 essential to specifying a test case.
156
157### Test Case
158
159A **test case** is the unit of test execution. That is, distinct test cases are
160 executed independently. The failure of one is independent of the failure of any other.
161
162A test case consists of a single, possibly collective, assertion. The possibly multiple
163 constituent assertions in a test case's collective assertion are **not** independent.
164 Their interdependence may be crucial to specifying correct operation for a test. A test
165 case may involve a series of steps, each concluding in an assertion, where each step
166 must succeed in order for the test case to continue. As another example, a test may
167 require some "set up" to be performed that must be undone ("torn down" in JUnit
168 parlance) once the test is complete. In this case, you could use Haskell's
169     `IO.bracket` function to achieve the desired effect.
170
171You can make a test case from an assertion by applying the `TestCase` constructor.
172 For example, `(TestCase (return ()))` is a test case that never
173 fails, and `(TestCase (assertEqual "for x," 3 x))`
174 is a test case that checks that the value of `x` is 3.  Additional ways
175 to create test cases are described later under [Advanced Features](#advanced-eatures).
176
177### Tests
178
179As soon as you have more than one test, you'll want to name them to tell them apart. As
180 soon as you have more than several tests, you'll want to group them to process them more
181 easily. So, naming and grouping are the two keys to managing collections of tests.
182
183In tune with the "composite" design pattern [1], a
184 **test** is defined as a package of test cases. Concretely, a test is either a single
185 test case, a group of tests, or either of the first two identified by a label.
186
187```haskell
188data Test = TestCase Assertion
189          | TestList [Test]
190          | TestLabel String Test
191```
192
193There are three important features of this definition to note:
194
195
196* A `TestList` consists of a list of tests rather than a list of test cases.
197   This means that the structure of a `Test` is actually a tree. Using a
198   hierarchy helps organize tests just as it helps organize files in a file system.
199* A `TestLabel` is attached to a test rather than to a test case. This means
200   that all nodes in the test tree, not just test case (leaf) nodes, can be labeled.
201   Hierarchical naming helps organize tests just as it helps organize files in a file
202   system.
203* A `TestLabel` is separate from both `TestCase` and `TestList`.
204   This means that labeling is optional everywhere in the tree. Why is this a good
205   thing? Because of the hierarchical structure of a test, each constituent test case
206   is uniquely identified by its path in the tree, ignoring all labels. Sometimes a
207   test case's path (or perhaps its subpath below a certain node) is a perfectly
208   adequate "name" for the test case (perhaps relative to a certain node). In this
209   case, creating a label for the test case is both unnecessary and inconvenient.
210
211
212The number of test cases that a test comprises can be computed with `testCaseCount`.
213
214```haskell
215testCaseCount :: Test -> Int
216```
217
218As mentioned above, a test is identified by its **path** in the test hierarchy.
219
220```haskell
221data Node  = ListItem Int | Label String
222  deriving (Eq, Show, Read)
223
224type Path = [Node]    -- Node order is from test case to root.
225```
226
227Each occurrence of `TestList` gives rise to a `ListItem` and each
228 occurrence of `TestLabel` gives rise to a `Label`. The `ListItem`s
229 by themselves ensure uniqueness among test case paths, while the `Label`s allow
230 you to add mnemonic names for individual test cases and collections of them.
231
232Note that the order of nodes in a path is reversed from what you might expect: The first
233 node in the list is the one deepest in the tree. This order is a concession to
234 efficiency: It allows common path prefixes to be shared.
235
236The paths of the test cases that a test comprises can be computed with
237 `testCasePaths`. The paths are listed in the order in which the corresponding
238 test cases would be executed.
239
240```haskell
241testCasePaths :: Test -> [Path]
242```
243
244The three variants of `Test` can be constructed simply by applying
245 `TestCase`, `TestList`, and `TestLabel` to appropriate arguments.
246 Additional ways to create tests are described later under [Advanced Features](#advanced-features).
247
248The design of the type `Test` provides great conciseness, flexibility, and
249 convenience in specifying tests. Moreover, the nature of Haskell significantly augments
250 these qualities:
251
252* Combining assertions and other code to construct test cases is easy with the
253    `IO` monad.
254* Using overloaded functions and special operators (see below), specification of
255    assertions and tests is extremely compact.
256* Structuring a test tree by value, rather than by name as in JUnit, provides for more
257    convenient, flexible, and robust test suite specification. In particular, a test
258    suite can more easily be computed "on the fly" than in other test frameworks.
259* Haskell's powerful abstraction facilities provide unmatched support for test
260    refactoring.
261
262### Advanced Features
263
264HUnit provides additional features for specifying assertions and tests more conveniently
265 and concisely. These facilities make use of Haskell type classes.
266
267The following operators can be used to construct assertions.
268
269```haskell
270infix 1 @?, @=?, @?=
271
272(@?) :: (AssertionPredicable t) => t -> String -> Assertion
273pred @? msg = assertionPredicate pred >>= assertBool msg
274
275(@=?) :: (Eq a, Show a) => a -> a -> Assertion
276expected @=? actual = assertEqual "" expected actual
277
278(@?=) :: (Eq a, Show a) => a -> a -> Assertion
279actual @?= expected = assertEqual "" expected actual
280```
281
282You provide a boolean condition and failure message separately to `(@?)`, as for
283     `assertBool`, but in a different order. The `(@=?)` and `(@?=)`
284 operators provide shorthands for `assertEqual` when no preface is required. They
285 differ only in the order in which the expected and actual values are provided. (The
286 actual value--the uncertain one--goes on the "?" side of the operator.)
287
288The `(@?)` operator's first argument is something from which an assertion
289 predicate can be made, that is, its type must be `AssertionPredicable`.
290
291```haskell
292type AssertionPredicate = IO Bool
293
294class AssertionPredicable t
295 where assertionPredicate :: t -> AssertionPredicate
296
297instance AssertionPredicable Bool
298 where assertionPredicate = return
299
300instance (AssertionPredicable t) => AssertionPredicable (IO t)
301 where assertionPredicate = (>>= assertionPredicate)
302```
303
304The overloaded `assert` function in the `Assertable` type class constructs
305 an assertion.
306
307```haskell
308class Assertable t
309 where assert :: t -> Assertion
310
311instance Assertable ()
312 where assert = return
313
314instance Assertable Bool
315 where assert = assertBool ""
316
317instance (ListAssertable t) => Assertable [t]
318 where assert = listAssert
319
320instance (Assertable t) => Assertable (IO t)
321 where assert = (>>= assert)
322```
323
324The `ListAssertable` class allows `assert` to be applied to `[Char]`
325 (that is, `String`).
326
327```haskell
328class ListAssertable t
329 where listAssert :: [t] -> Assertion
330
331instance ListAssertable Char
332 where listAssert = assertString
333```
334
335With the above declarations, `(assert ())`,
336 `(assert True)`, and `(assert "")` (as well as
337 `IO` forms of these values, such as `(return ())`) are all
338 assertions that never fail, while `(assert False)` and
339     `(assert "some failure message")` (and their
340     `IO` forms) are assertions that always fail. You may define additional
341 instances for the type classes `Assertable`, `ListAssertable`, and
342     `AssertionPredicable` if that should be useful in your application.
343
344The overloaded `test` function in the `Testable` type class constructs a
345 test.
346
347```haskell
348class Testable t
349 where test :: t -> Test
350
351instance Testable Test
352 where test = id
353
354instance (Assertable t) => Testable (IO t)
355 where test = TestCase . assert
356
357instance (Testable t) => Testable [t]
358 where test = TestList . map test
359```
360
361The `test` function makes a test from either an `Assertion` (using
362     `TestCase`), a list of `Testable` items (using `TestList`), or
363 a `Test` (making no change).
364
365The following operators can be used to construct tests.
366
367```haskell
368infix  1 ~?, ~=?, ~?=
369infixr 0 ~:
370
371(~?) :: (AssertionPredicable t) => t -> String -> Test
372pred ~? msg = TestCase (pred @? msg)
373
374(~=?) :: (Eq a, Show a) => a -> a -> Test
375expected ~=? actual = TestCase (expected @=? actual)
376
377(~?=) :: (Eq a, Show a) => a -> a -> Test
378actual ~?= expected = TestCase (actual @?= expected)
379
380(~:) :: (Testable t) => String -> t -> Test
381label ~: t = TestLabel label (test t)
382```
383
384`(~?)`, `(~=?)`, and `(~?=)` each make an assertion, as for
385 `(@?)`, `(@=?)`, and `(@?=)`, respectively, and then a test case
386 from that assertion. `(~:)` attaches a label to something that is
387 `Testable`. You may define additional instances for the type class
388 `Testable` should that be useful.
389
390## Running Tests
391
392HUnit is structured to support multiple test controllers. The first
393 subsection below describes the [test execution](#test-execution)
394 characteristics common to all test controllers. The second subsection
395 describes the text-based controller that is included with HUnit.
396
397## Test Execution
398
399All test controllers share a common test execution model. They differ only in how the
400 results of test execution are shown.
401
402The execution of a test (a value of type `Test`) involves the serial execution (in
403 the `IO` monad) of its constituent test cases. The test cases are executed in a
404 depth-first, left-to-right order. During test execution, four counts of test cases are
405 maintained:
406
407```haskell
408data Counts = Counts { cases, tried, errors, failures :: Int }
409  deriving (Eq, Show, Read)
410```
411
412
413* `cases` is the number of test cases included in the test. This number is a
414    static property of a test and remains unchanged during test execution.
415* `tried` is the number of test cases that have been executed so far during the
416    test execution.
417* `errors` is the number of test cases whose execution ended with an unexpected
418    exception being raised. Errors indicate problems with test cases, as opposed to the
419    code under test.
420* `failures` is the number of test cases whose execution asserted failure.
421    Failures indicate problems with the code under test.
422
423
424Why is there no count for test case successes? The technical reason is that the counts
425 are maintained such that the number of test case successes is always equal to
426     `(tried - (errors + failures))`. The
427 psychosocial reason is that, with test-centered development and the expectation that
428 test failures will be few and short-lived, attention should be focused on the failures
429 rather than the successes.
430
431As test execution proceeds, three kinds of reporting event are communicated to the test
432 controller. (What the controller does in response to the reporting events depends on the
433 controller.)
434
435* *start* -- Just prior to initiation of a test case, the path of the test case
436    and the current counts (excluding the current test case) are reported.
437* *error* -- When a test case terminates with an error, the error message is
438    reported, along with the test case path and current counts (including the current
439    test case).
440* *failure* -- When a test case terminates with a failure, the failure message is
441    reported, along with the test case path and current counts (including the current
442    test case).
443
444Typically, a test controller shows *error* and *failure* reports immediately
445 but uses the *start* report merely to update an indication of overall test
446 execution progress.
447
448### Text-Based Controller
449
450A text-based test controller is included with HUnit.
451
452```haskell
453runTestText :: PutText st -> Test -> IO (Counts, st)
454```
455
456`runTestText` is generalized on a *reporting scheme* given as its first
457 argument. During execution of the test given as its second argument, the controller
458 creates a string for each reporting event and processes it according to the reporting
459 scheme. When test execution is complete, the controller returns the final counts along
460 with the final state for the reporting scheme.
461
462The strings for the three kinds of reporting event are as follows.
463
464* A *start* report is the result of the function `showCounts` applied to
465    the counts current immediately prior to initiation of the test case being started.
466* An *error* report is of the form
467            "`Error in:   *path*\n*message*`",
468    where *path* is the path of the test case in error, as shown by
469    `showPath`, and *message* is a message describing the error. If the path
470    is empty, the report has the form "`Error:\n*message*`".
471* A *failure* report is of the form
472            "`Failure in: *path*\n*message*`", where
473        *path* is the path of the test case in error, as shown by
474    `showPath`, and *message* is the failure message. If the path is empty,
475    the report has the form "`Failure:\n*message*`".
476
477The function `showCounts` shows a set of counts.
478
479```haskell
480showCounts :: Counts -> String
481```
482
483The form of its result is
484`Cases: *cases*  Tried: *tried*  Errors: *errors*  Failures: *failures*`
485where *cases*, *tried*, *errors*, and *failures* are the count values.
486
487The function `showPath` shows a test case path.
488
489```haskell
490 showPath :: Path -> String
491```
492
493The nodes in the path are reversed (so that the path reads from the root down to the test
494 case), and the representations for the nodes are joined by '`:`' separators. The
495 representation for `(ListItem *n*)` is `(show n)`. The representation
496 for `(Label *label*)` is normally *label*. However, if *label*
497 contains a colon or if `(show *label*)` is different from *label*
498 surrounded by quotation marks--that is, if any ambiguity could exist--then `(Label
499         *label*)` is represented as `(show *label*)`.
500
501HUnit includes two reporting schemes for the text-based test controller. You may define
502 others if you wish.
503
504```haskell
505putTextToHandle :: Handle -> Bool -> PutText Int
506```
507
508`putTextToHandle` writes error and failure reports, plus a report of the final
509 counts, to the given handle. Each of these reports is terminated by a newline. In
510 addition, if the given flag is `True`, it writes start reports to the handle as
511 well. A start report, however, is not terminated by a newline. Before the next report is
512 written, the start report is "erased" with an appropriate sequence of carriage return
513 and space characters. Such overwriting realizes its intended effect on terminal devices.
514
515```haskell
516putTextToShowS :: PutText ShowS
517```
518
519`putTextToShowS` ignores start reports and simply accumulates error and failure
520 reports, terminating them with newlines. The accumulated reports are returned (as the
521 second element of the pair returned by `runTestText`) as a `ShowS`
522 function (that is, one with type `(String -> String)`) whose
523 first argument is a string to be appended to the accumulated report lines.
524
525HUnit provides a shorthand for the most common use of the text-based test controller.
526
527```haskell
528runTestTT :: Test -> IO Counts
529```
530
531`runTestTT` invokes `runTestText`, specifying `(putTextToHandle stderr
532True)` for the reporting scheme, and returns the final counts from the
533test execution.
534
535## References
536
537* [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.
538
539* [junit.org](http://www.junit.org): Web page for JUnit, the tool after which HUnit is modeled.
540
541* [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.
542
543* [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.
544
545The HUnit software and this guide were written by Dean Herington [heringto@cs.unc.edu](mailto:heringto@cs.unc.edu)
546