extrapolate-0.1.0: 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.

Obtaining generalizations

Generalizable types

The following typeclass and functions are currently very hacky. Expect them to change in the near future.

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

Minimal complete definition

expr

Methods

expr :: a -> Expr Source #

useful :: a -> [Expr] Source #

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

Instances

Generalizable Bool Source # 
Generalizable Char Source # 
Generalizable Int Source # 
Generalizable Integer Source # 
Generalizable () Source # 

Methods

expr :: () -> Expr Source #

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

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

Generalizable a => Generalizable [a] Source # 

Methods

expr :: [a] -> Expr Source #

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

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

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

Methods

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

useful :: (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 #

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

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

data Expr :: * #

An encoded Haskell functional-application expression for use by Speculate.

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 #

Encode a constant Haskell expression for use by Speculate. It takes a string representation of a value and a value, returning an Expr. Examples:

constant "0" 0
constant "'a'" 'a'
constant "True" True
constant "id" (id :: Int -> Int)
constant "(+)" ((+) :: Int -> Int -> Int)
constant "sort" (sort :: [Bool] -> [Bool])

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

A shorthand for constant to be used on values that are Show instances. Examples:

showConstant 0     =  constant "0" 0
showConstant 'a'   =  constant "'a'" 'a' 
showConstant True  =  constant "True" True

Testable properties

class Testable a Source #

Minimal complete definition

resultiers, ($-|), tinstances

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 #

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