Safe Haskell | None |
---|---|
Language | Haskell2010 |
This module extends QuickCheck so that it returns counterexamples
as Haskell values instead of just printing them. To use it, import
this module instead of Test.QuickCheck. The API and functionality
are the same as normal QuickCheck; the only difference is that the
return types of quickCheck
(and related functions)
include a counterexample.
Note that this module re-exports most functions from Test.QuickCheck. Those functions are not documented here! You will need to refer to the main Test.QuickCheck documentation when using this module.
Here is an example of getting counterexamples. Suppose we have the following property:
prop_reverse_append :: [Int] -> [Int] -> Property prop_reverse_append xs ys = reverse (xs++ys) === reverse xs ++ reverse ys
If we look the type of quickCheck prop_reverse_append
, we see that
it returns a counterexample:
>>>
:t quickCheck prop_reverse_append
quickCheck prop_reverse_append :: IO (Maybe ([Int] :&: [Int] :&: ()))
The Maybe
is there because quickCheck
will return Nothing
if the
property succeeds; :&:
is a datatype of pairs.
If we run QuickCheck, we can get the counterexample as a normal Haskell value:
>>>
Just (xs :&: ys :&: ()) <- quickCheck prop_reverse_append
*** Failed! Falsifiable (after 5 tests and 4 shrinks): [0] [1] [1,0] /= [0,1]
>>>
:t xs
xs :: [Int]
>>>
xs
[0]
>>>
ys
[1]
Here is how this module's API differs from normal QuickCheck, in more detail:
- The
Testable
class now has an associated typeCounterexample
which describes the counterexample.Property
is now a synonym for
, wherePropertyOf
()
represents a property with an associated counterexamplePropertyOf
cexcex
. The QuickCheck property combinators preserve the counterexample, by returningPropertyOf
instead ofProperty
. quickCheck
and related functions return a
.Counterexample
prop- Finally, there are a couple of new combinators, documented below.
- newtype PropertyOf cex = MkProperty {
- unProperty :: (cex -> IO ()) -> Property
- type Property = PropertyOf ()
- type PropertyFrom prop = PropertyOf (Counterexample prop)
- class Testable prop => Testable prop where
- type Counterexample prop
- data a :&: b = a :&: b
- typedCounterexample :: Testable prop => a -> prop -> PropertyOf (a :&: Counterexample prop)
- onProperty :: Testable prop => (Property -> Property) -> prop -> PropertyFrom prop
- quickCheck :: Testable prop => prop -> IO (Maybe (Counterexample prop))
- quickCheckWith :: Testable prop => Args -> prop -> IO (Maybe (Counterexample prop))
- quickCheckResult :: Testable prop => prop -> IO (Maybe (Counterexample prop), Result)
- quickCheckWithResult :: Testable prop => Args -> prop -> IO (Maybe (Counterexample prop), Result)
- verboseCheck :: Testable prop => prop -> IO (Maybe (Counterexample prop))
- verboseCheckWith :: Testable prop => Args -> prop -> IO (Maybe (Counterexample prop))
- verboseCheckResult :: Testable prop => prop -> IO (Maybe (Counterexample prop), Result)
- verboseCheckWithResult :: Testable prop => Args -> prop -> IO (Maybe (Counterexample prop), Result)
- polyQuickCheck :: Name -> ExpQ
- polyVerboseCheck :: Name -> ExpQ
- forAll :: (Testable prop, Show a) => Gen a -> (a -> prop) -> PropertyOf (a :&: Counterexample prop)
- forAllShrink :: (Testable prop, Show a) => Gen a -> (a -> [a]) -> (a -> prop) -> PropertyOf (a :&: Counterexample prop)
- shrinking :: Testable prop => (a -> [a]) -> a -> (a -> prop) -> PropertyFrom prop
- (==>) :: Testable prop => Bool -> prop -> PropertyFrom prop
- (===) :: (Eq a, Show a) => a -> a -> Property
- ioProperty :: Testable prop => IO prop -> PropertyFrom prop
- verbose :: Testable prop => prop -> PropertyFrom prop
- once :: Testable prop => prop -> PropertyFrom prop
- again :: Testable prop => prop -> PropertyFrom prop
- within :: Testable prop => Int -> prop -> PropertyFrom prop
- noShrinking :: Testable prop => prop -> PropertyFrom prop
- counterexample :: Testable prop => String -> prop -> PropertyFrom prop
- whenFail :: Testable prop => IO () -> prop -> PropertyFrom prop
- whenFail' :: Testable prop => IO () -> prop -> PropertyFrom prop
- expectFailure :: Testable prop => prop -> PropertyFrom prop
- label :: Testable prop => String -> prop -> PropertyFrom prop
- collect :: (Show a, Testable prop) => a -> prop -> PropertyFrom prop
- classify :: Testable prop => Bool -> String -> prop -> PropertyFrom prop
- cover :: Testable prop => Bool -> Int -> String -> prop -> PropertyFrom prop
- mapSize :: Testable prop => (Int -> Int) -> prop -> PropertyFrom prop
- module Test.QuickCheck
The PropertyOf
type and Testable
typeclass
newtype PropertyOf cex Source #
A property. cex
is the type of counterexamples to the property.
Note that there is a Functor
instance, which is useful when you
want to manipulate the counterexample, e.g., to change its type.
For example, when some branches of your property produce a
counterexample and other branches do not, the types will not match
up, but using fmap
you can make the counterexample be a Maybe
.
MkProperty | |
|
Functor PropertyOf Source # | |
Testable (PropertyOf cex) Source # | |
Testable (PropertyOf cex) Source # | |
type Counterexample (PropertyOf cex) Source # | |
type Property = PropertyOf () Source #
A property which doesn't produce a counterexample.
type PropertyFrom prop = PropertyOf (Counterexample prop) Source #
A type synonym for the property which comes from a particular Testable
instance.
class Testable prop => Testable prop where Source #
The class of properties, i.e. types which QuickCheck knows how to test.
type Counterexample prop Source #
The type of counterexamples to the property.
property :: prop -> PropertyFrom prop Source #
Convert the property to a PropertyOf
.
New functionality which is not in QuickCheck
typedCounterexample :: Testable prop => a -> prop -> PropertyOf (a :&: Counterexample prop) Source #
Add a value to the counterexample.
onProperty :: Testable prop => (Property -> Property) -> prop -> PropertyFrom prop Source #
Lift an ordinary QuickCheck property combinator to one with counterexamples.
The standard QuickCheck combinators, updated to return counterexamples
quickCheck :: Testable prop => prop -> IO (Maybe (Counterexample prop)) Source #
See quickCheck
in Test.QuickCheck.
quickCheckWith :: Testable prop => Args -> prop -> IO (Maybe (Counterexample prop)) Source #
See quickCheckWith
in Test.QuickCheck.
quickCheckResult :: Testable prop => prop -> IO (Maybe (Counterexample prop), Result) Source #
See quickCheckResult
in Test.QuickCheck.
quickCheckWithResult :: Testable prop => Args -> prop -> IO (Maybe (Counterexample prop), Result) Source #
See quickCheckWithResult
in Test.QuickCheck.
verboseCheck :: Testable prop => prop -> IO (Maybe (Counterexample prop)) Source #
See verboseCheck
in Test.QuickCheck.
verboseCheckWith :: Testable prop => Args -> prop -> IO (Maybe (Counterexample prop)) Source #
See verboseCheckWith
in Test.QuickCheck.
verboseCheckResult :: Testable prop => prop -> IO (Maybe (Counterexample prop), Result) Source #
See verboseCheckResult
in Test.QuickCheck.
verboseCheckWithResult :: Testable prop => Args -> prop -> IO (Maybe (Counterexample prop), Result) Source #
polyQuickCheck :: Name -> ExpQ Source #
See polyQuickCheck
in Test.QuickCheck.
polyVerboseCheck :: Name -> ExpQ Source #
See polyVerboseCheck
in Test.QuickCheck.
forAll :: (Testable prop, Show a) => Gen a -> (a -> prop) -> PropertyOf (a :&: Counterexample prop) Source #
See forAll
in Test.QuickCheck.
forAllShrink :: (Testable prop, Show a) => Gen a -> (a -> [a]) -> (a -> prop) -> PropertyOf (a :&: Counterexample prop) Source #
See forAllShrink
in Test.QuickCheck.
shrinking :: Testable prop => (a -> [a]) -> a -> (a -> prop) -> PropertyFrom prop Source #
See shrinking
in Test.QuickCheck.
(==>) :: Testable prop => Bool -> prop -> PropertyFrom prop infixr 0 Source #
See ==>
in Test.QuickCheck.
ioProperty :: Testable prop => IO prop -> PropertyFrom prop Source #
See ioProperty
in Test.QuickCheck.
verbose :: Testable prop => prop -> PropertyFrom prop Source #
See verbose
in Test.QuickCheck.
once :: Testable prop => prop -> PropertyFrom prop Source #
See once
in Test.QuickCheck.
again :: Testable prop => prop -> PropertyFrom prop Source #
See again
in Test.QuickCheck.
within :: Testable prop => Int -> prop -> PropertyFrom prop Source #
See within
in Test.QuickCheck.
noShrinking :: Testable prop => prop -> PropertyFrom prop Source #
See noShrinking
in Test.QuickCheck.
counterexample :: Testable prop => String -> prop -> PropertyFrom prop Source #
See counterexample
in Test.QuickCheck.
whenFail :: Testable prop => IO () -> prop -> PropertyFrom prop Source #
See whenFail
in Test.QuickCheck.
whenFail' :: Testable prop => IO () -> prop -> PropertyFrom prop Source #
See whenFail'
in Test.QuickCheck.
expectFailure :: Testable prop => prop -> PropertyFrom prop Source #
See expectFailure
in Test.QuickCheck.
label :: Testable prop => String -> prop -> PropertyFrom prop Source #
See label
in Test.QuickCheck.
collect :: (Show a, Testable prop) => a -> prop -> PropertyFrom prop Source #
See collect
in Test.QuickCheck.
classify :: Testable prop => Bool -> String -> prop -> PropertyFrom prop Source #
See classify
in Test.QuickCheck.
cover :: Testable prop => Bool -> Int -> String -> prop -> PropertyFrom prop Source #
See cover
in Test.QuickCheck.
mapSize :: Testable prop => (Int -> Int) -> prop -> PropertyFrom prop Source #
See mapSize
in Test.QuickCheck.
module Test.QuickCheck