|
|
|
|
|
| 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 | | | | 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 | | model1 :: forall a. f a -> g a |
| | | arbs :: Arbitrary a => Int -> IO [a] | | | gens :: Int -> Gen a -> IO [a] | | | .&. | | | arbitrarySatisfying :: Arbitrary a => (a -> Bool) -> Gen a |
|
|
|
| Misc
|
|
|
| Named test
|
|
|
| Named batch of tests
|
|
|
| Flatten a test batch for inclusion in another
|
|
|
| Run a batch of tests. See quickBatch and verboseBatch.
|
|
|
| Check a batch tersely.
|
|
|
| Check a batch verbosely.
|
|
|
| Unary function, handy for type annotations
|
|
| type Binop a = a -> a -> a | Source |
|
| Binary function, handy for type annotations
|
|
|
|
|
| f is a left inverse of g. See also inverse.
|
|
|
| f is a left and right inverse of g. See also inverseL.
|
|
|
| Token Fractional type for tests
|
|
|
| Token Num type for tests
|
|
|
| Token Ord type for tests
|
|
|
| Token uninteresting type for tests
|
|
| Generalized equality
|
|
|
| Types of values that can be tested for equality, perhaps through
random sampling.
| | | Methods | | | Instances | |
|
|
|
| For Eq types as EqProp types
|
|
|
|
|
| Reflexive property: a rel a
|
|
|
| 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 property: a rel b ==> b rel a. Generate a
randomly, but use gen a to generate b. gen ought to satisfy
rel fairly often.
|
|
|
| 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.
|
|
|
| Has a given left identity, according to '(=-=)'
|
|
|
| Has a given right identity, according to '(=-=)'
|
|
|
| Has a given left and right identity, according to '(=-=)'
|
|
|
| Associative, according to '(=-=)'
|
|
|
| Commutative, according to '(=-=)'
|
|
|
| Commutative, according to '(=-=)'
|
|
|
| Explicit Monoid dictionary. Doesn't have to correspond to an
actual Monoid instance, though see monoidD.
|
|
|
|
| Monoid dictionary built from the Monoid methods.
|
|
|
| Monoid dictionary for an unwrapped endomorphism. See also monoidD
and Endo.
|
|
|
| Homomorphism properties with respect to given monoid dictionaries.
See also monoidMorphism.
|
|
|
| The unary function f is idempotent, i.e., f . f == f
|
|
|
| A binary function op is idempotent, i.e., x op x == x, for all x
|
|
|
| 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 where | Source |
|
| | Methods | | | Instances | |
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
|
| class Model1 f g | f -> g where | Source |
|
| Like Model but for unary type constructors.
| | | Methods | | model1 :: forall a. f a -> g a | Source |
|
|
|
|
| Some handy testing types
|
|
|
| Generate n arbitrary values
|
|
|
| Produce n values from a generator
|
|
| .&. |
|
|
|
| Produced by Haddock version 2.4.2 |