Safe Haskell | Safe |
---|---|
Language | Haskell2010 |
This module implements a simplified, pure version of Test.Quickcheck's quickCheck functionality.
- quickCheck :: STestable prop => QCGen -> prop -> String
- quickCheckResult :: STestable prop => QCGen -> prop -> Result
- quickCheckWith :: STestable prop => Args -> QCGen -> prop -> String
- quickCheckWithResult :: STestable prop => Args -> QCGen -> prop -> Result
- class STestable prop
- (==>) :: STestable prop => Bool -> prop -> SProperty
- (.||.) :: (STestable prop2, STestable prop1) => prop1 -> prop2 -> SProperty
- (.&&.) :: (STestable prop2, STestable prop1) => prop1 -> prop2 -> SProperty
- (.&.) :: (STestable prop2, STestable prop1) => prop1 -> prop2 -> SProperty
- (===) :: (Eq a, Show a) => a -> a -> SProperty
- label :: STestable prop => String -> prop -> SProperty
- shrinking :: STestable prop => (a -> [a]) -> a -> (a -> prop) -> SProperty
- noShrinking :: STestable prop => prop -> SProperty
- mapSize :: STestable prop => (Int -> Int) -> prop -> SProperty
- forAll :: (Show a, STestable prop) => Gen a -> (a -> prop) -> SProperty
- forAllShrink :: (Show a, STestable prop) => Gen a -> (a -> [a]) -> (a -> prop) -> SProperty
- inventQCGen :: a -> QCGen
- module Test.QuickCheck
Checking properties
quickCheck :: STestable prop => QCGen -> prop -> String Source #
Cf. quickCheck
. Note that in contrast to QuickCheck's
function, this one takes an additional QCGen
argument.
>>>
putStr $ quickCheck (inventQCGen ()) (\x -> length (x :: [()]) < 10)
*** Failed! Falsifiable (after 18 tests and 3 shrinks): [(),(),(),(),(),(),(),(),(),(),(),(),(),(),()]
quickCheckResult :: STestable prop => QCGen -> prop -> Result Source #
Cf. quickCheckResult
. Note that in contrast to
QuickCheck's function, this one takes an additional QCGen
argument.
quickCheckWith :: STestable prop => Args -> QCGen -> prop -> String Source #
Cf. quickCheckWith
. Note that in contrast to
QuickCheck's function, this one takes an additional QCGen
argument.
quickCheckWithResult :: STestable prop => Args -> QCGen -> prop -> Result Source #
Cf. quickCheckWithResult
. Note that in contrast to
QuickCheck's function, this one takes an additional QCGen
argument.
Creating and combining properties
sProperty
(.||.) :: (STestable prop2, STestable prop1) => prop1 -> prop2 -> SProperty Source #
Disjunction. Cf. .||.
.
(.&&.) :: (STestable prop2, STestable prop1) => prop1 -> prop2 -> SProperty Source #
Conjunction. Cf. .&&.
.
(.&.) :: (STestable prop2, STestable prop1) => prop1 -> prop2 -> SProperty Source #
Nondeterministic conjunction. Cf. &.
.
shrinking :: STestable prop => (a -> [a]) -> a -> (a -> prop) -> SProperty Source #
Shrink counterexamples. Cf. shrinking
.
noShrinking :: STestable prop => prop -> SProperty Source #
Suppress shrinking of counterexamples. Cf. noShrinking
.
mapSize :: STestable prop => (Int -> Int) -> prop -> SProperty Source #
Adjust testcase sizes. Cf. mapSize
.
forAll :: (Show a, STestable prop) => Gen a -> (a -> prop) -> SProperty Source #
Universal quantification. Cf. forAll
.
forAllShrink :: (Show a, STestable prop) => Gen a -> (a -> [a]) -> (a -> prop) -> SProperty Source #
Universal quantification with shrinking.
Cf. forAllShrink
.
Miscellaneous
inventQCGen :: a -> QCGen Source #
inventQCGen
invokes newQCGen
via
unsafePerformIO
. It is useful in connection with the
quickCheck
family of functions.
module Test.QuickCheck