QuickCheck-2.7.3: Automatic testing of Haskell programs

Safe HaskellTrustworthy

Test.QuickCheck.All

Contents

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.

Synopsis

Testing all properties in a module

quickCheckAll :: Q ExpSource

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.

Using quickCheckAll interactively doesn't work. Instead, add a definition to your module along the lines of

 runTests = $quickCheckAll

and then execute runTests.

verboseCheckAll :: Q ExpSource

Test all properties in the current module. This is just a convenience function that combines quickCheckAll and verbose.

forAllProperties :: Q ExpSource

Test all properties in the current module, using a custom quickCheck function. The same caveats as with quickCheckAll apply.

$forAllProperties has type (Property -> IO Result) -> IO Bool. An example invocation is $forAllProperties quickCheckResult, which does the same thing as $quickCheckAll.

Testing polymorphic properties

polyQuickCheck :: Name -> ExpQSource

Test a polymorphic property, defaulting all type variables to Integer.

Invoke as $(polyQuickCheck 'prop), where prop is a property. Note that just evaluating quickCheck prop in GHCi will seem to work, but will silently default all type variables to ()!

$(polyQuickCheck 'prop) means the same as quickCheck $(monomorphic 'prop). If you want to supply custom arguments to polyQuickCheck, you will have to combine quickCheckWith and monomorphic yourself.

polyVerboseCheck :: Name -> ExpQSource

Test a polymorphic property, defaulting all type variables to Integer. This is just a convenience function that combines verboseCheck and monomorphic.

monomorphic :: Name -> ExpQSource

Monomorphise an arbitrary property by defaulting all type variables to Integer.

For example, if f has type Ord a => [a] -> [a] then $(monomorphic 'f) has type [Integer] -> [Integer].