tasty-th-0.1.0: Automagically generate the HUnit- and Quickcheck-bulk-code using Template Haskell.

Safe HaskellNone

Test.Tasty.TH

Synopsis

Documentation

testGroupGenerator :: ExpQSource

Generate the usual code and extract the usual functions needed for a testGroup in HUnitQuickcheckQuickcheck2. All functions beginning with case_, prop_ or test_ will be extracted.

 -- file SomeModule.hs
 fooTestGroup = $(testGroupGenerator)
 main = defaultMain [fooTestGroup]
 case_1 = do 1 @=? 1
 case_2 = do 2 @=? 2
 prop_p xs = reverse (reverse xs) == xs
  where types = xs :: [Int]

is the same as

 -- file SomeModule.hs
 fooTestGroup = testGroup "SomeModule" [testProperty "p" prop_1, testCase "1" case_1, testCase "2" case_2]
 main = defaultMain [fooTestGroup]
 case_1 = do 1 @=? 1
 case_2 = do 2 @=? 2
 prop_1 xs = reverse (reverse xs) == xs
  where types = xs :: [Int]

defaultMainGenerator :: ExpQSource

Generate the usual code and extract the usual functions needed in order to run HUnitQuickcheckQuickcheck2. All functions beginning with case_, prop_ or test_ will be extracted.

 {-# OPTIONS_GHC -fglasgow-exts -XTemplateHaskell #-}
 module MyModuleTest where
 import Test.HUnit
 import MainTestGenerator

 main = $(defaultMainGenerator)

 case_Foo = do 4 @=? 4

 case_Bar = do "hej" @=? "hej"

 prop_Reverse xs = reverse (reverse xs) == xs
 where types = xs :: [Int]

 test_Group =
 [ testCase "1" case_Foo
 , testProperty "2" prop_Reverse
 ]

will automagically extract prop_Reverse, case_Foo, case_Bar and test_Group and run them as well as present them as belonging to the testGroup MyModuleTest such as

 me: runghc MyModuleTest.hs
 MyModuleTest:
 Reverse: [OK, passed 100 tests]
 Foo: [OK]
 Bar: [OK]
 Group:
 1: [OK]
 2: [OK, passed 100 tests]

 Properties Test Cases Total
 Passed 2 3 5
 Failed 0 0 0
 Total 2 3 5