leancheck-0.3.0: Cholesterol-free property-based testing

Safe HaskellNone
LanguageHaskell2010

Test.Check

Contents

Description

A simple property-based testing library based on enumeration of values via lists of lists.

In the context of this library, a property is a function returning a Bool that should return True for all input values.

To check if a property holds by testing a thousand values, you simply do:

holds 1000 property  -- yield True when Ok, False otherwise

For example:

holds $ \xs -> length (sort xs) == length (xs::[Int])

Arguments of properties should be instances of the Listable typeclass. Listable instances are provided for the most common Haskell types. New instances are easily defined (see the Listables documentation for more info).

Synopsis

Checking and testing

holds :: Testable a => Int -> a -> Bool Source

Does a property hold for a number of test values?

holds 1000 $ \xs -> length (sort xs) == length xs

fails :: Testable a => Int -> a -> Bool Source

Does a property fail for a number of test values?

fails 1000 $ \xs -> xs ++ ys == ys ++ xs

exists :: Testable a => Int -> a -> Bool Source

There exists and assignment of values that satisfy a property?

Boolean (property) operators

(==>) :: Bool -> Bool -> Bool infixr 0 Source

Boolean implication. Use this for defining conditional properties:

prop_something x y = condition x y ==> something x y

Counterexamples and witnesses

counterExample :: Testable a => Int -> a -> Maybe [String] Source

For a number of tests to a property, returns Just the first counter-example or Nothing.

counterExamples :: Testable a => Int -> a -> [[String]] Source

Lists all counter-examples for a number of tests to a property,

witness :: Testable a => Int -> a -> Maybe [String] Source

For a number of tests to a property, returns Just the first witness or Nothing.

witnesses :: Testable a => Int -> a -> [[String]] Source

Lists all witnesses for a number of tests to a property,

Listing test values

class Listable a where Source

A type is Listable when there exists a function that is able to list (ideally all of) its values.

Ideally, this type should be defined by a tiers function that returns a (possibly infinite) list of finite sub-lists (tiers): the first sub-list contains elements of size 0, the second sub-list contains elements of size 1 and so on. Size here is defined by the implementor of the type-class instance.

For algebraic data types, the general form for tiers is:

tiers = consN ConstructorA
     \/ consN ConstructorB
     \/ consN ConstructorC
     \/ ...

When defined by list, each sub-list in tiers is a singleton list (each element of list has +1 size).

The function deriveListable from Test.Check.Derive can automatically derive instances of this typeclass.

A Listable instance for functions is also available but is not exported by default. Import Test.Check.Function for that. (Test.Check.Function.Show for a Show instance for functions)

Minimal complete definition

list | tiers

Methods

tiers :: [[a]] Source

list :: [a] Source

Listing constructors

cons0 :: a -> [[a]] Source

Takes a constructor with no arguments and return tiers (with a single value). This value, by default, has size/weight 0.

cons1 :: Listable a => (a -> b) -> [[b]] Source

Takes a constructor with one argument and return tiers of that value. This value, by default, has size/weight 1.

cons2 :: (Listable a, Listable b) => (a -> b -> c) -> [[c]] Source

Takes a constructor with two arguments and return tiers of that value. This value, by default, has size/weight 1.

cons3 :: (Listable a, Listable b, Listable c) => (a -> b -> c -> d) -> [[d]] Source

cons4 :: (Listable a, Listable b, Listable c, Listable d) => (a -> b -> c -> d -> e) -> [[e]] Source

cons5 :: (Listable a, Listable b, Listable c, Listable d, Listable e) => (a -> b -> c -> d -> e -> f) -> [[f]] Source

cons6 :: (Listable a, Listable b, Listable c, Listable d, Listable e, Listable f) => (a -> b -> c -> d -> e -> f -> g) -> [[g]] Source

cons7 :: (Listable a, Listable b, Listable c, Listable d, Listable e, Listable f, Listable g) => (a -> b -> c -> d -> e -> f -> g -> h) -> [[h]] Source

cons8 :: (Listable a, Listable b, Listable c, Listable d, Listable e, Listable f, Listable g, Listable h) => (a -> b -> c -> d -> e -> f -> g -> h -> i) -> [[i]] Source

cons9 :: (Listable a, Listable b, Listable c, Listable d, Listable e, Listable f, Listable g, Listable h, Listable i) => (a -> b -> c -> d -> e -> f -> g -> h -> i -> j) -> [[j]] Source

cons10 :: (Listable a, Listable b, Listable c, Listable d, Listable e, Listable f, Listable g, Listable h, Listable i, Listable j) => (a -> b -> c -> d -> e -> f -> g -> h -> i -> j -> k) -> [[k]] Source

cons11 :: (Listable a, Listable b, Listable c, Listable d, Listable e, Listable f, Listable g, Listable h, Listable i, Listable j, Listable k) => (a -> b -> c -> d -> e -> f -> g -> h -> i -> j -> k -> l) -> [[l]] Source

cons12 :: (Listable a, Listable b, Listable c, Listable d, Listable e, Listable f, Listable g, Listable h, Listable i, Listable j, Listable k, Listable l) => (a -> b -> c -> d -> e -> f -> g -> h -> i -> j -> k -> l -> m) -> [[m]] Source

ofWeight :: [[a]] -> Int -> [[a]] Source

Resets the weight of a constructor (or tiers) Typically used as an infix constructor when defining Listable instances:

cons<N> `ofWeight` W

Be careful: do not apply ofWeight 0 to recursive data structure constructors. In general this will make the list of size 0 infinite, breaking the tier invariant (each tier must be finite).

addWeight :: [[a]] -> Int -> [[a]] Source

Adds to the weight of tiers of a constructor

suchThat :: [[a]] -> (a -> Bool) -> [[a]] Source

Tiers of values that follow a property

cons<N> `suchThat` condition

Combining tiers

(\/) :: [[a]] -> [[a]] -> [[a]] infixr 7 Source

Append tiers.

[xs,ys,zs,...] \/ [as,bs,cs,...] = [xs++as,ys++bs,zs++cs,...]

(\\//) :: [[a]] -> [[a]] -> [[a]] infixr 7 Source

Interleave tiers. When in doubt, use / instead.

[xs,ys,zs,...] \/ [as,bs,cs,...] = [xs+|as,ys+|bs,zs+|cs,...]

(><) :: [[a]] -> [[b]] -> [[(a, b)]] infixr 8 Source

Take a tiered product of lists of tiers.

[t0,t1,t2,...] >< [u0,u1,u2,...] =
[ t0**u0
, t0**u1 ++ t1**u0
, t0**u2 ++ t1**u1 ++ t2**u0
, ...       ...       ...       ...
where xs ** ys = [(x,y) | x <- xs, y <- ys]

Example:

[[0],[1],[2],...] >< [[0],[1],[2],...]
== [  [(0,0)]
   ,  [(1,0),(0,1)]
   ,  [(2,0),(1,1),(0,2)]
   ,  [(3,0),(2,1),(1,2),(0,3)]
   ...
   ]

productWith :: (a -> b -> c) -> [[a]] -> [[b]] -> [[c]] Source

Take the product of two lists of tiers.

productWith f xss yss = map (uncurry f) $ xss >< yss

Manipulating tiers

mapT :: (a -> b) -> [[a]] -> [[b]] Source

map over tiers

filterT :: (a -> Bool) -> [[a]] -> [[a]] Source

filter tiers

concatT :: [[[[a]]]] -> [[a]] Source

concat tiers of tiers

concatMapT :: (a -> [[b]]) -> [[a]] -> [[b]] Source

concatMap over tiers

deleteT :: Eq a => a -> [[a]] -> [[a]] Source

Delete the first occurence of an element in a tier, for tiers without repetitions:

deleteT x === normalizeT . (`suchThat` (/= x))

normalizeT :: [[a]] -> [[a]] Source

toTiers :: [a] -> [[a]] Source

Takes a list of values xs and transform it into tiers on which each tier is occupied by a single element from xs.

To convert back to a list, just concat.

Automatically deriving Listable instances

deriveListable :: Name -> DecsQ Source

Derives a Listable instance for a given type (Name).

Extra constructors

consFromList :: Listable a => ([a] -> b) -> [[b]] Source

Given a constructor for a type that takes a list, return tiers for that type.

consFromAscendingList :: Listable a => ([a] -> b) -> [[b]] Source

consFromStrictlyAscendingList :: Listable a => ([a] -> b) -> [[b]] Source

Given a constructor for a type that takes a list with strictly ascending elements, return tiers of that type (e.g.: a Set type).

consFromSet :: Listable a => ([a] -> b) -> [[b]] Source

Given a constructor for a type that takes a set of elements (as a list) return tiers of that type (e.g.: a Set type).

consFromNoDupList :: Listable a => ([a] -> b) -> [[b]] Source

Given a constructor for a type that takes a list with no duplicate elements, return tiers of that type.

Products of tiers

product3With :: (a -> b -> c -> d) -> [[a]] -> [[b]] -> [[c]] -> [[d]] Source

Like product, but over 3 lists of tiers.

productMaybeWith :: (a -> b -> Maybe c) -> [[a]] -> [[b]] -> [[c]] Source

Take the product of lists of tiers by a function returning a maybe value.

Listing lists

listsOf :: [[a]] -> [[[a]]] Source

Given tiers of values, returns tiers of lists of those values

listsOf [[]] == [[[]]]
listsOf [[x]] == [ [[]]
                 , [[x]]
                 , [[x,x]]
                 , [[x,x,x]]
                 , ...
                 ]
listsOf [[x],[y]] == [ [[]]
                     , [[x]]
                     , [[x,x],[y]]
                     , [[x,x,x],[x,y],[y,x]]
                     , ...
                     ]

setsOf :: [[a]] -> [[[a]]] Source

Returns tiers of sets represented as lists of values (no repeated sets). Shorthand for strictlyAscendingListsOf.

ascendingListsOf :: [[a]] -> [[[a]]] Source

Given tiers of values, returns tiers of lists of elements in ascending order (from tiered enumeration).

strictlyAscendingListsOf :: [[a]] -> [[[a]]] Source

Given tiers of values, returns tiers of lists of elements in strictly ascending order (from tiered enumeration). If you only care about whether elements are in returned lists, this returns the tiers of all sets of values.

strictlyAscendingListsOf [[0],[1],[2],...] ==
  [ [[]]
  , [[0]]
  , [[1]]
  , [[0,1],[2]]
  , [[0,2],[3]]
  , [[0,3],[1,2],[4]]
  , [[0,1,2],[0,4],[1,3],[5]]
  , ...
  ]

noDupListsOf :: [[a]] -> [[[a]]] Source

Given tiers of values, returns tiers of lists with no repeated elements.

noDupListsOf [[0],[1],[2],...] ==
  [ [[]]
  , [[0]]
  , [[1]]
  , [[0,1],[1,0],[2]]
  , [[0,2],[2,0],[3]]
  , ...
  ]

products :: [[[a]]] -> [[[a]]] Source

Generates several lists of the same size.

products [ xss, yss, zss ] ==

Tiers of all lists combining elements of tiers: xss, yss and zss

listsOfLength :: Int -> [[a]] -> [[[a]]] Source

Given tiers, returns tiers of lists of a given length.

Listing values

tiersFractional :: Fractional a => [[a]] Source

Tiers of Fractional values. This can be used as the implementation of tiers for Fractional types.

listIntegral :: (Enum a, Num a) => [a] Source

(+|) :: [a] -> [a] -> [a] infixr 5 Source

Lazily interleaves two lists, switching between elements of the two. Union/sum of the elements in the lists.

[x,y,z] +| [a,b,c] == [x,a,y,b,z,c]

Test results

class Testable a Source

Testable values are functions of Listable arguments that return boolean values, e.g.:

  •  Bool
  •  Int -> Bool
  •  Listable a => a -> a -> Bool

Minimal complete definition

resultiers

Instances

results :: Testable a => a -> [([String], Bool)] Source

List all results of a Testable property. Each results is composed by a list of strings and a boolean. The list of strings represents the arguments applied to the function. The boolean tells whether the property holds for that selection of argument. This list is usually infinite.