checkers-0.1.1: Check properties on standard classes and data structures.

Stabilityexperimental
Maintainerconal@conal.net

Test.QuickCheck.Checkers

Contents

Description

Some QuickCheck helpers

Synopsis

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 :: Config -> 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 = CharSource

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

Instances

EqProp Bool 
EqProp Char 
EqProp Double 
EqProp Int 
EqProp a => EqProp [a] 
EqProp a => EqProp (Maybe a) 
(Show a, Arbitrary a, EqProp b) => EqProp (a -> b) 
(EqProp a, EqProp b) => EqProp (Either a b) 
(EqProp a, EqProp b) => EqProp (a, b) 

eq :: Eq a => a -> a -> PropertySource

For Eq types as EqProp types

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

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

newtype NonZero a Source

Constructors

NonZero 

Fields

unNonZero :: a
 

Instances

Enum a => Enum (NonZero a) 
Eq a => Eq (NonZero a) 
Integral a => Integral (NonZero a) 
Num a => Num (NonZero a) 
Ord a => Ord (NonZero a) 
Read a => Read (NonZero a) 
Real a => Real (NonZero a) 
Show a => Show (NonZero a) 
(Num a, Arbitrary a) => Arbitrary (NonZero a) 

newtype NonNegative a Source

Constructors

NonNegative 

Fields

unNonNegative :: a
 

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, Arbitrary a) => Arbitrary (NonNegative a) 

suchThat :: Gen a -> (a -> Bool) -> Gen aSource

Generates a value that satisfies a predicate.

suchThatMaybe :: Gen a -> (a -> Bool) -> Gen (Maybe a)Source

Tries to generate a value that satisfies a predicate.

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

Property conjunction