extrapolate-0.3.2: generalize counter-examples of test properties

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

Test.Extrapolate.Core

Description

This module is part of Extrapolate, a library for generalization of counter-examples.

This is the core of extrapolate.

Synopsis

Documentation

listsOfLength :: Int -> [[a]] -> [[[a]]] #

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

setsOf :: [[a]] -> [[[a]]] #

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

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

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

normalizeT :: [[a]] -> [[a]] #

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.

deleteT :: Eq a => a -> [[a]] -> [[a]] #

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

products :: [[[a]]] -> [[[a]]] #

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

listsOf :: [[a]] -> [[[a]]] #

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

productMaybeWith :: (a -> b -> Maybe c) -> [[a]] -> [[b]] -> [[c]] #

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

product3With :: (a -> b -> c -> d) -> [[a]] -> [[b]] -> [[c]] -> [[d]] #

Like productWith, but over 3 lists of tiers.

noDupListCons :: Listable a => ([a] -> b) -> [[b]] #

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

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

setCons :: Listable a => ([a] -> b) -> [[b]] #

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

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

deriveListableCascading :: Name -> DecsQ #

Derives a Listable instance for a given type Name cascading derivation of type arguments as well.

deriveListable :: Name -> DecsQ #

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

Needs the TemplateHaskell extension.

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

Adds to the weight of tiers of a constructor

addWeight is closely related to delay.

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

Resets the weight of a constructor (or tiers) Typically used as an infix constructor when defining Listable instances:

cons<N> `ofWeight` <W>

Be careful: 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 is closely related to reset.

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

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

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

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

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

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

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

(==>) :: Bool -> Bool -> Bool infixr 0 #

Boolean implication operator. Useful for defining conditional properties:

prop_something x y = condition x y ==> something x y

exists :: Testable a => Int -> a -> Bool #

There exists an assignment of values that satisfies a property up to a number of test values?

exists 1000 $ \x -> x > 10

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

Does a property fail for a number of test values?

fails 1000 $ \xs -> xs ++ ys == ys ++ xs

holds :: Testable a => Int -> a -> Bool #

Does a property hold up to a number of test values?

holds 1000 $ \xs -> length (sort xs) == length xs

witness :: Testable a => Int -> a -> Maybe [String] #

Up to a number of tests to a property, returns Just the first witness or Nothing if there is none.

witnesses :: Testable a => Int -> a -> [[String]] #

Lists all witnesses up to a number of tests to a property,

(><) :: [[a]] -> [[b]] -> [[(a, b)]] infixr 8 #

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

(\\//) :: [[a]] -> [[a]] -> [[a]] infixr 7 #

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]] -> [[a]] -> [[a]] infixr 7 #

Append tiers --- sum of two tiers enumerations.

[xs,ys,zs,...] \/ [as,bs,cs,...] = [xs++as,ys++bs,zs++cs,...]

(+|) :: [a] -> [a] -> [a] infixr 5 #

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]

suchThat :: [[a]] -> (a -> Bool) -> [[a]] #

Tiers of values that follow a property

cons<N> `suchThat` condition

reset :: [[a]] -> [[a]] #

Resets any delays in a list-of tiers. Conceptually this function makes a constructor "weightless", assuring the first tier is non-empty. Typically used when defining Listable instances:

reset (cons<N> <Constr>)

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

delay :: [[a]] -> [[a]] #

Delays the enumeration of tiers. Conceptually this function adds to the weight of a constructor. Typically used when defining Listable instances:

delay (cons<N> <Constr>)

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

Returns tiers of applications of a 5-argument constructor.

Test.LeanCheck.Basic defines cons6 up to cons12. Those are exported by default from Test.LeanCheck, but are hidden from the Haddock documentation.

cons4 :: (Listable a, Listable b, Listable c, Listable d) => (a -> b -> c -> d -> e) -> [[e]] #

Returns tiers of applications of a 4-argument constructor.

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

Returns tiers of applications of a 3-argument constructor.

cons2 :: (Listable a, Listable b) => (a -> b -> c) -> [[c]] #

Given a constructor with two Listable arguments, return tiers of applications of this constructor. By default, returned values will have size/weight of 1.

cons1 :: Listable a => (a -> b) -> [[b]] #

Given a constructor with one Listable argument, return tiers of applications of this constructor. By default, returned values will have size/weight of 1.

cons0 :: a -> [[a]] #

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.

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

concatMap over tiers

concatT :: [[[[a]]]] -> [[a]] #

concat tiers of tiers

filterT :: (a -> Bool) -> [[a]] -> [[a]] #

filter tiers

mapT :: (a -> b) -> [[a]] -> [[b]] #

map over tiers

tiersFractional :: Fractional a => [[a]] #

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

listIntegral :: (Enum a, Num a) => [a] #

Tiers of Integral values. Can be used as a default implementation of list for Integral types.

toTiers :: [a] -> [[a]] #

Takes a list of values xs and transform it into tiers on which each tier is occupied by a single element from xs.

To convert back to a list, just concat.

class Listable a where #

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

Methods

tiers :: [[a]] #

list :: [a] #

Instances
Listable Bool
tiers :: [[Bool]] = [[False,True]]
list :: [[Bool]] = [False,True]
Instance details

Defined in Test.LeanCheck.Core

Methods

tiers :: [[Bool]] #

list :: [Bool] #

Listable Char 
Instance details

Defined in Test.LeanCheck.Core

Methods

tiers :: [[Char]] #

list :: [Char] #

Listable Double 
Instance details

Defined in Test.LeanCheck.Core

Methods

tiers :: [[Double]] #

list :: [Double] #

Listable Float 
Instance details

Defined in Test.LeanCheck.Core

Methods

tiers :: [[Float]] #

list :: [Float] #

Listable Int
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]] #

list :: [Int] #

Listable Integer 
Instance details

Defined in Test.LeanCheck.Core

Methods

tiers :: [[Integer]] #

list :: [Integer] #

Listable Ordering 
Instance details

Defined in Test.LeanCheck.Core

Methods

tiers :: [[Ordering]] #

list :: [Ordering] #

Listable () 
Instance details

Defined in Test.LeanCheck.Core

Methods

tiers :: [[()]] #

list :: [()] #

Listable Int1 
Instance details

Defined in Test.LeanCheck.Utils.Types

Methods

tiers :: [[Int1]] #

list :: [Int1] #

Listable Int2 
Instance details

Defined in Test.LeanCheck.Utils.Types

Methods

tiers :: [[Int2]] #

list :: [Int2] #

Listable Int3 
Instance details

Defined in Test.LeanCheck.Utils.Types

Methods

tiers :: [[Int3]] #

list :: [Int3] #

Listable Int4 
Instance details

Defined in Test.LeanCheck.Utils.Types

Methods

tiers :: [[Int4]] #

list :: [Int4] #

Listable Word1 
Instance details

Defined in Test.LeanCheck.Utils.Types

Methods

tiers :: [[Word1]] #

list :: [Word1] #

Listable Word2 
Instance details

Defined in Test.LeanCheck.Utils.Types

Methods

tiers :: [[Word2]] #

list :: [Word2] #

Listable Word3 
Instance details

Defined in Test.LeanCheck.Utils.Types

Methods

tiers :: [[Word3]] #

list :: [Word3] #

Listable Word4 
Instance details

Defined in Test.LeanCheck.Utils.Types

Methods

tiers :: [[Word4]] #

list :: [Word4] #

Listable Natural 
Instance details

Defined in Test.LeanCheck.Utils.Types

Methods

tiers :: [[Natural]] #

list :: [Natural] #

Listable Nat 
Instance details

Defined in Test.LeanCheck.Utils.Types

Methods

tiers :: [[Nat]] #

list :: [Nat] #

Listable Nat1 
Instance details

Defined in Test.LeanCheck.Utils.Types

Methods

tiers :: [[Nat1]] #

list :: [Nat1] #

Listable Nat2 
Instance details

Defined in Test.LeanCheck.Utils.Types

Methods

tiers :: [[Nat2]] #

list :: [Nat2] #

Listable Nat3 
Instance details

Defined in Test.LeanCheck.Utils.Types

Methods

tiers :: [[Nat3]] #

list :: [Nat3] #

Listable Nat4 
Instance details

Defined in Test.LeanCheck.Utils.Types

Methods

tiers :: [[Nat4]] #

list :: [Nat4] #

Listable Nat5 
Instance details

Defined in Test.LeanCheck.Utils.Types

Methods

tiers :: [[Nat5]] #

list :: [Nat5] #

Listable Nat6 
Instance details

Defined in Test.LeanCheck.Utils.Types

Methods

tiers :: [[Nat6]] #

list :: [Nat6] #

Listable Nat7 
Instance details

Defined in Test.LeanCheck.Utils.Types

Methods

tiers :: [[Nat7]] #

list :: [Nat7] #

Listable a => Listable [a]
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]]] #

list :: [[a]] #

Listable a => Listable (Maybe a)
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]] #

list :: [Maybe a] #

Listable a => Listable (NoDup a) 
Instance details

Defined in Test.LeanCheck.Utils.Types

Methods

tiers :: [[NoDup a]] #

list :: [NoDup a] #

Listable a => Listable (Bag a) 
Instance details

Defined in Test.LeanCheck.Utils.Types

Methods

tiers :: [[Bag a]] #

list :: [Bag a] #

Listable a => Listable (Set a) 
Instance details

Defined in Test.LeanCheck.Utils.Types

Methods

tiers :: [[Set a]] #

list :: [Set a] #

(Integral a, Bounded a) => Listable (X a)

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

list :: [X a] #

(Integral a, Bounded a) => Listable (Xs a)

Lists with elements of the X type.

Instance details

Defined in Test.LeanCheck.Utils.Types

Methods

tiers :: [[Xs a]] #

list :: [Xs a] #

(Listable a, Listable b) => Listable (Either a b) 
Instance details

Defined in Test.LeanCheck.Core

Methods

tiers :: [[Either a b]] #

list :: [Either a b] #

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

list :: [(a, b)] #

(Listable a, Listable b) => Listable (Map a b) 
Instance details

Defined in Test.LeanCheck.Utils.Types

Methods

tiers :: [[Map a b]] #

list :: [Map a b] #

(Listable a, Listable b, Listable c) => Listable (a, b, c) 
Instance details

Defined in Test.LeanCheck.Core

Methods

tiers :: [[(a, b, c)]] #

list :: [(a, b, c)] #

(Listable a, Listable b, Listable c, Listable d) => Listable (a, b, c, d) 
Instance details

Defined in Test.LeanCheck.Core

Methods

tiers :: [[(a, b, c, d)]] #

list :: [(a, b, c, d)] #

(Listable a, Listable b, Listable c, Listable d, Listable e) => Listable (a, b, c, d, e) 
Instance details

Defined in Test.LeanCheck.Core

Methods

tiers :: [[(a, b, c, d, e)]] #

list :: [(a, b, c, d, e)] #

class (Listable a, Typeable a, Show a) => Generalizable a where Source #

Extrapolate can generalize counter-examples of any types that are Generalizable.

The core (and only required functions) of the generalizable typeclass are the expr and instances functions.

The following example shows a datatype and its instance:

data Stack a = Stack a (Stack a) | Empty
instance Generalizable a => Generalizable (Stack a) where
name _ = "s"
expr s@(Stack x y) = constant "Stack" (Stack ->>: s) :$ expr x :$ expr y
expr s@Empty       = constant "Empty" (Empty   -: s)
instances s = this s $ instances (argTy1of1 s)

To declare instances and expr it may be useful to use:

Minimal complete definition

expr, instances

Methods

expr :: a -> Expr Source #

Transforms a value into an manipulable expression tree. See constant and :$.

name :: a -> String Source #

Common name for a variable, defaults to "x".

background :: a -> [Expr] Source #

List of symbols allowed to appear in side-conditions. Defaults to []. See constant.

instances :: a -> Instances -> Instances Source #

Computes a list of reified instances. See this.

Instances
Generalizable Bool Source # 
Instance details

Defined in Test.Extrapolate.Core

Generalizable Char Source # 
Instance details

Defined in Test.Extrapolate.Core

Generalizable Int Source # 
Instance details

Defined in Test.Extrapolate.Core

Generalizable Integer Source # 
Instance details

Defined in Test.Extrapolate.Core

Generalizable Ordering Source # 
Instance details

Defined in Test.Extrapolate.Core

Generalizable () Source # 
Instance details

Defined in Test.Extrapolate.Core

Methods

expr :: () -> Expr Source #

name :: () -> String Source #

background :: () -> [Expr] Source #

instances :: () -> Instances -> Instances Source #

Generalizable a => Generalizable [a] Source # 
Instance details

Defined in Test.Extrapolate.Core

Methods

expr :: [a] -> Expr Source #

name :: [a] -> String Source #

background :: [a] -> [Expr] Source #

instances :: [a] -> Instances -> Instances Source #

Generalizable a => Generalizable (Maybe a) Source # 
Instance details

Defined in Test.Extrapolate.Core

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

Defined in Test.Extrapolate.Basic

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

Defined in Test.Extrapolate.Core

(Generalizable a, Generalizable b) => Generalizable (a, b) Source # 
Instance details

Defined in Test.Extrapolate.Core

Methods

expr :: (a, b) -> Expr Source #

name :: (a, b) -> String Source #

background :: (a, b) -> [Expr] Source #

instances :: (a, b) -> Instances -> Instances Source #

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

Defined in Test.Extrapolate.Core

Methods

expr :: (a, b, c) -> Expr Source #

name :: (a, b, c) -> String Source #

background :: (a, b, c) -> [Expr] Source #

instances :: (a, b, c) -> Instances -> Instances Source #

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

Defined in Test.Extrapolate.Core

Methods

expr :: (a, b, c, d) -> Expr Source #

name :: (a, b, c, d) -> String Source #

background :: (a, b, c, d) -> [Expr] Source #

instances :: (a, b, c, d) -> Instances -> Instances Source #

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

Defined in Test.Extrapolate.Basic

Methods

expr :: (a, b, c, d, e) -> Expr Source #

name :: (a, b, c, d, e) -> String Source #

background :: (a, b, c, d, e) -> [Expr] Source #

instances :: (a, b, c, d, e) -> Instances -> Instances Source #

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

Defined in Test.Extrapolate.Basic

Methods

expr :: (a, b, c, d, e, f) -> Expr Source #

name :: (a, b, c, d, e, f) -> String Source #

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

instances :: (a, b, c, d, e, f) -> Instances -> Instances Source #

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

Defined in Test.Extrapolate.Basic

Methods

expr :: (a, b, c, d, e, f, g) -> Expr Source #

name :: (a, b, c, d, e, f, g) -> String Source #

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

instances :: (a, b, c, d, e, f, g) -> Instances -> Instances Source #

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

Defined in Test.Extrapolate.Basic

Methods

expr :: (a, b, c, d, e, f, g, h) -> Expr Source #

name :: (a, b, c, d, e, f, g, h) -> String Source #

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

instances :: (a, b, c, d, e, f, g, h) -> Instances -> Instances Source #

(+++) :: Ord a => [a] -> [a] -> [a] infixr 5 Source #

bgEq :: (Eq a, Generalizable a) => a -> [Expr] Source #

bgOrd :: (Ord a, Generalizable a) => a -> [Expr] Source #

bgEqWith1 :: (Generalizable a, Generalizable b) => ((b -> b -> Bool) -> a -> a -> Bool) -> [Expr] Source #

bgEqWith2 :: (Generalizable a, Generalizable b, Generalizable c) => ((b -> b -> Bool) -> (c -> c -> Bool) -> a -> a -> Bool) -> [Expr] Source #

data WithOption a Source #

Constructors

With 

Fields

Instances
Testable a => Testable (WithOption a) Source # 
Instance details

Defined in Test.Extrapolate.Core

(*==*) :: Generalizable a => a -> a -> Bool Source #

(*/=*) :: Generalizable a => a -> a -> Bool Source #

(*<=*) :: Generalizable a => a -> a -> Bool Source #

(*<*) :: Generalizable a => a -> a -> Bool Source #

counterExamples :: Testable a => Int -> a -> [[Expr]] Source #

generalizationsCE :: Testable a => Int -> a -> [Expr] -> [[Expr]] Source #

generalizationsCEC :: Testable a => a -> [Expr] -> [(Expr, [Expr])] Source #

generalizationsCounts :: Testable a => Int -> a -> [Expr] -> [([Expr], Int)] Source #

atoms :: Testable a => a -> [[Expr]] Source #

theoryAndReprExprs :: Testable a => a -> (Thy, [Expr]) Source #

theoryAndReprConds :: Testable a => a -> (Thy, [Expr]) Source #

candidateConditions :: Testable a => (Thy, [Expr]) -> a -> [Expr] -> [Expr] Source #

validConditions :: Testable a => (Thy, [Expr]) -> a -> [Expr] -> [(Expr, Int)] Source #

weakestCondition :: Testable a => (Thy, [Expr]) -> a -> [Expr] -> Expr Source #

matchList :: [Expr] -> [Expr] -> Maybe Binds Source #

List matches of lists of expressions if possible

[0,1]   `matchList` [x,y]   = Just [x=0, y=1]
[0,1+2] `matchList` [x,y+y] = Nothing

class Testable a where Source #

Minimal complete definition

resultiers, ($-|), tinstances

Methods

resultiers :: a -> [[([Expr], Bool)]] Source #

($-|) :: a -> [Expr] -> Bool Source #

tinstances :: a -> Instances Source #

options :: a -> Options Source #

Instances
Testable Bool Source # 
Instance details

Defined in Test.Extrapolate.Core

Methods

resultiers :: Bool -> [[([Expr], Bool)]] Source #

($-|) :: Bool -> [Expr] -> Bool Source #

tinstances :: Bool -> Instances Source #

options :: Bool -> Options Source #

Testable a => Testable (WithOption a) Source # 
Instance details

Defined in Test.Extrapolate.Core

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

Defined in Test.Extrapolate.Core

Methods

resultiers :: (a -> b) -> [[([Expr], Bool)]] Source #

($-|) :: (a -> b) -> [Expr] -> Bool Source #

tinstances :: (a -> b) -> Instances Source #

options :: (a -> b) -> Options Source #

results :: Testable a => a -> [([Expr], Bool)] Source #