QuickCheck-2.9.1: Automatic testing of Haskell programs

Safe HaskellSafe
LanguageHaskell98

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

class Testable prop where Source #

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

Minimal complete definition

property

Methods

property :: prop -> Property Source #

Convert the thing to a property.

data Discard Source #

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

Constructors

Discard 

morallyDubiousIOProperty :: Testable prop => IO prop -> Property Source #

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 -> Property Source #

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

For more advanced monadic testing you may want to look at Test.QuickCheck.Monadic.

Note that if you use ioProperty on a property of type IO Bool, or more generally a property that does no quantification, the property will only be executed once. To test the property repeatedly you must use the again combinator.

Exception handling

protect :: (AnException -> a) -> IO a -> IO a Source #

Type Prop

newtype Prop Source #

Constructors

MkProp 

Fields

Instances

type Rose

data Rose a Source #

Constructors

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

Instances

Monad Rose Source # 

Methods

(>>=) :: Rose a -> (a -> Rose b) -> Rose b #

(>>) :: Rose a -> Rose b -> Rose b #

return :: a -> Rose a #

fail :: String -> Rose a #

Functor Rose Source # 

Methods

fmap :: (a -> b) -> Rose a -> Rose b #

(<$) :: a -> Rose b -> Rose a #

Applicative Rose Source # 

Methods

pure :: a -> Rose a #

(<*>) :: Rose (a -> b) -> Rose a -> Rose b #

(*>) :: Rose a -> Rose b -> Rose b #

(<*) :: Rose a -> Rose b -> Rose a #

reduceRose :: Rose Result -> IO (Rose Result) Source #

Execute the IORose bits of a rose tree, returning a tree constructed by MkRose.

onRose :: (a -> [Rose a] -> Rose a) -> Rose a -> Rose a Source #

Apply a function to the outermost MkRose constructor of a rose tree. The function must be total!

protectRose :: IO (Rose Result) -> IO (Rose Result) Source #

Wrap a rose tree in an exception handler.

protectResults :: Rose Result -> Rose Result Source #

Wrap all the Results in a rose tree in exception handlers.

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

Lifting and mapping functions

mapResult :: Testable prop => (Result -> Result) -> prop -> Property Source #

mapTotalResult :: Testable prop => (Result -> Result) -> prop -> Property Source #

mapProp :: Testable prop => (Prop -> Prop) -> prop -> Property Source #

Property combinators

mapSize :: Testable prop => (Int -> Int) -> prop -> Property Source #

Changes the maximum test case size for a property.

shrinking Source #

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 -> Property Source #

Disables shrinking for a property altogether.

callback :: Testable prop => Callback -> prop -> Property Source #

Adds a callback

counterexample :: Testable prop => String -> prop -> Property Source #

Adds the given string to the counterexample.

printTestCase :: Testable prop => String -> prop -> Property Source #

Deprecated: Use counterexample instead

Adds the given string to the counterexample.

whenFail :: Testable prop => IO () -> prop -> Property Source #

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

whenFail' :: Testable prop => IO () -> prop -> Property Source #

Performs an IO action every time a property fails. Thus, if shrinking is done, this can be used to keep track of the failures along the way.

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.

expectFailure :: Testable prop => prop -> Property Source #

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

once :: Testable prop => prop -> Property Source #

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

again :: Testable prop => prop -> Property Source #

Undoes the effect of once.

label :: Testable prop => String -> prop -> Property Source #

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

collect :: (Show a, Testable prop) => a -> prop -> Property Source #

Labels a property with a value:

collect x = label (show x)

classify Source #

Arguments

:: Testable prop 
=> Bool

True if the test case should be labelled.

-> String

Label.

-> prop 
-> Property 

Conditionally labels test case.

cover Source #

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 successful test cases belong to the given class. Discarded tests (i.e. ones with a false precondition) do not affect coverage.

(==>) :: 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.

within :: Testable prop => Int -> prop -> Property Source #

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

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

conjoin :: Testable prop => [prop] -> Property Source #

Take the conjunction of several properties.

(.||.) :: (Testable prop1, Testable prop2) => prop1 -> prop2 -> Property infixr 1 Source #

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

disjoin :: Testable prop => [prop] -> Property Source #

Take the disjunction of several properties.

(===) :: (Eq a, Show a) => a -> a -> Property infix 4 Source #

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