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

Copyright(c) Conal Elliott 20072008
LicenseBSD3
Maintainerconal@conal.net
Stabilityexperimental
Safe HaskellNone
LanguageHaskell2010

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 :: 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 -> a Source #

Unary function, handy for type annotations

type Binop a = a -> a -> a Source #

Binary function, handy for type annotations

genR :: Random a => (a, a) -> Gen a Source #

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.

type FracT = Float Source #

Token Fractional type for tests

type NumT = Int Source #

Token Num type for tests

type OrdT = Int Source #

Token Ord type for tests

type T = Char Source #

Token uninteresting type for tests

Generalized equality

class EqProp a where Source #

Types of values that can be tested for equality, perhaps through random sampling.

Minimal complete definition

Nothing

Methods

(=-=) :: a -> a -> Property infix 4 Source #

(=-=) :: (Generic a, GEqProp (Rep a)) => a -> a -> Property infix 4 Source #

Instances
EqProp Bool Source # 
Instance details

Defined in Test.QuickCheck.Checkers

Methods

(=-=) :: Bool -> Bool -> Property Source #

EqProp Char Source # 
Instance details

Defined in Test.QuickCheck.Checkers

Methods

(=-=) :: Char -> Char -> Property Source #

EqProp Double Source # 
Instance details

Defined in Test.QuickCheck.Checkers

EqProp Float Source # 
Instance details

Defined in Test.QuickCheck.Checkers

Methods

(=-=) :: Float -> Float -> Property Source #

EqProp Int Source # 
Instance details

Defined in Test.QuickCheck.Checkers

Methods

(=-=) :: Int -> Int -> Property Source #

EqProp Integer Source # 
Instance details

Defined in Test.QuickCheck.Checkers

EqProp Ordering Source # 
Instance details

Defined in Test.QuickCheck.Checkers

EqProp () Source # 
Instance details

Defined in Test.QuickCheck.Checkers

Methods

(=-=) :: () -> () -> Property Source #

EqProp All Source # 
Instance details

Defined in Test.QuickCheck.Checkers

Methods

(=-=) :: All -> All -> Property Source #

EqProp Any Source # 
Instance details

Defined in Test.QuickCheck.Checkers

Methods

(=-=) :: Any -> Any -> Property Source #

EqProp a => EqProp [a] Source # 
Instance details

Defined in Test.QuickCheck.Checkers

Methods

(=-=) :: [a] -> [a] -> Property Source #

EqProp a => EqProp (Maybe a) Source # 
Instance details

Defined in Test.QuickCheck.Checkers

Methods

(=-=) :: Maybe a -> Maybe a -> Property Source #

Eq a => EqProp (Ratio a) Source # 
Instance details

Defined in Test.QuickCheck.Checkers

Methods

(=-=) :: Ratio a -> Ratio a -> Property Source #

Eq a => EqProp (Complex a) Source # 
Instance details

Defined in Test.QuickCheck.Checkers

Methods

(=-=) :: Complex a -> Complex a -> Property Source #

EqProp a => EqProp (Min a) Source # 
Instance details

Defined in Test.QuickCheck.Checkers

Methods

(=-=) :: Min a -> Min a -> Property Source #

EqProp a => EqProp (Max a) Source # 
Instance details

Defined in Test.QuickCheck.Checkers

Methods

(=-=) :: Max a -> Max a -> Property Source #

EqProp a => EqProp (First a) Source # 
Instance details

Defined in Test.QuickCheck.Checkers

Methods

(=-=) :: First a -> First a -> Property Source #

EqProp a => EqProp (Last a) Source # 
Instance details

Defined in Test.QuickCheck.Checkers

Methods

(=-=) :: Last a -> Last a -> Property Source #

EqProp a => EqProp (ZipList a) Source # 
Instance details

Defined in Test.QuickCheck.Checkers

Methods

(=-=) :: ZipList a -> ZipList a -> Property Source #

EqProp a => EqProp (Identity a) Source # 
Instance details

Defined in Test.QuickCheck.Checkers

Methods

(=-=) :: Identity a -> Identity a -> Property Source #

EqProp a => EqProp (Dual a) Source # 
Instance details

Defined in Test.QuickCheck.Checkers

Methods

(=-=) :: Dual a -> Dual a -> Property Source #

(Show a, Arbitrary a, EqProp a) => EqProp (Endo a) Source # 
Instance details

Defined in Test.QuickCheck.Checkers

Methods

(=-=) :: Endo a -> Endo a -> Property Source #

EqProp a => EqProp (Sum a) Source # 
Instance details

Defined in Test.QuickCheck.Checkers

Methods

(=-=) :: Sum a -> Sum a -> Property Source #

EqProp a => EqProp (Product a) Source # 
Instance details

Defined in Test.QuickCheck.Checkers

Methods

(=-=) :: Product a -> Product a -> Property Source #

EqProp a => EqProp (NonEmpty a) Source # 
Instance details

Defined in Test.QuickCheck.Checkers

Methods

(=-=) :: NonEmpty a -> NonEmpty a -> Property Source #

(Show a, Arbitrary a, EqProp b) => EqProp (a -> b) Source # 
Instance details

Defined in Test.QuickCheck.Checkers

Methods

(=-=) :: (a -> b) -> (a -> b) -> Property Source #

(EqProp a, EqProp b) => EqProp (Either a b) Source # 
Instance details

Defined in Test.QuickCheck.Checkers

Methods

(=-=) :: Either a b -> Either a b -> Property Source #

(EqProp a, EqProp b) => EqProp (a, b) Source # 
Instance details

Defined in Test.QuickCheck.Checkers

Methods

(=-=) :: (a, b) -> (a, b) -> Property Source #

EqProp (Proxy a) Source # 
Instance details

Defined in Test.QuickCheck.Checkers

Methods

(=-=) :: Proxy a -> Proxy a -> Property Source #

(EqProp a, EqProp b, EqProp c) => EqProp (a, b, c) Source # 
Instance details

Defined in Test.QuickCheck.Checkers

Methods

(=-=) :: (a, b, c) -> (a, b, c) -> Property Source #

EqProp a => EqProp (Const a b) Source # 
Instance details

Defined in Test.QuickCheck.Checkers

Methods

(=-=) :: Const a b -> Const a b -> Property Source #

EqProp (f a) => EqProp (Ap f a) Source # 
Instance details

Defined in Test.QuickCheck.Checkers

Methods

(=-=) :: Ap f a -> Ap f a -> Property Source #

EqProp (f a) => EqProp (Alt f a) Source # 
Instance details

Defined in Test.QuickCheck.Checkers

Methods

(=-=) :: Alt f a -> Alt f a -> Property Source #

(EqProp a, EqProp b, EqProp c, EqProp d) => EqProp (a, b, c, d) Source # 
Instance details

Defined in Test.QuickCheck.Checkers

Methods

(=-=) :: (a, b, c, d) -> (a, b, c, d) -> Property Source #

(EqProp (f a), EqProp (g a)) => EqProp (Product f g a) Source # 
Instance details

Defined in Test.QuickCheck.Checkers

Methods

(=-=) :: Product f g a -> Product f g a -> Property Source #

(EqProp (f a), EqProp (g a)) => EqProp (Sum f g a) Source # 
Instance details

Defined in Test.QuickCheck.Checkers

Methods

(=-=) :: Sum f g a -> Sum f g a -> Property Source #

EqProp (f (g a)) => EqProp (Compose f g a) Source # 
Instance details

Defined in Test.QuickCheck.Checkers

Methods

(=-=) :: Compose f g a -> Compose f g a -> Property Source #

eq :: Eq a => a -> a -> Property Source #

For Eq types as EqProp types

type BinRel a = a -> a -> Bool Source #

reflexive :: (Arbitrary a, Show a) => BinRel a -> Property Source #

Reflexive property: a rel a

transitive :: (Arbitrary a, Show a) => BinRel a -> (a -> Gen a) -> Property Source #

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) -> Property Source #

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 -> Property Source #

Antisymmetric property: (a rel b) && (a /= b) ==> not (b rel a).

Since: 0.5.0

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 '(=-=)'

data MonoidD a Source #

Explicit Monoid dictionary. Doesn't have to correspond to an actual Monoid instance, though see monoidD.

monoidD :: Monoid a => MonoidD a Source #

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) -> 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 op x == x, for all x

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

class Model a b | a -> b where Source #

Methods

model :: a -> b Source #

Instances
Model Bool Bool Source # 
Instance details

Defined in Test.QuickCheck.Checkers

Methods

model :: Bool -> Bool Source #

Model Char Char Source # 
Instance details

Defined in Test.QuickCheck.Checkers

Methods

model :: Char -> Char Source #

Model Double Double Source # 
Instance details

Defined in Test.QuickCheck.Checkers

Methods

model :: Double -> Double Source #

Model Float Float Source # 
Instance details

Defined in Test.QuickCheck.Checkers

Methods

model :: Float -> Float Source #

Model Int Int Source # 
Instance details

Defined in Test.QuickCheck.Checkers

Methods

model :: Int -> Int Source #

Model String String Source # 
Instance details

Defined in Test.QuickCheck.Checkers

Methods

model :: String -> String Source #

Model b b' => Model (a -> b) (a -> b') Source # 
Instance details

Defined in Test.QuickCheck.Checkers

Methods

model :: (a -> b) -> a -> b' Source #

(Model a b, Model a' b') => Model (a, a') (b, b') Source # 
Instance details

Defined in Test.QuickCheck.Checkers

Methods

model :: (a, a') -> (b, b') Source #

meq :: (Model a b, EqProp b) => a -> b -> Property Source #

meq1 :: (Model a b, Model a1 b1, EqProp b) => (a1 -> a) -> (b1 -> b) -> a1 -> Property Source #

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 #

eqModels :: (Model a b, EqProp b) => a -> a -> Property Source #

denotationFor :: (Model b b', Arbitrary a, EqProp b', Show a) => (a -> b') -> (a -> b) -> TestBatch Source #

f `denotationFor' g proves that f is a model for g, ie that model . g =-= f.

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

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 -> 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.

Orphan instances

Testable a => Testable [a] Source # 
Instance details

Methods

property :: [a] -> Property #

propertyForAllShrinkShow :: Gen a0 -> (a0 -> [a0]) -> (a0 -> [String]) -> (a0 -> [a]) -> Property #

(Testable a, Testable b) => Testable (a, b) Source # 
Instance details

Methods

property :: (a, b) -> Property #

propertyForAllShrinkShow :: Gen a0 -> (a0 -> [a0]) -> (a0 -> [String]) -> (a0 -> (a, b)) -> Property #