| Safe Haskell | Safe | 
|---|---|
| Language | Haskell98 | 
Test.QuickCheck
Contents
- Running tests
- The Arbitrarytypeclass: generation of random values
- The Genmonad: combinators for building random generators
- The Functiontypeclass: generation of random shrinkable, showable functions
- The CoArbitrarytypeclass: generation of functions the old-fashioned way
- Type-level modifiers for changing generator behavior
- Property combinators
- Analysing test case distribution
Description
The QuickCheck manual gives detailed information about using QuickCheck effectively. You can also try https://begriffs.com/posts/2017-01-14-design-use-quickcheck.html, a tutorial written by a user of QuickCheck.
To start using QuickCheck, write down your property as a function returning Bool.
For example, to check that reversing a list twice gives back the same list you can write:
import Test.QuickCheck prop_reverse :: [Int] -> Bool prop_reverse xs = reverse (reverse xs) == xs
You can then use QuickCheck to test prop_reverse on 100 random lists:
>>>quickCheck prop_reverse+++ OK, passed 100 tests.
To run more tests you can use the withMaxSuccess combinator:
>>>quickCheck (withMaxSuccess 10000 prop_reverse)+++ OK, passed 10000 tests.
To use QuickCheck on your own data types you will need to write Arbitrary
instances for those types. See the
QuickCheck manual for
details about how to do that.
Synopsis
- quickCheck :: Testable prop => prop -> IO ()
- data Args = Args {- replay :: Maybe (QCGen, Int)
- maxSuccess :: Int
- maxDiscardRatio :: Int
- maxSize :: Int
- chatty :: Bool
- maxShrinks :: Int
 
- data Result- = Success { }
- | GaveUp { }
- | Failure { - numTests :: Int
- numDiscarded :: Int
- numShrinks :: Int
- numShrinkTries :: Int
- numShrinkFinal :: Int
- usedSeed :: QCGen
- usedSize :: Int
- reason :: String
- theException :: Maybe AnException
- output :: String
- failingTestCase :: [String]
- failingLabels :: [String]
- failingClasses :: Set String
 
- | NoExpectedFailure { }
 
- stdArgs :: Args
- quickCheckWith :: Testable prop => Args -> prop -> IO ()
- quickCheckWithResult :: Testable prop => Args -> prop -> IO Result
- quickCheckResult :: Testable prop => prop -> IO Result
- isSuccess :: Result -> Bool
- verboseCheck :: Testable prop => prop -> IO ()
- verboseCheckWith :: Testable prop => Args -> prop -> IO ()
- verboseCheckWithResult :: Testable prop => Args -> prop -> IO Result
- verboseCheckResult :: Testable prop => prop -> IO Result
- quickCheckAll :: Q Exp
- verboseCheckAll :: Q Exp
- forAllProperties :: Q Exp
- allProperties :: Q Exp
- polyQuickCheck :: Name -> ExpQ
- polyVerboseCheck :: Name -> ExpQ
- monomorphic :: Name -> ExpQ
- class Arbitrary a where
- genericShrink :: (Generic a, RecursivelyShrink (Rep a), GSubterms (Rep a) a) => a -> [a]
- subterms :: (Generic a, GSubterms (Rep a) a) => a -> [a]
- recursivelyShrink :: (Generic a, RecursivelyShrink (Rep a)) => a -> [a]
- shrinkNothing :: a -> [a]
- shrinkList :: (a -> [a]) -> [a] -> [[a]]
- shrinkMap :: Arbitrary a => (a -> b) -> (b -> a) -> b -> [b]
- shrinkMapBy :: (a -> b) -> (b -> a) -> (a -> [a]) -> b -> [b]
- shrinkIntegral :: Integral a => a -> [a]
- shrinkRealFrac :: RealFrac a => a -> [a]
- shrinkDecimal :: RealFrac a => a -> [a]
- class Arbitrary1 f where
- arbitrary1 :: (Arbitrary1 f, Arbitrary a) => Gen (f a)
- shrink1 :: (Arbitrary1 f, Arbitrary a) => f a -> [f a]
- class Arbitrary2 f where
- arbitrary2 :: (Arbitrary2 f, Arbitrary a, Arbitrary b) => Gen (f a b)
- shrink2 :: (Arbitrary2 f, Arbitrary a, Arbitrary b) => f a b -> [f a b]
- data Gen a
- choose :: Random a => (a, a) -> Gen a
- oneof :: [Gen a] -> Gen a
- frequency :: [(Int, Gen a)] -> Gen a
- elements :: [a] -> Gen a
- growingElements :: [a] -> Gen a
- sized :: (Int -> Gen a) -> Gen a
- getSize :: Gen Int
- resize :: Int -> Gen a -> Gen a
- scale :: (Int -> Int) -> Gen a -> Gen a
- suchThat :: Gen a -> (a -> Bool) -> Gen a
- suchThatMap :: Gen a -> (a -> Maybe b) -> Gen b
- suchThatMaybe :: Gen a -> (a -> Bool) -> Gen (Maybe a)
- applyArbitrary2 :: (Arbitrary a, Arbitrary b) => (a -> b -> r) -> Gen r
- applyArbitrary3 :: (Arbitrary a, Arbitrary b, Arbitrary c) => (a -> b -> c -> r) -> Gen r
- applyArbitrary4 :: (Arbitrary a, Arbitrary b, Arbitrary c, Arbitrary d) => (a -> b -> c -> d -> r) -> Gen r
- listOf :: Gen a -> Gen [a]
- listOf1 :: Gen a -> Gen [a]
- vectorOf :: Int -> Gen a -> Gen [a]
- vector :: Arbitrary a => Int -> Gen [a]
- infiniteListOf :: Gen a -> Gen [a]
- infiniteList :: Arbitrary a => Gen [a]
- shuffle :: [a] -> Gen [a]
- sublistOf :: [a] -> Gen [a]
- orderedList :: (Ord a, Arbitrary a) => Gen [a]
- arbitrarySizedIntegral :: Integral a => Gen a
- arbitrarySizedNatural :: Integral a => Gen a
- arbitrarySizedFractional :: Fractional a => Gen a
- arbitrarySizedBoundedIntegral :: (Bounded a, Integral a) => Gen a
- arbitraryBoundedIntegral :: (Bounded a, Integral a) => Gen a
- arbitraryBoundedRandom :: (Bounded a, Random a) => Gen a
- arbitraryBoundedEnum :: (Bounded a, Enum a) => Gen a
- arbitraryUnicodeChar :: Gen Char
- arbitraryASCIIChar :: Gen Char
- arbitraryPrintableChar :: Gen Char
- generate :: Gen a -> IO a
- sample :: Show a => Gen a -> IO ()
- sample' :: Gen a -> IO [a]
- data Fun a b = Fun (a :-> b, b, Shrunk) (a -> b)
- applyFun :: Fun a b -> a -> b
- applyFun2 :: Fun (a, b) c -> a -> b -> c
- applyFun3 :: Fun (a, b, c) d -> a -> b -> c -> d
- pattern Fn :: (a -> b) -> Fun a b
- pattern Fn2 :: (a -> b -> c) -> Fun (a, b) c
- pattern Fn3 :: (a -> b -> c -> d) -> Fun (a, b, c) d
- class Function a where
- functionMap :: Function b => (a -> b) -> (b -> a) -> (a -> c) -> a :-> c
- functionShow :: (Show a, Read a) => (a -> c) -> a :-> c
- functionIntegral :: Integral a => (a -> b) -> a :-> b
- functionRealFrac :: RealFrac a => (a -> b) -> a :-> b
- functionBoundedEnum :: (Eq a, Bounded a, Enum a) => (a -> b) -> a :-> b
- class CoArbitrary a where
- genericCoarbitrary :: (Generic a, GCoArbitrary (Rep a)) => a -> Gen b -> Gen b
- variant :: Integral n => n -> Gen a -> Gen a
- coarbitraryIntegral :: Integral a => a -> Gen b -> Gen b
- coarbitraryReal :: Real a => a -> Gen b -> Gen b
- coarbitraryShow :: Show a => a -> Gen b -> Gen b
- coarbitraryEnum :: Enum a => a -> Gen b -> Gen b
- (><) :: (Gen a -> Gen a) -> (Gen a -> Gen a) -> Gen a -> Gen a
- newtype Blind a = Blind {- getBlind :: a
 
- newtype Fixed a = Fixed {- getFixed :: a
 
- newtype OrderedList a = Ordered {- getOrdered :: [a]
 
- newtype NonEmptyList a = NonEmpty {- getNonEmpty :: [a]
 
- data InfiniteList a = InfiniteList {- getInfiniteList :: [a]
- infiniteListInternalData :: InfiniteListInternalData a
 
- newtype SortedList a = Sorted {- getSorted :: [a]
 
- newtype Positive a = Positive {- getPositive :: a
 
- newtype NonZero a = NonZero {- getNonZero :: a
 
- newtype NonNegative a = NonNegative {- getNonNegative :: a
 
- newtype Large a = Large {- getLarge :: a
 
- newtype Small a = Small {- getSmall :: a
 
- data Smart a = Smart Int a
- newtype Shrink2 a = Shrink2 {- getShrink2 :: a
 
- data Shrinking s a = Shrinking s a
- class ShrinkState s a where
- newtype ASCIIString = ASCIIString {}
- newtype UnicodeString = UnicodeString {}
- newtype PrintableString = PrintableString {}
- data Property
- class Testable prop where
- forAll :: (Show a, Testable prop) => Gen a -> (a -> prop) -> Property
- forAllShrink :: (Show a, Testable prop) => Gen a -> (a -> [a]) -> (a -> prop) -> Property
- forAllShow :: Testable prop => Gen a -> (a -> String) -> (a -> prop) -> Property
- forAllShrinkShow :: Testable prop => Gen a -> (a -> [a]) -> (a -> String) -> (a -> prop) -> Property
- forAllBlind :: Testable prop => Gen a -> (a -> prop) -> Property
- forAllShrinkBlind :: Testable prop => Gen a -> (a -> [a]) -> (a -> prop) -> Property
- shrinking :: Testable prop => (a -> [a]) -> a -> (a -> prop) -> Property
- (==>) :: Testable prop => Bool -> prop -> Property
- data Discard = Discard
- discard :: a
- (===) :: (Eq a, Show a) => a -> a -> Property
- (=/=) :: (Eq a, Show a) => a -> a -> Property
- total :: NFData a => a -> Property
- ioProperty :: Testable prop => IO prop -> Property
- idempotentIOProperty :: Testable prop => IO prop -> Property
- verbose :: Testable prop => prop -> Property
- verboseShrinking :: Testable prop => prop -> Property
- noShrinking :: Testable prop => prop -> Property
- withMaxSuccess :: Testable prop => Int -> prop -> Property
- within :: Testable prop => Int -> prop -> Property
- once :: Testable prop => prop -> Property
- again :: Testable prop => prop -> Property
- mapSize :: Testable prop => (Int -> Int) -> prop -> Property
- (.&.) :: (Testable prop1, Testable prop2) => prop1 -> prop2 -> Property
- (.&&.) :: (Testable prop1, Testable prop2) => prop1 -> prop2 -> Property
- conjoin :: Testable prop => [prop] -> Property
- (.||.) :: (Testable prop1, Testable prop2) => prop1 -> prop2 -> Property
- disjoin :: Testable prop => [prop] -> Property
- counterexample :: Testable prop => String -> prop -> Property
- printTestCase :: Testable prop => String -> prop -> Property
- whenFail :: Testable prop => IO () -> prop -> Property
- whenFail' :: Testable prop => IO () -> prop -> Property
- expectFailure :: Testable prop => prop -> Property
- label :: Testable prop => String -> prop -> Property
- collect :: (Show a, Testable prop) => a -> prop -> Property
- classify :: Testable prop => Bool -> String -> prop -> Property
- tabulate :: Testable prop => String -> [String] -> prop -> Property
- cover :: Testable prop => Double -> Bool -> String -> prop -> Property
- coverTable :: Testable prop => String -> [(String, Double)] -> prop -> Property
- checkCoverage :: Testable prop => prop -> Property
- checkCoverageWith :: Testable prop => Confidence -> prop -> Property
- data Confidence = Confidence {}
- stdConfidence :: Confidence
- labelledExamples :: Testable prop => prop -> IO ()
- labelledExamplesWith :: Testable prop => Args -> prop -> IO ()
- labelledExamplesWithResult :: Testable prop => Args -> prop -> IO Result
- labelledExamplesResult :: Testable prop => prop -> IO Result
Running tests
quickCheck :: Testable prop => prop -> IO () Source #
Tests a property and prints the results to stdout.
By default up to 100 tests are performed, which may not be enough
 to find all bugs. To run more tests, use withMaxSuccess.
Args specifies arguments to the QuickCheck driver
Constructors
| Args | |
| Fields 
 | |
Result represents the test result
Constructors
| Success | A successful test run | 
| Fields 
 | |
| GaveUp | Given up | 
| Fields 
 | |
| Failure | A failed test run | 
| Fields 
 | |
| NoExpectedFailure | A property that should have failed did not | 
| Fields 
 | |
quickCheckWith :: Testable prop => Args -> prop -> IO () Source #
Tests a property, using test arguments, and prints the results to stdout.
quickCheckWithResult :: Testable prop => Args -> prop -> IO Result Source #
Tests a property, using test arguments, produces a test result, and prints the results to stdout.
quickCheckResult :: Testable prop => prop -> IO Result Source #
Tests a property, produces a test result, and prints the results to stdout.
Running tests verbosely
verboseCheck :: Testable prop => prop -> IO () Source #
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 () Source #
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 Source #
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 Source #
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
These functions 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 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 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 -> 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 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 [].
The Arbitrary typeclass: generation of random values
class Arbitrary a where Source #
Random generation and shrinking of values.
QuickCheck provides Arbitrary instances for most types in base,
 except those which incur extra dependencies.
 For a wider range of Arbitrary instances see the
 quickcheck-instances
 package.
Minimal complete definition
Methods
A generator for values of the given type.
It is worth spending time thinking about what sort of test data
 you want - good generators are often the difference between
 finding bugs and not finding them. You can use sample,
 label and classify to check the quality of your test data.
There is no generic arbitrary implementation included because we don't
 know how to make a high-quality one. If you want one, consider using the
 testing-feat or
 generic-random packages.
The QuickCheck manual goes into detail on how to write good generators. Make sure to look at it, especially if your type is recursive!
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. If your data type has no special invariants, you can
 enable shrinking by defining shrink = , but by customising
 the behaviour of genericShrinkshrink you can often get simpler counterexamples.
Most implementations of shrink should try at least three things:
- Shrink a term to any of its immediate subterms.
    You can use subtermsto do this.
- Recursively apply shrinkto all immediate subterms. You can userecursivelyShrinkto do this.
- 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 shrinkx,landrin 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.
 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 xNil to Nil, and shrinking will go into an
 infinite loop.
If all this leaves you bewildered, you might try shrink = genericShrinkGeneric 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
Helper functions for implementing shrink
genericShrink :: (Generic a, RecursivelyShrink (Rep a), GSubterms (Rep a) a) => a -> [a] Source #
Shrink a term to any of its immediate subterms, and also recursively shrink all subterms.
recursivelyShrink :: (Generic a, RecursivelyShrink (Rep a)) => a -> [a] Source #
Recursively shrink all immediate subterms.
shrinkNothing :: a -> [a] Source #
Returns no shrinking alternatives.
shrinkList :: (a -> [a]) -> [a] -> [[a]] Source #
Shrink a list of values given a shrinking function for individual values.
shrinkMap :: Arbitrary a => (a -> b) -> (b -> a) -> b -> [b] Source #
Map a shrink function to another domain. This is handy if your data type has special invariants, but is almost isomorphic to some other type.
shrinkOrderedList :: (Ord a, Arbitrary a) => [a] -> [[a]] shrinkOrderedList = shrinkMap sort id shrinkSet :: (Ord a, Arbitrary a) => Set a -> Set [a] shrinkSet = shrinkMap fromList toList
shrinkMapBy :: (a -> b) -> (b -> a) -> (a -> [a]) -> b -> [b] Source #
Non-overloaded version of shrinkMap.
shrinkIntegral :: Integral a => a -> [a] Source #
Shrink an integral number.
shrinkRealFrac :: RealFrac a => a -> [a] Source #
Shrink a fraction, preferring numbers with smaller
 numerators or denominators. See also shrinkDecimal.
shrinkDecimal :: RealFrac a => a -> [a] Source #
Shrink a real number, preferring numbers with shorter
 decimal representations. See also shrinkRealFrac.
Lifting of Arbitrary to unary and binary type constructors
class Arbitrary1 f where Source #
Lifting of the Arbitrary class to unary type constructors.
Minimal complete definition
Methods
liftArbitrary :: Gen a -> Gen (f a) Source #
liftShrink :: (a -> [a]) -> f a -> [f a] Source #
Instances
arbitrary1 :: (Arbitrary1 f, Arbitrary a) => Gen (f a) Source #
shrink1 :: (Arbitrary1 f, Arbitrary a) => f a -> [f a] Source #
class Arbitrary2 f where Source #
Lifting of the Arbitrary class to binary type constructors.
Minimal complete definition
Methods
liftArbitrary2 :: Gen a -> Gen b -> Gen (f a b) Source #
liftShrink2 :: (a -> [a]) -> (b -> [b]) -> f a b -> [f a b] Source #
Instances
| Arbitrary2 Either Source # | |
| Defined in Test.QuickCheck.Arbitrary | |
| Arbitrary2 (,) Source # | |
| Defined in Test.QuickCheck.Arbitrary Methods liftArbitrary2 :: Gen a -> Gen b -> Gen (a, b) Source # liftShrink2 :: (a -> [a]) -> (b -> [b]) -> (a, b) -> [(a, b)] Source # | |
| Arbitrary2 (Const :: * -> * -> *) Source # | |
| Defined in Test.QuickCheck.Arbitrary | |
| Arbitrary2 (Constant :: * -> * -> *) Source # | |
| Defined in Test.QuickCheck.Arbitrary | |
arbitrary2 :: (Arbitrary2 f, Arbitrary a, Arbitrary b) => Gen (f a b) Source #
The Gen monad: combinators for building random generators
A generator for values of type a.
The third-party package
 QuickCheck-GenT
 provides a monad transformer version of GenT.
Generator combinators
choose :: Random a => (a, a) -> Gen a Source #
Generates a random element in the given inclusive range.
oneof :: [Gen a] -> Gen a Source #
Randomly uses one of the given generators. The input list must be non-empty.
frequency :: [(Int, Gen a)] -> Gen a Source #
Chooses one of the given generators, with a weighted random distribution. The input list must be non-empty.
elements :: [a] -> Gen a Source #
Generates one of the given values. The input list must be non-empty.
growingElements :: [a] -> Gen a Source #
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 Source #
Used to construct generators that depend on the size parameter.
For example, listOf, which uses the size parameter as an upper bound on
 length of lists it generates, can be defined like this:
listOf :: Gen a -> Gen [a]
listOf gen = sized $ \n ->
  do k <- choose (0,n)
     vectorOf k genYou can also do this using getSize.
Returns the size parameter. Used to construct generators that depend on the size parameter.
For example, listOf, which uses the size parameter as an upper bound on
 length of lists it generates, can be defined like this:
listOf :: Gen a -> Gen [a] listOf gen = do n <- getSize k <- choose (0,n) vectorOf k gen
You can also do this using sized.
resize :: Int -> Gen a -> Gen a Source #
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 Source #
Adjust the size parameter, by transforming it with the given function.
suchThatMap :: Gen a -> (a -> Maybe b) -> Gen b Source #
Generates a value for which the given function returns a Just, and then
 applies the function.
suchThatMaybe :: Gen a -> (a -> Bool) -> Gen (Maybe a) Source #
Tries to generate a value that satisfies a predicate.
 If it fails to do so after enough attempts, returns Nothing.
applyArbitrary2 :: (Arbitrary a, Arbitrary b) => (a -> b -> r) -> Gen r Source #
Apply a binary function to random arguments.
applyArbitrary3 :: (Arbitrary a, Arbitrary b, Arbitrary c) => (a -> b -> c -> r) -> Gen r Source #
Apply a ternary function to random arguments.
applyArbitrary4 :: (Arbitrary a, Arbitrary b, Arbitrary c, Arbitrary d) => (a -> b -> c -> d -> r) -> Gen r Source #
Apply a function of arity 4 to random arguments.
Generators for lists
listOf :: Gen a -> Gen [a] Source #
Generates a list of random length. The maximum length depends on the size parameter.
listOf1 :: Gen a -> Gen [a] Source #
Generates a non-empty list of random length. The maximum length depends on the size parameter.
infiniteListOf :: Gen a -> Gen [a] Source #
Generates an infinite list.
infiniteList :: Arbitrary a => Gen [a] Source #
Generates an infinite list.
Generators for particular types
arbitrarySizedIntegral :: Integral a => Gen a Source #
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 Source #
Generates a natural number. The number's maximum value depends on the size parameter.
arbitrarySizedFractional :: Fractional a => Gen a Source #
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 Source #
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 Source #
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 Source #
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 Source #
Generates an element of a bounded enumeration.
arbitraryUnicodeChar :: Gen Char Source #
Generates any Unicode character (but not a surrogate)
arbitraryASCIIChar :: Gen Char Source #
Generates a random ASCII character (0-127).
arbitraryPrintableChar :: Gen Char Source #
Generates a printable Unicode character.
Running generators
generate :: Gen a -> IO a Source #
Run a generator. The size passed to the generator is always 30;
 if you want another size then you should explicitly use resize.
Debugging generators
The Function typeclass: generation of random shrinkable, showable functions
Example of use:
>>>:{>>>let prop :: Fun String Integer -> Bool>>>prop (Fun _ f) = f "monkey" == f "banana" || f "banana" == f "elephant">>>:}>>>quickCheck prop*** Failed! Falsifiable (after 3 tests and 134 shrinks): {"elephant"->1, "monkey"->1, _->0}
To generate random values of type Fun a bFunction aShow instance, you can use functionShow to write the instance; otherwise,
 use functionMap to give a bijection between your type and a type that is already an instance of Function.
 See the Function [a]
For more information, see the paper "Shrinking and showing functions" by Koen Claessen.
Generation of random shrinkable, showable functions.
To generate random values of type Fun a bFunction a
applyFun :: Fun a b -> a -> b Source #
Extracts the value of a function.
Fn is the pattern equivalent of this function.
prop :: Fun String Integer -> Bool
prop f = applyFun f "banana" == applyFun f "monkey"
      || applyFun f "banana" == applyFun f "elephant"applyFun2 :: Fun (a, b) c -> a -> b -> c Source #
Extracts the value of a binary function.
Fn2 is the pattern equivalent of this function.
prop_zipWith :: Fun (Int, Bool) Char -> [Int] -> [Bool] -> Bool prop_zipWith f xs ys = zipWith (applyFun2 f) xs ys == [ applyFun2 f x y | (x, y) <- zip xs ys]
applyFun3 :: Fun (a, b, c) d -> a -> b -> c -> d Source #
Extracts the value of a ternary function. Fn3 is the
 pattern equivalent of this function.
pattern Fn :: (a -> b) -> Fun a b Source #
A modifier for testing functions.
prop :: Fun String Integer -> Bool
prop (Fn f) = f "banana" == f "monkey"
           || f "banana" == f "elephant"pattern Fn2 :: (a -> b -> c) -> Fun (a, b) c Source #
A modifier for testing binary functions.
prop_zipWith :: Fun (Int, Bool) Char -> [Int] -> [Bool] -> Bool prop_zipWith (Fn2 f) xs ys = zipWith f xs ys == [ f x y | (x, y) <- zip xs ys]
pattern Fn3 :: (a -> b -> c -> d) -> Fun (a, b, c) d Source #
A modifier for testing ternary functions.
class Function a where Source #
The class Function a is used for random generation of showable
 functions of type a -> b.
There is a default implementation for function, which you can use
 if your type has structural equality. Otherwise, you can normally
 use functionMap or functionShow.
Methods
function :: (a -> b) -> a :-> b Source #
function :: (Generic a, GFunction (Rep a)) => (a -> b) -> a :-> b Source #
Instances
functionMap :: Function b => (a -> b) -> (b -> a) -> (a -> c) -> a :-> c Source #
functionIntegral :: Integral a => (a -> b) -> a :-> b Source #
functionRealFrac :: RealFrac a => (a -> b) -> a :-> b Source #
The CoArbitrary typeclass: generation of functions the old-fashioned way
class CoArbitrary a where Source #
Used for random generation of functions.
 You should consider using Fun instead, which
 can show the generated functions as strings.
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).
Methods
coarbitrary :: a -> Gen b -> Gen b Source #
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 [] =variant0 coarbitrary (x:xs) =variant1 . coarbitrary (x,xs)
coarbitrary :: (Generic a, GCoArbitrary (Rep a)) => a -> Gen b -> Gen b Source #
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 [] =variant0 coarbitrary (x:xs) =variant1 . coarbitrary (x,xs)
Instances
genericCoarbitrary :: (Generic a, GCoArbitrary (Rep a)) => a -> Gen b -> Gen b Source #
Generic CoArbitrary implementation.
coarbitraryIntegral :: Integral a => a -> Gen b -> Gen b Source #
A coarbitrary implementation for integral numbers.
coarbitraryReal :: Real a => a -> Gen b -> Gen b Source #
A coarbitrary implementation for real numbers.
coarbitraryShow :: Show a => a -> Gen b -> Gen b Source #
coarbitrary helper for lazy people :-).
coarbitraryEnum :: Enum a => a -> Gen b -> Gen b Source #
A coarbitrary implementation for enums.
(><) :: (Gen a -> Gen a) -> (Gen a -> Gen a) -> Gen a -> Gen a Source #
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
These types do things such as restricting the kind of test data that can be generated. They can be pattern-matched on in properties as a stylistic alternative to using explicit quantification.
Examples:
-- Functions cannot be shown (but seeFunction) prop_TakeDropWhile (Blindp) (xs :: [A]) = takeWhile p xs ++ dropWhile p xs == xs
prop_TakeDrop (NonNegativen) (xs :: [A]) = take n xs ++ drop n xs == xs
-- cycle does not work for empty lists prop_Cycle (NonNegativen) (NonEmpty(xs :: [A])) = take n (cycle xs) == take n (xs ++ cycle xs)
-- Instead offorAllorderedListprop_Sort (Ordered(xs :: [OrdA])) = sort xs == xs
Blind x: as x, but x does not have to be in the Show class.
Instances
| Functor Blind Source # | |
| Enum a => Enum (Blind a) Source # | |
| Eq a => Eq (Blind a) Source # | |
| Integral a => Integral (Blind a) Source # | |
| Defined in Test.QuickCheck.Modifiers | |
| Num a => Num (Blind a) Source # | |
| Ord a => Ord (Blind a) Source # | |
| Defined in Test.QuickCheck.Modifiers | |
| Real a => Real (Blind a) Source # | |
| Defined in Test.QuickCheck.Modifiers Methods toRational :: Blind a -> Rational # | |
| Show (Blind a) Source # | |
| Arbitrary a => Arbitrary (Blind a) Source # | |
Fixed x: as x, but will not be shrunk.
Instances
| Functor Fixed Source # | |
| Enum a => Enum (Fixed a) Source # | |
| Eq a => Eq (Fixed a) Source # | |
| Integral a => Integral (Fixed a) Source # | |
| Defined in Test.QuickCheck.Modifiers | |
| Num a => Num (Fixed a) Source # | |
| Ord a => Ord (Fixed a) Source # | |
| Defined in Test.QuickCheck.Modifiers | |
| Read a => Read (Fixed a) Source # | |
| Real a => Real (Fixed a) Source # | |
| Defined in Test.QuickCheck.Modifiers Methods toRational :: Fixed a -> Rational # | |
| Show a => Show (Fixed a) Source # | |
| Arbitrary a => Arbitrary (Fixed a) Source # | |
newtype OrderedList a Source #
Ordered xs: guarantees that xs is ordered.
Constructors
| Ordered | |
| Fields 
 | |
Instances
newtype NonEmptyList a Source #
NonEmpty xs: guarantees that xs is non-empty.
Constructors
| NonEmpty | |
| Fields 
 | |
Instances
data InfiniteList a Source #
InfiniteList xs _: guarantees that xs is an infinite list.
 When a counterexample is found, only prints the prefix of xs
 that was used by the program.
Here is a contrived example property:
prop_take_10 :: InfiniteList Char -> Bool prop_take_10 (InfiniteList xs _) = or [ x == 'a' | x <- take 10 xs ]
In the following counterexample, the list must start with "bbbbbbbbbb" but
 the remaining (infinite) part can contain anything:
>>>quickCheck prop_take_10*** Failed! Falsifiable (after 1 test and 14 shrinks): "bbbbbbbbbb" ++ ...
Constructors
| InfiniteList | |
| Fields 
 | |
Instances
| Show a => Show (InfiniteList a) Source # | |
| Defined in Test.QuickCheck.Modifiers Methods showsPrec :: Int -> InfiniteList a -> ShowS # show :: InfiniteList a -> String # showList :: [InfiniteList a] -> ShowS # | |
| Arbitrary a => Arbitrary (InfiniteList a) Source # | |
| Defined in Test.QuickCheck.Modifiers Methods arbitrary :: Gen (InfiniteList a) Source # shrink :: InfiniteList a -> [InfiniteList a] Source # | |
newtype SortedList a Source #
Sorted xs: guarantees that xs is sorted.
Instances
Positive x: guarantees that x > 0.
Constructors
| Positive | |
| Fields 
 | |
Instances
| Functor Positive Source # | |
| Enum a => Enum (Positive a) Source # | |
| Defined in Test.QuickCheck.Modifiers Methods succ :: Positive a -> Positive a # pred :: Positive a -> Positive a # fromEnum :: Positive a -> Int # enumFrom :: Positive a -> [Positive a] # enumFromThen :: Positive a -> Positive a -> [Positive a] # enumFromTo :: Positive a -> Positive a -> [Positive a] # enumFromThenTo :: Positive a -> Positive a -> Positive a -> [Positive a] # | |
| Eq a => Eq (Positive a) Source # | |
| Ord a => Ord (Positive a) Source # | |
| Defined in Test.QuickCheck.Modifiers | |
| Read a => Read (Positive a) Source # | |
| Show a => Show (Positive a) Source # | |
| (Num a, Ord a, Arbitrary a) => Arbitrary (Positive a) Source # | |
NonZero x: guarantees that x /= 0.
Constructors
| NonZero | |
| Fields 
 | |
Instances
| Functor NonZero Source # | |
| Enum a => Enum (NonZero a) Source # | |
| Defined in Test.QuickCheck.Modifiers Methods succ :: NonZero a -> NonZero a # pred :: NonZero a -> NonZero a # fromEnum :: NonZero a -> Int # enumFrom :: NonZero a -> [NonZero a] # enumFromThen :: NonZero a -> NonZero a -> [NonZero a] # enumFromTo :: NonZero a -> NonZero a -> [NonZero a] # enumFromThenTo :: NonZero a -> NonZero a -> NonZero a -> [NonZero a] # | |
| Eq a => Eq (NonZero a) Source # | |
| Ord a => Ord (NonZero a) Source # | |
| Read a => Read (NonZero a) Source # | |
| Show a => Show (NonZero a) Source # | |
| (Num a, Eq a, Arbitrary a) => Arbitrary (NonZero a) Source # | |
newtype NonNegative a Source #
NonNegative x: guarantees that x >= 0.
Constructors
| NonNegative | |
| Fields 
 | |
Instances
Large x: by default, QuickCheck generates Ints drawn from a small
 range. Large Int gives you values drawn from the entire range instead.
Instances
| Functor Large Source # | |
| Enum a => Enum (Large a) Source # | |
| Eq a => Eq (Large a) Source # | |
| Integral a => Integral (Large a) Source # | |
| Defined in Test.QuickCheck.Modifiers | |
| Num a => Num (Large a) Source # | |
| Ord a => Ord (Large a) Source # | |
| Defined in Test.QuickCheck.Modifiers | |
| Read a => Read (Large a) Source # | |
| Real a => Real (Large a) Source # | |
| Defined in Test.QuickCheck.Modifiers Methods toRational :: Large a -> Rational # | |
| Show a => Show (Large a) Source # | |
| Ix a => Ix (Large a) Source # | |
| Defined in Test.QuickCheck.Modifiers | |
| (Integral a, Bounded a) => Arbitrary (Large a) Source # | |
Small x: generates values of x drawn from a small range.
 The opposite of Large.
Instances
| Functor Small Source # | |
| Enum a => Enum (Small a) Source # | |
| Eq a => Eq (Small a) Source # | |
| Integral a => Integral (Small a) Source # | |
| Defined in Test.QuickCheck.Modifiers | |
| Num a => Num (Small a) Source # | |
| Ord a => Ord (Small a) Source # | |
| Defined in Test.QuickCheck.Modifiers | |
| Read a => Read (Small a) Source # | |
| Real a => Real (Small a) Source # | |
| Defined in Test.QuickCheck.Modifiers Methods toRational :: Small a -> Rational # | |
| Show a => Show (Small a) Source # | |
| Ix a => Ix (Small a) Source # | |
| Defined in Test.QuickCheck.Modifiers | |
| Integral a => Arbitrary (Small a) Source # | |
Smart _ x: tries a different order when shrinking.
Shrink2 x: allows 2 shrinking steps at the same time when shrinking x
Constructors
| Shrink2 | |
| Fields 
 | |
Instances
Shrinking _ x: allows for maintaining a state during shrinking.
Constructors
| Shrinking s a | 
class ShrinkState s a where Source #
Minimal complete definition
newtype ASCIIString Source #
ASCIIString: generates an ASCII string.
Constructors
| ASCIIString | |
| Fields | |
Instances
| Eq ASCIIString Source # | |
| Defined in Test.QuickCheck.Modifiers | |
| Ord ASCIIString Source # | |
| Defined in Test.QuickCheck.Modifiers Methods compare :: ASCIIString -> ASCIIString -> Ordering # (<) :: ASCIIString -> ASCIIString -> Bool # (<=) :: ASCIIString -> ASCIIString -> Bool # (>) :: ASCIIString -> ASCIIString -> Bool # (>=) :: ASCIIString -> ASCIIString -> Bool # max :: ASCIIString -> ASCIIString -> ASCIIString # min :: ASCIIString -> ASCIIString -> ASCIIString # | |
| Read ASCIIString Source # | |
| Defined in Test.QuickCheck.Modifiers Methods readsPrec :: Int -> ReadS ASCIIString # readList :: ReadS [ASCIIString] # readPrec :: ReadPrec ASCIIString # readListPrec :: ReadPrec [ASCIIString] # | |
| Show ASCIIString Source # | |
| Defined in Test.QuickCheck.Modifiers Methods showsPrec :: Int -> ASCIIString -> ShowS # show :: ASCIIString -> String # showList :: [ASCIIString] -> ShowS # | |
| Arbitrary ASCIIString Source # | |
| Defined in Test.QuickCheck.Modifiers | |
newtype UnicodeString Source #
UnicodeString: generates a unicode String.
 The string will not contain surrogate pairs.
Constructors
| UnicodeString | |
| Fields | |
Instances
newtype PrintableString Source #
PrintableString: generates a printable unicode String.
 The string will not contain surrogate pairs.
Constructors
| PrintableString | |
| Fields | |
Instances
Property combinators
The type of properties.
class Testable prop where Source #
The class of properties, i.e., types which QuickCheck knows how to test.
 Typically a property will be a function returning Bool or Property.
If a property does no quantification, i.e. has no
 parameters and doesn't use forAll, it will only be tested once.
 This may not be what you want if your property is an IO Bool.
 You can change this behaviour using the again combinator.
Minimal complete definition
forAll :: (Show a, Testable prop) => Gen a -> (a -> prop) -> Property Source #
Explicit universal quantification: uses an explicitly given test case generator.
forAllShrink :: (Show a, Testable prop) => Gen a -> (a -> [a]) -> (a -> prop) -> Property Source #
Like forAll, but tries to shrink the argument for failing test cases.
forAllShow :: Testable prop => Gen a -> (a -> String) -> (a -> prop) -> Property Source #
Like forAll, but with an explicitly given show function.
forAllShrinkShow :: Testable prop => Gen a -> (a -> [a]) -> (a -> String) -> (a -> prop) -> Property Source #
Like forAllShrink, but with an explicitly given show function.
forAllBlind :: Testable prop => Gen a -> (a -> prop) -> Property Source #
Like forAll, but without printing the generated value.
forAllShrinkBlind :: Testable prop => Gen a -> (a -> [a]) -> (a -> prop) -> Property Source #
Like forAllShrink, but without printing the generated value.
Arguments
| :: Testable prop | |
| => (a -> [a]) | 
 | 
| -> a | The original argument | 
| -> (a -> prop) | |
| -> Property | 
Shrinks the argument to a property if it fails. Shrinking is done automatically for most types. This function is only needed when you want to override the default behavior.
(==>) :: Testable prop => Bool -> prop -> Property infixr 0 Source #
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. Note that using implication carelessly can
 severely skew test case distribution: consider using cover to make sure
 that your test data is still good quality.
If a property returns Discard, the current test case is discarded,
 the same as if a precondition was false.
An example is the definition of ==>:
(==>) :: Testable prop => Bool -> prop -> Property False ==> _ = property Discard True ==> p = property p
Constructors
| Discard | 
(===) :: (Eq a, Show a) => a -> a -> Property infix 4 Source #
Like ==, but prints a counterexample when it fails.
(=/=) :: (Eq a, Show a) => a -> a -> Property infix 4 Source #
Like /=, but prints a counterexample when it fails.
total :: NFData a => a -> Property Source #
Checks that a value is total, i.e., doesn't crash when evaluated.
ioProperty :: Testable prop => IO prop -> Property Source #
Do I/O inside a property.
Warning: any random values generated inside of the argument to ioProperty
 will not currently be shrunk. For best results, generate all random values
 before calling ioProperty, or use idempotentIOProperty if that is safe.
Note: if your property does no quantification, it will only be tested once.
 To test it repeatedly, use again.
idempotentIOProperty :: Testable prop => IO prop -> Property Source #
Do I/O inside a property.
Warning: during shrinking, the I/O may not always be re-executed.
 Instead, the I/O may be executed once and then its result retained.
 If this is not acceptable, use ioProperty instead.
Controlling property execution
verbose :: Testable prop => prop -> Property Source #
Prints out the generated testcase every time the property is tested.
 Only variables quantified over inside the verbose are printed.
verboseShrinking :: Testable prop => prop -> Property Source #
Prints out the generated testcase every time the property fails, including during shrinking.
 Only variables quantified over inside the verboseShrinking are printed.
noShrinking :: Testable prop => prop -> Property Source #
Disables shrinking for a property altogether.
 Only quantification inside the call to noShrinking is affected.
withMaxSuccess :: Testable prop => Int -> prop -> Property Source #
Configures how many times a property will be tested.
For example,
quickCheck (withMaxSuccess 1000 p)
will test p up to 1000 times.
within :: Testable prop => Int -> prop -> Property Source #
Considers a property failed if it does not complete within the given number of microseconds.
once :: Testable prop => prop -> Property Source #
Modifies a property so that it only will be tested once.
 Opposite of again.
again :: Testable prop => prop -> Property Source #
Modifies a property so that it will be tested repeatedly.
 Opposite of once.
mapSize :: Testable prop => (Int -> Int) -> prop -> Property Source #
Adjust the test case size for a property, by transforming it with the given function.
Conjunction and disjunction
(.&.) :: (Testable prop1, Testable prop2) => prop1 -> prop2 -> Property infixr 1 Source #
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 Source #
Conjunction: p1 .&&. p2 passes if both p1 and p2 pass.
(.||.) :: (Testable prop1, Testable prop2) => prop1 -> prop2 -> Property infixr 1 Source #
Disjunction: p1 .||. p2 passes unless p1 and p2 simultaneously fail.
What to do on failure
counterexample :: Testable prop => String -> prop -> Property Source #
Adds the given string to the counterexample if the property fails.
printTestCase :: Testable prop => String -> prop -> Property Source #
Deprecated: Use counterexample instead
Adds the given string to the counterexample if the property fails.
whenFail :: Testable prop => IO () -> prop -> Property Source #
Performs an IO action after the last failure of a property.
whenFail' :: Testable prop => IO () -> prop -> Property Source #
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 Source #
Indicates that a property is supposed to fail. QuickCheck will report an error if it does not fail.
Analysing test case distribution
label :: Testable prop => String -> prop -> Property Source #
Attaches a label to a test case. This is used for reporting test case distribution.
For example:
prop_reverse_reverse :: [Int] -> Property
prop_reverse_reverse xs =
  label ("length of input is " ++ show (length xs)) $
    reverse (reverse xs) === xs>>>quickCheck prop_reverse_reverse+++ OK, passed 100 tests: 7% length of input is 7 6% length of input is 3 5% length of input is 4 4% length of input is 6 ...
Each use of label in your property results in a separate
 table of test case distribution in the output. If this is
 not what you want, use tabulate.
collect :: (Show a, Testable prop) => a -> prop -> Property Source #
Attaches a label to a test case. This is used for reporting test case distribution.
collect x = label (show x)
For example:
prop_reverse_reverse :: [Int] -> Property
prop_reverse_reverse xs =
  collect (length xs) $
    reverse (reverse xs) === xs>>>quickCheck prop_reverse_reverse+++ OK, passed 100 tests: 7% 7 6% 3 5% 4 4% 6 ...
Each use of collect in your property results in a separate
 table of test case distribution in the output. If this is
 not what you want, use tabulate.
Arguments
| :: Testable prop | |
| => Bool | 
 | 
| -> String | Label. | 
| -> prop | |
| -> Property | 
Reports how many test cases satisfy a given condition.
For example:
prop_sorted_sort :: [Int] -> Property prop_sorted_sort xs = sorted xs ==> classify (length xs > 1) "non-trivial" $ sort xs === xs
>>>quickCheck prop_sorted_sort+++ OK, passed 100 tests (22% non-trivial).
tabulate :: Testable prop => String -> [String] -> prop -> Property Source #
Collects information about test case distribution into a table.
 The arguments to tabulate are the table's name and a list of values
 associated with the current test case. After testing, QuickCheck prints the
 frequency of all collected values. The frequencies are expressed as a
 percentage of the total number of values collected.
You should prefer tabulate to label when each test case is associated
 with a varying number of values. Here is a (not terribly useful) example,
 where the test data is a list of integers and we record all values that
 occur in the list:
prop_sorted_sort :: [Int] -> Property prop_sorted_sort xs = sorted xs ==> tabulate "List elements" (map show xs) $ sort xs === xs
>>>quickCheck prop_sorted_sort+++ OK, passed 100 tests; 1684 discarded. List elements (109 in total): 3.7% 0 3.7% 17 3.7% 2 3.7% 6 2.8% -6 2.8% -7
Here is a more useful example. We are testing a chatroom, where the user can log in, log out, or send a message:
data Command = LogIn | LogOut | SendMessage String deriving (Data, Show) instance Arbitrary Command where ...
There are some restrictions on command sequences; for example, the user must
 log in before doing anything else. The function valid :: [Command] -> Bool
 checks that a command sequence is allowed. Our property then has the form:
prop_chatroom :: [Command] -> Property
prop_chatroom cmds =
  valid cmds ==>
    ...The use of ==> may skew test case distribution. We use collect to see the
 length of the command sequences, and tabulate to get the frequencies of the
 individual commands:
prop_chatroom :: [Command] -> Property
prop_chatroom cmds =
  wellFormed cmds LoggedOut ==>
  'collect' (length cmds) $
  'tabulate' "Commands" (map (show . 'Data.Data.toConstr') cmds) $
    ...>>>quickCheckWith stdArgs{maxDiscardRatio = 1000} prop_chatroom+++ OK, passed 100 tests; 2775 discarded: 60% 0 20% 1 15% 2 3% 3 1% 4 1% 5 Commands (68 in total): 62% LogIn 22% SendMessage 16% LogOut
Checking test case distribution
Arguments
| :: Testable prop | |
| => Double | The required percentage (0-100) of test cases. | 
| -> Bool | 
 | 
| -> 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.
Note: If the coverage check fails, QuickCheck prints out a warning, but
 the property does not fail. To make the property fail, use checkCoverage.
For example:
prop_sorted_sort :: [Int] -> Property prop_sorted_sort xs = sorted xs ==> cover 50 (length xs > 1) "non-trivial" $ sort xs === xs
>>>quickCheck prop_sorted_sort+++ OK, passed 100 tests; 135 discarded (26% non-trivial). Only 26% non-trivial, but expected 50%
coverTable :: Testable prop => String -> [(String, Double)] -> prop -> Property Source #
Checks that the values in a given table appear a certain proportion of
 the time. A call to coverTable table [(x1, p1), ..., (xn, pn)] asserts
 that of the values in table, x1 should appear at least p1 percent of
 the time, x2 at least p2 percent of the time, and so on.
Note: If the coverage check fails, QuickCheck prints out a warning, but
 the property does not fail. To make the property fail, use checkCoverage.
Continuing the example from the tabular combinator...
data Command = LogIn | LogOut | SendMessage String deriving (Data, Show)
prop_chatroom :: [Command] -> Property
prop_chatroom cmds =
  wellFormed cmds LoggedOut ==>
  'tabulate' "Commands" (map (show . 'Data.Data.toConstr') cmds) $
    ......we can add a coverage requirement as follows, which checks that LogIn,
 LogOut and SendMessage each occur at least 25% of the time:
prop_chatroom :: [Command] -> Property
prop_chatroom cmds =
  wellFormed cmds LoggedOut ==>
  coverTable "Commands" [("LogIn", 25), ("LogOut", 25), ("SendMessage", 25)] $
  'tabulate' "Commands" (map (show . 'Data.Data.toConstr') cmds) $
    ... property goes here ...>>>quickCheck prop_chatroom+++ OK, passed 100 tests; 2909 discarded: 56% 0 17% 1 10% 2 6% 3 5% 4 3% 5 3% 7 Commands (111 in total): 51.4% LogIn 30.6% SendMessage 18.0% LogOut Table 'Commands' had only 18.0% LogOut, but expected 25.0%
checkCoverage :: Testable prop => prop -> Property Source #
Check that all coverage requirements defined by cover and coverTable
 are met, using a statistically sound test, and fail if they are not met.
Ordinarily, a failed coverage check does not cause the property to fail.
 This is because the coverage requirement is not tested in a statistically
 sound way. If you use cover to express that a certain value must appear 20%
 of the time, QuickCheck will warn you if the value only appears in 19 out of
 100 test cases - but since the coverage varies randomly, you may have just
 been unlucky, and there may not be any real problem with your test
 generation.
When you use checkCoverage, QuickCheck uses a statistical test to account
 for the role of luck in coverage failures. It will run as many tests as
 needed until it is sure about whether the coverage requirements are met. If a
 coverage requirement is not met, the property fails.
Example:
quickCheck (checkCoverage prop_foo)
checkCoverageWith :: Testable prop => Confidence -> prop -> Property Source #
Check coverage requirements using a custom confidence level.
 See stdConfidence.
An example of making the statistical test less stringent in order to improve performance:
quickCheck (checkCoverageWith stdConfidence{certainty = 10^6} prop_foo)data Confidence Source #
The statistical parameters used by checkCoverage.
Constructors
| Confidence | |
| Fields 
 | |
Instances
| Show Confidence Source # | |
| Defined in Test.QuickCheck.State Methods showsPrec :: Int -> Confidence -> ShowS # show :: Confidence -> String # showList :: [Confidence] -> ShowS # | |
stdConfidence :: Confidence Source #
The standard parameters used by checkCoverage: certainty = 10^9,
 tolerance = 0.9. See Confidence for the meaning of the parameters.
Generating example test cases
labelledExamples :: Testable prop => prop -> IO () Source #
Given a property, which must use label, collect, classify or cover
 to associate labels with test cases, find an example test case for each possible label.
 The example test cases are minimised using shrinking.
For example, suppose we test delete x xsx occurs in xs:
prop_delete :: Int -> [Int] -> Property prop_delete x xs = classify (count x xs == 0) "count x xs == 0" $ classify (count x xs == 1) "count x xs == 1" $ classify (count x xs >= 2) "count x xs >= 2" $ counterexample (show (delete x xs)) $ count x (delete x xs) == max 0 (count x xs-1) where count x xs = length (filter (== x) xs)
labelledExamples generates three example test cases, one for each label:
>>>labelledExamples prop_delete*** Found example of count x xs == 0 0 [] [] *** Found example of count x xs == 1 0 [0] [] *** Found example of count x xs >= 2 5 [5,5] [5] +++ OK, passed 100 tests: 78% count x xs == 0 21% count x xs == 1 1% count x xs >= 2
labelledExamplesWith :: Testable prop => Args -> prop -> IO () Source #
A variant of labelledExamples that takes test arguments.
labelledExamplesWithResult :: Testable prop => Args -> prop -> IO Result Source #
A variant of labelledExamples that takes test arguments and returns a result.
labelledExamplesResult :: Testable prop => prop -> IO Result Source #
A variant of labelledExamples that returns a result.