| Copyright | (c) 2017 Rudy Matela |
|---|---|
| License | 3-Clause BSD (see the file LICENSE) |
| Maintainer | Rudy Matela <rudy@matela.com.br> |
| Safe Haskell | None |
| Language | Haskell2010 |
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.
- check :: Testable a => a -> IO ()
- checkResult :: Testable a => a -> IO Bool
- for :: Testable a => (WithOption a -> b) -> Int -> a -> b
- withBackground :: Testable a => (WithOption a -> b) -> [Expr] -> a -> b
- withConditionSize :: Testable a => (WithOption a -> b) -> Int -> a -> b
- class (Listable a, Typeable a, Show a) => Generalizable a where
- this :: Generalizable a => a -> (Instances -> Instances) -> Instances -> Instances
- data Expr :: *
- constant :: Typeable * a => String -> a -> Expr
- showConstant :: (Typeable * a, Show a) => a -> Expr
- bgEq :: (Eq a, Generalizable a) => a -> [Expr]
- bgOrd :: (Ord a, Generalizable a) => a -> [Expr]
- class Testable a
- deriveGeneralizable :: Name -> DecsQ
- deriveGeneralizableIfNeeded :: Name -> DecsQ
- deriveGeneralizableCascading :: Name -> DecsQ
- module Test.Extrapolate.TypeBinding
- module Test.LeanCheck
- module Test.LeanCheck.Utils.TypeBinding
- ordering :: Ordering
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:_)
for :: Testable a => (WithOption a -> b) -> Int -> a -> b Source #
Use to configure the number of tests performed by forcheck.
> 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 to provide additional functions to appear in side-conditions.withBackground
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 to configure the maximum condition size allowed.withConditionSize
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:
- LeanCheck's Test.LeanCheck.Utils.TypeBinding operators:
-:,->:,->>:, ...; - Extrapolate's Test.Extrapolate.TypeBinding operators:
argTy1of1,argTy1of2,argTy2of2, ....
Methods
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 # | |
| Generalizable Char Source # | |
| Generalizable Int Source # | |
| Generalizable Integer Source # | |
| Generalizable Ordering Source # | |
| Generalizable () Source # | |
| Generalizable a => Generalizable [a] Source # | |
| Generalizable a => Generalizable (Maybe a) Source # | |
| (Generalizable a, Generalizable b) => Generalizable (Either a b) Source # | |
| (Generalizable a, Generalizable b) => Generalizable (a, b) Source # | |
| (Generalizable a, Generalizable b, Generalizable c) => Generalizable (a, b, c) Source # | |
An encoded Haskell functional-application expression for use by Speculate.
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])
Testable properties
Minimal complete definition
resultiers, ($-|), tinstances
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 yThis 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
module Test.Extrapolate.TypeBinding
module Test.LeanCheck