leancheck-0.8.0: Enumerative property-based testing

Copyright(c) 2015-2018 Rudy Matela
License3-Clause BSD (see the file LICENSE)
MaintainerRudy Matela <rudy@matela.com.br>
Safe HaskellSafe
LanguageHaskell2010

Test.LeanCheck.Core

Contents

Description

LeanCheck is a simple enumerative property-based testing library.

This is the core module of the library, with the most basic definitions. If you are looking just to use the library, import and see Test.LeanCheck.

If you want to understand how the code works, this is the place to start reading.

Other important modules:

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

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,

> counterExamples 12 $ \xs -> xs == nub (xs :: [Int])
[["[0,0]"],["[0,0,0]"],["[0,0,0,0]"],["[0,0,1]"],["[0,1,0]"]]

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.

> witness 1000 (\x -> x > 1 && x < 77 && 77 `rem` x == 0)
Just ["7"]

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

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"]]

class Testable a where Source #

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

Minimal complete definition

resultiers

Methods

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

Instances
Testable Bool Source # 
Instance details

Defined in Test.LeanCheck.Core

Methods

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

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

Defined in Test.LeanCheck.Core

Methods

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

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.

> results (<)
[ (["0","0"],    False)
, (["0","1"],    True)
, (["1","0"],    False)
, (["0","(-1)"], False)
, (["1","1"],    False)
, (["(-1)","0"], True)
, (["0","2"],    True)
, (["1","(-1)"], False)
, ...
]
> take 10 $ results (\xs -> xs == nub (xs :: [Int]))
[ (["[]"],      True)
, (["[0]"],     True)
, (["[0,0]"],   False)
, (["[1]"],     True)
, (["[0,0,0]"], False)
, ...
]

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.

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.

Minimal complete definition

list | tiers

Methods

tiers :: [[a]] Source #

list :: [a] Source #

Instances
Listable Bool Source #
tiers :: [[Bool]] = [[False,True]]
list :: [[Bool]] = [False,True]
Instance details

Defined in Test.LeanCheck.Core

Methods

tiers :: [[Bool]] Source #

list :: [Bool] Source #

Listable Char Source #
list :: [Char] = ['a', ' ', 'b', 'A', 'c', '\', 'n', 'd', ...]
Instance details

Defined in Test.LeanCheck.Core

Methods

tiers :: [[Char]] Source #

list :: [Char] Source #

Listable Double Source #

NaN and -0 are not included in the list of Doubles.

list :: [Double]  =  [0.0, 1.0, -1.0, Infinity, 0.5, 2.0, ...]
Instance details

Defined in Test.LeanCheck.Core

Methods

tiers :: [[Double]] Source #

list :: [Double] Source #

Listable Float Source #

NaN and -0 are not included in the list of Floats.

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
  , ...
  ]
Instance details

Defined in Test.LeanCheck.Core

Methods

tiers :: [[Float]] Source #

list :: [Float] Source #

Listable Int Source #
tiers :: [[Int]] = [[0], [1], [-1], [2], [-2], [3], [-3], ...]
list :: [Int] = [0, 1, -1, 2, -2, 3, -3, 4, -4, 5, -5, 6, ...]
Instance details

Defined in Test.LeanCheck.Core

Methods

tiers :: [[Int]] Source #

list :: [Int] Source #

Listable Integer Source #
list :: [Int] = [0, 1, -1, 2, -2, 3, -3, 4, -4, 5, -5, 6, ...]
Instance details

Defined in Test.LeanCheck.Core

Methods

tiers :: [[Integer]] Source #

list :: [Integer] Source #

Listable Ordering Source #
list :: [Ordering]  = [LT, EQ, GT]
Instance details

Defined in Test.LeanCheck.Core

Listable Word Source #
list :: [0, 1, 2, 3, 4, 5, 6, 7, 8, 9, 10, 11, ...]
Instance details

Defined in Test.LeanCheck.Basic

Methods

tiers :: [[Word]] Source #

list :: [Word] Source #

Listable () Source #
list :: [()]  =  [()]
tiers :: [[()]]  =  [[()]]
Instance details

Defined in Test.LeanCheck.Core

Methods

tiers :: [[()]] Source #

list :: [()] Source #

Listable Letters Source # 
Instance details

Defined in Test.LeanCheck.Utils.Types

Methods

tiers :: [[Letters]] Source #

list :: [Letters] Source #

Listable AlphaNums Source # 
Instance details

Defined in Test.LeanCheck.Utils.Types

Listable Digits Source # 
Instance details

Defined in Test.LeanCheck.Utils.Types

Methods

tiers :: [[Digits]] Source #

list :: [Digits] Source #

Listable Alphas Source # 
Instance details

Defined in Test.LeanCheck.Utils.Types

Methods

tiers :: [[Alphas]] Source #

list :: [Alphas] Source #

Listable Uppers Source # 
Instance details

Defined in Test.LeanCheck.Utils.Types

Methods

tiers :: [[Uppers]] Source #

list :: [Uppers] Source #

Listable Lowers Source # 
Instance details

Defined in Test.LeanCheck.Utils.Types

Methods

tiers :: [[Lowers]] Source #

list :: [Lowers] Source #

Listable Spaces Source # 
Instance details

Defined in Test.LeanCheck.Utils.Types

Methods

tiers :: [[Spaces]] Source #

list :: [Spaces] Source #

Listable Letter Source # 
Instance details

Defined in Test.LeanCheck.Utils.Types

Methods

tiers :: [[Letter]] Source #

list :: [Letter] Source #

Listable AlphaNum Source # 
Instance details

Defined in Test.LeanCheck.Utils.Types

Listable Digit Source # 
Instance details

Defined in Test.LeanCheck.Utils.Types

Methods

tiers :: [[Digit]] Source #

list :: [Digit] Source #

Listable Alpha Source # 
Instance details

Defined in Test.LeanCheck.Utils.Types

Methods

tiers :: [[Alpha]] Source #

list :: [Alpha] Source #

Listable Upper Source # 
Instance details

Defined in Test.LeanCheck.Utils.Types

Methods

tiers :: [[Upper]] Source #

list :: [Upper] Source #

Listable Lower Source # 
Instance details

Defined in Test.LeanCheck.Utils.Types

Methods

tiers :: [[Lower]] Source #

list :: [Lower] Source #

Listable Space Source # 
Instance details

Defined in Test.LeanCheck.Utils.Types

Methods

tiers :: [[Space]] Source #

list :: [Space] Source #

Listable Nat7 Source # 
Instance details

Defined in Test.LeanCheck.Utils.Types

Methods

tiers :: [[Nat7]] Source #

list :: [Nat7] Source #

Listable Nat6 Source # 
Instance details

Defined in Test.LeanCheck.Utils.Types

Methods

tiers :: [[Nat6]] Source #

list :: [Nat6] Source #

Listable Nat5 Source # 
Instance details

Defined in Test.LeanCheck.Utils.Types

Methods

tiers :: [[Nat5]] Source #

list :: [Nat5] Source #

Listable Nat4 Source # 
Instance details

Defined in Test.LeanCheck.Utils.Types

Methods

tiers :: [[Nat4]] Source #

list :: [Nat4] Source #

Listable Nat3 Source # 
Instance details

Defined in Test.LeanCheck.Utils.Types

Methods

tiers :: [[Nat3]] Source #

list :: [Nat3] Source #

Listable Nat2 Source # 
Instance details

Defined in Test.LeanCheck.Utils.Types

Methods

tiers :: [[Nat2]] Source #

list :: [Nat2] Source #

Listable Nat1 Source # 
Instance details

Defined in Test.LeanCheck.Utils.Types

Methods

tiers :: [[Nat1]] Source #

list :: [Nat1] Source #

Listable Nat Source # 
Instance details

Defined in Test.LeanCheck.Utils.Types

Methods

tiers :: [[Nat]] Source #

list :: [Nat] Source #

Listable Natural Source # 
Instance details

Defined in Test.LeanCheck.Utils.Types

Methods

tiers :: [[Natural]] Source #

list :: [Natural] Source #

Listable Word4 Source # 
Instance details

Defined in Test.LeanCheck.Utils.Types

Methods

tiers :: [[Word4]] Source #

list :: [Word4] Source #

Listable Word3 Source # 
Instance details

Defined in Test.LeanCheck.Utils.Types

Methods

tiers :: [[Word3]] Source #

list :: [Word3] Source #

Listable Word2 Source # 
Instance details

Defined in Test.LeanCheck.Utils.Types

Methods

tiers :: [[Word2]] Source #

list :: [Word2] Source #

Listable Word1 Source # 
Instance details

Defined in Test.LeanCheck.Utils.Types

Methods

tiers :: [[Word1]] Source #

list :: [Word1] Source #

Listable Int4 Source # 
Instance details

Defined in Test.LeanCheck.Utils.Types

Methods

tiers :: [[Int4]] Source #

list :: [Int4] Source #

Listable Int3 Source # 
Instance details

Defined in Test.LeanCheck.Utils.Types

Methods

tiers :: [[Int3]] Source #

list :: [Int3] Source #

Listable Int2 Source # 
Instance details

Defined in Test.LeanCheck.Utils.Types

Methods

tiers :: [[Int2]] Source #

list :: [Int2] Source #

Listable Int1 Source # 
Instance details

Defined in Test.LeanCheck.Utils.Types

Methods

tiers :: [[Int1]] Source #

list :: [Int1] Source #

Listable a => Listable [a] Source #
tiers :: [[ [Int] ]] = [ [ [] ]
                       , [ [0] ]
                       , [ [0,0], [1] ]
                       , [ [0,0,0], [0,1], [1,0], [-1] ]
                       , ... ]
list :: [ [Int] ] = [ [], [0], [0,0], [1], [0,0,0], ... ]
Instance details

Defined in Test.LeanCheck.Core

Methods

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

list :: [[a]] Source #

Listable a => Listable (Maybe a) Source #
tiers :: [[Maybe Int]] = [[Nothing], [Just 0], [Just 1], ...]
tiers :: [[Maybe Bool]] = [[Nothing], [Just False, Just True]]
Instance details

Defined in Test.LeanCheck.Core

Methods

tiers :: [[Maybe a]] Source #

list :: [Maybe a] Source #

(Integral a, Listable a) => Listable (Ratio a) Source #
list :: [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
  , ...
  ]
Instance details

Defined in Test.LeanCheck.Basic

Methods

tiers :: [[Ratio a]] Source #

list :: [Ratio a] Source #

(Integral a, Bounded a) => Listable (Xs a) Source #

Lists with elements of the X type.

Instance details

Defined in Test.LeanCheck.Utils.Types

Methods

tiers :: [[Xs a]] Source #

list :: [Xs a] Source #

(Integral a, Bounded a) => Listable (X a) Source #

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
     , ... ]
Instance details

Defined in Test.LeanCheck.Utils.Types

Methods

tiers :: [[X a]] Source #

list :: [X a] Source #

Listable a => Listable (Set a) Source # 
Instance details

Defined in Test.LeanCheck.Utils.Types

Methods

tiers :: [[Set a]] Source #

list :: [Set a] Source #

Listable a => Listable (Bag a) Source # 
Instance details

Defined in Test.LeanCheck.Utils.Types

Methods

tiers :: [[Bag a]] Source #

list :: [Bag a] Source #

Listable a => Listable (NoDup a) Source # 
Instance details

Defined in Test.LeanCheck.Utils.Types

Methods

tiers :: [[NoDup a]] Source #

list :: [NoDup a] Source #

(Eq a, Listable a, Listable b) => Listable (a -> b) Source # 
Instance details

Defined in Test.LeanCheck.Function.Listable.ListsOfPairs

Methods

tiers :: [[a -> b]] Source #

list :: [a -> b] Source #

(Listable a, Listable b) => Listable (Either a b) Source #
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]
                              , ... ]
Instance details

Defined in Test.LeanCheck.Core

Methods

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

list :: [Either a b] Source #

(Listable a, Listable b) => Listable (a, b) Source #
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), ...]
Instance details

Defined in Test.LeanCheck.Core

Methods

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

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

(Listable a, Listable b) => Listable (Map a b) Source # 
Instance details

Defined in Test.LeanCheck.Utils.Types

Methods

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

list :: [Map a b] Source #

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

Defined in Test.LeanCheck.Core

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 # 
Instance details

Defined in Test.LeanCheck.Core

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 # 
Instance details

Defined in Test.LeanCheck.Core

Methods

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

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

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

Defined in Test.LeanCheck.Basic

Methods

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

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

(Listable a, Listable b, Listable c, Listable d, Listable e, Listable f, Listable g) => Listable (a, b, c, d, e, f, g) Source # 
Instance details

Defined in Test.LeanCheck.Basic

Methods

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

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

(Listable a, Listable b, Listable c, Listable d, Listable e, Listable f, Listable g, Listable h) => Listable (a, b, c, d, e, f, g, h) Source # 
Instance details

Defined in Test.LeanCheck.Basic

Methods

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

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

(Listable a, Listable b, Listable c, Listable d, Listable e, Listable f, Listable g, Listable h, Listable i) => Listable (a, b, c, d, e, f, g, h, i) Source # 
Instance details

Defined in Test.LeanCheck.Basic

Methods

tiers :: [[(a, b, c, d, e, f, g, h, i)]] Source #

list :: [(a, b, c, d, e, f, g, h, i)] Source #

(Listable a, Listable b, Listable c, Listable d, Listable e, Listable f, Listable g, Listable h, Listable i, Listable j) => Listable (a, b, c, d, e, f, g, h, i, j) Source # 
Instance details

Defined in Test.LeanCheck.Basic

Methods

tiers :: [[(a, b, c, d, e, f, g, h, i, j)]] Source #

list :: [(a, b, c, d, e, f, g, h, i, j)] Source #

(Listable a, Listable b, Listable c, Listable d, Listable e, Listable f, Listable g, Listable h, Listable i, Listable j, Listable k) => Listable (a, b, c, d, e, f, g, h, i, j, k) Source # 
Instance details

Defined in Test.LeanCheck.Basic

Methods

tiers :: [[(a, b, c, d, e, f, g, h, i, j, k)]] Source #

list :: [(a, b, c, d, e, f, g, h, i, j, k)] Source #

(Listable a, Listable b, Listable c, Listable d, Listable e, Listable f, Listable g, Listable h, Listable i, Listable j, Listable k, Listable l) => Listable (a, b, c, d, e, f, g, h, i, j, k, l) Source # 
Instance details

Defined in Test.LeanCheck.Basic

Methods

tiers :: [[(a, b, c, d, e, f, g, h, i, j, k, l)]] Source #

list :: [(a, b, c, d, e, f, g, h, i, j, k, l)] Source #

Constructing lists of tiers

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.

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

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>)
         \/ ...

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

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).

suchThat :: [[a]] -> (a -> Bool) -> [[a]] Source #

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], [], ...]

This function is just a flipped version of filterT.

Combining lists of 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 lists of tiers

mapT :: (a -> b) -> [[a]] -> [[b]] Source #

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]

filterT :: (a -> Bool) -> [[a]] -> [[a]] Source #

filter tiers

filterT p [xs, yz, zs, ...]  =  [filter p xs, filter p ys, filter p zs]
filterT odd tiers  =  [[], [1], [-1], [], [], [3], [-3], [], [], [5], ...]

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

concat tiers of tiers

concatMapT :: (a -> [[b]]) -> [[a]] -> [[b]] Source #

concatMap over tiers

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.

> toTiers [x, y, z, ...]
[ [x], [y], [z], ...]

To convert back to a list, just concat.

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

Examples:

> prop_addMonotonic x y  =  y > 0 ==> x + y > x
> check prop_addMonotonic
+++ OK, passed 200 tests.

Misc utilities

(+|) :: [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,...]

listIntegral :: (Ord a, Num a) => [a] Source #

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.

tiersFractional :: Fractional a => [[a]] Source #

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]
  , ...
  ]

tiersFloating :: Fractional a => [[a]] Source #

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.