QuickCheck-2.6: Automatic testing of Haskell programs

Safe HaskellSafe-Inferred

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.

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

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

shrinkNothing :: a -> [a]Source

Returns no shrinking alternatives.

shrinkList :: (a -> [a]) -> [a] -> [[a]]Source

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

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

A coarbitrary implementation for enums.

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.