testpack-2.0.1: Test Utililty Pack for HUnit and QuickCheckSource codeContentsIndex
Test.HUnit.Tools
Portabilityportable
Stabilityprovisional
MaintainerJohn Goerzen <jgoerzen@complete.org>
Description

Utilities for HUnit unit testing.

Written by John Goerzen, jgoerzen@complete.org

Synopsis
assertRaises :: (Show a, Exception e, Show e, Eq e) => String -> e -> IO a -> IO ()
mapassertEqual :: (Show b, Eq b) => String -> (a -> b) -> [(a, b)] -> [Test]
runVerbTestText :: PutText st -> Test -> IO (Counts, st)
runVerboseTests :: Test -> IO (Counts, Int)
qccheck :: Testable a => Args -> String -> a -> Test
qctest :: Testable a => String -> a -> Test
qc2hu :: Testable a => Int -> String -> a -> Test
tl :: String -> [Test] -> Test
Documentation
assertRaises :: (Show a, Exception e, Show e, Eq e) => String -> e -> IO a -> IO ()Source
Asserts that a specific exception is raised by a given action.
mapassertEqual :: (Show b, Eq b) => String -> (a -> b) -> [(a, b)] -> [Test]Source
runVerbTestText :: PutText st -> Test -> IO (Counts, st)Source
Like runTestText, but with more verbose output.
runVerboseTests :: Test -> IO (Counts, Int)Source

Run verbose tests. Example:

test1 = TestCase ("x" @=? "x")

alltests = [TestLabel "test1" test1,
            tl "TestNum" TestNum.allt,
            tl "TestMap" TestMap.allt,
            tl "TestTime" TestTime.allt]

main = do runVerboseTests (TestList alltests)
          return ()
qccheckSource
:: Testable a
=> Argsquickcheck config
-> Stringlabel for the property
-> aquickcheck property
-> Test
qccheck turns the quickcheck test into an hunit test
qctest :: Testable a => String -> a -> TestSource
qctest is equivalent to 'qccheck stdArgs'
qc2hu :: Testable a => Int -> String -> a -> TestSource

Convert QuickCheck tests to HUnit, with a configurable maximum test count. Often used like this:

q :: QC.Testable a => String -> a -> HU.Test
q = qc2hu 250

allt = [q "Int -> Integer" prop_int_to_integer,
        q "Integer -> Int (safe bounds)" prop_integer_to_int_pass]
tl :: String -> [Test] -> TestSource
Label the tests list. See example under runVerboseTests.
Produced by Haddock version 2.6.1