a package:leancheck

Generic type A. Can be used to test polymorphic functions with a type variable such as take or sort:
take :: Int -> [a] -> [a]
sort :: Ord a => [a] -> [a]
by binding them to the following types:
take :: Int -> [A] -> [A]
sort :: [A] -> [A]
This type is homomorphic to Nat6, B, C, D, E and F. It is instance to several typeclasses so that it can be used to test functions with type contexts.
Adds to the weight of a constructor or tiers.
instance Listable <Type> where
tiers  =  ...
\/ cons<N> <Cons>  `addWeight`  <W>
\/ ...
Typically used as an infix operator when defining Listable instances:
> [ xs, ys, zs, ... ] `addWeight` 1
[ [], xs, ys, zs, ... ]
> [ xs, ys, zs, ... ] `addWeight` 2
[ [], [], xs, ys, zs, ... ]
> [ [], xs, ys, zs, ... ] `addWeight` 3
[ [], [], [], [], xs, ys, zs, ... ]
`addWeight` n is equivalent to n applications of delay.
Transforms a value into Right that value or 'Left String' on error. Only the first line of the error's string representation is included. This function uses unsafePerformIO. See: errorToLeft.
Transforms a value into Just that value or Nothing on error.
This function can be used to define an Eq instance for functions based on testing and equality of returned values, like so:
instance (Listable a, Eq b) => Eq (a -> b) where
(==)  =  areEqualFor 12
This catches errors and undefined values and treats them as equal.
Deprecated: Use isAntisymmetric.
Deprecated: Use isAssociative.
Deprecated: Use isAsymmetric.
Alphabetic characters.
list :: [Alpha]  =  "aAbBcC..."
> check $ \(Alpha c) -> isAlpha c
+++ OK, passed 52 tests (exhausted).
Equivalent to Letter.
Alphanumeric characters.
list :: [AlphaNum]  =  "0a1A2b3B4c..."
> check $ \(AlphaNum c) -> isAlphaNum c
+++ OK, passed 62 tests (exhausted).
Strings of alphanumeric characters
Strings of alphabetic characters
Enumerative property-based testing LeanCheck is a simple enumerative property-based testing library. Properties are defined as Haskell functions returning a boolean value which should be true for all possible choices of argument values. LeanCheck applies enumerated argument values to these properties in search for a counterexample. Properties can be viewed as parameterized unit tests. LeanCheck works by producing tiers of test values: a possibly infinite list of finite sublists of same-and-increasingly-sized values. LeanCheck has lean core with only 200 lines of Haskell code.
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:
> import Data.List (sort)
> holds 1000 $ \xs -> length (sort xs) == length (xs::[Int])
True
To get the smallest counterExample by testing up to a thousand values, we evaluate:
counterExample 1000 property
Nothing indicates no counterexample was found, a Just value indicates a counterexample. For instance:
> import Data.List (union)
> counterExample 1000 $ \xs ys -> union xs ys == union ys (xs :: [Int])
Just ["[]","[0,0]"]
The suggested values for the number of tests to use with LeanCheck are 500, 1 000 or 10 000. LeanCheck is memory intensive and you should take care if you go beyond that. The function check can also be used to test and report counterexamples.
> check $ \xs ys -> union xs ys == union ys (xs :: [Int])
*** Failed! Falsifiable (after 4 tests):
[] [0,0]
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).
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. Here is a datatype with 4 constructors and its listable instance:
data MyType  =  MyConsA
|  MyConsB Int
|  MyConsC Int Char
|  MyConsD String

instance Listable MyType where
tiers =  cons0 MyConsA
\/ cons1 MyConsB
\/ cons2 MyConsC
\/ cons1 MyConsD
The instance for Hutton's Razor is given by:
data Expr  =  Val Int
|  Add Expr Expr

instance Listable Expr where
tiers  =  cons1 Val
\/ cons2 Add
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.
Testable values are functions of Listable arguments that return boolean values.
  •  Bool
  •  Listable a => a -> Bool
  •  (Listable a, Listable b) => a -> b ->
    Bool
  •  (Listable a, Listable b, Listable c) => a -> b -> c
    -> Bool
  •  (Listable a, Listable b, Listable c, ...) => a -> b
    -> c -> ... -> Bool
For example:
  •  Int -> Bool
  •  String -> [Int] -> Bool
(cf. results)
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
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]]
, ...
]
concatMap over tiers
concatMapT f [ [x0, y0, z0]
, [x1, y1, z1]
, [x2, y2, z2]
, ...
]
=  f x0 \/ f y0 \/ f z0 \/ ...
\/ delay (f x1 \/ f y1 \/ f z1 \/ ...
\/ delay (f x2 \/ f y2 \/ f z2 \/ ...
\/ (delay ...)))
(cf. concatT)
concat tiers of tiers
concatT [ [xss0, yss0, zss0, ...]
, [xss1, yss1, zss1, ...]
, [xss2, yss2, zss2, ...]
, ...
]
=  xss0 \/ yss0 \/ zss0 \/ ...
\/ delay (xss1 \/ yss1 \/ zss1 \/ ...
\/ delay (xss2 \/ yss2 \/ zss2 \/ ...
\/ (delay ...)))
(cf. concatMapT)
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]"]