QuickCheck-2.9.2: Automatic testing of Haskell programs

Safe HaskellSafe
LanguageHaskell98

Test.QuickCheck.Arbitrary

Contents

Description

Type classes for random generation of values.

Synopsis

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 # 

Methods

arbitrary :: Gen Bool #

shrink :: Bool -> [Bool] #

Arbitrary Char # 

Methods

arbitrary :: Gen Char #

shrink :: Char -> [Char] #

Arbitrary Double # 
Arbitrary Float # 

Methods

arbitrary :: Gen Float #

shrink :: Float -> [Float] #

Arbitrary Int # 

Methods

arbitrary :: Gen Int #

shrink :: Int -> [Int] #

Arbitrary Int8 # 

Methods

arbitrary :: Gen Int8 #

shrink :: Int8 -> [Int8] #

Arbitrary Int16 # 

Methods

arbitrary :: Gen Int16 #

shrink :: Int16 -> [Int16] #

Arbitrary Int32 # 

Methods

arbitrary :: Gen Int32 #

shrink :: Int32 -> [Int32] #

Arbitrary Int64 # 

Methods

arbitrary :: Gen Int64 #

shrink :: Int64 -> [Int64] #

Arbitrary Integer # 
Arbitrary Ordering # 
Arbitrary Word # 

Methods

arbitrary :: Gen Word #

shrink :: Word -> [Word] #

Arbitrary Word8 # 

Methods

arbitrary :: Gen Word8 #

shrink :: Word8 -> [Word8] #

Arbitrary Word16 # 
Arbitrary Word32 # 
Arbitrary Word64 # 
Arbitrary () # 

Methods

arbitrary :: Gen () #

shrink :: () -> [()] #

Arbitrary Natural # 
Arbitrary Version #

Generates Version with non-empty non-negative versionBranch, and empty versionTags

Arbitrary All # 

Methods

arbitrary :: Gen All #

shrink :: All -> [All] #

Arbitrary Any # 

Methods

arbitrary :: Gen Any #

shrink :: Any -> [Any] #

Arbitrary IntSet # 
Arbitrary OrdC # 

Methods

arbitrary :: Gen OrdC #

shrink :: OrdC -> [OrdC] #

Arbitrary OrdB # 

Methods

arbitrary :: Gen OrdB #

shrink :: OrdB -> [OrdB] #

Arbitrary OrdA # 

Methods

arbitrary :: Gen OrdA #

shrink :: OrdA -> [OrdA] #

Arbitrary C # 

Methods

arbitrary :: Gen C #

shrink :: C -> [C] #

Arbitrary B # 

Methods

arbitrary :: Gen B #

shrink :: B -> [B] #

Arbitrary A # 

Methods

arbitrary :: Gen A #

shrink :: A -> [A] #

Arbitrary a => Arbitrary [a] # 

Methods

arbitrary :: Gen [a] #

shrink :: [a] -> [[a]] #

Arbitrary a => Arbitrary (Maybe a) # 

Methods

arbitrary :: Gen (Maybe a) #

shrink :: Maybe a -> [Maybe a] #

Integral a => Arbitrary (Ratio a) # 

Methods

arbitrary :: Gen (Ratio a) #

shrink :: Ratio a -> [Ratio a] #

Arbitrary a => Arbitrary (Identity a) # 

Methods

arbitrary :: Gen (Identity a) #

shrink :: Identity a -> [Identity a] #

Arbitrary a => Arbitrary (NonEmpty a) # 

Methods

arbitrary :: Gen (NonEmpty a) #

shrink :: NonEmpty a -> [NonEmpty a] #

HasResolution a => Arbitrary (Fixed a) # 

Methods

arbitrary :: Gen (Fixed a) #

shrink :: Fixed a -> [Fixed a] #

(RealFloat a, Arbitrary a) => Arbitrary (Complex a) # 

Methods

arbitrary :: Gen (Complex a) #

shrink :: Complex a -> [Complex a] #

Arbitrary a => Arbitrary (ZipList a) # 

Methods

arbitrary :: Gen (ZipList a) #

shrink :: ZipList a -> [ZipList a] #

Arbitrary a => Arbitrary (Dual a) # 

Methods

arbitrary :: Gen (Dual a) #

shrink :: Dual a -> [Dual a] #

(Arbitrary a, CoArbitrary a) => Arbitrary (Endo a) # 

Methods

arbitrary :: Gen (Endo a) #

shrink :: Endo a -> [Endo a] #

Arbitrary a => Arbitrary (Sum a) # 

Methods

arbitrary :: Gen (Sum a) #

shrink :: Sum a -> [Sum a] #

Arbitrary a => Arbitrary (Product a) # 

Methods

arbitrary :: Gen (Product a) #

shrink :: Product a -> [Product a] #

Arbitrary a => Arbitrary (First a) # 

Methods

arbitrary :: Gen (First a) #

shrink :: First a -> [First a] #

Arbitrary a => Arbitrary (Last a) # 

Methods

arbitrary :: Gen (Last a) #

shrink :: Last a -> [Last a] #

Arbitrary a => Arbitrary (IntMap a) # 

Methods

arbitrary :: Gen (IntMap a) #

shrink :: IntMap a -> [IntMap a] #

Arbitrary a => Arbitrary (Seq a) # 

Methods

arbitrary :: Gen (Seq a) #

shrink :: Seq a -> [Seq a] #

(Ord a, Arbitrary a) => Arbitrary (Set a) # 

Methods

arbitrary :: Gen (Set a) #

shrink :: Set a -> [Set a] #

Arbitrary a => Arbitrary (Smart a) # 

Methods

arbitrary :: Gen (Smart a) #

shrink :: Smart a -> [Smart a] #

Arbitrary a => Arbitrary (Shrink2 a) # 

Methods

arbitrary :: Gen (Shrink2 a) #

shrink :: Shrink2 a -> [Shrink2 a] #

Integral a => Arbitrary (Small a) # 

Methods

arbitrary :: Gen (Small a) #

shrink :: Small a -> [Small a] #

(Integral a, Bounded a) => Arbitrary (Large a) # 

Methods

arbitrary :: Gen (Large a) #

shrink :: Large a -> [Large a] #

(Num a, Ord a, Arbitrary a) => Arbitrary (NonNegative a) # 
(Num a, Eq a, Arbitrary a) => Arbitrary (NonZero a) # 

Methods

arbitrary :: Gen (NonZero a) #

shrink :: NonZero a -> [NonZero a] #

(Num a, Ord a, Arbitrary a) => Arbitrary (Positive a) # 

Methods

arbitrary :: Gen (Positive a) #

shrink :: Positive a -> [Positive a] #

Arbitrary a => Arbitrary (NonEmptyList a) # 
(Ord a, Arbitrary a) => Arbitrary (OrderedList a) # 
Arbitrary a => Arbitrary (Fixed a) # 

Methods

arbitrary :: Gen (Fixed a) #

shrink :: Fixed a -> [Fixed a] #

Arbitrary a => Arbitrary (Blind a) # 

Methods

arbitrary :: Gen (Blind a) #

shrink :: Blind a -> [Blind a] #

(CoArbitrary a, Arbitrary b) => Arbitrary (a -> b) # 

Methods

arbitrary :: Gen (a -> b) #

shrink :: (a -> b) -> [a -> b] #

(Arbitrary a, Arbitrary b) => Arbitrary (Either a b) # 

Methods

arbitrary :: Gen (Either a b) #

shrink :: Either a b -> [Either a b] #

(Arbitrary a, Arbitrary b) => Arbitrary (a, b) # 

Methods

arbitrary :: Gen (a, b) #

shrink :: (a, b) -> [(a, b)] #

(Ord k, Arbitrary k, Arbitrary v) => Arbitrary (Map k v) # 

Methods

arbitrary :: Gen (Map k v) #

shrink :: Map k v -> [Map k v] #

(Arbitrary a, ShrinkState s a) => Arbitrary (Shrinking s a) # 

Methods

arbitrary :: Gen (Shrinking s a) #

shrink :: Shrinking s a -> [Shrinking s a] #

(Function a, CoArbitrary a, Arbitrary b) => Arbitrary (Fun a b) # 

Methods

arbitrary :: Gen (Fun a b) #

shrink :: Fun a b -> [Fun a b] #

(Function a, CoArbitrary a, Arbitrary b) => Arbitrary ((:->) a b) # 

Methods

arbitrary :: Gen (a :-> b) #

shrink :: (a :-> b) -> [a :-> b] #

(Arbitrary a, Arbitrary b, Arbitrary c) => Arbitrary (a, b, c) # 

Methods

arbitrary :: Gen (a, b, c) #

shrink :: (a, b, c) -> [(a, b, c)] #

Arbitrary a => Arbitrary (Const * a b) # 

Methods

arbitrary :: Gen (Const * a b) #

shrink :: Const * a b -> [Const * a b] #

Arbitrary (f a) => Arbitrary (Alt * f a) # 

Methods

arbitrary :: Gen (Alt * f a) #

shrink :: Alt * f a -> [Alt * f a] #

Arbitrary a => Arbitrary (Constant * a b) # 

Methods

arbitrary :: Gen (Constant * a b) #

shrink :: Constant * a b -> [Constant * a b] #

(Arbitrary a, Arbitrary b, Arbitrary c, Arbitrary d) => Arbitrary (a, b, c, d) # 

Methods

arbitrary :: Gen (a, b, c, d) #

shrink :: (a, b, c, d) -> [(a, b, c, d)] #

(Arbitrary a, Arbitrary b, Arbitrary c, Arbitrary d, Arbitrary e) => Arbitrary (a, b, c, d, e) # 

Methods

arbitrary :: Gen (a, b, c, d, e) #

shrink :: (a, b, c, d, e) -> [(a, b, c, d, e)] #

(Arbitrary a, Arbitrary b, Arbitrary c, Arbitrary d, Arbitrary e, Arbitrary f) => Arbitrary (a, b, c, d, e, f) # 

Methods

arbitrary :: Gen (a, b, c, d, e, f) #

shrink :: (a, b, c, d, e, f) -> [(a, b, c, d, e, f)] #

(Arbitrary a, Arbitrary b, Arbitrary c, Arbitrary d, Arbitrary e, Arbitrary f, Arbitrary g) => Arbitrary (a, b, c, d, e, f, g) # 

Methods

arbitrary :: Gen (a, b, c, d, e, f, g) #

shrink :: (a, b, c, d, e, f, g) -> [(a, b, c, d, e, f, g)] #

(Arbitrary a, Arbitrary b, Arbitrary c, Arbitrary d, Arbitrary e, Arbitrary f, Arbitrary g, Arbitrary h) => Arbitrary (a, b, c, d, e, f, g, h) # 

Methods

arbitrary :: Gen (a, b, c, d, e, f, g, h) #

shrink :: (a, b, c, d, e, f, g, h) -> [(a, b, c, d, e, f, g, h)] #

(Arbitrary a, Arbitrary b, Arbitrary c, Arbitrary d, Arbitrary e, Arbitrary f, Arbitrary g, Arbitrary h, Arbitrary i) => Arbitrary (a, b, c, d, e, f, g, h, i) # 

Methods

arbitrary :: Gen (a, b, c, d, e, f, g, h, i) #

shrink :: (a, b, c, d, e, f, g, h, i) -> [(a, b, c, d, e, f, g, h, i)] #

(Arbitrary a, Arbitrary b, Arbitrary c, Arbitrary d, Arbitrary e, Arbitrary f, Arbitrary g, Arbitrary h, Arbitrary i, Arbitrary j) => Arbitrary (a, b, c, d, e, f, g, h, i, j) # 

Methods

arbitrary :: Gen (a, b, c, d, e, f, g, h, i, j) #

shrink :: (a, b, c, d, e, f, g, h, i, j) -> [(a, b, c, d, e, f, g, h, i, j)] #

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

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)

coarbitrary :: (Generic a, GCoArbitrary (Rep a)) => 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)

Instances

CoArbitrary Bool # 

Methods

coarbitrary :: Bool -> Gen b -> Gen b #

CoArbitrary Char # 

Methods

coarbitrary :: Char -> Gen b -> Gen b #

CoArbitrary Double # 

Methods

coarbitrary :: Double -> Gen b -> Gen b #

CoArbitrary Float # 

Methods

coarbitrary :: Float -> Gen b -> Gen b #

CoArbitrary Int # 

Methods

coarbitrary :: Int -> Gen b -> Gen b #

CoArbitrary Int8 # 

Methods

coarbitrary :: Int8 -> Gen b -> Gen b #

CoArbitrary Int16 # 

Methods

coarbitrary :: Int16 -> Gen b -> Gen b #

CoArbitrary Int32 # 

Methods

coarbitrary :: Int32 -> Gen b -> Gen b #

CoArbitrary Int64 # 

Methods

coarbitrary :: Int64 -> Gen b -> Gen b #

CoArbitrary Integer # 

Methods

coarbitrary :: Integer -> Gen b -> Gen b #

CoArbitrary Ordering # 

Methods

coarbitrary :: Ordering -> Gen b -> Gen b #

CoArbitrary Word # 

Methods

coarbitrary :: Word -> Gen b -> Gen b #

CoArbitrary Word8 # 

Methods

coarbitrary :: Word8 -> Gen b -> Gen b #

CoArbitrary Word16 # 

Methods

coarbitrary :: Word16 -> Gen b -> Gen b #

CoArbitrary Word32 # 

Methods

coarbitrary :: Word32 -> Gen b -> Gen b #

CoArbitrary Word64 # 

Methods

coarbitrary :: Word64 -> Gen b -> Gen b #

CoArbitrary () # 

Methods

coarbitrary :: () -> Gen b -> Gen b #

CoArbitrary Natural # 

Methods

coarbitrary :: Natural -> Gen b -> Gen b #

CoArbitrary Version # 

Methods

coarbitrary :: Version -> Gen b -> Gen b #

CoArbitrary All # 

Methods

coarbitrary :: All -> Gen b -> Gen b #

CoArbitrary Any # 

Methods

coarbitrary :: Any -> Gen b -> Gen b #

CoArbitrary IntSet # 

Methods

coarbitrary :: IntSet -> Gen b -> Gen b #

CoArbitrary OrdC # 

Methods

coarbitrary :: OrdC -> Gen b -> Gen b #

CoArbitrary OrdB # 

Methods

coarbitrary :: OrdB -> Gen b -> Gen b #

CoArbitrary OrdA # 

Methods

coarbitrary :: OrdA -> Gen b -> Gen b #

CoArbitrary C # 

Methods

coarbitrary :: C -> Gen b -> Gen b #

CoArbitrary B # 

Methods

coarbitrary :: B -> Gen b -> Gen b #

CoArbitrary A # 

Methods

coarbitrary :: A -> Gen b -> Gen b #

CoArbitrary a => CoArbitrary [a] # 

Methods

coarbitrary :: [a] -> Gen b -> Gen b #

CoArbitrary a => CoArbitrary (Maybe a) # 

Methods

coarbitrary :: Maybe a -> Gen b -> Gen b #

(Integral a, CoArbitrary a) => CoArbitrary (Ratio a) # 

Methods

coarbitrary :: Ratio a -> Gen b -> Gen b #

CoArbitrary a => CoArbitrary (Identity a) # 

Methods

coarbitrary :: Identity a -> Gen b -> Gen b #

CoArbitrary a => CoArbitrary (NonEmpty a) # 

Methods

coarbitrary :: NonEmpty a -> Gen b -> Gen b #

HasResolution a => CoArbitrary (Fixed a) # 

Methods

coarbitrary :: Fixed a -> Gen b -> Gen b #

(RealFloat a, CoArbitrary a) => CoArbitrary (Complex a) # 

Methods

coarbitrary :: Complex a -> Gen b -> Gen b #

CoArbitrary a => CoArbitrary (ZipList a) # 

Methods

coarbitrary :: ZipList a -> Gen b -> Gen b #

CoArbitrary a => CoArbitrary (Dual a) # 

Methods

coarbitrary :: Dual a -> Gen b -> Gen b #

(Arbitrary a, CoArbitrary a) => CoArbitrary (Endo a) # 

Methods

coarbitrary :: Endo a -> Gen b -> Gen b #

CoArbitrary a => CoArbitrary (Sum a) # 

Methods

coarbitrary :: Sum a -> Gen b -> Gen b #

CoArbitrary a => CoArbitrary (Product a) # 

Methods

coarbitrary :: Product a -> Gen b -> Gen b #

CoArbitrary a => CoArbitrary (First a) # 

Methods

coarbitrary :: First a -> Gen b -> Gen b #

CoArbitrary a => CoArbitrary (Last a) # 

Methods

coarbitrary :: Last a -> Gen b -> Gen b #

CoArbitrary a => CoArbitrary (IntMap a) # 

Methods

coarbitrary :: IntMap a -> Gen b -> Gen b #

CoArbitrary a => CoArbitrary (Seq a) # 

Methods

coarbitrary :: Seq a -> Gen b -> Gen b #

CoArbitrary a => CoArbitrary (Set a) # 

Methods

coarbitrary :: Set a -> Gen b -> Gen b #

(Arbitrary a, CoArbitrary b) => CoArbitrary (a -> b) # 

Methods

coarbitrary :: (a -> b) -> Gen b -> Gen b #

(CoArbitrary a, CoArbitrary b) => CoArbitrary (Either a b) # 

Methods

coarbitrary :: Either a b -> Gen b -> Gen b #

(CoArbitrary a, CoArbitrary b) => CoArbitrary (a, b) # 

Methods

coarbitrary :: (a, b) -> Gen b -> Gen b #

(CoArbitrary k, CoArbitrary v) => CoArbitrary (Map k v) # 

Methods

coarbitrary :: Map k v -> Gen b -> Gen b #

(CoArbitrary a, CoArbitrary b, CoArbitrary c) => CoArbitrary (a, b, c) # 

Methods

coarbitrary :: (a, b, c) -> Gen b -> Gen b #

CoArbitrary a => CoArbitrary (Const * a b) # 

Methods

coarbitrary :: Const * a b -> Gen b -> Gen b #

CoArbitrary (f a) => CoArbitrary (Alt * f a) # 

Methods

coarbitrary :: Alt * f a -> Gen b -> Gen b #

CoArbitrary a => CoArbitrary (Constant * a b) # 

Methods

coarbitrary :: Constant * a b -> Gen b -> Gen b #

(CoArbitrary a, CoArbitrary b, CoArbitrary c, CoArbitrary d) => CoArbitrary (a, b, c, d) # 

Methods

coarbitrary :: (a, b, c, d) -> Gen b -> Gen b #

(CoArbitrary a, CoArbitrary b, CoArbitrary c, CoArbitrary d, CoArbitrary e) => CoArbitrary (a, b, c, d, e) # 

Methods

coarbitrary :: (a, b, c, d, e) -> Gen b -> Gen b #

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.

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.

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.

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.

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

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.

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

Generic CoArbitrary implementation.

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.

Helper functions for implementing coarbitrary

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.

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.