QuickCheck-2.11.3: Automatic testing of Haskell programs

Safe HaskellSafe
LanguageHaskell98

Test.QuickCheck

Contents

Description

The QuickCheck manual gives detailed information about using QuickCheck effectively.

To start using QuickCheck, write down your property as a function returning Bool. For example, to check that reversing a list twice gives back the same list you can write:

import Test.QuickCheck

prop_reverse :: [Int] -> Bool
prop_reverse xs = reverse (reverse xs) == xs

You can then use QuickCheck to test prop_reverse on 100 random lists:

>>> quickCheck prop_reverse
+++ OK, passed 100 tests.

To run more tests you can use the withMaxSuccess combinator:

>>> quickCheck (withMaxSuccess 10000 prop_reverse)
+++ OK, passed 10000 tests.

To use QuickCheck on your own data types you will need to write Arbitrary instances for those types. See the QuickCheck manual for details about how to do that.

This module exports most of QuickCheck's functionality, but see also Test.QuickCheck.Monadic which helps with testing impure or monadic code.

Synopsis

Running tests

quickCheck :: Testable prop => prop -> IO () Source #

Tests a property and prints the results to stdout.

By default up to 100 tests are performed, which may not be enough to find all bugs. To run more tests, use withMaxSuccess.

data Args Source #

Args specifies arguments to the QuickCheck driver

Constructors

Args 

Fields

  • replay :: Maybe (QCGen, Int)

    Should we replay a previous test? Note: saving a seed from one version of QuickCheck and replaying it in another is not supported. If you want to store a test case permanently you should save the test case itself.

  • maxSuccess :: Int

    Maximum number of successful tests before succeeding. Testing stops at the first failure. If all tests are passing and you want to run more tests, increase this number.

  • maxDiscardRatio :: Int

    Maximum number of discarded tests per successful test before giving up

  • maxSize :: Int

    Size to use for the biggest test cases

  • chatty :: Bool

    Whether to print anything

  • maxShrinks :: Int

    Maximum number of shrinks to before giving up. Setting this to zero turns shrinking off.

Instances
Read Args Source # 
Instance details

Defined in Test.QuickCheck.Test

Show Args Source # 
Instance details

Defined in Test.QuickCheck.Test

Methods

showsPrec :: Int -> Args -> ShowS #

show :: Args -> String #

showList :: [Args] -> ShowS #

data Result Source #

Result represents the test result

Constructors

Success

A successful test run

Fields

GaveUp

Given up

Fields

Failure

A failed test run

Fields

NoExpectedFailure

A property that should have failed did not

Fields

InsufficientCoverage

The tests passed but a use of cover had insufficient coverage

Fields

Instances
Show Result Source # 
Instance details

Defined in Test.QuickCheck.Test

stdArgs :: Args Source #

The default test arguments

quickCheckWith :: Testable prop => Args -> prop -> IO () Source #

Tests a property, using test arguments, and prints the results to stdout.

quickCheckWithResult :: Testable prop => Args -> prop -> IO Result Source #

Tests a property, using test arguments, produces a test result, and prints the results to stdout.

quickCheckResult :: Testable prop => prop -> IO Result Source #

Tests a property, produces a test result, and prints the results to stdout.

Running tests verbosely

verboseCheck :: Testable prop => prop -> IO () Source #

Tests a property and prints the results and all test cases generated to stdout. This is just a convenience function that means the same as quickCheck . verbose.

verboseCheckWith :: Testable prop => Args -> prop -> IO () Source #

Tests a property, using test arguments, and prints the results and all test cases generated to stdout. This is just a convenience function that combines quickCheckWith and verbose.

verboseCheckWithResult :: Testable prop => Args -> prop -> IO Result Source #

Tests a property, using test arguments, produces a test result, and prints the results and all test cases generated to stdout. This is just a convenience function that combines quickCheckWithResult and verbose.

verboseCheckResult :: Testable prop => prop -> IO Result Source #

Tests a property, produces a test result, and prints the results and all test cases generated to stdout. This is just a convenience function that combines quickCheckResult and verbose.

Testing all properties in a module

quickCheckAll :: Q Exp Source #

Test all properties in the current module. The name of the property must begin with prop_. Polymorphic properties will be defaulted to Integer. Returns True if all tests succeeded, False otherwise.

To use quickCheckAll, add a definition to your module along the lines of

return []
runTests = $quickCheckAll

and then execute runTests.

Note: the bizarre return [] in the example above is needed on GHC 7.8 and later; without it, quickCheckAll will not be able to find any of the properties. For the curious, the return [] is a Template Haskell splice that makes GHC insert the empty list of declarations at that point in the program; GHC typechecks everything before the return [] before it starts on the rest of the module, which means that the later call to quickCheckAll can see everything that was defined before the return []. Yikes!

verboseCheckAll :: Q Exp Source #

Test all properties in the current module. This is just a convenience function that combines quickCheckAll and verbose.

verboseCheckAll has the same issue with scoping as quickCheckAll: see the note there about return [].

forAllProperties :: Q Exp Source #

Test all properties in the current module, using a custom quickCheck function. The same caveats as with quickCheckAll apply.

$forAllProperties has type (Property -> IO Result) -> IO Bool. An example invocation is $forAllProperties quickCheckResult, which does the same thing as $quickCheckAll.

forAllProperties has the same issue with scoping as quickCheckAll: see the note there about return [].

allProperties :: Q Exp Source #

List all properties in the current module.

$allProperties has type [(String, Property)].

allProperties has the same issue with scoping as quickCheckAll: see the note there about return [].

Testing polymorphic properties

polyQuickCheck :: Name -> ExpQ Source #

Test a polymorphic property, defaulting all type variables to Integer.

Invoke as $(polyQuickCheck 'prop), where prop is a property. Note that just evaluating quickCheck prop in GHCi will seem to work, but will silently default all type variables to ()!

$(polyQuickCheck 'prop) means the same as quickCheck $(monomorphic 'prop). If you want to supply custom arguments to polyQuickCheck, you will have to combine quickCheckWith and monomorphic yourself.

If you want to use polyQuickCheck in the same file where you defined the property, the same scoping problems pop up as in quickCheckAll: see the note there about return [].

polyVerboseCheck :: Name -> ExpQ Source #

Test a polymorphic property, defaulting all type variables to Integer. This is just a convenience function that combines verboseCheck and monomorphic.

If you want to use polyVerboseCheck in the same file where you defined the property, the same scoping problems pop up as in quickCheckAll: see the note there about return [].

monomorphic :: Name -> ExpQ Source #

Monomorphise an arbitrary property by defaulting all type variables to Integer.

For example, if f has type Ord a => [a] -> [a] then $(monomorphic 'f) has type [Integer] -> [Integer].

If you want to use monomorphic in the same file where you defined the property, the same scoping problems pop up as in quickCheckAll: see the note there about return [].

Random generation

data Gen a Source #

A generator for values of type a.

The third-party package QuickCheck-GenT provides a monad transformer version of GenT.

Instances
Monad Gen Source # 
Instance details

Defined in Test.QuickCheck.Gen

Methods

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

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

return :: a -> Gen a #

fail :: String -> Gen a #

Functor Gen Source # 
Instance details

Defined in Test.QuickCheck.Gen

Methods

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

(<$) :: a -> Gen b -> Gen a #

Applicative Gen Source # 
Instance details

Defined in Test.QuickCheck.Gen

Methods

pure :: a -> Gen a #

(<*>) :: Gen (a -> b) -> Gen a -> Gen b #

liftA2 :: (a -> b -> c) -> Gen a -> Gen b -> Gen c #

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

(<*) :: Gen a -> Gen b -> Gen a #

Testable prop => Testable (Gen prop) Source # 
Instance details

Defined in Test.QuickCheck.Property

Methods

property :: Gen prop -> Property Source #

Generator combinators

choose :: Random a => (a, a) -> Gen a Source #

Generates a random element in the given inclusive range.

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

Randomly uses one of the given generators. The input list must be non-empty.

frequency :: [(Int, Gen a)] -> Gen a Source #

Chooses one of the given generators, with a weighted random distribution. The input list must be non-empty.

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

Generates one of the given values. The input list must be non-empty.

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

Takes a list of elements of increasing size, and chooses among an initial segment of the list. The size of this initial segment increases with the size parameter. The input list must be non-empty.

sized :: (Int -> Gen a) -> Gen a Source #

Used to construct generators that depend on the size parameter.

For example, listOf, which uses the size parameter as an upper bound on length of lists it generates, can be defined like this:

listOf :: Gen a -> Gen [a]
listOf gen = sized $ \n ->
  do k <- choose (0,n)
     vectorOf k gen

You can also do this using getSize.

getSize :: Gen Int Source #

Generates the size parameter. Used to construct generators that depend on the size parameter.

For example, listOf, which uses the size parameter as an upper bound on length of lists it generates, can be defined like this:

listOf :: Gen a -> Gen [a]
listOf gen = do
  n <- getSize
  k <- choose (0,n)
  vectorOf k gen

You can also do this using sized.

resize :: Int -> Gen a -> Gen a Source #

Overrides the size parameter. Returns a generator which uses the given size instead of the runtime-size parameter.

scale :: (Int -> Int) -> Gen a -> Gen a Source #

Adjust the size parameter, by transforming it with the given function.

suchThat :: Gen a -> (a -> Bool) -> Gen a Source #

Generates a value that satisfies a predicate.

suchThatMap :: Gen a -> (a -> Maybe b) -> Gen b Source #

Generates a value for which the given function returns a Just, and then applies the function.

suchThatMaybe :: Gen a -> (a -> Bool) -> Gen (Maybe a) Source #

Tries to generate a value that satisfies a predicate. If it fails to do so after enough attempts, returns Nothing.

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

Generates a list of random length. The maximum length depends on the size parameter.

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

Generates a non-empty list of random length. The maximum length depends on the size parameter.

vectorOf :: Int -> Gen a -> Gen [a] Source #

Generates a list of the given length.

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

Generates an infinite list.

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

Generates a random permutation of the given list.

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

Generates a random subsequence of the given list.

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.

Running a generator

generate :: Gen a -> IO a Source #

Run a generator. The size passed to the generator is always 30; if you want another size then you should explicitly use resize.

Generator debugging

sample :: Show a => Gen a -> IO () Source #

Generates some example values and prints them to stdout.

sample' :: Gen a -> IO [a] Source #

Generates some example values.

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

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

Defined in Test.QuickCheck.Arbitrary

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 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 (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 (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 (Positive 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 #

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.

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

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

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

Defined in Test.QuickCheck.Arbitrary

Methods

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

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

Defined in Test.QuickCheck.Arbitrary

Methods

coarbitrary :: Fixed 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 (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 #

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

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.

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.

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.

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.

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

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

Generic CoArbitrary implementation.

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.

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.

Helper functions for implementing coarbitrary

variant :: Integral n => n -> Gen a -> Gen a Source #

Modifies a generator using an integer seed.

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.

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 

Fields

Instances
Functor Blind Source # 
Instance details

Defined in Test.QuickCheck.Modifiers

Methods

fmap :: (a -> b) -> Blind a -> Blind b #

(<$) :: a -> Blind b -> Blind a #

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

Defined in Test.QuickCheck.Modifiers

Methods

succ :: Blind a -> Blind a #

pred :: Blind a -> Blind a #

toEnum :: Int -> Blind a #

fromEnum :: Blind a -> Int #

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

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

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

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

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

Defined in Test.QuickCheck.Modifiers

Methods

(==) :: Blind a -> Blind a -> Bool #

(/=) :: Blind a -> Blind a -> Bool #

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

Defined in Test.QuickCheck.Modifiers

Methods

quot :: Blind a -> Blind a -> Blind a #

rem :: Blind a -> Blind a -> Blind a #

div :: Blind a -> Blind a -> Blind a #

mod :: Blind a -> Blind a -> Blind a #

quotRem :: Blind a -> Blind a -> (Blind a, Blind a) #

divMod :: Blind a -> Blind a -> (Blind a, Blind a) #

toInteger :: Blind a -> Integer #

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

Defined in Test.QuickCheck.Modifiers

Methods

(+) :: Blind a -> Blind a -> Blind a #

(-) :: Blind a -> Blind a -> Blind a #

(*) :: Blind a -> Blind a -> Blind a #

negate :: Blind a -> Blind a #

abs :: Blind a -> Blind a #

signum :: Blind a -> Blind a #

fromInteger :: Integer -> Blind a #

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

Defined in Test.QuickCheck.Modifiers

Methods

compare :: Blind a -> Blind a -> Ordering #

(<) :: Blind a -> Blind a -> Bool #

(<=) :: Blind a -> Blind a -> Bool #

(>) :: Blind a -> Blind a -> Bool #

(>=) :: Blind a -> Blind a -> Bool #

max :: Blind a -> Blind a -> Blind a #

min :: Blind a -> Blind a -> Blind a #

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

Defined in Test.QuickCheck.Modifiers

Methods

toRational :: Blind a -> Rational #

Show (Blind a) Source # 
Instance details

Defined in Test.QuickCheck.Modifiers

Methods

showsPrec :: Int -> Blind a -> ShowS #

show :: Blind a -> String #

showList :: [Blind a] -> ShowS #

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 #

newtype Fixed a Source #

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

Constructors

Fixed 

Fields

Instances
Functor Fixed Source # 
Instance details

Defined in Test.QuickCheck.Modifiers

Methods

fmap :: (a -> b) -> Fixed a -> Fixed b #

(<$) :: a -> Fixed b -> Fixed a #

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

Defined in Test.QuickCheck.Modifiers

Methods

succ :: Fixed a -> Fixed a #

pred :: Fixed a -> Fixed a #

toEnum :: Int -> Fixed a #

fromEnum :: Fixed a -> Int #

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

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

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

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

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

Defined in Test.QuickCheck.Modifiers

Methods

(==) :: Fixed a -> Fixed a -> Bool #

(/=) :: Fixed a -> Fixed a -> Bool #

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

Defined in Test.QuickCheck.Modifiers

Methods

quot :: Fixed a -> Fixed a -> Fixed a #

rem :: Fixed a -> Fixed a -> Fixed a #

div :: Fixed a -> Fixed a -> Fixed a #

mod :: Fixed a -> Fixed a -> Fixed a #

quotRem :: Fixed a -> Fixed a -> (Fixed a, Fixed a) #

divMod :: Fixed a -> Fixed a -> (Fixed a, Fixed a) #

toInteger :: Fixed a -> Integer #

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

Defined in Test.QuickCheck.Modifiers

Methods

(+) :: Fixed a -> Fixed a -> Fixed a #

(-) :: Fixed a -> Fixed a -> Fixed a #

(*) :: Fixed a -> Fixed a -> Fixed a #

negate :: Fixed a -> Fixed a #

abs :: Fixed a -> Fixed a #

signum :: Fixed a -> Fixed a #

fromInteger :: Integer -> Fixed a #

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

Defined in Test.QuickCheck.Modifiers

Methods

compare :: Fixed a -> Fixed a -> Ordering #

(<) :: Fixed a -> Fixed a -> Bool #

(<=) :: Fixed a -> Fixed a -> Bool #

(>) :: Fixed a -> Fixed a -> Bool #

(>=) :: Fixed a -> Fixed a -> Bool #

max :: Fixed a -> Fixed a -> Fixed a #

min :: Fixed a -> Fixed a -> Fixed a #

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

Defined in Test.QuickCheck.Modifiers

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

Defined in Test.QuickCheck.Modifiers

Methods

toRational :: Fixed a -> Rational #

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

Defined in Test.QuickCheck.Modifiers

Methods

showsPrec :: Int -> Fixed a -> ShowS #

show :: Fixed a -> String #

showList :: [Fixed a] -> ShowS #

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 #

newtype OrderedList a Source #

Ordered xs: guarantees that xs is ordered.

Constructors

Ordered 

Fields

Instances
Functor OrderedList Source # 
Instance details

Defined in Test.QuickCheck.Modifiers

Methods

fmap :: (a -> b) -> OrderedList a -> OrderedList b #

(<$) :: a -> OrderedList b -> OrderedList a #

Eq a => Eq (OrderedList a) Source # 
Instance details

Defined in Test.QuickCheck.Modifiers

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

Defined in Test.QuickCheck.Modifiers

Read a => Read (OrderedList a) Source # 
Instance details

Defined in Test.QuickCheck.Modifiers

Show a => Show (OrderedList a) Source # 
Instance details

Defined in Test.QuickCheck.Modifiers

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

Defined in Test.QuickCheck.Modifiers

newtype NonEmptyList a Source #

NonEmpty xs: guarantees that xs is non-empty.

Constructors

NonEmpty 

Fields

Instances
Functor NonEmptyList Source # 
Instance details

Defined in Test.QuickCheck.Modifiers

Methods

fmap :: (a -> b) -> NonEmptyList a -> NonEmptyList b #

(<$) :: a -> NonEmptyList b -> NonEmptyList a #

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

Defined in Test.QuickCheck.Modifiers

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

Defined in Test.QuickCheck.Modifiers

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

Defined in Test.QuickCheck.Modifiers

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

Defined in Test.QuickCheck.Modifiers

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

Defined in Test.QuickCheck.Modifiers

data InfiniteList a Source #

InfiniteList xs _: guarantees that xs is an infinite list. When a counterexample is found, only prints the prefix of xs that was used by the program.

Here is a contrived example property:

prop_take_10 :: InfiniteList Char -> Bool
prop_take_10 (InfiniteList xs _) =
  or [ x == 'a' | x <- take 10 xs ]

In the following counterexample, the list must start with "bbbbbbbbbb" but the remaining (infinite) part can contain anything:

>>> quickCheck prop_take_10
*** Failed! Falsifiable (after 1 test and 14 shrinks):
"bbbbbbbbbb" ++ ...

Constructors

InfiniteList 

Fields

Instances
Show a => Show (InfiniteList a) Source # 
Instance details

Defined in Test.QuickCheck.Modifiers

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

Defined in Test.QuickCheck.Modifiers

newtype Positive a Source #

Positive x: guarantees that x > 0.

Constructors

Positive 

Fields

Instances
Functor Positive Source # 
Instance details

Defined in Test.QuickCheck.Modifiers

Methods

fmap :: (a -> b) -> Positive a -> Positive b #

(<$) :: a -> Positive b -> Positive a #

Enum a => Enum (Positive a) Source # 
Instance details

Defined in Test.QuickCheck.Modifiers

Eq a => Eq (Positive a) Source # 
Instance details

Defined in Test.QuickCheck.Modifiers

Methods

(==) :: Positive a -> Positive a -> Bool #

(/=) :: Positive a -> Positive a -> Bool #

Ord a => Ord (Positive a) Source # 
Instance details

Defined in Test.QuickCheck.Modifiers

Methods

compare :: Positive a -> Positive a -> Ordering #

(<) :: Positive a -> Positive a -> Bool #

(<=) :: Positive a -> Positive a -> Bool #

(>) :: Positive a -> Positive a -> Bool #

(>=) :: Positive a -> Positive a -> Bool #

max :: Positive a -> Positive a -> Positive a #

min :: Positive a -> Positive a -> Positive a #

Read a => Read (Positive a) Source # 
Instance details

Defined in Test.QuickCheck.Modifiers

Show a => Show (Positive a) Source # 
Instance details

Defined in Test.QuickCheck.Modifiers

Methods

showsPrec :: Int -> Positive a -> ShowS #

show :: Positive a -> String #

showList :: [Positive a] -> ShowS #

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

Defined in Test.QuickCheck.Modifiers

newtype NonZero a Source #

NonZero x: guarantees that x /= 0.

Constructors

NonZero 

Fields

Instances
Functor NonZero Source # 
Instance details

Defined in Test.QuickCheck.Modifiers

Methods

fmap :: (a -> b) -> NonZero a -> NonZero b #

(<$) :: a -> NonZero b -> NonZero a #

Enum a => Enum (NonZero a) Source # 
Instance details

Defined in Test.QuickCheck.Modifiers

Methods

succ :: NonZero a -> NonZero a #

pred :: NonZero a -> NonZero a #

toEnum :: Int -> NonZero a #

fromEnum :: NonZero a -> Int #

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

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

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

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

Eq a => Eq (NonZero a) Source # 
Instance details

Defined in Test.QuickCheck.Modifiers

Methods

(==) :: NonZero a -> NonZero a -> Bool #

(/=) :: NonZero a -> NonZero a -> Bool #

Ord a => Ord (NonZero a) Source # 
Instance details

Defined in Test.QuickCheck.Modifiers

Methods

compare :: NonZero a -> NonZero a -> Ordering #

(<) :: NonZero a -> NonZero a -> Bool #

(<=) :: NonZero a -> NonZero a -> Bool #

(>) :: NonZero a -> NonZero a -> Bool #

(>=) :: NonZero a -> NonZero a -> Bool #

max :: NonZero a -> NonZero a -> NonZero a #

min :: NonZero a -> NonZero a -> NonZero a #

Read a => Read (NonZero a) Source # 
Instance details

Defined in Test.QuickCheck.Modifiers

Show a => Show (NonZero a) Source # 
Instance details

Defined in Test.QuickCheck.Modifiers

Methods

showsPrec :: Int -> NonZero a -> ShowS #

show :: NonZero a -> String #

showList :: [NonZero a] -> ShowS #

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

Defined in Test.QuickCheck.Modifiers

newtype NonNegative a Source #

NonNegative x: guarantees that x >= 0.

Constructors

NonNegative 

Fields

Instances
Functor NonNegative Source # 
Instance details

Defined in Test.QuickCheck.Modifiers

Methods

fmap :: (a -> b) -> NonNegative a -> NonNegative b #

(<$) :: a -> NonNegative b -> NonNegative a #

Enum a => Enum (NonNegative a) Source # 
Instance details

Defined in Test.QuickCheck.Modifiers

Eq a => Eq (NonNegative a) Source # 
Instance details

Defined in Test.QuickCheck.Modifiers

Ord a => Ord (NonNegative a) Source # 
Instance details

Defined in Test.QuickCheck.Modifiers

Read a => Read (NonNegative a) Source # 
Instance details

Defined in Test.QuickCheck.Modifiers

Show a => Show (NonNegative 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

newtype Large a Source #

Large x: by default, QuickCheck generates Ints drawn from a small range. Large Int gives you values drawn from the entire range instead.

Constructors

Large 

Fields

Instances
Functor Large Source # 
Instance details

Defined in Test.QuickCheck.Modifiers

Methods

fmap :: (a -> b) -> Large a -> Large b #

(<$) :: a -> Large b -> Large a #

Enum a => Enum (Large a) Source # 
Instance details

Defined in Test.QuickCheck.Modifiers

Methods

succ :: Large a -> Large a #

pred :: Large a -> Large a #

toEnum :: Int -> Large a #

fromEnum :: Large a -> Int #

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

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

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

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

Eq a => Eq (Large a) Source # 
Instance details

Defined in Test.QuickCheck.Modifiers

Methods

(==) :: Large a -> Large a -> Bool #

(/=) :: Large a -> Large a -> Bool #

Integral a => Integral (Large a) Source # 
Instance details

Defined in Test.QuickCheck.Modifiers

Methods

quot :: Large a -> Large a -> Large a #

rem :: Large a -> Large a -> Large a #

div :: Large a -> Large a -> Large a #

mod :: Large a -> Large a -> Large a #

quotRem :: Large a -> Large a -> (Large a, Large a) #

divMod :: Large a -> Large a -> (Large a, Large a) #

toInteger :: Large a -> Integer #

Num a => Num (Large a) Source # 
Instance details

Defined in Test.QuickCheck.Modifiers

Methods

(+) :: Large a -> Large a -> Large a #

(-) :: Large a -> Large a -> Large a #

(*) :: Large a -> Large a -> Large a #

negate :: Large a -> Large a #

abs :: Large a -> Large a #

signum :: Large a -> Large a #

fromInteger :: Integer -> Large a #

Ord a => Ord (Large a) Source # 
Instance details

Defined in Test.QuickCheck.Modifiers

Methods

compare :: Large a -> Large a -> Ordering #

(<) :: Large a -> Large a -> Bool #

(<=) :: Large a -> Large a -> Bool #

(>) :: Large a -> Large a -> Bool #

(>=) :: Large a -> Large a -> Bool #

max :: Large a -> Large a -> Large a #

min :: Large a -> Large a -> Large a #

Read a => Read (Large a) Source # 
Instance details

Defined in Test.QuickCheck.Modifiers

Real a => Real (Large a) Source # 
Instance details

Defined in Test.QuickCheck.Modifiers

Methods

toRational :: Large a -> Rational #

Show a => Show (Large a) Source # 
Instance details

Defined in Test.QuickCheck.Modifiers

Methods

showsPrec :: Int -> Large a -> ShowS #

show :: Large a -> String #

showList :: [Large a] -> ShowS #

Ix a => Ix (Large a) Source # 
Instance details

Defined in Test.QuickCheck.Modifiers

Methods

range :: (Large a, Large a) -> [Large a] #

index :: (Large a, Large a) -> Large a -> Int #

unsafeIndex :: (Large a, Large a) -> Large a -> Int

inRange :: (Large a, Large a) -> Large a -> Bool #

rangeSize :: (Large a, Large a) -> Int #

unsafeRangeSize :: (Large a, Large a) -> Int

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

newtype Small a Source #

Small x: generates values of x drawn from a small range. The opposite of Large.

Constructors

Small 

Fields

Instances
Functor Small Source # 
Instance details

Defined in Test.QuickCheck.Modifiers

Methods

fmap :: (a -> b) -> Small a -> Small b #

(<$) :: a -> Small b -> Small a #

Enum a => Enum (Small a) Source # 
Instance details

Defined in Test.QuickCheck.Modifiers

Methods

succ :: Small a -> Small a #

pred :: Small a -> Small a #

toEnum :: Int -> Small a #

fromEnum :: Small a -> Int #

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

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

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

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

Eq a => Eq (Small a) Source # 
Instance details

Defined in Test.QuickCheck.Modifiers

Methods

(==) :: Small a -> Small a -> Bool #

(/=) :: Small a -> Small a -> Bool #

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

Defined in Test.QuickCheck.Modifiers

Methods

quot :: Small a -> Small a -> Small a #

rem :: Small a -> Small a -> Small a #

div :: Small a -> Small a -> Small a #

mod :: Small a -> Small a -> Small a #

quotRem :: Small a -> Small a -> (Small a, Small a) #

divMod :: Small a -> Small a -> (Small a, Small a) #

toInteger :: Small a -> Integer #

Num a => Num (Small a) Source # 
Instance details

Defined in Test.QuickCheck.Modifiers

Methods

(+) :: Small a -> Small a -> Small a #

(-) :: Small a -> Small a -> Small a #

(*) :: Small a -> Small a -> Small a #

negate :: Small a -> Small a #

abs :: Small a -> Small a #

signum :: Small a -> Small a #

fromInteger :: Integer -> Small a #

Ord a => Ord (Small a) Source # 
Instance details

Defined in Test.QuickCheck.Modifiers

Methods

compare :: Small a -> Small a -> Ordering #

(<) :: Small a -> Small a -> Bool #

(<=) :: Small a -> Small a -> Bool #

(>) :: Small a -> Small a -> Bool #

(>=) :: Small a -> Small a -> Bool #

max :: Small a -> Small a -> Small a #

min :: Small a -> Small a -> Small a #

Read a => Read (Small a) Source # 
Instance details

Defined in Test.QuickCheck.Modifiers

Real a => Real (Small a) Source # 
Instance details

Defined in Test.QuickCheck.Modifiers

Methods

toRational :: Small a -> Rational #

Show a => Show (Small a) Source # 
Instance details

Defined in Test.QuickCheck.Modifiers

Methods

showsPrec :: Int -> Small a -> ShowS #

show :: Small a -> String #

showList :: [Small a] -> ShowS #

Ix a => Ix (Small a) Source # 
Instance details

Defined in Test.QuickCheck.Modifiers

Methods

range :: (Small a, Small a) -> [Small a] #

index :: (Small a, Small a) -> Small a -> Int #

unsafeIndex :: (Small a, Small a) -> Small a -> Int

inRange :: (Small a, Small a) -> Small a -> Bool #

rangeSize :: (Small a, Small a) -> Int #

unsafeRangeSize :: (Small a, Small a) -> Int

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 #

data Smart a Source #

Smart _ x: tries a different order when shrinking.

Constructors

Smart Int a 
Instances
Functor Smart Source # 
Instance details

Defined in Test.QuickCheck.Modifiers

Methods

fmap :: (a -> b) -> Smart a -> Smart b #

(<$) :: a -> Smart b -> Smart a #

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

Defined in Test.QuickCheck.Modifiers

Methods

showsPrec :: Int -> Smart a -> ShowS #

show :: Smart a -> String #

showList :: [Smart a] -> ShowS #

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 #

newtype Shrink2 a Source #

Shrink2 x: allows 2 shrinking steps at the same time when shrinking x

Constructors

Shrink2 

Fields

Instances
Functor Shrink2 Source # 
Instance details

Defined in Test.QuickCheck.Modifiers

Methods

fmap :: (a -> b) -> Shrink2 a -> Shrink2 b #

(<$) :: a -> Shrink2 b -> Shrink2 a #

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

Defined in Test.QuickCheck.Modifiers

Methods

succ :: Shrink2 a -> Shrink2 a #

pred :: Shrink2 a -> Shrink2 a #

toEnum :: Int -> Shrink2 a #

fromEnum :: Shrink2 a -> Int #

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

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

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

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

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

Defined in Test.QuickCheck.Modifiers

Methods

(==) :: Shrink2 a -> Shrink2 a -> Bool #

(/=) :: Shrink2 a -> Shrink2 a -> Bool #

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

Defined in Test.QuickCheck.Modifiers

Methods

quot :: Shrink2 a -> Shrink2 a -> Shrink2 a #

rem :: Shrink2 a -> Shrink2 a -> Shrink2 a #

div :: Shrink2 a -> Shrink2 a -> Shrink2 a #

mod :: Shrink2 a -> Shrink2 a -> Shrink2 a #

quotRem :: Shrink2 a -> Shrink2 a -> (Shrink2 a, Shrink2 a) #

divMod :: Shrink2 a -> Shrink2 a -> (Shrink2 a, Shrink2 a) #

toInteger :: Shrink2 a -> Integer #

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

Defined in Test.QuickCheck.Modifiers

Methods

(+) :: Shrink2 a -> Shrink2 a -> Shrink2 a #

(-) :: Shrink2 a -> Shrink2 a -> Shrink2 a #

(*) :: Shrink2 a -> Shrink2 a -> Shrink2 a #

negate :: Shrink2 a -> Shrink2 a #

abs :: Shrink2 a -> Shrink2 a #

signum :: Shrink2 a -> Shrink2 a #

fromInteger :: Integer -> Shrink2 a #

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

Defined in Test.QuickCheck.Modifiers

Methods

compare :: Shrink2 a -> Shrink2 a -> Ordering #

(<) :: Shrink2 a -> Shrink2 a -> Bool #

(<=) :: Shrink2 a -> Shrink2 a -> Bool #

(>) :: Shrink2 a -> Shrink2 a -> Bool #

(>=) :: Shrink2 a -> Shrink2 a -> Bool #

max :: Shrink2 a -> Shrink2 a -> Shrink2 a #

min :: Shrink2 a -> Shrink2 a -> Shrink2 a #

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

Defined in Test.QuickCheck.Modifiers

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

Defined in Test.QuickCheck.Modifiers

Methods

toRational :: Shrink2 a -> Rational #

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

Defined in Test.QuickCheck.Modifiers

Methods

showsPrec :: Int -> Shrink2 a -> ShowS #

show :: Shrink2 a -> String #

showList :: [Shrink2 a] -> ShowS #

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

Defined in Test.QuickCheck.Modifiers

data Shrinking s a Source #

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

Constructors

Shrinking s a 
Instances
Functor (Shrinking s) Source # 
Instance details

Defined in Test.QuickCheck.Modifiers

Methods

fmap :: (a -> b) -> Shrinking s a -> Shrinking s b #

(<$) :: a -> Shrinking s b -> Shrinking s a #

Show a => Show (Shrinking s a) Source # 
Instance details

Defined in Test.QuickCheck.Modifiers

Methods

showsPrec :: Int -> Shrinking s a -> ShowS #

show :: Shrinking s a -> String #

showList :: [Shrinking s a] -> ShowS #

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

class ShrinkState s a where Source #

Minimal complete definition

shrinkInit, shrinkState

Methods

shrinkInit :: a -> s Source #

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

newtype PrintableString Source #

PrintableString: generates a printable unicode String. The string will not contain surrogate pairs.

Constructors

PrintableString 

Functions

data Fun a b Source #

Generation of random shrinkable, showable functions.

To generate random values of type Fun a b, you must have an instance Function a.

See also applyFun, and Fn with GHC >= 7.8.

Constructors

Fun (a :-> b, b, Shrunk) (a -> b) 
Instances
(Show a, Show b) => Show (Fun a b) Source # 
Instance details

Defined in Test.QuickCheck.Function

Methods

showsPrec :: Int -> Fun a b -> ShowS #

show :: Fun a b -> String #

showList :: [Fun a b] -> ShowS #

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

applyFun :: Fun a b -> a -> b Source #

Extracts the value of a function.

Fn is the pattern equivalent of this function.

prop :: Fun String Integer -> Bool
prop f = applyFun f "banana" == applyFun f "monkey"
      || applyFun f "banana" == applyFun f "elephant"

applyFun2 :: Fun (a, b) c -> a -> b -> c Source #

Extracts the value of a binary function.

Fn2 is the pattern equivalent of this function.

prop_zipWith :: Fun (Int, Bool) Char -> [Int] -> [Bool] -> Bool
prop_zipWith f xs ys = zipWith (applyFun2 f) xs ys == [ applyFun2 f x y | (x, y) <- zip xs ys]

applyFun3 :: Fun (a, b, c) d -> a -> b -> c -> d Source #

Extracts the value of a ternary function. Fn3 is the pattern equivalent of this function.

pattern Fn :: (a -> b) -> Fun a b Source #

A modifier for testing functions.

prop :: Fun String Integer -> Bool
prop (Fn f) = f "banana" == f "monkey"
           || f "banana" == f "elephant"

pattern Fn2 :: (a -> b -> c) -> Fun (a, b) c Source #

A modifier for testing binary functions.

prop_zipWith :: Fun (Int, Bool) Char -> [Int] -> [Bool] -> Bool
prop_zipWith (Fn2 f) xs ys = zipWith f xs ys == [ f x y | (x, y) <- zip xs ys]

pattern Fn3 :: (a -> b -> c -> d) -> Fun (a, b, c) d Source #

A modifier for testing ternary functions.

class Function a where Source #

The class Function a is used for random generation of showable functions of type a -> b.

There is a default implementation for function, which you can use if your type has structural equality. Otherwise, you can normally use functionMap or functionShow.

Methods

function :: (a -> b) -> a :-> b Source #

function :: (Generic a, GFunction (Rep a)) => (a -> b) -> a :-> b Source #

Instances
Function Bool Source # 
Instance details

Defined in Test.QuickCheck.Function

Methods

function :: (Bool -> b) -> Bool :-> b Source #

Function Char Source # 
Instance details

Defined in Test.QuickCheck.Function

Methods

function :: (Char -> b) -> Char :-> b Source #

Function Double Source # 
Instance details

Defined in Test.QuickCheck.Function

Methods

function :: (Double -> b) -> Double :-> b Source #

Function Float Source # 
Instance details

Defined in Test.QuickCheck.Function

Methods

function :: (Float -> b) -> Float :-> b Source #

Function Int Source # 
Instance details

Defined in Test.QuickCheck.Function

Methods

function :: (Int -> b) -> Int :-> b Source #

Function Int8 Source # 
Instance details

Defined in Test.QuickCheck.Function

Methods

function :: (Int8 -> b) -> Int8 :-> b Source #

Function Int16 Source # 
Instance details

Defined in Test.QuickCheck.Function

Methods

function :: (Int16 -> b) -> Int16 :-> b Source #

Function Int32 Source # 
Instance details

Defined in Test.QuickCheck.Function

Methods

function :: (Int32 -> b) -> Int32 :-> b Source #

Function Int64 Source # 
Instance details

Defined in Test.QuickCheck.Function

Methods

function :: (Int64 -> b) -> Int64 :-> b Source #

Function Integer Source # 
Instance details

Defined in Test.QuickCheck.Function

Methods

function :: (Integer -> b) -> Integer :-> b Source #

Function Ordering Source # 
Instance details

Defined in Test.QuickCheck.Function

Methods

function :: (Ordering -> b) -> Ordering :-> b Source #

Function Word Source # 
Instance details

Defined in Test.QuickCheck.Function

Methods

function :: (Word -> b) -> Word :-> b Source #

Function Word8 Source # 
Instance details

Defined in Test.QuickCheck.Function

Methods

function :: (Word8 -> b) -> Word8 :-> b Source #

Function Word16 Source # 
Instance details

Defined in Test.QuickCheck.Function

Methods

function :: (Word16 -> b) -> Word16 :-> b Source #

Function Word32 Source # 
Instance details

Defined in Test.QuickCheck.Function

Methods

function :: (Word32 -> b) -> Word32 :-> b Source #

Function Word64 Source # 
Instance details

Defined in Test.QuickCheck.Function

Methods

function :: (Word64 -> b) -> Word64 :-> b Source #

Function () Source # 
Instance details

Defined in Test.QuickCheck.Function

Methods

function :: (() -> b) -> () :-> b Source #

Function IntSet Source # 
Instance details

Defined in Test.QuickCheck.Function

Methods

function :: (IntSet -> b) -> IntSet :-> b Source #

Function OrdC Source # 
Instance details

Defined in Test.QuickCheck.Function

Methods

function :: (OrdC -> b) -> OrdC :-> b Source #

Function OrdB Source # 
Instance details

Defined in Test.QuickCheck.Function

Methods

function :: (OrdB -> b) -> OrdB :-> b Source #

Function OrdA Source # 
Instance details

Defined in Test.QuickCheck.Function

Methods

function :: (OrdA -> b) -> OrdA :-> b Source #

Function C Source # 
Instance details

Defined in Test.QuickCheck.Function

Methods

function :: (C -> b) -> C :-> b Source #

Function B Source # 
Instance details

Defined in Test.QuickCheck.Function

Methods

function :: (B -> b) -> B :-> b Source #

Function A Source # 
Instance details

Defined in Test.QuickCheck.Function

Methods

function :: (A -> b) -> A :-> b Source #

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

Defined in Test.QuickCheck.Function

Methods

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

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

Defined in Test.QuickCheck.Function

Methods

function :: (Maybe a -> b) -> Maybe a :-> b Source #

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

Defined in Test.QuickCheck.Function

Methods

function :: (Ratio a -> b) -> Ratio a :-> b Source #

(RealFloat a, Function a) => Function (Complex a) Source # 
Instance details

Defined in Test.QuickCheck.Function

Methods

function :: (Complex a -> b) -> Complex a :-> b Source #

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

Defined in Test.QuickCheck.Function

Methods

function :: (Fixed a -> b) -> Fixed a :-> b Source #

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

Defined in Test.QuickCheck.Function

Methods

function :: (IntMap a -> b) -> IntMap a :-> b Source #

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

Defined in Test.QuickCheck.Function

Methods

function :: (Seq a -> b) -> Seq a :-> b Source #

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

Defined in Test.QuickCheck.Function

Methods

function :: (Set a -> b) -> Set a :-> b Source #

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

Defined in Test.QuickCheck.Function

Methods

function :: (Either a b -> b0) -> Either a b :-> b0 Source #

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

Defined in Test.QuickCheck.Function

Methods

function :: ((a, b) -> b0) -> (a, b) :-> b0 Source #

(Ord a, Function a, Function b) => Function (Map a b) Source # 
Instance details

Defined in Test.QuickCheck.Function

Methods

function :: (Map a b -> b0) -> Map a b :-> b0 Source #

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

Defined in Test.QuickCheck.Function

Methods

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

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

Defined in Test.QuickCheck.Function

Methods

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

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

Defined in Test.QuickCheck.Function

Methods

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

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

Defined in Test.QuickCheck.Function

Methods

function :: ((a, b, c, d, e, f) -> b0) -> (a, b, c, d, e, f) :-> b0 Source #

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

Defined in Test.QuickCheck.Function

Methods

function :: ((a, b, c, d, e, f, g) -> b0) -> (a, b, c, d, e, f, g) :-> b0 Source #

functionMap :: Function b => (a -> b) -> (b -> a) -> (a -> c) -> a :-> c Source #

The basic building block for Function instances. Provides a Function instance by mapping to and from a type that already has a Function instance.

Properties

data Property Source #

The type of properties.

Instances
Testable Property Source # 
Instance details

Defined in Test.QuickCheck.Property

class Testable prop where Source #

The class of properties, i.e., types which QuickCheck knows how to test. Typically a property will be a function returning Bool or Property.

If a property does no quantification, i.e. has no parameters and doesn't use forAll, it will only be tested once. This may not be what you want if your property is an IO Bool. You can change this behaviour using the again combinator.

Minimal complete definition

property

Methods

property :: prop -> Property Source #

Convert the thing to a property.

Instances
Testable Bool Source # 
Instance details

Defined in Test.QuickCheck.Property

Testable () Source # 
Instance details

Defined in Test.QuickCheck.Property

Methods

property :: () -> Property Source #

Testable Result Source # 
Instance details

Defined in Test.QuickCheck.Property

Testable Prop Source # 
Instance details

Defined in Test.QuickCheck.Property

Testable Discard Source # 
Instance details

Defined in Test.QuickCheck.Property

Testable Property Source # 
Instance details

Defined in Test.QuickCheck.Property

Testable prop => Testable (Gen prop) Source # 
Instance details

Defined in Test.QuickCheck.Property

Methods

property :: Gen prop -> Property Source #

(Arbitrary a, Show a, Testable prop) => Testable (a -> prop) Source # 
Instance details

Defined in Test.QuickCheck.Property

Methods

property :: (a -> prop) -> Property Source #

Property combinators

forAll :: (Show a, Testable prop) => Gen a -> (a -> prop) -> Property Source #

Explicit universal quantification: uses an explicitly given test case generator.

forAllShrink :: (Show a, Testable prop) => Gen a -> (a -> [a]) -> (a -> prop) -> Property Source #

Like forAll, but tries to shrink the argument for failing test cases.

shrinking Source #

Arguments

:: Testable prop 
=> (a -> [a])

shrink-like function.

-> a

The original argument

-> (a -> prop) 
-> Property 

Shrinks the argument to a property if it fails. Shrinking is done automatically for most types. This function is only needed when you want to override the default behavior.

(==>) :: Testable prop => Bool -> prop -> Property infixr 0 Source #

Implication for properties: The resulting property holds if the first argument is False (in which case the test case is discarded), or if the given property holds.

(===) :: (Eq a, Show a) => a -> a -> Property infix 4 Source #

Like ==, but prints a counterexample when it fails.

total :: NFData a => a -> Property Source #

Checks that a value is total, i.e., doesn't crash when evaluated.

ioProperty :: Testable prop => IO prop -> Property Source #

Do I/O inside a property.

Warning: any random values generated inside of the argument to ioProperty will not currently be shrunk. For best results, generate all random values before calling ioProperty.

Controlling property execution

verbose :: Testable prop => prop -> Property Source #

Prints out the generated testcase every time the property is tested. Only variables quantified over inside the verbose are printed.

once :: Testable prop => prop -> Property Source #

Modifies a property so that it only will be tested once. Opposite of again.

again :: Testable prop => prop -> Property Source #

Modifies a property so that it will be tested repeatedly. Opposite of once.

withMaxSuccess :: Testable prop => Int -> prop -> Property Source #

Configures how many times a property will be tested.

For example,

quickCheck (withMaxSuccess 1000 p)

will test p up to 1000 times.

within :: Testable prop => Int -> prop -> Property Source #

Considers a property failed if it does not complete within the given number of microseconds.

noShrinking :: Testable prop => prop -> Property Source #

Disables shrinking for a property altogether.

Conjunction and disjunction

(.&.) :: (Testable prop1, Testable prop2) => prop1 -> prop2 -> Property infixr 1 Source #

Nondeterministic choice: p1 .&. p2 picks randomly one of p1 and p2 to test. If you test the property 100 times it makes 100 random choices.

(.&&.) :: (Testable prop1, Testable prop2) => prop1 -> prop2 -> Property infixr 1 Source #

Conjunction: p1 .&&. p2 passes if both p1 and p2 pass.

conjoin :: Testable prop => [prop] -> Property Source #

Take the conjunction of several properties.

(.||.) :: (Testable prop1, Testable prop2) => prop1 -> prop2 -> Property infixr 1 Source #

Disjunction: p1 .||. p2 passes unless p1 and p2 simultaneously fail.

disjoin :: Testable prop => [prop] -> Property Source #

Take the disjunction of several properties.

What to do on failure

counterexample :: Testable prop => String -> prop -> Property Source #

Adds the given string to the counterexample if the property fails.

printTestCase :: Testable prop => String -> prop -> Property Source #

Deprecated: Use counterexample instead

Adds the given string to the counterexample if the property fails.

whenFail :: Testable prop => IO () -> prop -> Property Source #

Performs an IO action after the last failure of a property.

whenFail' :: Testable prop => IO () -> prop -> Property Source #

Performs an IO action every time a property fails. Thus, if shrinking is done, this can be used to keep track of the failures along the way.

expectFailure :: Testable prop => prop -> Property Source #

Indicates that a property is supposed to fail. QuickCheck will report an error if it does not fail.

Analysing test distribution

label :: Testable prop => String -> prop -> Property Source #

Attaches a label to a property. This is used for reporting test case distribution.

For example:

prop_reverse_reverse :: [Int] -> Property
prop_reverse_reverse xs =
  label ("length of input is " ++ show (length xs)) $
    reverse (reverse xs) === xs
>>> quickCheck prop_reverse_reverse
+++ OK, passed 100 tests:
7% length of input is 7
6% length of input is 3
5% length of input is 4
4% length of input is 6
...

collect :: (Show a, Testable prop) => a -> prop -> Property Source #

Attaches a label to a property. This is used for reporting test case distribution.

collect x = label (show x)

For example:

prop_reverse_reverse :: [Int] -> Property
prop_reverse_reverse xs =
  collect (length xs) $
    reverse (reverse xs) === xs
>>> quickCheck prop_reverse_reverse
+++ OK, passed 100 tests:
7% 7
6% 3
5% 4
4% 6
...

classify Source #

Arguments

:: Testable prop 
=> Bool

True if the test case should be labelled.

-> String

Label.

-> prop 
-> Property 

Records how many test cases satisfy a given condition.

For example:

prop_sorted_sort :: [Int] -> Property
prop_sorted_sort xs =
  sorted xs ==>
  classify (length xs > 1) "non-trivial" $
  sort xs === xs
>>> quickCheck prop_sorted_sort
+++ OK, passed 100 tests (22% non-trivial).

cover Source #

Arguments

:: Testable prop 
=> Bool

True if the test case belongs to the class.

-> Int

The required percentage (0-100) of test cases.

-> String

Label for the test case class.

-> prop 
-> Property 

Checks that at least the given proportion of successful test cases belong to the given class. Discarded tests (i.e. ones with a false precondition) do not affect coverage.

For example:

prop_sorted_sort :: [Int] -> Property
prop_sorted_sort xs =
  sorted xs ==>
  cover (length xs > 1) 50 "non-trivial" $
  sort xs === xs
>>> quickCheck prop_sorted_sort
*** Insufficient coverage after 100 tests (only 24% non-trivial, not 50%).

Miscellaneous

data Discard Source #

If a property returns Discard, the current test case is discarded, the same as if a precondition was false.

Constructors

Discard 
Instances
Testable Discard Source # 
Instance details

Defined in Test.QuickCheck.Property

discard :: a Source #

A special exception that makes QuickCheck discard the test case. Normally you should use ==>, but if for some reason this isn't possible (e.g. you are deep inside a generator), use discard instead.

mapSize :: Testable prop => (Int -> Int) -> prop -> Property Source #

Changes the maximum test case size for a property.