extrapolate-0.2.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

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 # 

Methods

expr :: Bool -> Expr Source #

name :: Bool -> String Source #

background :: Bool -> [Expr] Source #

instances :: Bool -> Instances -> Instances Source #

Generalizable Char Source # 

Methods

expr :: Char -> Expr Source #

name :: Char -> String Source #

background :: Char -> [Expr] Source #

instances :: Char -> Instances -> Instances Source #

Generalizable Int Source # 

Methods

expr :: Int -> Expr Source #

name :: Int -> String Source #

background :: Int -> [Expr] Source #

instances :: Int -> Instances -> Instances Source #

Generalizable Integer Source # 

Methods

expr :: Integer -> Expr Source #

name :: Integer -> String Source #

background :: Integer -> [Expr] Source #

instances :: Integer -> Instances -> Instances Source #

Generalizable Ordering Source # 

Methods

expr :: Ordering -> Expr Source #

name :: Ordering -> String Source #

background :: Ordering -> [Expr] Source #

instances :: Ordering -> Instances -> Instances Source #

Generalizable () Source # 

Methods

expr :: () -> Expr Source #

name :: () -> String Source #

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

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

Generalizable a => Generalizable [a] Source # 

Methods

expr :: [a] -> Expr Source #

name :: [a] -> String Source #

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

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

Generalizable a => Generalizable (Maybe a) Source # 

Methods

expr :: Maybe a -> Expr Source #

name :: Maybe a -> String Source #

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

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

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

Methods

expr :: Either a b -> Expr Source #

name :: Either a b -> String Source #

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

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

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

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 # 

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 # 

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 #

this :: Generalizable a => a -> (Instances -> Instances) -> Instances -> Instances Source #

backgroundWith :: Typeable a => [Expr] -> a -> 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 #

data Option Source #

Constructors

MaxTests Int 
ExtraInstances Instances 
MaxConditionSize Int 

Instances

options :: Testable a => a -> Options Source #

data WithOption a Source #

Constructors

With 

Fields

Instances

Testable a => Testable (WithOption a) Source # 

Methods

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

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

tinstances :: WithOption a -> Instances

options :: WithOption a -> Options Source #

extraInstances :: Testable a => a -> Instances Source #

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

generalizations :: Instances -> [Expr] -> [[Expr]] Source #

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

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

generalizationsCounts :: Testable a => Int -> a -> [Expr] -> [([Expr], Int)] 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

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

class Testable a where Source #

Minimal complete definition

resultiers, ($-|), tinstances

Methods

options :: a -> Options Source #

Instances

Testable Bool Source # 

Methods

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

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

tinstances :: Bool -> Instances

options :: Bool -> Options Source #

Testable a => Testable (WithOption a) Source # 

Methods

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

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

tinstances :: WithOption a -> Instances

options :: WithOption a -> Options Source #

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

Methods

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

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

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

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

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