leancheck-1.0.2: Enumerative property-based testing
Copyright(c) 2015-2024 Rudy Matela
License3-Clause BSD (see the file LICENSE)
MaintainerRudy Matela <rudy@matela.com.br>
Safe HaskellSafe-Inferred
LanguageHaskell2010

Test.LeanCheck

Description

LeanCheck is a simple enumerative property-based testing library.

A property is a function returning a Bool that should be True for all possible choices of arguments. Properties can be viewed as a parameterized unit tests.

To check if a property holds by testing up to a thousand values, we evaluate:

holds 1000 property

True indicates success. False indicates a bug.

For example:

> import Data.List (sort)
> holds 1000 $ \xs -> length (sort xs) == length (xs::[Int])
True

To get the smallest counterExample by testing up to a thousand values, we evaluate:

counterExample 1000 property

Nothing indicates no counterexample was found, a Just value indicates a counterexample.

For instance:

> import Data.List (union)
> counterExample 1000 $ \xs ys -> union xs ys == union ys (xs :: [Int])
Just ["[]","[0,0]"]

The suggested values for the number of tests to use with LeanCheck are 500, 1 000 or 10 000. LeanCheck is memory intensive and you should take care if you go beyond that.

The function check can also be used to test and report counterexamples.

> check $ \xs ys -> union xs ys == union ys (xs :: [Int])
*** Failed! Falsifiable (after 4 tests):
[] [0,0]

Arguments of properties should be instances of the Listable typeclass. Listable instances are provided for the most common Haskell types. New instances are easily defined (see Listable for more info).

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

fails :: Testable a => Int -> a -> Bool Source #

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.

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
True

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.

Counterexamples and witnesses

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

Reporting

check :: Testable a => a -> IO () Source #

Checks a property printing results on stdout

> check $ \xs -> sort (sort xs) == sort (xs::[Int])
+++ OK, passed 200 tests.
> check $ \xs ys -> xs `union` ys == ys `union` (xs::[Int])
*** Failed! Falsifiable (after 4 tests):
[] [0,0]

checkFor :: Testable a => Int -> a -> IO () Source #

Check a property for a given number of tests printing results on stdout

> checkFor 1000 $ \xs -> sort (sort xs) == sort (xs::[Int])
+++ OK, passed 1000 tests.

Test exhaustion is reported when the configured number of tests is larger than the number of available test values:

> checkFor 3 $ \p -> p == not (not p)
+++ OK, passed 2 tests (exhausted).

checkResult :: Testable a => a -> IO Bool Source #

Check a property printing results on stdout and returning True on success.

> p <- checkResult $ \xs -> sort (sort xs) == sort (xs::[Int])
+++ OK, passed 200 tests.

> q <- checkResult $ \xs ys -> xs `union` ys == ys `union` (xs::[Int])
*** Failed! Falsifiable (after 4 tests):
[] [0,0]

> p && q
False

There is no option to silence this function: for silence, you should use holds.

checkResultFor :: Testable a => Int -> a -> IO Bool Source #

Check a property for a given number of tests printing results on stdout and returning True on success.

> checkResultFor 1000 $ \xs -> sort (sort xs) == sort (xs::[Int])
+++ OK, passed 1000 tests.
True

There is no option to silence this function: for silence, you should use holds.

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

Instances details
Listable CBool Source # 
Instance details

Defined in Test.LeanCheck.Basic

Methods

tiers :: [[CBool]] Source #

list :: [CBool] Source #

Listable CChar Source # 
Instance details

Defined in Test.LeanCheck.Basic

Methods

tiers :: [[CChar]] Source #

list :: [CChar] Source #

Listable CClock Source # 
Instance details

Defined in Test.LeanCheck.Basic

Methods

tiers :: [[CClock]] Source #

list :: [CClock] Source #

Listable CDouble Source # 
Instance details

Defined in Test.LeanCheck.Basic

Methods

tiers :: [[CDouble]] Source #

list :: [CDouble] Source #

Listable CFloat Source # 
Instance details

Defined in Test.LeanCheck.Basic

Methods

tiers :: [[CFloat]] Source #

list :: [CFloat] Source #

Listable CInt Source # 
Instance details

Defined in Test.LeanCheck.Basic

Methods

tiers :: [[CInt]] Source #

list :: [CInt] Source #

Listable CIntMax Source # 
Instance details

Defined in Test.LeanCheck.Basic

Methods

tiers :: [[CIntMax]] Source #

list :: [CIntMax] Source #

Listable CIntPtr Source # 
Instance details

Defined in Test.LeanCheck.Basic

Methods

tiers :: [[CIntPtr]] Source #

list :: [CIntPtr] Source #

Listable CLLong Source # 
Instance details

Defined in Test.LeanCheck.Basic

Methods

tiers :: [[CLLong]] Source #

list :: [CLLong] Source #

Listable CLong Source # 
Instance details

Defined in Test.LeanCheck.Basic

Methods

tiers :: [[CLong]] Source #

list :: [CLong] Source #

Listable CPtrdiff Source # 
Instance details

Defined in Test.LeanCheck.Basic

Listable CSChar Source # 
Instance details

Defined in Test.LeanCheck.Basic

Methods

tiers :: [[CSChar]] Source #

list :: [CSChar] Source #

Listable CSUSeconds Source # 
Instance details

Defined in Test.LeanCheck.Basic

Listable CShort Source # 
Instance details

Defined in Test.LeanCheck.Basic

Methods

tiers :: [[CShort]] Source #

list :: [CShort] Source #

Listable CSigAtomic Source # 
Instance details

Defined in Test.LeanCheck.Basic

Listable CSize Source # 
Instance details

Defined in Test.LeanCheck.Basic

Methods

tiers :: [[CSize]] Source #

list :: [CSize] Source #

Listable CTime Source # 
Instance details

Defined in Test.LeanCheck.Basic

Methods

tiers :: [[CTime]] Source #

list :: [CTime] Source #

Listable CUChar Source # 
Instance details

Defined in Test.LeanCheck.Basic

Methods

tiers :: [[CUChar]] Source #

list :: [CUChar] Source #

Listable CUInt Source # 
Instance details

Defined in Test.LeanCheck.Basic

Methods

tiers :: [[CUInt]] Source #

list :: [CUInt] Source #

Listable CUIntMax Source # 
Instance details

Defined in Test.LeanCheck.Basic

Listable CUIntPtr Source # 
Instance details

Defined in Test.LeanCheck.Basic

Listable CULLong Source # 
Instance details

Defined in Test.LeanCheck.Basic

Methods

tiers :: [[CULLong]] Source #

list :: [CULLong] Source #

Listable CULong Source # 
Instance details

Defined in Test.LeanCheck.Basic

Methods

tiers :: [[CULong]] Source #

list :: [CULong] Source #

Listable CUSeconds Source # 
Instance details

Defined in Test.LeanCheck.Basic

Listable CUShort Source # 
Instance details

Defined in Test.LeanCheck.Basic

Methods

tiers :: [[CUShort]] Source #

list :: [CUShort] Source #

Listable CWchar Source # 
Instance details

Defined in Test.LeanCheck.Basic

Methods

tiers :: [[CWchar]] Source #

list :: [CWchar] Source #

Listable SeekMode Source # 
Instance details

Defined in Test.LeanCheck.Basic

Listable ExitCode Source #

Only includes valid POSIX exit codes

> list :: [ExitCode]
[ExitSuccess, ExitFailure 1, ExitFailure 2, ..., ExitFailure 255]
Instance details

Defined in Test.LeanCheck.Basic

Listable BufferMode Source # 
Instance details

Defined in Test.LeanCheck.Basic

Listable IOMode Source # 
Instance details

Defined in Test.LeanCheck.Basic

Methods

tiers :: [[IOMode]] Source #

list :: [IOMode] Source #

Listable Int16 Source #
list :: [Int16]  =  [0, 1, -1, 2, -2, ..., 32767, -32767, -32768]
Instance details

Defined in Test.LeanCheck.Basic

Methods

tiers :: [[Int16]] Source #

list :: [Int16] Source #

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

Defined in Test.LeanCheck.Basic

Methods

tiers :: [[Int32]] Source #

list :: [Int32] Source #

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

Defined in Test.LeanCheck.Basic

Methods

tiers :: [[Int64]] Source #

list :: [Int64] Source #

Listable Int8 Source #
list :: [Int8]  =  [0, 1, -1, 2, -2, 3, -3, ..., 127, -127, -128]
Instance details

Defined in Test.LeanCheck.Basic

Methods

tiers :: [[Int8]] Source #

list :: [Int8] Source #

Listable GeneralCategory Source # 
Instance details

Defined in Test.LeanCheck.Basic

Listable Word16 Source #
list :: [Word16]  =  [0, 1, 2, 3, 4, 5, 6, 7, 8, 9, ..., 65535]
Instance details

Defined in Test.LeanCheck.Basic

Methods

tiers :: [[Word16]] Source #

list :: [Word16] Source #

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

Defined in Test.LeanCheck.Basic

Methods

tiers :: [[Word32]] Source #

list :: [Word32] Source #

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

Defined in Test.LeanCheck.Basic

Methods

tiers :: [[Word64]] Source #

list :: [Word64] Source #

Listable Word8 Source #
list :: [Word8]  =  [0, 1, 2, 3, 4, 5, 6, 7, 8, 9, ..., 255]
Instance details

Defined in Test.LeanCheck.Basic

Methods

tiers :: [[Word8]] Source #

list :: [Word8] Source #

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

Defined in Test.LeanCheck.Core

Listable A Source # 
Instance details

Defined in Test.LeanCheck.Utils.Types

Methods

tiers :: [[A]] Source #

list :: [A] Source #

Listable Alpha Source # 
Instance details

Defined in Test.LeanCheck.Utils.Types

Methods

tiers :: [[Alpha]] Source #

list :: [Alpha] Source #

Listable AlphaNum Source # 
Instance details

Defined in Test.LeanCheck.Utils.Types

Listable AlphaNums Source # 
Instance details

Defined in Test.LeanCheck.Utils.Types

Listable Alphas Source # 
Instance details

Defined in Test.LeanCheck.Utils.Types

Methods

tiers :: [[Alphas]] Source #

list :: [Alphas] Source #

Listable B Source # 
Instance details

Defined in Test.LeanCheck.Utils.Types

Methods

tiers :: [[B]] Source #

list :: [B] Source #

Listable C Source # 
Instance details

Defined in Test.LeanCheck.Utils.Types

Methods

tiers :: [[C]] Source #

list :: [C] Source #

Listable D Source # 
Instance details

Defined in Test.LeanCheck.Utils.Types

Methods

tiers :: [[D]] Source #

list :: [D] Source #

Listable Digit Source # 
Instance details

Defined in Test.LeanCheck.Utils.Types

Methods

tiers :: [[Digit]] Source #

list :: [Digit] Source #

Listable Digits Source # 
Instance details

Defined in Test.LeanCheck.Utils.Types

Methods

tiers :: [[Digits]] Source #

list :: [Digits] Source #

Listable E Source # 
Instance details

Defined in Test.LeanCheck.Utils.Types

Methods

tiers :: [[E]] Source #

list :: [E] Source #

Listable F Source # 
Instance details

Defined in Test.LeanCheck.Utils.Types

Methods

tiers :: [[F]] Source #

list :: [F] Source #

Listable Int1 Source # 
Instance details

Defined in Test.LeanCheck.Utils.Types

Methods

tiers :: [[Int1]] Source #

list :: [Int1] Source #

Listable Int2 Source # 
Instance details

Defined in Test.LeanCheck.Utils.Types

Methods

tiers :: [[Int2]] Source #

list :: [Int2] Source #

Listable Int3 Source # 
Instance details

Defined in Test.LeanCheck.Utils.Types

Methods

tiers :: [[Int3]] Source #

list :: [Int3] Source #

Listable Int4 Source # 
Instance details

Defined in Test.LeanCheck.Utils.Types

Methods

tiers :: [[Int4]] Source #

list :: [Int4] Source #

Listable Letter Source # 
Instance details

Defined in Test.LeanCheck.Utils.Types

Methods

tiers :: [[Letter]] Source #

list :: [Letter] Source #

Listable Letters Source # 
Instance details

Defined in Test.LeanCheck.Utils.Types

Methods

tiers :: [[Letters]] Source #

list :: [Letters] Source #

Listable Lower Source # 
Instance details

Defined in Test.LeanCheck.Utils.Types

Methods

tiers :: [[Lower]] Source #

list :: [Lower] Source #

Listable Lowers Source # 
Instance details

Defined in Test.LeanCheck.Utils.Types

Methods

tiers :: [[Lowers]] Source #

list :: [Lowers] Source #

Listable Nat Source # 
Instance details

Defined in Test.LeanCheck.Utils.Types

Methods

tiers :: [[Nat]] Source #

list :: [Nat] Source #

Listable Nat1 Source # 
Instance details

Defined in Test.LeanCheck.Utils.Types

Methods

tiers :: [[Nat1]] Source #

list :: [Nat1] Source #

Listable Nat2 Source # 
Instance details

Defined in Test.LeanCheck.Utils.Types

Methods

tiers :: [[Nat2]] Source #

list :: [Nat2] Source #

Listable Nat3 Source # 
Instance details

Defined in Test.LeanCheck.Utils.Types

Methods

tiers :: [[Nat3]] Source #

list :: [Nat3] Source #

Listable Nat4 Source # 
Instance details

Defined in Test.LeanCheck.Utils.Types

Methods

tiers :: [[Nat4]] Source #

list :: [Nat4] Source #

Listable Nat5 Source # 
Instance details

Defined in Test.LeanCheck.Utils.Types

Methods

tiers :: [[Nat5]] Source #

list :: [Nat5] Source #

Listable Nat6 Source # 
Instance details

Defined in Test.LeanCheck.Utils.Types

Methods

tiers :: [[Nat6]] Source #

list :: [Nat6] Source #

Listable Nat7 Source # 
Instance details

Defined in Test.LeanCheck.Utils.Types

Methods

tiers :: [[Nat7]] Source #

list :: [Nat7] Source #

Listable Natural Source # 
Instance details

Defined in Test.LeanCheck.Utils.Types

Methods

tiers :: [[Natural]] Source #

list :: [Natural] Source #

Listable Space Source # 
Instance details

Defined in Test.LeanCheck.Utils.Types

Methods

tiers :: [[Space]] Source #

list :: [Space] Source #

Listable Spaces Source # 
Instance details

Defined in Test.LeanCheck.Utils.Types

Methods

tiers :: [[Spaces]] Source #

list :: [Spaces] Source #

Listable Upper Source # 
Instance details

Defined in Test.LeanCheck.Utils.Types

Methods

tiers :: [[Upper]] Source #

list :: [Upper] Source #

Listable Uppers Source # 
Instance details

Defined in Test.LeanCheck.Utils.Types

Methods

tiers :: [[Uppers]] Source #

list :: [Uppers] Source #

Listable Word1 Source # 
Instance details

Defined in Test.LeanCheck.Utils.Types

Methods

tiers :: [[Word1]] Source #

list :: [Word1] Source #

Listable Word2 Source # 
Instance details

Defined in Test.LeanCheck.Utils.Types

Methods

tiers :: [[Word2]] Source #

list :: [Word2] Source #

Listable Word3 Source # 
Instance details

Defined in Test.LeanCheck.Utils.Types

Methods

tiers :: [[Word3]] Source #

list :: [Word3] Source #

Listable Word4 Source # 
Instance details

Defined in Test.LeanCheck.Utils.Types

Methods

tiers :: [[Word4]] Source #

list :: [Word4] 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 () Source #
list :: [()]  =  [()]
tiers :: [[()]]  =  [[()]]
Instance details

Defined in Test.LeanCheck.Core

Methods

tiers :: [[()]] Source #

list :: [()] Source #

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 Word Source #
list :: [Word]  =  [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 #

(RealFloat a, Listable a) => Listable (Complex a) Source # 
Instance details

Defined in Test.LeanCheck.Basic

Methods

tiers :: [[Complex a]] Source #

list :: [Complex 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 #

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 #

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

Defined in Test.LeanCheck.Utils.Types

Methods

tiers :: [[Set a]] Source #

list :: [Set 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 #

(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 #

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 #

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 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 (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 (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 #

(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 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 #

Listing constructors

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.

To be used in the declaration of tiers in Listable instances.

instance Listable <Type> where
  tiers  =  ...
         \/ cons0 <Constructor>
         \/ ...

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.

To be used in the declaration of tiers in Listable instances.

instance Listable <Type> where
  tiers  =  ...
         \/ cons1 <Constructor>
         \/ ...

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.

To be used in the declaration of tiers in Listable instances.

instance Listable <Type> where
  tiers  =  ...
         \/ cons2 <Constructor>
         \/ ...

cons3 :: (Listable a, Listable b, Listable c) => (a -> b -> c -> d) -> [[d]] Source #

Returns tiers of applications of a 3-argument constructor.

To be used in the declaration of tiers in Listable instances.

instance Listable <Type> where
  tiers  =  ...
         \/ cons3 <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.

To be used in the declaration of tiers in Listable instances.

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.

To be used in the declaration of tiers in Listable instances.

cons6 :: (Listable a, Listable b, Listable c, Listable d, Listable e, Listable f) => (a -> b -> c -> d -> e -> f -> g) -> [[g]] Source #

Returns tiers of applications of a 6-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]] Source #

Returns tiers of applications of a 7-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]] Source #

Returns tiers of applications of a 8-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]] Source #

Returns tiers of applications of a 9-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]] Source #

Returns tiers of applications of a 10-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]] Source #

Returns tiers of applications of a 11-argument constructor.

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]] Source #

Returns tiers of applications of a 12-argument constructor.

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

ofWeight :: [[a]] -> Int -> [[a]] Source #

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.

addWeight :: [[a]] -> Int -> [[a]] Source #

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.

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

(cf. productWith)

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

(cf. ><)

Manipulating 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

concatT [ [xss0, yss0, zss0, ...]
        , [xss1, yss1, zss1, ...]
        , [xss2, yss2, zss2, ...]
        , ...
        ]
  =  xss0 \/ yss0 \/ zss0 \/ ...
          \/ delay (xss1 \/ yss1 \/ zss1 \/ ...
                         \/ delay (xss2 \/ yss2 \/ zss2 \/ ...
                                        \/ (delay ...)))

(cf. concatMapT)

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

concatMap over tiers

concatMapT f [ [x0, y0, z0]
             , [x1, y1, z1]
             , [x2, y2, z2]
             , ...
             ]
  =  f x0 \/ f y0 \/ f z0 \/ ...
          \/ delay (f x1 \/ f y1 \/ f z1 \/ ...
                         \/ delay (f x2 \/ f y2 \/ f z2 \/ ...
                                        \/ (delay ...)))

(cf. concatT)

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.

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.

Automatically deriving Listable instances

deriveListable :: Name -> DecsQ Source #

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.

deriveListableCascading :: Name -> DecsQ Source #

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

Specialized constructors of tiers

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

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.

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

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 #

Take the product of lists of tiers by a function returning a Maybe value discarding Nothing values.

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

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

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

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

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

Listing values

tiersFloating :: (Ord a, 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.

NaN and -0 are excluded from this enumeration.

This function is deprecated. Please consider using listFloating instead or use toTiers listFloating.

tiersFractional :: (Ord a, Fractional a) => [[a]] Source #

Tiers of Fractional values. This can be used as the implementation of tiers for Fractional types.

This function is deprecated. Please consider using listFractional instead or use toTiers listFractional.

listFloating :: (Ord a, Fractional a) => [a] Source #

Listing of Floating values. This can be used as the implementation of list for Floating types.

listFloating :: [Double]  =
  [0.0, 1.0, -1.0, 0.5, -0.5, 2.0, Infinity, -Infinity, -2.0, 0.333, ...]

This follow the same Calkin-Wilf sequence of listFractional but positive and negative infinities are artificially included after two.

NaN and -0 are excluded from this enumeration.

listFractional :: (Ord a, Fractional a) => [a] Source #

Listing of Fractional values. This can be used as the implementation of list for Fractional types.

listFractional :: [[Rational]]  =
  [0 % 1, 1 % 1, (-1) % 1, 1 % 2, (-1) % 2, 2 % 1, (-2) % 1, 1 % 3, ...]

All rationals are included without repetition in their most simple form. This is the Calkin-Wilf sequence computed with the help of the fusc function (EWD 570).

This also works for unsigned types that wrap around zero, yielding:

listFractional :: [Ratio Word]  =
  [0 % 1, 1 % 1, 1 % 2, 2 % 1, 1 % 3, 3 % 2, 2 % 3, 3 % 1, 1 % 4, ...]

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.

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

Test results

class Testable a 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

(cf. results)

Minimal complete definition

resultiers

Instances

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