QuickCheck-2.7: Automatic testing of Haskell programs

Safe HaskellNone

Test.QuickCheck.Arbitrary

Contents

Description

Type classes for random generation of values.

Synopsis

Arbitrary and CoArbitrary classes

class Arbitrary a whereSource

Random generation and shrinking of values.

Methods

arbitrary :: Gen aSource

A generator for values of the given type.

shrink :: a -> [a]Source

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 and Typeable 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 OrdC 
Arbitrary OrdB 
Arbitrary OrdA 
Arbitrary C 
Arbitrary B 
Arbitrary A 
Arbitrary a => Arbitrary [a] 
(Integral a, Arbitrary a) => Arbitrary (Ratio a) 
HasResolution a => Arbitrary (Fixed a) 
(RealFloat a, Arbitrary a) => Arbitrary (Complex a) 
Arbitrary a => Arbitrary (Maybe 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, Ord 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) 
(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 whereSource

Used for random generation of functions.

Methods

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

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 :: Num a => Gen aSource

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

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

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

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

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.

arbitrarySizedFractional :: Fractional a => Gen aSource

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

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

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

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

Generates an element of a bounded enumeration.

Helper functions for implementing shrink

genericShrink :: (Generic a, Typeable a, RecursivelyShrink (Rep a), Subterms (Rep a)) => a -> [a]Source

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

subterms :: (Generic a, Typeable a, Subterms (Rep a)) => a -> [a]Source

All immediate subterms of a term.

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.

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

Shrink an integral number.

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

Shrink a fraction.

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

Shrink a fraction, but only shrink to integral values.

Helper functions for implementing coarbitrary

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

A coarbitrary implementation for integral numbers.

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

A coarbitrary implementation for real numbers.

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

coarbitrary helper for lazy people :-).

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

A coarbitrary implementation for enums.

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

Deprecated: Use ordinary function composition instead

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

Generators which use arbitrary

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

Generates a list of a given length.

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

Generates an ordered list of a given length.

infiniteList :: Arbitrary a => Gen [a]Source

Generate an infinite list.