quickcheck-with-counterexamples-1.1: Get counterexamples from QuickCheck as Haskell values

Safe HaskellNone
LanguageHaskell2010

Test.QuickCheck.Counterexamples

Description

This module extends QuickCheck so that it returns counterexamples as Haskell values instead of just printing them. To use it, import this module instead of Test.QuickCheck. The API and functionality are the same as normal QuickCheck; the only difference is that the return types of quickCheck (and related functions) include a counterexample.

Note that this module re-exports most functions from Test.QuickCheck. Those functions are not documented here! You will need to refer to the main Test.QuickCheck documentation when using this module.

Here is an example of getting counterexamples. Suppose we have the following property:

prop_reverse_append :: [Int] -> [Int] -> Property
prop_reverse_append xs ys =
  reverse (xs++ys) === reverse xs ++ reverse ys

If we look the type of quickCheck prop_reverse_append, we see that it returns a counterexample:

>>> :t quickCheck prop_reverse_append
quickCheck prop_reverse_append :: IO (Maybe ([Int] :&: [Int] :&: ()))

The Maybe is there because quickCheck will return Nothing if the property succeeds; :&: is a datatype of pairs.

If we run QuickCheck, we can get the counterexample as a normal Haskell value:

>>> Just (xs :&: ys :&: ()) <- quickCheck prop_reverse_append
*** Failed! Falsifiable (after 5 tests and 4 shrinks):
[0]
[1]
[1,0] /= [0,1]
>>> :t xs
xs :: [Int]
>>> xs
[0]
>>> ys
[1]

Here is how this module's API differs from normal QuickCheck, in more detail:

  • The Testable class now has an associated type Counterexample which describes the counterexample. Property is now a synonym for PropertyOf (), where PropertyOf cex represents a property with an associated counterexample cex. The QuickCheck property combinators preserve the counterexample, by returning PropertyOf instead of Property.
  • quickCheck and related functions return a Counterexample prop.
  • Finally, there are a couple of new combinators, documented below.
Synopsis

Documentation

data a :&: b infixr 6 Source #

A type of pairs. Used in counterexamples.

Constructors

a :&: b infixr 6 
Instances
(Eq a, Eq b) => Eq (a :&: b) Source # 
Instance details

Defined in Test.QuickCheck.Counterexamples

Methods

(==) :: (a :&: b) -> (a :&: b) -> Bool #

(/=) :: (a :&: b) -> (a :&: b) -> Bool #

(Ord a, Ord b) => Ord (a :&: b) Source # 
Instance details

Defined in Test.QuickCheck.Counterexamples

Methods

compare :: (a :&: b) -> (a :&: b) -> Ordering #

(<) :: (a :&: b) -> (a :&: b) -> Bool #

(<=) :: (a :&: b) -> (a :&: b) -> Bool #

(>) :: (a :&: b) -> (a :&: b) -> Bool #

(>=) :: (a :&: b) -> (a :&: b) -> Bool #

max :: (a :&: b) -> (a :&: b) -> a :&: b #

min :: (a :&: b) -> (a :&: b) -> a :&: b #

(Read a, Read b) => Read (a :&: b) Source # 
Instance details

Defined in Test.QuickCheck.Counterexamples

Methods

readsPrec :: Int -> ReadS (a :&: b) #

readList :: ReadS [a :&: b] #

readPrec :: ReadPrec (a :&: b) #

readListPrec :: ReadPrec [a :&: b] #

(Show a, Show b) => Show (a :&: b) Source # 
Instance details

Defined in Test.QuickCheck.Counterexamples

Methods

showsPrec :: Int -> (a :&: b) -> ShowS #

show :: (a :&: b) -> String #

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

class Testable prop => Testable prop where Source #

The class of properties, i.e. types which QuickCheck knows how to test.

Minimal complete definition

property

Associated Types

type Counterexample prop Source #

The type of counterexamples to the property.

Methods

property :: prop -> PropertyFrom prop Source #

Convert the property to a PropertyOf.

Instances
Testable Bool Source # 
Instance details

Defined in Test.QuickCheck.Counterexamples

Associated Types

type Counterexample Bool :: * Source #

Testable Property Source # 
Instance details

Defined in Test.QuickCheck.Counterexamples

Associated Types

type Counterexample Property :: * Source #

Testable Discard Source # 
Instance details

Defined in Test.QuickCheck.Counterexamples

Associated Types

type Counterexample Discard :: * Source #

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

Defined in Test.QuickCheck.Counterexamples

Associated Types

type Counterexample (Gen prop) :: * Source #

Methods

property :: Gen prop -> PropertyFrom (Gen prop) Source #

Testable (PropertyOf cex) Source # 
Instance details

Defined in Test.QuickCheck.Counterexamples

Associated Types

type Counterexample (PropertyOf cex) :: * Source #

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

Defined in Test.QuickCheck.Counterexamples

Associated Types

type Counterexample (a -> b) :: * Source #

Methods

property :: (a -> b) -> PropertyFrom (a -> b) Source #

type PropertyFrom prop = PropertyOf (Counterexample prop) Source #

A type synonym for the property which comes from a particular Testable instance.

type Property = PropertyOf () Source #

A property which doesn't produce a counterexample.

newtype PropertyOf cex Source #

A property. cex is the type of counterexamples to the property.

Note that there is a Functor instance, which is useful when you want to manipulate the counterexample, e.g., to change its type. For example, when some branches of your property produce a counterexample and other branches do not, the types will not match up, but using fmap you can make the counterexample be a Maybe.

Constructors

MkProperty 

Fields

  • unProperty :: (cex -> IO ()) -> Property

    Implementation note: the property receives a callback to which it should pass the counterexample after shrinking.

Instances
Functor PropertyOf Source # 
Instance details

Defined in Test.QuickCheck.Counterexamples

Methods

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

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

Testable (PropertyOf cex) Source # 
Instance details

Defined in Test.QuickCheck.Counterexamples

Methods

property :: PropertyOf cex -> Property #

Testable (PropertyOf cex) Source # 
Instance details

Defined in Test.QuickCheck.Counterexamples

Associated Types

type Counterexample (PropertyOf cex) :: * Source #

type Counterexample (PropertyOf cex) Source # 
Instance details

Defined in Test.QuickCheck.Counterexamples

type Counterexample (PropertyOf cex) = cex

typedCounterexample :: Testable prop => a -> prop -> PropertyOf (a :&: Counterexample prop) Source #

Add a value to the counterexample.

onProperty :: Testable prop => (Property -> Property) -> prop -> PropertyFrom prop Source #

Lift an ordinary QuickCheck property combinator to one with counterexamples.

forAll :: (Testable prop, Show a) => Gen a -> (a -> prop) -> PropertyOf (a :&: Counterexample prop) Source #

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

forAllShow :: Testable prop => Gen a -> (a -> String) -> (a -> prop) -> PropertyOf (a :&: Counterexample prop) Source #

forAllShrinkShow :: Testable prop => Gen a -> (a -> [a]) -> (a -> String) -> (a -> prop) -> PropertyOf (a :&: Counterexample prop) Source #

forAllBlind :: Testable prop => Gen a -> (a -> prop) -> PropertyOf (a :&: Counterexample prop) Source #

forAllShrinkBlind :: Testable prop => Gen a -> (a -> [a]) -> (a -> prop) -> PropertyOf (a :&: Counterexample prop) Source #

shrinking :: Testable prop => (a -> [a]) -> a -> (a -> prop) -> PropertyFrom prop Source #

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

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

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

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

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

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

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

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

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

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

cover :: Testable prop => Double -> Bool -> String -> prop -> PropertyFrom prop Source #

tabulate :: Testable prop => String -> [String] -> prop -> PropertyFrom prop Source #

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

verboseCheckAll :: Q Exp #

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 [].

quickCheckAll :: Q Exp #

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!

allProperties :: Q Exp #

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 [].

forAllProperties :: Q Exp #

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 [].

monomorphic :: Name -> ExpQ #

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 [].

stdArgs :: Args #

The default test arguments

data Args #

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 
Instance details

Defined in Test.QuickCheck.Test

Show Args 
Instance details

Defined in Test.QuickCheck.Test

Methods

showsPrec :: Int -> Args -> ShowS #

show :: Args -> String #

showList :: [Args] -> ShowS #

data Result #

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

Instances
Show Result 
Instance details

Defined in Test.QuickCheck.Test

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

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

stdConfidence :: Confidence #

The standard parameters used by checkCoverage: certainty = 10^9, tolerance = 0.9. See Confidence for the meaning of the parameters.

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

Configures how many times a property will be tested.

For example,

quickCheck (withMaxSuccess 1000 p)

will test p up to 1000 times.

data Discard #

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

An example is the definition of ==>:

(==>) :: Testable prop => Bool -> prop -> Property
False ==> _ = property Discard
True  ==> p = property p

Constructors

Discard 
Instances
Testable Discard 
Instance details

Defined in Test.QuickCheck.Property

Methods

property :: Discard -> Property #

Testable Discard Source # 
Instance details

Defined in Test.QuickCheck.Counterexamples

Associated Types

type Counterexample Discard :: * Source #

type Counterexample Discard Source # 
Instance details

Defined in Test.QuickCheck.Counterexamples

data Confidence #

The statistical parameters used by checkCoverage.

Constructors

Confidence 

Fields

  • certainty :: Integer

    How certain checkCoverage must be before the property fails. If the coverage requirement is met, and the certainty parameter is n, then you should get a false positive at most one in n runs of QuickCheck. The default value is 10^9.

    Lower values will speed up checkCoverage at the cost of false positives.

    If you are using checkCoverage as part of a test suite, you should be careful not to set certainty too low. If you want, say, a 1% chance of a false positive during a project's lifetime, then certainty should be set to at least 100 * m * n, where m is the number of uses of cover in the test suite, and n is the number of times you expect the test suite to be run during the project's lifetime. The default value is chosen to be big enough for most projects.

  • tolerance :: Double

    For statistical reasons, checkCoverage will not reject coverage levels that are only slightly below the required levels. If the required level is p then an actual level of tolerance * p will be accepted. The default value is 0.9.

    Lower values will speed up checkCoverage at the cost of not detecting minor coverage violations.

Instances
Show Confidence 
Instance details

Defined in Test.QuickCheck.State

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

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

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

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]

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

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"

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

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

functionShow :: (Show a, Read a) => (a -> c) -> a :-> c #

Provides a Function instance for types with Show and Read.

functionIntegral :: Integral a => (a -> b) -> a :-> b #

Provides a Function instance for types with Integral.

functionRealFrac :: RealFrac a => (a -> b) -> a :-> b #

Provides a Function instance for types with RealFrac.

functionBoundedEnum :: (Eq a, Bounded a, Enum a) => (a -> b) -> a :-> b #

Provides a Function instance for types with Bounded and Enum. Use only for small types (i.e. not integers): creates the list ['minBound'..'maxBound']!

pattern Fn :: forall a b. (a -> b) -> Fun a b #

A modifier for testing functions.

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

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

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 :: forall a b c d. (a -> b -> c -> d) -> Fun (a, b, c) d #

A modifier for testing ternary functions.

class Function a where #

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 #

Instances
Function Bool 
Instance details

Defined in Test.QuickCheck.Function

Methods

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

Function Char 
Instance details

Defined in Test.QuickCheck.Function

Methods

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

Function Double 
Instance details

Defined in Test.QuickCheck.Function

Methods

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

Function Float 
Instance details

Defined in Test.QuickCheck.Function

Methods

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

Function Int 
Instance details

Defined in Test.QuickCheck.Function

Methods

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

Function Int8 
Instance details

Defined in Test.QuickCheck.Function

Methods

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

Function Int16 
Instance details

Defined in Test.QuickCheck.Function

Methods

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

Function Int32 
Instance details

Defined in Test.QuickCheck.Function

Methods

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

Function Int64 
Instance details

Defined in Test.QuickCheck.Function

Methods

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

Function Integer 
Instance details

Defined in Test.QuickCheck.Function

Methods

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

Function Ordering 
Instance details

Defined in Test.QuickCheck.Function

Methods

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

Function Word 
Instance details

Defined in Test.QuickCheck.Function

Methods

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

Function Word8 
Instance details

Defined in Test.QuickCheck.Function

Methods

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

Function Word16 
Instance details

Defined in Test.QuickCheck.Function

Methods

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

Function Word32 
Instance details

Defined in Test.QuickCheck.Function

Methods

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

Function Word64 
Instance details

Defined in Test.QuickCheck.Function

Methods

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

Function () 
Instance details

Defined in Test.QuickCheck.Function

Methods

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

Function A 
Instance details

Defined in Test.QuickCheck.Function

Methods

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

Function B 
Instance details

Defined in Test.QuickCheck.Function

Methods

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

Function C 
Instance details

Defined in Test.QuickCheck.Function

Methods

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

Function OrdA 
Instance details

Defined in Test.QuickCheck.Function

Methods

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

Function OrdB 
Instance details

Defined in Test.QuickCheck.Function

Methods

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

Function OrdC 
Instance details

Defined in Test.QuickCheck.Function

Methods

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

Function All 
Instance details

Defined in Test.QuickCheck.Function

Methods

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

Function Any 
Instance details

Defined in Test.QuickCheck.Function

Methods

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

Function IntSet 
Instance details

Defined in Test.QuickCheck.Function

Methods

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

Function a => Function [a] 
Instance details

Defined in Test.QuickCheck.Function

Methods

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

Function a => Function (Maybe a) 
Instance details

Defined in Test.QuickCheck.Function

Methods

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

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

Defined in Test.QuickCheck.Function

Methods

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

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

Defined in Test.QuickCheck.Function

Methods

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

HasResolution a => Function (Fixed a) 
Instance details

Defined in Test.QuickCheck.Function

Methods

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

Function a => Function (Identity a) 
Instance details

Defined in Test.QuickCheck.Function

Methods

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

Function a => Function (First a) 
Instance details

Defined in Test.QuickCheck.Function

Methods

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

Function a => Function (Last a) 
Instance details

Defined in Test.QuickCheck.Function

Methods

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

Function a => Function (Dual a) 
Instance details

Defined in Test.QuickCheck.Function

Methods

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

Function a => Function (Sum a) 
Instance details

Defined in Test.QuickCheck.Function

Methods

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

Function a => Function (Product a) 
Instance details

Defined in Test.QuickCheck.Function

Methods

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

Function a => Function (IntMap a) 
Instance details

Defined in Test.QuickCheck.Function

Methods

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

Function a => Function (Seq a) 
Instance details

Defined in Test.QuickCheck.Function

Methods

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

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

Defined in Test.QuickCheck.Function

Methods

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

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

Defined in Test.QuickCheck.Function

Methods

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

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

Defined in Test.QuickCheck.Function

Methods

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

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

Defined in Test.QuickCheck.Function

Methods

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

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

Defined in Test.QuickCheck.Function

Methods

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

Function a => Function (Const a b) 
Instance details

Defined in Test.QuickCheck.Function

Methods

function :: (Const a b -> b0) -> Const a b :-> b0 #

Function (f a) => Function (Alt f a) 
Instance details

Defined in Test.QuickCheck.Function

Methods

function :: (Alt f a -> b) -> Alt f a :-> b #

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

Defined in Test.QuickCheck.Function

Methods

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

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

Defined in Test.QuickCheck.Function

Methods

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

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

Defined in Test.QuickCheck.Function

Methods

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

(Function a, Function b, Function c, Function d, Function e, Function f, Function g) => Function (a, b, c, d, e, f, g) 
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 #

data Fun a b #

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
Functor (Fun a) 
Instance details

Defined in Test.QuickCheck.Function

Methods

fmap :: (a0 -> b) -> Fun a a0 -> Fun a b #

(<$) :: a0 -> Fun a b -> Fun a a0 #

(Show a, Show b) => Show (Fun a b) 
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) 
Instance details

Defined in Test.QuickCheck.Function

Methods

arbitrary :: Gen (Fun a b) #

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

newtype Blind a #

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

Constructors

Blind 

Fields

Instances
Functor Blind 
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) 
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) 
Instance details

Defined in Test.QuickCheck.Modifiers

Methods

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

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

Integral a => Integral (Blind a) 
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) 
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) 
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) 
Instance details

Defined in Test.QuickCheck.Modifiers

Methods

toRational :: Blind a -> Rational #

Show (Blind a) 
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) 
Instance details

Defined in Test.QuickCheck.Modifiers

Methods

arbitrary :: Gen (Blind a) #

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

newtype Fixed a #

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

Constructors

Fixed 

Fields

Instances
Functor Fixed 
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) 
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) 
Instance details

Defined in Test.QuickCheck.Modifiers

Methods

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

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

Integral a => Integral (Fixed a) 
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) 
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) 
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) 
Instance details

Defined in Test.QuickCheck.Modifiers

Real a => Real (Fixed a) 
Instance details

Defined in Test.QuickCheck.Modifiers

Methods

toRational :: Fixed a -> Rational #

Show a => Show (Fixed a) 
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) 
Instance details

Defined in Test.QuickCheck.Modifiers

Methods

arbitrary :: Gen (Fixed a) #

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

newtype OrderedList a #

Ordered xs: guarantees that xs is ordered.

Constructors

Ordered 

Fields

Instances
Functor OrderedList 
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) 
Instance details

Defined in Test.QuickCheck.Modifiers

Ord a => Ord (OrderedList a) 
Instance details

Defined in Test.QuickCheck.Modifiers

Read a => Read (OrderedList a) 
Instance details

Defined in Test.QuickCheck.Modifiers

Show a => Show (OrderedList a) 
Instance details

Defined in Test.QuickCheck.Modifiers

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

Defined in Test.QuickCheck.Modifiers

newtype NonEmptyList a #

NonEmpty xs: guarantees that xs is non-empty.

Constructors

NonEmpty 

Fields

Instances
Functor NonEmptyList 
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) 
Instance details

Defined in Test.QuickCheck.Modifiers

Ord a => Ord (NonEmptyList a) 
Instance details

Defined in Test.QuickCheck.Modifiers

Read a => Read (NonEmptyList a) 
Instance details

Defined in Test.QuickCheck.Modifiers

Show a => Show (NonEmptyList a) 
Instance details

Defined in Test.QuickCheck.Modifiers

Arbitrary a => Arbitrary (NonEmptyList a) 
Instance details

Defined in Test.QuickCheck.Modifiers

data InfiniteList a #

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

Defined in Test.QuickCheck.Modifiers

Arbitrary a => Arbitrary (InfiniteList a) 
Instance details

Defined in Test.QuickCheck.Modifiers

newtype Positive a #

Positive x: guarantees that x > 0.

Constructors

Positive 

Fields

Instances
Functor Positive 
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) 
Instance details

Defined in Test.QuickCheck.Modifiers

Eq a => Eq (Positive a) 
Instance details

Defined in Test.QuickCheck.Modifiers

Methods

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

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

Ord a => Ord (Positive a) 
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) 
Instance details

Defined in Test.QuickCheck.Modifiers

Show a => Show (Positive a) 
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) 
Instance details

Defined in Test.QuickCheck.Modifiers

Methods

arbitrary :: Gen (Positive a) #

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

newtype NonZero a #

NonZero x: guarantees that x /= 0.

Constructors

NonZero 

Fields

Instances
Functor NonZero 
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) 
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) 
Instance details

Defined in Test.QuickCheck.Modifiers

Methods

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

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

Ord a => Ord (NonZero a) 
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) 
Instance details

Defined in Test.QuickCheck.Modifiers

Show a => Show (NonZero a) 
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) 
Instance details

Defined in Test.QuickCheck.Modifiers

Methods

arbitrary :: Gen (NonZero a) #

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

newtype NonNegative a #

NonNegative x: guarantees that x >= 0.

Constructors

NonNegative 

Fields

Instances
Functor NonNegative 
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) 
Instance details

Defined in Test.QuickCheck.Modifiers

Eq a => Eq (NonNegative a) 
Instance details

Defined in Test.QuickCheck.Modifiers

Ord a => Ord (NonNegative a) 
Instance details

Defined in Test.QuickCheck.Modifiers

Read a => Read (NonNegative a) 
Instance details

Defined in Test.QuickCheck.Modifiers

Show a => Show (NonNegative a) 
Instance details

Defined in Test.QuickCheck.Modifiers

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

Defined in Test.QuickCheck.Modifiers

newtype Large a #

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

Defined in Test.QuickCheck.Modifiers

Methods

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

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

Integral a => Integral (Large a) 
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) 
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) 
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) 
Instance details

Defined in Test.QuickCheck.Modifiers

Real a => Real (Large a) 
Instance details

Defined in Test.QuickCheck.Modifiers

Methods

toRational :: Large a -> Rational #

Show a => Show (Large a) 
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) 
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) 
Instance details

Defined in Test.QuickCheck.Modifiers

Methods

arbitrary :: Gen (Large a) #

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

newtype Small a #

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

Constructors

Small 

Fields

Instances
Functor Small 
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) 
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) 
Instance details

Defined in Test.QuickCheck.Modifiers

Methods

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

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

Integral a => Integral (Small a) 
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) 
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) 
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) 
Instance details

Defined in Test.QuickCheck.Modifiers

Real a => Real (Small a) 
Instance details

Defined in Test.QuickCheck.Modifiers

Methods

toRational :: Small a -> Rational #

Show a => Show (Small a) 
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) 
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) 
Instance details

Defined in Test.QuickCheck.Modifiers

Methods

arbitrary :: Gen (Small a) #

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

newtype Shrink2 a #

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

Constructors

Shrink2 

Fields

Instances
Functor Shrink2 
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) 
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) 
Instance details

Defined in Test.QuickCheck.Modifiers

Methods

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

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

Integral a => Integral (Shrink2 a) 
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) 
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) 
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) 
Instance details

Defined in Test.QuickCheck.Modifiers

Real a => Real (Shrink2 a) 
Instance details

Defined in Test.QuickCheck.Modifiers

Methods

toRational :: Shrink2 a -> Rational #

Show a => Show (Shrink2 a) 
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) 
Instance details

Defined in Test.QuickCheck.Modifiers

Methods

arbitrary :: Gen (Shrink2 a) #

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

data Smart a #

Smart _ x: tries a different order when shrinking.

Constructors

Smart Int a 
Instances
Functor Smart 
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) 
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) 
Instance details

Defined in Test.QuickCheck.Modifiers

Methods

arbitrary :: Gen (Smart a) #

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

data Shrinking s a #

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

Constructors

Shrinking s a 
Instances
Functor (Shrinking s) 
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) 
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) 
Instance details

Defined in Test.QuickCheck.Modifiers

Methods

arbitrary :: Gen (Shrinking s a) #

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

class ShrinkState s a where #

Minimal complete definition

shrinkInit, shrinkState

Methods

shrinkInit :: a -> s #

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

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

Generates an infinite list.

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

Generates an ordered list.

vector :: Arbitrary a => Int -> Gen [a] #

Generates a list of a given length.

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

A coarbitrary implementation for enums.

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

coarbitrary helper for lazy people :-).

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

A coarbitrary implementation for real numbers.

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

A coarbitrary implementation for integral numbers.

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

Combine two generator perturbing functions, for example the results of calls to variant or coarbitrary.

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

Generic CoArbitrary implementation.

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

Shrink a fraction, via continued-fraction approximations.

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

Shrink an integral number.

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

Non-overloaded version of shrinkMap.

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

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

shrinkNothing :: a -> [a] #

Returns no shrinking alternatives.

arbitraryPrintableChar :: Gen Char #

Generates a printable Unicode character.

arbitraryASCIIChar :: Gen Char #

Generates a random ASCII character (0-127).

arbitraryUnicodeChar :: Gen Char #

Generates any Unicode character (but not a surrogate)

arbitrarySizedBoundedIntegral :: (Bounded a, Integral a) => Gen a #

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.

arbitraryBoundedEnum :: (Bounded a, Enum a) => Gen a #

Generates an element of a bounded enumeration.

arbitraryBoundedRandom :: (Bounded a, Random a) => Gen a #

Generates an element of a bounded type. The element is chosen from the entire range of the type.

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

Generates an integral number. The number is chosen uniformly from the entire range of the type. You may want to use arbitrarySizedBoundedIntegral instead.

arbitrarySizedFractional :: Fractional a => Gen a #

Generates a fractional number. The number can be positive or negative and its maximum absolute value depends on the size parameter.

arbitrarySizedNatural :: Integral a => Gen a #

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

arbitrarySizedIntegral :: Integral a => Gen a #

Generates an integral number. The number can be positive or negative and its maximum absolute value depends on the size parameter.

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

Apply a function of arity 4 to random arguments.

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

Apply a ternary function to random arguments.

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

Apply a binary function to random arguments.

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

Shrink a list of values given a shrinking function for individual values.

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

All immediate subterms of a term.

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

Recursively shrink all immediate subterms.

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

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

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

arbitrary2 :: (Arbitrary2 f, Arbitrary a, Arbitrary b) => Gen (f a b) #

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

arbitrary1 :: (Arbitrary1 f, Arbitrary a) => Gen (f a) #

class Arbitrary a where #

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 #

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

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 
Instance details

Defined in Test.QuickCheck.Arbitrary

Methods

arbitrary :: Gen Bool #

shrink :: Bool -> [Bool] #

Arbitrary Char 
Instance details

Defined in Test.QuickCheck.Arbitrary

Methods

arbitrary :: Gen Char #

shrink :: Char -> [Char] #

Arbitrary Double 
Instance details

Defined in Test.QuickCheck.Arbitrary

Arbitrary Float 
Instance details

Defined in Test.QuickCheck.Arbitrary

Methods

arbitrary :: Gen Float #

shrink :: Float -> [Float] #

Arbitrary Int 
Instance details

Defined in Test.QuickCheck.Arbitrary

Methods

arbitrary :: Gen Int #

shrink :: Int -> [Int] #

Arbitrary Int8 
Instance details

Defined in Test.QuickCheck.Arbitrary

Methods

arbitrary :: Gen Int8 #

shrink :: Int8 -> [Int8] #

Arbitrary Int16 
Instance details

Defined in Test.QuickCheck.Arbitrary

Methods

arbitrary :: Gen Int16 #

shrink :: Int16 -> [Int16] #

Arbitrary Int32 
Instance details

Defined in Test.QuickCheck.Arbitrary

Methods

arbitrary :: Gen Int32 #

shrink :: Int32 -> [Int32] #

Arbitrary Int64 
Instance details

Defined in Test.QuickCheck.Arbitrary

Methods

arbitrary :: Gen Int64 #

shrink :: Int64 -> [Int64] #

Arbitrary Integer 
Instance details

Defined in Test.QuickCheck.Arbitrary

Arbitrary Ordering 
Instance details

Defined in Test.QuickCheck.Arbitrary

Arbitrary Word 
Instance details

Defined in Test.QuickCheck.Arbitrary

Methods

arbitrary :: Gen Word #

shrink :: Word -> [Word] #

Arbitrary Word8 
Instance details

Defined in Test.QuickCheck.Arbitrary

Methods

arbitrary :: Gen Word8 #

shrink :: Word8 -> [Word8] #

Arbitrary Word16 
Instance details

Defined in Test.QuickCheck.Arbitrary

Arbitrary Word32 
Instance details

Defined in Test.QuickCheck.Arbitrary

Arbitrary Word64 
Instance details

Defined in Test.QuickCheck.Arbitrary

Arbitrary () 
Instance details

Defined in Test.QuickCheck.Arbitrary

Methods

arbitrary :: Gen () #

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

Arbitrary Version

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

Instance details

Defined in Test.QuickCheck.Arbitrary

Arbitrary QCGen 
Instance details

Defined in Test.QuickCheck.Arbitrary

Methods

arbitrary :: Gen QCGen #

shrink :: QCGen -> [QCGen] #

Arbitrary ASCIIString 
Instance details

Defined in Test.QuickCheck.Modifiers

Arbitrary UnicodeString 
Instance details

Defined in Test.QuickCheck.Modifiers

Arbitrary PrintableString 
Instance details

Defined in Test.QuickCheck.Modifiers

Arbitrary ExitCode 
Instance details

Defined in Test.QuickCheck.Arbitrary

Arbitrary All 
Instance details

Defined in Test.QuickCheck.Arbitrary

Methods

arbitrary :: Gen All #

shrink :: All -> [All] #

Arbitrary Any 
Instance details

Defined in Test.QuickCheck.Arbitrary

Methods

arbitrary :: Gen Any #

shrink :: Any -> [Any] #

Arbitrary CChar 
Instance details

Defined in Test.QuickCheck.Arbitrary

Methods

arbitrary :: Gen CChar #

shrink :: CChar -> [CChar] #

Arbitrary CSChar 
Instance details

Defined in Test.QuickCheck.Arbitrary

Arbitrary CUChar 
Instance details

Defined in Test.QuickCheck.Arbitrary

Arbitrary CShort 
Instance details

Defined in Test.QuickCheck.Arbitrary

Arbitrary CUShort 
Instance details

Defined in Test.QuickCheck.Arbitrary

Arbitrary CInt 
Instance details

Defined in Test.QuickCheck.Arbitrary

Methods

arbitrary :: Gen CInt #

shrink :: CInt -> [CInt] #

Arbitrary CUInt 
Instance details

Defined in Test.QuickCheck.Arbitrary

Methods

arbitrary :: Gen CUInt #

shrink :: CUInt -> [CUInt] #

Arbitrary CLong 
Instance details

Defined in Test.QuickCheck.Arbitrary

Methods

arbitrary :: Gen CLong #

shrink :: CLong -> [CLong] #

Arbitrary CULong 
Instance details

Defined in Test.QuickCheck.Arbitrary

Arbitrary CLLong 
Instance details

Defined in Test.QuickCheck.Arbitrary

Arbitrary CULLong 
Instance details

Defined in Test.QuickCheck.Arbitrary

Arbitrary CFloat 
Instance details

Defined in Test.QuickCheck.Arbitrary

Arbitrary CDouble 
Instance details

Defined in Test.QuickCheck.Arbitrary

Arbitrary CPtrdiff 
Instance details

Defined in Test.QuickCheck.Arbitrary

Arbitrary CSize 
Instance details

Defined in Test.QuickCheck.Arbitrary

Methods

arbitrary :: Gen CSize #

shrink :: CSize -> [CSize] #

Arbitrary CWchar 
Instance details

Defined in Test.QuickCheck.Arbitrary

Arbitrary CSigAtomic 
Instance details

Defined in Test.QuickCheck.Arbitrary

Arbitrary CClock 
Instance details

Defined in Test.QuickCheck.Arbitrary

Arbitrary CTime 
Instance details

Defined in Test.QuickCheck.Arbitrary

Methods

arbitrary :: Gen CTime #

shrink :: CTime -> [CTime] #

Arbitrary CUSeconds 
Instance details

Defined in Test.QuickCheck.Arbitrary

Arbitrary CSUSeconds 
Instance details

Defined in Test.QuickCheck.Arbitrary

Arbitrary CIntPtr 
Instance details

Defined in Test.QuickCheck.Arbitrary

Arbitrary CUIntPtr 
Instance details

Defined in Test.QuickCheck.Arbitrary

Arbitrary CIntMax 
Instance details

Defined in Test.QuickCheck.Arbitrary

Arbitrary CUIntMax 
Instance details

Defined in Test.QuickCheck.Arbitrary

Arbitrary IntSet 
Instance details

Defined in Test.QuickCheck.Arbitrary

Arbitrary a => Arbitrary [a] 
Instance details

Defined in Test.QuickCheck.Arbitrary

Methods

arbitrary :: Gen [a] #

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

Arbitrary a => Arbitrary (Maybe a) 
Instance details

Defined in Test.QuickCheck.Arbitrary

Methods

arbitrary :: Gen (Maybe a) #

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

Integral a => Arbitrary (Ratio a) 
Instance details

Defined in Test.QuickCheck.Arbitrary

Methods

arbitrary :: Gen (Ratio a) #

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

Arbitrary a => Arbitrary (Blind a) 
Instance details

Defined in Test.QuickCheck.Modifiers

Methods

arbitrary :: Gen (Blind a) #

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

Arbitrary a => Arbitrary (Fixed a) 
Instance details

Defined in Test.QuickCheck.Modifiers

Methods

arbitrary :: Gen (Fixed a) #

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

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

Defined in Test.QuickCheck.Modifiers

Arbitrary a => Arbitrary (NonEmptyList a) 
Instance details

Defined in Test.QuickCheck.Modifiers

Arbitrary a => Arbitrary (InfiniteList a) 
Instance details

Defined in Test.QuickCheck.Modifiers

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

Defined in Test.QuickCheck.Modifiers

Methods

arbitrary :: Gen (Positive a) #

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

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

Defined in Test.QuickCheck.Modifiers

Methods

arbitrary :: Gen (NonZero a) #

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

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

Defined in Test.QuickCheck.Modifiers

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

Defined in Test.QuickCheck.Modifiers

Methods

arbitrary :: Gen (Large a) #

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

Integral a => Arbitrary (Small a) 
Instance details

Defined in Test.QuickCheck.Modifiers

Methods

arbitrary :: Gen (Small a) #

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

Arbitrary a => Arbitrary (Shrink2 a) 
Instance details

Defined in Test.QuickCheck.Modifiers

Methods

arbitrary :: Gen (Shrink2 a) #

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

Arbitrary a => Arbitrary (Smart a) 
Instance details

Defined in Test.QuickCheck.Modifiers

Methods

arbitrary :: Gen (Smart a) #

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

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

Defined in Test.QuickCheck.Arbitrary

Methods

arbitrary :: Gen (Complex a) #

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

HasResolution a => Arbitrary (Fixed a) 
Instance details

Defined in Test.QuickCheck.Arbitrary

Methods

arbitrary :: Gen (Fixed a) #

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

Arbitrary a => Arbitrary (ZipList a) 
Instance details

Defined in Test.QuickCheck.Arbitrary

Methods

arbitrary :: Gen (ZipList a) #

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

Arbitrary a => Arbitrary (Identity a) 
Instance details

Defined in Test.QuickCheck.Arbitrary

Methods

arbitrary :: Gen (Identity a) #

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

Arbitrary a => Arbitrary (First a) 
Instance details

Defined in Test.QuickCheck.Arbitrary

Methods

arbitrary :: Gen (First a) #

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

Arbitrary a => Arbitrary (Last a) 
Instance details

Defined in Test.QuickCheck.Arbitrary

Methods

arbitrary :: Gen (Last a) #

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

Arbitrary a => Arbitrary (Dual a) 
Instance details

Defined in Test.QuickCheck.Arbitrary

Methods

arbitrary :: Gen (Dual a) #

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

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

Defined in Test.QuickCheck.Arbitrary

Methods

arbitrary :: Gen (Endo a) #

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

Arbitrary a => Arbitrary (Sum a) 
Instance details

Defined in Test.QuickCheck.Arbitrary

Methods

arbitrary :: Gen (Sum a) #

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

Arbitrary a => Arbitrary (Product a) 
Instance details

Defined in Test.QuickCheck.Arbitrary

Methods

arbitrary :: Gen (Product a) #

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

Arbitrary a => Arbitrary (IntMap a) 
Instance details

Defined in Test.QuickCheck.Arbitrary

Methods

arbitrary :: Gen (IntMap a) #

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

Arbitrary a => Arbitrary (Seq a) 
Instance details

Defined in Test.QuickCheck.Arbitrary

Methods

arbitrary :: Gen (Seq a) #

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

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

Defined in Test.QuickCheck.Arbitrary

Methods

arbitrary :: Gen (Set a) #

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

Arbitrary a => Arbitrary (InfiniteListInternalData a) 
Instance details

Defined in Test.QuickCheck.Modifiers

Methods

arbitrary :: Gen (InfiniteListInternalData a) #

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

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

Defined in Test.QuickCheck.Arbitrary

Methods

arbitrary :: Gen (a -> b) #

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

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

Defined in Test.QuickCheck.Arbitrary

Methods

arbitrary :: Gen (Either a b) #

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

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

Defined in Test.QuickCheck.Arbitrary

Methods

arbitrary :: Gen (a, b) #

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

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

Defined in Test.QuickCheck.Function

Methods

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

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

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

Defined in Test.QuickCheck.Function

Methods

arbitrary :: Gen (Fun a b) #

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

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

Defined in Test.QuickCheck.Modifiers

Methods

arbitrary :: Gen (Shrinking s a) #

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

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

Defined in Test.QuickCheck.Arbitrary

Methods

arbitrary :: Gen (WrappedMonad m a) #

shrink :: WrappedMonad m a -> [WrappedMonad m a] #

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

Defined in Test.QuickCheck.Arbitrary

Methods

arbitrary :: Gen (Map k v) #

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

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

Defined in Test.QuickCheck.Arbitrary

Methods

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

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

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

Defined in Test.QuickCheck.Arbitrary

Methods

arbitrary :: Gen (WrappedArrow a b c) #

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

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

Defined in Test.QuickCheck.Arbitrary

Methods

arbitrary :: Gen (Const a b) #

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

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

Defined in Test.QuickCheck.Arbitrary

Methods

arbitrary :: Gen (Alt f a) #

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

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

Defined in Test.QuickCheck.Arbitrary

Methods

arbitrary :: Gen (Constant a b) #

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

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

Defined in Test.QuickCheck.Arbitrary

Methods

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

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

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

Defined in Test.QuickCheck.Arbitrary

Methods

arbitrary :: Gen (Product f g a) #

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

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

Defined in Test.QuickCheck.Arbitrary

Methods

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

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

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

Defined in Test.QuickCheck.Arbitrary

Methods

arbitrary :: Gen (Compose f g a) #

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

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

Defined in Test.QuickCheck.Arbitrary

Methods

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

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

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

Defined in Test.QuickCheck.Arbitrary

Methods

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

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

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

Defined in Test.QuickCheck.Arbitrary

Methods

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

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

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

Defined in Test.QuickCheck.Arbitrary

Methods

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

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

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

Defined in Test.QuickCheck.Arbitrary

Methods

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

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

class Arbitrary1 (f :: * -> *) where #

Lifting of the Arbitrary class to unary type constructors.

Minimal complete definition

liftArbitrary

Methods

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

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

Instances
Arbitrary1 [] 
Instance details

Defined in Test.QuickCheck.Arbitrary

Methods

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

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

Arbitrary1 Maybe 
Instance details

Defined in Test.QuickCheck.Arbitrary

Methods

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

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

Arbitrary1 ZipList 
Instance details

Defined in Test.QuickCheck.Arbitrary

Methods

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

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

Arbitrary1 Identity 
Instance details

Defined in Test.QuickCheck.Arbitrary

Methods

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

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

Arbitrary1 IntMap 
Instance details

Defined in Test.QuickCheck.Arbitrary

Methods

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

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

Arbitrary1 Seq 
Instance details

Defined in Test.QuickCheck.Arbitrary

Methods

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

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

Arbitrary a => Arbitrary1 (Either a) 
Instance details

Defined in Test.QuickCheck.Arbitrary

Methods

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

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

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

Defined in Test.QuickCheck.Arbitrary

Methods

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

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

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

Defined in Test.QuickCheck.Arbitrary

Methods

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

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

Arbitrary a => Arbitrary1 (Const a :: * -> *) 
Instance details

Defined in Test.QuickCheck.Arbitrary

Methods

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

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

Arbitrary a => Arbitrary1 (Constant a :: * -> *) 
Instance details

Defined in Test.QuickCheck.Arbitrary

Methods

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

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

CoArbitrary a => Arbitrary1 ((->) a :: * -> *) 
Instance details

Defined in Test.QuickCheck.Arbitrary

Methods

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

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

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

Defined in Test.QuickCheck.Arbitrary

Methods

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

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

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

Defined in Test.QuickCheck.Arbitrary

Methods

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

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

class Arbitrary2 (f :: * -> * -> *) where #

Lifting of the Arbitrary class to binary type constructors.

Minimal complete definition

liftArbitrary2

Methods

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

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

Instances
Arbitrary2 Either 
Instance details

Defined in Test.QuickCheck.Arbitrary

Methods

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

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

Arbitrary2 (,) 
Instance details

Defined in Test.QuickCheck.Arbitrary

Methods

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

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

Arbitrary2 (Const :: * -> * -> *) 
Instance details

Defined in Test.QuickCheck.Arbitrary

Methods

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

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

Arbitrary2 (Constant :: * -> * -> *) 
Instance details

Defined in Test.QuickCheck.Arbitrary

Methods

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

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

class CoArbitrary a where #

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

Methods

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

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 
Instance details

Defined in Test.QuickCheck.Arbitrary

Methods

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

CoArbitrary Char 
Instance details

Defined in Test.QuickCheck.Arbitrary

Methods

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

CoArbitrary Double 
Instance details

Defined in Test.QuickCheck.Arbitrary

Methods

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

CoArbitrary Float 
Instance details

Defined in Test.QuickCheck.Arbitrary

Methods

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

CoArbitrary Int 
Instance details

Defined in Test.QuickCheck.Arbitrary

Methods

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

CoArbitrary Int8 
Instance details

Defined in Test.QuickCheck.Arbitrary

Methods

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

CoArbitrary Int16 
Instance details

Defined in Test.QuickCheck.Arbitrary

Methods

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

CoArbitrary Int32 
Instance details

Defined in Test.QuickCheck.Arbitrary

Methods

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

CoArbitrary Int64 
Instance details

Defined in Test.QuickCheck.Arbitrary

Methods

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

CoArbitrary Integer 
Instance details

Defined in Test.QuickCheck.Arbitrary

Methods

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

CoArbitrary Ordering 
Instance details

Defined in Test.QuickCheck.Arbitrary

Methods

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

CoArbitrary Word 
Instance details

Defined in Test.QuickCheck.Arbitrary

Methods

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

CoArbitrary Word8 
Instance details

Defined in Test.QuickCheck.Arbitrary

Methods

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

CoArbitrary Word16 
Instance details

Defined in Test.QuickCheck.Arbitrary

Methods

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

CoArbitrary Word32 
Instance details

Defined in Test.QuickCheck.Arbitrary

Methods

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

CoArbitrary Word64 
Instance details

Defined in Test.QuickCheck.Arbitrary

Methods

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

CoArbitrary () 
Instance details

Defined in Test.QuickCheck.Arbitrary

Methods

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

CoArbitrary Version 
Instance details

Defined in Test.QuickCheck.Arbitrary

Methods

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

CoArbitrary All 
Instance details

Defined in Test.QuickCheck.Arbitrary

Methods

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

CoArbitrary Any 
Instance details

Defined in Test.QuickCheck.Arbitrary

Methods

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

CoArbitrary IntSet 
Instance details

Defined in Test.QuickCheck.Arbitrary

Methods

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

CoArbitrary a => CoArbitrary [a] 
Instance details

Defined in Test.QuickCheck.Arbitrary

Methods

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

CoArbitrary a => CoArbitrary (Maybe a) 
Instance details

Defined in Test.QuickCheck.Arbitrary

Methods

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

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

Defined in Test.QuickCheck.Arbitrary

Methods

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

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

Defined in Test.QuickCheck.Arbitrary

Methods

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

HasResolution a => CoArbitrary (Fixed a) 
Instance details

Defined in Test.QuickCheck.Arbitrary

Methods

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

CoArbitrary a => CoArbitrary (ZipList a) 
Instance details

Defined in Test.QuickCheck.Arbitrary

Methods

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

CoArbitrary a => CoArbitrary (Identity a) 
Instance details

Defined in Test.QuickCheck.Arbitrary

Methods

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

CoArbitrary a => CoArbitrary (First a) 
Instance details

Defined in Test.QuickCheck.Arbitrary

Methods

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

CoArbitrary a => CoArbitrary (Last a) 
Instance details

Defined in Test.QuickCheck.Arbitrary

Methods

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

CoArbitrary a => CoArbitrary (Dual a) 
Instance details

Defined in Test.QuickCheck.Arbitrary

Methods

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

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

Defined in Test.QuickCheck.Arbitrary

Methods

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

CoArbitrary a => CoArbitrary (Sum a) 
Instance details

Defined in Test.QuickCheck.Arbitrary

Methods

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

CoArbitrary a => CoArbitrary (Product a) 
Instance details

Defined in Test.QuickCheck.Arbitrary

Methods

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

CoArbitrary a => CoArbitrary (IntMap a) 
Instance details

Defined in Test.QuickCheck.Arbitrary

Methods

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

CoArbitrary a => CoArbitrary (Seq a) 
Instance details

Defined in Test.QuickCheck.Arbitrary

Methods

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

CoArbitrary a => CoArbitrary (Set a) 
Instance details

Defined in Test.QuickCheck.Arbitrary

Methods

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

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

Defined in Test.QuickCheck.Arbitrary

Methods

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

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

Defined in Test.QuickCheck.Arbitrary

Methods

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

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

Defined in Test.QuickCheck.Arbitrary

Methods

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

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

Defined in Test.QuickCheck.Arbitrary

Methods

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

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

Defined in Test.QuickCheck.Arbitrary

Methods

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

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

Defined in Test.QuickCheck.Arbitrary

Methods

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

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

Defined in Test.QuickCheck.Arbitrary

Methods

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

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

Defined in Test.QuickCheck.Arbitrary

Methods

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

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

Defined in Test.QuickCheck.Arbitrary

Methods

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

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

Defined in Test.QuickCheck.Arbitrary

Methods

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

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

Generates an infinite list.

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

Generates a list of the given length.

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

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

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

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

growingElements :: [a] -> Gen a #

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.

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

Generates a random permutation of the given list.

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

Generates a random subsequence of the given list.

elements :: [a] -> Gen a #

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

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

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

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

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

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

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

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

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

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

Generates a value that satisfies a predicate.

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

Generates some example values and prints them to stdout.

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

Generates some example values.

generate :: Gen a -> IO a #

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

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

Generates a random element in the given inclusive range.

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

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

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

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

getSize :: Gen Int #

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

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

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.

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

Modifies a generator using an integer seed.

data Gen a #

A generator for values of type a.

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

Instances
Monad Gen 
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 
Instance details

Defined in Test.QuickCheck.Gen

Methods

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

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

MonadFix Gen 
Instance details

Defined in Test.QuickCheck.Gen

Methods

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

Applicative Gen 
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) 
Instance details

Defined in Test.QuickCheck.Property

Methods

property :: Gen prop -> Property #

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

Defined in Test.QuickCheck.Counterexamples

Associated Types

type Counterexample (Gen prop) :: * Source #

Methods

property :: Gen prop -> PropertyFrom (Gen prop) Source #

type Counterexample (Gen prop) Source # 
Instance details

Defined in Test.QuickCheck.Counterexamples

type Counterexample (Gen prop) = Counterexample prop

discard :: a #

A special error value. If a property evaluates discard, it causes QuickCheck to discard the current test case. This can be useful if you want to discard the current test case, but are somewhere you can't use ==>, such as inside a generator.