Safe Haskell | Trustworthy |
---|---|
Language | Haskell2010 |
Note: the contents of this module are re-exported by Test.QuickCheck. You do not need to import it directly.
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.
Synopsis
- quickCheckAll :: Q Exp
- verboseCheckAll :: Q Exp
- forAllProperties :: Q Exp
- allProperties :: Q Exp
- polyQuickCheck :: Name -> ExpQ
- polyVerboseCheck :: Name -> ExpQ
- monomorphic :: Name -> ExpQ
Testing all properties in a module
quickCheckAll :: Q Exp Source #
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 and later; 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 Exp Source #
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 Exp Source #
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 []
.
allProperties :: Q Exp Source #
List all properties in the current module.
$
has type allProperties
[(
.String
, Property
)]
allProperties
has the same issue with scoping as quickCheckAll
:
see the note there about return []
.
Testing polymorphic properties
polyQuickCheck :: Name -> ExpQ Source #
Test a polymorphic property, defaulting all type variables to Integer
.
Invoke as $(
, where polyQuickCheck
'prop)prop
is a property.
Note that just evaluating
in GHCi will seem to
work, but will silently default all type variables to quickCheck
prop()
!
$(
means the same as
polyQuickCheck
'prop)
.
If you want to supply custom arguments to 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 -> ExpQ Source #
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 -> ExpQ Source #
Monomorphise an arbitrary property by defaulting all type variables to Integer
.
For example, if f
has type
then 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 []
.