| Safe Haskell | Safe | 
|---|---|
| Language | Haskell98 | 
Test.QuickCheck
Description
For further information see the QuickCheck manual.
To use QuickCheck to check a property, first define a function expressing that property (functions expressing properties under test tend to be prefixed with prop_). Testing that n + m = m + n holds for Integers one might write:
import Test.QuickCheck prop_commutativeAdd :: Integer -> Integer -> Bool prop_commutativeAdd n m = n + m == m + n
and testing:
>>>quickcheck prop_commutativeAdd+++ OK, passed 100 tests.
which tests prop_commutativeAdd on 100 random (Integer, Integer) pairs.
verboseCheck can be used to see the actual values generated:
>>>verboseCheck prop_commutativeAddPassed: 0 0 …98 tests omitted… Passed: -68 6 +++ OK, passed 100 tests.
and if more than 100 tests are needed the number of tests can be increased by updating the stdArgs record:
>>>quickCheckWith stdArgs { maxSuccess = 500 } prop_commutativeAdd+++ OK, passed 500 tests.
To let QuickCheck generate values of your own data type an Arbitrary instance must be defined:
data Point = MkPoint Int Int deriving Eq instance Arbitrary Point where arbitrary = do x <- arbitrary y <- arbitrary return (MkPoint x y) swapPoint :: Point -> Point swapPoint (MkPoint x y) = MkPoint y x -- swapPoint . swapPoint = id prop_swapInvolution point = swapPoint (swapPoint point) == point >>>quickCheck prop_swapInvolution+++ OK, passed 100 tests.
See Test.QuickCheck.Function for generating random shrinkable, showable functions used for testing higher-order functions and Test.QuickCheck.Monadic for testing impure or monadic code (e.g. effectful code in IO).
- quickCheck :: Testable prop => prop -> IO ()
- data Args = Args {}
- data Result- = Success { }
- | GaveUp { }
- | Failure { - numTests :: Int
- numShrinks :: Int
- numShrinkTries :: Int
- numShrinkFinal :: Int
- usedSeed :: QCGen
- usedSize :: Int
- reason :: String
- theException :: Maybe AnException
- labels :: [(String, Int)]
- output :: String
 
- | NoExpectedFailure { }
- | InsufficientCoverage { }
 
- stdArgs :: Args
- quickCheckWith :: Testable prop => Args -> prop -> IO ()
- quickCheckWithResult :: Testable prop => Args -> prop -> IO Result
- quickCheckResult :: Testable prop => prop -> IO Result
- verboseCheck :: Testable prop => prop -> IO ()
- verboseCheckWith :: Testable prop => Args -> prop -> IO ()
- verboseCheckWithResult :: Testable prop => Args -> prop -> IO Result
- verboseCheckResult :: Testable prop => prop -> IO Result
- quickCheckAll :: Q Exp
- verboseCheckAll :: Q Exp
- forAllProperties :: Q Exp
- polyQuickCheck :: Name -> ExpQ
- polyVerboseCheck :: Name -> ExpQ
- monomorphic :: Name -> ExpQ
- data Gen a
- choose :: Random a => (a, a) -> Gen a
- oneof :: [Gen a] -> Gen a
- frequency :: [(Int, Gen a)] -> Gen a
- elements :: [a] -> Gen a
- growingElements :: [a] -> Gen a
- sized :: (Int -> Gen a) -> Gen a
- resize :: Int -> Gen a -> Gen a
- scale :: (Int -> Int) -> Gen a -> Gen a
- suchThat :: Gen a -> (a -> Bool) -> Gen a
- suchThatMaybe :: Gen a -> (a -> Bool) -> Gen (Maybe a)
- listOf :: Gen a -> Gen [a]
- listOf1 :: Gen a -> Gen [a]
- vectorOf :: Int -> Gen a -> Gen [a]
- infiniteListOf :: Gen a -> Gen [a]
- shuffle :: [a] -> Gen [a]
- sublistOf :: [a] -> Gen [a]
- vector :: Arbitrary a => Int -> Gen [a]
- orderedList :: (Ord a, Arbitrary a) => Gen [a]
- infiniteList :: Arbitrary a => Gen [a]
- generate :: Gen a -> IO a
- sample :: Show a => Gen a -> IO ()
- sample' :: Gen a -> IO [a]
- class Arbitrary a where
- class CoArbitrary a where- coarbitrary :: a -> Gen b -> Gen b
 
- arbitrarySizedIntegral :: Integral a => Gen a
- arbitrarySizedNatural :: Integral a => Gen a
- arbitrarySizedFractional :: Fractional a => Gen a
- arbitrarySizedBoundedIntegral :: (Bounded a, Integral a) => Gen a
- arbitraryBoundedIntegral :: (Bounded a, Integral a) => Gen a
- arbitraryBoundedRandom :: (Bounded a, Random a) => Gen a
- arbitraryBoundedEnum :: (Bounded a, Enum a) => Gen a
- genericCoarbitrary :: (Generic a, GCoArbitrary (Rep a)) => a -> Gen b -> Gen b
- genericShrink :: (Generic a, Arbitrary a, RecursivelyShrink (Rep a), GSubterms (Rep a) a) => a -> [a]
- subterms :: (Generic a, Arbitrary a, GSubterms (Rep a) a) => a -> [a]
- recursivelyShrink :: (Generic a, RecursivelyShrink (Rep a)) => a -> [a]
- shrinkNothing :: a -> [a]
- shrinkList :: (a -> [a]) -> [a] -> [[a]]
- shrinkIntegral :: Integral a => a -> [a]
- shrinkRealFrac :: RealFrac a => a -> [a]
- shrinkRealFracToInteger :: RealFrac a => a -> [a]
- variant :: Integral n => n -> Gen a -> Gen a
- coarbitraryIntegral :: Integral a => a -> Gen b -> Gen b
- coarbitraryReal :: Real a => a -> Gen b -> Gen b
- coarbitraryShow :: Show a => a -> Gen b -> Gen b
- coarbitraryEnum :: Enum a => a -> Gen b -> Gen b
- (><) :: (Gen a -> Gen a) -> (Gen a -> Gen a) -> Gen a -> Gen a
- newtype Blind a = Blind {- getBlind :: a
 
- newtype Fixed a = Fixed {- getFixed :: a
 
- newtype OrderedList a = Ordered {- getOrdered :: [a]
 
- newtype NonEmptyList a = NonEmpty {- getNonEmpty :: [a]
 
- newtype Positive a = Positive {- getPositive :: a
 
- newtype NonZero a = NonZero {- getNonZero :: a
 
- newtype NonNegative a = NonNegative {- getNonNegative :: a
 
- newtype Large a = Large {- getLarge :: a
 
- newtype Small a = Small {- getSmall :: a
 
- data Smart a = Smart Int a
- newtype Shrink2 a = Shrink2 {- getShrink2 :: a
 
- data Shrinking s a = Shrinking s a
- class ShrinkState s a where- shrinkInit :: a -> s
- shrinkState :: a -> s -> [(a, s)]
 
- data Property
- class Testable prop where- property :: prop -> Property
- exhaustive :: prop -> Bool
 
- forAll :: (Show a, Testable prop) => Gen a -> (a -> prop) -> Property
- forAllShrink :: (Show a, Testable prop) => Gen a -> (a -> [a]) -> (a -> prop) -> Property
- shrinking :: Testable prop => (a -> [a]) -> a -> (a -> prop) -> Property
- (==>) :: Testable prop => Bool -> prop -> Property
- (===) :: (Eq a, Show a) => a -> a -> Property
- ioProperty :: Testable prop => IO prop -> Property
- verbose :: Testable prop => prop -> Property
- once :: Testable prop => prop -> Property
- within :: Testable prop => Int -> prop -> Property
- noShrinking :: Testable prop => prop -> Property
- (.&.) :: (Testable prop1, Testable prop2) => prop1 -> prop2 -> Property
- (.&&.) :: (Testable prop1, Testable prop2) => prop1 -> prop2 -> Property
- conjoin :: Testable prop => [prop] -> Property
- (.||.) :: (Testable prop1, Testable prop2) => prop1 -> prop2 -> Property
- disjoin :: Testable prop => [prop] -> Property
- counterexample :: Testable prop => String -> prop -> Property
- printTestCase :: Testable prop => String -> prop -> Property
- whenFail :: Testable prop => IO () -> prop -> Property
- whenFail' :: Testable prop => IO () -> prop -> Property
- expectFailure :: Testable prop => prop -> Property
- label :: Testable prop => String -> prop -> Property
- collect :: (Show a, Testable prop) => a -> prop -> Property
- classify :: Testable prop => Bool -> String -> prop -> Property
- cover :: Testable prop => Bool -> Int -> String -> prop -> Property
- data Discard = Discard
- discard :: a
- mapSize :: Testable prop => (Int -> Int) -> prop -> Property
Running tests
quickCheck :: Testable prop => prop -> IO () Source
Tests a property and prints the results to stdout.
Args specifies arguments to the QuickCheck driver
Constructors
| Args | |
| Fields 
 | |
Result represents the test result
Constructors
| Success | A successful test run | 
| GaveUp | Given up | 
| Failure | A failed test run | 
| Fields 
 | |
| NoExpectedFailure | A property that should have failed did not | 
| InsufficientCoverage | The tests passed but a use of  | 
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; 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.
$ has type forAllProperties(. An example invocation is Property -> IO Result) -> IO Bool$, which does the same thing as forAllProperties quickCheckResult$.quickCheckAll
forAllProperties 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 $(, where polyQuickCheck 'prop)prop is a property. Note that just evaluating quickCheck prop()!
$( means the same as polyQuickCheck 'prop)quickCheck $(monomorphic 'prop)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]$( has type monomorphic 'f)[.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
A generator for values of type a.
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.
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.
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.
suchThatMaybe :: Gen a -> (a -> Bool) -> Gen (Maybe a) Source
Tries to generate a value that satisfies a predicate.
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.
infiniteListOf :: Gen a -> Gen [a] Source
Generates an infinite list.
Generators which use Arbitrary
orderedList :: (Ord a, Arbitrary a) => Gen [a] Source
Generates an ordered list of a given length.
infiniteList :: Arbitrary a => Gen [a] Source
Generate 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
Arbitrary and CoArbitrary classes
class Arbitrary a where Source
Random generation and shrinking of values.
Minimal complete definition
Nothing
Methods
A generator for values of the given type.
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.
Most implementations of shrink should try at least three things:
- Shrink a term to any of its immediate subterms.
- Recursively apply shrinkto all immediate subterms.
- 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 shrinkx,landrin 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; note that these only work on GHC 7.2 and above. 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 xNil to Nil, and shrinking will go into an infinite loop.
If all this leaves you bewildered, you might try shrink = genericShrinkGeneric 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
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).
Minimal complete definition
Nothing
Methods
coarbitrary :: a -> Gen b -> Gen b Source
Used to generate a function of type a -> b. The first argument is a value, the second a generator. You should use variant to perturb the random generator; the goal is that different values for the first argument will lead to different calls to variant. An example will help:
instance CoArbitrary a => CoArbitrary [a] where coarbitrary [] =variant0 coarbitrary (x:xs) =variant1 . coarbitrary (x,xs)
Instances
Helper functions for implementing arbitrary
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.
Helper functions for implementing shrink
genericCoarbitrary :: (Generic a, GCoArbitrary (Rep a)) => a -> Gen b -> Gen b Source
Generic CoArbitrary implementation.
genericShrink :: (Generic a, Arbitrary 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, Arbitrary 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.
shrinkIntegral :: Integral a => a -> [a] Source
Shrink an integral number.
shrinkRealFrac :: RealFrac a => a -> [a] Source
Shrink a fraction.
shrinkRealFracToInteger :: RealFrac a => a -> [a] Source
Shrink a fraction, but only shrink to integral values.
Helper functions for implementing coarbitrary
coarbitraryIntegral :: Integral a => a -> Gen b -> Gen b Source
A coarbitrary implementation for integral numbers.
coarbitraryReal :: Real a => a -> Gen b -> Gen b Source
A coarbitrary implementation for real numbers.
coarbitraryShow :: Show a => a -> Gen b -> Gen b Source
coarbitrary helper for lazy people :-).
coarbitraryEnum :: Enum a => a -> Gen b -> Gen b Source
A coarbitrary implementation for enums.
(><) :: (Gen a -> Gen a) -> (Gen a -> Gen a) -> Gen a -> Gen a Source
Deprecated: Use ordinary function composition instead
Combine two generator perturbing functions, for example the results of calls to variant or coarbitrary.
Type-level modifiers for changing generator behavior
Blind x: as x, but x does not have to be in the Show class.
Fixed x: as x, but will not be shrunk.
newtype OrderedList a Source
Ordered xs: guarantees that xs is ordered.
Constructors
| Ordered | |
| Fields 
 | |
Instances
| Functor OrderedList | |
| Eq a => Eq (OrderedList a) | |
| Ord a => Ord (OrderedList a) | |
| Read a => Read (OrderedList a) | |
| Show a => Show (OrderedList a) | |
| (Ord a, Arbitrary a) => Arbitrary (OrderedList a) | 
newtype NonEmptyList a Source
NonEmpty xs: guarantees that xs is non-empty.
Constructors
| NonEmpty | |
| Fields 
 | |
Instances
| Functor NonEmptyList | |
| Eq a => Eq (NonEmptyList a) | |
| Ord a => Ord (NonEmptyList a) | |
| Read a => Read (NonEmptyList a) | |
| Show a => Show (NonEmptyList a) | |
| Arbitrary a => Arbitrary (NonEmptyList a) | 
Positive x: guarantees that x > 0.
Constructors
| Positive | |
| Fields 
 | |
NonZero x: guarantees that x /= 0.
Constructors
| NonZero | |
| Fields 
 | |
newtype NonNegative a Source
NonNegative x: guarantees that x >= 0.
Constructors
| NonNegative | |
| Fields 
 | |
Instances
| Functor NonNegative | |
| Enum a => Enum (NonNegative a) | |
| Eq a => Eq (NonNegative a) | |
| Ord a => Ord (NonNegative a) | |
| Read a => Read (NonNegative a) | |
| Show a => Show (NonNegative a) | |
| (Num a, Ord a, Arbitrary a) => Arbitrary (NonNegative a) | 
Large x: by default, QuickCheck generates Ints drawn from a small range. Large Int gives you values drawn from the entire range instead.
Small x: generates values of x drawn from a small range. The opposite of Large.
Smart _ x: tries a different order when shrinking.
Shrink2 x: allows 2 shrinking steps at the same time when shrinking x
Constructors
| Shrink2 | |
| Fields 
 | |
Shrinking _ x: allows for maintaining a state during shrinking.
Constructors
| Shrinking s a | 
class ShrinkState s a where Source
Properties
The type of properties.
Backwards combatibility note: in older versions of QuickCheck Property was a type synonym for Gen PropGen monad operations. Code that does this will no longer typecheck. However, it is easy to fix: because of the Testable typeclass, any combinator that expects a Property will also accept a Gen PropertyProperty where you need a Gen areturn to get a Gen Property
class Testable prop where Source
The class of things which can be tested, i.e. turned into a property.
Minimal complete definition
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.
Arguments
| :: Testable prop | |
| => (a -> [a]) | 
 | 
| -> a | The original argument | 
| -> (a -> prop) | |
| -> Property | 
Shrinks the argument to property if it fails. Shrinking is done automatically for most types. This 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.
ioProperty :: Testable prop => IO prop -> Property Source
Do I/O inside a property. This can obviously lead to unrepeatable testcases, so use with care.
For more advanced monadic testing you may want to look at Test.QuickCheck.Monadic.
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.
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.
(.||.) :: (Testable prop1, Testable prop2) => prop1 -> prop2 -> Property infixr 1 Source
Disjunction: p1 .||. p2 passes unless p1 and p2 simultaneously fail.
What to do on failure
counterexample :: Testable prop => String -> prop -> Property Source
Adds the given string to the counterexample.
printTestCase :: Testable prop => String -> prop -> Property Source
Deprecated: Use counterexample instead
Adds the given string to the counterexample.
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.
collect :: (Show a, Testable prop) => a -> prop -> Property Source
Labels a property with a value:
collect x = label (show x)
Arguments
| :: Testable prop | |
| => Bool | 
 | 
| -> String | Label. | 
| -> prop | |
| -> Property | 
Conditionally labels test case.
Arguments
| :: Testable prop | |
| => Bool | 
 | 
| -> 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.
Miscellaneous
If a property returns Discard, the current test case is discarded, the same as if a precondition was false.
Constructors
| Discard | 
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.