Safe Haskell | None |
---|---|
Language | Haskell2010 |
This module extends QuickCheck so that it returns counterexamples
as Haskell values instead of just printing them. To use it, import
this module instead of Test.QuickCheck. The API and functionality
are the same as normal QuickCheck; the only difference is that the
return types of quickCheck
(and related functions)
include a counterexample.
Note that this module re-exports most functions from Test.QuickCheck. Those functions are not documented here! You will need to refer to the main Test.QuickCheck documentation when using this module.
Here is an example of getting counterexamples. Suppose we have the following property:
prop_reverse_append :: [Int] -> [Int] -> Property prop_reverse_append xs ys = reverse (xs++ys) === reverse xs ++ reverse ys
If we look the type of quickCheck prop_reverse_append
, we see that
it returns a counterexample:
>>>
:t quickCheck prop_reverse_append
quickCheck prop_reverse_append :: IO (Maybe ([Int] :&: [Int] :&: ()))
The Maybe
is there because quickCheck
will return Nothing
if the
property succeeds; :&:
is a datatype of pairs.
If we run QuickCheck, we can get the counterexample as a normal Haskell value:
>>>
Just (xs :&: ys :&: ()) <- quickCheck prop_reverse_append
*** Failed! Falsifiable (after 5 tests and 4 shrinks): [0] [1] [1,0] /= [0,1]
>>>
:t xs
xs :: [Int]
>>>
xs
[0]
>>>
ys
[1]
If you use counterexample
in your property, the string you pass
won't be returned as a Haskell value. You might instead want to use
typedCounterexample
, which adds a Haskell value to the counterexample
(but doesn't print it).
That ought to be all you need to know to use this module. If you want all the details, here is how this module alters QuickCheck's API:
- There is a new type
, which represents a property that (if it fails) generates a counterexample of typePropertyOf
cexcex
.Property
is now a synonym for
. ThePropertyOf
()Testable
class now has an associated typeCounterexample
which describes the counterexample. - The QuickCheck property combinators take and return
PropertyOf
instead ofProperty
wherever possible, in order to preserve the counterexample. quickCheck
and related functions return a
.Counterexample
prop- There are two new combinators
typedCounterexample
andonProperty
.
Synopsis
- data a :&: b = a :&: b
- class Testable prop => Testable prop where
- type Counterexample prop
- property :: prop -> PropertyFrom prop
- propertyForAllShrinkShow :: Show a => Gen a -> (a -> [a]) -> (a -> String) -> (a -> prop) -> PropertyOf (a :&: Counterexample prop)
- type PropertyFrom prop = PropertyOf (Counterexample prop)
- type Property = PropertyOf ()
- newtype PropertyOf cex = MkProperty {
- unProperty :: (cex -> IO ()) -> Property
- typedCounterexample :: Testable prop => a -> prop -> PropertyOf (a :&: Counterexample prop)
- onProperty :: Testable prop => (Property -> Property) -> prop -> PropertyFrom prop
- quickCheck :: Testable prop => prop -> IO (Maybe (Counterexample prop))
- quickCheckWith :: Testable prop => Args -> prop -> IO (Maybe (Counterexample prop))
- quickCheckResult :: Testable prop => prop -> IO (Maybe (Counterexample prop), Result)
- quickCheckWithResult :: Testable prop => Args -> prop -> IO (Maybe (Counterexample prop), Result)
- verboseCheck :: Testable prop => prop -> IO (Maybe (Counterexample prop))
- verboseCheckWith :: Testable prop => Args -> prop -> IO (Maybe (Counterexample prop))
- verboseCheckResult :: Testable prop => prop -> IO (Maybe (Counterexample prop), Result)
- verboseCheckWithResult :: Testable prop => Args -> prop -> IO (Maybe (Counterexample prop), Result)
- labelledExamples :: Testable prop => prop -> IO (Maybe (Counterexample prop))
- labelledExamplesWith :: Testable prop => Args -> prop -> IO (Maybe (Counterexample prop))
- labelledExamplesResult :: Testable prop => prop -> IO (Maybe (Counterexample prop), Result)
- labelledExamplesWithResult :: Testable prop => Args -> prop -> IO (Maybe (Counterexample prop), Result)
- polyQuickCheck :: Name -> ExpQ
- polyVerboseCheck :: Name -> ExpQ
- forAll :: (Testable prop, Show a) => Gen a -> (a -> prop) -> PropertyOf (a :&: Counterexample prop)
- forAllShrink :: (Testable prop, Show a) => Gen a -> (a -> [a]) -> (a -> prop) -> PropertyOf (a :&: Counterexample prop)
- forAllShow :: Testable prop => Gen a -> (a -> String) -> (a -> prop) -> PropertyOf (a :&: Counterexample prop)
- forAllShrinkShow :: Testable prop => Gen a -> (a -> [a]) -> (a -> String) -> (a -> prop) -> PropertyOf (a :&: Counterexample prop)
- forAllBlind :: Testable prop => Gen a -> (a -> prop) -> PropertyOf (a :&: Counterexample prop)
- forAllShrinkBlind :: Testable prop => Gen a -> (a -> [a]) -> (a -> prop) -> PropertyOf (a :&: Counterexample prop)
- shrinking :: Testable prop => (a -> [a]) -> a -> (a -> prop) -> PropertyFrom prop
- (==>) :: Testable prop => Bool -> prop -> PropertyFrom prop
- (===) :: (Eq a, Show a) => a -> a -> Property
- (=/=) :: (Eq a, Show a) => a -> a -> Property
- ioProperty :: Testable prop => IO prop -> PropertyFrom prop
- idempotentIOProperty :: Testable prop => IO prop -> PropertyFrom prop
- verbose :: Testable prop => prop -> PropertyFrom prop
- verboseShrinking :: Testable prop => prop -> PropertyFrom prop
- once :: Testable prop => prop -> PropertyFrom prop
- again :: Testable prop => prop -> PropertyFrom prop
- within :: Testable prop => Int -> prop -> PropertyFrom prop
- noShrinking :: Testable prop => prop -> PropertyFrom prop
- counterexample :: Testable prop => String -> prop -> PropertyFrom prop
- whenFail :: Testable prop => IO () -> prop -> PropertyFrom prop
- whenFail' :: Testable prop => IO () -> prop -> PropertyFrom prop
- expectFailure :: Testable prop => prop -> PropertyFrom prop
- label :: Testable prop => String -> prop -> PropertyFrom prop
- collect :: (Show a, Testable prop) => a -> prop -> PropertyFrom prop
- classify :: Testable prop => Bool -> String -> prop -> PropertyFrom prop
- cover :: Testable prop => Double -> Bool -> String -> prop -> PropertyFrom prop
- tabulate :: Testable prop => String -> [String] -> prop -> PropertyFrom prop
- coverTables :: Testable prop => String -> [(String, Double)] -> prop -> PropertyFrom prop
- checkCoverage :: Testable prop => prop -> PropertyFrom prop
- checkCoverageWith :: Testable prop => Confidence -> prop -> PropertyFrom prop
- mapSize :: Testable prop => (Int -> Int) -> prop -> PropertyFrom prop
- verboseCheckAll :: Q Exp
- quickCheckAll :: Q Exp
- allProperties :: Q Exp
- forAllProperties :: Q Exp
- monomorphic :: Name -> ExpQ
- stdArgs :: Args
- isSuccess :: Result -> Bool
- data Args = Args {
- replay :: Maybe (QCGen, Int)
- maxSuccess :: Int
- maxDiscardRatio :: Int
- maxSize :: Int
- chatty :: Bool
- maxShrinks :: Int
- data Result
- = Success { }
- | GaveUp { }
- | Failure {
- numTests :: Int
- numDiscarded :: Int
- numShrinks :: Int
- numShrinkTries :: Int
- numShrinkFinal :: Int
- usedSeed :: QCGen
- usedSize :: Int
- reason :: String
- theException :: Maybe AnException
- output :: String
- failingTestCase :: [String]
- failingLabels :: [String]
- failingClasses :: Set String
- | NoExpectedFailure { }
- total :: NFData a => a -> Property
- stdConfidence :: Confidence
- withMaxSuccess :: Testable prop => Int -> prop -> Property
- data Discard = Discard
- data Confidence = Confidence {}
- applyFun3 :: Fun (a, b, c) d -> a -> b -> c -> d
- applyFun2 :: Fun (a, b) c -> a -> b -> c
- applyFun :: Fun a b -> a -> b
- functionMap :: Function b => (a -> b) -> (b -> a) -> (a -> c) -> a :-> c
- functionShow :: (Show a, Read a) => (a -> c) -> a :-> c
- functionIntegral :: Integral a => (a -> b) -> a :-> b
- functionRealFrac :: RealFrac a => (a -> b) -> a :-> b
- functionBoundedEnum :: (Eq a, Bounded a, Enum a) => (a -> b) -> a :-> b
- pattern Fn :: forall a b. (a -> b) -> Fun a b
- pattern Fn2 :: forall a b c. (a -> b -> c) -> Fun (a, b) c
- pattern Fn3 :: forall a b c d. (a -> b -> c -> d) -> Fun (a, b, c) d
- class Function a where
- data Fun a b = Fun (a :-> b, b, Shrunk) (a -> b)
- newtype Blind a = Blind {
- getBlind :: a
- newtype Fixed a = Fixed {
- getFixed :: a
- newtype OrderedList a = Ordered {
- getOrdered :: [a]
- newtype NonEmptyList a = NonEmpty {
- getNonEmpty :: [a]
- data InfiniteList a = InfiniteList {
- getInfiniteList :: [a]
- infiniteListInternalData :: InfiniteListInternalData a
- newtype SortedList a = Sorted {
- getSorted :: [a]
- newtype Positive a = Positive {
- getPositive :: a
- newtype Negative a = Negative {
- getNegative :: a
- newtype NonZero a = NonZero {
- getNonZero :: a
- newtype NonNegative a = NonNegative {
- getNonNegative :: a
- newtype NonPositive a = NonPositive {
- getNonPositive :: a
- newtype Large a = Large {
- getLarge :: a
- newtype Small a = Small {
- getSmall :: a
- newtype Shrink2 a = Shrink2 {
- getShrink2 :: a
- data Smart a = Smart Int a
- data Shrinking s a = Shrinking s a
- class ShrinkState s a where
- shrinkInit :: a -> s
- shrinkState :: a -> s -> [(a, s)]
- newtype ASCIIString = ASCIIString {}
- newtype UnicodeString = UnicodeString {}
- newtype PrintableString = PrintableString {}
- infiniteList :: Arbitrary a => Gen [a]
- orderedList :: (Ord a, Arbitrary a) => Gen [a]
- vector :: Arbitrary a => Int -> Gen [a]
- coarbitraryEnum :: Enum a => a -> Gen b -> Gen b
- coarbitraryShow :: Show a => a -> Gen b -> Gen b
- coarbitraryReal :: Real a => a -> Gen b -> Gen b
- coarbitraryIntegral :: Integral a => a -> Gen b -> Gen b
- (><) :: (Gen a -> Gen a) -> (Gen a -> Gen a) -> Gen a -> Gen a
- genericCoarbitrary :: (Generic a, GCoArbitrary (Rep a)) => a -> Gen b -> Gen b
- shrinkDecimal :: RealFrac a => a -> [a]
- shrinkRealFrac :: RealFrac a => a -> [a]
- shrinkIntegral :: Integral a => a -> [a]
- shrinkMapBy :: (a -> b) -> (b -> a) -> (a -> [a]) -> b -> [b]
- shrinkMap :: Arbitrary a => (a -> b) -> (b -> a) -> b -> [b]
- shrinkNothing :: a -> [a]
- arbitraryPrintableChar :: Gen Char
- arbitraryASCIIChar :: Gen Char
- arbitraryUnicodeChar :: Gen Char
- arbitrarySizedBoundedIntegral :: (Bounded a, Integral a) => Gen a
- arbitraryBoundedEnum :: (Bounded a, Enum a) => Gen a
- arbitraryBoundedRandom :: (Bounded a, Random a) => Gen a
- arbitraryBoundedIntegral :: (Bounded a, Integral a) => Gen a
- arbitrarySizedFractional :: Fractional a => Gen a
- arbitrarySizedNatural :: Integral a => Gen a
- arbitrarySizedIntegral :: Integral a => Gen a
- applyArbitrary4 :: (Arbitrary a, Arbitrary b, Arbitrary c, Arbitrary d) => (a -> b -> c -> d -> r) -> Gen r
- applyArbitrary3 :: (Arbitrary a, Arbitrary b, Arbitrary c) => (a -> b -> c -> r) -> Gen r
- applyArbitrary2 :: (Arbitrary a, Arbitrary b) => (a -> b -> r) -> Gen r
- shrinkList :: (a -> [a]) -> [a] -> [[a]]
- subterms :: (Generic a, GSubterms (Rep a) a) => a -> [a]
- recursivelyShrink :: (Generic a, RecursivelyShrink (Rep a)) => a -> [a]
- genericShrink :: (Generic a, RecursivelyShrink (Rep a), GSubterms (Rep a) a) => a -> [a]
- shrink2 :: (Arbitrary2 f, Arbitrary a, Arbitrary b) => f a b -> [f a b]
- arbitrary2 :: (Arbitrary2 f, Arbitrary a, Arbitrary b) => Gen (f a b)
- shrink1 :: (Arbitrary1 f, Arbitrary a) => f a -> [f a]
- arbitrary1 :: (Arbitrary1 f, Arbitrary a) => Gen (f a)
- class Arbitrary a where
- class Arbitrary1 (f :: Type -> Type) where
- liftArbitrary :: Gen a -> Gen (f a)
- liftShrink :: (a -> [a]) -> f a -> [f a]
- class Arbitrary2 (f :: Type -> Type -> Type) where
- liftArbitrary2 :: Gen a -> Gen b -> Gen (f a b)
- liftShrink2 :: (a -> [a]) -> (b -> [b]) -> f a b -> [f a b]
- class CoArbitrary a where
- coarbitrary :: a -> Gen b -> Gen b
- infiniteListOf :: Gen a -> Gen [a]
- vectorOf :: Int -> Gen a -> Gen [a]
- listOf1 :: Gen a -> Gen [a]
- listOf :: Gen a -> Gen [a]
- growingElements :: [a] -> Gen a
- shuffle :: [a] -> Gen [a]
- sublistOf :: [a] -> Gen [a]
- elements :: [a] -> Gen a
- frequency :: [(Int, Gen a)] -> Gen a
- oneof :: [Gen a] -> Gen a
- suchThatMaybe :: Gen a -> (a -> Bool) -> Gen (Maybe a)
- suchThatMap :: Gen a -> (a -> Maybe b) -> Gen b
- suchThat :: Gen a -> (a -> Bool) -> Gen a
- sample :: Show a => Gen a -> IO ()
- sample' :: Gen a -> IO [a]
- generate :: Gen a -> IO a
- choose :: Random a => (a, a) -> Gen a
- scale :: (Int -> Int) -> Gen a -> Gen a
- resize :: Int -> Gen a -> Gen a
- getSize :: Gen Int
- sized :: (Int -> Gen a) -> Gen a
- variant :: Integral n => n -> Gen a -> Gen a
- data Gen a
- discard :: a
Documentation
data a :&: b infixr 6 Source #
A type of pairs. Used in counterexamples.
a :&: b infixr 6 |
class Testable prop => Testable prop where Source #
The class of properties, i.e. types which QuickCheck knows how to test.
type Counterexample prop Source #
The type of counterexamples to the property.
property :: prop -> PropertyFrom prop Source #
Convert the property to a PropertyOf
.
propertyForAllShrinkShow :: Show a => Gen a -> (a -> [a]) -> (a -> String) -> (a -> prop) -> PropertyOf (a :&: Counterexample prop) Source #
Instances
type PropertyFrom prop = PropertyOf (Counterexample prop) Source #
A type synonym for the property which comes from a particular Testable
instance.
type Property = PropertyOf () Source #
A property which doesn't produce a counterexample.
newtype PropertyOf cex Source #
A property. cex
is the type of counterexamples to the property.
Note that there is a Functor
instance, which is useful when you
want to manipulate the counterexample, e.g., to change its type.
For example, when some branches of your property produce a
counterexample and other branches do not, the types will not match
up, but using fmap
you can make the counterexample be a Maybe
.
MkProperty | |
|
Instances
Functor PropertyOf Source # | |
Defined in Test.QuickCheck.Counterexamples fmap :: (a -> b) -> PropertyOf a -> PropertyOf b # (<$) :: a -> PropertyOf b -> PropertyOf a # | |
Testable (PropertyOf cex) Source # | |
Defined in Test.QuickCheck.Counterexamples property :: PropertyOf cex -> Property # propertyForAllShrinkShow :: Show a => Gen a -> (a -> [a]) -> (a -> String) -> (a -> PropertyOf cex) -> Property # | |
Testable (PropertyOf cex) Source # | |
Defined in Test.QuickCheck.Counterexamples type Counterexample (PropertyOf cex) :: Type Source # property :: PropertyOf cex -> PropertyFrom (PropertyOf cex) Source # propertyForAllShrinkShow :: Show a => Gen a -> (a -> [a]) -> (a -> String) -> (a -> PropertyOf cex) -> PropertyOf (a :&: Counterexample (PropertyOf cex)) Source # | |
type Counterexample (PropertyOf cex) Source # | |
Defined in Test.QuickCheck.Counterexamples |
typedCounterexample :: Testable prop => a -> prop -> PropertyOf (a :&: Counterexample prop) Source #
Add a value to the counterexample.
The value is not printed as part of the counterexample;
if you want it to be, use counterexample
as well.
onProperty :: Testable prop => (Property -> Property) -> prop -> PropertyFrom prop Source #
Lift an ordinary QuickCheck property combinator to one with counterexamples.
quickCheck :: Testable prop => prop -> IO (Maybe (Counterexample prop)) Source #
See quickCheck
in Test.QuickCheck.
quickCheckWith :: Testable prop => Args -> prop -> IO (Maybe (Counterexample prop)) Source #
See quickCheckWith
in Test.QuickCheck.
quickCheckResult :: Testable prop => prop -> IO (Maybe (Counterexample prop), Result) Source #
See quickCheckResult
in Test.QuickCheck.
quickCheckWithResult :: Testable prop => Args -> prop -> IO (Maybe (Counterexample prop), Result) Source #
See quickCheckWithResult
in Test.QuickCheck.
verboseCheck :: Testable prop => prop -> IO (Maybe (Counterexample prop)) Source #
See verboseCheck
in Test.QuickCheck.
verboseCheckWith :: Testable prop => Args -> prop -> IO (Maybe (Counterexample prop)) Source #
See verboseCheckWith
in Test.QuickCheck.
verboseCheckResult :: Testable prop => prop -> IO (Maybe (Counterexample prop), Result) Source #
See verboseCheckResult
in Test.QuickCheck.
verboseCheckWithResult :: Testable prop => Args -> prop -> IO (Maybe (Counterexample prop), Result) Source #
labelledExamples :: Testable prop => prop -> IO (Maybe (Counterexample prop)) Source #
See labelledExamples
in Test.QuickCheck.
labelledExamplesWith :: Testable prop => Args -> prop -> IO (Maybe (Counterexample prop)) Source #
See labelledExamplesWith
in Test.QuickCheck.
labelledExamplesResult :: Testable prop => prop -> IO (Maybe (Counterexample prop), Result) Source #
labelledExamplesWithResult :: Testable prop => Args -> prop -> IO (Maybe (Counterexample prop), Result) Source #
polyQuickCheck :: Name -> ExpQ Source #
See polyQuickCheck
in Test.QuickCheck.
polyVerboseCheck :: Name -> ExpQ Source #
See polyVerboseCheck
in Test.QuickCheck.
forAll :: (Testable prop, Show a) => Gen a -> (a -> prop) -> PropertyOf (a :&: Counterexample prop) Source #
See forAll
in Test.QuickCheck.
forAllShrink :: (Testable prop, Show a) => Gen a -> (a -> [a]) -> (a -> prop) -> PropertyOf (a :&: Counterexample prop) Source #
See forAllShrink
in Test.QuickCheck.
forAllShow :: Testable prop => Gen a -> (a -> String) -> (a -> prop) -> PropertyOf (a :&: Counterexample prop) Source #
See forAllShow
in Test.QuickCheck.
forAllShrinkShow :: Testable prop => Gen a -> (a -> [a]) -> (a -> String) -> (a -> prop) -> PropertyOf (a :&: Counterexample prop) Source #
See forAllShrinkShow
in Test.QuickCheck.
forAllBlind :: Testable prop => Gen a -> (a -> prop) -> PropertyOf (a :&: Counterexample prop) Source #
See forAllBlind
in Test.QuickCheck.
forAllShrinkBlind :: Testable prop => Gen a -> (a -> [a]) -> (a -> prop) -> PropertyOf (a :&: Counterexample prop) Source #
See forAllShrinkBlind
in Test.QuickCheck.
shrinking :: Testable prop => (a -> [a]) -> a -> (a -> prop) -> PropertyFrom prop Source #
See shrinking
in Test.QuickCheck.
(==>) :: Testable prop => Bool -> prop -> PropertyFrom prop infixr 0 Source #
See ==>
in Test.QuickCheck.
ioProperty :: Testable prop => IO prop -> PropertyFrom prop Source #
See ioProperty
in Test.QuickCheck.
idempotentIOProperty :: Testable prop => IO prop -> PropertyFrom prop Source #
See idempotentIOProperty
in Test.QuickCheck.
verbose :: Testable prop => prop -> PropertyFrom prop Source #
See verbose
in Test.QuickCheck.
verboseShrinking :: Testable prop => prop -> PropertyFrom prop Source #
See verboseShrinking
in Test.QuickCheck.
once :: Testable prop => prop -> PropertyFrom prop Source #
See once
in Test.QuickCheck.
again :: Testable prop => prop -> PropertyFrom prop Source #
See again
in Test.QuickCheck.
within :: Testable prop => Int -> prop -> PropertyFrom prop Source #
See within
in Test.QuickCheck.
noShrinking :: Testable prop => prop -> PropertyFrom prop Source #
See noShrinking
in Test.QuickCheck.
counterexample :: Testable prop => String -> prop -> PropertyFrom prop Source #
See counterexample
in Test.QuickCheck.
whenFail :: Testable prop => IO () -> prop -> PropertyFrom prop Source #
See whenFail
in Test.QuickCheck.
whenFail' :: Testable prop => IO () -> prop -> PropertyFrom prop Source #
See whenFail'
in Test.QuickCheck.
expectFailure :: Testable prop => prop -> PropertyFrom prop Source #
See expectFailure
in Test.QuickCheck.
label :: Testable prop => String -> prop -> PropertyFrom prop Source #
See label
in Test.QuickCheck.
collect :: (Show a, Testable prop) => a -> prop -> PropertyFrom prop Source #
See collect
in Test.QuickCheck.
classify :: Testable prop => Bool -> String -> prop -> PropertyFrom prop Source #
See classify
in Test.QuickCheck.
cover :: Testable prop => Double -> Bool -> String -> prop -> PropertyFrom prop Source #
See cover
in Test.QuickCheck.
tabulate :: Testable prop => String -> [String] -> prop -> PropertyFrom prop Source #
See tabulate
in Test.QuickCheck.
coverTables :: Testable prop => String -> [(String, Double)] -> prop -> PropertyFrom prop Source #
See coverTables
in Test.QuickCheck.
checkCoverage :: Testable prop => prop -> PropertyFrom prop Source #
See checkCoverage
in Test.QuickCheck.
checkCoverageWith :: Testable prop => Confidence -> prop -> PropertyFrom prop Source #
See checkCoverageWith
in Test.QuickCheck.
mapSize :: Testable prop => (Int -> Int) -> prop -> PropertyFrom prop Source #
See mapSize
in Test.QuickCheck.
verboseCheckAll :: Q Exp #
Test all properties in the current module.
This is just a convenience function that combines quickCheckAll
and verbose
.
verboseCheckAll
has the same issue with scoping as quickCheckAll
:
see the note there about return []
.
quickCheckAll :: Q Exp #
Test all properties in the current module.
The name of the property must begin with prop_
.
Polymorphic properties will be defaulted to Integer
.
Returns True
if all tests succeeded, False
otherwise.
To use quickCheckAll
, add a definition to your module along
the lines of
return [] runTests = $quickCheckAll
and then execute runTests
.
Note: the bizarre return []
in the example above is needed on
GHC 7.8 and later; without it, quickCheckAll
will not be able to find
any of the properties. For the curious, the return []
is a
Template Haskell splice that makes GHC insert the empty list
of declarations at that point in the program; GHC typechecks
everything before the return []
before it starts on the rest
of the module, which means that the later call to quickCheckAll
can see everything that was defined before the return []
. Yikes!
allProperties :: Q Exp #
List all properties in the current module.
$
has type allProperties
[(
.String
, Property
)]
allProperties
has the same issue with scoping as quickCheckAll
:
see the note there about return []
.
forAllProperties :: Q Exp #
Test all properties in the current module, using a custom
quickCheck
function. The same caveats as with quickCheckAll
apply.
$
has type forAllProperties
(
.
An example invocation is Property
-> IO
Result
) -> IO
Bool
$
,
which does the same thing as forAllProperties
quickCheckResult
$
.quickCheckAll
forAllProperties
has the same issue with scoping as quickCheckAll
:
see the note there about return []
.
monomorphic :: Name -> ExpQ #
Monomorphise an arbitrary property by defaulting all type variables to Integer
.
For example, if f
has type
then Ord
a => [a] -> [a]$(
has type monomorphic
'f)[
.Integer
] -> [Integer
]
If you want to use monomorphic
in the same file where you defined the
property, the same scoping problems pop up as in quickCheckAll
:
see the note there about return []
.
Args specifies arguments to the QuickCheck driver
Args | |
|
Result represents the test result
Success | A successful test run |
| |
GaveUp | Given up |
| |
Failure | A failed test run |
| |
NoExpectedFailure | A property that should have failed did not |
|
total :: NFData a => a -> Property #
Checks that a value is total, i.e., doesn't crash when evaluated.
The standard parameters used by checkCoverage
: certainty = 10^9
,
tolerance = 0.9
. See Confidence
for the meaning of the parameters.
withMaxSuccess :: Testable prop => Int -> prop -> Property #
Configures how many times a property will be tested.
For example,
quickCheck (withMaxSuccess 1000 p)
will test p
up to 1000 times.
If a property returns Discard
, the current test case is discarded,
the same as if a precondition was false.
An example is the definition of ==>
:
(==>) :: Testable prop => Bool -> prop -> Property False ==> _ = property Discard True ==> p = property p
Instances
Testable Discard | |
Testable Discard Source # | |
Defined in Test.QuickCheck.Counterexamples type Counterexample Discard :: Type Source # property :: Discard -> PropertyFrom Discard Source # propertyForAllShrinkShow :: Show a => Gen a -> (a -> [a]) -> (a -> String) -> (a -> Discard) -> PropertyOf (a :&: Counterexample Discard) Source # | |
type Counterexample Discard Source # | |
Defined in Test.QuickCheck.Counterexamples |
data Confidence #
The statistical parameters used by checkCoverage
.
Confidence | |
|
Instances
Show Confidence | |
Defined in Test.QuickCheck.State showsPrec :: Int -> Confidence -> ShowS # show :: Confidence -> String # showList :: [Confidence] -> ShowS # |
applyFun3 :: Fun (a, b, c) d -> a -> b -> c -> d #
Extracts the value of a ternary function. Fn3
is the
pattern equivalent of this function.
applyFun2 :: Fun (a, b) c -> a -> b -> c #
Extracts the value of a binary function.
Fn2
is the pattern equivalent of this function.
prop_zipWith :: Fun (Int, Bool) Char -> [Int] -> [Bool] -> Bool prop_zipWith f xs ys = zipWith (applyFun2 f) xs ys == [ applyFun2 f x y | (x, y) <- zip xs ys]
applyFun :: Fun a b -> a -> b #
Extracts the value of a function.
Fn
is the pattern equivalent of this function.
prop :: Fun String Integer -> Bool prop f = applyFun f "banana" == applyFun f "monkey" || applyFun f "banana" == applyFun f "elephant"
functionMap :: Function b => (a -> b) -> (b -> a) -> (a -> c) -> a :-> c #
functionShow :: (Show a, Read a) => (a -> c) -> a :-> c #
functionIntegral :: Integral a => (a -> b) -> a :-> b #
functionRealFrac :: RealFrac a => (a -> b) -> a :-> b #
pattern Fn :: forall a b. (a -> b) -> Fun a b #
A modifier for testing functions.
prop :: Fun String Integer -> Bool prop (Fn f) = f "banana" == f "monkey" || f "banana" == f "elephant"
pattern Fn2 :: forall a b c. (a -> b -> c) -> Fun (a, b) c #
A modifier for testing binary functions.
prop_zipWith :: Fun (Int, Bool) Char -> [Int] -> [Bool] -> Bool prop_zipWith (Fn2 f) xs ys = zipWith f xs ys == [ f x y | (x, y) <- zip xs ys]
pattern Fn3 :: forall a b c d. (a -> b -> c -> d) -> Fun (a, b, c) d #
A modifier for testing ternary functions.
The class Function a
is used for random generation of showable
functions of type a -> b
.
There is a default implementation for function
, which you can use
if your type has structural equality. Otherwise, you can normally
use functionMap
or functionShow
.
Nothing
Instances
Generation of random shrinkable, showable functions.
To generate random values of type
,
you must have an instance Fun
a b
.Function
a
Blind x
: as x, but x does not have to be in the Show
class.
Instances
Functor Blind | |
Enum a => Enum (Blind a) | |
Eq a => Eq (Blind a) | |
Integral a => Integral (Blind a) | |
Defined in Test.QuickCheck.Modifiers | |
Num a => Num (Blind a) | |
Ord a => Ord (Blind a) | |
Real a => Real (Blind a) | |
Defined in Test.QuickCheck.Modifiers toRational :: Blind a -> Rational # | |
Show (Blind a) | |
Arbitrary a => Arbitrary (Blind a) | |
Fixed x
: as x, but will not be shrunk.
Instances
Functor Fixed | |
Enum a => Enum (Fixed a) | |
Eq a => Eq (Fixed a) | |
Integral a => Integral (Fixed a) | |
Defined in Test.QuickCheck.Modifiers | |
Num a => Num (Fixed a) | |
Ord a => Ord (Fixed a) | |
Read a => Read (Fixed a) | |
Real a => Real (Fixed a) | |
Defined in Test.QuickCheck.Modifiers toRational :: Fixed a -> Rational # | |
Show a => Show (Fixed a) | |
Arbitrary a => Arbitrary (Fixed a) | |
newtype OrderedList a #
Ordered xs
: guarantees that xs is ordered.
Ordered | |
|
Instances
newtype NonEmptyList a #
NonEmpty xs
: guarantees that xs is non-empty.
NonEmpty | |
|
Instances
data InfiniteList a #
InfiniteList xs _
: guarantees that xs is an infinite list.
When a counterexample is found, only prints the prefix of xs
that was used by the program.
Here is a contrived example property:
prop_take_10 :: InfiniteList Char -> Bool prop_take_10 (InfiniteList xs _) = or [ x == 'a' | x <- take 10 xs ]
In the following counterexample, the list must start with "bbbbbbbbbb"
but
the remaining (infinite) part can contain anything:
>>>
quickCheck prop_take_10
*** Failed! Falsified (after 1 test and 14 shrinks): "bbbbbbbbbb" ++ ...
InfiniteList | |
|
Instances
Show a => Show (InfiniteList a) | |
Defined in Test.QuickCheck.Modifiers showsPrec :: Int -> InfiniteList a -> ShowS # show :: InfiniteList a -> String # showList :: [InfiniteList a] -> ShowS # | |
Arbitrary a => Arbitrary (InfiniteList a) | |
Defined in Test.QuickCheck.Modifiers arbitrary :: Gen (InfiniteList a) # shrink :: InfiniteList a -> [InfiniteList a] # |
newtype SortedList a #
Sorted xs
: guarantees that xs is sorted.
Instances
Positive x
: guarantees that x > 0
.
Positive | |
|
Instances
Functor Positive | |
Enum a => Enum (Positive a) | |
Defined in Test.QuickCheck.Modifiers succ :: Positive a -> Positive a # pred :: Positive a -> Positive a # fromEnum :: Positive a -> Int # enumFrom :: Positive a -> [Positive a] # enumFromThen :: Positive a -> Positive a -> [Positive a] # enumFromTo :: Positive a -> Positive a -> [Positive a] # enumFromThenTo :: Positive a -> Positive a -> Positive a -> [Positive a] # | |
Eq a => Eq (Positive a) | |
Ord a => Ord (Positive a) | |
Read a => Read (Positive a) | |
Show a => Show (Positive a) | |
(Num a, Ord a, Arbitrary a) => Arbitrary (Positive a) | |
Negative x
: guarantees that x < 0
.
Negative | |
|
Instances
Functor Negative | |
Enum a => Enum (Negative a) | |
Defined in Test.QuickCheck.Modifiers succ :: Negative a -> Negative a # pred :: Negative a -> Negative a # fromEnum :: Negative a -> Int # enumFrom :: Negative a -> [Negative a] # enumFromThen :: Negative a -> Negative a -> [Negative a] # enumFromTo :: Negative a -> Negative a -> [Negative a] # enumFromThenTo :: Negative a -> Negative a -> Negative a -> [Negative a] # | |
Eq a => Eq (Negative a) | |
Ord a => Ord (Negative a) | |
Read a => Read (Negative a) | |
Show a => Show (Negative a) | |
(Num a, Ord a, Arbitrary a) => Arbitrary (Negative a) | |
NonZero x
: guarantees that x /= 0
.
NonZero | |
|
Instances
Functor NonZero | |
Enum a => Enum (NonZero a) | |
Defined in Test.QuickCheck.Modifiers succ :: NonZero a -> NonZero a # pred :: NonZero a -> NonZero a # fromEnum :: NonZero a -> Int # enumFrom :: NonZero a -> [NonZero a] # enumFromThen :: NonZero a -> NonZero a -> [NonZero a] # enumFromTo :: NonZero a -> NonZero a -> [NonZero a] # enumFromThenTo :: NonZero a -> NonZero a -> NonZero a -> [NonZero a] # | |
Eq a => Eq (NonZero a) | |
Ord a => Ord (NonZero a) | |
Defined in Test.QuickCheck.Modifiers | |
Read a => Read (NonZero a) | |
Show a => Show (NonZero a) | |
(Num a, Eq a, Arbitrary a) => Arbitrary (NonZero a) | |
newtype NonNegative a #
NonNegative x
: guarantees that x >= 0
.
Instances
newtype NonPositive a #
NonPositive x
: guarantees that x <= 0
.
Instances
Large x
: by default, QuickCheck generates Int
s drawn from a small
range. Large Int
gives you values drawn from the entire range instead.
Instances
Functor Large | |
Enum a => Enum (Large a) | |
Eq a => Eq (Large a) | |
Integral a => Integral (Large a) | |
Defined in Test.QuickCheck.Modifiers | |
Num a => Num (Large a) | |
Ord a => Ord (Large a) | |
Read a => Read (Large a) | |
Real a => Real (Large a) | |
Defined in Test.QuickCheck.Modifiers toRational :: Large a -> Rational # | |
Show a => Show (Large a) | |
Ix a => Ix (Large a) | |
Defined in Test.QuickCheck.Modifiers | |
(Integral a, Bounded a) => Arbitrary (Large a) | |
Small x
: generates values of x
drawn from a small range.
The opposite of Large
.
Instances
Functor Small | |
Enum a => Enum (Small a) | |
Eq a => Eq (Small a) | |
Integral a => Integral (Small a) | |
Defined in Test.QuickCheck.Modifiers | |
Num a => Num (Small a) | |
Ord a => Ord (Small a) | |
Read a => Read (Small a) | |
Real a => Real (Small a) | |
Defined in Test.QuickCheck.Modifiers toRational :: Small a -> Rational # | |
Show a => Show (Small a) | |
Ix a => Ix (Small a) | |
Defined in Test.QuickCheck.Modifiers | |
Integral a => Arbitrary (Small a) | |
Shrink2 x
: allows 2 shrinking steps at the same time when shrinking x
Shrink2 | |
|
Instances
Functor Shrink2 | |
Enum a => Enum (Shrink2 a) | |
Defined in Test.QuickCheck.Modifiers succ :: Shrink2 a -> Shrink2 a # pred :: Shrink2 a -> Shrink2 a # fromEnum :: Shrink2 a -> Int # enumFrom :: Shrink2 a -> [Shrink2 a] # enumFromThen :: Shrink2 a -> Shrink2 a -> [Shrink2 a] # enumFromTo :: Shrink2 a -> Shrink2 a -> [Shrink2 a] # enumFromThenTo :: Shrink2 a -> Shrink2 a -> Shrink2 a -> [Shrink2 a] # | |
Eq a => Eq (Shrink2 a) | |
Integral a => Integral (Shrink2 a) | |
Defined in Test.QuickCheck.Modifiers | |
Num a => Num (Shrink2 a) | |
Defined in Test.QuickCheck.Modifiers | |
Ord a => Ord (Shrink2 a) | |
Defined in Test.QuickCheck.Modifiers | |
Read a => Read (Shrink2 a) | |
Real a => Real (Shrink2 a) | |
Defined in Test.QuickCheck.Modifiers toRational :: Shrink2 a -> Rational # | |
Show a => Show (Shrink2 a) | |
Arbitrary a => Arbitrary (Shrink2 a) | |
Smart _ x
: tries a different order when shrinking.
Shrinking _ x
: allows for maintaining a state during shrinking.
Shrinking s a |
class ShrinkState s a where #
shrinkInit :: a -> s #
shrinkState :: a -> s -> [(a, s)] #
newtype ASCIIString #
ASCIIString
: generates an ASCII string.
Instances
newtype UnicodeString #
UnicodeString
: generates a unicode String.
The string will not contain surrogate pairs.
Instances
newtype PrintableString #
PrintableString
: generates a printable unicode String.
The string will not contain surrogate pairs.
Instances
Eq PrintableString | |
Defined in Test.QuickCheck.Modifiers (==) :: PrintableString -> PrintableString -> Bool # (/=) :: PrintableString -> PrintableString -> Bool # | |
Ord PrintableString | |
Defined in Test.QuickCheck.Modifiers compare :: PrintableString -> PrintableString -> Ordering # (<) :: PrintableString -> PrintableString -> Bool # (<=) :: PrintableString -> PrintableString -> Bool # (>) :: PrintableString -> PrintableString -> Bool # (>=) :: PrintableString -> PrintableString -> Bool # max :: PrintableString -> PrintableString -> PrintableString # min :: PrintableString -> PrintableString -> PrintableString # | |
Read PrintableString | |
Defined in Test.QuickCheck.Modifiers | |
Show PrintableString | |
Defined in Test.QuickCheck.Modifiers showsPrec :: Int -> PrintableString -> ShowS # show :: PrintableString -> String # showList :: [PrintableString] -> ShowS # | |
Arbitrary PrintableString | |
Defined in Test.QuickCheck.Modifiers arbitrary :: Gen PrintableString # shrink :: PrintableString -> [PrintableString] # |
infiniteList :: Arbitrary a => Gen [a] #
Generates an infinite list.
orderedList :: (Ord a, Arbitrary a) => Gen [a] #
Generates an ordered list.
coarbitraryEnum :: Enum a => a -> Gen b -> Gen b #
A coarbitrary
implementation for enums.
coarbitraryShow :: Show a => a -> Gen b -> Gen b #
coarbitrary
helper for lazy people :-).
coarbitraryReal :: Real a => a -> Gen b -> Gen b #
A coarbitrary
implementation for real numbers.
coarbitraryIntegral :: Integral a => a -> Gen b -> Gen b #
A coarbitrary
implementation for integral numbers.
(><) :: (Gen a -> Gen a) -> (Gen a -> Gen a) -> Gen a -> Gen a #
Combine two generator perturbing functions, for example the
results of calls to variant
or coarbitrary
.
genericCoarbitrary :: (Generic a, GCoArbitrary (Rep a)) => a -> Gen b -> Gen b #
Generic CoArbitrary implementation.
shrinkDecimal :: RealFrac a => a -> [a] #
Shrink a real number, preferring numbers with shorter
decimal representations. See also shrinkRealFrac
.
shrinkRealFrac :: RealFrac a => a -> [a] #
Shrink a fraction, preferring numbers with smaller
numerators or denominators. See also shrinkDecimal
.
shrinkIntegral :: Integral a => a -> [a] #
Shrink an integral number.
shrinkMapBy :: (a -> b) -> (b -> a) -> (a -> [a]) -> b -> [b] #
Non-overloaded version of shrinkMap
.
shrinkMap :: Arbitrary a => (a -> b) -> (b -> a) -> b -> [b] #
Map a shrink function to another domain. This is handy if your data type has special invariants, but is almost isomorphic to some other type.
shrinkOrderedList :: (Ord a, Arbitrary a) => [a] -> [[a]] shrinkOrderedList = shrinkMap sort id shrinkSet :: (Ord a, Arbitrary a) => Set a -> Set [a] shrinkSet = shrinkMap fromList toList
shrinkNothing :: a -> [a] #
Returns no shrinking alternatives.
arbitraryPrintableChar :: Gen Char #
Generates a printable Unicode character.
arbitraryASCIIChar :: Gen Char #
Generates a random ASCII character (0-127).
arbitraryUnicodeChar :: Gen Char #
Generates any Unicode character (but not a surrogate)
arbitrarySizedBoundedIntegral :: (Bounded a, Integral a) => Gen a #
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.
arbitraryBoundedEnum :: (Bounded a, Enum a) => Gen a #
Generates an element of a bounded enumeration.
arbitraryBoundedRandom :: (Bounded a, Random a) => Gen a #
Generates an element of a bounded type. The element is chosen from the entire range of the type.
arbitraryBoundedIntegral :: (Bounded a, Integral a) => Gen a #
Generates an integral number. The number is chosen uniformly from
the entire range of the type. You may want to use
arbitrarySizedBoundedIntegral
instead.
arbitrarySizedFractional :: Fractional a => Gen a #
Generates a fractional number. The number can be positive or negative and its maximum absolute value depends on the size parameter.
arbitrarySizedNatural :: Integral a => Gen a #
Generates a natural number. The number's maximum value depends on the size parameter.
arbitrarySizedIntegral :: Integral a => Gen a #
Generates an integral number. The number can be positive or negative and its maximum absolute value depends on the size parameter.
applyArbitrary4 :: (Arbitrary a, Arbitrary b, Arbitrary c, Arbitrary d) => (a -> b -> c -> d -> r) -> Gen r #
Apply a function of arity 4 to random arguments.
applyArbitrary3 :: (Arbitrary a, Arbitrary b, Arbitrary c) => (a -> b -> c -> r) -> Gen r #
Apply a ternary function to random arguments.
applyArbitrary2 :: (Arbitrary a, Arbitrary b) => (a -> b -> r) -> Gen r #
Apply a binary function to random arguments.
shrinkList :: (a -> [a]) -> [a] -> [[a]] #
Shrink a list of values given a shrinking function for individual values.
recursivelyShrink :: (Generic a, RecursivelyShrink (Rep a)) => a -> [a] #
Recursively shrink all immediate subterms.
genericShrink :: (Generic a, RecursivelyShrink (Rep a), GSubterms (Rep a) a) => a -> [a] #
Shrink a term to any of its immediate subterms, and also recursively shrink all subterms.
shrink2 :: (Arbitrary2 f, Arbitrary a, Arbitrary b) => f a b -> [f a b] #
arbitrary2 :: (Arbitrary2 f, Arbitrary a, Arbitrary b) => Gen (f a b) #
shrink1 :: (Arbitrary1 f, Arbitrary a) => f a -> [f a] #
arbitrary1 :: (Arbitrary1 f, Arbitrary a) => Gen (f a) #
Random generation and shrinking of values.
QuickCheck provides Arbitrary
instances for most types in base
,
except those which incur extra dependencies.
For a wider range of Arbitrary
instances see the
quickcheck-instances
package.
A generator for values of the given type.
It is worth spending time thinking about what sort of test data
you want - good generators are often the difference between
finding bugs and not finding them. You can use sample
,
label
and classify
to check the quality of your test data.
There is no generic arbitrary
implementation included because we don't
know how to make a high-quality one. If you want one, consider using the
testing-feat or
generic-random packages.
The QuickCheck manual goes into detail on how to write good generators. Make sure to look at it, especially if your type is recursive!
Produces a (possibly) empty list of all the possible immediate shrinks of the given value.
The default implementation returns the empty list, so will not try to
shrink the value. If your data type has no special invariants, you can
enable shrinking by defining shrink =
, but by customising
the behaviour of genericShrink
shrink
you can often get simpler counterexamples.
Most implementations of shrink
should try at least three things:
- Shrink a term to any of its immediate subterms.
You can use
subterms
to do this. - Recursively apply
shrink
to all immediate subterms. You can userecursivelyShrink
to do this. - Type-specific shrinkings such as replacing a constructor by a simpler constructor.
For example, suppose we have the following implementation of binary trees:
data Tree a = Nil | Branch a (Tree a) (Tree a)
We can then define shrink
as follows:
shrink Nil = [] shrink (Branch x l r) = -- shrink Branch to Nil [Nil] ++ -- shrink to subterms [l, r] ++ -- recursively shrink subterms [Branch x' l' r' | (x', l', r') <- shrink (x, l, r)]
There are a couple of subtleties here:
- QuickCheck tries the shrinking candidates in the order they
appear in the list, so we put more aggressive shrinking steps
(such as replacing the whole tree by
Nil
) before smaller ones (such as recursively shrinking the subtrees). - It is tempting to write the last line as
[Branch x' l' r' | x' <- shrink x, l' <- shrink l, r' <- shrink r]
but this is the wrong thing! It will force QuickCheck to shrinkx
,l
andr
in tandem, and shrinking will stop once one of the three is fully shrunk.
There is a fair bit of boilerplate in the code above.
We can avoid it with the help of some generic functions.
The function genericShrink
tries shrinking a term to all of its
subterms and, failing that, recursively shrinks the subterms.
Using it, we can define shrink
as:
shrink x = shrinkToNil x ++ genericShrink x where shrinkToNil Nil = [] shrinkToNil (Branch _ l r) = [Nil]
genericShrink
is a combination of subterms
, which shrinks
a term to any of its subterms, and recursivelyShrink
, which shrinks
all subterms of a term. These may be useful if you need a bit more
control over shrinking than genericShrink
gives you.
A final gotcha: we cannot define shrink
as simply
as this shrinks shrink
x = Nil:genericShrink
xNil
to Nil
, and shrinking will go into an
infinite loop.
If all this leaves you bewildered, you might try
to begin with,
after deriving shrink
= genericShrink
Generic
for your type. However, if your data type has any
special invariants, you will need to check that genericShrink
can't break those invariants.
Instances
class Arbitrary1 (f :: Type -> Type) where #
Lifting of the Arbitrary
class to unary type constructors.
liftArbitrary :: Gen a -> Gen (f a) #
liftShrink :: (a -> [a]) -> f a -> [f a] #
Instances
class Arbitrary2 (f :: Type -> Type -> Type) where #
Lifting of the Arbitrary
class to binary type constructors.
liftArbitrary2 :: Gen a -> Gen b -> Gen (f a b) #
liftShrink2 :: (a -> [a]) -> (b -> [b]) -> f a b -> [f a b] #
Instances
Arbitrary2 Either | |
Defined in Test.QuickCheck.Arbitrary liftArbitrary2 :: Gen a -> Gen b -> Gen (Either a b) # liftShrink2 :: (a -> [a]) -> (b -> [b]) -> Either a b -> [Either a b] # | |
Arbitrary2 (,) | |
Defined in Test.QuickCheck.Arbitrary liftArbitrary2 :: Gen a -> Gen b -> Gen (a, b) # liftShrink2 :: (a -> [a]) -> (b -> [b]) -> (a, b) -> [(a, b)] # | |
Arbitrary2 (Const :: Type -> Type -> Type) | |
Defined in Test.QuickCheck.Arbitrary liftArbitrary2 :: Gen a -> Gen b -> Gen (Const a b) # liftShrink2 :: (a -> [a]) -> (b -> [b]) -> Const a b -> [Const a b] # | |
Arbitrary2 (Constant :: Type -> Type -> Type) | |
Defined in Test.QuickCheck.Arbitrary liftArbitrary2 :: Gen a -> Gen b -> Gen (Constant a b) # liftShrink2 :: (a -> [a]) -> (b -> [b]) -> Constant a b -> [Constant a b] # |
class CoArbitrary a where #
Used for random generation of functions.
You should consider using Fun
instead, which
can show the generated functions as strings.
If you are using a recent GHC, there is a default definition of
coarbitrary
using genericCoarbitrary
, so if your type has a
Generic
instance it's enough to say
instance CoArbitrary MyType
You should only use genericCoarbitrary
for data types where
equality is structural, i.e. if you can't have two different
representations of the same value. An example where it's not
safe is sets implemented using binary search trees: the same
set can be represented as several different trees.
Here you would have to explicitly define
coarbitrary s = coarbitrary (toList s)
.
Nothing
coarbitrary :: a -> Gen b -> Gen b #
Used to generate a function of type a -> b
.
The first argument is a value, the second a generator.
You should use variant
to perturb the random generator;
the goal is that different values for the first argument will
lead to different calls to variant
. An example will help:
instance CoArbitrary a => CoArbitrary [a] where coarbitrary [] =variant
0 coarbitrary (x:xs) =variant
1 . coarbitrary (x,xs)
Instances
infiniteListOf :: Gen a -> Gen [a] #
Generates an infinite list.
Generates a non-empty list of random length. The maximum length depends on the size parameter.
Generates a list of random length. The maximum length depends on the size parameter.
growingElements :: [a] -> Gen a #
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.
frequency :: [(Int, Gen a)] -> Gen a #
Chooses one of the given generators, with a weighted random distribution. The input list must be non-empty.
Randomly uses one of the given generators. The input list must be non-empty.
suchThatMaybe :: Gen a -> (a -> Bool) -> Gen (Maybe a) #
Tries to generate a value that satisfies a predicate.
If it fails to do so after enough attempts, returns Nothing
.
suchThatMap :: Gen a -> (a -> Maybe b) -> Gen b #
Generates a value for which the given function returns a Just
, and then
applies the function.
Run a generator. The size passed to the generator is always 30;
if you want another size then you should explicitly use resize
.
scale :: (Int -> Int) -> Gen a -> Gen a #
Adjust the size parameter, by transforming it with the given function.
resize :: Int -> Gen a -> Gen a #
Overrides the size parameter. Returns a generator which uses the given size instead of the runtime-size parameter.
Returns the size parameter. Used to construct generators that depend on the size parameter.
For example, listOf
, which uses the size parameter as an upper bound on
length of lists it generates, can be defined like this:
listOf :: Gen a -> Gen [a] listOf gen = do n <- getSize k <- choose (0,n) vectorOf k gen
You can also do this using sized
.
sized :: (Int -> Gen a) -> Gen a #
Used to construct generators that depend on the size parameter.
For example, listOf
, which uses the size parameter as an upper bound on
length of lists it generates, can be defined like this:
listOf :: Gen a -> Gen [a] listOf gen = sized $ \n -> do k <- choose (0,n) vectorOf k gen
You can also do this using getSize
.
A generator for values of type a
.
The third-party packages
QuickCheck-GenT
and
quickcheck-transformer
provide monad transformer versions of Gen
.
Instances
Monad Gen | |
Functor Gen | |
MonadFix Gen | |
Defined in Test.QuickCheck.Gen | |
Applicative Gen | |
Testable prop => Testable (Gen prop) | |
Testable prop => Testable (Gen prop) Source # | |
Defined in Test.QuickCheck.Counterexamples type Counterexample (Gen prop) :: Type Source # property :: Gen prop -> PropertyFrom (Gen prop) Source # propertyForAllShrinkShow :: Show a => Gen a -> (a -> [a]) -> (a -> String) -> (a -> Gen prop) -> PropertyOf (a :&: Counterexample (Gen prop)) Source # | |
type Counterexample (Gen prop) Source # | |
Defined in Test.QuickCheck.Counterexamples |