Safe Haskell | None |
---|---|
Language | Haskell98 |
Test.QuickCheck
- quickCheck :: Testable prop => prop -> IO ()
- data Args = Args {}
- data Result
- = Success { }
- | GaveUp { }
- | Failure { }
- | NoExpectedFailure { }
- stdArgs :: Args
- quickCheckWith :: Testable prop => Args -> prop -> IO ()
- quickCheckWithResult :: Testable prop => Args -> prop -> IO Result
- quickCheckResult :: Testable prop => prop -> IO Result
- verboseCheck :: Testable prop => prop -> IO ()
- verboseCheckWith :: Testable prop => Args -> prop -> IO ()
- verboseCheckWithResult :: Testable prop => Args -> prop -> IO Result
- verboseCheckResult :: Testable prop => prop -> IO Result
- verbose :: Testable prop => prop -> Property
- data Gen a
- sized :: (Int -> Gen a) -> Gen a
- resize :: Int -> Gen a -> Gen a
- choose :: Random a => (a, a) -> Gen a
- promote :: Monad m => m (Gen a) -> Gen (m a)
- suchThat :: Gen a -> (a -> Bool) -> Gen a
- suchThatMaybe :: Gen a -> (a -> Bool) -> Gen (Maybe a)
- oneof :: [Gen a] -> Gen a
- frequency :: [(Int, Gen a)] -> Gen a
- elements :: [a] -> Gen a
- growingElements :: [a] -> Gen a
- listOf :: Gen a -> Gen [a]
- listOf1 :: Gen a -> Gen [a]
- vectorOf :: Int -> Gen a -> Gen [a]
- vector :: Arbitrary a => Int -> Gen [a]
- orderedList :: (Ord a, Arbitrary a) => Gen [a]
- sample :: Show a => Gen a -> IO ()
- sample' :: Gen a -> IO [a]
- class Arbitrary a where
- class CoArbitrary a where
- coarbitrary :: a -> Gen c -> Gen c
- arbitrarySizedIntegral :: Num a => Gen a
- arbitrarySizedFractional :: Fractional a => Gen a
- arbitrarySizedBoundedIntegral :: (Bounded a, Integral a) => Gen a
- arbitraryBoundedIntegral :: (Bounded a, Integral a) => Gen a
- arbitraryBoundedRandom :: (Bounded a, Random a) => Gen a
- arbitraryBoundedEnum :: (Bounded a, Enum a) => Gen a
- coarbitraryEnum :: Enum a => a -> Gen b -> Gen b
- shrinkNothing :: a -> [a]
- shrinkIntegral :: Integral a => a -> [a]
- shrinkRealFrac :: RealFrac a => a -> [a]
- variant :: Integral n => n -> Gen a -> Gen a
- (><) :: (Gen a -> Gen a) -> (Gen a -> Gen a) -> Gen a -> Gen a
- coarbitraryIntegral :: Integral a => a -> Gen b -> Gen b
- coarbitraryReal :: Real a => a -> Gen b -> Gen b
- coarbitraryShow :: Show a => a -> Gen b -> Gen b
- newtype Blind a = Blind a
- newtype Fixed a = Fixed a
- newtype OrderedList a = Ordered {
- getOrdered :: [a]
- newtype NonEmptyList a = NonEmpty {
- getNonEmpty :: [a]
- newtype Positive a = Positive {
- getPositive :: a
- newtype NonZero a = NonZero {
- getNonZero :: a
- newtype NonNegative a = NonNegative {
- getNonNegative :: a
- data Smart a = Smart Int a
- newtype Shrink2 a = Shrink2 a
- data Shrinking s a = Shrinking s a
- class ShrinkState s a where
- shrinkInit :: a -> s
- shrinkState :: a -> s -> [(a, s)]
- type Property = Gen Prop
- data Prop
- class Testable prop where
- property :: prop -> Property
- exhaustive :: prop -> Bool
- mapSize :: Testable prop => (Int -> Int) -> prop -> Property
- shrinking :: Testable prop => (a -> [a]) -> a -> (a -> prop) -> Property
- (==>) :: Testable prop => Bool -> prop -> Property
- discard :: a
- forAll :: (Show a, Testable prop) => Gen a -> (a -> prop) -> Property
- forAllShrink :: (Show a, Testable prop) => Gen a -> (a -> [a]) -> (a -> prop) -> Property
- (.&.) :: (Testable prop1, Testable prop2) => prop1 -> prop2 -> Property
- (.&&.) :: (Testable prop1, Testable prop2) => prop1 -> prop2 -> Property
- conjoin :: Testable prop => [prop] -> Property
- (.||.) :: (Testable prop1, Testable prop2) => prop1 -> prop2 -> Property
- disjoin :: Testable prop => [prop] -> Property
- whenFail :: Testable prop => IO () -> prop -> Property
- printTestCase :: Testable prop => String -> prop -> Property
- whenFail' :: Testable prop => IO () -> prop -> Property
- expectFailure :: Testable prop => prop -> Property
- within :: Testable prop => Int -> prop -> Property
- label :: Testable prop => String -> prop -> Property
- collect :: (Show a, Testable prop) => a -> prop -> Property
- classify :: Testable prop => Bool -> String -> prop -> Property
- cover :: Testable prop => Bool -> Int -> String -> prop -> Property
- once :: Testable prop => prop -> Property
- newtype Str = MkStr String
- ranges :: (Show a, Integral a) => a -> a -> Str
Running tests
quickCheck :: Testable prop => prop -> IO () Source
Tests a property and prints the results to stdout
.
Args specifies arguments to the QuickCheck driver
Constructors
Args | |
Fields
|
Result represents the test result
Constructors
Success | |
GaveUp | |
Failure | |
Fields
| |
NoExpectedFailure | |
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 Result Source
Tests a property, using test arguments, produces a test result, and prints the results to stdout
.
quickCheckResult :: Testable prop => prop -> IO Result Source
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 Result Source
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 Result Source
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 -> Property Source
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
Generator combinators
sized :: (Int -> Gen a) -> Gen a Source
Used to construct generators that depend on the size parameter.
resize :: Int -> Gen a -> Gen a Source
Overrides the size parameter. Returns a generator which uses the given size instead of the runtime-size parameter.
choose :: Random a => (a, a) -> Gen a Source
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.
suchThatMaybe :: Gen a -> (a -> Bool) -> Gen (Maybe a) Source
Tries to generate a value that satisfies a predicate.
oneof :: [Gen a] -> Gen a Source
Randomly uses one of the given generators. The input list must be non-empty.
frequency :: [(Int, Gen a)] -> Gen a Source
Chooses one of the given generators, with a weighted random distribution. The input list must be non-empty.
growingElements :: [a] -> Gen a Source
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.
Generators which use Arbitrary
orderedList :: (Ord a, Arbitrary a) => Gen [a] Source
Generates an ordered list of a given length.
Generator debugging
Arbitrary and CoArbitrary classes
class Arbitrary a where Source
Random generation and shrinking of values.
Minimal complete definition
Nothing
Methods
A generator for values of the given type.
Produces a (possibly) empty list of all the possible immediate shrinks of the given value.
Instances
class CoArbitrary a where Source
Used for random generation of functions.
Methods
coarbitrary :: a -> Gen c -> Gen c Source
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
.
Instances
Helper functions for implementing arbitrary
arbitrarySizedIntegral :: Num a => Gen a Source
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 a Source
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 a Source
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 a Source
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 a Source
Generates an element of a bounded type. The element is chosen from the entire range of the type.
arbitraryBoundedEnum :: (Bounded a, Enum a) => Gen a Source
Generates an element of a bounded enumeration.
coarbitraryEnum :: Enum a => a -> Gen b -> Gen b Source
A coarbitrary
implementation for enums.
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
(><) :: (Gen a -> Gen a) -> (Gen a -> Gen a) -> Gen a -> Gen a Source
Combine two generator perturbing functions, for example the
results of calls to variant
or coarbitrary
.
coarbitraryIntegral :: Integral a => a -> Gen b -> Gen b Source
A coarbitrary
implementation for integral numbers.
coarbitraryReal :: Real a => a -> Gen b -> Gen b Source
A coarbitrary
implementation for real numbers.
coarbitraryShow :: Show a => a -> Gen b -> Gen b Source
coarbitrary
helper for lazy people :-).
Type-level modifiers for changing generator behavior
Fixed x
: as x, but will not be shrunk.
Constructors
Fixed a |
newtype OrderedList a Source
Ordered xs
: guarantees that xs is ordered.
Constructors
Ordered | |
Fields
|
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 | |
Fields
|
Instances
Eq a => Eq (NonEmptyList a) | |
Ord a => Ord (NonEmptyList a) | |
Read a => Read (NonEmptyList a) | |
Show a => Show (NonEmptyList a) | |
Arbitrary a => Arbitrary (NonEmptyList a) |
Positive x
: guarantees that x > 0
.
Constructors
Positive | |
Fields
|
NonZero x
: guarantees that x /= 0
.
Constructors
NonZero | |
Fields
|
newtype NonNegative a Source
NonNegative x
: guarantees that x >= 0
.
Constructors
NonNegative | |
Fields
|
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) |
Smart _ x
: tries a different order when shrinking.
Shrink2 x
: allows 2 shrinking steps at the same time when shrinking x
Constructors
Shrink2 a |
Shrinking _ x
: allows for maintaining a state during shrinking.
Constructors
Shrinking s a |
class ShrinkState s a where Source
Properties
class Testable prop where Source
The class of things which can be tested, i.e. turned into a property.
Minimal complete definition
Property combinators
mapSize :: Testable prop => (Int -> Int) -> prop -> Property Source
Changes the maximum test case size for a property.
Arguments
:: Testable prop | |
=> (a -> [a]) |
|
-> 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 -> 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.
A special exception that makes QuickCheck discard the test case.
Normally you should use ==>
, but if for some reason this isn't
possible (e.g. you are deep inside a generator), use discard
instead.
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.
Experimental combinators for conjunction and disjunction
(.&.) :: (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.
(.||.) :: (Testable prop1, Testable prop2) => prop1 -> prop2 -> Property infixr 1 Source
Disjunction: p1
.||.
p2
passes unless p1
and p2
simultaneously fail.
Handling failure
whenFail :: Testable prop => IO () -> prop -> Property Source
Performs an IO
action after the last failure of a property.
printTestCase :: Testable prop => String -> prop -> Property Source
Prints a message to the terminal as part of the counterexample.
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.
expectFailure :: Testable prop => prop -> Property Source
Modifies a property so that it is expected to fail for some test cases.
within :: Testable prop => Int -> prop -> Property Source
Considers a property failed if it does not complete within the given number of microseconds.
Test distribution
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)
Arguments
:: Testable prop | |
=> Bool |
|
-> String | Label. |
-> prop | |
-> Property |
Conditionally labels test case.
Arguments
:: Testable prop | |
=> Bool |
|
-> 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.
once :: Testable prop => prop -> Property Source
Modifies a property so that it only will be tested once.