extrapolate-0.4.6: generalize counter-examples of test properties
Copyright(c) 2017-2019 Rudy Matela
License3-Clause BSD (see the file LICENSE)
MaintainerRudy Matela <rudy@matela.com.br>
Safe HaskellNone
LanguageHaskell2010

Test.Extrapolate.Generalizable

Description

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

This defines the Generalizable typeclass and utilities involving it.

You are probably better off importing Test.Extrapolate.

Synopsis

Documentation

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

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

Generalizable types must first be instances of

  • Listable, so Extrapolate knows how to enumerate values;
  • Express, so Extrapolate can represent then manipulate values;
  • Name, so Extrapolate knows how to name variables.

There are no required functions, so we can define instances with:

instance Generalizable OurType

However, it is desirable to define both background and subInstances.

The following example shows a datatype and its instance:

data Stack a = Stack a (Stack a) | Empty
instance Generalizable a => Generalizable (Stack a) where
  subInstances s  =  instances (argTy1of1 s)

To declare instances it may be useful to use type binding operators such as: argTy1of1, argTy1of2 and argTy2of2.

Instances can be automatically derived using deriveGeneralizable which will also automatically derivate Listable, Express and Name when needed.

Minimal complete definition

Nothing

Methods

background :: a -> [Expr] Source #

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

subInstances :: a -> Instances -> Instances Source #

Computes a list of reified subtype instances. Defaults to id. See instances.

Instances

Instances details
Generalizable Bool Source # 
Instance details

Defined in Test.Extrapolate.Generalizable

Generalizable Char Source # 
Instance details

Defined in Test.Extrapolate.Generalizable

Generalizable Int Source # 
Instance details

Defined in Test.Extrapolate.Generalizable

Generalizable Integer Source # 
Instance details

Defined in Test.Extrapolate.Generalizable

Generalizable Ordering Source # 
Instance details

Defined in Test.Extrapolate.Generalizable

Generalizable () Source # 
Instance details

Defined in Test.Extrapolate.Generalizable

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

Defined in Test.Extrapolate.Generalizable

Methods

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

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

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

Defined in Test.Extrapolate.Generalizable

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

Defined in Test.Extrapolate.Generalizable

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

Defined in Test.Extrapolate.Generalizable

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

Defined in Test.Extrapolate.Generalizable

Methods

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

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

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

Defined in Test.Extrapolate.Generalizable

Methods

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

subInstances :: (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.Generalizable

Methods

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

subInstances :: (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.Generalizable

Methods

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

subInstances :: (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.Generalizable

Methods

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

subInstances :: (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.Generalizable

Methods

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

subInstances :: (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.Generalizable

Methods

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

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

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

Used in the definition of subInstances in Generalizable typeclass instances.

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

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

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

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

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

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

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

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

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

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

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

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

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.

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

Methods

tiers :: [[a]] #

list :: [a] #

Instances

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

Defined in Test.LeanCheck.Core

Methods

tiers :: [[Bool]] #

list :: [Bool] #

Listable Char
list :: [Char]  =  ['a', ' ', 'b', 'A', 'c', '\', 'n', 'd', ...]
Instance details

Defined in Test.LeanCheck.Core

Methods

tiers :: [[Char]] #

list :: [Char] #

Listable Double

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

list :: [Double] #

Listable Float

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

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
list :: [Int]  =  [0, 1, -1, 2, -2, 3, -3, 4, -4, 5, -5, 6, ...]
Instance details

Defined in Test.LeanCheck.Core

Methods

tiers :: [[Integer]] #

list :: [Integer] #

Listable Ordering
list :: [Ordering]  =  [LT, EQ, GT]
Instance details

Defined in Test.LeanCheck.Core

Methods

tiers :: [[Ordering]] #

list :: [Ordering] #

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

Defined in Test.LeanCheck.Utils.Types

Methods

tiers :: [[A]] #

list :: [A] #

Listable B 
Instance details

Defined in Test.LeanCheck.Utils.Types

Methods

tiers :: [[B]] #

list :: [B] #

Listable C 
Instance details

Defined in Test.LeanCheck.Utils.Types

Methods

tiers :: [[C]] #

list :: [C] #

Listable D 
Instance details

Defined in Test.LeanCheck.Utils.Types

Methods

tiers :: [[D]] #

list :: [D] #

Listable E 
Instance details

Defined in Test.LeanCheck.Utils.Types

Methods

tiers :: [[E]] #

list :: [E] #

Listable F 
Instance details

Defined in Test.LeanCheck.Utils.Types

Methods

tiers :: [[F]] #

list :: [F] #

Listable Space 
Instance details

Defined in Test.LeanCheck.Utils.Types

Methods

tiers :: [[Space]] #

list :: [Space] #

Listable Lower 
Instance details

Defined in Test.LeanCheck.Utils.Types

Methods

tiers :: [[Lower]] #

list :: [Lower] #

Listable Upper 
Instance details

Defined in Test.LeanCheck.Utils.Types

Methods

tiers :: [[Upper]] #

list :: [Upper] #

Listable Alpha 
Instance details

Defined in Test.LeanCheck.Utils.Types

Methods

tiers :: [[Alpha]] #

list :: [Alpha] #

Listable Digit 
Instance details

Defined in Test.LeanCheck.Utils.Types

Methods

tiers :: [[Digit]] #

list :: [Digit] #

Listable AlphaNum 
Instance details

Defined in Test.LeanCheck.Utils.Types

Methods

tiers :: [[AlphaNum]] #

list :: [AlphaNum] #

Listable Letter 
Instance details

Defined in Test.LeanCheck.Utils.Types

Methods

tiers :: [[Letter]] #

list :: [Letter] #

Listable Spaces 
Instance details

Defined in Test.LeanCheck.Utils.Types

Methods

tiers :: [[Spaces]] #

list :: [Spaces] #

Listable Lowers 
Instance details

Defined in Test.LeanCheck.Utils.Types

Methods

tiers :: [[Lowers]] #

list :: [Lowers] #

Listable Uppers 
Instance details

Defined in Test.LeanCheck.Utils.Types

Methods

tiers :: [[Uppers]] #

list :: [Uppers] #

Listable Alphas 
Instance details

Defined in Test.LeanCheck.Utils.Types

Methods

tiers :: [[Alphas]] #

list :: [Alphas] #

Listable Digits 
Instance details

Defined in Test.LeanCheck.Utils.Types

Methods

tiers :: [[Digits]] #

list :: [Digits] #

Listable AlphaNums 
Instance details

Defined in Test.LeanCheck.Utils.Types

Methods

tiers :: [[AlphaNums]] #

list :: [AlphaNums] #

Listable Letters 
Instance details

Defined in Test.LeanCheck.Utils.Types

Methods

tiers :: [[Letters]] #

list :: [Letters] #

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

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

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