checkers-0.2.4: Check properties on standard classes and data structures.Source codeContentsIndex
Test.QuickCheck.Checkers
Stabilityexperimental
Maintainerconal@conal.net
Contents
Misc
Generalized equality
Model-based (semantics-based) testing
Some handy testing types
Description
Some QuickCheck helpers
Synopsis
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
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
(=-=) :: a -> a -> Property
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
model :: a -> b
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
model1 :: forall a. f a -> g a
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
type Test = (String, Property)Source
Named test
type TestBatch = (String, [Test])Source
Named batch of tests
unbatch :: TestBatch -> [Test]Source
Flatten a test batch for inclusion in another
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.
type Unop a = a -> aSource
Unary function, handy for type annotations
type Binop a = a -> a -> aSource
Binary function, handy for type annotations
genR :: Random a => (a, a) -> Gen aSource
inverseL :: (EqProp b, Arbitrary b, Show b) => (a -> b) -> (b -> a) -> PropertySource
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) -> PropertySource
f is a left and right inverse of g. See also inverseL.
type FracT = FloatSource
Token Fractional type for tests
type NumT = IntSource
Token Num type for tests
type OrdT = IntSource
Token Ord type for tests
type T = CharSource
Token uninteresting type for tests
Generalized equality
class EqProp a whereSource
Types of values that can be tested for equality, perhaps through random sampling.
Methods
(=-=) :: a -> a -> PropertySource
show/hide Instances
eq :: Eq a => a -> a -> PropertySource
For Eq types as EqProp types
type BinRel a = a -> a -> BoolSource
reflexive :: (Arbitrary a, Show a) => BinRel a -> PropertySource
Reflexive property: a rel a
transitive :: (Arbitrary a, Show a) => BinRel a -> (a -> Gen a) -> PropertySource
Transitive property: a rel b && b rel c ==> a rel c. Generate a 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) -> PropertySource
Symmetric property: a rel b ==> b rel a. Generate a 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) -> PropertySource
Symmetric property: a rel b && b rel a ==> a == b. Generate a 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 -> PropertySource
Has a given left identity, according to '(=-=)'
rightId :: (Show a, Arbitrary a, EqProp a) => (a -> i -> a) -> i -> PropertySource
Has a given right identity, according to '(=-=)'
bothId :: (Show a, Arbitrary a, EqProp a) => (a -> a -> a) -> a -> PropertySource
Has a given left and right identity, according to '(=-=)'
isAssoc :: (EqProp a, Show a, Arbitrary a) => (a -> a -> a) -> PropertySource
Associative, according to '(=-=)'
isCommut :: (EqProp a, Show a, Arbitrary a) => (a -> a -> a) -> PropertySource
Commutative, according to '(=-=)'
commutes :: EqProp z => (a -> a -> z) -> a -> a -> PropertySource
Commutative, according to '(=-=)'
data MonoidD a Source
Explicit Monoid dictionary. Doesn't have to correspond to an actual Monoid instance, though see monoidD.
monoidD :: Monoid a => MonoidD aSource
Monoid dictionary built from the Monoid methods.
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) -> PropertySource
The unary function f is idempotent, i.e., f . f == f
idempotent2 :: (Show a, Arbitrary a, EqProp a) => (a -> a -> a) -> PropertySource
A binary function op is idempotent, i.e., x op x == x, for all x
idemElem :: EqProp a => (a -> a -> a) -> a -> PropertySource
A binary function op is has an idempotent element x, i.e., x op x == x
Model-based (semantics-based) testing
class Model a b | a -> b whereSource
Methods
model :: a -> bSource
show/hide Instances
meq :: (Model a b, EqProp b) => a -> b -> PropertySource
meq1 :: (Model a b, Model a1 b1, EqProp b) => (a1 -> a) -> (b1 -> b) -> a1 -> PropertySource
meq2 :: (Model a b, Model a1 b1, Model a2 b2, EqProp b) => (a1 -> a2 -> a) -> (b1 -> b2 -> b) -> a1 -> a2 -> PropertySource
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 -> PropertySource
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 -> PropertySource
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 -> PropertySource
eqModels :: (Model a b, EqProp b) => a -> a -> PropertySource
class Model1 f g | f -> g whereSource
Like Model but for unary type constructors.
Methods
model1 :: forall a. f a -> g aSource
Some handy testing types
arbs :: Arbitrary a => Int -> IO [a]Source
Generate n arbitrary values
gens :: Int -> Gen a -> IO [a]Source
Produce n values from a generator
(.&.) :: (Testable prop1, Testable prop2) => prop1 -> prop2 -> PropertySource
arbitrarySatisfying :: Arbitrary a => (a -> Bool) -> Gen aSource
Produced by Haddock version 2.6.0