Copyright | (c) 2017-2019 Rudy Matela |
---|---|
License | 3-Clause BSD (see the file LICENSE) |
Maintainer | Rudy Matela <[email protected]> |
Safe Haskell | None |
Language | Haskell2010 |
Test.Extrapolate
Contents
Description
Extrapolate is a property-based testing library capable of reporting generalized counter-examples.
Consider the following faulty implementation of sort:
sort :: Ord a => [a] -> [a] sort [] = [] sort (x:xs) = sort (filter (< x) xs) ++ [x] ++ sort (filter (> x) xs)
When tests pass, Extrapolate works like a regular property-based testing library. See:
> check $ \xs -> sort (sort xs :: [Int]) == sort xs +++ OK, passed 500 tests.
When tests fail, Extrapolate reports a fully defined counter-example and a generalization of failing inputs. See:
> check $ \xs -> length (sort xs :: [Int]) == length xs *** Failed! Falsifiable (after 3 tests): [0,0] Generalization: x:x:_ Conditional Generalization: x:xs when elem x xs
Generalization:
the property fails for any integer x
and for any list _
at the tail.
Conditional Generalization:
the property fails for a list x:xs
whenever x
is an element of xs
This hints at the actual source of the fault:
our sort
above discards repeated elements!
Synopsis
- check :: Testable a => a -> IO ()
- checkResult :: Testable a => a -> IO Bool
- for :: Testable a => (WithOption a -> b) -> Int -> a -> b
- withBackground :: Testable a => (WithOption a -> b) -> [Expr] -> a -> b
- withConditionSize :: Testable a => (WithOption a -> b) -> Int -> a -> b
- class (Listable a, Express a, Name a, Show a) => Generalizable a where
- background :: a -> [Expr]
- subInstances :: a -> Instances -> Instances
- instances :: Generalizable a => a -> Instances -> Instances
- data Expr
- value :: Typeable a => String -> a -> Expr
- val :: (Typeable a, Show a) => a -> Expr
- reifyEq :: (Typeable a, Eq a) => a -> [Expr]
- reifyOrd :: (Typeable a, Ord a) => a -> [Expr]
- reifyEqOrd :: (Typeable a, Ord a) => a -> [Expr]
- class Typeable a => Testable a
- deriveGeneralizable :: Name -> DecsQ
- deriveGeneralizableIfNeeded :: Name -> DecsQ
- deriveGeneralizableCascading :: Name -> DecsQ
- class Name a where
- class Typeable a => Express a where
- module Test.Extrapolate.TypeBinding
- listsOfLength :: Int -> [[a]] -> [[[a]]]
- setsOf :: [[a]] -> [[[a]]]
- bagsOf :: [[a]] -> [[[a]]]
- noDupListsOf :: [[a]] -> [[[a]]]
- normalizeT :: [[a]] -> [[a]]
- deleteT :: Eq a => a -> [[a]] -> [[a]]
- products :: [[[a]]] -> [[[a]]]
- listsOf :: [[a]] -> [[[a]]]
- productMaybeWith :: (a -> b -> Maybe c) -> [[a]] -> [[b]] -> [[c]]
- product3With :: (a -> b -> c -> d) -> [[a]] -> [[b]] -> [[c]] -> [[d]]
- noDupListCons :: Listable a => ([a] -> b) -> [[b]]
- mapCons :: (Listable a, Listable b) => ([(a, b)] -> c) -> [[c]]
- setCons :: Listable a => ([a] -> b) -> [[b]]
- bagCons :: Listable a => ([a] -> b) -> [[b]]
- deriveListableCascading :: Name -> DecsQ
- deriveListable :: Name -> DecsQ
- addWeight :: [[a]] -> Int -> [[a]]
- ofWeight :: [[a]] -> Int -> [[a]]
- 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]]
- 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]]
- 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]]
- 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]]
- 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]]
- cons7 :: (Listable a, Listable b, Listable c, Listable d, Listable e, Listable f, Listable g) => (a -> b -> c -> d -> e -> f -> g -> h) -> [[h]]
- cons6 :: (Listable a, Listable b, Listable c, Listable d, Listable e, Listable f) => (a -> b -> c -> d -> e -> f -> g) -> [[g]]
- (==>) :: Bool -> Bool -> Bool
- exists :: Testable a => Int -> a -> Bool
- fails :: Testable a => Int -> a -> Bool
- holds :: Testable a => Int -> a -> Bool
- witness :: Testable a => Int -> a -> Maybe [String]
- witnesses :: Testable a => Int -> a -> [[String]]
- (><) :: [[a]] -> [[b]] -> [[(a, b)]]
- (\\//) :: [[a]] -> [[a]] -> [[a]]
- (\/) :: [[a]] -> [[a]] -> [[a]]
- (+|) :: [a] -> [a] -> [a]
- suchThat :: [[a]] -> (a -> Bool) -> [[a]]
- reset :: [[a]] -> [[a]]
- delay :: [[a]] -> [[a]]
- cons5 :: (Listable a, Listable b, Listable c, Listable d, Listable e) => (a -> b -> c -> d -> e -> f) -> [[f]]
- cons4 :: (Listable a, Listable b, Listable c, Listable d) => (a -> b -> c -> d -> e) -> [[e]]
- cons3 :: (Listable a, Listable b, Listable c) => (a -> b -> c -> d) -> [[d]]
- cons2 :: (Listable a, Listable b) => (a -> b -> c) -> [[c]]
- cons1 :: Listable a => (a -> b) -> [[b]]
- cons0 :: a -> [[a]]
- concatMapT :: (a -> [[b]]) -> [[a]] -> [[b]]
- concatT :: [[[[a]]]] -> [[a]]
- filterT :: (a -> Bool) -> [[a]] -> [[a]]
- mapT :: (a -> b) -> [[a]] -> [[b]]
- tiersFloating :: Fractional a => [[a]]
- tiersFractional :: Fractional a => [[a]]
- listIntegral :: (Ord a, Num a) => [a]
- toTiers :: [a] -> [[a]]
- class Listable a where
Checking properties
check :: Testable a => a -> IO () Source #
Checks a property printing results on stdout
> check $ \xs -> sort (sort xs) == sort (xs::[Int]) +++ OK, passed 360 tests. > check $ \xs ys -> xs `union` ys == ys `union` (xs::[Int]) *** Failed! Falsifiable (after 4 tests): [] [0,0] Generalization: [] (x:x:_)
withBackground :: Testable a => (WithOption a -> b) -> [Expr] -> a -> b Source #
Use
to provide additional functions to appear in side-conditions.withBackground
check `withBackground` [value "isSpace" isSpace] $ \xs -> unwords (words xs) == xs *** Failed! Falsifiable (after 4 tests): " " Generalization: ' ':_ Conditional Generalization: c:_ when isSpace c
withConditionSize :: Testable a => (WithOption a -> b) -> Int -> a -> b Source #
Use
to configure the maximum condition size allowed.withConditionSize
Generalizable types
class (Listable a, Express a, Name a, Show a) => Generalizable a where Source #
Extrapolate can generalize counter-examples of any types that are
Generalizable
.
Generalizable
types must first be instances of
Listable
, so Extrapolate knows how to enumerate values;Express
, so Extrapolate can represent then manipulate values;Name
, so Extrapolate knows how to name variables.
There are no required functions, so we can define instances with:
instance Generalizable OurType
However, it is desirable to define both background
and subInstances
.
The following example shows a datatype and its instance:
data Stack a = Stack a (Stack a) | Empty
instance Generalizable a => Generalizable (Stack a) where subInstances s = instances (argTy1of1 s)
To declare instances
it may be useful to use type binding
operators such as: argTy1of1
, argTy1of2
and argTy2of2
.
Instances can be automatically derived using
deriveGeneralizable
which will also automatically derivate
Listable
, Express
and Name
when needed.
Minimal complete definition
Nothing
Methods
background :: a -> [Expr] Source #
List of symbols allowed to appear in side-conditions.
Defaults to []
. See value
.
subInstances :: a -> Instances -> Instances Source #
Instances
instances :: Generalizable a => a -> Instances -> Instances Source #
Used in the definition of subInstances
in Generalizable
typeclass instances.
Values of type Expr
represent objects or applications between objects.
Each object is encapsulated together with its type and string representation.
Values encoded in Expr
s are always monomorphic.
An Expr
can be constructed using:
val
, for values that areShow
instances;value
, for values that are notShow
instances, like functions;:$
, for applications betweenExpr
s.
> val False False :: Bool
> value "not" not :$ val False not False :: Bool
An Expr
can be evaluated using evaluate
, eval
or evl
.
> evl $ val (1 :: Int) :: Int 1
> evaluate $ val (1 :: Int) :: Maybe Bool Nothing
> eval 'a' (val 'b') 'b'
Show
ing a value of type Expr
will return a pretty-printed representation
of the expression together with its type.
> show (value "not" not :$ val False) "not False :: Bool"
Expr
is like Dynamic
but has support for applications and variables
(:$
, var
).
The var
underscore convention:
Functions that manipulate Expr
s usually follow the convention
where a value
whose String
representation starts with '_'
represents a var
iable.
value :: Typeable a => String -> a -> Expr #
O(1).
It takes a string representation of a value and a value, returning an
Expr
with that terminal value.
For instances of Show
, it is preferable to use val
.
> value "0" (0 :: Integer) 0 :: Integer
> value "'a'" 'a' 'a' :: Char
> value "True" True True :: Bool
> value "id" (id :: Int -> Int) id :: Int -> Int
> value "(+)" ((+) :: Int -> Int -> Int) (+) :: Int -> Int -> Int
> value "sort" (sort :: [Bool] -> [Bool]) sort :: [Bool] -> [Bool]
reifyEq :: (Typeable a, Eq a) => a -> [Expr] #
O(1).
Reifies an Eq
instance into a list of Expr
s.
The list will contain ==
and /=
for the given type.
(cf. mkEq
, mkEquation
)
> reifyEq (undefined :: Int) [ (==) :: Int -> Int -> Bool , (/=) :: Int -> Int -> Bool ]
> reifyEq (undefined :: Bool) [ (==) :: Bool -> Bool -> Bool , (/=) :: Bool -> Bool -> Bool ]
> reifyEq (undefined :: String) [ (==) :: [Char] -> [Char] -> Bool , (/=) :: [Char] -> [Char] -> Bool ]
reifyOrd :: (Typeable a, Ord a) => a -> [Expr] #
O(1).
Reifies an Ord
instance into a list of Expr
s.
The list will contain compare
, <=
and <
for the given type.
(cf. mkOrd
, mkOrdLessEqual
, mkComparisonLE
, mkComparisonLT
)
> reifyOrd (undefined :: Int) [ (<=) :: Int -> Int -> Bool , (<) :: Int -> Int -> Bool ]
> reifyOrd (undefined :: Bool) [ (<=) :: Bool -> Bool -> Bool , (<) :: Bool -> Bool -> Bool ]
> reifyOrd (undefined :: [Bool]) [ (<=) :: [Bool] -> [Bool] -> Bool , (<) :: [Bool] -> [Bool] -> Bool ]
reifyEqOrd :: (Typeable a, Ord a) => a -> [Expr] #
Testable properties
class Typeable a => Testable a Source #
Minimal complete definition
Instances
Testable Bool Source # | |
Testable a => Testable (WithOption a) Source # | |
Defined in Test.Extrapolate.Testable Methods resultiers :: WithOption a -> [[(Expr, Bool)]] Source # tinstances :: WithOption a -> Instances Source # options :: WithOption a -> Options Source # | |
(Testable b, Generalizable a, Listable a) => Testable (a -> b) Source # | |
Defined in Test.Extrapolate.Testable |
Automatically deriving Generalizable instances
deriveGeneralizable :: Name -> DecsQ Source #
Derives a Generalizable
instance for a given type Name
.
If needed, this function also automatically derivates
Listable
, Express
and Name
instances using respectively
deriveListable
, deriveExpress
and deriveName
.
Consider the following Stack
datatype:
data Stack a = Stack a (Stack a) | Empty
Writing
deriveGeneralizable ''Stack
will automatically derive the following Generalizable
instance:
instance Generalizable a => Generalizable (Stack a) where instances s = this "s" s $ let Stack x y = Stack undefined undefined `asTypeOf` s in instances x . instances y
This function needs the TemplateHaskell
extension.
deriveGeneralizableIfNeeded :: Name -> DecsQ Source #
Same as deriveGeneralizable
but does not warn when instance already exists
(deriveGeneralizable
is preferable).
deriveGeneralizableCascading :: Name -> DecsQ Source #
Derives a Generalizable
instance for a given type Name
cascading derivation of type arguments as well.
Typeclasses required by Generalizable
If we were to come up with a variable name for the given type
what name
would it be?
An instance for a given type Ty
is simply given by:
instance Name Ty where name _ = "x"
Examples:
> name (undefined :: Int) "x"
> name (undefined :: Bool) "p"
> name (undefined :: [Int]) "xs"
This is then used to generate an infinite list of variable names
:
> names (undefined :: Int) ["x", "y", "z", "x'", "y'", "z'", "x''", "y''", "z''", ...]
> names (undefined :: Bool) ["p", "q", "r", "p'", "q'", "r'", "p''", "q''", "r''", ...]
> names (undefined :: [Int]) ["xs", "ys", "zs", "xs'", "ys'", "zs'", "xs''", "ys''", ...]
Minimal complete definition
Nothing
Methods
O(1).
Returns a name for a variable of the given argument's type.
> name (undefined :: Int) "x"
> name (undefined :: [Bool]) "ps"
> name (undefined :: [Maybe Integer]) "mxs"
The default definition is:
name _ = "x"
Instances
Name Bool | name (undefined :: Bool) = "p" names (undefined :: Bool) = ["p", "q", "r", "p'", "q'", ...] |
Defined in Data.Express.Name | |
Name Char | name (undefined :: Char) = "c" names (undefined :: Char) = ["c", "d", "e", "c'", "d'", ...] |
Defined in Data.Express.Name | |
Name Double | name (undefined :: Double) = "x" names (undefined :: Double) = ["x", "y", "z", "x'", ...] |
Defined in Data.Express.Name | |
Name Float | name (undefined :: Float) = "x" names (undefined :: Float) = ["x", "y", "z", "x'", ...] |
Defined in Data.Express.Name | |
Name Int | name (undefined :: Int) = "x" names (undefined :: Int) = ["x", "y", "z", "x'", "y'", ...] |
Defined in Data.Express.Name | |
Name Integer | name (undefined :: Integer) = "x" names (undefined :: Integer) = ["x", "y", "z", "x'", ...] |
Defined in Data.Express.Name | |
Name Ordering | name (undefined :: Ordering) = "o" names (undefined :: Ordering) = ["o", "p", "q", "o'", ...] |
Defined in Data.Express.Name | |
Name Word | |
Defined in Data.Express.Name | |
Name () | name (undefined :: ()) = "u" names (undefined :: ()) = ["u", "v", "w", "u'", "v'", ...] |
Defined in Data.Express.Name | |
Name a => Name [a] | names (undefined :: [Int]) = ["xs", "ys", "zs", "xs'", ...] names (undefined :: [Bool]) = ["ps", "qs", "rs", "ps'", ...] |
Defined in Data.Express.Name | |
Name a => Name (Maybe a) | names (undefined :: Maybe Int) = ["mx", "mx1", "mx2", ...] nemes (undefined :: Maybe Bool) = ["mp", "mp1", "mp2", ...] |
Defined in Data.Express.Name | |
Name (Ratio a) | name (undefined :: Rational) = "q" names (undefined :: Rational) = ["q", "r", "s", "q'", ...] |
Defined in Data.Express.Name | |
Name (a -> b) | names (undefined :: ()->()) = ["f", "g", "h", "f'", ...] names (undefined :: Int->Int) = ["f", "g", "h", ...] |
Defined in Data.Express.Name | |
(Name a, Name b) => Name (Either a b) | names (undefined :: Either Int Int) = ["exy", "exy1", ...] names (undefined :: Either Int Bool) = ["exp", "exp1", ...] |
Defined in Data.Express.Name | |
(Name a, Name b) => Name (a, b) | names (undefined :: (Int,Int)) = ["xy", "zw", "xy'", ...] names (undefined :: (Bool,Bool)) = ["pq", "rs", "pq'", ...] |
Defined in Data.Express.Name | |
(Name a, Name b, Name c) => Name (a, b, c) | names (undefined :: (Int,Int,Int)) = ["xyz","uvw", ...] names (undefined :: (Int,Bool,Char)) = ["xpc", "xpc1", ...] |
Defined in Data.Express.Name | |
(Name a, Name b, Name c, Name d) => Name (a, b, c, d) | names (undefined :: ((),(),(),())) = ["uuuu", "uuuu1", ...] names (undefined :: (Int,Int,Int,Int)) = ["xxxx", ...] |
Defined in Data.Express.Name | |
(Name a, Name b, Name c, Name d, Name e) => Name (a, b, c, d, e) | |
Defined in Data.Express.Name | |
(Name a, Name b, Name c, Name d, Name e, Name f) => Name (a, b, c, d, e, f) | |
Defined in Data.Express.Name | |
(Name a, Name b, Name c, Name d, Name e, Name f, Name g) => Name (a, b, c, d, e, f, g) | |
Defined in Data.Express.Name | |
(Name a, Name b, Name c, Name d, Name e, Name f, Name g, Name h) => Name (a, b, c, d, e, f, g, h) | |
Defined in Data.Express.Name | |
(Name a, Name b, Name c, Name d, Name e, Name f, Name g, Name h, Name i) => Name (a, b, c, d, e, f, g, h, i) | |
Defined in Data.Express.Name | |
(Name a, Name b, Name c, Name d, Name e, Name f, Name g, Name h, Name i, Name j) => Name (a, b, c, d, e, f, g, h, i, j) | |
Defined in Data.Express.Name | |
(Name a, Name b, Name c, Name d, Name e, Name f, Name g, Name h, Name i, Name j, Name k) => Name (a, b, c, d, e, f, g, h, i, j, k) | |
Defined in Data.Express.Name | |
(Name a, Name b, Name c, Name d, Name e, Name f, Name g, Name h, Name i, Name j, Name k, Name l) => Name (a, b, c, d, e, f, g, h, i, j, k, l) | |
Defined in Data.Express.Name |
class Typeable a => Express a where #
Express
typeclass instances provide an expr
function
that allows values to be deeply encoded as applications of Expr
s.
expr False = val False expr (Just True) = value "Just" (Just :: Bool -> Maybe Bool) :$ val True
The function expr
can be contrasted with the function val
:
val
always encodes values as atomicValue
Expr
s -- shallow encoding.expr
ideally encodes expressions as applications (:$
) betweenValue
Expr
s -- deep encoding.
Depending on the situation, one or the other may be desirable.
Instances can be automatically derived using the TH function
deriveExpress
.
The following example shows a datatype and its instance:
data Stack a = Stack a (Stack a) | Empty
instance Express a => Express (Stack a) where expr s@(Stack x y) = value "Stack" (Stack ->>: s) :$ expr x :$ expr y expr s@Empty = value "Empty" (Empty -: s)
To declare expr
it may be useful to use auxiliary type binding operators:
-:
, ->:
, ->>:
, ->>>:
, ->>>>:
, ->>>>>:
, ...
For types with atomic values, just declare expr = val
Instances
Other useful modules
module Test.Extrapolate.TypeBinding
listsOfLength :: Int -> [[a]] -> [[[a]]] #
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]] , ... ]
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
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]]] #
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]] , ... ]
normalizeT :: [[a]] -> [[a]] #
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.
deleteT :: Eq a => a -> [[a]] -> [[a]] #
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))
products :: [[[a]]] -> [[[a]]] #
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
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]] , ... ]
productMaybeWith :: (a -> b -> Maybe c) -> [[a]] -> [[b]] -> [[c]] #
product3With :: (a -> b -> c -> d) -> [[a]] -> [[b]] -> [[c]] -> [[d]] #
Like productWith
, but over 3 lists of tiers.
noDupListCons :: Listable a => ([a] -> b) -> [[b]] #
Given a constructor that takes a list with no duplicate elements, return tiers of applications of this constructor.
mapCons :: (Listable a, Listable b) => ([(a, b)] -> c) -> [[c]] #
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
setCons :: Listable a => ([a] -> b) -> [[b]] #
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]] #
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
deriveListableCascading :: Name -> DecsQ #
Derives a Listable
instance for a given type Name
cascading derivation of type arguments as well.
Consider the following series of datatypes:
data Position = CEO | Manager | Programmer data Person = Person { name :: String , age :: Int , position :: Position } data Company = Company { name :: String , employees :: [Person] }
Writing
deriveListableCascading ''Company
will automatically derive the following three Listable
instances:
instance Listable Position where tiers = cons0 CEO \/ cons0 Manager \/ cons0 Programmer instance Listable Person where tiers = cons3 Person instance Listable Company where tiers = cons2 Company
deriveListable :: Name -> DecsQ #
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
Warning: if the values in your type need to follow a data invariant, the derived instance won't respect it. Use this only on "free" datatypes.
Needs the TemplateHaskell
extension.
addWeight :: [[a]] -> Int -> [[a]] #
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
.
ofWeight :: [[a]] -> Int -> [[a]] #
Resets the weight of a constructor or tiers.
> [ [], [], ..., xs, ys, zs, ... ] `ofWeight` 1 [ [], xs, ys, zs, ... ]
> [ xs, ys, zs, ... ] `ofWeight` 2 [ [], [], xs, ys, zs, ... ]
> [ [], xs, ys, zs, ... ] `ofWeight` 3 [ [], [], [], xs, ys, zs, ... ]
Typically used as an infix operator when defining Listable
instances:
instance Listable <Type> where tiers = ... \/ cons<N> <Cons> `ofWeight` <W> \/ ...
Warning: 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).
`ofWeight` n
is equivalent to reset
followed
by n
applications of delay
.
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]] #
Returns tiers of applications of a 12-argument constructor.
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]] #
Returns tiers of applications of a 11-argument constructor.
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]] #
Returns tiers of applications of a 10-argument constructor.
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]] #
Returns tiers of applications of a 9-argument constructor.
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]] #
Returns tiers of applications of a 8-argument constructor.
cons7 :: (Listable a, Listable b, Listable c, Listable d, Listable e, Listable f, Listable g) => (a -> b -> c -> d -> e -> f -> g -> h) -> [[h]] #
Returns tiers of applications of a 7-argument constructor.
cons6 :: (Listable a, Listable b, Listable c, Listable d, Listable e, Listable f) => (a -> b -> c -> d -> e -> f -> g) -> [[g]] #
Returns tiers of applications of a 6-argument constructor.
(==>) :: Bool -> Bool -> Bool infixr 0 #
Boolean implication operator. Useful for defining conditional properties:
prop_something x y = condition x y ==> something x y
Examples:
> prop_addMonotonic x y = y > 0 ==> x + y > x > check prop_addMonotonic +++ OK, passed 200 tests.
exists :: Testable a => Int -> a -> Bool #
There exists an assignment of values that satisfies a property up to a number of test values?
> exists 1000 $ \x -> x > 10 True
fails :: Testable a => Int -> a -> Bool #
Does a property fail for a number of test values?
> fails 1000 $ \xs -> xs ++ ys == ys ++ xs True
> holds 1000 $ \xs -> length (sort xs) == length xs False
This is the negation of holds
.
holds :: Testable a => Int -> a -> Bool #
Does a property hold up to a number of test values?
> holds 1000 $ \xs -> length (sort xs) == length xs True
> holds 1000 $ \x -> x == x + 1 False
The suggested number of test values are 500, 1 000 or 10 000.
With more than that you may or may not run out of memory
depending on the types being tested.
This also applies to fails
, exists
, etc.
(cf. fails
, counterExample
)
witnesses :: Testable a => Int -> a -> [[String]] #
Lists all witnesses up to a number of tests to a property.
> witnesses 1000 (\x -> x > 1 && x < 77 && 77 `rem` x == 0) [["7"],["11"]]
(><) :: [[a]] -> [[b]] -> [[(a, b)]] infixr 8 #
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)] , ... ]
(cf. productWith
)
(\\//) :: [[a]] -> [[a]] -> [[a]] infixr 7 #
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]] -> [[a]] -> [[a]] infixr 7 #
Append tiers --- sum of two tiers enumerations.
[xs,ys,zs,...] \/ [as,bs,cs,...] = [xs++as, ys++bs, zs++cs, ...]
(+|) :: [a] -> [a] -> [a] infixr 5 #
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,...]
suchThat :: [[a]] -> (a -> Bool) -> [[a]] #
Tiers of values that follow a property.
Typically used in the definition of Listable
tiers:
instance Listable <Type> where tiers = ... \/ cons<N> `suchThat` <condition> \/ ...
Examples:
> tiers `suchThat` odd [[], [1], [-1], [], [], [3], [-3], [], [], [5], ...]
> tiers `suchThat` even [[0], [], [], [2], [-2], [], [], [4], [-4], [], ...]
Resets any delays in a list-of tiers
.
Conceptually this function makes a constructor "weightless",
assuring the first tier is non-empty.
reset [[], [], ..., xs, ys, zs, ...] = [xs, ys, zs, ...]
reset [[], xs, ys, zs, ...] = [xs, ys, zs, ...]
reset [[], [], ..., [x], [y], [z], ...] = [[x], [y], [z], ...]
Typically used when defining Listable
instances:
instance Listable <Type> where tiers = ... \/ reset (cons<N> <Constructor>) \/ ...
Be careful: do not apply reset
to recursive data structure
constructors. In general this will make the list of size 0 infinite,
breaking the tiers
invariant (each tier must be finite).
Delays the enumeration of tiers
.
Conceptually this function adds to the weight of a constructor.
delay [xs, ys, zs, ... ] = [[], xs, ys, zs, ...]
delay [[x,...], [y,...], ...] = [[], [x,...], [y,...], ...]
Typically used when defining Listable
instances:
instance Listable <Type> where tiers = ... \/ delay (cons<N> <Constructor>) \/ ...
cons5 :: (Listable a, Listable b, Listable c, Listable d, Listable e) => (a -> b -> c -> d -> e -> f) -> [[f]] #
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.
To be used in the declaration of tiers
in Listable
instances.
instance Listable <Type> where tiers = ... \/ cons0 <Constructor> \/ ...
concatMapT :: (a -> [[b]]) -> [[a]] -> [[b]] #
concatT :: [[[[a]]]] -> [[a]] #
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
)
filterT :: (a -> Bool) -> [[a]] -> [[a]] #
filter
tiers
filterT p [xs, yz, zs, ...] = [filter p xs, filter p ys, filter p zs]
filterT odd tiers = [[], [1], [-1], [], [], [3], [-3], [], [], [5], ...]
mapT :: (a -> b) -> [[a]] -> [[b]] #
map
over tiers
mapT f [[x], [y,z], [w,...], ...] = [[f x], [f y, f z], [f w, ...], ...]
mapT f [xs, ys, zs, ...] = [map f xs, map f ys, map f zs]
tiersFloating :: Fractional a => [[a]] #
Tiers of Floating
values.
This can be used as the implementation of tiers
for Floating
types.
This function is equivalent to tiersFractional
with positive and negative infinities included: 10 and -10.
tiersFloating :: [[Float]] = [ [0.0] , [1.0] , [-1.0, Infinity] , [ 0.5, 2.0, -Infinity] , [-0.5, -2.0] , [ 0.33333334, 3.0] , [-0.33333334, -3.0] , [ 0.25, 0.6666667, 1.5, 4.0] , [-0.25, -0.6666667, -1.5, -4.0] , [ 0.2, 5.0] , [-0.2, -5.0] , [ 0.16666667, 0.4, 0.75, 1.3333334, 2.5, 6.0] , [-0.16666667, -0.4, -0.75, -1.3333334, -2.5, -6.0] , ... ]
NaN
and -0
are excluded from this enumeration.
tiersFractional :: Fractional a => [[a]] #
Tiers of Fractional
values.
This can be used as the implementation of tiers
for Fractional
types.
tiersFractional :: [[Rational]] = [ [ 0 % 1] , [ 1 % 1] , [(-1) % 1] , [ 1 % 2, 2 % 1] , [(-1) % 2, (-2) % 1] , [ 1 % 3, 3 % 1] , [(-1) % 3, (-3) % 1] , [ 1 % 4, 2 % 3, 3 % 2, 4 % 1] , [(-1) % 4, (-2) % 3, (-3) % 2, (-4) % 1] , [ 1 % 5, 5 % 1] , [(-1) % 5, (-5) % 1] , [ 1 % 6, 2 % 5, 3 % 4, 4 % 3, 5 % 2, 6 % 1] , [(-1) % 6, (-2) % 5, (-3) % 4, (-4) % 3, (-5) % 2, (-6) % 1] , ... ]
listIntegral :: (Ord a, Num a) => [a] #
Tiers of Integral
values.
Can be used as a default implementation of list
for Integral
types.
For types with negative values, like Int
,
the list starts with 0 then intercalates between positives and negatives.
listIntegral = [0, 1, -1, 2, -2, 3, -3, 4, -4, ...]
For types without negative values, like Word
,
the list starts with 0 followed by positives of increasing magnitude.
listIntegral = [0, 1, 2, 3, 4, 5, 6, 7, 8, 9, ...]
This function will not work for types that throw errors when the result of
an arithmetic operation is negative such as Natural
. For these, use
[0..]
as the list
implementation.
Takes a list of values xs
and transform it into tiers on which each
tier is occupied by a single element from xs
.
toTiers [x, y, z, ...] = [[x], [y], [z], ...]
To convert back to a list, just concat
.
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.
Instances
Listable Bool | tiers :: [[Bool]] = [[False,True]] list :: [[Bool]] = [False,True] |
Listable Char | list :: [Char] = ['a', ' ', 'b', 'A', 'c', '\', 'n', 'd', ...] |
Listable Double |
list :: [Double] = [0.0, 1.0, -1.0, Infinity, 0.5, 2.0, ...] |
Listable Float |
list :: [Float] = [ 0.0 , 1.0, -1.0, Infinity , 0.5, 2.0, -Infinity, -0.5, -2.0 , 0.33333334, 3.0, -0.33333334, -3.0 , 0.25, 0.6666667, 1.5, 4.0, -0.25, -0.6666667, -1.5, -4.0 , ... ] |
Listable Int | tiers :: [[Int]] = [[0], [1], [-1], [2], [-2], [3], [-3], ...] list :: [Int] = [0, 1, -1, 2, -2, 3, -3, 4, -4, 5, -5, 6, ...] |
Listable Integer | list :: [Int] = [0, 1, -1, 2, -2, 3, -3, 4, -4, 5, -5, 6, ...] |
Listable Ordering | list :: [Ordering] = [LT, EQ, GT] |
Listable () | list :: [()] = [()] tiers :: [[()]] = [[()]] |
Defined in Test.LeanCheck.Core | |
Listable Int1 | |
Listable Int2 | |
Listable Int3 | |
Listable Int4 | |
Listable Word1 | |
Listable Word2 | |
Listable Word3 | |
Listable Word4 | |
Listable Natural | |
Listable Nat | |
Listable Nat1 | |
Listable Nat2 | |
Listable Nat3 | |
Listable Nat4 | |
Listable Nat5 | |
Listable Nat6 | |
Listable Nat7 | |
Listable Space | |
Listable Lower | |
Listable Upper | |
Listable Alpha | |
Listable Digit | |
Listable AlphaNum | |
Listable Letter | |
Listable Spaces | |
Listable Lowers | |
Listable Uppers | |
Listable Alphas | |
Listable Digits | |
Listable AlphaNums | |
Listable Letters | |
Listable a => Listable [a] | tiers :: [[ [Int] ]] = [ [ [] ] , [ [0] ] , [ [0,0], [1] ] , [ [0,0,0], [0,1], [1,0], [-1] ] , ... ] list :: [ [Int] ] = [ [], [0], [0,0], [1], [0,0,0], ... ] |
Defined in Test.LeanCheck.Core | |
Listable a => Listable (Maybe a) | tiers :: [[Maybe Int]] = [[Nothing], [Just 0], [Just 1], ...] tiers :: [[Maybe Bool]] = [[Nothing], [Just False, Just True]] |
Listable a => Listable (NoDup a) | |
Listable a => Listable (Bag a) | |
Listable a => Listable (Set a) | |
(Integral a, Bounded a) => Listable (X a) | Extremily large integers are intercalated with small integers. list :: [X Int] = map X [ 0, 1, -1, maxBound, minBound , 2, -2, maxBound-1, minBound+1 , 3, -3, maxBound-2, minBound+2 , ... ] |
(Integral a, Bounded a) => Listable (Xs a) | Lists with elements of the |
(Listable a, Listable b) => Listable (Either a b) | tiers :: [[Either Bool Bool]] = [[Left False, Right False, Left True, Right True]] tiers :: [[Either Int Int]] = [ [Left 0, Right 0] , [Left 1, Right 1] , [Left (-1), Right (-1)] , [Left 2, Right 2] , ... ] |
(Listable a, Listable b) => Listable (a, b) | tiers :: [[(Int,Int)]] = [ [(0,0)] , [(0,1),(1,0)] , [(0,-1),(1,1),(-1,0)] , ...] list :: [(Int,Int)] = [ (0,0), (0,1), (1,0), (0,-1), (1,1), ...] |
Defined in Test.LeanCheck.Core | |
(Listable a, Listable b) => Listable (Map a b) | |
(Listable a, Listable b, Listable c) => Listable (a, b, c) | list :: [(Int,Int,Int)] = [ (0,0,0), (0,0,1), (0,1,0), ...] |
Defined in Test.LeanCheck.Core | |
(Listable a, Listable b, Listable c, Listable d) => Listable (a, b, c, d) | |
Defined in Test.LeanCheck.Core | |
(Listable a, Listable b, Listable c, Listable d, Listable e) => Listable (a, b, c, d, e) | |
Defined in Test.LeanCheck.Core |