QuickCheck-2.4.2: Automatic testing of Haskell programs

Safe HaskellSafe-Infered

Test.QuickCheck

Contents

Synopsis

Running tests

quickCheck :: Testable prop => prop -> IO ()Source

Tests a property and prints the results to stdout.

data Args Source

Args specifies arguments to the QuickCheck driver

Constructors

Args 

Fields

replay :: Maybe (StdGen, Int)

should we replay a previous test?

maxSuccess :: Int

maximum number of successful tests before succeeding

maxDiscard :: Int

maximum number of discarded tests before giving up

maxSize :: Int

size to use for the biggest test cases

chatty :: Bool

whether to print anything

Instances

data Result Source

Result represents the test result

Constructors

Success 

Fields

numTests :: Int

number of tests performed

number of tests performed

number of successful tests performed

number of successful tests performed

labels :: [(String, Int)]

labels and frequencies found during all successful tests

labels and frequencies found during all successful tests

labels and frequencies found during all tests

labels and frequencies found during all tests

output :: String

printed output

printed output

printed output

printed output

GaveUp 

Fields

numTests :: Int

number of tests performed

number of tests performed

number of successful tests performed

number of successful tests performed

labels :: [(String, Int)]

labels and frequencies found during all successful tests

labels and frequencies found during all successful tests

labels and frequencies found during all tests

labels and frequencies found during all tests

output :: String

printed output

printed output

printed output

printed output

Failure 

Fields

numTests :: Int

number of tests performed

number of tests performed

number of successful tests performed

number of successful tests performed

numShrinks :: Int

number of successful shrinking steps performed

usedSeed :: StdGen

what seed was used

usedSize :: Int

what was the test size

reason :: String

what was the reason

labels :: [(String, Int)]

labels and frequencies found during all successful tests

labels and frequencies found during all successful tests

labels and frequencies found during all tests

labels and frequencies found during all tests

output :: String

printed output

printed output

printed output

printed output

NoExpectedFailure 

Fields

numTests :: Int

number of tests performed

number of tests performed

number of successful tests performed

number of successful tests performed

labels :: [(String, Int)]

labels and frequencies found during all successful tests

labels and frequencies found during all successful tests

labels and frequencies found during all tests

labels and frequencies found during all tests

output :: String

printed output

printed output

printed output

printed output

Instances

stdArgs :: ArgsSource

stdArgs are the default test arguments used

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 ResultSource

Tests a property, using test arguments, produces a test result, and prints the results to stdout.

quickCheckResult :: Testable prop => prop -> IO ResultSource

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 ResultSource

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 ResultSource

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.

verbose :: Testable prop => prop -> PropertySource

Prints out the generated testcase every time the property is tested, like verboseCheck from QuickCheck 1. Only variables quantified over inside the verbose are printed.

Random generation

data Gen a Source

Instances

Generator combinators

sized :: (Int -> Gen a) -> Gen aSource

Used to construct generators that depend on the size parameter.

resize :: Int -> Gen a -> Gen aSource

Overrides the size parameter. Returns a generator which uses the given size instead of the runtime-size parameter.

choose :: Random a => (a, a) -> Gen aSource

Generates a random element in the given inclusive range.

promote :: Monad m => m (Gen a) -> Gen (m a)Source

Promotes a monadic generator to a generator of monadic values.

suchThat :: Gen a -> (a -> Bool) -> Gen aSource

Generates a value that satisfies a predicate.

suchThatMaybe :: Gen a -> (a -> Bool) -> Gen (Maybe a)Source

Tries to generate a value that satisfies a predicate.

oneof :: [Gen a] -> Gen aSource

Randomly uses one of the given generators. The input list must be non-empty.

frequency :: [(Int, Gen a)] -> Gen aSource

Chooses one of the given generators, with a weighted random distribution. The input list must be non-empty.

elements :: [a] -> Gen aSource

Generates one of the given values. The input list must be non-empty.

growingElements :: [a] -> Gen aSource

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.

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.

vectorOf :: Int -> Gen a -> Gen [a]Source

Generates a list of the given length.

Generators which use Arbitrary

vector :: Arbitrary a => Int -> Gen [a]Source

Generates a list of a given length.

orderedList :: (Ord a, Arbitrary a) => Gen [a]Source

Generates an ordered list of a given length.

Generator debugging

sample :: Show a => Gen a -> IO ()Source

Generates some example values and prints them to stdout.

sample' :: Gen a -> IO [a]Source

Generates some example values.

Arbitrary and CoArbitrary classes

class Arbitrary a whereSource

Random generation and shrinking of values.

Methods

arbitrary :: Gen aSource

A generator for values of the given type.

shrink :: a -> [a]Source

Produces a (possibly) empty list of all the possible immediate shrinks of the given value.

Instances

Arbitrary Bool 
Arbitrary Char 
Arbitrary Double 
Arbitrary Float 
Arbitrary Int 
Arbitrary Int8 
Arbitrary Int16 
Arbitrary Int32 
Arbitrary Int64 
Arbitrary Integer 
Arbitrary Word 
Arbitrary Word8 
Arbitrary Word16 
Arbitrary Word32 
Arbitrary Word64 
Arbitrary () 
Arbitrary OrdC 
Arbitrary OrdB 
Arbitrary OrdA 
Arbitrary C 
Arbitrary B 
Arbitrary A 
Arbitrary a => Arbitrary [a] 
(Integral a, Arbitrary a) => Arbitrary (Ratio a) 
(RealFloat a, Arbitrary a) => Arbitrary (Complex a) 
Arbitrary a => Arbitrary (Maybe a) 
Arbitrary a => Arbitrary (Smart a) 
Arbitrary a => Arbitrary (Shrink2 a) 
(Num a, Ord a, Arbitrary a) => Arbitrary (NonNegative a) 
(Num a, Ord a, Arbitrary a) => Arbitrary (NonZero a) 
(Num a, Ord a, Arbitrary a) => Arbitrary (Positive a) 
Arbitrary a => Arbitrary (NonEmptyList a) 
(Ord a, Arbitrary a) => Arbitrary (OrderedList a) 
Arbitrary a => Arbitrary (Fixed a) 
Arbitrary a => Arbitrary (Blind a) 
(CoArbitrary a, Arbitrary b) => Arbitrary (a -> b) 
(Arbitrary a, Arbitrary b) => Arbitrary (Either a b) 
(Arbitrary a, Arbitrary b) => Arbitrary (a, b) 
(Arbitrary a, ShrinkState s a) => Arbitrary (Shrinking s a) 
(Function a, CoArbitrary a, Arbitrary b) => Arbitrary (Fun a b) 
(Function a, CoArbitrary a, Arbitrary b) => Arbitrary (:-> a b) 
(Arbitrary a, Arbitrary b, Arbitrary c) => Arbitrary (a, b, c) 
(Arbitrary a, Arbitrary b, Arbitrary c, Arbitrary d) => Arbitrary (a, b, c, d) 
(Arbitrary a, Arbitrary b, Arbitrary c, Arbitrary d, Arbitrary e) => Arbitrary (a, b, c, d, e) 

class CoArbitrary a whereSource

Used for random generation of functions.

Methods

coarbitrary :: a -> Gen c -> Gen cSource

Used to generate a function of type a -> c. The implementation should use the first argument to perturb the random generator given as the second argument. the returned generator is then used to generate the function result. You can often use variant and >< to implement coarbitrary.

Helper functions for implementing arbitrary

arbitrarySizedIntegral :: Num a => Gen aSource

Generates an integral number. The number can be positive or negative and its maximum absolute value depends on the size parameter.

arbitrarySizedFractional :: Fractional a => Gen aSource

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 aSource

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 aSource

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 aSource

Generates an element of a bounded type. The element is chosen from the entire range of the type.

Helper functions for implementing shrink

shrinkNothing :: a -> [a]Source

Returns no shrinking alternatives.

shrinkIntegral :: Integral a => a -> [a]Source

Shrink an integral number.

shrinkRealFrac :: RealFrac a => a -> [a]Source

Shrink a fraction.

Helper functions for implementing coarbitrary

variant :: Integral n => n -> Gen a -> Gen aSource

Modifies a generator using an integer seed.

(><) :: (Gen a -> Gen a) -> (Gen a -> Gen a) -> Gen a -> Gen aSource

Combine two generator perturbing functions, for example the results of calls to variant or coarbitrary.

coarbitraryIntegral :: Integral a => a -> Gen b -> Gen bSource

A coarbitrary implementation for integral numbers.

coarbitraryReal :: Real a => a -> Gen b -> Gen bSource

A coarbitrary implementation for real numbers.

coarbitraryShow :: Show a => a -> Gen b -> Gen bSource

coarbitrary helper for lazy people :-).

Type-level modifiers for changing generator behavior

newtype Blind a Source

Blind x: as x, but x does not have to be in the Show class.

Constructors

Blind a 

Instances

Enum a => Enum (Blind a) 
Eq a => Eq (Blind a) 
Integral a => Integral (Blind a) 
Num a => Num (Blind a) 
Ord a => Ord (Blind a) 
Real a => Real (Blind a) 
Show (Blind a) 
Arbitrary a => Arbitrary (Blind a) 

newtype Fixed a Source

Fixed x: as x, but will not be shrunk.

Constructors

Fixed a 

Instances

Enum a => Enum (Fixed a) 
Eq a => Eq (Fixed a) 
Integral a => Integral (Fixed a) 
Num a => Num (Fixed a) 
Ord a => Ord (Fixed a) 
Read a => Read (Fixed a) 
Real a => Real (Fixed a) 
Show a => Show (Fixed a) 
Arbitrary a => Arbitrary (Fixed a) 

newtype OrderedList a Source

Ordered xs: guarantees that xs is ordered.

Constructors

Ordered [a] 

Instances

Eq a => Eq (OrderedList a) 
Ord a => Ord (OrderedList a) 
Read a => Read (OrderedList a) 
Show a => Show (OrderedList a) 
(Ord a, Arbitrary a) => Arbitrary (OrderedList a) 

newtype NonEmptyList a Source

NonEmpty xs: guarantees that xs is non-empty.

Constructors

NonEmpty [a] 

Instances

newtype Positive a Source

Positive x: guarantees that x > 0.

Constructors

Positive a 

Instances

Enum a => Enum (Positive a) 
Eq a => Eq (Positive a) 
Integral a => Integral (Positive a) 
Num a => Num (Positive a) 
Ord a => Ord (Positive a) 
Read a => Read (Positive a) 
Real a => Real (Positive a) 
Show a => Show (Positive a) 
(Num a, Ord a, Arbitrary a) => Arbitrary (Positive a) 

newtype NonZero a Source

NonZero x: guarantees that x /= 0.

Constructors

NonZero a 

Instances

Enum a => Enum (NonZero a) 
Eq a => Eq (NonZero a) 
Integral a => Integral (NonZero a) 
Num a => Num (NonZero a) 
Ord a => Ord (NonZero a) 
Read a => Read (NonZero a) 
Real a => Real (NonZero a) 
Show a => Show (NonZero a) 
(Num a, Ord a, Arbitrary a) => Arbitrary (NonZero a) 

newtype NonNegative a Source

NonNegative x: guarantees that x >= 0.

Constructors

NonNegative a 

Instances

Enum a => Enum (NonNegative a) 
Eq a => Eq (NonNegative a) 
Integral a => Integral (NonNegative a) 
Num a => Num (NonNegative a) 
Ord a => Ord (NonNegative a) 
Read a => Read (NonNegative a) 
Real a => Real (NonNegative a) 
Show a => Show (NonNegative a) 
(Num a, Ord a, Arbitrary a) => Arbitrary (NonNegative a) 

data Smart a Source

Smart _ x: tries a different order when shrinking.

Constructors

Smart Int a 

Instances

Show a => Show (Smart a) 
Arbitrary a => Arbitrary (Smart a) 

newtype Shrink2 a Source

Shrink2 x: allows 2 shrinking steps at the same time when shrinking x

Constructors

Shrink2 a 

Instances

Enum a => Enum (Shrink2 a) 
Eq a => Eq (Shrink2 a) 
Integral a => Integral (Shrink2 a) 
Num a => Num (Shrink2 a) 
Ord a => Ord (Shrink2 a) 
Read a => Read (Shrink2 a) 
Real a => Real (Shrink2 a) 
Show a => Show (Shrink2 a) 
Arbitrary a => Arbitrary (Shrink2 a) 

data Shrinking s a Source

Shrinking _ x: allows for maintaining a state during shrinking.

Constructors

Shrinking s a 

Instances

Show a => Show (Shrinking s a) 
(Arbitrary a, ShrinkState s a) => Arbitrary (Shrinking s a) 

class ShrinkState s a whereSource

Methods

shrinkInit :: a -> sSource

shrinkState :: a -> s -> [(a, s)]Source

Properties

data Prop Source

Instances

class Testable prop whereSource

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

Methods

property :: prop -> PropertySource

Instances

Testable Bool 
Testable () 
Testable Result 
Testable Prop 
Testable prop => Testable (Gen prop) 
(Arbitrary a, Show a, Testable prop) => Testable (a -> prop) 

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.

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

Implication for properties: The resulting property holds if the first argument is False, or if the given property holds.

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.

Experimental combinators for conjunction and disjunction

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

Handling failure

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

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

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

Prints a message to the terminal as part of the counterexample.

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.

expectFailure :: Testable prop => prop -> PropertySource

Modifies a property so that it is expected to fail for some test cases.

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

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

Test distribution

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.

Text formatting

newtype Str Source

Constructors

MkStr String 

Instances

ranges :: (Show a, Integral a) => a -> a -> StrSource