| Safe Haskell | Trustworthy | 
|---|
Test.QuickCheck.All
Description
Test all properties in the current module, using Template Haskell.
 You need to have a {-# LANGUAGE TemplateHaskell #-} pragma in
 your module for any of these to work.
- quickCheckAll :: Q Exp
- verboseCheckAll :: Q Exp
- forAllProperties :: Q Exp
- polyQuickCheck :: Name -> ExpQ
- polyVerboseCheck :: Name -> ExpQ
- monomorphic :: Name -> ExpQ
Testing all properties in a module
Test all properties in the current module.
 The name of the property must begin with prop_.
 Polymorphic properties will be defaulted to Integer.
 Returns True if all tests succeeded, False otherwise.
To use quickCheckAll, add a definition to your module along
 the lines of
return [] runTests = $quickCheckAll
and then execute runTests.
Note: the bizarre return [] in the example above is needed on
 GHC 7.8; without it, quickCheckAll will not be able to find
 any of the properties. For the curious, the return [] is a
 Template Haskell splice that makes GHC insert the empty list
 of declarations at that point in the program; GHC typechecks
 everything before the return [] before it starts on the rest
 of the module, which means that the later call to quickCheckAll
 can see everything that was defined before the return []. Yikes!
verboseCheckAll :: Q ExpSource
Test all properties in the current module.
 This is just a convenience function that combines quickCheckAll and verbose.
verboseCheckAll has the same issue with scoping as quickCheckAll:
 see the note there about return [].
forAllProperties :: Q ExpSource
Test all properties in the current module, using a custom
 quickCheck function. The same caveats as with quickCheckAll
 apply.
$ has type forAllProperties(.
 An example invocation is Property -> IO Result) -> IO Bool$,
 which does the same thing as forAllProperties quickCheckResult$.
quickCheckAll
forAllProperties has the same issue with scoping as quickCheckAll:
 see the note there about return [].
Testing polymorphic properties
polyQuickCheck :: Name -> ExpQSource
Test a polymorphic property, defaulting all type variables to Integer.
Invoke as $(, where polyQuickCheck 'prop)prop is a property.
 Note that just evaluating quickCheck prop()!
$( means the same as
 polyQuickCheck 'prop)quickCheck $(monomorphic 'prop)polyQuickCheck,
 you will have to combine quickCheckWith and monomorphic yourself.
If you want to use polyQuickCheck in the same file where you defined the
 property, the same scoping problems pop up as in quickCheckAll:
 see the note there about return [].
polyVerboseCheck :: Name -> ExpQSource
Test a polymorphic property, defaulting all type variables to Integer.
 This is just a convenience function that combines verboseCheck and monomorphic.
If you want to use polyVerboseCheck in the same file where you defined the
 property, the same scoping problems pop up as in quickCheckAll:
 see the note there about return [].
monomorphic :: Name -> ExpQSource
Monomorphise an arbitrary property by defaulting all type variables to Integer.
For example, if f has type Ord a => [a] -> [a]$( has type monomorphic 'f)[.
Integer] -> [Integer]
If you want to use monomorphic in the same file where you defined the
 property, the same scoping problems pop up as in quickCheckAll:
 see the note there about return [].