QuickCheck-2.8.2: Automatic testing of Haskell programs

Safe HaskellSafe
LanguageHaskell98

Test.QuickCheck

Contents

Description

For further information see the QuickCheck manual.

To use QuickCheck to check a property, first define a function expressing that property (functions expressing properties under test tend to be prefixed with prop_). Testing that n + m = m + n holds for Integers one might write:

import Test.QuickCheck

prop_commutativeAdd :: Integer -> Integer -> Bool
prop_commutativeAdd n m = n + m == m + n

and testing:

>>> quickcheck prop_commutativeAdd
+++ OK, passed 100 tests.

which tests prop_commutativeAdd on 100 random (Integer, Integer) pairs.

verboseCheck can be used to see the actual values generated:

>>> verboseCheck prop_commutativeAdd
Passed:
0
0
  …98 tests omitted…
Passed:
-68
6
+++ OK, passed 100 tests.

and if more than 100 tests are needed the number of tests can be increased by updating the stdArgs record:

>>> quickCheckWith stdArgs { maxSuccess = 500 } prop_commutativeAdd
+++ OK, passed 500 tests.

To let QuickCheck generate values of your own data type an Arbitrary instance must be defined:

data Point = MkPoint Int Int deriving Eq

instance Arbitrary Point where
  arbitrary = do
    x <- arbitrary
    y <- arbitrary
    return (MkPoint x y)

swapPoint :: Point -> Point
swapPoint (MkPoint x y) = MkPoint y x

-- swapPoint . swapPoint = id
prop_swapInvolution point = swapPoint (swapPoint point) == point
>>> quickCheck prop_swapInvolution
+++ OK, passed 100 tests.

See Test.QuickCheck.Function for generating random shrinkable, showable functions used for testing higher-order functions and Test.QuickCheck.Monadic for testing impure or monadic code (e.g. effectful code in IO).

Synopsis

Running tests

quickCheck :: Testable prop => prop -> IO ()

Tests a property and prints the results to stdout.

data Args

Args specifies arguments to the QuickCheck driver

Constructors

Args 

Fields

replay :: Maybe (QCGen, Int)

Should we replay a previous test? Note: saving a seed from one version of QuickCheck and replaying it in another is not supported. If you want to store a test case permanently you should save the test case itself.

maxSuccess :: Int

Maximum number of successful tests before succeeding

maxDiscardRatio :: Int

Maximum number of discarded tests per successful test before giving up

maxSize :: Int

Size to use for the biggest test cases

chatty :: Bool

Whether to print anything

Instances

data Result

Result represents the test result

Constructors

Success

A successful test run

Fields

numTests :: Int

Number of tests performed

labels :: [(String, Int)]

Labels and frequencies found during all successful tests

output :: String

Printed output

GaveUp

Given up

Fields

numTests :: Int

Number of tests performed

labels :: [(String, Int)]

Labels and frequencies found during all successful tests

output :: String

Printed output

Failure

A failed test run

Fields

numTests :: Int

Number of tests performed

numShrinks :: Int

Number of successful shrinking steps performed

numShrinkTries :: Int

Number of unsuccessful shrinking steps performed

numShrinkFinal :: Int

Number of unsuccessful shrinking steps performed since last successful shrink

usedSeed :: QCGen

What seed was used

usedSize :: Int

What was the test size

reason :: String

Why did the property fail

theException :: Maybe AnException

The exception the property threw, if any

labels :: [(String, Int)]

Labels and frequencies found during all successful tests

output :: String

Printed output

NoExpectedFailure

A property that should have failed did not

Fields

numTests :: Int

Number of tests performed

labels :: [(String, Int)]

Labels and frequencies found during all successful tests

output :: String

Printed output

InsufficientCoverage

The tests passed but a use of cover had insufficient coverage

Fields

numTests :: Int

Number of tests performed

labels :: [(String, Int)]

Labels and frequencies found during all successful tests

output :: String

Printed output

Instances

stdArgs :: Args

The default test arguments

quickCheckWith :: Testable prop => Args -> prop -> IO ()

Tests a property, using test arguments, and prints the results to stdout.

quickCheckWithResult :: Testable prop => Args -> prop -> IO Result

Tests a property, using test arguments, produces a test result, and prints the results to stdout.

quickCheckResult :: Testable prop => prop -> IO Result

Tests a property, produces a test result, and prints the results to stdout.

Running tests verbosely

verboseCheck :: Testable prop => prop -> IO ()

Tests a property and prints the results and all test cases generated to stdout. This is just a convenience function that means the same as quickCheck . verbose.

verboseCheckWith :: Testable prop => Args -> prop -> IO ()

Tests a property, using test arguments, and prints the results and all test cases generated to stdout. This is just a convenience function that combines quickCheckWith and verbose.

verboseCheckWithResult :: Testable prop => Args -> prop -> IO Result

Tests a property, using test arguments, produces a test result, and prints the results and all test cases generated to stdout. This is just a convenience function that combines quickCheckWithResult and verbose.

verboseCheckResult :: Testable prop => prop -> IO Result

Tests a property, produces a test result, and prints the results and all test cases generated to stdout. This is just a convenience function that combines quickCheckResult and verbose.

Testing all properties in a module

quickCheckAll :: Q Exp

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 Exp

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

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.

forAllProperties has the same issue with scoping as quickCheckAll: see the note there about return [].

Testing polymorphic properties

polyQuickCheck :: Name -> ExpQ

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.

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

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

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].

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 [].

Random generation

data Gen a

A generator for values of type a.

Instances

Generator combinators

choose :: Random a => (a, a) -> Gen a

Generates a random element in the given inclusive range.

oneof :: [Gen a] -> Gen a

Randomly uses one of the given generators. The input list must be non-empty.

frequency :: [(Int, Gen a)] -> Gen a

Chooses one of the given generators, with a weighted random distribution. The input list must be non-empty.

elements :: [a] -> Gen a

Generates one of the given values. The input list must be non-empty.

growingElements :: [a] -> Gen a

Takes a list of elements of increasing size, and chooses among an initial segment of the list. The size of this initial segment increases with the size parameter. The input list must be non-empty.

sized :: (Int -> Gen a) -> Gen a

Used to construct generators that depend on the size parameter.

resize :: Int -> Gen a -> Gen a

Overrides the size parameter. Returns a generator which uses the given size instead of the runtime-size parameter.

scale :: (Int -> Int) -> Gen a -> Gen a

Adjust the size parameter, by transforming it with the given function.

suchThat :: Gen a -> (a -> Bool) -> Gen a

Generates a value that satisfies a predicate.

suchThatMaybe :: Gen a -> (a -> Bool) -> Gen (Maybe a)

Tries to generate a value that satisfies a predicate.

listOf :: Gen a -> Gen [a]

Generates a list of random length. The maximum length depends on the size parameter.

listOf1 :: Gen a -> Gen [a]

Generates a non-empty list of random length. The maximum length depends on the size parameter.

vectorOf :: Int -> Gen a -> Gen [a]

Generates a list of the given length.

infiniteListOf :: Gen a -> Gen [a]

Generates an infinite list.

shuffle :: [a] -> Gen [a]

Generates a random permutation of the given list.

sublistOf :: [a] -> Gen [a]

Generates a random subsequence of the given list.

Generators which use Arbitrary

vector :: Arbitrary a => Int -> Gen [a]

Generates a list of a given length.

orderedList :: (Ord a, Arbitrary a) => Gen [a]

Generates an ordered list.

infiniteList :: Arbitrary a => Gen [a]

Generate an infinite list.

Running a generator

generate :: Gen a -> IO a

Run a generator. The size passed to the generator is always 30; if you want another size then you should explicitly use resize.

Generator debugging

sample :: Show a => Gen a -> IO ()

Generates some example values and prints them to stdout.

sample' :: Gen a -> IO [a]

Generates some example values.

Arbitrary and CoArbitrary classes

class Arbitrary a where

Random generation and shrinking of values.

Minimal complete definition

arbitrary

Methods

arbitrary :: Gen a

A generator for values of the given type.

shrink :: a -> [a]

Produces a (possibly) empty list of all the possible immediate shrinks of the given value. The default implementation returns the empty list, so will not try to shrink the value.

Most implementations of shrink should try at least three things:

  1. Shrink a term to any of its immediate subterms.
  2. Recursively apply shrink to all immediate subterms.
  3. Type-specific shrinkings such as replacing a constructor by a simpler constructor.

For example, suppose we have the following implementation of binary trees:

data Tree a = Nil | Branch a (Tree a) (Tree a)

We can then define shrink as follows:

shrink Nil = []
shrink (Branch x l r) =
  -- shrink Branch to Nil
  [Nil] ++
  -- shrink to subterms
  [l, r] ++
  -- recursively shrink subterms
  [Branch x' l' r' | (x', l', r') <- shrink (x, l, r)]

There are a couple of subtleties here:

  • QuickCheck tries the shrinking candidates in the order they appear in the list, so we put more aggressive shrinking steps (such as replacing the whole tree by Nil) before smaller ones (such as recursively shrinking the subtrees).
  • It is tempting to write the last line as [Branch x' l' r' | x' <- shrink x, l' <- shrink l, r' <- shrink r] but this is the wrong thing! It will force QuickCheck to shrink x, l and r in tandem, and shrinking will stop once one of the three is fully shrunk.

There is a fair bit of boilerplate in the code above. We can avoid it with the help of some generic functions; note that these only work on GHC 7.2 and above. The function genericShrink tries shrinking a term to all of its subterms and, failing that, recursively shrinks the subterms. Using it, we can define shrink as:

shrink x = shrinkToNil x ++ genericShrink x
  where
    shrinkToNil Nil = []
    shrinkToNil (Branch _ l r) = [Nil]

genericShrink is a combination of subterms, which shrinks a term to any of its subterms, and recursivelyShrink, which shrinks all subterms of a term. These may be useful if you need a bit more control over shrinking than genericShrink gives you.

A final gotcha: we cannot define shrink as simply shrink x = Nil:genericShrink x as this shrinks Nil to Nil, and shrinking will go into an infinite loop.

If all this leaves you bewildered, you might try shrink = genericShrink to begin with, after deriving Generic for your type. However, if your data type has any special invariants, you will need to check that genericShrink can't break those invariants.

Instances

Arbitrary Bool 
Arbitrary Char 
Arbitrary Double 
Arbitrary Float 
Arbitrary Int 
Arbitrary Int8 
Arbitrary Int16 
Arbitrary Int32 
Arbitrary Int64 
Arbitrary Integer 
Arbitrary Ordering 
Arbitrary Word 
Arbitrary Word8 
Arbitrary Word16 
Arbitrary Word32 
Arbitrary Word64 
Arbitrary () 
Arbitrary Natural 
Arbitrary IntSet 
Arbitrary OrdC 
Arbitrary OrdB 
Arbitrary OrdA 
Arbitrary C 
Arbitrary B 
Arbitrary A 
Arbitrary a => Arbitrary [a] 
Integral a => Arbitrary (Ratio a) 
HasResolution a => Arbitrary (Fixed a) 
(RealFloat a, Arbitrary a) => Arbitrary (Complex a) 
Arbitrary a => Arbitrary (Maybe a) 
Arbitrary a => Arbitrary (IntMap a) 
(Ord a, Arbitrary a) => Arbitrary (Set a) 
Arbitrary a => Arbitrary (Seq a) 
Arbitrary a => Arbitrary (Smart a) 
Arbitrary a => Arbitrary (Shrink2 a) 
Integral a => Arbitrary (Small a) 
(Integral a, Bounded a) => Arbitrary (Large a) 
(Num a, Ord a, Arbitrary a) => Arbitrary (NonNegative a) 
(Num a, Eq a, Arbitrary a) => Arbitrary (NonZero a) 
(Num a, Ord a, Arbitrary a) => Arbitrary (Positive a) 
Arbitrary a => Arbitrary (NonEmptyList a) 
(Ord a, Arbitrary a) => Arbitrary (OrderedList a) 
Arbitrary a => Arbitrary (Fixed a) 
Arbitrary a => Arbitrary (Blind a) 
(CoArbitrary a, Arbitrary b) => Arbitrary (a -> b) 
(Arbitrary a, Arbitrary b) => Arbitrary (Either a b) 
(Arbitrary a, Arbitrary b) => Arbitrary (a, b) 
(Ord k, Arbitrary k, Arbitrary v) => Arbitrary (Map k v) 
(Arbitrary a, ShrinkState s a) => Arbitrary (Shrinking s a) 
(Function a, CoArbitrary a, Arbitrary b) => Arbitrary (Fun a b) 
(Function a, CoArbitrary a, Arbitrary b) => Arbitrary ((:->) a b) 
(Arbitrary a, Arbitrary b, Arbitrary c) => Arbitrary (a, b, c) 
(Arbitrary a, Arbitrary b, Arbitrary c, Arbitrary d) => Arbitrary (a, b, c, d) 
(Arbitrary a, Arbitrary b, Arbitrary c, Arbitrary d, Arbitrary e) => Arbitrary (a, b, c, d, e) 

class CoArbitrary a where

Used for random generation of functions.

If you are using a recent GHC, there is a default definition of coarbitrary using genericCoarbitrary, so if your type has a Generic instance it's enough to say

instance CoArbitrary MyType

You should only use genericCoarbitrary for data types where equality is structural, i.e. if you can't have two different representations of the same value. An example where it's not safe is sets implemented using binary search trees: the same set can be represented as several different trees. Here you would have to explicitly define coarbitrary s = coarbitrary (toList s).

Minimal complete definition

Nothing

Methods

coarbitrary :: a -> Gen b -> Gen b

Used to generate a function of type a -> b. The first argument is a value, the second a generator. You should use variant to perturb the random generator; the goal is that different values for the first argument will lead to different calls to variant. An example will help:

instance CoArbitrary a => CoArbitrary [a] where
  coarbitrary []     = variant 0
  coarbitrary (x:xs) = variant 1 . coarbitrary (x,xs)

Helper functions for implementing arbitrary

arbitrarySizedIntegral :: Integral a => Gen a

Generates an integral number. The number can be positive or negative and its maximum absolute value depends on the size parameter.

arbitrarySizedNatural :: Integral a => Gen a

Generates a natural number. The number's maximum value depends on the size parameter.

arbitrarySizedFractional :: Fractional a => Gen a

Generates a fractional number. The number can be positive or negative and its maximum absolute value depends on the size parameter.

arbitrarySizedBoundedIntegral :: (Bounded a, Integral a) => Gen a

Generates an integral number from a bounded domain. The number is chosen from the entire range of the type, but small numbers are generated more often than big numbers. Inspired by demands from Phil Wadler.

arbitraryBoundedIntegral :: (Bounded a, Integral a) => Gen a

Generates an integral number. The number is chosen uniformly from the entire range of the type. You may want to use arbitrarySizedBoundedIntegral instead.

arbitraryBoundedRandom :: (Bounded a, Random a) => Gen a

Generates an element of a bounded type. The element is chosen from the entire range of the type.

arbitraryBoundedEnum :: (Bounded a, Enum a) => Gen a

Generates an element of a bounded enumeration.

Helper functions for implementing shrink

genericCoarbitrary :: (Generic a, GCoArbitrary (Rep a)) => a -> Gen b -> Gen b

Generic CoArbitrary implementation.

genericShrink :: (Generic a, RecursivelyShrink (Rep a), GSubterms (Rep a) a) => a -> [a]

Shrink a term to any of its immediate subterms, and also recursively shrink all subterms.

subterms :: (Generic a, GSubterms (Rep a) a) => a -> [a]

All immediate subterms of a term.

recursivelyShrink :: (Generic a, RecursivelyShrink (Rep a)) => a -> [a]

Recursively shrink all immediate subterms.

shrinkNothing :: a -> [a]

Returns no shrinking alternatives.

shrinkList :: (a -> [a]) -> [a] -> [[a]]

Shrink a list of values given a shrinking function for individual values.

shrinkIntegral :: Integral a => a -> [a]

Shrink an integral number.

shrinkRealFrac :: RealFrac a => a -> [a]

Shrink a fraction.

shrinkRealFracToInteger :: RealFrac a => a -> [a]

Shrink a fraction, but only shrink to integral values.

Helper functions for implementing coarbitrary

variant :: Integral n => n -> Gen a -> Gen a

Modifies a generator using an integer seed.

coarbitraryIntegral :: Integral a => a -> Gen b -> Gen b

A coarbitrary implementation for integral numbers.

coarbitraryReal :: Real a => a -> Gen b -> Gen b

A coarbitrary implementation for real numbers.

coarbitraryShow :: Show a => a -> Gen b -> Gen b

coarbitrary helper for lazy people :-).

coarbitraryEnum :: Enum a => a -> Gen b -> Gen b

A coarbitrary implementation for enums.

(><) :: (Gen a -> Gen a) -> (Gen a -> Gen a) -> Gen a -> Gen a

Deprecated: Use ordinary function composition instead

Combine two generator perturbing functions, for example the results of calls to variant or coarbitrary.

Type-level modifiers for changing generator behavior

newtype Blind a

Blind x: as x, but x does not have to be in the Show class.

Constructors

Blind 

Fields

getBlind :: a
 

Instances

Functor Blind 
Enum a => Enum (Blind a) 
Eq a => Eq (Blind a) 
Integral a => Integral (Blind a) 
Num a => Num (Blind a) 
Ord a => Ord (Blind a) 
Real a => Real (Blind a) 
Show (Blind a) 
Arbitrary a => Arbitrary (Blind a) 

newtype Fixed a

Fixed x: as x, but will not be shrunk.

Constructors

Fixed 

Fields

getFixed :: a
 

Instances

Functor Fixed 
Enum a => Enum (Fixed a) 
Eq a => Eq (Fixed a) 
Integral a => Integral (Fixed a) 
Num a => Num (Fixed a) 
Ord a => Ord (Fixed a) 
Read a => Read (Fixed a) 
Real a => Real (Fixed a) 
Show a => Show (Fixed a) 
Arbitrary a => Arbitrary (Fixed a) 

newtype OrderedList a

Ordered xs: guarantees that xs is ordered.

Constructors

Ordered 

Fields

getOrdered :: [a]
 

Instances

newtype NonEmptyList a

NonEmpty xs: guarantees that xs is non-empty.

Constructors

NonEmpty 

Fields

getNonEmpty :: [a]
 

newtype Positive a

Positive x: guarantees that x > 0.

Constructors

Positive 

Fields

getPositive :: a
 

Instances

Functor Positive 
Enum a => Enum (Positive a) 
Eq a => Eq (Positive a) 
Ord a => Ord (Positive a) 
Read a => Read (Positive a) 
Show a => Show (Positive a) 
(Num a, Ord a, Arbitrary a) => Arbitrary (Positive a) 

newtype NonZero a

NonZero x: guarantees that x /= 0.

Constructors

NonZero 

Fields

getNonZero :: a
 

Instances

Functor NonZero 
Enum a => Enum (NonZero a) 
Eq a => Eq (NonZero a) 
Ord a => Ord (NonZero a) 
Read a => Read (NonZero a) 
Show a => Show (NonZero a) 
(Num a, Eq a, Arbitrary a) => Arbitrary (NonZero a) 

newtype NonNegative a

NonNegative x: guarantees that x >= 0.

Constructors

NonNegative 

Fields

getNonNegative :: a
 

Instances

newtype Large a

Large x: by default, QuickCheck generates Ints drawn from a small range. Large Int gives you values drawn from the entire range instead.

Constructors

Large 

Fields

getLarge :: a
 

Instances

Functor Large 
Enum a => Enum (Large a) 
Eq a => Eq (Large a) 
Integral a => Integral (Large a) 
Num a => Num (Large a) 
Ord a => Ord (Large a) 
Read a => Read (Large a) 
Real a => Real (Large a) 
Show a => Show (Large a) 
(Integral a, Bounded a) => Arbitrary (Large a) 

newtype Small a

Small x: generates values of x drawn from a small range. The opposite of Large.

Constructors

Small 

Fields

getSmall :: a
 

Instances

Functor Small 
Enum a => Enum (Small a) 
Eq a => Eq (Small a) 
Integral a => Integral (Small a) 
Num a => Num (Small a) 
Ord a => Ord (Small a) 
Read a => Read (Small a) 
Real a => Real (Small a) 
Show a => Show (Small a) 
Integral a => Arbitrary (Small a) 

data Smart a

Smart _ x: tries a different order when shrinking.

Constructors

Smart Int a 

Instances

newtype Shrink2 a

Shrink2 x: allows 2 shrinking steps at the same time when shrinking x

Constructors

Shrink2 

Fields

getShrink2 :: a
 

Instances

Functor Shrink2 
Enum a => Enum (Shrink2 a) 
Eq a => Eq (Shrink2 a) 
Integral a => Integral (Shrink2 a) 
Num a => Num (Shrink2 a) 
Ord a => Ord (Shrink2 a) 
Read a => Read (Shrink2 a) 
Real a => Real (Shrink2 a) 
Show a => Show (Shrink2 a) 
Arbitrary a => Arbitrary (Shrink2 a) 

data Shrinking s a

Shrinking _ x: allows for maintaining a state during shrinking.

Constructors

Shrinking s a 

Instances

class ShrinkState s a where

Methods

shrinkInit :: a -> s

shrinkState :: a -> s -> [(a, s)]

Properties

data Property

The type of properties.

Backwards combatibility note: in older versions of QuickCheck Property was a type synonym for Gen Prop, so you could mix and match property combinators and Gen monad operations. Code that does this will no longer typecheck. However, it is easy to fix: because of the Testable typeclass, any combinator that expects a Property will also accept a Gen Property. If you have a Property where you need a Gen a, simply wrap the property combinator inside a return to get a Gen Property, and all should be well.

Instances

class Testable prop where

The class of things which can be tested, i.e. turned into a property.

Minimal complete definition

property

Methods

property :: prop -> Property

Convert the thing to a property.

exhaustive :: prop -> Bool

If true, the property will only be tested once. However, if used inside a quantifier, it will be tested normally.

Property combinators

forAll :: (Show a, Testable prop) => Gen a -> (a -> prop) -> Property

Explicit universal quantification: uses an explicitly given test case generator.

forAllShrink :: (Show a, Testable prop) => Gen a -> (a -> [a]) -> (a -> prop) -> Property

Like forAll, but tries to shrink the argument for failing test cases.

shrinking

Arguments

:: Testable prop 
=> (a -> [a])

shrink-like function.

-> a

The original argument

-> (a -> prop) 
-> Property 

Shrinks the argument to property if it fails. Shrinking is done automatically for most types. This is only needed when you want to override the default behavior.

(==>) :: Testable prop => Bool -> prop -> Property infixr 0

Implication for properties: The resulting property holds if the first argument is False (in which case the test case is discarded), or if the given property holds.

(===) :: (Eq a, Show a) => a -> a -> Property infix 4

Like ==, but prints a counterexample when it fails.

ioProperty :: Testable prop => IO prop -> Property

Do I/O inside a property. This can obviously lead to unrepeatable testcases, so use with care.

For more advanced monadic testing you may want to look at Test.QuickCheck.Monadic.

Controlling property execution

verbose :: Testable prop => prop -> Property

Prints out the generated testcase every time the property is tested. Only variables quantified over inside the verbose are printed.

once :: Testable prop => prop -> Property

Modifies a property so that it only will be tested once.

within :: Testable prop => Int -> prop -> Property

Considers a property failed if it does not complete within the given number of microseconds.

noShrinking :: Testable prop => prop -> Property

Disables shrinking for a property altogether.

Conjunction and disjunction

(.&.) :: (Testable prop1, Testable prop2) => prop1 -> prop2 -> Property infixr 1

Nondeterministic choice: p1 .&. p2 picks randomly one of p1 and p2 to test. If you test the property 100 times it makes 100 random choices.

(.&&.) :: (Testable prop1, Testable prop2) => prop1 -> prop2 -> Property infixr 1

Conjunction: p1 .&&. p2 passes if both p1 and p2 pass.

conjoin :: Testable prop => [prop] -> Property

Take the conjunction of several properties.

(.||.) :: (Testable prop1, Testable prop2) => prop1 -> prop2 -> Property infixr 1

Disjunction: p1 .||. p2 passes unless p1 and p2 simultaneously fail.

disjoin :: Testable prop => [prop] -> Property

Take the disjunction of several properties.

What to do on failure

counterexample :: Testable prop => String -> prop -> Property

Adds the given string to the counterexample.

printTestCase :: Testable prop => String -> prop -> Property

Deprecated: Use counterexample instead

Adds the given string to the counterexample.

whenFail :: Testable prop => IO () -> prop -> Property

Performs an IO action after the last failure of a property.

whenFail' :: Testable prop => IO () -> prop -> Property

Performs an IO action every time a property fails. Thus, if shrinking is done, this can be used to keep track of the failures along the way.

expectFailure :: Testable prop => prop -> Property

Indicates that a property is supposed to fail. QuickCheck will report an error if it does not fail.

Analysing test distribution

label :: Testable prop => String -> prop -> Property

Attaches a label to a property. This is used for reporting test case distribution.

collect :: (Show a, Testable prop) => a -> prop -> Property

Labels a property with a value:

collect x = label (show x)

classify

Arguments

:: Testable prop 
=> Bool

True if the test case should be labelled.

-> String

Label.

-> prop 
-> Property 

Conditionally labels test case.

cover

Arguments

:: Testable prop 
=> Bool

True if the test case belongs to the class.

-> Int

The required percentage (0-100) of test cases.

-> String

Label for the test case class.

-> prop 
-> Property 

Checks that at least the given proportion of successful test cases belong to the given class. Discarded tests (i.e. ones with a false precondition) do not affect coverage.

Miscellaneous

data Discard

If a property returns Discard, the current test case is discarded, the same as if a precondition was false.

Constructors

Discard 

Instances

discard :: a

A special exception that makes QuickCheck discard the test case. Normally you should use ==>, but if for some reason this isn't possible (e.g. you are deep inside a generator), use discard instead.

mapSize :: Testable prop => (Int -> Int) -> prop -> Property

Changes the maximum test case size for a property.