Safe Haskell | Safe |
---|---|
Language | Haskell98 |
The QuickCheck manual gives detailed information about using QuickCheck effectively.
To start using QuickCheck, write down your property as a function returning Bool
.
For example, to check that reversing a list twice gives back the same list you can write:
import Test.QuickCheck prop_reverse :: [Int] -> Bool prop_reverse xs = reverse (reverse xs) == xs
You can then use QuickCheck to test prop_reverse
on 100 random lists:
>>>
quickCheck prop_reverse
+++ OK, passed 100 tests.
To run more tests you can use the withMaxSuccess
combinator:
>>>
quickCheck (withMaxSuccess 10000 prop_reverse)
+++ OK, passed 10000 tests.
To use QuickCheck on your own data types you will need to write Arbitrary
instances for those types. See the
QuickCheck manual for
details about how to do that.
This module exports most of QuickCheck's functionality, but see also Test.QuickCheck.Monadic which helps with testing impure or monadic code.
Synopsis
- quickCheck :: Testable prop => prop -> IO ()
- data Args = Args {
- replay :: Maybe (QCGen, Int)
- maxSuccess :: Int
- maxDiscardRatio :: Int
- maxSize :: Int
- chatty :: Bool
- maxShrinks :: Int
- data Result
- = Success { }
- | GaveUp { }
- | Failure {
- numTests :: Int
- numShrinks :: Int
- numShrinkTries :: Int
- numShrinkFinal :: Int
- usedSeed :: QCGen
- usedSize :: Int
- reason :: String
- theException :: Maybe AnException
- labels :: [(String, Double)]
- output :: String
- failingTestCase :: [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
- allProperties :: 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
- getSize :: Gen Int
- resize :: Int -> Gen a -> Gen a
- scale :: (Int -> Int) -> Gen a -> Gen a
- suchThat :: Gen a -> (a -> Bool) -> Gen a
- suchThatMap :: Gen a -> (a -> Maybe b) -> Gen b
- 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
- class Arbitrary1 f where
- arbitrary1 :: (Arbitrary1 f, Arbitrary a) => Gen (f a)
- shrink1 :: (Arbitrary1 f, Arbitrary a) => f a -> [f a]
- class Arbitrary2 f where
- arbitrary2 :: (Arbitrary2 f, Arbitrary a, Arbitrary b) => Gen (f a b)
- shrink2 :: (Arbitrary2 f, Arbitrary a, Arbitrary b) => f a b -> [f a b]
- applyArbitrary2 :: (Arbitrary a, Arbitrary b) => (a -> b -> r) -> Gen r
- applyArbitrary3 :: (Arbitrary a, Arbitrary b, Arbitrary c) => (a -> b -> c -> r) -> Gen r
- applyArbitrary4 :: (Arbitrary a, Arbitrary b, Arbitrary c, Arbitrary d) => (a -> b -> c -> d -> r) -> Gen r
- 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
- arbitraryUnicodeChar :: Gen Char
- arbitraryASCIIChar :: Gen Char
- arbitraryPrintableChar :: Gen Char
- genericCoarbitrary :: (Generic a, GCoArbitrary (Rep a)) => a -> Gen b -> Gen b
- genericShrink :: (Generic a, RecursivelyShrink (Rep a), GSubterms (Rep a) a) => a -> [a]
- subterms :: (Generic a, GSubterms (Rep a) a) => a -> [a]
- recursivelyShrink :: (Generic a, RecursivelyShrink (Rep a)) => a -> [a]
- shrinkNothing :: a -> [a]
- shrinkList :: (a -> [a]) -> [a] -> [[a]]
- shrinkMap :: Arbitrary a => (a -> b) -> (b -> a) -> b -> [b]
- shrinkMapBy :: (a -> b) -> (b -> a) -> (a -> [a]) -> b -> [b]
- shrinkIntegral :: Integral a => a -> [a]
- shrinkRealFrac :: 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]
- data InfiniteList a = InfiniteList {
- getInfiniteList :: [a]
- infiniteListInternalData :: InfiniteListInternalData 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
- newtype ASCIIString = ASCIIString {}
- newtype UnicodeString = UnicodeString {}
- newtype PrintableString = PrintableString {}
- data Fun a b = Fun (a :-> b, b, Shrunk) (a -> b)
- applyFun :: Fun a b -> a -> b
- applyFun2 :: Fun (a, b) c -> a -> b -> c
- applyFun3 :: Fun (a, b, c) d -> a -> b -> c -> d
- pattern Fn :: (a -> b) -> Fun a b
- pattern Fn2 :: (a -> b -> c) -> Fun (a, b) c
- pattern Fn3 :: (a -> b -> c -> d) -> Fun (a, b, c) d
- class Function a where
- functionMap :: Function b => (a -> b) -> (b -> a) -> (a -> c) -> a :-> c
- data Property
- class Testable prop where
- 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
- total :: NFData a => a -> Property
- ioProperty :: Testable prop => IO prop -> Property
- verbose :: Testable prop => prop -> Property
- once :: Testable prop => prop -> Property
- again :: Testable prop => prop -> Property
- withMaxSuccess :: Testable prop => Int -> 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
.
By default up to 100 tests are performed, which may not be enough
to find all bugs. To run more tests, use withMaxSuccess
.
Args specifies arguments to the QuickCheck driver
Args | |
|
Result represents the test result
Success | A successful test run |
GaveUp | Given up |
Failure | A failed test run |
| |
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 and later; without it, quickCheckAll
will not be able to find
any of the properties. For the curious, the return []
is a
Template Haskell splice that makes GHC insert the empty list
of declarations at that point in the program; GHC typechecks
everything before the return []
before it starts on the rest
of the module, which means that the later call to quickCheckAll
can see everything that was defined before the return []
. Yikes!
verboseCheckAll :: Q Exp Source #
Test all properties in the current module.
This is just a convenience function that combines quickCheckAll
and verbose
.
verboseCheckAll
has the same issue with scoping as quickCheckAll
:
see the note there about return []
.
forAllProperties :: Q Exp Source #
Test all properties in the current module, using a custom
quickCheck
function. The same caveats as with quickCheckAll
apply.
$
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 []
.
allProperties :: Q Exp Source #
List all properties in the current module.
$
has type allProperties
[(
.String
, Property
)]
allProperties
has the same issue with scoping as quickCheckAll
:
see the note there about return []
.
Testing polymorphic properties
polyQuickCheck :: Name -> ExpQ Source #
Test a polymorphic property, defaulting all type variables to Integer
.
Invoke as $(
, where polyQuickCheck
'prop)prop
is a property.
Note that just evaluating
in GHCi will seem to
work, but will silently default all type variables to quickCheck
prop()
!
$(
means the same as
polyQuickCheck
'prop)
.
If you want to supply custom arguments to 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
then 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
.
The third-party package
QuickCheck-GenT
provides a monad transformer version of GenT
.
Generator combinators
choose :: Random a => (a, a) -> Gen a Source #
Generates a random element in the given inclusive range.
oneof :: [Gen a] -> Gen a Source #
Randomly uses one of the given generators. The input list must be non-empty.
frequency :: [(Int, Gen a)] -> Gen a Source #
Chooses one of the given generators, with a weighted random distribution. The input list must be non-empty.
elements :: [a] -> Gen a Source #
Generates one of the given values. The input list must be non-empty.
growingElements :: [a] -> Gen a Source #
Takes a list of elements of increasing size, and chooses among an initial segment of the list. The size of this initial segment increases with the size parameter. The input list must be non-empty.
sized :: (Int -> Gen a) -> Gen a Source #
Used to construct generators that depend on the size parameter.
For example, listOf
, which uses the size parameter as an upper bound on
length of lists it generates, can be defined like this:
listOf :: Gen a -> Gen [a] listOf gen = sized $ \n -> do k <- choose (0,n) vectorOf k gen
You can also do this using getSize
.
Generates the size parameter. Used to construct generators that depend on the size parameter.
For example, listOf
, which uses the size parameter as an upper bound on
length of lists it generates, can be defined like this:
listOf :: Gen a -> Gen [a] listOf gen = do n <- getSize k <- choose (0,n) vectorOf k gen
You can also do this using sized
.
resize :: Int -> Gen a -> Gen a Source #
Overrides the size parameter. Returns a generator which uses the given size instead of the runtime-size parameter.
scale :: (Int -> Int) -> Gen a -> Gen a Source #
Adjust the size parameter, by transforming it with the given function.
suchThatMap :: Gen a -> (a -> Maybe b) -> Gen b Source #
Generates a value for which the given function returns a Just
, and then
applies the function.
suchThatMaybe :: Gen a -> (a -> Bool) -> Gen (Maybe a) Source #
Tries to generate a value that satisfies a predicate.
If it fails to do so after enough attempts, returns Nothing
.
listOf :: Gen a -> Gen [a] Source #
Generates a list of random length. The maximum length depends on the size parameter.
listOf1 :: Gen a -> Gen [a] Source #
Generates a non-empty list of random length. The maximum length depends on the size parameter.
infiniteListOf :: Gen a -> Gen [a] Source #
Generates an infinite list.
Generators which use Arbitrary
infiniteList :: Arbitrary a => Gen [a] Source #
Generates an infinite list.
Running a generator
generate :: Gen a -> IO a Source #
Run a generator. The size passed to the generator is always 30;
if you want another size then you should explicitly use resize
.
Generator debugging
Arbitrary and CoArbitrary classes
class Arbitrary a where Source #
Random generation and shrinking of values.
QuickCheck provides Arbitrary
instances for most types in base
,
except those which incur extra dependencies.
For a wider range of Arbitrary
instances see the
quickcheck-instances
package.
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!
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 =
, but by customising
the behaviour of genericShrink
shrink
you can often get simpler counterexamples.
Most implementations of shrink
should try at least three things:
- Shrink a term to any of its immediate subterms.
You can use
subterms
to do this. - Recursively apply
shrink
to all immediate subterms. You can userecursivelyShrink
to do this. - 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
,l
andr
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
as this shrinks shrink
x = Nil:genericShrink
xNil
to Nil
, and shrinking will go into an
infinite loop.
If all this leaves you bewildered, you might try
to begin with,
after deriving shrink
= genericShrink
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
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)
.
coarbitrary :: a -> Gen b -> Gen b Source #
Used to generate a function of type a -> b
.
The first argument is a value, the second a generator.
You should use variant
to perturb the random generator;
the goal is that different values for the first argument will
lead to different calls to variant
. An example will help:
instance CoArbitrary a => CoArbitrary [a] where coarbitrary [] =variant
0 coarbitrary (x:xs) =variant
1 . coarbitrary (x,xs)
coarbitrary :: (Generic a, GCoArbitrary (Rep a)) => a -> Gen b -> Gen b Source #
Used to generate a function of type a -> b
.
The first argument is a value, the second a generator.
You should use variant
to perturb the random generator;
the goal is that different values for the first argument will
lead to different calls to variant
. An example will help:
instance CoArbitrary a => CoArbitrary [a] where coarbitrary [] =variant
0 coarbitrary (x:xs) =variant
1 . coarbitrary (x,xs)
Instances
Unary and Binary classes
class Arbitrary1 f where Source #
Lifting of the Arbitrary
class to unary type constructors.
liftArbitrary :: Gen a -> Gen (f a) Source #
liftShrink :: (a -> [a]) -> f a -> [f a] Source #
Instances
arbitrary1 :: (Arbitrary1 f, Arbitrary a) => Gen (f a) Source #
shrink1 :: (Arbitrary1 f, Arbitrary a) => f a -> [f a] Source #
class Arbitrary2 f where Source #
Lifting of the Arbitrary
class to binary type constructors.
liftArbitrary2 :: Gen a -> Gen b -> Gen (f a b) Source #
liftShrink2 :: (a -> [a]) -> (b -> [b]) -> f a b -> [f a b] Source #
Instances
Arbitrary2 Either Source # | |
Defined in Test.QuickCheck.Arbitrary | |
Arbitrary2 (,) Source # | |
Defined in Test.QuickCheck.Arbitrary liftArbitrary2 :: Gen a -> Gen b -> Gen (a, b) Source # liftShrink2 :: (a -> [a]) -> (b -> [b]) -> (a, b) -> [(a, b)] Source # | |
Arbitrary2 (Const :: * -> * -> *) Source # | |
Defined in Test.QuickCheck.Arbitrary | |
Arbitrary2 (Constant :: * -> * -> *) Source # | |
Defined in Test.QuickCheck.Arbitrary |
arbitrary2 :: (Arbitrary2 f, Arbitrary a, Arbitrary b) => Gen (f a b) Source #
Helper functions for implementing arbitrary
applyArbitrary2 :: (Arbitrary a, Arbitrary b) => (a -> b -> r) -> Gen r Source #
Apply a binary function to random arguments.
applyArbitrary3 :: (Arbitrary a, Arbitrary b, Arbitrary c) => (a -> b -> c -> r) -> Gen r Source #
Apply a ternary function to random arguments.
applyArbitrary4 :: (Arbitrary a, Arbitrary b, Arbitrary c, Arbitrary d) => (a -> b -> c -> d -> r) -> Gen r Source #
Apply a function of arity 4 to random arguments.
arbitrarySizedIntegral :: Integral a => Gen a Source #
Generates an integral number. The number can be positive or negative and its maximum absolute value depends on the size parameter.
arbitrarySizedNatural :: Integral a => Gen a Source #
Generates a natural number. The number's maximum value depends on the size parameter.
arbitrarySizedFractional :: Fractional a => Gen a Source #
Generates a fractional number. The number can be positive or negative and its maximum absolute value depends on the size parameter.
arbitrarySizedBoundedIntegral :: (Bounded a, Integral a) => Gen a Source #
Generates an integral number from a bounded domain. The number is chosen from the entire range of the type, but small numbers are generated more often than big numbers. Inspired by demands from Phil Wadler.
arbitraryBoundedIntegral :: (Bounded a, Integral a) => Gen a Source #
Generates an integral number. The number is chosen uniformly from
the entire range of the type. You may want to use
arbitrarySizedBoundedIntegral
instead.
arbitraryBoundedRandom :: (Bounded a, Random a) => Gen a Source #
Generates an element of a bounded type. The element is chosen from the entire range of the type.
arbitraryBoundedEnum :: (Bounded a, Enum a) => Gen a Source #
Generates an element of a bounded enumeration.
arbitraryUnicodeChar :: Gen Char Source #
Generates any Unicode character (but not a surrogate)
arbitraryASCIIChar :: Gen Char Source #
Generates a random ASCII character (0-127).
arbitraryPrintableChar :: Gen Char Source #
Generates a printable Unicode character.
Helper functions for implementing shrink
genericCoarbitrary :: (Generic a, GCoArbitrary (Rep a)) => a -> Gen b -> Gen b Source #
Generic CoArbitrary implementation.
genericShrink :: (Generic a, RecursivelyShrink (Rep a), GSubterms (Rep a) a) => a -> [a] Source #
Shrink a term to any of its immediate subterms, and also recursively shrink all subterms.
recursivelyShrink :: (Generic a, RecursivelyShrink (Rep a)) => a -> [a] Source #
Recursively shrink all immediate subterms.
shrinkNothing :: a -> [a] Source #
Returns no shrinking alternatives.
shrinkList :: (a -> [a]) -> [a] -> [[a]] Source #
Shrink a list of values given a shrinking function for individual values.
shrinkMap :: Arbitrary a => (a -> b) -> (b -> a) -> b -> [b] Source #
Map a shrink function to another domain. This is handy if your data type has special invariants, but is almost isomorphic to some other type.
shrinkOrderedList :: (Ord a, Arbitrary a) => [a] -> [[a]] shrinkOrderedList = shrinkMap sort id shrinkSet :: (Ord a, Arbitrary a) => Set a -> Set [a] shrinkSet = shrinkMap fromList toList
shrinkMapBy :: (a -> b) -> (b -> a) -> (a -> [a]) -> b -> [b] Source #
Non-overloaded version of shrinkMap
.
shrinkIntegral :: Integral a => a -> [a] Source #
Shrink an integral number.
shrinkRealFrac :: RealFrac a => a -> [a] Source #
Shrink a fraction.
Helper functions for implementing coarbitrary
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.
Instances
Functor Blind Source # | |
Enum a => Enum (Blind a) Source # | |
Eq a => Eq (Blind a) Source # | |
Integral a => Integral (Blind a) Source # | |
Defined in Test.QuickCheck.Modifiers | |
Num a => Num (Blind a) Source # | |
Ord a => Ord (Blind a) Source # | |
Real a => Real (Blind a) Source # | |
Defined in Test.QuickCheck.Modifiers toRational :: Blind a -> Rational # | |
Show (Blind a) Source # | |
Arbitrary a => Arbitrary (Blind a) Source # | |
Fixed x
: as x, but will not be shrunk.
Instances
Functor Fixed Source # | |
Enum a => Enum (Fixed a) Source # | |
Eq a => Eq (Fixed a) Source # | |
Integral a => Integral (Fixed a) Source # | |
Defined in Test.QuickCheck.Modifiers | |
Num a => Num (Fixed a) Source # | |
Ord a => Ord (Fixed a) Source # | |
Read a => Read (Fixed a) Source # | |
Real a => Real (Fixed a) Source # | |
Defined in Test.QuickCheck.Modifiers toRational :: Fixed a -> Rational # | |
Show a => Show (Fixed a) Source # | |
Arbitrary a => Arbitrary (Fixed a) Source # | |
newtype OrderedList a Source #
Ordered xs
: guarantees that xs is ordered.
Ordered | |
|
Instances
newtype NonEmptyList a Source #
NonEmpty xs
: guarantees that xs is non-empty.
NonEmpty | |
|
Instances
data InfiniteList a Source #
InfiniteList xs _
: guarantees that xs is an infinite list.
When a counterexample is found, only prints the prefix of xs
that was used by the program.
Here is a contrived example property:
prop_take_10 :: InfiniteList Char -> Bool prop_take_10 (InfiniteList xs _) = or [ x == 'a' | x <- take 10 xs ]
In the following counterexample, the list must start with "bbbbbbbbbb"
but
the remaining (infinite) part can contain anything:
>>>
quickCheck prop_take_10
*** Failed! Falsifiable (after 1 test and 14 shrinks): "bbbbbbbbbb" ++ ...
InfiniteList | |
|
Instances
Show a => Show (InfiniteList a) Source # | |
Defined in Test.QuickCheck.Modifiers showsPrec :: Int -> InfiniteList a -> ShowS # show :: InfiniteList a -> String # showList :: [InfiniteList a] -> ShowS # | |
Arbitrary a => Arbitrary (InfiniteList a) Source # | |
Defined in Test.QuickCheck.Modifiers arbitrary :: Gen (InfiniteList a) Source # shrink :: InfiniteList a -> [InfiniteList a] Source # |
Positive x
: guarantees that x > 0
.
Positive | |
|
Instances
Functor Positive Source # | |
Enum a => Enum (Positive a) Source # | |
Defined in Test.QuickCheck.Modifiers succ :: Positive a -> Positive a # pred :: Positive a -> Positive a # fromEnum :: Positive a -> Int # enumFrom :: Positive a -> [Positive a] # enumFromThen :: Positive a -> Positive a -> [Positive a] # enumFromTo :: Positive a -> Positive a -> [Positive a] # enumFromThenTo :: Positive a -> Positive a -> Positive a -> [Positive a] # | |
Eq a => Eq (Positive a) Source # | |
Ord a => Ord (Positive a) Source # | |
Read a => Read (Positive a) Source # | |
Show a => Show (Positive a) Source # | |
(Num a, Ord a, Arbitrary a) => Arbitrary (Positive a) Source # | |
NonZero x
: guarantees that x /= 0
.
NonZero | |
|
Instances
Functor NonZero Source # | |
Enum a => Enum (NonZero a) Source # | |
Defined in Test.QuickCheck.Modifiers succ :: NonZero a -> NonZero a # pred :: NonZero a -> NonZero a # fromEnum :: NonZero a -> Int # enumFrom :: NonZero a -> [NonZero a] # enumFromThen :: NonZero a -> NonZero a -> [NonZero a] # enumFromTo :: NonZero a -> NonZero a -> [NonZero a] # enumFromThenTo :: NonZero a -> NonZero a -> NonZero a -> [NonZero a] # | |
Eq a => Eq (NonZero a) Source # | |
Ord a => Ord (NonZero a) Source # | |
Defined in Test.QuickCheck.Modifiers | |
Read a => Read (NonZero a) Source # | |
Show a => Show (NonZero a) Source # | |
(Num a, Eq a, Arbitrary a) => Arbitrary (NonZero a) Source # | |
newtype NonNegative a Source #
NonNegative x
: guarantees that x >= 0
.
Instances
Large x
: by default, QuickCheck generates Int
s drawn from a small
range. Large Int
gives you values drawn from the entire range instead.
Instances
Functor Large Source # | |
Enum a => Enum (Large a) Source # | |
Eq a => Eq (Large a) Source # | |
Integral a => Integral (Large a) Source # | |
Defined in Test.QuickCheck.Modifiers | |
Num a => Num (Large a) Source # | |
Ord a => Ord (Large a) Source # | |
Read a => Read (Large a) Source # | |
Real a => Real (Large a) Source # | |
Defined in Test.QuickCheck.Modifiers toRational :: Large a -> Rational # | |
Show a => Show (Large a) Source # | |
Ix a => Ix (Large a) Source # | |
Defined in Test.QuickCheck.Modifiers | |
(Integral a, Bounded a) => Arbitrary (Large a) Source # | |
Small x
: generates values of x
drawn from a small range.
The opposite of Large
.
Instances
Functor Small Source # | |
Enum a => Enum (Small a) Source # | |
Eq a => Eq (Small a) Source # | |
Integral a => Integral (Small a) Source # | |
Defined in Test.QuickCheck.Modifiers | |
Num a => Num (Small a) Source # | |
Ord a => Ord (Small a) Source # | |
Read a => Read (Small a) Source # | |
Real a => Real (Small a) Source # | |
Defined in Test.QuickCheck.Modifiers toRational :: Small a -> Rational # | |
Show a => Show (Small a) Source # | |
Ix a => Ix (Small a) Source # | |
Defined in Test.QuickCheck.Modifiers | |
Integral a => Arbitrary (Small a) Source # | |
Smart _ x
: tries a different order when shrinking.
Shrink2 x
: allows 2 shrinking steps at the same time when shrinking x
Shrink2 | |
|
Instances
Functor Shrink2 Source # | |
Enum a => Enum (Shrink2 a) Source # | |
Defined in Test.QuickCheck.Modifiers succ :: Shrink2 a -> Shrink2 a # pred :: Shrink2 a -> Shrink2 a # fromEnum :: Shrink2 a -> Int # enumFrom :: Shrink2 a -> [Shrink2 a] # enumFromThen :: Shrink2 a -> Shrink2 a -> [Shrink2 a] # enumFromTo :: Shrink2 a -> Shrink2 a -> [Shrink2 a] # enumFromThenTo :: Shrink2 a -> Shrink2 a -> Shrink2 a -> [Shrink2 a] # | |
Eq a => Eq (Shrink2 a) Source # | |
Integral a => Integral (Shrink2 a) Source # | |
Defined in Test.QuickCheck.Modifiers | |
Num a => Num (Shrink2 a) Source # | |
Defined in Test.QuickCheck.Modifiers | |
Ord a => Ord (Shrink2 a) Source # | |
Defined in Test.QuickCheck.Modifiers | |
Read a => Read (Shrink2 a) Source # | |
Real a => Real (Shrink2 a) Source # | |
Defined in Test.QuickCheck.Modifiers toRational :: Shrink2 a -> Rational # | |
Show a => Show (Shrink2 a) Source # | |
Arbitrary a => Arbitrary (Shrink2 a) Source # | |
Shrinking _ x
: allows for maintaining a state during shrinking.
Shrinking s a |
class ShrinkState s a where Source #
shrinkInit :: a -> s Source #
shrinkState :: a -> s -> [(a, s)] Source #
newtype ASCIIString Source #
ASCIIString
: generates an ASCII string.
Instances
newtype UnicodeString Source #
UnicodeString
: generates a unicode String.
The string will not contain surrogate pairs.
Instances
newtype PrintableString Source #
PrintableString
: generates a printable unicode String.
The string will not contain surrogate pairs.
Instances
Eq PrintableString Source # | |
Defined in Test.QuickCheck.Modifiers (==) :: PrintableString -> PrintableString -> Bool # (/=) :: PrintableString -> PrintableString -> Bool # | |
Ord PrintableString Source # | |
Defined in Test.QuickCheck.Modifiers compare :: PrintableString -> PrintableString -> Ordering # (<) :: PrintableString -> PrintableString -> Bool # (<=) :: PrintableString -> PrintableString -> Bool # (>) :: PrintableString -> PrintableString -> Bool # (>=) :: PrintableString -> PrintableString -> Bool # max :: PrintableString -> PrintableString -> PrintableString # min :: PrintableString -> PrintableString -> PrintableString # | |
Read PrintableString Source # | |
Defined in Test.QuickCheck.Modifiers | |
Show PrintableString Source # | |
Defined in Test.QuickCheck.Modifiers showsPrec :: Int -> PrintableString -> ShowS # show :: PrintableString -> String # showList :: [PrintableString] -> ShowS # | |
Arbitrary PrintableString Source # | |
Defined in Test.QuickCheck.Modifiers |
Functions
Generation of random shrinkable, showable functions.
To generate random values of type
,
you must have an instance Fun
a b
.Function
a
applyFun :: Fun a b -> a -> b Source #
Extracts the value of a function.
Fn
is the pattern equivalent of this function.
prop :: Fun String Integer -> Bool prop f = applyFun f "banana" == applyFun f "monkey" || applyFun f "banana" == applyFun f "elephant"
applyFun2 :: Fun (a, b) c -> a -> b -> c Source #
Extracts the value of a binary function.
Fn2
is the pattern equivalent of this function.
prop_zipWith :: Fun (Int, Bool) Char -> [Int] -> [Bool] -> Bool prop_zipWith f xs ys = zipWith (applyFun2 f) xs ys == [ applyFun2 f x y | (x, y) <- zip xs ys]
applyFun3 :: Fun (a, b, c) d -> a -> b -> c -> d Source #
Extracts the value of a ternary function. Fn3
is the
pattern equivalent of this function.
pattern Fn :: (a -> b) -> Fun a b Source #
A modifier for testing functions.
prop :: Fun String Integer -> Bool prop (Fn f) = f "banana" == f "monkey" || f "banana" == f "elephant"
pattern Fn2 :: (a -> b -> c) -> Fun (a, b) c Source #
A modifier for testing binary functions.
prop_zipWith :: Fun (Int, Bool) Char -> [Int] -> [Bool] -> Bool prop_zipWith (Fn2 f) xs ys = zipWith f xs ys == [ f x y | (x, y) <- zip xs ys]
pattern Fn3 :: (a -> b -> c -> d) -> Fun (a, b, c) d Source #
A modifier for testing ternary functions.
class Function a where Source #
The class Function a
is used for random generation of showable
functions of type a -> b
.
There is a default implementation for function
, which you can use
if your type has structural equality. Otherwise, you can normally
use functionMap
or functionShow
.
function :: (a -> b) -> a :-> b Source #
function :: (Generic a, GFunction (Rep a)) => (a -> b) -> a :-> b Source #
Instances
functionMap :: Function b => (a -> b) -> (b -> a) -> (a -> c) -> a :-> c Source #
Properties
The type of properties.
class Testable prop where Source #
The class of properties, i.e., types which QuickCheck knows how to test.
Typically a property will be a function returning Bool
or Property
.
If a property does no quantification, i.e. has no
parameters and doesn't use forAll
, it will only be tested once.
This may not be what you want if your property is an IO Bool
.
You can change this behaviour using the again
combinator.
Instances
Testable Bool Source # | |
Testable () Source # | |
Defined in Test.QuickCheck.Property | |
Testable Result Source # | |
Testable Prop Source # | |
Testable Discard Source # | |
Testable Property Source # | |
Testable prop => Testable (Gen prop) Source # | |
(Arbitrary a, Show a, Testable prop) => Testable (a -> prop) Source # | |
Defined in Test.QuickCheck.Property |
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.
:: Testable prop | |
=> (a -> [a]) |
|
-> a | The original argument |
-> (a -> prop) | |
-> Property |
Shrinks the argument to a property if it fails. Shrinking is done automatically for most types. This function is only needed when you want to override the default behavior.
(==>) :: Testable prop => Bool -> prop -> Property infixr 0 Source #
Implication for properties: The resulting property holds if
the first argument is False
(in which case the test case is discarded),
or if the given property holds.
(===) :: (Eq a, Show a) => a -> a -> Property infix 4 Source #
Like ==
, but prints a counterexample when it fails.
total :: NFData a => a -> Property Source #
Checks that a value is total, i.e., doesn't crash when evaluated.
ioProperty :: Testable prop => IO prop -> Property Source #
Do I/O inside a property.
Warning: any random values generated inside of the argument to ioProperty
will not currently be shrunk. For best results, generate all random values
before calling ioProperty
.
Controlling property execution
verbose :: Testable prop => prop -> Property Source #
Prints out the generated testcase every time the property is tested.
Only variables quantified over inside the verbose
are printed.
once :: Testable prop => prop -> Property Source #
Modifies a property so that it only will be tested once.
Opposite of again
.
again :: Testable prop => prop -> Property Source #
Modifies a property so that it will be tested repeatedly.
Opposite of once
.
withMaxSuccess :: Testable prop => Int -> prop -> Property Source #
Configures how many times a property will be tested.
For example,
quickCheck (withMaxSuccess 1000 p)
will test p
up to 1000 times.
within :: Testable prop => Int -> prop -> Property Source #
Considers a property failed if it does not complete within the given number of microseconds.
noShrinking :: Testable prop => prop -> Property Source #
Disables shrinking for a property altogether.
Conjunction and disjunction
(.&.) :: (Testable prop1, Testable prop2) => prop1 -> prop2 -> Property infixr 1 Source #
Nondeterministic choice: p1
.&.
p2
picks randomly one of
p1
and p2
to test. If you test the property 100 times it
makes 100 random choices.
(.&&.) :: (Testable prop1, Testable prop2) => prop1 -> prop2 -> Property infixr 1 Source #
Conjunction: p1
.&&.
p2
passes if both p1
and p2
pass.
(.||.) :: (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 if the property fails.
printTestCase :: Testable prop => String -> prop -> Property Source #
Deprecated: Use counterexample instead
Adds the given string to the counterexample if the property fails.
whenFail :: Testable prop => IO () -> prop -> Property Source #
Performs an IO
action after the last failure of a property.
whenFail' :: Testable prop => IO () -> prop -> Property Source #
Performs an IO
action every time a property fails. Thus,
if shrinking is done, this can be used to keep track of the
failures along the way.
expectFailure :: Testable prop => prop -> Property Source #
Indicates that a property is supposed to fail. QuickCheck will report an error if it does not fail.
Analysing test distribution
label :: Testable prop => String -> prop -> Property Source #
Attaches a label to a property. This is used for reporting test case distribution.
For example:
prop_reverse_reverse :: [Int] -> Property prop_reverse_reverse xs = label ("length of input is " ++ show (length xs)) $ reverse (reverse xs) === xs
>>>
quickCheck prop_reverse_reverse
+++ OK, passed 100 tests: 7% length of input is 7 6% length of input is 3 5% length of input is 4 4% length of input is 6 ...
collect :: (Show a, Testable prop) => a -> prop -> Property Source #
Attaches a label to a property. This is used for reporting test case distribution.
collect x = label (show x)
For example:
prop_reverse_reverse :: [Int] -> Property prop_reverse_reverse xs = collect (length xs) $ reverse (reverse xs) === xs
>>>
quickCheck prop_reverse_reverse
+++ OK, passed 100 tests: 7% 7 6% 3 5% 4 4% 6 ...
Records how many test cases satisfy a given condition.
For example:
prop_sorted_sort :: [Int] -> Property prop_sorted_sort xs = sorted xs ==> classify (length xs > 1) "non-trivial" $ sort xs === xs
>>>
quickCheck prop_sorted_sort
+++ OK, passed 100 tests (22% non-trivial).
:: 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.
For example:
prop_sorted_sort :: [Int] -> Property prop_sorted_sort xs = sorted xs ==> cover (length xs > 1) 50 "non-trivial" $ sort xs === xs
>>>
quickCheck prop_sorted_sort
*** Insufficient coverage after 100 tests (only 24% non-trivial, not 50%).
Miscellaneous
If a property returns Discard
, the current test case is discarded,
the same as if a precondition was false.
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.