leancheck-0.9.3: Enumerative property-based testing

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

Test.LeanCheck.Function.ShowFunction

Contents

Description

This module is part of LeanCheck, a simple enumerative property-based testing library.

This module exports the ShowFunction typeclass, its instances and related functions.

Using this module, it is possible to implement a Show instance for functions:

import Test.LeanCheck.ShowFunction
instance (Show a, Listable a, ShowFunction b) => Show (a->b) where
  show = showFunction 8

This shows functions as a case pattern with up to 8 cases.

It will only work for functions whose ultimate return value is an instance of ShowFunction. This module provides instances for most standard data types (Int, Bool, Maybe, ...). Please see the ShowFunction typeclass documentation for how to declare istances for user-defined data types.

The modules Test.LeanCheck.Function and Test.LeanCheck.Function.Show exports an instance like the one above.

Synopsis

Showing functions

showFunction :: ShowFunction a => Int -> a -> String Source #

Given the number of patterns to show, shows a ShowFunction value.

> putStrLn $ showFunction undefined True
True

> putStrLn $ showFunction 3 (id::Int->Int)
\x -> case x of
      0 -> 0
      1 -> 1
      -1 -> -1
      ...

> putStrLn $ showFunction 4 (&&)
\x y -> case (x,y) of
        (True,True) -> True
        _ -> False

In the examples above, "..." should be interpreted literally.

This can be used as an implementation of show for functions:

instance (Show a, Listable a, ShowFunction b) => Show (a->b) where
  show = showFunction 8

See showFunctionLine for an alternative without line breaks.

showFunctionLine :: ShowFunction a => Int -> a -> String Source #

Same as showFunction, but has no line breaks.

> putStrLn $ showFunctionLine 3 (id::Int->Int)
\x -> case x of 0 -> 0; 1 -> 1; -1 -> -1; ...
> putStrLn $ showFunctionLine 3 (&&)
\x y -> case (x,y) of (True,True) -> True; _ -> False

This can be used as an implementation of show for functions:

instance (Show a, Listable a, ShowFunction b) => Show (a->b) where
  show = showFunction 8

Support for user-defined algebraic datatypes on return values

class ShowFunction a where Source #

ShowFunction values are those for which we can return a list of functional bindings.

Instances for showable algebraic datatypes are defined using bindtiersShow:

instance ShowFunction Ty where bindtiers = bindtiersShow

Methods

bindtiers :: a -> [[Binding]] Source #

Instances
ShowFunction Bool Source # 
Instance details

Defined in Test.LeanCheck.Function.ShowFunction

Methods

bindtiers :: Bool -> [[Binding]] Source #

ShowFunction Char Source # 
Instance details

Defined in Test.LeanCheck.Function.ShowFunction

Methods

bindtiers :: Char -> [[Binding]] Source #

ShowFunction Double Source # 
Instance details

Defined in Test.LeanCheck.Function.ShowFunction

Methods

bindtiers :: Double -> [[Binding]] Source #

ShowFunction Float Source # 
Instance details

Defined in Test.LeanCheck.Function.ShowFunction

Methods

bindtiers :: Float -> [[Binding]] Source #

ShowFunction Int Source # 
Instance details

Defined in Test.LeanCheck.Function.ShowFunction

Methods

bindtiers :: Int -> [[Binding]] Source #

ShowFunction Int8 Source # 
Instance details

Defined in Test.LeanCheck.Function.ShowFunction

Methods

bindtiers :: Int8 -> [[Binding]] Source #

ShowFunction Int16 Source # 
Instance details

Defined in Test.LeanCheck.Function.ShowFunction

Methods

bindtiers :: Int16 -> [[Binding]] Source #

ShowFunction Int32 Source # 
Instance details

Defined in Test.LeanCheck.Function.ShowFunction

Methods

bindtiers :: Int32 -> [[Binding]] Source #

ShowFunction Int64 Source # 
Instance details

Defined in Test.LeanCheck.Function.ShowFunction

Methods

bindtiers :: Int64 -> [[Binding]] Source #

ShowFunction Integer Source # 
Instance details

Defined in Test.LeanCheck.Function.ShowFunction

Methods

bindtiers :: Integer -> [[Binding]] Source #

ShowFunction Ordering Source # 
Instance details

Defined in Test.LeanCheck.Function.ShowFunction

Methods

bindtiers :: Ordering -> [[Binding]] Source #

ShowFunction Word Source # 
Instance details

Defined in Test.LeanCheck.Function.ShowFunction

Methods

bindtiers :: Word -> [[Binding]] Source #

ShowFunction Word8 Source # 
Instance details

Defined in Test.LeanCheck.Function.ShowFunction

Methods

bindtiers :: Word8 -> [[Binding]] Source #

ShowFunction Word16 Source # 
Instance details

Defined in Test.LeanCheck.Function.ShowFunction

Methods

bindtiers :: Word16 -> [[Binding]] Source #

ShowFunction Word32 Source # 
Instance details

Defined in Test.LeanCheck.Function.ShowFunction

Methods

bindtiers :: Word32 -> [[Binding]] Source #

ShowFunction Word64 Source # 
Instance details

Defined in Test.LeanCheck.Function.ShowFunction

Methods

bindtiers :: Word64 -> [[Binding]] Source #

ShowFunction () Source # 
Instance details

Defined in Test.LeanCheck.Function.ShowFunction

Methods

bindtiers :: () -> [[Binding]] Source #

ShowFunction ExitCode Source # 
Instance details

Defined in Test.LeanCheck.Function.ShowFunction

Methods

bindtiers :: ExitCode -> [[Binding]] Source #

ShowFunction BufferMode Source # 
Instance details

Defined in Test.LeanCheck.Function.ShowFunction

ShowFunction SeekMode Source # 
Instance details

Defined in Test.LeanCheck.Function.ShowFunction

Methods

bindtiers :: SeekMode -> [[Binding]] Source #

ShowFunction CChar Source # 
Instance details

Defined in Test.LeanCheck.Function.ShowFunction

Methods

bindtiers :: CChar -> [[Binding]] Source #

ShowFunction CSChar Source # 
Instance details

Defined in Test.LeanCheck.Function.ShowFunction

Methods

bindtiers :: CSChar -> [[Binding]] Source #

ShowFunction CUChar Source # 
Instance details

Defined in Test.LeanCheck.Function.ShowFunction

Methods

bindtiers :: CUChar -> [[Binding]] Source #

ShowFunction CShort Source # 
Instance details

Defined in Test.LeanCheck.Function.ShowFunction

Methods

bindtiers :: CShort -> [[Binding]] Source #

ShowFunction CUShort Source # 
Instance details

Defined in Test.LeanCheck.Function.ShowFunction

Methods

bindtiers :: CUShort -> [[Binding]] Source #

ShowFunction CInt Source # 
Instance details

Defined in Test.LeanCheck.Function.ShowFunction

Methods

bindtiers :: CInt -> [[Binding]] Source #

ShowFunction CUInt Source # 
Instance details

Defined in Test.LeanCheck.Function.ShowFunction

Methods

bindtiers :: CUInt -> [[Binding]] Source #

ShowFunction CLong Source # 
Instance details

Defined in Test.LeanCheck.Function.ShowFunction

Methods

bindtiers :: CLong -> [[Binding]] Source #

ShowFunction CULong Source # 
Instance details

Defined in Test.LeanCheck.Function.ShowFunction

Methods

bindtiers :: CULong -> [[Binding]] Source #

ShowFunction CLLong Source # 
Instance details

Defined in Test.LeanCheck.Function.ShowFunction

Methods

bindtiers :: CLLong -> [[Binding]] Source #

ShowFunction CULLong Source # 
Instance details

Defined in Test.LeanCheck.Function.ShowFunction

Methods

bindtiers :: CULLong -> [[Binding]] Source #

ShowFunction CBool Source # 
Instance details

Defined in Test.LeanCheck.Function.ShowFunction

Methods

bindtiers :: CBool -> [[Binding]] Source #

ShowFunction CFloat Source # 
Instance details

Defined in Test.LeanCheck.Function.ShowFunction

Methods

bindtiers :: CFloat -> [[Binding]] Source #

ShowFunction CDouble Source # 
Instance details

Defined in Test.LeanCheck.Function.ShowFunction

Methods

bindtiers :: CDouble -> [[Binding]] Source #

ShowFunction CPtrdiff Source # 
Instance details

Defined in Test.LeanCheck.Function.ShowFunction

Methods

bindtiers :: CPtrdiff -> [[Binding]] Source #

ShowFunction CSize Source # 
Instance details

Defined in Test.LeanCheck.Function.ShowFunction

Methods

bindtiers :: CSize -> [[Binding]] Source #

ShowFunction CWchar Source # 
Instance details

Defined in Test.LeanCheck.Function.ShowFunction

Methods

bindtiers :: CWchar -> [[Binding]] Source #

ShowFunction CSigAtomic Source # 
Instance details

Defined in Test.LeanCheck.Function.ShowFunction

ShowFunction CClock Source # 
Instance details

Defined in Test.LeanCheck.Function.ShowFunction

Methods

bindtiers :: CClock -> [[Binding]] Source #

ShowFunction CTime Source # 
Instance details

Defined in Test.LeanCheck.Function.ShowFunction

Methods

bindtiers :: CTime -> [[Binding]] Source #

ShowFunction CUSeconds Source # 
Instance details

Defined in Test.LeanCheck.Function.ShowFunction

ShowFunction CSUSeconds Source # 
Instance details

Defined in Test.LeanCheck.Function.ShowFunction

ShowFunction CIntPtr Source # 
Instance details

Defined in Test.LeanCheck.Function.ShowFunction

Methods

bindtiers :: CIntPtr -> [[Binding]] Source #

ShowFunction CUIntPtr Source # 
Instance details

Defined in Test.LeanCheck.Function.ShowFunction

Methods

bindtiers :: CUIntPtr -> [[Binding]] Source #

ShowFunction CIntMax Source # 
Instance details

Defined in Test.LeanCheck.Function.ShowFunction

Methods

bindtiers :: CIntMax -> [[Binding]] Source #

ShowFunction CUIntMax Source # 
Instance details

Defined in Test.LeanCheck.Function.ShowFunction

Methods

bindtiers :: CUIntMax -> [[Binding]] Source #

ShowFunction IOMode Source # 
Instance details

Defined in Test.LeanCheck.Function.ShowFunction

Methods

bindtiers :: IOMode -> [[Binding]] Source #

ShowFunction GeneralCategory Source # 
Instance details

Defined in Test.LeanCheck.Function.ShowFunction

ShowFunction Letters Source # 
Instance details

Defined in Test.LeanCheck.Function.ShowFunction

Methods

bindtiers :: Letters -> [[Binding]] Source #

ShowFunction AlphaNums Source # 
Instance details

Defined in Test.LeanCheck.Function.ShowFunction

ShowFunction Digits Source # 
Instance details

Defined in Test.LeanCheck.Function.ShowFunction

Methods

bindtiers :: Digits -> [[Binding]] Source #

ShowFunction Alphas Source # 
Instance details

Defined in Test.LeanCheck.Function.ShowFunction

Methods

bindtiers :: Alphas -> [[Binding]] Source #

ShowFunction Uppers Source # 
Instance details

Defined in Test.LeanCheck.Function.ShowFunction

Methods

bindtiers :: Uppers -> [[Binding]] Source #

ShowFunction Lowers Source # 
Instance details

Defined in Test.LeanCheck.Function.ShowFunction

Methods

bindtiers :: Lowers -> [[Binding]] Source #

ShowFunction Spaces Source # 
Instance details

Defined in Test.LeanCheck.Function.ShowFunction

Methods

bindtiers :: Spaces -> [[Binding]] Source #

ShowFunction Letter Source # 
Instance details

Defined in Test.LeanCheck.Function.ShowFunction

Methods

bindtiers :: Letter -> [[Binding]] Source #

ShowFunction AlphaNum Source # 
Instance details

Defined in Test.LeanCheck.Function.ShowFunction

Methods

bindtiers :: AlphaNum -> [[Binding]] Source #

ShowFunction Digit Source # 
Instance details

Defined in Test.LeanCheck.Function.ShowFunction

Methods

bindtiers :: Digit -> [[Binding]] Source #

ShowFunction Alpha Source # 
Instance details

Defined in Test.LeanCheck.Function.ShowFunction

Methods

bindtiers :: Alpha -> [[Binding]] Source #

ShowFunction Upper Source # 
Instance details

Defined in Test.LeanCheck.Function.ShowFunction

Methods

bindtiers :: Upper -> [[Binding]] Source #

ShowFunction Lower Source # 
Instance details

Defined in Test.LeanCheck.Function.ShowFunction

Methods

bindtiers :: Lower -> [[Binding]] Source #

ShowFunction Space Source # 
Instance details

Defined in Test.LeanCheck.Function.ShowFunction

Methods

bindtiers :: Space -> [[Binding]] Source #

ShowFunction Nat7 Source # 
Instance details

Defined in Test.LeanCheck.Function.ShowFunction

Methods

bindtiers :: Nat7 -> [[Binding]] Source #

ShowFunction Nat6 Source # 
Instance details

Defined in Test.LeanCheck.Function.ShowFunction

Methods

bindtiers :: Nat6 -> [[Binding]] Source #

ShowFunction Nat5 Source # 
Instance details

Defined in Test.LeanCheck.Function.ShowFunction

Methods

bindtiers :: Nat5 -> [[Binding]] Source #

ShowFunction Nat4 Source # 
Instance details

Defined in Test.LeanCheck.Function.ShowFunction

Methods

bindtiers :: Nat4 -> [[Binding]] Source #

ShowFunction Nat3 Source # 
Instance details

Defined in Test.LeanCheck.Function.ShowFunction

Methods

bindtiers :: Nat3 -> [[Binding]] Source #

ShowFunction Nat2 Source # 
Instance details

Defined in Test.LeanCheck.Function.ShowFunction

Methods

bindtiers :: Nat2 -> [[Binding]] Source #

ShowFunction Nat1 Source # 
Instance details

Defined in Test.LeanCheck.Function.ShowFunction

Methods

bindtiers :: Nat1 -> [[Binding]] Source #

ShowFunction Nat Source # 
Instance details

Defined in Test.LeanCheck.Function.ShowFunction

Methods

bindtiers :: Nat -> [[Binding]] Source #

ShowFunction Natural Source # 
Instance details

Defined in Test.LeanCheck.Function.ShowFunction

Methods

bindtiers :: Natural -> [[Binding]] Source #

ShowFunction Word4 Source # 
Instance details

Defined in Test.LeanCheck.Function.ShowFunction

Methods

bindtiers :: Word4 -> [[Binding]] Source #

ShowFunction Word3 Source # 
Instance details

Defined in Test.LeanCheck.Function.ShowFunction

Methods

bindtiers :: Word3 -> [[Binding]] Source #

ShowFunction Word2 Source # 
Instance details

Defined in Test.LeanCheck.Function.ShowFunction

Methods

bindtiers :: Word2 -> [[Binding]] Source #

ShowFunction Word1 Source # 
Instance details

Defined in Test.LeanCheck.Function.ShowFunction

Methods

bindtiers :: Word1 -> [[Binding]] Source #

ShowFunction Int4 Source # 
Instance details

Defined in Test.LeanCheck.Function.ShowFunction

Methods

bindtiers :: Int4 -> [[Binding]] Source #

ShowFunction Int3 Source # 
Instance details

Defined in Test.LeanCheck.Function.ShowFunction

Methods

bindtiers :: Int3 -> [[Binding]] Source #

ShowFunction Int2 Source # 
Instance details

Defined in Test.LeanCheck.Function.ShowFunction

Methods

bindtiers :: Int2 -> [[Binding]] Source #

ShowFunction Int1 Source # 
Instance details

Defined in Test.LeanCheck.Function.ShowFunction

Methods

bindtiers :: Int1 -> [[Binding]] Source #

Show a => ShowFunction [a] Source # 
Instance details

Defined in Test.LeanCheck.Function.ShowFunction

Methods

bindtiers :: [a] -> [[Binding]] Source #

Show a => ShowFunction (Maybe a) Source # 
Instance details

Defined in Test.LeanCheck.Function.ShowFunction

Methods

bindtiers :: Maybe a -> [[Binding]] Source #

(Integral a, Show a) => ShowFunction (Ratio a) Source # 
Instance details

Defined in Test.LeanCheck.Function.ShowFunction

Methods

bindtiers :: Ratio a -> [[Binding]] Source #

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

Defined in Test.LeanCheck.Function.ShowFunction

Methods

bindtiers :: Complex a -> [[Binding]] Source #

Show a => ShowFunction (Xs a) Source # 
Instance details

Defined in Test.LeanCheck.Function.ShowFunction

Methods

bindtiers :: Xs a -> [[Binding]] Source #

Show a => ShowFunction (X a) Source # 
Instance details

Defined in Test.LeanCheck.Function.ShowFunction

Methods

bindtiers :: X a -> [[Binding]] Source #

Show a => ShowFunction (Set a) Source # 
Instance details

Defined in Test.LeanCheck.Function.ShowFunction

Methods

bindtiers :: Set a -> [[Binding]] Source #

Show a => ShowFunction (Bag a) Source # 
Instance details

Defined in Test.LeanCheck.Function.ShowFunction

Methods

bindtiers :: Bag a -> [[Binding]] Source #

Show a => ShowFunction (NoDup a) Source # 
Instance details

Defined in Test.LeanCheck.Function.ShowFunction

Methods

bindtiers :: NoDup a -> [[Binding]] Source #

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

Defined in Test.LeanCheck.Function.ShowFunction

Methods

bindtiers :: (a -> b) -> [[Binding]] Source #

(Show a, Show b) => ShowFunction (Either a b) Source # 
Instance details

Defined in Test.LeanCheck.Function.ShowFunction

Methods

bindtiers :: Either a b -> [[Binding]] Source #

(Show a, Show b) => ShowFunction (a, b) Source # 
Instance details

Defined in Test.LeanCheck.Function.ShowFunction

Methods

bindtiers :: (a, b) -> [[Binding]] Source #

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

Defined in Test.LeanCheck.Function.ShowFunction

Methods

bindtiers :: Map a b -> [[Binding]] Source #

(Show a, Show b, Show c) => ShowFunction (a, b, c) Source # 
Instance details

Defined in Test.LeanCheck.Function.ShowFunction

Methods

bindtiers :: (a, b, c) -> [[Binding]] Source #

(Show a, Show b, Show c, Show d) => ShowFunction (a, b, c, d) Source # 
Instance details

Defined in Test.LeanCheck.Function.ShowFunction

Methods

bindtiers :: (a, b, c, d) -> [[Binding]] Source #

(Show a, Show b, Show c, Show d, Show e) => ShowFunction (a, b, c, d, e) Source # 
Instance details

Defined in Test.LeanCheck.Function.ShowFunction

Methods

bindtiers :: (a, b, c, d, e) -> [[Binding]] Source #

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

Defined in Test.LeanCheck.Function.ShowFunction

Methods

bindtiers :: (a, b, c, d, e, f) -> [[Binding]] Source #

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

Defined in Test.LeanCheck.Function.ShowFunction

Methods

bindtiers :: (a, b, c, d, e, f, g) -> [[Binding]] Source #

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

Defined in Test.LeanCheck.Function.ShowFunction

Methods

bindtiers :: (a, b, c, d, e, f, g, h) -> [[Binding]] Source #

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

Defined in Test.LeanCheck.Function.ShowFunction

Methods

bindtiers :: (a, b, c, d, e, f, g, h, i) -> [[Binding]] Source #

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

Defined in Test.LeanCheck.Function.ShowFunction

Methods

bindtiers :: (a, b, c, d, e, f, g, h, i, j) -> [[Binding]] Source #

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

Defined in Test.LeanCheck.Function.ShowFunction

Methods

bindtiers :: (a, b, c, d, e, f, g, h, i, j, k) -> [[Binding]] Source #

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

Defined in Test.LeanCheck.Function.ShowFunction

Methods

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

bindtiersShow :: Show a => a -> [[Binding]] Source #

A drop-in implementation of bindtiers for showable types.

Define instances for showable algebraic datatypes as:

instance ShowFunction Ty where bindtiers = bindtiersShow

Listing functional bindings

type Binding = ([String], Maybe String) Source #

A functional binding in a showable format. Argument values are represented as a list of strings. The result value is represented by Just a String when defined or by Nothing when undefined.

bindings :: ShowFunction a => a -> [Binding] Source #

Given a ShowFunction value, return a list of Bindings. If the domain of the given argument function is infinite, the resulting list is infinite.

Some examples follow. These are used as running examples in the definition of explainedBindings, describedBindings and clarifiedBindings.

  • Defined return values are represented as Just Strings:

    > bindings True
    [([],Just "True")]
  • Undefined return values are represented as Nothing:

    > bindings undefined
    [([],Nothing)]
  • Infinite domains result in an infinite bindings list:

    > bindings (id::Int->Int)
    [ (["0"], Just "0")
    , (["1"], Just "1")
    , (["-1"], Just "-1")
    , ...
    ]
  • Finite domains result in a finite bindings list:

    > bindings (&&)
    [ (["False","False"], Just "False")
    , (["False","True"], Just "False")
    , (["True","False"], Just "False")
    , (["True","True"], Just "True")
    ]
    > bindings (||)
    [ (["False","False"], Just "False")
    , (["False","True"], Just "True")
    , (["True","False"], Just "True")
    , (["True","True"], Just "True")
    ]
  • Even very simple functions are represented by an infinite list of bindings:

    > bindings (== 0)
    [ (["0"], Just "True")
    , (["1"], Just "False")
    , (["-1"], Just "False")
    , ...
    ]
    > bindings (== 1)
    [ (["0"], Just "False")
    , (["1"], Just "True")
    , (["-1"], Just "False")
    , ...
    ]
  • Ignored arguments are still listed:

    > bindings ((\_ y -> y == 1) :: Int -> Int -> Bool)
    [ (["0","0"], Just "False")
    , (["0","1"], Just "True")
    , (["1","0"], Just "False")
    , ...
    ]
  • Again, undefined values are represented as Nothing. Here, the head of an empty list is undefined:

    > bindings (head :: [Int] -> Int)
    [ (["[]"], Nothing)
    , (["[0]"], Just "0")
    , (["[0,0]"], Just "0")
    , (["[1]"], Just "1")
    , ...
    ]

Pipeline for explaining, describing and clarifying bindings

explainedBindings :: ShowFunction a => Int -> a -> [Binding] Source #

Returns a set of bindings explaining how a function works. Some argument values are generalized to "_" when possible. It takes as argument the maximum number of cases considered for computing the explanation.

A measure of success in this generalization process is if this function returns less values than the asked maximum number of cases.

This is the first function in the clarification pipeline.

  • In some cases, bindings cannot be "explained" an almost unchanged result of bindings is returned with the last binding having variables replaced by "_":

    > explainedBindings 4 (id::Int->Int)
    [ (["0"],Just "0")
    , (["1"],Just "1")
    , (["-1"],Just "-1")
    , (["_"],Just "2") ]
  • When possible, some cases are generalized using _:

    > explainedBindings 10 (||)
    [ (["False","False"],Just "False")
    , (["_","_"],Just "True") ]

    but the resulting "explanation" might not be the shortest possible (cf. describedBindings):

    > explainedBindings 10 (&&)
    [ ( ["False","_"],Just "False")
    , (["_","False"],Just "False")
    , (["_","_"],Just "True") ]
  • Generalization works for infinite domains (heuristically):

    > explainedBindings 10 (==0)
    [ (["0"],Just "True")
    , (["_"],Just "False") ]
  • Generalization for each item is processed in the order they are generated by bindings hence explanations are not always the shortest possible (cf. describedBindings). In the following examples, the first case is redundant.

    > explainedBindings 10 (==1)
    [ (["0"],Just "False")
    , (["1"],Just "True"),
    , (["_"],Just "False") ]
    > explainedBindings 10 (\_ y -> y == 1)
    [ (["_","0"],Just "False")
    , (["_","1"],Just "True")
    , (["_","_"],Just "False") ]

describedBindings :: ShowFunction a => Int -> Int -> a -> [Binding] Source #

Returns a set of bindings describing how a function works. Some argument values are generalized to "_" when possible. It takes two integer arguments:

  1. m: the maximum number of cases considered for computing description;
  2. n: the maximum number of cases in the actual description.

As a general rule of thumb, set m=n*n+1.

This is the second function in the clarification pipeline.

This function processes the result of explainedBindings to sometimes return shorter descriptions. It chooses the shortest of the following (in order):

Here are some examples:

  • Sometimes the result is the same as explainedBindings:

    > describedBindings 100 10 (||)
    [ (["False","False"],Just "False")
    , (["_","_"],Just "True") ]
    > describedBindings 100 10 (==0)
    [ (["0"],Just "True")
    , (["_"],Just "False") ]
  • but sometimes it is shorter because we consider generalizing least occurring cases first:

    > describedBindings 100 10 (&&)
    [ ( ["True","True"],Just "True")
    , ( ["_","_"],Just "False") ]
    > describedBindings 100 10 (==1)
    [ (["1"],Just "True"),
    , (["_"],Just "False") ]
    > describedBindings 100 10 (\_ y -> y == 1)
    [ (["_","1"],Just "True")
    , (["_","_"],Just "False") ]

clarifiedBindings :: ShowFunction a => Int -> Int -> a -> ([String], [Binding]) Source #

Returns a set of variables and a set of bindings describing how a function works.

Some argument values are generalized to "_" when possible. If one of the function arguments is not used altogether, it is ommited in the set of bindings and appears as "_" in the variables list.

This is the last function in the clarification pipeline.

It takes two integer arguments:

  1. m: the maximum number of cases considered for computing the description;
  2. n: the maximum number of cases in the actual description.

As a general rule of thumb, set m=n*n+1.

Some examples follow:

  • When all arguments are used, the result is the same as describedBindings:

    > clarifiedBindings 100 10 (==1)
    ( ["x"], [ (["1"],Just "True"),
             , (["_"],Just "False") ] )
  • When some arguments are unused, they are omitted in the list of bindings and appear as "_" in the list of variables.

    > clarifiedBindings 100 10 (\_ y -> y == 1)
    ( ["_", "y"], [ (["1"],Just "True")
                  , (["_"],Just "False") ] )

Re-exports

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

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

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

Defined in Test.LeanCheck.Core

Methods

tiers :: [[()]] Source #

list :: [()] Source #

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

Defined in Test.LeanCheck.Basic

Listable CChar Source # 
Instance details

Defined in Test.LeanCheck.Basic

Methods

tiers :: [[CChar]] Source #

list :: [CChar] Source #

Listable CSChar Source # 
Instance details

Defined in Test.LeanCheck.Basic

Methods

tiers :: [[CSChar]] Source #

list :: [CSChar] Source #

Listable CUChar Source # 
Instance details

Defined in Test.LeanCheck.Basic

Methods

tiers :: [[CUChar]] Source #

list :: [CUChar] Source #

Listable CShort Source # 
Instance details

Defined in Test.LeanCheck.Basic

Methods

tiers :: [[CShort]] Source #

list :: [CShort] Source #

Listable CUShort Source # 
Instance details

Defined in Test.LeanCheck.Basic

Methods

tiers :: [[CUShort]] Source #

list :: [CUShort] Source #

Listable CInt Source # 
Instance details

Defined in Test.LeanCheck.Basic

Methods

tiers :: [[CInt]] Source #

list :: [CInt] Source #

Listable CUInt Source # 
Instance details

Defined in Test.LeanCheck.Basic

Methods

tiers :: [[CUInt]] Source #

list :: [CUInt] Source #

Listable CLong Source # 
Instance details

Defined in Test.LeanCheck.Basic

Methods

tiers :: [[CLong]] Source #

list :: [CLong] Source #

Listable CULong Source # 
Instance details

Defined in Test.LeanCheck.Basic

Methods

tiers :: [[CULong]] Source #

list :: [CULong] Source #

Listable CLLong Source # 
Instance details

Defined in Test.LeanCheck.Basic

Methods

tiers :: [[CLLong]] Source #

list :: [CLLong] Source #

Listable CULLong Source # 
Instance details

Defined in Test.LeanCheck.Basic

Methods

tiers :: [[CULLong]] Source #

list :: [CULLong] Source #

Listable CBool Source # 
Instance details

Defined in Test.LeanCheck.Basic

Methods

tiers :: [[CBool]] Source #

list :: [CBool] Source #

Listable CFloat Source # 
Instance details

Defined in Test.LeanCheck.Basic

Methods

tiers :: [[CFloat]] Source #

list :: [CFloat] Source #

Listable CDouble Source # 
Instance details

Defined in Test.LeanCheck.Basic

Methods

tiers :: [[CDouble]] Source #

list :: [CDouble] Source #

Listable CPtrdiff 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 CWchar Source # 
Instance details

Defined in Test.LeanCheck.Basic

Methods

tiers :: [[CWchar]] Source #

list :: [CWchar] Source #

Listable CSigAtomic Source # 
Instance details

Defined in Test.LeanCheck.Basic

Listable CClock Source # 
Instance details

Defined in Test.LeanCheck.Basic

Methods

tiers :: [[CClock]] Source #

list :: [CClock] Source #

Listable CTime Source # 
Instance details

Defined in Test.LeanCheck.Basic

Methods

tiers :: [[CTime]] Source #

list :: [CTime] Source #

Listable CUSeconds Source # 
Instance details

Defined in Test.LeanCheck.Basic

Listable CSUSeconds Source # 
Instance details

Defined in Test.LeanCheck.Basic

Listable CIntPtr Source # 
Instance details

Defined in Test.LeanCheck.Basic

Methods

tiers :: [[CIntPtr]] Source #

list :: [CIntPtr] Source #

Listable CUIntPtr Source # 
Instance details

Defined in Test.LeanCheck.Basic

Listable CIntMax Source # 
Instance details

Defined in Test.LeanCheck.Basic

Methods

tiers :: [[CIntMax]] Source #

list :: [CIntMax] Source #

Listable CUIntMax 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 GeneralCategory Source # 
Instance details

Defined in Test.LeanCheck.Basic

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 #

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