Jump to content
Main menu
Main menu
move to sidebar
hide
Navigation
Haskell
Wiki community
Recent changes
Random page
HaskellWiki
Search
Search
Create account
Log in
Personal tools
Create account
Log in
Pages for logged out editors
learn more
Contributions
Talk
Editing
HUnit 1.0 User's Guide
(section)
Page
Discussion
English
Read
Edit
View history
Tools
Tools
move to sidebar
hide
Actions
Read
Edit
View history
General
What links here
Related changes
Special pages
Page information
Warning:
You are not logged in. Your IP address will be publicly visible if you make any edits. If you
log in
or
create an account
, your edits will be attributed to your username, along with other benefits.
Anti-spam check. Do
not
fill this in!
== 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. === Assertions === The basic building block of a test is an ''assertion''. <haskell> type Assertion = IO () </haskell> 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>. <haskell> assertFailure :: String -> Assertion assertFailure msg = ioError (userError ("HUnit:" ++ msg)) </haskell> <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.) <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. <haskell> 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 </haskell> 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]]. 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. === 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 <code>IO.bracket</code> function to achieve the desired effect. You can make a test case from an assertion by applying the <code>TestCase</code> constructor. For example, <code>(TestCase (return ()))</code> is a test case that never fails, and <code>(TestCase assertEqual "for x," 3 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]]. === 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<ref>Gamma, E., et al. ''Design Patterns: Elements of Reusable Object-Oriented Software''. Reading, MA: Addison-Wesley, 1994. ISBN 9780201633610.</ref>, 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. <haskell> data Test = TestCase Assertion | TestList [Test] | TestLabel String Test </haskell> There are three important features of this definition to note: * 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. * 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. * 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>. <haskell> testCaseCount :: Test -> Int </haskell> As mentioned above, a test is identified by its ''path'' in the test hierarchy. <haskell> data Node = ListItem Int | Label String deriving (Eq, Show, Read) type Path = [Node] -- Node order is from test case to root. </haskell> 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. 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 <code>testCasePaths</code>. The paths are listed in the order in which the corresponding test cases would be executed. <haskell> testCasePaths :: Test -> [Path] </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]]. 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: * Combining assertions and other code to construct test cases is easy with the <code>IO</code> 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. <haskell> 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 </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.) 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>. <haskell> 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) </haskell> The overloaded <code>assert</code> function in the <code>Assertable</code> type class constructs an assertion. <haskell> 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) </haskell> The <code>ListAssertable</code> class allows <code>assert</code> to be applied to <code>[Char]</code> (that is, <code>String</code>). <haskell> class ListAssertable t where listAssert :: [t] -> Assertion instance ListAssertable Char where listAssert = assertString </haskell> With the above declarations, <code>(assert ())</code>, <code>(assert True)</code>, and <code>(assert "")</code> (as well as <code>IO</code> forms of these values, such as <code>(return ())</code>) are all assertions that never fail, while <code>(assert False)</code> and <code>(assert "some failure 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. The overloaded <code>test</code> function in the <code>Testable</code> type class constructs a test. <haskell> 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 </haskell> 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). 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.
Summary:
Please note that all contributions to HaskellWiki are considered to be released under simple permissive license (see
HaskellWiki:Copyrights
for details). If you don't want your writing to be edited mercilessly and redistributed at will, then don't submit it here.
You are also promising us that you wrote this yourself, or copied it from a public domain or similar free resource.
DO NOT SUBMIT COPYRIGHTED WORK WITHOUT PERMISSION!
Cancel
Editing help
(opens in new window)
Toggle limited content width