Copyright | (c) 2015-2020 Rudy Matela |
---|---|
License | 3-Clause BSD (see the file LICENSE) |
Maintainer | Rudy Matela <rudy@matela.com.br> |
Safe Haskell | Safe-Inferred |
Language | Haskell2010 |
LeanCheck is a simple enumerative property-based testing library.
This module provides advanced functions for manipulating tiers
.
Most definitions given here are exported by Test.LeanCheck, except:
listCons
,
choices
,
setChoices
and
bagChoices
.
Synopsis
- listCons :: Listable a => ([a] -> b) -> [[b]]
- setCons :: Listable a => ([a] -> b) -> [[b]]
- bagCons :: Listable a => ([a] -> b) -> [[b]]
- mapCons :: (Listable a, Listable b) => ([(a, b)] -> c) -> [[c]]
- noDupListCons :: Listable a => ([a] -> b) -> [[b]]
- maybeCons0 :: Maybe b -> [[b]]
- maybeCons1 :: Listable a => (a -> Maybe b) -> [[b]]
- maybeCons2 :: (Listable a, Listable b) => (a -> b -> Maybe c) -> [[c]]
- product3 :: [[a]] -> [[b]] -> [[c]] -> [[(a, b, c)]]
- product3With :: (a -> b -> c -> d) -> [[a]] -> [[b]] -> [[c]] -> [[d]]
- productMaybeWith :: (a -> b -> Maybe c) -> [[a]] -> [[b]] -> [[c]]
- listsOf :: [[a]] -> [[[a]]]
- bagsOf :: [[a]] -> [[[a]]]
- setsOf :: [[a]] -> [[[a]]]
- noDupListsOf :: [[a]] -> [[[a]]]
- products :: [[[a]]] -> [[[a]]]
- maps :: [[a]] -> [[b]] -> [[[(a, b)]]]
- listsOfLength :: Int -> [[a]] -> [[[a]]]
- distinctPairs :: [[a]] -> [[(a, a)]]
- distinctPairsWith :: (a -> a -> b) -> [[a]] -> [[b]]
- unorderedPairs :: [[a]] -> [[(a, a)]]
- unorderedPairsWith :: (a -> a -> b) -> [[a]] -> [[b]]
- unorderedDistinctPairs :: [[a]] -> [[(a, a)]]
- unorderedDistinctPairsWith :: (a -> a -> b) -> [[a]] -> [[b]]
- deleteT :: Eq a => a -> [[a]] -> [[a]]
- normalizeT :: [[a]] -> [[a]]
- catMaybesT :: [[Maybe a]] -> [[a]]
- mapMaybeT :: (a -> Maybe b) -> [[a]] -> [[b]]
- discardT :: (a -> Bool) -> [[a]] -> [[a]]
- discardLaterT :: (a -> a -> Bool) -> [[a]] -> [[a]]
- nubT :: Ord a => [[a]] -> [[a]]
- choices :: [[a]] -> [[(a, [[a]])]]
- setChoices :: [[a]] -> [[(a, [[a]])]]
- bagChoices :: [[a]] -> [[(a, [[a]])]]
- printTiers :: Show a => Int -> [[a]] -> IO ()
- showTiers :: Show a => Int -> [[a]] -> String
- finite :: [[a]] -> Bool
Additional tiers constructors
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
mapCons :: (Listable a, Listable b) => ([(a, b)] -> c) -> [[c]] Source #
Given a constructor that takes a map of elements (encoded as a list), lists tiers of applications of this constructor
So long as the underlying Listable
enumerations have no repetitions,
this will generate no repetitions.
This allows defining an efficient implementation of tiers
that does not
repeat maps given by:
tiers = mapCons fromList
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.
maybeCons0 :: Maybe b -> [[b]] Source #
maybeCons1 :: Listable a => (a -> Maybe b) -> [[b]] Source #
maybeCons2 :: (Listable a, Listable b) => (a -> b -> Maybe c) -> [[c]] Source #
Like cons2
but lifted over a Maybe
result.
This discard Nothing
values.
Only Just
values are returned.
Useful when declaring generators which have pre-conditions:
data Fraction = Fraction Int Int mkFraction _ 0 = Nothing mkFraction n d = Fraction n d instance Listable Fraction where tiers = maybeCons2 mkFraction
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 #
Tiers of 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]] , ... ]
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]] , ... ]
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
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
maps :: [[a]] -> [[b]] -> [[[(a, b)]]] Source #
Takes as arguments tiers of source and target values; returns tiers of maps from the source to the target encoded as lists without repetition.
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]] , ... ]
Tiers of pairs
distinctPairs :: [[a]] -> [[(a, a)]] Source #
Takes as argument tiers of element values; returns tiers of pairs with distinct element values.
When argument tiers have no repeated elements:
distinctPairs xss = xss >< xss `suchThat` uncurry (/=)
distinctPairsWith :: (a -> a -> b) -> [[a]] -> [[b]] Source #
distinctPairs
by a given function:
distinctPairsWith f = mapT (uncurry f) . distinctPairs
unorderedPairs :: [[a]] -> [[(a, a)]] Source #
Takes as argument tiers of element values; returns tiers of unordered pairs where, in enumeration order, the first element is less than or equal to the second.
The name of this function is perhaps a misnomer. But in mathematics,
an unordered pair is a pair where you don't care about element order, e.g.:
(1,2) = (2,1)
. This function will enumerate canonical versions of such
pairs where the first element is less than the second.
The returned element pairs can be seen as bags with two elements.
When argument tiers are listed in Ord
:
distinctPairs xss = xss >< xss `suchThat` uncurry (<=)
unorderedPairsWith :: (a -> a -> b) -> [[a]] -> [[b]] Source #
unorderedPairs
by a given function:
unorderedPairsWith f = mapT (uncurry f) . unorderedPairs
unorderedDistinctPairs :: [[a]] -> [[(a, a)]] Source #
Takes as argument tiers of element values; returns tiers of unordered pairs where, in enumeration order, the first element is strictly less than the second.
The returned element pairs can be seen as sets with two elements.
When argument tiers are listed in Ord
:
distinctPairs xss = xss >< xss `suchThat` uncurry (<)
unorderedDistinctPairsWith :: (a -> a -> b) -> [[a]] -> [[b]] Source #
unorderedPairs
by a given function:
unorderedDistinctPairsWith f = mapT (uncurry f) . unorderedDistinctPairs
deleteT :: Eq a => a -> [[a]] -> [[a]] Source #
Delete the first occurence of an element in a tier.
For normalized lists-of-tiers without repetitions, the following holds:
deleteT x = normalizeT . (`suchThat` (/= x))
normalizeT :: [[a]] -> [[a]] Source #
Normalizes tiers by removing up to 12 empty tiers from the end of a list of tiers.
normalizeT [xs0,xs1,...,xsN,[]] = [xs0,xs1,...,xsN] normalizeT [xs0,xs1,...,xsN,[],[]] = [xs0,xs1,...,xsN]
The arbitrary limit of 12 tiers is necessary as this function would loop if there is an infinite trail of empty tiers.
catMaybesT :: [[Maybe a]] -> [[a]] Source #
Concatenate tiers of maybes
discardT :: (a -> Bool) -> [[a]] -> [[a]] Source #
Discard elements _not_ matching a predicate.
discardT odd [[1],[2,3],[4]] = [[],[2],[4]]
discardLaterT :: (a -> a -> Bool) -> [[a]] -> [[a]] Source #
Discard later elements maching a binary predicate (in relation to an earlier element).
discardLaterT (>) [[0],[1],[-1],[2],[-2],...] = [[0],[],[-1],[],[-2],...] discardLaterT (==) [[0],[0,1],[0,1,2],[0,1,2,3],...] = [[0],[1],[2],[3]]
This function is quite innefficient, use with care.
Consuming the n-th element takes O(n^2)
operations.
nubT :: Ord a => [[a]] -> [[a]] Source #
Removes repetitions from tiers.
nubT [[0],[0,1],[0,1,2],[0,1,2,3],...] = [[0],[1],[2],[3],...] nubT [[0],[-1,0,1],[-2,-1,0,1,2],...] = [[0],[-1,1],[-2,2],...]
Consuming the n-th element takes O(n^2)
operations.
Tiers of choices
choices :: [[a]] -> [[(a, [[a]])]] Source #
Lists tiers of choices. Choices are pairs of values and tiers excluding that value.
choices [[False,True]] == [[(False,[[True]]),(True,[[False]])]] choices [[1],[2],[3]] == [ [(1,[[],[2],[3]])] , [(2,[[1],[],[3]])] , [(3,[[1],[2],[]])] ]
Each choice is sized by the extracted element.
setChoices :: [[a]] -> [[(a, [[a]])]] Source #
bagChoices :: [[a]] -> [[(a, [[a]])]] Source #
Showing and printing lists-of-tiers
Lists-of-tiers are already show instances as their type is just [[a]]
.
The following functions are alternatives to print
and show
with one
element per line and can be useful for debugging.