leancheck-0.7.3: Enumerative property-based testing

Copyright(c) 2015-2018 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.

The module Test.LeanCheck.Function.Show (Show) exports an instance like the one above.

Synopsis

Documentation

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

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

showFunction undefined True == "True"
showFunction 3 (id::Int) == "\\x -> case x of\n\
                             \        0 -> 0\n\
                             \        1 -> 1\n\
                             \        -1 -> -1\n\
                             \        ...\n"
showFunction 4 (&&) == "\\x y -> case (x,y) of\n\
                        \          (False,False) -> False\n\
                        \          (False,True) -> False\n\
                        \          (True,False) -> False\n\
                        \          (True,True) -> True\n"

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

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

Same as showFunction, but has no line breaks.

showFunction 2 (id::Int) == "\\x -> case x of 0 -> 0; 1 -> 1; ..."

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

A functional binding in a showable format.

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

Given a ShowFunction value, return a list of bindings for printing. Examples:

bindings True == [([],True)]
bindings (id::Int) == [(["0"],"0"), (["1"],"1"), (["-1"],"-1"), ...
bindings (&&) == [ (["False","False"], "False")
                 , (["False","True"], "False")
                 , (["True","False"], "False")
                 , (["True","True"], "True")
                 ]

class ShowFunction a where Source #

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

As a user, you probably want showFunction and showFunctionLine.

Non functional instances should be defined by:

instance ShowFunction Ty where tBindings = tBindingsShow

Minimal complete definition

tBindings

Methods

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

Instances
ShowFunction Bool Source # 
Instance details

Defined in Test.LeanCheck.Function.ShowFunction

Methods

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

ShowFunction Char Source # 
Instance details

Defined in Test.LeanCheck.Function.ShowFunction

Methods

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

ShowFunction Double Source # 
Instance details

Defined in Test.LeanCheck.Function.ShowFunction

Methods

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

ShowFunction Float Source # 
Instance details

Defined in Test.LeanCheck.Function.ShowFunction

Methods

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

ShowFunction Int Source # 
Instance details

Defined in Test.LeanCheck.Function.ShowFunction

Methods

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

ShowFunction Integer Source # 
Instance details

Defined in Test.LeanCheck.Function.ShowFunction

Methods

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

ShowFunction Ordering Source # 
Instance details

Defined in Test.LeanCheck.Function.ShowFunction

Methods

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

ShowFunction () Source # 
Instance details

Defined in Test.LeanCheck.Function.ShowFunction

Methods

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

ShowFunction Nat7 Source # 
Instance details

Defined in Test.LeanCheck.Function.ShowFunction

Methods

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

ShowFunction Nat6 Source # 
Instance details

Defined in Test.LeanCheck.Function.ShowFunction

Methods

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

ShowFunction Nat5 Source # 
Instance details

Defined in Test.LeanCheck.Function.ShowFunction

Methods

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

ShowFunction Nat4 Source # 
Instance details

Defined in Test.LeanCheck.Function.ShowFunction

Methods

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

ShowFunction Nat3 Source # 
Instance details

Defined in Test.LeanCheck.Function.ShowFunction

Methods

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

ShowFunction Nat2 Source # 
Instance details

Defined in Test.LeanCheck.Function.ShowFunction

Methods

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

ShowFunction Nat1 Source # 
Instance details

Defined in Test.LeanCheck.Function.ShowFunction

Methods

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

ShowFunction Nat Source # 
Instance details

Defined in Test.LeanCheck.Function.ShowFunction

Methods

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

ShowFunction Word4 Source # 
Instance details

Defined in Test.LeanCheck.Function.ShowFunction

Methods

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

ShowFunction Word3 Source # 
Instance details

Defined in Test.LeanCheck.Function.ShowFunction

Methods

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

ShowFunction Word2 Source # 
Instance details

Defined in Test.LeanCheck.Function.ShowFunction

Methods

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

ShowFunction Word1 Source # 
Instance details

Defined in Test.LeanCheck.Function.ShowFunction

Methods

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

ShowFunction Int4 Source # 
Instance details

Defined in Test.LeanCheck.Function.ShowFunction

Methods

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

ShowFunction Int3 Source # 
Instance details

Defined in Test.LeanCheck.Function.ShowFunction

Methods

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

ShowFunction Int2 Source # 
Instance details

Defined in Test.LeanCheck.Function.ShowFunction

Methods

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

ShowFunction Int1 Source # 
Instance details

Defined in Test.LeanCheck.Function.ShowFunction

Methods

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

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

Defined in Test.LeanCheck.Function.ShowFunction

Methods

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

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

Defined in Test.LeanCheck.Function.ShowFunction

Methods

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

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

Defined in Test.LeanCheck.Function.ShowFunction

Methods

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

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

Defined in Test.LeanCheck.Function.ShowFunction

Methods

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

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

Defined in Test.LeanCheck.Function.ShowFunction

Methods

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

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

Defined in Test.LeanCheck.Function.ShowFunction

Methods

tBindings :: (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

tBindings :: (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

tBindings :: (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

tBindings :: (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

tBindings :: (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

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

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

A default implementation of tBindings for already Show-able types.

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.

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

Defined in Test.LeanCheck.Core

Methods

tiers :: [[Char]] Source #

list :: [Char] Source #

Listable Double Source # 
Instance details

Defined in Test.LeanCheck.Core

Methods

tiers :: [[Double]] Source #

list :: [Double] Source #

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

Defined in Test.LeanCheck.Core

Methods

tiers :: [[Integer]] Source #

list :: [Integer] Source #

Listable Ordering Source # 
Instance details

Defined in Test.LeanCheck.Core

Listable Word Source # 
Instance details

Defined in Test.LeanCheck.Basic

Methods

tiers :: [[Word]] Source #

list :: [Word] Source #

Listable () Source # 
Instance details

Defined in Test.LeanCheck.Core

Methods

tiers :: [[()]] Source #

list :: [()] 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 # 
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 #

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

Defined in Test.LeanCheck.Function.Listable.Periodic

Methods

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

list :: [a -> b] Source #

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

Defined in Test.LeanCheck.Function.Listable.FunListable

Methods

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

list :: [a -> b] Source #

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

Defined in Test.LeanCheck.Function.Listable.Mixed

Methods

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

list :: [a -> b] Source #

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

Defined in Test.LeanCheck.Function.Listable.CoListable

Methods

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

list :: [a -> b] Source #

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