Test.QuickCheck.Arbitrary
Contents
- class Arbitrary a where
- class CoArbitrary a where
- coarbitrary :: a -> Gen c -> Gen c
- arbitrarySizedIntegral :: Num a => Gen a
- arbitrarySizedFractional :: Fractional a => Gen a
- arbitraryBoundedIntegral :: (Bounded a, Integral a) => Gen a
- arbitraryBoundedRandom :: (Bounded a, Random a) => Gen a
- shrinkNothing :: a -> [a]
- shrinkIntegral :: Integral a => a -> [a]
- shrinkRealFrac :: RealFrac a => a -> [a]
- (><) :: (Gen a -> Gen a) -> (Gen a -> Gen a) -> Gen a -> Gen 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
- vector :: Arbitrary a => Int -> Gen [a]
- orderedList :: (Ord a, Arbitrary a) => Gen [a]
- newtype Blind a = Blind a
- newtype Fixed a = Fixed a
- newtype OrderedList a = Ordered [a]
- newtype NonEmptyList a = NonEmpty [a]
- newtype Positive a = Positive a
- newtype NonZero a = NonZero a
- newtype NonNegative a = NonNegative a
- data Smart a = Smart Int a
- data Shrinking s a = Shrinking s a
- class ShrinkState s a where
- shrinkInit :: a -> s
- shrinkState :: a -> s -> [(a, s)]
Arbitrary and CoArbitrary classes.
Random generation and shrinking of values.
Methods
A generator for values of the given type.
Produces a (possibly) empty list of all the possible immediate shrinks of the given value.
Instances
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
.
Instances
CoArbitrary Bool | |
CoArbitrary Char | |
CoArbitrary Double | |
CoArbitrary Float | |
CoArbitrary Int | |
CoArbitrary Integer | |
CoArbitrary () | |
CoArbitrary OrdC | |
CoArbitrary OrdB | |
CoArbitrary OrdA | |
CoArbitrary C | |
CoArbitrary B | |
CoArbitrary A | |
CoArbitrary a => CoArbitrary [a] | |
(Integral a, CoArbitrary a) => CoArbitrary (Ratio a) | |
CoArbitrary a => CoArbitrary (Maybe a) | |
(Arbitrary a, CoArbitrary b) => CoArbitrary (a -> b) | |
(CoArbitrary a, CoArbitrary b) => CoArbitrary (Either a b) | |
(CoArbitrary a, CoArbitrary b) => CoArbitrary (a, b) | |
(CoArbitrary a, CoArbitrary b, CoArbitrary c) => CoArbitrary (a, b, c) | |
(CoArbitrary a, CoArbitrary b, CoArbitrary c, CoArbitrary d) => CoArbitrary (a, b, c, d) | |
(CoArbitrary a, CoArbitrary b, CoArbitrary c, CoArbitrary d, CoArbitrary e) => CoArbitrary (a, b, c, d, e) |
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
orderedList :: (Ord a, Arbitrary a) => Gen [a]Source
Generates an ordered list of a given length.
Type-level modifiers for changing generator behavior
Fixed x
: as x, but will not be shrunk.
Constructors
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
Eq a => Eq (NonEmptyList a) | |
Ord a => Ord (NonEmptyList a) | |
Read a => Read (NonEmptyList a) | |
Show a => Show (NonEmptyList a) | |
Arbitrary a => Arbitrary (NonEmptyList a) |
Positive x
: guarantees that x > 0
.
Constructors
Positive a |
NonZero x
: guarantees that x /= 0
.
Constructors
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) |
Smart _ x
: tries a different order when shrinking.
Shrinking _ x
: allows for maintaining a state during shrinking.
Constructors
Shrinking s a |
class ShrinkState s a whereSource