| Copyright | (c) Conal Elliott 20072008 |
|---|---|
| License | BSD3 |
| Maintainer | conal@conal.net |
| Stability | experimental |
| Safe Haskell | None |
| Language | Haskell98 |
Test.QuickCheck.Checkers
Contents
Description
Some QuickCheck helpers
- type Test = (String, Property)
- type TestBatch = (String, [Test])
- unbatch :: TestBatch -> [Test]
- checkBatch :: Args -> TestBatch -> IO ()
- quickBatch :: TestBatch -> IO ()
- verboseBatch :: TestBatch -> IO ()
- type Unop a = a -> a
- type Binop a = a -> a -> a
- genR :: Random a => (a, a) -> Gen a
- involution :: (Show a, Arbitrary a, EqProp a) => (a -> a) -> Property
- inverseL :: (EqProp b, Arbitrary b, Show b) => (a -> b) -> (b -> a) -> Property
- inverse :: (EqProp a, Arbitrary a, Show a, EqProp b, Arbitrary b, Show b) => (a -> b) -> (b -> a) -> Property
- type FracT = Float
- type NumT = Int
- type OrdT = Int
- type T = Char
- class EqProp a where
- eq :: Eq a => a -> a -> Property
- type BinRel a = a -> a -> Bool
- reflexive :: (Arbitrary a, Show a) => BinRel a -> Property
- transitive :: (Arbitrary a, Show a) => BinRel a -> (a -> Gen a) -> Property
- symmetric :: (Arbitrary a, Show a) => BinRel a -> (a -> Gen a) -> Property
- antiSymmetric :: (Arbitrary a, Show a, Eq a) => BinRel a -> (a -> Gen a) -> Property
- leftId :: (Show a, Arbitrary a, EqProp a) => (i -> a -> a) -> i -> Property
- rightId :: (Show a, Arbitrary a, EqProp a) => (a -> i -> a) -> i -> Property
- bothId :: (Show a, Arbitrary a, EqProp a) => (a -> a -> a) -> a -> Property
- isAssoc :: (EqProp a, Show a, Arbitrary a) => (a -> a -> a) -> Property
- isCommut :: (EqProp a, Show a, Arbitrary a) => (a -> a -> a) -> Property
- commutes :: EqProp z => (a -> a -> z) -> a -> a -> Property
- data MonoidD a
- monoidD :: Monoid a => MonoidD a
- endoMonoidD :: MonoidD (a -> a)
- homomorphism :: (EqProp b, Show a, Arbitrary a) => MonoidD a -> MonoidD b -> (a -> b) -> [(String, Property)]
- idempotent :: (Show a, Arbitrary a, EqProp a) => (a -> a) -> Property
- idempotent2 :: (Show a, Arbitrary a, EqProp a) => (a -> a -> a) -> Property
- idemElem :: EqProp a => (a -> a -> a) -> a -> Property
- class Model a b | a -> b where
- meq :: (Model a b, EqProp b) => a -> b -> Property
- meq1 :: (Model a b, Model a1 b1, EqProp b) => (a1 -> a) -> (b1 -> b) -> a1 -> Property
- meq2 :: (Model a b, Model a1 b1, Model a2 b2, EqProp b) => (a1 -> a2 -> a) -> (b1 -> b2 -> b) -> a1 -> a2 -> Property
- meq3 :: (Model a b, Model a1 b1, Model a2 b2, Model a3 b3, EqProp b) => (a1 -> a2 -> a3 -> a) -> (b1 -> b2 -> b3 -> b) -> a1 -> a2 -> a3 -> Property
- meq4 :: (Model a b, Model a1 b1, Model a2 b2, Model a3 b3, Model a4 b4, EqProp b) => (a1 -> a2 -> a3 -> a4 -> a) -> (b1 -> b2 -> b3 -> b4 -> b) -> a1 -> a2 -> a3 -> a4 -> Property
- meq5 :: (Model a b, Model a1 b1, Model a2 b2, Model a3 b3, Model a4 b4, Model a5 b5, EqProp b) => (a1 -> a2 -> a3 -> a4 -> a5 -> a) -> (b1 -> b2 -> b3 -> b4 -> b5 -> b) -> a1 -> a2 -> a3 -> a4 -> a5 -> Property
- eqModels :: (Model a b, EqProp b) => a -> a -> Property
- class Model1 f g | f -> g where
- arbs :: Arbitrary a => Int -> IO [a]
- gens :: Int -> Gen a -> IO [a]
- (.&.) :: (Testable prop1, Testable prop2) => prop1 -> prop2 -> Property
- arbitrarySatisfying :: Arbitrary a => (a -> Bool) -> Gen a
Misc
checkBatch :: Args -> TestBatch -> IO () Source #
Run a batch of tests. See quickBatch and verboseBatch.
quickBatch :: TestBatch -> IO () Source #
Check a batch tersely.
verboseBatch :: TestBatch -> IO () Source #
Check a batch verbosely.
involution :: (Show a, Arbitrary a, EqProp a) => (a -> a) -> Property Source #
f is its own inverse. See also inverse.
inverseL :: (EqProp b, Arbitrary b, Show b) => (a -> b) -> (b -> a) -> Property Source #
f is a left inverse of g. See also inverse.
inverse :: (EqProp a, Arbitrary a, Show a, EqProp b, Arbitrary b, Show b) => (a -> b) -> (b -> a) -> Property Source #
f is a left and right inverse of g. See also inverseL.
Token Fractional type for tests
Generalized equality
Types of values that can be tested for equality, perhaps through random sampling.
Minimal complete definition
Instances
| EqProp Bool Source # | |
| EqProp Char Source # | |
| EqProp Double Source # | |
| EqProp Float Source # | |
| EqProp Int Source # | |
| EqProp () Source # | |
| EqProp a => EqProp [a] Source # | |
| EqProp a => EqProp (Maybe a) Source # | |
| (Show a, Arbitrary a, EqProp b) => EqProp (a -> b) Source # | |
| (EqProp a, EqProp b) => EqProp (Either a b) Source # | |
| (EqProp a, EqProp b) => EqProp (a, b) Source # | |
| (EqProp a, EqProp b, EqProp c) => EqProp (a, b, c) Source # | |
| (EqProp a, EqProp b, EqProp c, EqProp d) => EqProp (a, b, c, d) Source # | |
transitive :: (Arbitrary a, Show a) => BinRel a -> (a -> Gen a) -> Property Source #
Transitive property: a .
Generate rel b && b rel c ==> a rel ca randomly, but use gen a to generate b and gen b to
generate c. gen ought to satisfy rel fairly often.
symmetric :: (Arbitrary a, Show a) => BinRel a -> (a -> Gen a) -> Property Source #
Symmetric property: a . Generate rel b ==> b rel aa
randomly, but use gen a to generate b. gen ought to satisfy
rel fairly often.
antiSymmetric :: (Arbitrary a, Show a, Eq a) => BinRel a -> (a -> Gen a) -> Property Source #
Symmetric property: a . Generate
rel b && b rel a ==> a == ba randomly, but use gen a to generate b. gen ought to satisfy
both rel directions fairly often but not always.
leftId :: (Show a, Arbitrary a, EqProp a) => (i -> a -> a) -> i -> Property Source #
Has a given left identity, according to '(=-=)'
rightId :: (Show a, Arbitrary a, EqProp a) => (a -> i -> a) -> i -> Property Source #
Has a given right identity, according to '(=-=)'
bothId :: (Show a, Arbitrary a, EqProp a) => (a -> a -> a) -> a -> Property Source #
Has a given left and right identity, according to '(=-=)'
isAssoc :: (EqProp a, Show a, Arbitrary a) => (a -> a -> a) -> Property Source #
Associative, according to '(=-=)'
isCommut :: (EqProp a, Show a, Arbitrary a) => (a -> a -> a) -> Property Source #
Commutative, according to '(=-=)'
commutes :: EqProp z => (a -> a -> z) -> a -> a -> Property Source #
Commutative, according to '(=-=)'
endoMonoidD :: MonoidD (a -> a) Source #
Monoid dictionary for an unwrapped endomorphism. See also monoidD
and Endo.
homomorphism :: (EqProp b, Show a, Arbitrary a) => MonoidD a -> MonoidD b -> (a -> b) -> [(String, Property)] Source #
Homomorphism properties with respect to given monoid dictionaries.
See also monoidMorphism.
idempotent :: (Show a, Arbitrary a, EqProp a) => (a -> a) -> Property Source #
The unary function f is idempotent, i.e., f . f == f
idempotent2 :: (Show a, Arbitrary a, EqProp a) => (a -> a -> a) -> Property Source #
A binary function op is idempotent, i.e., x , for all op x == xx
idemElem :: EqProp a => (a -> a -> a) -> a -> Property Source #
A binary function op is has an idempotent element x, i.e.,
x op x == x
Model-based (semantics-based) testing
meq2 :: (Model a b, Model a1 b1, Model a2 b2, EqProp b) => (a1 -> a2 -> a) -> (b1 -> b2 -> b) -> a1 -> a2 -> Property Source #
meq3 :: (Model a b, Model a1 b1, Model a2 b2, Model a3 b3, EqProp b) => (a1 -> a2 -> a3 -> a) -> (b1 -> b2 -> b3 -> b) -> a1 -> a2 -> a3 -> Property Source #
meq4 :: (Model a b, Model a1 b1, Model a2 b2, Model a3 b3, Model a4 b4, EqProp b) => (a1 -> a2 -> a3 -> a4 -> a) -> (b1 -> b2 -> b3 -> b4 -> b) -> a1 -> a2 -> a3 -> a4 -> Property Source #
meq5 :: (Model a b, Model a1 b1, Model a2 b2, Model a3 b3, Model a4 b4, Model a5 b5, EqProp b) => (a1 -> a2 -> a3 -> a4 -> a5 -> a) -> (b1 -> b2 -> b3 -> b4 -> b5 -> b) -> a1 -> a2 -> a3 -> a4 -> a5 -> Property Source #
class Model1 f g | f -> g where Source #
Like Model but for unary type constructors.
Minimal complete definition
Some handy testing types
(.&.) :: (Testable prop1, Testable prop2) => prop1 -> prop2 -> Property infixr 1 #
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.