| Copyright | (c) 2017 Rudy Matela |
|---|---|
| License | 3-Clause BSD (see the file LICENSE) |
| Maintainer | Rudy Matela <rudy@matela.com.br> |
| 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 360 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:_
The property fails for any integer x and for any list _ at the tail.
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
- minFailures :: Testable a => (WithOption a -> b) -> Ratio Int -> a -> b
- class (Listable a, Typeable a, Show a) => Generalizable a where
- this :: Generalizable a => a -> (Instances -> Instances) -> Instances -> Instances
- data Expr
- constant :: Typeable a => String -> a -> Expr
- showConstant :: (Typeable a, Show a) => a -> Expr
- bgEq :: (Eq a, Generalizable a) => a -> [Expr]
- bgOrd :: (Ord a, Generalizable a) => a -> [Expr]
- class Testable a
- deriveGeneralizable :: Name -> DecsQ
- deriveGeneralizableIfNeeded :: Name -> DecsQ
- deriveGeneralizableCascading :: Name -> DecsQ
- 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]]
- tiersFractional :: Fractional a => [[a]]
- listIntegral :: (Enum a, Num a) => [a]
- toTiers :: [a] -> [[a]]
- class Listable a where
- module Test.LeanCheck.Utils.TypeBinding
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:_)
for :: Testable a => (WithOption a -> b) -> Int -> a -> b Source #
Use to configure the number of tests performed by forcheck.
> check `for` 10080 $ \xs -> sort (sort xs) == sort (xs :: [Int]) +++ OK, passed 10080 tests.
Don't forget the dollar ($)!
withBackground :: Testable a => (WithOption a -> b) -> [Expr] -> a -> b Source #
Use to provide additional functions to appear in side-conditions.withBackground
check `withBackground` [constant "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
minFailures :: Testable a => (WithOption a -> b) -> Ratio Int -> a -> b Source #
Use to configure the minimum number of failures for a
conditional generalization in function of the maximum number of tests.minFailures
To set that conditional generalizations should fail for 10% of cases:
> check minFailures (div 10) $ prop
To set that conditional generalizations should fail for 5% of cases:
> check minFailures (div 20) $ prop
Generalizable types
class (Listable a, Typeable a, Show a) => Generalizable a where Source #
Extrapolate can generalize counter-examples of any types that are
Generalizable.
The core (and only required functions) of the generalizable typeclass are
the expr and instances functions.
The following example shows a datatype and its instance:
data Stack a = Stack a (Stack a) | Empty
instance Generalizable a => Generalizable (Stack a) where name _ = "s" expr s@(Stack x y) = constant "Stack" (Stack ->>: s) :$ expr x :$ expr y expr s@Empty = constant "Empty" (Empty -: s) instances s = this s $ instances (argTy1of1 s)
To declare instances and expr it may be useful to use:
- LeanCheck's Test.LeanCheck.Utils.TypeBinding operators:
-:,->:,->>:, ...; - Extrapolate's Test.Extrapolate.TypeBinding operators:
argTy1of1,argTy1of2,argTy2of2, ....
Methods
Common name for a variable, defaults to "x".
background :: a -> [Expr] Source #
List of symbols allowed to appear in side-conditions.
Defaults to []. See constant.
instances :: a -> Instances -> Instances Source #
Computes a list of reified instances. See this.
Instances
showConstant :: (Typeable a, Show a) => a -> Expr #
Testable properties
Minimal complete definition
Instances
| Testable Bool Source # | |
| Testable a => Testable (WithOption a) Source # | |
Defined in Test.Extrapolate.Core Methods resultiers :: WithOption a -> [[([Expr], Bool)]] Source # ($-|) :: 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 # | |
Automatically deriving Generalizable instances
deriveGeneralizable :: Name -> DecsQ Source #
Derives a Generalizable instance for a given type Name.
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
expr s@(Stack x y) = constant "Stack" (Stack ->>: s) :$ expr x :$ expr y
expr s@Empty = constant "Empty" (Empty -: s)
instances s = this "s" s
$ let Stack x y = Stack undefined undefined `asTypeOf` s
in instances x
. instances yThis 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.
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 #
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
Needs the TemplateHaskell extension.
ofWeight :: [[a]] -> Int -> [[a]] #
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 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 0
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 infixr 0 #
Boolean implication operator. Useful for defining conditional properties:
prop_something x y = condition x y ==> something x y
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
fails :: Testable a => Int -> a -> Bool #
Does a property fail for a number of test values?
fails 1000 $ \xs -> xs ++ ys == ys ++ xs
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
witnesses :: Testable a => Int -> a -> [[String]] #
Lists all witnesses up to a number of tests to a property,
(><) :: [[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)] ... ]
(\\//) :: [[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
cons<N> `suchThat` condition
Resets any delays in a list-of tiers.
Conceptually this function makes a constructor "weightless",
assuring the first tier is non-empty.
Typically used when defining Listable instances:
reset (cons<N> <Constr>)
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).
cons5 :: (Listable a, Listable b, Listable c, Listable d, Listable e) => (a -> b -> c -> d -> e -> f) -> [[f]] #
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.
cons4 :: (Listable a, Listable b, Listable c, Listable d) => (a -> b -> c -> d -> e) -> [[e]] #
Returns tiers of applications of a 4-argument constructor.
cons3 :: (Listable a, Listable b, Listable c) => (a -> b -> c -> d) -> [[d]] #
Returns tiers of applications of a 3-argument constructor.
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.
concatMapT :: (a -> [[b]]) -> [[a]] -> [[b]] #
concatMap over tiers
tiersFractional :: Fractional a => [[a]] #
Tiers of Fractional values.
This can be used as the implementation of tiers for Fractional types.
listIntegral :: (Enum a, Num a) => [a] #
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.
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> ConstructorZwhere 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.
Instances
| Listable Bool | tiers :: [[Bool]] = [[False,True]] list :: [[Bool]] = [False,True] |
| Listable Char | |
| Listable Double | |
| Listable Float | |
| 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 | |
| Listable Ordering | |
| Listable () | |
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 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) | |
| (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) | |
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 | |