[Add tutorial Reinier Lamers **20090607133937 Ignore-this: d266ef365ef9f2eab842750d2c571827 ] hunk ./README 27 -See the file manual.html +See the file using-testrunner.html addfile ./using-testrunner.html hunk ./using-testrunner.html 1 + + + + + Using testrunner + + + +

Using testrunner

+

This is a tutorial for the testrunner library. For the details of the exported API, please + consult the haddock + documentation.

+ +

Two ways to use it

+ +

+ There are two ways you can use the testrunner library. The first is to put + all the unit tests of your application in a big list, and then have a + one-line main function for your unit test program that calls + the testRunnerMain function from Test.Runner to + run the unit tests.

+

If you use testrunner this way, you get a unit test program with a couple + of nice features almost for free. You can replay QuickCheck tests, + select which tests to run, and choose how many tests to run at the same + time from the command line. If you wish to extend the functionality of the unit test + program however, you have to modify the testrunner library.

+

That is why there is another way to use testrunner: you can use the + functions exported by Test.Runner.Driver and + Test.Runner.Backends to run unit tests. You can tell testrunner + how many tests to run in parallel, or tell it the QuickCheck arguments to + use when running QuickCheck tests. You get back a data structure that you + can examine to see which tests failed and which succeeded. This way of using + testrunner is not further described in this document, but see the haddock.

+ +

Using testrunner the first way, using + testRunnerMain

+

Say you have a program called hello, which contains the + simple source file Hello.hs shown here:

+
+    module Hello where
+
+    helloWorld :: String
+    helloWorld = hello "world"
+
+    hello :: String -> String
+    hello s = "hello " ++ s
+    
+ +

Now we want to define unit tests for this module. Let's say we come up + with the following. I realize that they are silly, but this is + not a guide to testing the right properties, this is a guide to using + testrunner. Here is the test code, in a file Test.hs:

+
+    module Main where
+
+    import Test.HUnit
+    import Test.QuickCheck
+
+    import Hello
+
+    -- use HUnit to assert that helloWorld produces "hello world"
+    hunitTest :: Test
+    hunitTest = TestCase $ do
+        assertEqual "hello world" "hello world" helloWorld
+
+    -- use QuickCheck to check the length of hello's result
+    helloLength :: String -> Bool
+    helloLength s = length (hello s) == length "hello " + length s
+
+    -- A simple boolean expression that states that hello of an empty string is
+    -- "hello"
+    helloEmpty :: Bool
+    helloEmpty = hello "" == "hello "
+    
+

The only thing lacking from this test module is a main function. Of + course, you could easily write your own, but the simple version would not + support parallel test execution, selecting unit tests to execute, or running + the QuickCheck test with the same random sample as a previous run.

+ +

+ testrunner lets you write your main function more concise and gives you + those nice properties for free. Here is Test.hs again, with the + testrunner-based main function: +

+
+    module Main where
+
+    import Test.HUnit
+    import Test.QuickCheck
+    import Test.Runner
+
+    import Hello
+
+    -- use HUnit to assert that helloWorld produces "hello world"
+    hunitTest :: Test
+    hunitTest = TestCase $ do
+        assertEqual "hello world" "hello world" helloWorld
+
+    -- use QuickCheck to check the length of hello's result
+    helloLength :: String -> Bool
+    helloLength s = length (hello s) == length "hello " + length s
+
+    -- A simple boolean expression that states that hello of an empty string is
+    -- "hello"
+    helloEmpty :: Bool
+    helloEmpty = hello "" == "hello "
+
+    tests :: [(String, TestRunnerTest)]
+    tests = [("helloWorld value", TestRunnerTest hunitTest),
+             ("hello length", runWithQuickCheck helloLength),
+             ("value of hello applied to empty string", TestRunnerTest helloEmpty)]
+    main :: IO ()
+    main = testRunnerMain tests
+    
+

Here, we put all the unit tests in a list of type [(String, + TestRunnerTest)], where the first element of every tuple is the + name of the test. We use the TestRunnerTest constructor + to create a TestRunnerTest from HUnit tests and boolean + expressions, and use runWithQuickCheck to turn QuickCheck + Testables into TestRunnerTests. Then our main + function is a one-liner that calls testRunnerMain on this + list.

+ +

Now your powerful unit test program is ready! For example, try the + commands:

+
+      ghc --make -threaded Test.hs -o test
+      ./test
+      ./test -m length
+      ./test -r '1387922338 2147483372,86'
+      ./test -r '1387922338 2147483372,86' -m length
+      ./test -j 3 +RTS -N3
+    
+

The first command compiles the Test.hs file to an executable + named test. The second command just runs all the tests and + reports the result. The second command runs only the test whose name matches + the regular expression 'length'. The third command tries the QuickCheck test + (helloLength) with the random seed of 1387922338 2147483372 and + size 86, a combination that makes a lot of darcs unit tests fail. The fourth + command runs only the QuickCheck tests like the second, and runs it with the + random seed and size of the third command. The fifth command runs all the + unit tests in parallel.

+ +

You may notice that screen output becomes garbled when running tests in + parallel. This is partly due to the QuickCheck API, and that is why it is + not fixed. The report at the end (the single line "3 tests passed" in this + example) is printed after the worker threads have + quit, and thus will always be readable.

+ +

That's it folks, enjoy!

+ +