leancheck-0.6.0: Cholesterol-free property-based testing

Safe HaskellNone
LanguageHaskell2010

Test.LeanCheck

Contents

Description

LeanCheck is a simple enumerative property-based testing library.

A property is a function returning a Bool that should be True for all possible choices of arguments. Properties can be viewed as a parameterized unit tests.

To check if a property holds by testing up to a thousand values, we evaluate:

holds 1000 property

True indicates success. False indicates a bug.

For example:

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

To get the smallest counterExample by testing up to a thousand values, we evaluate:

counterExample 1000 property

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 Listable for more info).

Synopsis

Checking and testing

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

Does a property hold up to 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 an assignment of values that satisfies a property up to a number of test values?

exists 1000 $ \x -> x > 10

Boolean (property) operators

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

Boolean implication operator. Useful 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 #

Up to a number of tests to a property, returns Just the first counter-example or Nothing if there is none.

counterExample 100 $ \xs -> [] `union` xs == (xs::[Int])
-- > Just ["[0,0]"]

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 #

Up to a number of tests to a property, returns Just the first witness or Nothing if there is none.

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

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

Reporting

check :: Testable a => a -> IO () Source #

Checks a property printing results on stdout

> check $ \xs -> sort (sort xs) == sort (xs::[Int])
+++ OK, passed 200 tests.
> check $ \xs ys -> xs `union` ys == ys `union` (xs::[Int])
*** Failed! Falsifiable (after 4 tests):
[] [0,0]

checkFor :: Testable a => Int -> a -> IO () Source #

Check a property for a given number of tests printing results on stdout

checkResult :: Testable a => a -> IO Bool Source #

Check a property printing results on stdout and returning True on success.

There is no option to silence this function: for silence, you should use holds.

checkResultFor :: Testable a => Int -> a -> IO Bool Source #

Check a property for a given number of tests printing results on stdout and returning True on success.

There is no option to silence this function: for silence, you should use holds.

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, instances should be defined by a tiers function that returns a (potentially 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 = cons<N> ConstructorA
     \/ cons<N> ConstructorB
     \/ ...
     \/ cons<N> ConstructorZ

where N is the number of arguments of each constructor A...Z.

Instances can be alternatively defined by list. In this case, each sub-list in tiers is a singleton list (each succeeding element of list has +1 size).

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

A Listable instance for functions is also available but is not exported by default. Import Test.LeanCheck.Function if you need to test higher-order properties.

Minimal complete definition

list | tiers

Methods

tiers :: [[a]] Source #

list :: [a] Source #

Instances

Listable Bool Source # 

Methods

tiers :: [[Bool]] Source #

list :: [Bool] Source #

Listable Char Source # 

Methods

tiers :: [[Char]] Source #

list :: [Char] Source #

Listable Double Source # 

Methods

tiers :: [[Double]] Source #

list :: [Double] Source #

Listable Float Source # 

Methods

tiers :: [[Float]] Source #

list :: [Float] Source #

Listable Int Source # 

Methods

tiers :: [[Int]] Source #

list :: [Int] Source #

Listable Integer Source # 

Methods

tiers :: [[Integer]] Source #

list :: [Integer] Source #

Listable Ordering Source # 
Listable () Source # 

Methods

tiers :: [[()]] Source #

list :: [()] Source #

Listable Nat7 Source # 

Methods

tiers :: [[Nat7]] Source #

list :: [Nat7] Source #

Listable Nat6 Source # 

Methods

tiers :: [[Nat6]] Source #

list :: [Nat6] Source #

Listable Nat5 Source # 

Methods

tiers :: [[Nat5]] Source #

list :: [Nat5] Source #

Listable Nat4 Source # 

Methods

tiers :: [[Nat4]] Source #

list :: [Nat4] Source #

Listable Nat3 Source # 

Methods

tiers :: [[Nat3]] Source #

list :: [Nat3] Source #

Listable Nat2 Source # 

Methods

tiers :: [[Nat2]] Source #

list :: [Nat2] Source #

Listable Nat1 Source # 

Methods

tiers :: [[Nat1]] Source #

list :: [Nat1] Source #

Listable Nat Source # 

Methods

tiers :: [[Nat]] Source #

list :: [Nat] Source #

Listable Word4 Source # 

Methods

tiers :: [[Word4]] Source #

list :: [Word4] Source #

Listable Word3 Source # 

Methods

tiers :: [[Word3]] Source #

list :: [Word3] Source #

Listable Word2 Source # 

Methods

tiers :: [[Word2]] Source #

list :: [Word2] Source #

Listable Word1 Source # 

Methods

tiers :: [[Word1]] Source #

list :: [Word1] Source #

Listable Int4 Source # 

Methods

tiers :: [[Int4]] Source #

list :: [Int4] Source #

Listable Int3 Source # 

Methods

tiers :: [[Int3]] Source #

list :: [Int3] Source #

Listable Int2 Source # 

Methods

tiers :: [[Int2]] Source #

list :: [Int2] Source #

Listable Int1 Source # 

Methods

tiers :: [[Int1]] Source #

list :: [Int1] Source #

Listable a => Listable [a] Source # 

Methods

tiers :: [[[a]]] Source #

list :: [[a]] Source #

Listable a => Listable (Maybe a) Source # 

Methods

tiers :: [[Maybe a]] Source #

list :: [Maybe a] Source #

(Listable a, Listable b) => Listable (Either a b) Source # 

Methods

tiers :: [[Either a b]] Source #

list :: [Either a b] Source #

(Listable a, Listable b) => Listable (a, b) Source #
list :: [(Int,Int)] = [(0,0), (0,1), (1,0), (0,-1), (1,1), ...]

Methods

tiers :: [[(a, b)]] Source #

list :: [(a, b)] Source #

(Listable a, Listable b, Listable c) => Listable (a, b, c) Source # 

Methods

tiers :: [[(a, b, c)]] Source #

list :: [(a, b, c)] Source #

(Listable a, Listable b, Listable c, Listable d) => Listable (a, b, c, d) Source # 

Methods

tiers :: [[(a, b, c, d)]] Source #

list :: [(a, b, c, d)] Source #

(Listable a, Listable b, Listable c, Listable d, Listable e) => Listable (a, b, c, d, e) Source #

Instances for Listable sixtuples up to 12-tuples are exported by default form Test.LeanCheck but are hidden from Haddock documentation. These instances are defined in Test.LeanCheck.Basic.

Methods

tiers :: [[(a, b, c, d, e)]] Source #

list :: [(a, b, c, d, e)] Source #

Listing constructors

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

Given a constructor with no arguments, returns tiers of all possible applications of this constructor. Since in this case there is only one possible application (to no arguments), only a single value, of size/weight 0, will be present in the resulting list of tiers.

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

Given a constructor with one Listable argument, return tiers of applications of this constructor. By default, returned values will have size/weight of 1.

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

Given a constructor with two Listable arguments, return tiers of applications of this constructor. By default, returned values will have size/weight of 1.

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

Returns tiers of applications of a 3-argument constructor.

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

Returns tiers of applications of a 4-argument constructor.

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

Returns tiers of applications of a 5-argument constructor.

Test.LeanCheck.Basic defines cons6 up to cons12. Those are exported by default from Test.LeanCheck, but are hidden from the Haddock documentation.

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 --- sum of two tiers enumerations.

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

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

Interleave tiers --- sum of two tiers enumerations. 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 a tiered product of lists of tiers. productWith can be defined by ><, as:

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, the following holds:

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

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

Normalizes tiers by removing an empty tier from the end of a list of tiers.

normalizeT [xs0,xs1,...,xsN,[]] = [xs0,xs1,...,xsN]

Note this will only remove a single empty tier:

normalizeT [xs0,xs1,...,xsN,[],[]] = [xs0,xs1,...,xsN,[]]

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.

Consider the following Stack datatype:

data Stack a = Stack a (Stack a) | Empty

Writing

deriveListable ''Stack

will automatically derive the following Listable instance:

instance Listable a => Listable (Stack a) where
  tiers = cons2 Stack \/ cons0 Empty

Needs the TemplateHaskell extension.

deriveListableCascading :: Name -> DecsQ Source #

Derives a Listable instance for a given type Name cascading derivation of type arguments as well.

Specialized constructors of tiers

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

Given a constructor that takes a set of elements (as a list), lists tiers of applications of this constructor.

A naive Listable instance for the Set (of Data.Set) would read:

instance Listable a => Listable (Set a) where
  tiers = cons0 empty \/ cons2 insert

The above instance has a problem: it generates repeated sets. A more efficient implementation that does not repeat sets is given by:

  tiers = setCons fromList

Alternatively, you can use setsOf direclty.

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

Given a constructor that takes a bag of elements (as a list), lists tiers of applications of this constructor.

For example, a Bag represented as a list.

bagCons Bag

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

Given a constructor that takes a list with no duplicate elements, return tiers of applications of this constructor.

Products of tiers

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

Like productWith, 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 discarding Nothing values.

Listing lists

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

Takes as argument tiers of element values; returns tiers of lists of elements.

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 #

Takes as argument tiers of element values; returns tiers of size-ordered lists of elements without repetition.

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

Can be used in the constructor of specialized Listable instances. For Set (from Data.Set), we would have:

instance Listable a => Listable (Set a) where
  tiers = mapT fromList $ setsOf tiers

bagsOf :: [[a]] -> [[[a]]] Source #

Takes as argument tiers of element values; returns tiers of size-ordered lists of elements possibly with repetition.

bagsOf [[0],[1],[2],...] =
  [ [[]]
  , [[0]]
  , [[0,0],[1]]
  , [[0,0,0],[0,1],[2]]
  , [[0,0,0,0],[0,0,1],[0,2],[1,1],[3]]
  , [[0,0,0,0,0],[0,0,0,1],[0,0,2],[0,1,1],[0,3],[1,2],[4]]
  , ...
  ]

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

Takes as argument tiers of element 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 #

Takes the product of N lists of tiers, producing lists of length N.

Alternatively, takes as argument a list of lists of tiers of elements; returns lists combining elements of each list of tiers.

products [xss] = mapT (:[]) xss
products [xss,yss] = mapT (\(x,y) -> [x,y]) (xss >< yss)
products [xss,yss,zss] = product3With (\x y z -> [x,y,z]) xss yss zss

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

Takes as argument an integer length and tiers of element values; returns tiers of lists of element values of the given length.

listsOfLength 3 [[0],[1],[2],[3],[4]...] =
  [ [[0,0,0]]
  , [[0,0,1],[0,1,0],[1,0,0]]
  , [[0,0,2],[0,1,1],[0,2,0],[1,0,1],[1,1,0],[2,0,0]]
  , ...
  ]

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 #

Tiers of Integral values. Can be used as a default implementation of list for Integral types.

(+|) :: [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
  •  Listable a => a -> Bool
  •  Listable a => a -> a -> Bool
  •  Int -> Bool
  •  String -> [Int] -> Bool

Minimal complete definition

resultiers

Instances

Testable Bool Source # 

Methods

resultiers :: Bool -> [[([String], Bool)]]

(Testable b, Show a, Listable a) => Testable (a -> b) Source # 

Methods

resultiers :: (a -> b) -> [[([String], Bool)]]

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

List all results of a Testable property. Each result is a pair of a list of strings and a boolean. The list of strings is a printable representation of one possible choice of argument values for the property. Each boolean paired with such a list indicates whether the property holds for this choice. The outer list is potentially infinite and lazily evaluated.