speculate-0.2.4: discovery of properties about Haskell functions

Copyright(c) 2016-2017 Rudy Matela
License3-Clause BSD (see the file LICENSE)
MaintainerRudy Matela <rudy@matela.com.br>
Safe HaskellNone
LanguageHaskell2010

Test.Speculate

Contents

Description

Speculate: discovery of properties by reasoning from test results

Speculate automatically discovers laws about Haskell functions. Those laws involve:

  • equations, such as id x == x ;
  • inequalities, such as 0 <= x * x ;
  • conditional equations, such as x <= 0 ==> x + abs x == 0 .

_Example:_ the following program prints laws about 0, 1, + and abs.

import Test.Speculate

main :: IO ()
main = speculate args
  { constants =
      [ showConstant (0::Int)
      , showConstant (1::Int)
      , constant "+"   ((+)  :: Int -> Int -> Int)
      , constant "abs" (abs  :: Int -> Int)
      , background
      , constant "<="  ((<=) :: Int -> Int -> Bool)
      ]
  }

Synopsis

Documentation

speculate :: Args -> IO () Source #

Calls Speculate. See the example above (at the top of the file). Its only argument is an Args structure.

data Args Source #

Arguments to Speculate

Constructors

Args 

Fields

args :: Args Source #

Default arguments to Speculate

The constants list

The following combinators are used to build the constants list from Args.

data Expr Source #

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

Instances

Eq Expr Source # 

Methods

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

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

Ord Expr Source # 

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

Methods

showsPrec :: Int -> Expr -> ShowS #

show :: Expr -> String #

showList :: [Expr] -> ShowS #

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

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

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

hole :: (Listable a, Typeable a) => a -> Expr Source #

(intended for advanced users)

hole (undefined :: Ty) returns a hole of type Ty

By convention, a Hole is a variable named with the empty string.

foreground :: Expr Source #

A special Expr value. When provided on the constants list, makes all the following constants foreground constants.

background :: Expr Source #

A special Expr value. When provided on the constants list, makes all the following constants background constants. Background constants can appear in laws about other constants, but not by themselves.

The instances list

The following combinators are used to build the instances list from Args.

type Instances = [Instance] Source #

Type information needed to Speculate expressions.

ins :: (Typeable a, Listable a, Show a, Eq a, Ord a) => String -> a -> Instances Source #

eq :: (Typeable a, Eq a) => a -> Instances Source #

ord :: (Typeable a, Ord a) => a -> Instances Source #

eqWith :: (Typeable a, Eq a) => (a -> a -> Bool) -> Instances Source #

ordWith :: (Typeable a, Ord a) => (a -> a -> Bool) -> Instances Source #

Misc.

report :: Args -> IO () Source #