QuickCheck-2.14.2: Automatic testing of Haskell programs
Safe HaskellTrustworthy
LanguageHaskell2010

Test.QuickCheck.Arbitrary

Description

Type classes for random generation of values.

Note: the contents of this module are re-exported by Test.QuickCheck. You do not need to import it directly.

Synopsis

Arbitrary and CoArbitrary classes

class Arbitrary a where Source #

Random generation and shrinking of values.

QuickCheck provides Arbitrary instances for most types in base, except those which incur extra dependencies. For a wider range of Arbitrary instances see the quickcheck-instances package.

Minimal complete definition

arbitrary

Methods

arbitrary :: Gen a Source #

A generator for values of the given type.

It is worth spending time thinking about what sort of test data you want - good generators are often the difference between finding bugs and not finding them. You can use sample, label and classify to check the quality of your test data.

There is no generic arbitrary implementation included because we don't know how to make a high-quality one. If you want one, consider using the testing-feat or generic-random packages.

The QuickCheck manual goes into detail on how to write good generators. Make sure to look at it, especially if your type is recursive!

shrink :: a -> [a] Source #

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. If your data type has no special invariants, you can enable shrinking by defining shrink = genericShrink, but by customising the behaviour of shrink you can often get simpler counterexamples.

Most implementations of shrink should try at least three things:

  1. Shrink a term to any of its immediate subterms. You can use subterms to do this.
  2. Recursively apply shrink to all immediate subterms. You can use recursivelyShrink to do this.
  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. 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

Instances details
Arbitrary Bool Source # 
Instance details

Defined in Test.QuickCheck.Arbitrary

Arbitrary Char Source # 
Instance details

Defined in Test.QuickCheck.Arbitrary

Arbitrary Double Source # 
Instance details

Defined in Test.QuickCheck.Arbitrary

Arbitrary Float Source # 
Instance details

Defined in Test.QuickCheck.Arbitrary

Arbitrary Int Source # 
Instance details

Defined in Test.QuickCheck.Arbitrary

Arbitrary Int8 Source # 
Instance details

Defined in Test.QuickCheck.Arbitrary

Arbitrary Int16 Source # 
Instance details

Defined in Test.QuickCheck.Arbitrary

Arbitrary Int32 Source # 
Instance details

Defined in Test.QuickCheck.Arbitrary

Arbitrary Int64 Source # 
Instance details

Defined in Test.QuickCheck.Arbitrary

Arbitrary Integer Source # 
Instance details

Defined in Test.QuickCheck.Arbitrary

Arbitrary Ordering Source # 
Instance details

Defined in Test.QuickCheck.Arbitrary

Arbitrary Word Source # 
Instance details

Defined in Test.QuickCheck.Arbitrary

Arbitrary Word8 Source # 
Instance details

Defined in Test.QuickCheck.Arbitrary

Arbitrary Word16 Source # 
Instance details

Defined in Test.QuickCheck.Arbitrary

Arbitrary Word32 Source # 
Instance details

Defined in Test.QuickCheck.Arbitrary

Arbitrary Word64 Source # 
Instance details

Defined in Test.QuickCheck.Arbitrary

Arbitrary () Source # 
Instance details

Defined in Test.QuickCheck.Arbitrary

Methods

arbitrary :: Gen () Source #

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

Arbitrary Version Source #

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

Instance details

Defined in Test.QuickCheck.Arbitrary

Arbitrary ExitCode Source # 
Instance details

Defined in Test.QuickCheck.Arbitrary

Arbitrary All Source # 
Instance details

Defined in Test.QuickCheck.Arbitrary

Arbitrary Any Source # 
Instance details

Defined in Test.QuickCheck.Arbitrary

Arbitrary CChar Source # 
Instance details

Defined in Test.QuickCheck.Arbitrary

Arbitrary CSChar Source # 
Instance details

Defined in Test.QuickCheck.Arbitrary

Arbitrary CUChar Source # 
Instance details

Defined in Test.QuickCheck.Arbitrary

Arbitrary CShort Source # 
Instance details

Defined in Test.QuickCheck.Arbitrary

Arbitrary CUShort Source # 
Instance details

Defined in Test.QuickCheck.Arbitrary

Arbitrary CInt Source # 
Instance details

Defined in Test.QuickCheck.Arbitrary

Arbitrary CUInt Source # 
Instance details

Defined in Test.QuickCheck.Arbitrary

Arbitrary CLong Source # 
Instance details

Defined in Test.QuickCheck.Arbitrary

Arbitrary CULong Source # 
Instance details

Defined in Test.QuickCheck.Arbitrary

Arbitrary CLLong Source # 
Instance details

Defined in Test.QuickCheck.Arbitrary

Arbitrary CULLong Source # 
Instance details

Defined in Test.QuickCheck.Arbitrary

Arbitrary CFloat Source # 
Instance details

Defined in Test.QuickCheck.Arbitrary

Arbitrary CDouble Source # 
Instance details

Defined in Test.QuickCheck.Arbitrary

Arbitrary CPtrdiff Source # 
Instance details

Defined in Test.QuickCheck.Arbitrary

Arbitrary CSize Source # 
Instance details

Defined in Test.QuickCheck.Arbitrary

Arbitrary CWchar Source # 
Instance details

Defined in Test.QuickCheck.Arbitrary

Arbitrary CSigAtomic Source # 
Instance details

Defined in Test.QuickCheck.Arbitrary

Arbitrary CClock Source # 
Instance details

Defined in Test.QuickCheck.Arbitrary

Arbitrary CTime Source # 
Instance details

Defined in Test.QuickCheck.Arbitrary

Arbitrary CUSeconds Source # 
Instance details

Defined in Test.QuickCheck.Arbitrary

Arbitrary CSUSeconds Source # 
Instance details

Defined in Test.QuickCheck.Arbitrary

Arbitrary CIntPtr Source # 
Instance details

Defined in Test.QuickCheck.Arbitrary

Arbitrary CUIntPtr Source # 
Instance details

Defined in Test.QuickCheck.Arbitrary

Arbitrary CIntMax Source # 
Instance details

Defined in Test.QuickCheck.Arbitrary

Arbitrary CUIntMax Source # 
Instance details

Defined in Test.QuickCheck.Arbitrary

Arbitrary IntSet Source # 
Instance details

Defined in Test.QuickCheck.Arbitrary

Arbitrary OrdC Source # 
Instance details

Defined in Test.QuickCheck.Poly

Arbitrary OrdB Source # 
Instance details

Defined in Test.QuickCheck.Poly

Arbitrary OrdA Source # 
Instance details

Defined in Test.QuickCheck.Poly

Arbitrary C Source # 
Instance details

Defined in Test.QuickCheck.Poly

Methods

arbitrary :: Gen C Source #

shrink :: C -> [C] Source #

Arbitrary B Source # 
Instance details

Defined in Test.QuickCheck.Poly

Methods

arbitrary :: Gen B Source #

shrink :: B -> [B] Source #

Arbitrary A Source # 
Instance details

Defined in Test.QuickCheck.Poly

Methods

arbitrary :: Gen A Source #

shrink :: A -> [A] Source #

Arbitrary PrintableString Source # 
Instance details

Defined in Test.QuickCheck.Modifiers

Arbitrary UnicodeString Source # 
Instance details

Defined in Test.QuickCheck.Modifiers

Arbitrary ASCIIString Source # 
Instance details

Defined in Test.QuickCheck.Modifiers

Arbitrary a => Arbitrary [a] Source # 
Instance details

Defined in Test.QuickCheck.Arbitrary

Methods

arbitrary :: Gen [a] Source #

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

Arbitrary a => Arbitrary (Maybe a) Source # 
Instance details

Defined in Test.QuickCheck.Arbitrary

Methods

arbitrary :: Gen (Maybe a) Source #

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

Integral a => Arbitrary (Ratio a) Source # 
Instance details

Defined in Test.QuickCheck.Arbitrary

Methods

arbitrary :: Gen (Ratio a) Source #

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

Arbitrary a => Arbitrary (Complex a) Source # 
Instance details

Defined in Test.QuickCheck.Arbitrary

Arbitrary a => Arbitrary (ZipList a) Source # 
Instance details

Defined in Test.QuickCheck.Arbitrary

Arbitrary a => Arbitrary (Identity a) Source # 
Instance details

Defined in Test.QuickCheck.Arbitrary

Arbitrary a => Arbitrary (First a) Source # 
Instance details

Defined in Test.QuickCheck.Arbitrary

Methods

arbitrary :: Gen (First a) Source #

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

Arbitrary a => Arbitrary (Last a) Source # 
Instance details

Defined in Test.QuickCheck.Arbitrary

Methods

arbitrary :: Gen (Last a) Source #

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

Arbitrary a => Arbitrary (Dual a) Source # 
Instance details

Defined in Test.QuickCheck.Arbitrary

Methods

arbitrary :: Gen (Dual a) Source #

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

(Arbitrary a, CoArbitrary a) => Arbitrary (Endo a) Source # 
Instance details

Defined in Test.QuickCheck.Arbitrary

Methods

arbitrary :: Gen (Endo a) Source #

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

Arbitrary a => Arbitrary (Sum a) Source # 
Instance details

Defined in Test.QuickCheck.Arbitrary

Methods

arbitrary :: Gen (Sum a) Source #

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

Arbitrary a => Arbitrary (Product a) Source # 
Instance details

Defined in Test.QuickCheck.Arbitrary

Arbitrary a => Arbitrary (IntMap a) Source # 
Instance details

Defined in Test.QuickCheck.Arbitrary

Methods

arbitrary :: Gen (IntMap a) Source #

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

Arbitrary a => Arbitrary (Tree a) Source # 
Instance details

Defined in Test.QuickCheck.Arbitrary

Methods

arbitrary :: Gen (Tree a) Source #

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

Arbitrary a => Arbitrary (Seq a) Source # 
Instance details

Defined in Test.QuickCheck.Arbitrary

Methods

arbitrary :: Gen (Seq a) Source #

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

(Ord a, Arbitrary a) => Arbitrary (Set a) Source # 
Instance details

Defined in Test.QuickCheck.Arbitrary

Methods

arbitrary :: Gen (Set a) Source #

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

Arbitrary a => Arbitrary (Smart a) Source # 
Instance details

Defined in Test.QuickCheck.Modifiers

Methods

arbitrary :: Gen (Smart a) Source #

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

Arbitrary a => Arbitrary (Shrink2 a) Source # 
Instance details

Defined in Test.QuickCheck.Modifiers

Integral a => Arbitrary (Small a) Source # 
Instance details

Defined in Test.QuickCheck.Modifiers

Methods

arbitrary :: Gen (Small a) Source #

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

(Integral a, Bounded a) => Arbitrary (Large a) Source # 
Instance details

Defined in Test.QuickCheck.Modifiers

Methods

arbitrary :: Gen (Large a) Source #

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

(Num a, Ord a, Arbitrary a) => Arbitrary (NonPositive a) Source # 
Instance details

Defined in Test.QuickCheck.Modifiers

(Num a, Ord a, Arbitrary a) => Arbitrary (NonNegative a) Source # 
Instance details

Defined in Test.QuickCheck.Modifiers

(Num a, Eq a, Arbitrary a) => Arbitrary (NonZero a) Source # 
Instance details

Defined in Test.QuickCheck.Modifiers

(Num a, Ord a, Arbitrary a) => Arbitrary (Negative a) Source # 
Instance details

Defined in Test.QuickCheck.Modifiers

(Num a, Ord a, Arbitrary a) => Arbitrary (Positive a) Source # 
Instance details

Defined in Test.QuickCheck.Modifiers

(Arbitrary a, Ord a) => Arbitrary (SortedList a) Source # 
Instance details

Defined in Test.QuickCheck.Modifiers

Arbitrary a => Arbitrary (InfiniteList a) Source # 
Instance details

Defined in Test.QuickCheck.Modifiers

Arbitrary a => Arbitrary (NonEmptyList a) Source # 
Instance details

Defined in Test.QuickCheck.Modifiers

(Ord a, Arbitrary a) => Arbitrary (OrderedList a) Source # 
Instance details

Defined in Test.QuickCheck.Modifiers

Arbitrary a => Arbitrary (Fixed a) Source # 
Instance details

Defined in Test.QuickCheck.Modifiers

Methods

arbitrary :: Gen (Fixed a) Source #

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

Arbitrary a => Arbitrary (Blind a) Source # 
Instance details

Defined in Test.QuickCheck.Modifiers

Methods

arbitrary :: Gen (Blind a) Source #

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

(CoArbitrary a, Arbitrary b) => Arbitrary (a -> b) Source # 
Instance details

Defined in Test.QuickCheck.Arbitrary

Methods

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

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

(Arbitrary a, Arbitrary b) => Arbitrary (Either a b) Source # 
Instance details

Defined in Test.QuickCheck.Arbitrary

Methods

arbitrary :: Gen (Either a b) Source #

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

(Arbitrary a, Arbitrary b) => Arbitrary (a, b) Source # 
Instance details

Defined in Test.QuickCheck.Arbitrary

Methods

arbitrary :: Gen (a, b) Source #

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

HasResolution a => Arbitrary (Fixed a) Source # 
Instance details

Defined in Test.QuickCheck.Arbitrary

Methods

arbitrary :: Gen (Fixed a) Source #

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

Arbitrary (m a) => Arbitrary (WrappedMonad m a) Source # 
Instance details

Defined in Test.QuickCheck.Arbitrary

(Ord k, Arbitrary k, Arbitrary v) => Arbitrary (Map k v) Source # 
Instance details

Defined in Test.QuickCheck.Arbitrary

Methods

arbitrary :: Gen (Map k v) Source #

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

(Arbitrary a, ShrinkState s a) => Arbitrary (Shrinking s a) Source # 
Instance details

Defined in Test.QuickCheck.Modifiers

Methods

arbitrary :: Gen (Shrinking s a) Source #

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

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

Defined in Test.QuickCheck.Function

Methods

arbitrary :: Gen (Fun a b) Source #

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

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

Defined in Test.QuickCheck.Function

Methods

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

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

(Arbitrary a, Arbitrary b, Arbitrary c) => Arbitrary (a, b, c) Source # 
Instance details

Defined in Test.QuickCheck.Arbitrary

Methods

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

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

Arbitrary (a b c) => Arbitrary (WrappedArrow a b c) Source # 
Instance details

Defined in Test.QuickCheck.Arbitrary

Methods

arbitrary :: Gen (WrappedArrow a b c) Source #

shrink :: WrappedArrow a b c -> [WrappedArrow a b c] Source #

Arbitrary a => Arbitrary (Const a b) Source # 
Instance details

Defined in Test.QuickCheck.Arbitrary

Methods

arbitrary :: Gen (Const a b) Source #

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

Arbitrary (f a) => Arbitrary (Alt f a) Source # 
Instance details

Defined in Test.QuickCheck.Arbitrary

Methods

arbitrary :: Gen (Alt f a) Source #

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

Arbitrary a => Arbitrary (Constant a b) Source # 
Instance details

Defined in Test.QuickCheck.Arbitrary

Methods

arbitrary :: Gen (Constant a b) Source #

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

(Arbitrary a, Arbitrary b, Arbitrary c, Arbitrary d) => Arbitrary (a, b, c, d) Source # 
Instance details

Defined in Test.QuickCheck.Arbitrary

Methods

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

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

(Arbitrary1 f, Arbitrary1 g, Arbitrary a) => Arbitrary (Product f g a) Source # 
Instance details

Defined in Test.QuickCheck.Arbitrary

Methods

arbitrary :: Gen (Product f g a) Source #

shrink :: Product f g a -> [Product f g a] Source #

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

Defined in Test.QuickCheck.Arbitrary

Methods

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

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

(Arbitrary1 f, Arbitrary1 g, Arbitrary a) => Arbitrary (Compose f g a) Source # 
Instance details

Defined in Test.QuickCheck.Arbitrary

Methods

arbitrary :: Gen (Compose f g a) Source #

shrink :: Compose f g a -> [Compose f g a] Source #

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

Defined in Test.QuickCheck.Arbitrary

Methods

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

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

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

Defined in Test.QuickCheck.Arbitrary

Methods

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

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

(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) Source # 
Instance details

Defined in Test.QuickCheck.Arbitrary

Methods

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

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

(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) Source # 
Instance details

Defined in Test.QuickCheck.Arbitrary

Methods

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

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

(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) Source # 
Instance details

Defined in Test.QuickCheck.Arbitrary

Methods

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

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

class CoArbitrary a where Source #

Used for random generation of functions. You should consider using Fun instead, which can show the generated functions as strings.

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

Minimal complete definition

Nothing

Methods

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

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)

default coarbitrary :: (Generic a, GCoArbitrary (Rep a)) => a -> Gen b -> Gen b Source #

Instances

Instances details
CoArbitrary Bool Source # 
Instance details

Defined in Test.QuickCheck.Arbitrary

Methods

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

CoArbitrary Char Source # 
Instance details

Defined in Test.QuickCheck.Arbitrary

Methods

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

CoArbitrary Double Source # 
Instance details

Defined in Test.QuickCheck.Arbitrary

Methods

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

CoArbitrary Float Source # 
Instance details

Defined in Test.QuickCheck.Arbitrary

Methods

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

CoArbitrary Int Source # 
Instance details

Defined in Test.QuickCheck.Arbitrary

Methods

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

CoArbitrary Int8 Source # 
Instance details

Defined in Test.QuickCheck.Arbitrary

Methods

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

CoArbitrary Int16 Source # 
Instance details

Defined in Test.QuickCheck.Arbitrary

Methods

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

CoArbitrary Int32 Source # 
Instance details

Defined in Test.QuickCheck.Arbitrary

Methods

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

CoArbitrary Int64 Source # 
Instance details

Defined in Test.QuickCheck.Arbitrary

Methods

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

CoArbitrary Integer Source # 
Instance details

Defined in Test.QuickCheck.Arbitrary

Methods

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

CoArbitrary Ordering Source # 
Instance details

Defined in Test.QuickCheck.Arbitrary

Methods

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

CoArbitrary Word Source # 
Instance details

Defined in Test.QuickCheck.Arbitrary

Methods

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

CoArbitrary Word8 Source # 
Instance details

Defined in Test.QuickCheck.Arbitrary

Methods

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

CoArbitrary Word16 Source # 
Instance details

Defined in Test.QuickCheck.Arbitrary

Methods

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

CoArbitrary Word32 Source # 
Instance details

Defined in Test.QuickCheck.Arbitrary

Methods

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

CoArbitrary Word64 Source # 
Instance details

Defined in Test.QuickCheck.Arbitrary

Methods

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

CoArbitrary () Source # 
Instance details

Defined in Test.QuickCheck.Arbitrary

Methods

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

CoArbitrary Version Source # 
Instance details

Defined in Test.QuickCheck.Arbitrary

Methods

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

CoArbitrary All Source # 
Instance details

Defined in Test.QuickCheck.Arbitrary

Methods

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

CoArbitrary Any Source # 
Instance details

Defined in Test.QuickCheck.Arbitrary

Methods

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

CoArbitrary IntSet Source # 
Instance details

Defined in Test.QuickCheck.Arbitrary

Methods

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

CoArbitrary OrdC Source # 
Instance details

Defined in Test.QuickCheck.Poly

Methods

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

CoArbitrary OrdB Source # 
Instance details

Defined in Test.QuickCheck.Poly

Methods

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

CoArbitrary OrdA Source # 
Instance details

Defined in Test.QuickCheck.Poly

Methods

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

CoArbitrary C Source # 
Instance details

Defined in Test.QuickCheck.Poly

Methods

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

CoArbitrary B Source # 
Instance details

Defined in Test.QuickCheck.Poly

Methods

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

CoArbitrary A Source # 
Instance details

Defined in Test.QuickCheck.Poly

Methods

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

CoArbitrary a => CoArbitrary [a] Source # 
Instance details

Defined in Test.QuickCheck.Arbitrary

Methods

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

CoArbitrary a => CoArbitrary (Maybe a) Source # 
Instance details

Defined in Test.QuickCheck.Arbitrary

Methods

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

(Integral a, CoArbitrary a) => CoArbitrary (Ratio a) Source # 
Instance details

Defined in Test.QuickCheck.Arbitrary

Methods

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

CoArbitrary a => CoArbitrary (Complex a) Source # 
Instance details

Defined in Test.QuickCheck.Arbitrary

Methods

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

CoArbitrary a => CoArbitrary (ZipList a) Source # 
Instance details

Defined in Test.QuickCheck.Arbitrary

Methods

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

CoArbitrary a => CoArbitrary (Identity a) Source # 
Instance details

Defined in Test.QuickCheck.Arbitrary

Methods

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

CoArbitrary a => CoArbitrary (First a) Source # 
Instance details

Defined in Test.QuickCheck.Arbitrary

Methods

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

CoArbitrary a => CoArbitrary (Last a) Source # 
Instance details

Defined in Test.QuickCheck.Arbitrary

Methods

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

CoArbitrary a => CoArbitrary (Dual a) Source # 
Instance details

Defined in Test.QuickCheck.Arbitrary

Methods

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

(Arbitrary a, CoArbitrary a) => CoArbitrary (Endo a) Source # 
Instance details

Defined in Test.QuickCheck.Arbitrary

Methods

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

CoArbitrary a => CoArbitrary (Sum a) Source # 
Instance details

Defined in Test.QuickCheck.Arbitrary

Methods

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

CoArbitrary a => CoArbitrary (Product a) Source # 
Instance details

Defined in Test.QuickCheck.Arbitrary

Methods

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

CoArbitrary a => CoArbitrary (IntMap a) Source # 
Instance details

Defined in Test.QuickCheck.Arbitrary

Methods

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

CoArbitrary a => CoArbitrary (Tree a) Source # 
Instance details

Defined in Test.QuickCheck.Arbitrary

Methods

coarbitrary :: Tree a -> Gen b -> Gen b Source #

CoArbitrary a => CoArbitrary (Seq a) Source # 
Instance details

Defined in Test.QuickCheck.Arbitrary

Methods

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

CoArbitrary a => CoArbitrary (Set a) Source # 
Instance details

Defined in Test.QuickCheck.Arbitrary

Methods

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

(Arbitrary a, CoArbitrary b) => CoArbitrary (a -> b) Source # 
Instance details

Defined in Test.QuickCheck.Arbitrary

Methods

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

(CoArbitrary a, CoArbitrary b) => CoArbitrary (Either a b) Source # 
Instance details

Defined in Test.QuickCheck.Arbitrary

Methods

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

(CoArbitrary a, CoArbitrary b) => CoArbitrary (a, b) Source # 
Instance details

Defined in Test.QuickCheck.Arbitrary

Methods

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

HasResolution a => CoArbitrary (Fixed a) Source # 
Instance details

Defined in Test.QuickCheck.Arbitrary

Methods

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

(CoArbitrary k, CoArbitrary v) => CoArbitrary (Map k v) Source # 
Instance details

Defined in Test.QuickCheck.Arbitrary

Methods

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

(CoArbitrary a, CoArbitrary b, CoArbitrary c) => CoArbitrary (a, b, c) Source # 
Instance details

Defined in Test.QuickCheck.Arbitrary

Methods

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

CoArbitrary a => CoArbitrary (Const a b) Source # 
Instance details

Defined in Test.QuickCheck.Arbitrary

Methods

coarbitrary :: Const a b -> Gen b0 -> Gen b0 Source #

CoArbitrary (f a) => CoArbitrary (Alt f a) Source # 
Instance details

Defined in Test.QuickCheck.Arbitrary

Methods

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

CoArbitrary a => CoArbitrary (Constant a b) Source # 
Instance details

Defined in Test.QuickCheck.Arbitrary

Methods

coarbitrary :: Constant a b -> Gen b0 -> Gen b0 Source #

(CoArbitrary a, CoArbitrary b, CoArbitrary c, CoArbitrary d) => CoArbitrary (a, b, c, d) Source # 
Instance details

Defined in Test.QuickCheck.Arbitrary

Methods

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

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

Defined in Test.QuickCheck.Arbitrary

Methods

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

Unary and Binary classes

class Arbitrary1 f where Source #

Lifting of the Arbitrary class to unary type constructors.

Minimal complete definition

liftArbitrary

Methods

liftArbitrary :: Gen a -> Gen (f a) Source #

liftShrink :: (a -> [a]) -> f a -> [f a] Source #

Instances

Instances details
Arbitrary1 [] Source # 
Instance details

Defined in Test.QuickCheck.Arbitrary

Methods

liftArbitrary :: Gen a -> Gen [a] Source #

liftShrink :: (a -> [a]) -> [a] -> [[a]] Source #

Arbitrary1 Maybe Source # 
Instance details

Defined in Test.QuickCheck.Arbitrary

Methods

liftArbitrary :: Gen a -> Gen (Maybe a) Source #

liftShrink :: (a -> [a]) -> Maybe a -> [Maybe a] Source #

Arbitrary1 ZipList Source # 
Instance details

Defined in Test.QuickCheck.Arbitrary

Methods

liftArbitrary :: Gen a -> Gen (ZipList a) Source #

liftShrink :: (a -> [a]) -> ZipList a -> [ZipList a] Source #

Arbitrary1 Identity Source # 
Instance details

Defined in Test.QuickCheck.Arbitrary

Methods

liftArbitrary :: Gen a -> Gen (Identity a) Source #

liftShrink :: (a -> [a]) -> Identity a -> [Identity a] Source #

Arbitrary1 IntMap Source # 
Instance details

Defined in Test.QuickCheck.Arbitrary

Methods

liftArbitrary :: Gen a -> Gen (IntMap a) Source #

liftShrink :: (a -> [a]) -> IntMap a -> [IntMap a] Source #

Arbitrary1 Tree Source # 
Instance details

Defined in Test.QuickCheck.Arbitrary

Methods

liftArbitrary :: Gen a -> Gen (Tree a) Source #

liftShrink :: (a -> [a]) -> Tree a -> [Tree a] Source #

Arbitrary1 Seq Source # 
Instance details

Defined in Test.QuickCheck.Arbitrary

Methods

liftArbitrary :: Gen a -> Gen (Seq a) Source #

liftShrink :: (a -> [a]) -> Seq a -> [Seq a] Source #

Arbitrary a => Arbitrary1 (Either a) Source # 
Instance details

Defined in Test.QuickCheck.Arbitrary

Methods

liftArbitrary :: Gen a0 -> Gen (Either a a0) Source #

liftShrink :: (a0 -> [a0]) -> Either a a0 -> [Either a a0] Source #

Arbitrary a => Arbitrary1 ((,) a) Source # 
Instance details

Defined in Test.QuickCheck.Arbitrary

Methods

liftArbitrary :: Gen a0 -> Gen (a, a0) Source #

liftShrink :: (a0 -> [a0]) -> (a, a0) -> [(a, a0)] Source #

(Ord k, Arbitrary k) => Arbitrary1 (Map k) Source # 
Instance details

Defined in Test.QuickCheck.Arbitrary

Methods

liftArbitrary :: Gen a -> Gen (Map k a) Source #

liftShrink :: (a -> [a]) -> Map k a -> [Map k a] Source #

Arbitrary a => Arbitrary1 (Const a :: Type -> Type) Source # 
Instance details

Defined in Test.QuickCheck.Arbitrary

Methods

liftArbitrary :: Gen a0 -> Gen (Const a a0) Source #

liftShrink :: (a0 -> [a0]) -> Const a a0 -> [Const a a0] Source #

Arbitrary a => Arbitrary1 (Constant a :: Type -> Type) Source # 
Instance details

Defined in Test.QuickCheck.Arbitrary

Methods

liftArbitrary :: Gen a0 -> Gen (Constant a a0) Source #

liftShrink :: (a0 -> [a0]) -> Constant a a0 -> [Constant a a0] Source #

CoArbitrary a => Arbitrary1 ((->) a :: Type -> Type) Source # 
Instance details

Defined in Test.QuickCheck.Arbitrary

Methods

liftArbitrary :: Gen a0 -> Gen (a -> a0) Source #

liftShrink :: (a0 -> [a0]) -> (a -> a0) -> [a -> a0] Source #

(Arbitrary1 f, Arbitrary1 g) => Arbitrary1 (Product f g) Source # 
Instance details

Defined in Test.QuickCheck.Arbitrary

Methods

liftArbitrary :: Gen a -> Gen (Product f g a) Source #

liftShrink :: (a -> [a]) -> Product f g a -> [Product f g a] Source #

(Arbitrary1 f, Arbitrary1 g) => Arbitrary1 (Compose f g) Source # 
Instance details

Defined in Test.QuickCheck.Arbitrary

Methods

liftArbitrary :: Gen a -> Gen (Compose f g a) Source #

liftShrink :: (a -> [a]) -> Compose f g a -> [Compose f g a] Source #

shrink1 :: (Arbitrary1 f, Arbitrary a) => f a -> [f a] Source #

class Arbitrary2 f where Source #

Lifting of the Arbitrary class to binary type constructors.

Minimal complete definition

liftArbitrary2

Methods

liftArbitrary2 :: Gen a -> Gen b -> Gen (f a b) Source #

liftShrink2 :: (a -> [a]) -> (b -> [b]) -> f a b -> [f a b] Source #

Instances

Instances details
Arbitrary2 Either Source # 
Instance details

Defined in Test.QuickCheck.Arbitrary

Methods

liftArbitrary2 :: Gen a -> Gen b -> Gen (Either a b) Source #

liftShrink2 :: (a -> [a]) -> (b -> [b]) -> Either a b -> [Either a b] Source #

Arbitrary2 (,) Source # 
Instance details

Defined in Test.QuickCheck.Arbitrary

Methods

liftArbitrary2 :: Gen a -> Gen b -> Gen (a, b) Source #

liftShrink2 :: (a -> [a]) -> (b -> [b]) -> (a, b) -> [(a, b)] Source #

Arbitrary2 (Const :: Type -> Type -> Type) Source # 
Instance details

Defined in Test.QuickCheck.Arbitrary

Methods

liftArbitrary2 :: Gen a -> Gen b -> Gen (Const a b) Source #

liftShrink2 :: (a -> [a]) -> (b -> [b]) -> Const a b -> [Const a b] Source #

Arbitrary2 (Constant :: Type -> Type -> Type) Source # 
Instance details

Defined in Test.QuickCheck.Arbitrary

Methods

liftArbitrary2 :: Gen a -> Gen b -> Gen (Constant a b) Source #

liftShrink2 :: (a -> [a]) -> (b -> [b]) -> Constant a b -> [Constant a b] Source #

shrink2 :: (Arbitrary2 f, Arbitrary a, Arbitrary b) => f a b -> [f a b] Source #

Helper functions for implementing arbitrary

applyArbitrary2 :: (Arbitrary a, Arbitrary b) => (a -> b -> r) -> Gen r Source #

Apply a binary function to random arguments.

applyArbitrary3 :: (Arbitrary a, Arbitrary b, Arbitrary c) => (a -> b -> c -> r) -> Gen r Source #

Apply a ternary function to random arguments.

applyArbitrary4 :: (Arbitrary a, Arbitrary b, Arbitrary c, Arbitrary d) => (a -> b -> c -> d -> r) -> Gen r Source #

Apply a function of arity 4 to random arguments.

arbitrarySizedIntegral :: Integral a => Gen a Source #

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 Source #

Generates a natural number. The number's maximum value depends on the size parameter.

arbitraryBoundedIntegral :: (Bounded a, Integral a) => Gen a Source #

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 Source #

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 Source #

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 Source #

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 Source #

Generates an element of a bounded enumeration.

Generators for various kinds of character

arbitraryUnicodeChar :: Gen Char Source #

Generates any Unicode character (but not a surrogate)

arbitraryASCIIChar :: Gen Char Source #

Generates a random ASCII character (0-127).

arbitraryPrintableChar :: Gen Char Source #

Generates a printable Unicode character.

Helper functions for implementing shrink

class RecursivelyShrink f Source #

Minimal complete definition

grecursivelyShrink

Instances

Instances details
RecursivelyShrink (V1 :: k -> Type) Source # 
Instance details

Defined in Test.QuickCheck.Arbitrary

Methods

grecursivelyShrink :: forall (a :: k0). V1 a -> [V1 a]

RecursivelyShrink (U1 :: k -> Type) Source # 
Instance details

Defined in Test.QuickCheck.Arbitrary

Methods

grecursivelyShrink :: forall (a :: k0). U1 a -> [U1 a]

Arbitrary a => RecursivelyShrink (K1 i a :: k -> Type) Source # 
Instance details

Defined in Test.QuickCheck.Arbitrary

Methods

grecursivelyShrink :: forall (a0 :: k0). K1 i a a0 -> [K1 i a a0]

(RecursivelyShrink f, RecursivelyShrink g) => RecursivelyShrink (f :+: g :: k -> Type) Source # 
Instance details

Defined in Test.QuickCheck.Arbitrary

Methods

grecursivelyShrink :: forall (a :: k0). (f :+: g) a -> [(f :+: g) a]

(RecursivelyShrink f, RecursivelyShrink g) => RecursivelyShrink (f :*: g :: k -> Type) Source # 
Instance details

Defined in Test.QuickCheck.Arbitrary

Methods

grecursivelyShrink :: forall (a :: k0). (f :*: g) a -> [(f :*: g) a]

RecursivelyShrink f => RecursivelyShrink (M1 i c f :: k -> Type) Source # 
Instance details

Defined in Test.QuickCheck.Arbitrary

Methods

grecursivelyShrink :: forall (a :: k0). M1 i c f a -> [M1 i c f a]

class GSubterms f a Source #

Minimal complete definition

gSubterms

Instances

Instances details
GSubterms (V1 :: Type -> Type) a Source # 
Instance details

Defined in Test.QuickCheck.Arbitrary

Methods

gSubterms :: V1 a -> [a]

GSubterms (U1 :: Type -> Type) a Source # 
Instance details

Defined in Test.QuickCheck.Arbitrary

Methods

gSubterms :: U1 a -> [a]

GSubterms (K1 i a :: Type -> Type) b Source # 
Instance details

Defined in Test.QuickCheck.Arbitrary

Methods

gSubterms :: K1 i a b -> [b]

(GSubtermsIncl f a, GSubtermsIncl g a) => GSubterms (f :+: g) a Source # 
Instance details

Defined in Test.QuickCheck.Arbitrary

Methods

gSubterms :: (f :+: g) a -> [a]

(GSubtermsIncl f a, GSubtermsIncl g a) => GSubterms (f :*: g) a Source # 
Instance details

Defined in Test.QuickCheck.Arbitrary

Methods

gSubterms :: (f :*: g) a -> [a]

GSubterms f a => GSubterms (M1 i c f) a Source # 
Instance details

Defined in Test.QuickCheck.Arbitrary

Methods

gSubterms :: M1 i c f a -> [a]

genericShrink :: (Generic a, RecursivelyShrink (Rep a), GSubterms (Rep a) a) => a -> [a] Source #

Shrink a term to any of its immediate subterms, and also recursively shrink all subterms.

subterms :: (Generic a, GSubterms (Rep a) a) => a -> [a] Source #

All immediate subterms of a term.

recursivelyShrink :: (Generic a, RecursivelyShrink (Rep a)) => a -> [a] Source #

Recursively shrink all immediate subterms.

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

Generic CoArbitrary implementation.

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.

shrinkMap :: Arbitrary a => (a -> b) -> (b -> a) -> b -> [b] Source #

Map a shrink function to another domain. This is handy if your data type has special invariants, but is almost isomorphic to some other type.

shrinkOrderedList :: (Ord a, Arbitrary a) => [a] -> [[a]]
shrinkOrderedList = shrinkMap sort id

shrinkSet :: (Ord a, Arbitrary a) => Set a -> Set [a]
shrinkSet = shrinkMap fromList toList

shrinkMapBy :: (a -> b) -> (b -> a) -> (a -> [a]) -> b -> [b] Source #

Non-overloaded version of shrinkMap.

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

Shrink an integral number.

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

Shrink a fraction, preferring numbers with smaller numerators or denominators. See also shrinkDecimal.

shrinkDecimal :: RealFrac a => a -> [a] Source #

Shrink a real number, preferring numbers with shorter decimal representations. See also shrinkRealFrac.

Helper functions for implementing coarbitrary

coarbitraryIntegral :: Integral a => a -> Gen b -> Gen b Source #

A coarbitrary implementation for integral numbers.

coarbitraryReal :: Real a => a -> Gen b -> Gen b Source #

A coarbitrary implementation for real numbers.

coarbitraryShow :: Show a => a -> Gen b -> Gen b Source #

coarbitrary helper for lazy people :-).

coarbitraryEnum :: Enum a => a -> Gen b -> Gen b Source #

A coarbitrary implementation for enums.

(><) :: (Gen a -> Gen a) -> (Gen a -> Gen a) -> Gen a -> Gen a Source #

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] Source #

Generates a list of a given length.

orderedList :: (Ord a, Arbitrary a) => Gen [a] Source #

Generates an ordered list.

infiniteList :: Arbitrary a => Gen [a] Source #

Generates an infinite list.