Copyright | (c) 2015-2018 Rudy Matela |
---|---|
License | 3-Clause BSD (see the file LICENSE) |
Maintainer | Rudy Matela <rudy@matela.com.br> |
Safe Haskell | None |
Language | Haskell2010 |
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
- showFunction :: ShowFunction a => Int -> a -> String
- showFunctionLine :: ShowFunction a => Int -> a -> String
- type Binding = ([String], Maybe String)
- bindings :: ShowFunction a => a -> [Binding]
- class ShowFunction a where
- tBindingsShow :: Show a => a -> [[Binding]]
- class Listable a
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; ..."
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
Instances
tBindingsShow :: Show a => a -> [[Binding]] Source #
A default implementation of tBindings for already Show
-able types.
Re-exports
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.
Instances
Listable Bool Source # | tiers :: [[Bool]] = [[False,True]] list :: [[Bool]] = [False,True] |
Listable Char Source # | |
Listable Double Source # | |
Listable 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, ...] |
Listable Integer Source # | |
Listable Ordering Source # | |
Listable Word Source # | |
Listable () Source # | |
Listable Nat7 Source # | |
Listable Nat6 Source # | |
Listable Nat5 Source # | |
Listable Nat4 Source # | |
Listable Nat3 Source # | |
Listable Nat2 Source # | |
Listable Nat1 Source # | |
Listable Nat Source # | |
Listable Natural Source # | |
Listable Word4 Source # | |
Listable Word3 Source # | |
Listable Word2 Source # | |
Listable Word1 Source # | |
Listable Int4 Source # | |
Listable Int3 Source # | |
Listable Int2 Source # | |
Listable 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], ... ] |
Listable a => Listable (Maybe a) Source # | tiers :: [[Maybe Int]] = [[Nothing], [Just 0], [Just 1], ...] tiers :: [[Maybe Bool]] = [[Nothing], [Just False, Just True]] |
(Integral a, Listable a) => Listable (Ratio a) Source # | |
(Integral a, Bounded a) => Listable (Xs a) Source # | Lists with elements of the |
(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 , ... ] |
Listable a => Listable (Set a) Source # | |
Listable a => Listable (Bag a) Source # | |
Listable a => Listable (NoDup a) Source # | |
(Eq a, Listable a, Listable b) => Listable (a -> b) Source # | |
(Eq a, Eq b, Listable a, Listable b) => Listable (a -> b) Source # | |
(FunListable a, Listable b) => Listable (a -> b) Source # | |
(Eq a, Listable a, CoListable a, Listable b) => Listable (a -> b) Source # | |
(CoListable a, Listable b) => Listable (a -> b) Source # | |
(Listable a, Listable b) => Listable (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), ...] |
(Listable a, Listable b) => Listable (Map a b) Source # | |
(Listable a, Listable b, Listable c) => Listable (a, b, c) Source # | |
(Listable a, Listable b, Listable c, Listable d) => Listable (a, b, c, d) Source # | |
(Listable a, Listable b, Listable c, Listable d, Listable e) => Listable (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 # | |
(Listable a, Listable b, Listable c, Listable d, Listable e, Listable f, Listable g) => Listable (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 # | |
(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 # | |
(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 # | |
(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 # | |
(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 # | |