QuickCheck-2.1.0.1: Automatic testing of Haskell programs

Test.QuickCheck.Arbitrary

Contents

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.

class CoArbitrary a whereSource

Used for random generation of functions.

Methods

coarbitrary :: a -> Gen c -> Gen cSource

Used to generate a function of type a -> c. The implementation should use the first argument to perturb the random generator given as the second argument. the returned generator is then used to generate the function result. You can often use variant and >< to implement coarbitrary.

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.

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.

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

Generates an integral number. The number is chosen from the entire range of the type.

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.

Helper functions for implementing shrink

shrinkNothing :: a -> [a]Source

Returns no shrinking alternatives.

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

Shrink an integral number.

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

Shrink a fraction.

Helper functions for implementing coarbitrary

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

Combine two generator perturbing functions, for example the results of calls to variant or 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 :-).

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.

Type-level modifiers for changing generator behavior

newtype Blind a Source

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

Constructors

Blind a 

Instances

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 Source

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

Constructors

Fixed a 

Instances

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 Source

Ordered xs: guarantees that xs is ordered.

Constructors

Ordered [a] 

Instances

Eq a => Eq (OrderedList a) 
Ord a => Ord (OrderedList a) 
Read a => Read (OrderedList a) 
Show a => Show (OrderedList a) 
(Ord a, Arbitrary a) => Arbitrary (OrderedList a) 

newtype NonEmptyList a Source

NonEmpty xs: guarantees that xs is non-empty.

Constructors

NonEmpty [a] 

Instances

newtype Positive a Source

Positive x: guarantees that x > 0.

Constructors

Positive a 

Instances

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

newtype NonZero a Source

NonZero x: guarantees that x /= 0.

Constructors

NonZero a 

Instances

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

newtype NonNegative a Source

NonNegative x: guarantees that x >= 0.

Constructors

NonNegative a 

Instances

Enum a => Enum (NonNegative a) 
Eq a => Eq (NonNegative a) 
Integral a => Integral (NonNegative a) 
Num a => Num (NonNegative a) 
Ord a => Ord (NonNegative a) 
Read a => Read (NonNegative a) 
Real a => Real (NonNegative a) 
Show a => Show (NonNegative a) 
(Num a, Ord a, Arbitrary a) => Arbitrary (NonNegative a) 

data Smart a Source

Smart _ x: tries a different order when shrinking.

Constructors

Smart Int a 

Instances

Show a => Show (Smart a) 
Arbitrary a => Arbitrary (Smart a) 

data Shrinking s a Source

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

Constructors

Shrinking s a 

Instances

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

class ShrinkState s a whereSource

Methods

shrinkInit :: a -> sSource

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