Safe Haskell | Safe |
---|---|
Language | Haskell2010 |
Test.QuickCheck
Contents
- Running tests
-
The
Arbitrary
typeclass: generation of random values -
The
Gen
monad: combinators for building random generators -
The
Function
typeclass: generation of random shrinkable, showable functions -
The
CoArbitrary
typeclass: generation of functions the old-fashioned way - Type-level modifiers for changing generator behavior
- Property combinators
- Analysing test case distribution
Description
The QuickCheck manual gives detailed information about using QuickCheck effectively. You can also try https://begriffs.com/posts/2017-01-14-design-use-quickcheck.html , a tutorial written by a user of QuickCheck.
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.
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
- numDiscarded :: Int
- numShrinks :: Int
- numShrinkTries :: Int
- numShrinkFinal :: Int
- usedSeed :: QCGen
- usedSize :: Int
- reason :: String
- theException :: Maybe AnException
- output :: String
- failingTestCase :: [ String ]
- failingLabels :: [ String ]
- failingClasses :: Set String
- | NoExpectedFailure { }
- stdArgs :: Args
- quickCheckWith :: Testable prop => Args -> prop -> IO ()
- quickCheckWithResult :: Testable prop => Args -> prop -> IO Result
- quickCheckResult :: Testable prop => prop -> IO Result
- isSuccess :: Result -> Bool
- 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
- class Arbitrary a where
- 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]
- shrinkDecimal :: RealFrac a => a -> [a]
-
class
Arbitrary1
f
where
- liftArbitrary :: Gen a -> Gen (f a)
- liftShrink :: (a -> [a]) -> f a -> [f a]
- arbitrary1 :: ( Arbitrary1 f, Arbitrary a) => Gen (f a)
- shrink1 :: ( Arbitrary1 f, Arbitrary a) => f a -> [f a]
-
class
Arbitrary2
f
where
- liftArbitrary2 :: Gen a -> Gen b -> Gen (f a b)
- liftShrink2 :: (a -> [a]) -> (b -> [b]) -> f a b -> [f a b]
- arbitrary2 :: ( Arbitrary2 f, Arbitrary a, Arbitrary b) => Gen (f a b)
- shrink2 :: ( Arbitrary2 f, Arbitrary a, Arbitrary b) => f a b -> [f a b]
- data Gen a
- choose :: Random a => (a, a) -> Gen a
- chooseInt :: ( Int , Int ) -> Gen Int
- chooseInteger :: ( Integer , Integer ) -> Gen Integer
- chooseBoundedIntegral :: ( Bounded a, Integral a) => (a, a) -> Gen a
- chooseEnum :: Enum a => (a, a) -> Gen a
- chooseAny :: Random 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)
- 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
- listOf :: Gen a -> Gen [a]
- listOf1 :: Gen a -> Gen [a]
- vectorOf :: Int -> Gen a -> Gen [a]
- vector :: Arbitrary a => Int -> Gen [a]
- infiniteListOf :: Gen a -> Gen [a]
- infiniteList :: Arbitrary a => Gen [a]
- shuffle :: [a] -> Gen [a]
- sublistOf :: [a] -> Gen [a]
- orderedList :: ( Ord a, Arbitrary a) => Gen [a]
- 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
- generate :: Gen a -> IO a
- sample :: Show a => Gen a -> IO ()
- sample' :: Gen a -> IO [a]
- 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
- functionShow :: ( Show a, Read a) => (a -> c) -> a :-> c
- functionIntegral :: Integral a => (a -> b) -> a :-> b
- functionRealFrac :: RealFrac a => (a -> b) -> a :-> b
- functionBoundedEnum :: ( Eq a, Bounded a, Enum a) => (a -> b) -> a :-> b
- functionVoid :: ( forall b. void -> b) -> void :-> c
-
class
CoArbitrary
a
where
- coarbitrary :: a -> Gen b -> Gen b
- genericCoarbitrary :: ( Generic a, GCoArbitrary ( Rep a)) => a -> Gen b -> Gen b
- 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
SortedList
a =
Sorted
{
- getSorted :: [a]
-
newtype
Positive
a =
Positive
{
- getPositive :: a
-
newtype
Negative
a =
Negative
{
- getNegative :: a
-
newtype
NonZero
a =
NonZero
{
- getNonZero :: a
-
newtype
NonNegative
a =
NonNegative
{
- getNonNegative :: a
-
newtype
NonPositive
a =
NonPositive
{
- getNonPositive :: 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)]
- newtype ASCIIString = ASCIIString { }
- newtype UnicodeString = UnicodeString { }
- newtype PrintableString = PrintableString { }
- 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
- forAllShow :: Testable prop => Gen a -> (a -> String ) -> (a -> prop) -> Property
- forAllShrinkShow :: Testable prop => Gen a -> (a -> [a]) -> (a -> String ) -> (a -> prop) -> Property
- forAllBlind :: Testable prop => Gen a -> (a -> prop) -> Property
- forAllShrinkBlind :: Testable prop => Gen a -> (a -> [a]) -> (a -> prop) -> Property
- shrinking :: Testable prop => (a -> [a]) -> a -> (a -> prop) -> Property
- (==>) :: Testable prop => Bool -> prop -> Property
- data Discard = Discard
- discard :: a
- (===) :: ( Eq a, Show a) => a -> a -> Property
- (=/=) :: ( Eq a, Show a) => a -> a -> Property
- total :: NFData a => a -> Property
- ioProperty :: Testable prop => IO prop -> Property
- idempotentIOProperty :: Testable prop => IO prop -> Property
- verbose :: Testable prop => prop -> Property
- verboseShrinking :: Testable prop => prop -> Property
- noShrinking :: Testable prop => prop -> Property
- withMaxSuccess :: Testable prop => Int -> prop -> Property
- within :: Testable prop => Int -> prop -> Property
- once :: Testable prop => prop -> Property
- again :: Testable prop => prop -> Property
- mapSize :: Testable prop => ( Int -> Int ) -> 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
- tabulate :: Testable prop => String -> [ String ] -> prop -> Property
- cover :: Testable prop => Double -> Bool -> String -> prop -> Property
- coverTable :: Testable prop => String -> [( String , Double )] -> prop -> Property
- checkCoverage :: Testable prop => prop -> Property
- checkCoverageWith :: Testable prop => Confidence -> prop -> Property
- data Confidence = Confidence { }
- stdConfidence :: Confidence
- labelledExamples :: Testable prop => prop -> IO ()
- labelledExamplesWith :: Testable prop => Args -> prop -> IO ()
- labelledExamplesWithResult :: Testable prop => Args -> prop -> IO Result
- labelledExamplesResult :: Testable prop => prop -> IO Result
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
.
If you want to get the counterexample as a Haskell value, rather than just printing it, try the quickcheck-with-counterexamples package.
Args specifies arguments to the QuickCheck driver
Constructors
Args | |
Fields
|
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
|
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
Note: for technical reasons, the test case is printed out
after
the property is tested. To debug a property that goes into an
infinite loop, use
within
to add a timeout instead.
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
.
Note: for technical reasons, the test case is printed out
after
the property is tested. To debug a property that goes into an
infinite loop, use
within
to add a timeout instead.
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
.
Note: for technical reasons, the test case is printed out
after
the property is tested. To debug a property that goes into an
infinite loop, use
within
to add a timeout instead.
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
.
Note: for technical reasons, the test case is printed out
after
the property is tested. To debug a property that goes into an
infinite loop, use
within
to add a timeout instead.
Testing all properties in a module
These functions test all properties in the current module, using
Template Haskell. You need to have a
{-# LANGUAGE TemplateHaskell #-}
pragma in your module for any of these to work.
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 []
.
The
Arbitrary
typeclass: generation of random values
class Arbitrary a where Source #
Random generation and shrinking of values.
QuickCheck provides
Arbitrary
instances for most types in
base
,
except those which incur extra dependencies.
For a wider range of
Arbitrary
instances see the
quickcheck-instances
package.
Minimal complete definition
Methods
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
x
Nil
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
Helper functions for implementing
shrink
genericShrink :: ( Generic a, RecursivelyShrink ( Rep a), GSubterms ( Rep a) a) => a -> [a] Source #
Shrink a term to any of its immediate subterms, and also recursively shrink all subterms.
subterms :: ( Generic a, GSubterms ( Rep a) a) => a -> [a] Source #
All immediate subterms of a term.
recursivelyShrink :: ( Generic a, RecursivelyShrink ( Rep a)) => a -> [a] Source #
Recursively shrink all immediate subterms.
shrinkNothing :: a -> [a] Source #
Returns no shrinking alternatives.
shrinkList :: (a -> [a]) -> [a] -> [[a]] Source #
Shrink a list of values given a shrinking function for individual values.
shrinkMap :: Arbitrary a => (a -> b) -> (b -> a) -> b -> [b] Source #
Map a shrink function to another domain. This is handy if your data type has special invariants, but is almost isomorphic to some other type.
shrinkOrderedList :: (Ord a, Arbitrary a) => [a] -> [[a]] shrinkOrderedList = shrinkMap sort id shrinkSet :: (Ord a, Arbitrary a) => Set a -> Set [a] shrinkSet = shrinkMap fromList toList
shrinkMapBy :: (a -> b) -> (b -> a) -> (a -> [a]) -> b -> [b] Source #
Non-overloaded version of
shrinkMap
.
shrinkIntegral :: Integral a => a -> [a] Source #
Shrink an integral number.
shrinkRealFrac :: RealFrac a => a -> [a] Source #
Shrink a fraction, preferring numbers with smaller
numerators or denominators. See also
shrinkDecimal
.
shrinkDecimal :: RealFrac a => a -> [a] Source #
Shrink a real number, preferring numbers with shorter
decimal representations. See also
shrinkRealFrac
.
Lifting of
Arbitrary
to unary and binary type constructors
class Arbitrary1 f where Source #
Lifting of the
Arbitrary
class to unary type constructors.
Minimal complete definition
Methods
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.
Minimal complete definition
Methods
liftArbitrary2 :: Gen a -> Gen b -> Gen (f a b) Source #
liftShrink2 :: (a -> [a]) -> (b -> [b]) -> f a b -> [f a b] Source #
Instances
Arbitrary2 Either Source # | |
Defined in Test.QuickCheck.Arbitrary |
|
Arbitrary2 (,) Source # | |
Defined in Test.QuickCheck.Arbitrary Methods liftArbitrary2 :: Gen a -> Gen b -> Gen (a, b) Source # liftShrink2 :: (a -> [a]) -> (b -> [b]) -> (a, b) -> [(a, b)] Source # |
|
Arbitrary2 ( Const :: Type -> Type -> Type ) Source # | |
Defined in Test.QuickCheck.Arbitrary |
|
Arbitrary2 ( Constant :: Type -> Type -> Type ) Source # | |
Defined in Test.QuickCheck.Arbitrary |
arbitrary2 :: ( Arbitrary2 f, Arbitrary a, Arbitrary b) => Gen (f a b) Source #
The
Gen
monad: combinators for building random generators
A generator for values of type
a
.
The third-party packages
QuickCheck-GenT
and
quickcheck-transformer
provide monad transformer versions of
Gen
.
Generator combinators
choose :: Random a => (a, a) -> Gen a Source #
Generates a random element in the given inclusive range.
For integral and enumerated types, the specialised variants of
choose
below run much quicker.
chooseBoundedIntegral :: ( Bounded a, Integral a) => (a, a) -> Gen a Source #
A fast implementation of
choose
for bounded integral types.
chooseEnum :: Enum a => (a, a) -> Gen a Source #
A fast implementation of
choose
for enumerated types.
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
.
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
.
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
.
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.
Generators for lists
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.
infiniteList :: Arbitrary a => Gen [a] Source #
Generates an infinite list.
Generators for particular types
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.
Running generators
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
.
Debugging generators
sample :: Show a => Gen a -> IO () Source #
Generates some example values and prints them to
stdout
.
The
Function
typeclass: generation of random shrinkable, showable functions
Example of use:
>>>
:{
>>>
let prop :: Fun String Integer -> Bool
>>>
prop (Fun _ f) = f "monkey" == f "banana" || f "banana" == f "elephant"
>>>
:}
>>>
quickCheck prop
*** Failed! Falsified (after 3 tests and 134 shrinks): {"elephant"->1, "monkey"->1, _->0}
To generate random values of type
,
you must have an instance
Fun
a b
.
If your type has a
Function
a
Show
instance, you can use
functionShow
to write the instance; otherwise,
use
functionMap
to give a bijection between your type and a type that is already an instance of
Function
.
See the
instance for an example of the latter.
Function
[a]
For more information, see the paper "Shrinking and showing functions" by Koen Claessen.
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
.
Minimal complete definition
Nothing
Methods
Instances
functionMap :: Function b => (a -> b) -> (b -> a) -> (a -> c) -> a :-> c Source #
functionIntegral :: Integral a => (a -> b) -> a :-> b Source #
functionRealFrac :: RealFrac a => (a -> b) -> a :-> b Source #
functionVoid :: ( forall b. void -> b) -> void :-> c Source #
The
CoArbitrary
typeclass: generation of functions the old-fashioned way
class CoArbitrary a where Source #
Used for random generation of functions.
You should consider using
Fun
instead, which
can show the generated functions as strings.
If you are using a recent GHC, there is a default definition of
coarbitrary
using
genericCoarbitrary
, so if your type has a
Generic
instance it's enough to say
instance CoArbitrary MyType
You should only use
genericCoarbitrary
for data types where
equality is structural, i.e. if you can't have two different
representations of the same value. An example where it's not
safe is sets implemented using binary search trees: the same
set can be represented as several different trees.
Here you would have to explicitly define
coarbitrary s = coarbitrary (toList s)
.
Minimal complete definition
Nothing
Methods
coarbitrary :: a -> Gen b -> Gen b Source #
Used to generate a function of type
a -> b
.
The first argument is a value, the second a generator.
You should use
variant
to perturb the random generator;
the goal is that different values for the first argument will
lead to different calls to
variant
. An example will help:
instance CoArbitrary a => CoArbitrary [a] where coarbitrary [] =variant
0 coarbitrary (x:xs) =variant
1 . coarbitrary (x,xs)
Instances
genericCoarbitrary :: ( Generic a, GCoArbitrary ( Rep a)) => a -> Gen b -> Gen b Source #
Generic CoArbitrary implementation.
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
These types do things such as restricting the kind of test data that can be generated. They can be pattern-matched on in properties as a stylistic alternative to using explicit quantification.
Examples:
-- Functions cannot be shown (but seeFunction
) prop_TakeDropWhile (Blind
p) (xs :: [A
]) = takeWhile p xs ++ dropWhile p xs == xs
prop_TakeDrop (NonNegative
n) (xs :: [A
]) = take n xs ++ drop n xs == xs
-- cycle does not work for empty lists prop_Cycle (NonNegative
n) (NonEmpty
(xs :: [A
])) = take n (cycle xs) == take n (xs ++ cycle xs)
-- Instead offorAll
orderedList
prop_Sort (Ordered
(xs :: [OrdA
])) = sort xs == xs
Blind x
: as x, but x does not have to be in the
Show
class.
Instances
Fixed x
: as x, but will not be shrunk.
Instances
newtype OrderedList a Source #
Ordered xs
: guarantees that xs is ordered.
Constructors
Ordered | |
Fields
|
Instances
newtype NonEmptyList a Source #
NonEmpty xs
: guarantees that xs is non-empty.
Constructors
NonEmpty | |
Fields
|
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! Falsified (after 1 test and 14 shrinks): "bbbbbbbbbb" ++ ...
Constructors
InfiniteList | |
Fields
|
Instances
Show a => Show ( InfiniteList a) Source # | |
Defined in Test.QuickCheck.Modifiers |
|
Arbitrary a => Arbitrary ( InfiniteList a) Source # | |
Defined in Test.QuickCheck.Modifiers Methods arbitrary :: Gen ( InfiniteList a) Source # shrink :: InfiniteList a -> [ InfiniteList a] Source # |
newtype SortedList a Source #
Sorted xs
: guarantees that xs is sorted.
Instances
Positive x
: guarantees that
x > 0
.
Constructors
Positive | |
Fields
|
Instances
Functor Positive Source # | |
Enum a => Enum ( Positive a) Source # | |
Defined in Test.QuickCheck.Modifiers Methods succ :: Positive a -> Positive a Source # pred :: Positive a -> Positive a Source # toEnum :: Int -> Positive a Source # fromEnum :: Positive a -> Int Source # enumFrom :: Positive a -> [ Positive a] Source # enumFromThen :: Positive a -> Positive a -> [ Positive a] Source # enumFromTo :: Positive a -> Positive a -> [ Positive a] Source # enumFromThenTo :: Positive a -> Positive a -> Positive a -> [ Positive a] Source # |
|
Eq a => Eq ( Positive a) Source # | |
Ord a => Ord ( Positive a) Source |