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.Expr.Core

Contents

Description

This module is part of Speculate.

Defines the Expr type and basic operations on it.

Synopsis

Documentation

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 #

Smart constructors

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

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

var "x" (undefined :: Ty) returns a variable of type Ty named "x"

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.

($$) :: Expr -> Expr -> Maybe Expr Source #

Just an Expr application if the types match, Nothing otherwise.

Smart destructors

evaluate :: Typeable a => Expr -> Maybe a Source #

Just the value of an expression when possible (correct type, no holes), Nothing otherwise.

eval :: Typeable a => a -> Expr -> a Source #

Evaluates an expression when possible (correct type, no holes). Returns a default value otherwise.

typ :: Expr -> TypeRep Source #

The type of an expression. This raises errors, but those should not happen if expressions are smart-constructed.

etyp :: Expr -> Either Expr TypeRep Source #

etyp returns either: the Right type a Left expression with holes with the structure of the I'll typed expression

Queries

arity :: Expr -> Int Source #

Type arity of an Expr

holes :: Expr -> [TypeRep] Source #

List types holes (unamed variables) in an expression

vars :: Expr -> [(TypeRep, String)] Source #

List all variables in an expression.

consts :: Expr -> [Expr] Source #

List terminal constants in an expression. This does not repeat values.

subexprs :: Expr -> [Expr] Source #

Non-variable sub-expressions of an expression

This includes the expression itself

subexprsV :: Expr -> [Expr] Source #

Sub-expressions of an expression including variables and the expression itself.

isSub :: Expr -> Expr -> Bool Source #

Is a subexpression of.

unfoldApp :: Expr -> [Expr] Source #

Unfold function application:

(((f :$ e1) :$ e2) :$ e3) = [f,e1,e2,e3]

Properties of expressions

lengthE :: Expr -> Int Source #

Returns the length of an expression. In term rewriting terms: |s|

depthE :: Expr -> Int Source #

Returns the maximum depth of an expression.

countVar :: TypeRep -> String -> Expr -> Int Source #

Number of occurrences of a given variable name. In term rewriting terms: |s|_x

lexicompare :: Expr -> Expr -> Ordering Source #

Compare two expressiosn lexicographically

1st their type arity; 2nd their type; 3rd var < constants < apps 4th lexicographic order on names

compareComplexity :: Expr -> Expr -> Ordering Source #

Compares two expressions first by their complexity: 1st length; 2nd number of variables (more variables is less complex); 3nd sum of number of variable occurrences; 4th their depth; 5th lexicompare.

compareComplexityThen :: (Expr -> Expr -> Ordering) -> Expr -> Expr -> Ordering Source #

Compares two expressions first by their complexity: 1st length; 2nd number of variables (more variables is less complex); 3nd sum of number of variable occurrences; 4th their depth; 5th normal compare.

Useful expressions

Showing