extrapolate-0.2.4: 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

Contents

Description

Extrapolate is a property-based testing library capable of reporting generalized counter-examples.

Consider the following faulty implementation of sort:

sort :: Ord a => [a] -> [a]
sort []      =  []
sort (x:xs)  =  sort (filter (< x) xs)
             ++ [x]
             ++ sort (filter (> x) xs)

When tests pass, Extrapolate works like a regular property-based testing library. See:

> check $ \xs -> sort (sort xs :: [Int]) == sort xs
+++ OK, passed 360 tests.

When tests fail, Extrapolate reports a fully defined counter-example and a generalization of failing inputs. See:

> > check $ \xs -> length (sort xs :: [Int]) == length xs
*** Failed! Falsifiable (after 3 tests):
[0,0]

Generalization:
x:x:_

The property fails for any integer x and for any list _ at the tail.

Synopsis

Checking properties

check :: Testable a => a -> IO () Source #

Checks a property printing results on stdout

> check $ \xs -> sort (sort xs) == sort (xs::[Int])
+++ OK, passed 360 tests.

> check $ \xs ys -> xs `union` ys == ys `union` (xs::[Int])
*** Failed! Falsifiable (after 4 tests):
[] [0,0]

Generalization:
[] (x:x:_)

checkResult :: Testable a => a -> IO Bool Source #

Check a property printing results on stdout and returning True on success.

There is no option to silence this function: for silence, you should use holds.

for :: Testable a => (WithOption a -> b) -> Int -> a -> b Source #

Use for to configure the number of tests performed by check.

> check `for` 10080 $ \xs -> sort (sort xs) == sort (xs :: [Int])
+++ OK, passed 10080 tests.

Don't forget the dollar ($)!

withBackground :: Testable a => (WithOption a -> b) -> [Expr] -> a -> b Source #

Use withBackground to provide additional functions to appear in side-conditions.

check `withBackground` [constant "isSpace" isSpace] $ \xs -> unwords (words xs) == xs
*** Failed! Falsifiable (after 4 tests):
" "

Generalization:
' ':_

Conditional Generalization:
c:_  when  isSpace c

withConditionSize :: Testable a => (WithOption a -> b) -> Int -> a -> b Source #

Use withConditionSize to configure the maximum condition size allowed.

Generalizable types

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 #

data Expr :: * #

Instances

Eq Expr 

Methods

(==) :: Expr -> Expr -> Bool #

(/=) :: Expr -> Expr -> Bool #

Ord Expr 

Methods

compare :: Expr -> Expr -> Ordering #

(<) :: Expr -> Expr -> Bool #

(<=) :: Expr -> Expr -> Bool #

(>) :: Expr -> Expr -> Bool #

(>=) :: Expr -> Expr -> Bool #

max :: Expr -> Expr -> Expr #

min :: Expr -> Expr -> Expr #

Show Expr 

Methods

showsPrec :: Int -> Expr -> ShowS #

show :: Expr -> String #

showList :: [Expr] -> ShowS #

constant :: Typeable * a => String -> a -> Expr #

showConstant :: (Typeable * a, Show a) => a -> Expr #

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

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

Testable properties

class Testable a Source #

Minimal complete definition

resultiers, ($-|), tinstances

Instances

Testable Bool Source # 

Methods

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

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

tinstances :: Bool -> Instances Source #

options :: Bool -> Options Source #

Testable a => Testable (WithOption a) Source # 

Methods

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

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

tinstances :: WithOption a -> Instances Source #

options :: WithOption a -> Options Source #

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

Methods

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

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

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

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

Automatically deriving Generalizable instances

deriveGeneralizable :: Name -> DecsQ Source #

Derives a Generalizable instance for a given type Name.

Consider the following Stack datatype:

data Stack a = Stack a (Stack a) | Empty

Writing

deriveGeneralizable ''Stack

will automatically derive the following Generalizable instance:

instance Generalizable a => Generalizable (Stack a) where
  expr s@(Stack x y) = constant "Stack" (Stack ->>: s) :$ expr x :$ expr y
  expr s@Empty       = constant "Empty" (Empty   -: s)
  instances s = this "s" s
              $ let Stack x y = Stack undefined undefined `asTypeOf` s
                in instances x
                 . instances y

This function needs the TemplateHaskell extension.

deriveGeneralizableIfNeeded :: Name -> DecsQ Source #

Same as deriveGeneralizable but does not warn when instance already exists (deriveGeneralizable is preferable).

deriveGeneralizableCascading :: Name -> DecsQ Source #

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

Other useful modules