QuickCheck-2.7.6: Automatic testing of Haskell programs

Safe HaskellSafe

Test.QuickCheck.Property

Contents

Description

Combinators for constructing properties.

Synopsis

Property and Testable types

newtype Property Source

The type of properties.

Backwards combatibility note: in older versions of QuickCheck Property was a type synonym for Gen Prop, so you could mix and match property combinators and Gen 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 Property. If you have a Property where you need a Gen a, simply wrap the property combinator inside a return to get a Gen Property, and all should be well.

Constructors

MkProperty 

Fields

unProperty :: Gen Prop
 

Instances

class Testable prop whereSource

The class of things which can be tested, i.e. turned into a property.

Methods

property :: prop -> PropertySource

Convert the thing to a property.

exhaustive :: prop -> BoolSource

If true, the property will only be tested once. However, if used inside a quantifier, it will be tested normally.

data Discard Source

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

Constructors

Discard 

Instances

morallyDubiousIOProperty :: Testable prop => IO prop -> PropertySource

Deprecated: Use ioProperty instead

Do I/O inside a property. This can obviously lead to unrepeatable testcases, so use with care.

ioProperty :: Testable prop => IO prop -> PropertySource

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.

Exception handling

protect :: (AnException -> a) -> IO a -> IO aSource

Type Prop

newtype Prop Source

Constructors

MkProp 

Fields

unProp :: Rose Result
 

Instances

type Rose

data Rose a Source

Constructors

MkRose a [Rose a] 
IORose (IO (Rose a)) 

onRose :: (a -> [Rose a] -> Rose a) -> Rose a -> Rose aSource

Result type

data Callback Source

Different kinds of callbacks

Constructors

PostTest CallbackKind (State -> Result -> IO ())

Called just after a test

PostFinalFailure CallbackKind (State -> Result -> IO ())

Called with the final failing test-case

data CallbackKind Source

Constructors

Counterexample

Affected by the verbose combinator

NotCounterexample

Not affected by the verbose combinator

data Result Source

The result of a single test.

Constructors

MkResult 

Fields

ok :: Maybe Bool

result of the test case; Nothing = discard

expect :: Bool

indicates what the expected result of the property is

reason :: String

a message indicating what went wrong

theException :: Maybe AnException

the exception thrown, if any

abort :: Bool

if True, the test should not be repeated

stamp :: [(String, Int)]

the collected values for this test case

callbacks :: [Callback]

the callbacks for this test case

Instances

Lifting and mapping functions

mapResult :: Testable prop => (Result -> Result) -> prop -> PropertySource

mapProp :: Testable prop => (Prop -> Prop) -> prop -> PropertySource

Property combinators

mapSize :: Testable prop => (Int -> Int) -> prop -> PropertySource

Changes the maximum test case size for a property.

shrinkingSource

Arguments

:: Testable prop 
=> (a -> [a])

shrink-like function.

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

noShrinking :: Testable prop => prop -> PropertySource

Disables shrinking for a property altogether.

callback :: Testable prop => Callback -> prop -> PropertySource

Adds a callback

counterexample :: Testable prop => String -> prop -> PropertySource

Adds the given string to the counterexample.

printTestCase :: Testable prop => String -> prop -> PropertySource

Deprecated: Use counterexample instead

Adds the given string to the counterexample.

whenFail :: Testable prop => IO () -> prop -> PropertySource

Performs an IO action after the last failure of a property.

whenFail' :: Testable prop => IO () -> prop -> PropertySource

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.

verbose :: Testable prop => prop -> PropertySource

Prints out the generated testcase every time the property is tested. Only variables quantified over inside the verbose are printed.

expectFailure :: Testable prop => prop -> PropertySource

Indicates that a property is supposed to fail. QuickCheck will report an error if it does not fail.

once :: Testable prop => prop -> PropertySource

Modifies a property so that it only will be tested once.

label :: Testable prop => String -> prop -> PropertySource

Attaches a label to a property. This is used for reporting test case distribution.

collect :: (Show a, Testable prop) => a -> prop -> PropertySource

Labels a property with a value:

 collect x = label (show x)

classifySource

Arguments

:: Testable prop 
=> Bool

True if the test case should be labelled.

-> String

Label.

-> prop 
-> Property 

Conditionally labels test case.

coverSource

Arguments

:: Testable prop 
=> Bool

True if the test case belongs to the class.

-> 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 the test cases belong to the given class.

(==>) :: Testable prop => Bool -> prop -> PropertySource

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.

within :: Testable prop => Int -> prop -> PropertySource

Considers a property failed if it does not complete within the given number of microseconds.

forAll :: (Show a, Testable prop) => Gen a -> (a -> prop) -> PropertySource

Explicit universal quantification: uses an explicitly given test case generator.

forAllShrink :: (Show a, Testable prop) => Gen a -> (a -> [a]) -> (a -> prop) -> PropertySource

Like forAll, but tries to shrink the argument for failing test cases.

(.&.) :: (Testable prop1, Testable prop2) => prop1 -> prop2 -> PropertySource

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 -> PropertySource

Conjunction: p1 .&&. p2 passes if both p1 and p2 pass.

conjoin :: Testable prop => [prop] -> PropertySource

Take the conjunction of several properties.

(.||.) :: (Testable prop1, Testable prop2) => prop1 -> prop2 -> PropertySource

Disjunction: p1 .||. p2 passes unless p1 and p2 simultaneously fail.

disjoin :: Testable prop => [prop] -> PropertySource

Take the disjunction of several properties.

(===) :: (Eq a, Show a) => a -> a -> PropertySource

Like ==, but prints a counterexample when it fails.