leancheck-0.3.0: Cholesterol-free property-based testing

Safe HaskellSafe
LanguageHaskell2010

Test.Check.Core

Contents

Description

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

This is the core module of the library, with the most basic definitions. If you are looking just to use the library, import and see Test.Check.

If you want to understand how the code works, this is the place to start.

Other important modules:

Test.Check.Basic re-exports (almost) everything from this module along with constructors and instances for further arities.

Test.Check.Utils re-exports Test.Check.Basic along with functions for advanced Listable instance definitions.

Test.Check re-exports Test.Check.Utils along with a TH function to automatically derive Listable instances.

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?

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,

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.

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

Constructing lists of tiers

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

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 lists of 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 lists of 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

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.

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

Misc utilities

(+|) :: [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]

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

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

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