diff options
Diffstat (limited to '')
-rw-r--r-- | tests/genMain.hs | 22 |
1 files changed, 18 insertions, 4 deletions
diff --git a/tests/genMain.hs b/tests/genMain.hs index 90d8224..996f19a 100644 --- a/tests/genMain.hs +++ b/tests/genMain.hs @@ -6,7 +6,7 @@ Usage (your QuickCheck-1 version may vary): > ln -s ../../xmonad/tests/Properties.hs . > runghc genMain.hs > Main.hs -> ghc -DTESTING -i.. -i. -package QuickCheck-1.2.0.0 Main.hs -e main +> ghc -DTESTING -i.. -i. -package QuickCheck-1.2.0.0 Main.hs -e ':main 200' -} module Main where @@ -44,9 +44,23 @@ genModule :: [String] -> [String] -> Doc genModule imports props = vcat [header,imports', main ] where header = text "module Main where" - imports' = text "import Test.QuickCheck" + imports' = text "import Test.QuickCheck; import Data.Maybe; \ + \import System.Environment; import Text.Printf; \ + \import Properties hiding (main); import Control.Monad" $$ vcat [ text "import qualified" <+> text im | im <- imports ] - props' = vcat [ text "quickCheck" <+> text p | p <- props ] - main = hang (text "main = do") 4 props' + props' = [ parens $ doubleQuotes (text p) <> comma <> text "mytest" <+> text p + | p <- props ] + main = hang (text "main = do") 4 $ + text "n <- maybe (return 100) readIO . listToMaybe =<< getArgs" + $$ + hang (text "let props = ") 8 + (brackets $ foldr1 (\x xs -> x <> comma $$ xs) props') + $$ + text "(results, passed) <- liftM unzip $ \ + \mapM (\\(s,a) -> printf \"%-40s: \" s >> a n) props" + $$ + text "printf \"Passed %d tests!\\n\" (sum passed)" + $$ + text "when (any not results) $ fail \"Not all tests passed!\"" io x = liftIO x |