| Copyright | (c) 2015-2024 Rudy Matela |
|---|---|
| License | 3-Clause BSD (see the file LICENSE) |
| Maintainer | Rudy Matela <rudy@matela.com.br> |
| Safe Haskell | Safe-Inferred |
| Language | Haskell2010 |
Test.LeanCheck.Function.ShowFunction
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
- showFunction :: ShowFunction a => Int -> a -> String
- showFunctionLine :: ShowFunction a => Int -> a -> String
- class ShowFunction a where
- bindtiersShow :: Show a => a -> [[Binding]]
- type Binding = ([String], Maybe String)
- bindings :: ShowFunction a => a -> [Binding]
- explainedBindings :: ShowFunction a => Int -> a -> [Binding]
- describedBindings :: ShowFunction a => Int -> Int -> a -> [Binding]
- clarifiedBindings :: ShowFunction a => Int -> Int -> a -> ([String], [Binding])
- class Listable a
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
Instances
bindtiersShow :: Show a => a -> [[Binding]] Source #
Listing functional bindings
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
JustStrings:> 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, theheadof 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,
bindingscannot be "explained" an almost unchanged result ofbindingsis 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
bindingshence 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:
m: the maximum number of cases considered for computing description;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):
- regular unexplained-undescribed
bindings; - regular
explainedBindings; explainedBindingswith least occurring cases generalized first;
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:
m: the maximum number of cases considered for computing the description;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
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> ConstructorZwhere 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 MyConsDThe instance for Hutton's Razor is given by:
data Expr = Val Int
| Add Expr Expr
instance Listable Expr where
tiers = cons1 Val
\/ cons2 AddInstances 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 CBool Source # | |
| Listable CChar Source # | |
| Listable CClock Source # | |
| Listable CDouble Source # | |
| Listable CFloat Source # | |
| Listable CInt Source # | |
| Listable CIntMax Source # | |
| Listable CIntPtr Source # | |
| Listable CLLong Source # | |
| Listable CLong Source # | |
| Listable CPtrdiff Source # | |
| Listable CSChar Source # | |
| Listable CSUSeconds Source # | |
Defined in Test.LeanCheck.Basic | |
| Listable CShort Source # | |
| Listable CSigAtomic Source # | |
Defined in Test.LeanCheck.Basic | |
| Listable CSize Source # | |
| Listable CTime Source # | |
| Listable CUChar Source # | |
| Listable CUInt Source # | |
| Listable CUIntMax Source # | |
| Listable CUIntPtr Source # | |
| Listable CULLong Source # | |
| Listable CULong Source # | |
| Listable CUSeconds Source # | |
| Listable CUShort Source # | |
| Listable CWchar Source # | |
| Listable SeekMode Source # | |
| Listable ExitCode Source # | Only includes valid POSIX exit codes > list :: [ExitCode] [ExitSuccess, ExitFailure 1, ExitFailure 2, ..., ExitFailure 255] |
| Listable BufferMode Source # | |
Defined in Test.LeanCheck.Basic | |
| Listable IOMode Source # | |
| Listable Int16 Source # | list :: [Int16] = [0, 1, -1, 2, -2, ..., 32767, -32767, -32768] |
| Listable Int32 Source # | list :: [Int32] = [0, 1, -1, 2, -2, 3, -3, 4, -4, 5, -5, 6, ...] |
| Listable Int64 Source # | list :: [Int64] = [0, 1, -1, 2, -2, 3, -3, 4, -4, 5, -5, 6, ...] |
| Listable Int8 Source # | list :: [Int8] = [0, 1, -1, 2, -2, 3, -3, ..., 127, -127, -128] |
| Listable GeneralCategory Source # | |
Defined in Test.LeanCheck.Basic | |
| Listable Word16 Source # | list :: [Word16] = [0, 1, 2, 3, 4, 5, 6, 7, 8, 9, ..., 65535] |
| Listable Word32 Source # | list :: [Word32] = [0, 1, 2, 3, 4, 5, 6, 7, 8, 9, 10, 11, ...] |
| Listable Word64 Source # | list :: [Word64] = [0, 1, 2, 3, 4, 5, 6, 7, 8, 9, 10, 11, ...] |
| Listable Word8 Source # | list :: [Word8] = [0, 1, 2, 3, 4, 5, 6, 7, 8, 9, ..., 255] |
| Listable Ordering Source # | list :: [Ordering] = [LT, EQ, GT] |
| Listable A Source # | |
| Listable Alpha Source # | |
| Listable AlphaNum Source # | |
| Listable AlphaNums Source # | |
| Listable Alphas Source # | |
| Listable B Source # | |
| Listable C Source # | |
| Listable D Source # | |
| Listable Digit Source # | |
| Listable Digits Source # | |
| Listable E Source # | |
| Listable F Source # | |
| Listable Int1 Source # | |
| Listable Int2 Source # | |
| Listable Int3 Source # | |
| Listable Int4 Source # | |
| Listable Letter Source # | |
| Listable Letters Source # | |
| Listable Lower Source # | |
| Listable Lowers Source # | |
| Listable Nat Source # | |
| Listable Nat1 Source # | |
| Listable Nat2 Source # | |
| Listable Nat3 Source # | |
| Listable Nat4 Source # | |
| Listable Nat5 Source # | |
| Listable Nat6 Source # | |
| Listable Nat7 Source # | |
| Listable Natural Source # | |
| Listable Space Source # | |
| Listable Spaces Source # | |
| Listable Upper Source # | |
| Listable Uppers Source # | |
| Listable Word1 Source # | |
| Listable Word2 Source # | |
| Listable Word3 Source # | |
| Listable Word4 Source # | |
| Listable Integer Source # | list :: [Int] = [0, 1, -1, 2, -2, 3, -3, 4, -4, 5, -5, 6, ...] |
| Listable () Source # | list :: [()] = [()] tiers :: [[()]] = [[()]] |
| Listable Bool Source # | tiers :: [[Bool]] = [[False,True]] list :: [[Bool]] = [False,True] |
| Listable Char Source # | list :: [Char] = ['a', ' ', 'b', 'A', 'c', '\', 'n', 'd', ...] |
| Listable Double Source # |
list :: [Double] = [0.0, 1.0, -1.0, Infinity, 0.5, 2.0, ...] |
| Listable Float Source # |
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 , ... ] |
| 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 Word Source # | list :: [Word] = [0, 1, 2, 3, 4, 5, 6, 7, 8, 9, 10, 11, ...] |
| (RealFloat a, Listable a) => Listable (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 , ... ] |
| Listable a => Listable (Bag a) Source # | |
| Listable a => Listable (NoDup a) Source # | |
| Listable a => Listable (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
, ... ] |
| (Integral a, Bounded a) => Listable (Xs a) Source # | Lists with elements of the |
| Listable a => Listable (Maybe a) Source # | tiers :: [[Maybe Int]] = [[Nothing], [Just 0], [Just 1], ...] tiers :: [[Maybe Bool]] = [[Nothing], [Just False, Just True]] |
| 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 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]
, ... ] |
| (Listable a, Listable b) => Listable (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), ...] |
| (Eq a, Listable a, Listable b) => Listable (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), ...] |
| (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 # | |