Safe Haskell | Safe-Inferred |
---|
Type classes for random generation of values.
- class Arbitrary a where
- class CoArbitrary a where
- coarbitrary :: a -> Gen b -> Gen b
- arbitrarySizedIntegral :: Integral a => Gen a
- arbitraryBoundedIntegral :: (Bounded a, Integral a) => Gen a
- arbitrarySizedBoundedIntegral :: (Bounded a, Integral a) => Gen a
- arbitrarySizedFractional :: Fractional a => Gen a
- arbitraryBoundedRandom :: (Bounded a, Random a) => Gen a
- arbitraryBoundedEnum :: (Bounded a, Enum a) => Gen a
- genericShrink :: (Generic a, Typeable a, RecursivelyShrink (Rep a), Subterms (Rep a)) => a -> [a]
- subterms :: (Generic a, Typeable a, Subterms (Rep a)) => a -> [a]
- recursivelyShrink :: (Generic a, RecursivelyShrink (Rep a)) => a -> [a]
- shrinkNothing :: a -> [a]
- shrinkList :: (a -> [a]) -> [a] -> [[a]]
- shrinkIntegral :: Integral a => a -> [a]
- shrinkRealFrac :: RealFrac a => a -> [a]
- shrinkRealFracToInteger :: RealFrac a => a -> [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
- vector :: Arbitrary a => Int -> Gen [a]
- orderedList :: (Ord a, Arbitrary a) => Gen [a]
- infiniteList :: Arbitrary a => Gen [a]
Arbitrary and CoArbitrary classes
Random generation and shrinking of values.
A generator for values of the given type.
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:
- Shrink a term to any of its immediate subterms.
- Recursively apply
shrink
to all immediate subterms. - 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
,l
andr
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
as this shrinks shrink
x = Nil:genericShrink
xNil
to Nil
, and shrinking will go into an
infinite loop.
If all this leaves you bewildered, you might try
to begin with,
after deriving shrink
= genericShrink
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.
class CoArbitrary a whereSource
Used for random generation of functions.
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 :: Integral 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
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.