express-0.1.6: Dynamically-typed expressions involving applications and variables.
Copyright(c) 2019-2021 Rudy Matela
License3-Clause BSD (see the file LICENSE)
MaintainerRudy Matela <rudy@matela.com.br>
Safe HaskellNone
LanguageHaskell2010

Data.Express

Description

Express is a library for manipulating dynamically typed Haskell expressions. It's like Data.Dynamic but with support for encoding applications and variables.

It provides the Expr type and over a hundred functions for building, evaluating, comparing, folding, canonicalizing and matching Exprs.

Basics. For types that are Show instances, we can use val to encode values as Exprs:

> let false = val False
> :t false
false :: Expr
> print false
False :: Bool

As seen above, the Show instance for Expr produces a string with the encoded value and it's type.

For types that aren't Show instances, like functions, we can use value to encode values as Exprs.

> let notE = value "not" not
> :t notE
notE :: Expr
> print notE
not :: Bool -> Bool

Using :$ we can apply function valued Exprs, to other Exprs.

> let notFalse = notE :$ false
> :t notFalse
notFalse :: Expr
> notFalse
not False :: Bool

Using evaluate or eval we can evaluate Exprs back into a regular Haskell value.

> evaluate notFalse :: Maybe Bool
Just True
> evaluate notFalse :: Maybe Int
Nothing
> eval False notFalse
True
> eval (0::Int) notFalse
0

Example: Like with Data.Dynamic, we can use Express to create heterogeneous lists:

> let xs = [val False, val True, val (1::Int), val (2::Int), val (3::Integer), val "123"]
> :t xs
xs :: [Expr]
> xs
[ False :: Bool
, True :: Bool
, 1 :: Int
, 2 :: Int
, 3 :: Integer
, "123" :: [Char]
]

We can then apply evaluate to select values of different types:

> import Data.Maybe
> mapMaybe evaluate xs :: [Bool]
[False,True]
> mapMaybe evaluate xs :: [Int]
[1,2]
> mapMaybe evaluate xs :: [Integer]
[3]
> mapMaybe evaluate xs :: [String]
["123"]

If we define an heterogeneous list of functions encoded as Exprs:

> let fs = [value "not" not, value "&&" (&&), value "abs" (abs :: Int -> Int)]
> :t fs
fs :: [Expr]

Using $$ we can list the type correct applications between the two previously defined lists:

> catMaybes [f $$ x | f <- fs, x <- xs]
[ not False :: Bool
, not True :: Bool
, (False &&) :: Bool -> Bool
, (True &&) :: Bool -> Bool
, abs 1 :: Int
, abs 2 :: Int
]

Other uses of Express include:

  • generalizing counter-examples of property-based testing in Extrapolate;
  • conjecturing equations based on the results of testing in Speculate.

In this documentation, the complexity of most functions is given in big O notation where n is the size of the expression being manipulated or produced. There may still be a m cost associated with the values stored in Exprs.

Synopsis

The Expr datatype

data Expr Source #

Values of type Expr represent objects or applications between objects. Each object is encapsulated together with its type and string representation. Values encoded in Exprs are always monomorphic.

An Expr can be constructed using:

  • val, for values that are Show instances;
  • value, for values that are not Show instances, like functions;
  • :$, for applications between Exprs.
> val False
False :: Bool
> value "not" not :$ val False
not False :: Bool

An Expr can be evaluated using evaluate, eval or evl.

> evl $ val (1 :: Int) :: Int
1
> evaluate $ val (1 :: Int) :: Maybe Bool
Nothing
> eval 'a' (val 'b')
'b'

Showing a value of type Expr will return a pretty-printed representation of the expression together with its type.

> show (value "not" not :$ val False)
"not False :: Bool"

Expr is like Dynamic but has support for applications and variables (:$, var).

The var underscore convention: Functions that manipulate Exprs usually follow the convention where a value whose String representation starts with '_' represents a variable.

Constructors

Value String Dynamic

a value enconded as String and Dynamic

Expr :$ Expr

function application between expressions

Instances

Instances details
Eq Expr Source #

O(n). Does not evaluate values when comparing, but rather uses their representation as strings and their types.

This instance works for ill-typed expressions.

Instance details

Defined in Data.Express.Core

Methods

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

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

Ord Expr Source #

O(n). Does not evaluate values when comparing, but rather uses their representation as strings and their types.

This instance works for ill-typed expressions.

Expressions come first when they have smaller complexity (compareComplexity) or when they come first lexicographically (compareLexicographically).

Instance details

Defined in Data.Express.Core

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 #

Shows Exprs with their types.

> show (value "not" not :$ val False)
"not False :: Bool"
Instance details

Defined in Data.Express.Core

Methods

showsPrec :: Int -> Expr -> ShowS #

show :: Expr -> String #

showList :: [Expr] -> ShowS #

Building Exprs

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

O(1). It takes a string representation of a value and a value, returning an Expr with that terminal value. For instances of Show, it is preferable to use val.

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

val :: (Typeable a, Show a) => a -> Expr Source #

O(1). A shorthand for value for values that are Show instances.

> val (0 :: Int)
0 :: Int
> val 'a'
'a' :: Char
> val True
True :: Bool

Example equivalences to value:

val 0     =  value "0" 0
val 'a'   =  value "'a'" 'a'
val True  =  value "True" True

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

O(n). Creates an Expr representing a function application. Just an Expr application if the types match, Nothing otherwise. (cf. :$)

> value "id" (id :: () -> ()) $$ val ()
Just (id () :: ())
> value "abs" (abs :: Int -> Int) $$ val (1337 :: Int)
Just (abs 1337 :: Int)
> value "abs" (abs :: Int -> Int) $$ val 'a'
Nothing
> value "abs" (abs :: Int -> Int) $$ val ()
Nothing

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

O(1). Creates an Expr representing a variable with the given name and argument type.

> var "x" (undefined :: Int)
x :: Int
> var "u" (undefined :: ())
u :: ()
> var "xs" (undefined :: [Int])
xs :: [Int]

This function follows the underscore convention: a variable is just a value whose string representation starts with underscore ('_').

Evaluating Exprs

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

O(n). Just the value of an expression when possible (correct type), Nothing otherwise. This does not catch errors from undefined Dynamic values.

> let one = val (1 :: Int)
> let bee = val 'b'
> let negateE = value "negate" (negate :: Int -> Int)
> evaluate one :: Maybe Int
Just 1
> evaluate one :: Maybe Char
Nothing
> evaluate bee :: Maybe Int
Nothing
> evaluate bee :: Maybe Char
Just 'b'
> evaluate $ negateE :$ one :: Maybe Int
Just (-1)
> evaluate $ negateE :$ bee :: Maybe Int
Nothing

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

O(n). Evaluates an expression when possible (correct type). Returns a default value otherwise.

> let two = val (2 :: Int)
> let three = val (3 :: Int)
> let e1 -+- e2 = value "+" ((+) :: Int->Int->Int) :$ e1 :$ e2
> eval 0 $ two -+- three :: Int
5
> eval 'z' $ two -+- three :: Char
'z'
> eval 0 $ two -+- val '3' :: Int
0

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

O(n). Evaluates an expression when possible (correct type). Raises an error otherwise.

> evl $ two -+- three :: Int
5
> evl $ two -+- three :: Bool
*** Exception: evl: cannot evaluate Expr `2 + 3 :: Int' at the Bool type

This may raise errors, please consider using eval or evaluate.

typ :: Expr -> TypeRep Source #

O(n). Computes the type of an expression. This raises errors, but this should not happen if expressions are smart-constructed with $$.

> let one = val (1 :: Int)
> let bee = val 'b'
> let absE = value "abs" (abs :: Int -> Int)
> typ one
Int
> typ bee
Char
> typ absE
Int -> Int
> typ (absE :$ one)
Int
> typ (absE :$ bee)
*** Exception: type mismatch, cannot apply `Int -> Int' to `Char'
> typ ((absE :$ bee) :$ one)
*** Exception: type mismatch, cannot apply `Int -> Int' to `Char'

etyp :: Expr -> Either (TypeRep, TypeRep) TypeRep Source #

O(n). Computes the type of an expression returning either the type of the given expression when possible or when there is a type error, the pair of types which produced the error.

> let one = val (1 :: Int)
> let bee = val 'b'
> let absE = value "abs" (abs :: Int -> Int)
> etyp one
Right Int
> etyp bee
Right Char
> etyp absE
Right (Int -> Int)
> etyp (absE :$ one)
Right Int
> etyp (absE :$ bee)
Left (Int -> Int, Char)
> etyp ((absE :$ bee) :$ one)
Left (Int -> Int, Char)

mtyp :: Expr -> Maybe TypeRep Source #

O(n). Returns Just the type of an expression or Nothing when there is an error.

> let one = val (1 :: Int)
> let bee = val 'b'
> let absE = value "abs" (abs :: Int -> Int)
> mtyp one
Just Int
> mtyp (absE :$ bee)
Nothing

toDynamic :: Expr -> Maybe Dynamic Source #

O(n). Evaluates an expression to a terminal Dynamic value when possible. Returns Nothing otherwise.

> toDynamic $ val (123 :: Int) :: Maybe Dynamic
Just <<Int>>
> toDynamic $ value "abs" (abs :: Int -> Int) :$ val (-1 :: Int)
Just <<Int>>
> toDynamic $ value "abs" (abs :: Int -> Int) :$ val 'a'
Nothing

Boolean properties of Exprs

isValue :: Expr -> Bool Source #

O(1). Returns whether an Expr is a terminal value (Value).

> isValue $ var "x" (undefined :: Int)
True
> isValue $ val False
True
> isValue $ value "not" not :$ var "p" (undefined :: Bool)
False

This is equivalent to pattern matching the Value constructor.

Properties:

  •  isValue (Value e)  =  True
  •  isValue (e1 :$ e2)  =  False
  •  isValue  =  not . isApp
  •  isValue e  =  isVar e || isConst e

isApp :: Expr -> Bool Source #

O(1). Returns whether an Expr is an application (:$).

> isApp $ var "x" (undefined :: Int)
False
> isApp $ val False
False
> isApp $ value "not" not :$ var "p" (undefined :: Bool)
True

This is equivalent to pattern matching the :$ constructor.

Properties:

  •  isApp (e1 :$ e2)  =  True
  •  isApp (Value e)  =  False
  •  isApp  =  not . isValue
  •  isApp e  =  not (isVar e) && not (isConst e)

isVar :: Expr -> Bool Source #

O(1). Returns whether an Expr is a terminal variable (var). (cf. hasVar).

> isVar $ var "x" (undefined :: Int)
True
> isVar $ val False
False
> isVar $ value "not" not :$ var "p" (undefined :: Bool)
False

isConst :: Expr -> Bool Source #

O(1). Returns whether an Expr is a terminal constant. (cf. isGround).

> isConst $ var "x" (undefined :: Int)
False
> isConst $ val False
True
> isConst $ value "not" not :$ val False
False

isIllTyped :: Expr -> Bool Source #

O(n). Returns whether the given Expr is ill typed. (cf. isWellTyped)

> let one = val (1 :: Int)
> let bee = val 'b'
> let absE = value "abs" (abs :: Int -> Int)
> isIllTyped (absE :$ val (1 :: Int))
False
> isIllTyped (absE :$ val 'b')
True

isWellTyped :: Expr -> Bool Source #

O(n). Returns whether the given Expr is well typed. (cf. isIllTyped)

> isWellTyped (absE :$ val (1 :: Int))
True
> isWellTyped (absE :$ val 'b')
False

isFun :: Expr -> Bool Source #

O(n). Returns whether the given Expr is of a functional type. This is the same as checking if the arity of the given Expr is non-zero.

> isFun (value "abs" (abs :: Int -> Int))
True
> isFun (val (1::Int))
False
> isFun (value "const" (const :: Bool -> Bool -> Bool) :$ val False)
True

hasVar :: Expr -> Bool Source #

O(n). Check if an Expr has a variable. (By convention, any value whose String representation starts with '_'.)

> hasVar $ value "not" not :$ val True
False
> hasVar $ value "&&" (&&) :$ var "p" (undefined :: Bool) :$ val True
True

isGround :: Expr -> Bool Source #

O(n). Returns whether a Expr has no variables. This is equivalent to "not . hasVar".

The name "ground" comes from term rewriting.

> isGround $ value "not" not :$ val True
True
> isGround $ value "&&" (&&) :$ var "p" (undefined :: Bool) :$ val True
False

Comparing Exprs

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

O(n). Compares the complexity of two Exprs. An expression e1 is strictly simpler than another expression e2 if the first of the following conditions to distingish between them is:

  1. e1 is smaller in size/length than e2, e.g.: x + y < x + (y + z);
  2. or, e1 has more distinct variables than e2, e.g.: x + y < x + x;
  3. or, e1 has more variable occurrences than e2, e.g.: x + x < 1 + x;
  4. or, e1 has fewer distinct constants than e2, e.g.: 1 + 1 < 0 + 1.

They're otherwise considered of equal complexity, e.g.: x + y and y + z.

> (xx -+- yy) `compareComplexity` (xx -+- (yy -+- zz))
LT
> (xx -+- yy) `compareComplexity` (xx -+- xx)
LT
> (xx -+- xx) `compareComplexity` (one -+- xx)
LT
> (one -+- one) `compareComplexity` (zero -+- one)
LT
> (xx -+- yy) `compareComplexity` (yy -+- zz)
EQ
> (zero -+- one) `compareComplexity` (one -+- zero)
EQ

This comparison is not a total order.

compareLexicographically :: Expr -> Expr -> Ordering Source #

O(n). Lexicographical structural comparison of Exprs where variables < constants < applications then types are compared before string representations.

> compareLexicographically one (one -+- one)
LT
> compareLexicographically one zero
GT
> compareLexicographically (xx -+- zero) (zero -+- xx)
LT
> compareLexicographically (zero -+- xx) (zero -+- xx)
EQ

(cf. compareTy)

This comparison is a total order.

compareQuickly :: Expr -> Expr -> Ordering Source #

O(n). A fast total order between Exprs that can be used when sorting Expr values.

This is lazier than its counterparts compareComplexity and compareLexicographically and tries to evaluate the given Exprs as least as possible.

Properties of Exprs

arity :: Expr -> Int Source #

O(n). Return the arity of the given expression, i.e. the number of arguments that its type takes.

> arity (val (0::Int))
0
> arity (val False)
0
> arity (value "id" (id :: Int -> Int))
1
> arity (value "const" (const :: Int -> Int -> Int))
2
> arity (one -+- two)
0

size :: Expr -> Int Source #

O(n). Returns the size of the given expression, i.e. the number of terminal values in it.

zero       =  val (0 :: Int)
one        =  val (1 :: Int)
two        =  val (2 :: Int)
xx -+- yy  =  value "+" ((+) :: Int->Int->Int) :$ xx :$ yy
abs' xx    =  value "abs" (abs :: Int->Int) :$ xx
> size zero
1
> size (one -+- two)
3
> size (abs' one)
2

depth :: Expr -> Int Source #

O(n). Returns the maximum depth of a given expression given by the maximum number of nested function applications. Curried function application is counted only once, i.e. the application of a two argument function increases the depth of both its arguments by one. (cf. height)

With

zero       =  val (0 :: Int)
one        =  val (1 :: Int)
two        =  val (2 :: Int)
xx -+- yy  =  value "+" ((+) :: Int->Int->Int) :$ xx :$ yy
abs' xx    =  value "abs" (abs :: Int->Int) :$ xx
> depth zero
1
> depth (one -+- two)
2
> depth (abs' one -+- two)
3

Flipping arguments of applications in any of the subterms does not affect the result.

height :: Expr -> Int Source #

O(n). Returns the maximum height of a given expression given by the maximum number of nested function applications. Curried function application is counted each time, i.e. the application of a two argument function increases the depth of its first argument by two and of its second argument by one. (cf. depth)

With:

zero          =  val (0 :: Int)
one           =  val (1 :: Int)
two           =  val (2 :: Int)
const' xx yy  =  value "const" (const :: Int->Int->Int) :$ xx :$ yy
abs' xx       =  value "abs" (abs :: Int->Int) :$ xx

Then:

> height zero
1
> height (abs' one)
2
> height ((const' one) two)
3
> height ((const' (abs' one)) two)
4
> height ((const' one) (abs' two))
3

Flipping arguments of applications in subterms may change the result of the function.

Showing Exprs

showExpr :: Expr -> String Source #

O(n). Returns a string representation of an expression. Differently from show (:: Expr -> String) this function does not include the type in the output.

> putStrLn $ showExpr (one -+- two)
1 + 2
> putStrLn $ showExpr $ (pp -||- true) -&&- (qq -||- false)
(p || True) && (q || False)

Subexpressions

Listing subexpressions

subexprs :: Expr -> [Expr] Source #

O(n) for the spine, O(n^2) for full evaluation. Lists subexpressions of a given expression in order and with repetitions. This includes the expression itself and partial function applications. (cf. nubSubexprs)

> subexprs (xx -+- yy)
[ x + y :: Int
, (x +) :: Int -> Int
, (+) :: Int -> Int -> Int
, x :: Int
, y :: Int
]
> subexprs (pp -&&- (pp -&&- true))
[ p && (p && True) :: Bool
, (p &&) :: Bool -> Bool
, (&&) :: Bool -> Bool -> Bool
, p :: Bool
, p && True :: Bool
, (p &&) :: Bool -> Bool
, (&&) :: Bool -> Bool -> Bool
, p :: Bool
, True :: Bool
]

values :: Expr -> [Expr] Source #

O(n). Lists all terminal values in an expression in order and with repetitions. (cf. nubValues)

> values (xx -+- yy)
[ (+) :: Int -> Int -> Int
, x :: Int
, y :: Int
]
> values (xx -+- (yy -+- zz))
[ (+) :: Int -> Int -> Int
, x :: Int
, (+) :: Int -> Int -> Int
, y :: Int
, z :: Int
]
> values (zero -+- (one -*- two))
[ (+) :: Int -> Int -> Int
, 0 :: Int
, (*) :: Int -> Int -> Int
, 1 :: Int
, 2 :: Int
]
> values (pp -&&- true)
[ (&&) :: Bool -> Bool -> Bool
, p :: Bool
, True :: Bool
]

vars :: Expr -> [Expr] Source #

O(n). Lists all variables in an expression in order and with repetitions. (cf. nubVars)

> vars (xx -+- yy)
[ x :: Int
, y :: Int
]
> vars (xx -+- (yy -+- xx))
[ x :: Int
, y :: Int
, x :: Int
]
> vars (zero -+- (one -*- two))
[]
> vars (pp -&&- true)
[p :: Bool]

consts :: Expr -> [Expr] Source #

O(n). List terminal constants in an expression in order and with repetitions. (cf. nubConsts)

> consts (xx -+- yy)
[ (+) :: Int -> Int -> Int ]
> consts (xx -+- (yy -+- zz))
[ (+) :: Int -> Int -> Int
, (+) :: Int -> Int -> Int
]
> consts (zero -+- (one -*- two))
[ (+) :: Int -> Int -> Int
, 0 :: Int
, (*) :: Int -> Int -> Int
, 1 :: Int
, 2 :: Int
]
> consts (pp -&&- true)
[ (&&) :: Bool -> Bool -> Bool
, True :: Bool
]

nubSubexprs :: Expr -> [Expr] Source #

O(n^3) for full evaluation. Lists all subexpressions of a given expression without repetitions. This includes the expression itself and partial function applications. (cf. subexprs)

> nubSubexprs (xx -+- yy)
[ x :: Int
, y :: Int
, (+) :: Int -> Int -> Int
, (x +) :: Int -> Int
, x + y :: Int
]
> nubSubexprs (pp -&&- (pp -&&- true))
[ p :: Bool
, True :: Bool
, (&&) :: Bool -> Bool -> Bool
, (p &&) :: Bool -> Bool
, p && True :: Bool
, p && (p && True) :: Bool
]

Runtime averages to O(n^2 log n) on evenly distributed expressions such as (f x + g y) + (h z + f w); and to O(n^3) on deep expressions such as f (g (h (f (g (h x))))).

nubValues :: Expr -> [Expr] Source #

O(n^2). Lists all terminal values in an expression without repetitions. (cf. values)

> nubValues (xx -+- yy)
[ x :: Int
, y :: Int
, (+) :: Int -> Int -> Int

]

> nubValues (xx -+- (yy -+- zz))
[ x :: Int
, y :: Int
, z :: Int
, (+) :: Int -> Int -> Int
]
> nubValues (zero -+- (one -*- two))
[ 0 :: Int
, 1 :: Int
, 2 :: Int
, (*) :: Int -> Int -> Int
, (+) :: Int -> Int -> Int
]
> nubValues (pp -&&- pp)
[ p :: Bool
, (&&) :: Bool -> Bool -> Bool
]

Runtime averages to O(n log n) on evenly distributed expressions such as (f x + g y) + (h z + f w); and to O(n^2) on deep expressions such as f (g (h (f (g (h x))))).

nubVars :: Expr -> [Expr] Source #

O(n^2). Lists all variables in an expression without repetitions. (cf. vars)

> nubVars (yy -+- xx)
[ x :: Int
, y :: Int
]
> nubVars (xx -+- (yy -+- xx))
[ x :: Int
, y :: Int
]
> nubVars (zero -+- (one -*- two))
[]
> nubVars (pp -&&- true)
[p :: Bool]

Runtime averages to O(n log n) on evenly distributed expressions such as (f x + g y) + (h z + f w); and to O(n^2) on deep expressions such as f (g (h (f (g (h x))))).

nubConsts :: Expr -> [Expr] Source #

O(n^2). List terminal constants in an expression without repetitions. (cf. consts)

> nubConsts (xx -+- yy)
[ (+) :: Int -> Int -> Int ]
> nubConsts (xx -+- (yy -+- zz))
[ (+) :: Int -> Int -> Int ]
> nubConsts (pp -&&- true)
[ True :: Bool
, (&&) :: Bool -> Bool -> Bool
]

Runtime averages to O(n log n) on evenly distributed expressions such as (f x + g y) + (h z + f w); and to O(n^2) on deep expressions such as f (g (h (f (g (h x))))).

Mapping subexpressions

mapValues :: (Expr -> Expr) -> Expr -> Expr Source #

O(n*m). Applies a function to all terminal values in an expression. (cf. //-)

Given that:

> let zero  = val (0 :: Int)
> let one   = val (1 :: Int)
> let two   = val (2 :: Int)
> let three = val (3 :: Int)
> let xx -+- yy = value "+" ((+) :: Int->Int->Int) :$ xx :$ yy
> let intToZero e = if typ e == typ zero then zero else e

Then:

> one -+- (two -+- three)
1 + (2 + 3) :: Int
> mapValues intToZero $ one -+- (two -+- three)
0 + (0 + 0) :: Integer

Given that the argument function is O(m), this function is O(n*m).

mapVars :: (Expr -> Expr) -> Expr -> Expr Source #

O(n*m). Applies a function to all variables in an expression.

Given that:

> let primeify e = if isVar e
|                  then case e of (Value n d) -> Value (n ++ "'") d
|                  else e
> let xx = var "x" (undefined :: Int)
> let yy = var "y" (undefined :: Int)
> let xx -+- yy = value "+" ((+) :: Int->Int->Int) :$ xx :$ yy

Then:

> xx -+- yy
x + y :: Int
> primeify xx
x' :: Int
> mapVars primeify $ xx -+- yy
x' + y' :: Int
> mapVars (primeify . primeify) $ xx -+- yy
x'' + y'' :: Int

Given that the argument function is O(m), this function is O(n*m).

mapConsts :: (Expr -> Expr) -> Expr -> Expr Source #

O(n*m). Applies a function to all terminal constants in an expression.

Given that:

> let one   = val (1 :: Int)
> let two   = val (2 :: Int)
> let xx -+- yy = value "+" ((+) :: Int->Int->Int) :$ xx :$ yy
> let intToZero e = if typ e == typ zero then zero else e

Then:

> one -+- (two -+- xx)
1 + (2 + x) :: Int
> mapConsts intToZero (one -+- (two -+- xx))
0 + (0 + x) :: Integer

Given that the argument function is O(m), this function is O(n*m).

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

O(n*m). Substitute subexpressions of an expression using the given function. Outer expressions have more precedence than inner expressions. (cf. //)

With:

> let xx = var "x" (undefined :: Int)
> let yy = var "y" (undefined :: Int)
> let zz = var "z" (undefined :: Int)
> let plus = value "+" ((+) :: Int->Int->Int)
> let times = value "*" ((*) :: Int->Int->Int)
> let xx -+- yy = plus :$ xx :$ yy
> let xx -*- yy = times :$ xx :$ yy
> let pluswap (o :$ xx :$ yy) | o == plus = Just $ o :$ yy :$ xx
|     pluswap _                           = Nothing

Then:

> mapSubexprs pluswap $ (xx -*- yy) -+- (yy -*- zz)
y * z + x * y :: Int
> mapSubexprs pluswap $ (xx -+- yy) -*- (yy -+- zz)
(y + x) * (z + y) :: Int

Substitutions do not stack, in other words a replaced expression or its subexpressions are not further replaced:

> mapSubexprs pluswap $ (xx -+- yy) -+- (yy -+- zz)
(y + z) + (x + y) :: Int

Given that the argument function is O(m), this function is O(n*m).

(//-) :: Expr -> [(Expr, Expr)] -> Expr Source #

O(n*m). Substitute occurrences of values in an expression from the given list of substitutions. (cf. mapValues)

Given that:

> let xx = var "x" (undefined :: Int)
> let yy = var "y" (undefined :: Int)
> let zz = var "z" (undefined :: Int)
> let xx -+- yy = value "+" ((+) :: Int->Int->Int) :$ xx :$ yy

Then:

> ((xx -+- yy) -+- (yy -+- zz)) //- [(xx, yy), (zz, yy)]
(y + y) + (y + y) :: Int
> ((xx -+- yy) -+- (yy -+- zz)) //- [(yy, yy -+- zz)]
(x + (y + z)) + ((y + z) + z) :: Int

This function does not work for substituting non-terminal subexpressions:

> (xx -+- yy) //- [(xx -+- yy, zz)]
x + y :: Int

Please use the slower // if you want the above replacement to work.

Replacement happens only once:

> xx //- [(xx,yy), (yy,zz)]
y :: Int

Given that the argument list has length m, this function is O(n*m).

(//) :: Expr -> [(Expr, Expr)] -> Expr Source #

O(n*n*m). Substitute subexpressions in an expression from the given list of substitutions. (cf. mapSubexprs).

Please consider using //- if you are replacing just terminal values as it is faster.

Given that:

> let xx = var "x" (undefined :: Int)
> let yy = var "y" (undefined :: Int)
> let zz = var "z" (undefined :: Int)
> let xx -+- yy = value "+" ((+) :: Int->Int->Int) :$ xx :$ yy

Then:

> ((xx -+- yy) -+- (yy -+- zz)) // [(xx -+- yy, yy), (yy -+- zz, yy)]
y + y :: Int
> ((xx -+- yy) -+- zz) // [(xx -+- yy, zz), (zz, xx -+- yy)]
z + (x + y) :: Int

Replacement happens only once with outer expressions having more precedence than inner expressions.

> (xx -+- yy) // [(yy,xx), (xx -+- yy,zz), (zz,xx)]
z :: Int

Given that the argument list has length m, this function is O(n*n*m). Remember that since n is the size of an expression, comparing two expressions is O(n) in the worst case, and we may need to compare with n subexpressions in the worst case.

renameVarsBy :: (String -> String) -> Expr -> Expr Source #

Rename variables in an Expr.

> renameVarsBy (++ "'") (xx -+- yy)
x' + y' :: Int
> renameVarsBy (++ "'") (yy -+- (zz -+- xx))
(y' + (z' + x')) :: Int
> renameVarsBy (++ "1") (abs' xx)
abs x1 :: Int
> renameVarsBy (++ "2") $ abs' (xx -+- yy)
abs (x2 + y2) :: Int

NOTE: this will affect holes!

Variables and holes

Creating variables

varAsTypeOf :: String -> Expr -> Expr Source #

O(1). Creates a variable with the same type as the given Expr.

> let one = val (1::Int)
> "x" `varAsTypeOf` one
x :: Int
> "p" `varAsTypeOf` val False
p :: Bool

listVars :: Typeable a => String -> a -> [Expr] Source #

Generate an infinite list of variables based on a template and a given type. (cf. listVarsAsTypeOf)

> putL 10 $ listVars "x" (undefined :: Int)
[ x :: Int
, y :: Int
, z :: Int
, x' :: Int
, y' :: Int
, z' :: Int
, x'' :: Int
, ...
]
> putL 10 $ listVars "p" (undefined :: Bool)
[ p :: Bool
, q :: Bool
, r :: Bool
, p' :: Bool
, q' :: Bool
, r' :: Bool
, p'' :: Bool
, ...
]

listVarsAsTypeOf :: String -> Expr -> [Expr] Source #

Generate an infinite list of variables based on a template and the type of a given Expr. (cf. listVars)

> let one = val (1::Int)
> putL 10 $ "x" `listVarsAsTypeOf` one
[ x :: Int
, y :: Int
, z :: Int
, x' :: Int
, ...
]
> let false = val False
> putL 10 $ "p" `listVarsAsTypeOf` false
[ p :: Bool
, q :: Bool
, r :: Bool
, p' :: Bool
, ...
]

Typed holes

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

O(1). Creates an Expr representing a typed hole of the given argument type.

> hole (undefined :: Int)
_ :: Int
> hole (undefined :: Maybe String)
_ :: Maybe [Char]

A hole is represented as a variable with no name or a value named "_":

hole x = var "" x
hole x = value "_" x

isHole :: Expr -> Bool Source #

O(1). Checks if an Expr represents a typed hole. (cf. hole)

> isHole $ hole (undefined :: Int)
True
> isHole $ value "not" not :$ val True
False
> isHole $ val 'a'
False

holes :: Expr -> [Expr] Source #

O(n). Lists all holes in an expression, in order and with repetitions. (cf. nubHoles)

> holes $ hole (undefined :: Bool)
[_ :: Bool]
> holes $ value "&&" (&&) :$ hole (undefined :: Bool) :$ hole (undefined :: Bool)
[_ :: Bool,_ :: Bool]
> holes $ hole (undefined :: Bool->Bool) :$ hole (undefined::Bool)
[_ :: Bool -> Bool,_ :: Bool]

nubHoles :: Expr -> [Expr] Source #

O(n^2). Lists all holes in an expression without repetitions. (cf. holes)

> nubHoles $ hole (undefined :: Bool)
[_ :: Bool]
> nubHoles $ value "&&" (&&) :$ hole (undefined :: Bool) :$ hole (undefined :: Bool)
[_ :: Bool]
> nubHoles $ hole (undefined :: Bool->Bool) :$ hole (undefined::Bool)
[_ :: Bool,_ :: Bool -> Bool]

Runtime averages to O(n log n) on evenly distributed expressions such as (f x + g y) + (h z + f w); and to O(n^2) on deep expressions such as f (g (h (f (g (h x))))).

holeAsTypeOf :: Expr -> Expr Source #

O(1). Creates an Expr representing a typed hole with the type of the given Expr. (cf. hole)

> val (1::Int)
1 :: Int
> holeAsTypeOf $ val (1::Int)
_ :: Int

fill :: Expr -> [Expr] -> Expr Source #

Fill holes in an expression with the given list.

> let i_  =  hole (undefined :: Int)
> let e1 -+- e2  =  value "+" ((+) :: Int -> Int -> Int) :$ e1 :$ e2
> let xx  =  var "x" (undefined :: Int)
> let yy  =  var "y" (undefined :: Int)
> fill (i_ -+- i_) [xx, yy]
x + y :: Int
> fill (i_ -+- i_) [xx, xx]
x + x :: Int
> let one  =  val (1::Int)
> fill (i_ -+- i_) [one, one -+- one]
1 + (1 + 1) :: Int

This function silently remaining expressions:

> fill i_ [xx, yy]
x :: Int

This function silently keeps remaining holes:

> fill (i_ -+- i_ -+- i_) [xx, yy]
(x + y) + _ :: Int

This function silently skips remaining holes if one is not of the right type:

> fill (i_ -+- i_ -+- i_) [xx, val 'c', yy]
(x + _) + _ :: Int

Juggling Exprs

Folding Exprs

fold :: [Expr] -> Expr Source #

O(n). Folds a list of Exprs into a single Expr. (cf. unfold)

This always generates an ill-typed expression.

fold [val False, val True, val (1::Int)]
[False,True,1] :: ill-typed # ExprList $ Bool #

This is useful when applying transformations on lists of Exprs, such as canonicalize, mapValues or canonicalVariations.

> let ii = var "i" (undefined::Int)
> let kk = var "k" (undefined::Int)
> let qq = var "q" (undefined::Bool)
> let notE = value "not" not
> unfold . canonicalize . fold $ [ii,kk,notE :$ qq, notE :$ val False]
[x :: Int,y :: Int,not p :: Bool,not False :: Bool]

unfold :: Expr -> [Expr] Source #

O(n). Unfolds an Expr representing a list into a list of Exprs. This reverses the effect of fold.

> expr [1,2,3::Int]
[1,2,3] :: [Int]
> unfold $ expr [1,2,3::Int]
[1 :: Int,2 :: Int,3 :: Int]

foldPair :: (Expr, Expr) -> Expr Source #

O(1). Folds a pair of Expr values into a single Expr. (cf. unfoldPair)

This always generates an ill-typed expression.

> foldPair (val False, val (1::Int))
(False,1) :: ill-typed # ExprPair $ Bool #
> foldPair (val (0::Int), val True)
(0,True) :: ill-typed # ExprPair $ Int #

This is useful when applying transformations on pairs of Exprs, such as canonicalize, mapValues or canonicalVariations.

> let ii = var "i" (undefined::Int)
> let kk = var "k" (undefined::Int)
> unfoldPair $ canonicalize $ foldPair (ii,kk)
(x :: Int,y :: Int)

unfoldPair :: Expr -> (Expr, Expr) Source #

O(1). Unfolds an Expr representing a pair. This reverses the effect of foldPair.

> value "," ((,) :: Bool->Bool->(Bool,Bool)) :$ val True :$ val False
(True,False) :: (Bool,Bool)
> unfoldPair $ value "," ((,) :: Bool->Bool->(Bool,Bool)) :$ val True :$ val False
(True :: Bool,False :: Bool)

foldApp :: [Expr] -> Expr Source #

O(n). Folds a list of Expr with function application (:$). This reverses the effect of unfoldApp.

foldApp [e0]           =  e0
foldApp [e0,e1]        =  e0 :$ e1
foldApp [e0,e1,e2]     =  e0 :$ e1 :$ e2
foldApp [e0,e1,e2,e3]  =  e0 :$ e1 :$ e2 :$ e3

Remember :$ is left-associative, so:

foldApp [e0]           =    e0
foldApp [e0,e1]        =   (e0 :$ e1)
foldApp [e0,e1,e2]     =  ((e0 :$ e1) :$ e2)
foldApp [e0,e1,e2,e3]  = (((e0 :$ e1) :$ e2) :$ e3)

This function may produce an ill-typed expression.

unfoldApp :: Expr -> [Expr] Source #

O(n). Unfold a function application Expr into a list of function and arguments.

unfoldApp $ e0                    =  [e0]
unfoldApp $ e0 :$ e1              =  [e0,e1]
unfoldApp $ e0 :$ e1 :$ e2        =  [e0,e1,e2]
unfoldApp $ e0 :$ e1 :$ e2 :$ e3  =  [e0,e1,e2,e3]

Remember :$ is left-associative, so:

unfoldApp e0                          =  [e0]
unfoldApp (e0 :$ e1)                  =  [e0,e1]
unfoldApp ((e0 :$ e1) :$ e2)          =  [e0,e1,e2]
unfoldApp (((e0 :$ e1) :$ e2) :$ e3)  =  [e0,e1,e2,e3]

Canonicalizing Exprs

canonicalize :: Expr -> Expr Source #

Canonicalizes an Expr so that variable names appear in order. Variable names are taken from the preludeNameInstances.

> canonicalize (xx -+- yy)
x + y :: Int
> canonicalize (yy -+- xx)
x + y :: Int
> canonicalize (xx -+- xx)
x + x :: Int
> canonicalize (yy -+- yy)
x + x :: Int

Constants are untouched:

> canonicalize (jj -+- (zero -+- abs' ii))
x + (y + abs y) :: Int

This also works for variable functions:

> canonicalize (gg yy -+- ff xx -+- gg xx)
(f x + g y) + f y :: Int

canonicalizeWith :: (Expr -> [String]) -> Expr -> Expr Source #

Like canonicalize but allows customization of the list of variable names. (cf. lookupNames, variableNamesFromTemplate)

> canonicalizeWith (const ["i","j","k","l",...]) (xx -+- yy)
i + j :: Int

The argument Expr of the argument function allows to provide a different list of names for different types:

> let namesFor e
>   | typ e == typeOf (undefined::Char) = variableNamesFromTemplate "c1"
>   | typ e == typeOf (undefined::Int)  = variableNamesFromTemplate "i"
>   | otherwise                         = variableNamesFromTemplate "x"
> canonicalizeWith namesFor ((xx -+- ord' dd) -+- (ord' cc -+- yy))
(i + ord c1) + (ord c2 + j) :: Int

canonicalization :: Expr -> [(Expr, Expr)] Source #

Return a canonicalization of an Expr that makes variable names appear in order using names as provided by preludeNameInstances. By using //- it can canonicalize Exprs.

> canonicalization (gg yy -+- ff xx -+- gg xx)
[ (x :: Int,        y :: Int)
, (f :: Int -> Int, g :: Int -> Int)
, (y :: Int,        x :: Int)
, (g :: Int -> Int, f :: Int -> Int) ]
> canonicalization (yy -+- xx -+- yy)
[ (x :: Int, y :: Int)
, (y :: Int, x :: Int) ]

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

Like canonicalization but allows customization of the list of variable names. (cf. lookupNames, variableNamesFromTemplate)

isCanonical :: Expr -> Bool Source #

Returns whether an Expr is canonical: if applying canonicalize is an identity using names as provided by preludeNameInstances.

isCanonicalWith :: (Expr -> [String]) -> Expr -> Bool Source #

Like isCanonical but allows specifying the list of variable names.

canonicalVariations :: Expr -> [Expr] Source #

Returns all canonical variations of an Expr by filling holes with variables. Where possible, variations are listed from most general to least general.

> canonicalVariations $ i_
[x :: Int]
> canonicalVariations $ i_ -+- i_
[ x + y :: Int
, x + x :: Int ]
> canonicalVariations $ i_ -+- i_ -+- i_
[ (x + y) + z :: Int
, (x + y) + x :: Int
, (x + y) + y :: Int
, (x + x) + y :: Int
, (x + x) + x :: Int ]
> canonicalVariations $ i_ -+- ord' c_
[x + ord c :: Int]
> canonicalVariations $ i_ -+- i_ -+- ord' c_
[ (x + y) + ord c :: Int
, (x + x) + ord c :: Int ]
> canonicalVariations $ i_ -+- i_ -+- length' (c_ -:- unit c_)
[ (x + y) + length (c:d:"") :: Int
, (x + y) + length (c:c:"") :: Int
, (x + x) + length (c:d:"") :: Int
, (x + x) + length (c:c:"") :: Int ]

In an expression without holes this functions just returns a singleton list with the expression itself:

> canonicalVariations $ val (0 :: Int)
[0 :: Int]
> canonicalVariations $ ord' bee
[ord 'b' :: Int]

When applying this to expressions already containing variables new variables are introduced so name clashes are avoided:

> canonicalVariations $ i_ -+- ii -+- jj -+- i_
[ x + y + z + x' :: Int
, x + y + z + x :: Int ]
> canonicalVariations $ ii -+- jj
[x + y :: Int]
> canonicalVariations $ xx -+- i_ -+- i_ -+- length' (c_ -:- unit c_) -+- yy
[ (((x + y) + z) + length (c:d:"")) + x' :: Int
, (((x + y) + z) + length (c:c:"")) + x' :: Int
, (((x + y) + y) + length (c:d:"")) + z :: Int
, (((x + y) + y) + length (c:c:"")) + z :: Int
]

mostGeneralCanonicalVariation :: Expr -> Expr Source #

Returns the most general canonical variation of an Expr by filling holes with variables.

> mostGeneralCanonicalVariation $ i_
x :: Int
> mostGeneralCanonicalVariation $ i_ -+- i_
x + y :: Int
> mostGeneralCanonicalVariation $ i_ -+- i_ -+- i_
(x + y) + z :: Int
> mostGeneralCanonicalVariation $ i_ -+- ord' c_
x + ord c :: Int
> mostGeneralCanonicalVariation $ i_ -+- i_ -+- ord' c_
(x + y) + ord c :: Int
> mostGeneralCanonicalVariation $ i_ -+- i_ -+- length' (c_ -:- unit c_)
(x + y) + length (c:d:"") :: Int

In an expression without holes this functions just returns the given expression itself:

> mostGeneralCanonicalVariation $ val (0 :: Int)
0 :: Int
> mostGeneralCanonicalVariation $ ord' bee
ord 'b' :: Int

This function is the same as taking the head of canonicalVariations but a bit faster.

mostSpecificCanonicalVariation :: Expr -> Expr Source #

Returns the most specific canonical variation of an Expr by filling holes with variables.

> mostSpecificCanonicalVariation $ i_
x :: Int
> mostSpecificCanonicalVariation $ i_ -+- i_
x + x :: Int
> mostSpecificCanonicalVariation $ i_ -+- i_ -+- i_
(x + x) + x :: Int
> mostSpecificCanonicalVariation $ i_ -+- ord' c_
x + ord c :: Int
> mostSpecificCanonicalVariation $ i_ -+- i_ -+- ord' c_
(x + x) + ord c :: Int
> mostSpecificCanonicalVariation $ i_ -+- i_ -+- length' (c_ -:- unit c_)
(x + x) + length (c:c:"") :: Int

In an expression without holes this functions just returns the given expression itself:

> mostSpecificCanonicalVariation $ val (0 :: Int)
0 :: Int
> mostSpecificCanonicalVariation $ ord' bee
ord 'b' :: Int

This function is the same as taking the last of canonicalVariations but a bit faster.

fastCanonicalVariations :: Expr -> [Expr] Source #

A faster version of canonicalVariations that disregards name clashes across different types. Results are confusing to the user but fine for Express which differentiates between variables with the same name but different types.

Without applying canonicalize, the following Expr may seem to have only one variable:

> fastCanonicalVariations $ i_ -+- ord' c_
[x + ord x :: Int]

Where in fact it has two, as the second x has a different type. Applying canonicalize disambiguates:

> map canonicalize . fastCanonicalVariations $ i_ -+- ord' c_
[x + ord c :: Int]

This function is useful when resulting Exprs are not intended to be presented to the user but instead to be used by another function. It is simply faster to skip the step where clashes are resolved.

fastMostGeneralVariation :: Expr -> Expr Source #

A faster version of mostGeneralCanonicalVariation that disregards name clashes across different types. Consider using mostGeneralCanonicalVariation instead.

The same caveats of fastCanonicalVariations do apply here.

fastMostSpecificVariation :: Expr -> Expr Source #

A faster version of mostSpecificCanonicalVariation that disregards name clashes across different types. Consider using mostSpecificCanonicalVariation instead.

The same caveats of fastCanonicalVariations do apply here.

Matching Exprs

match :: Expr -> Expr -> Maybe [(Expr, Expr)] Source #

Given two expressions, returns a Just list of matches of subexpressions of the first expressions to variables in the second expression. Returns Nothing when there is no match.

> let zero = val (0::Int)
> let one  = val (1::Int)
> let xx   = var "x" (undefined :: Int)
> let yy   = var "y" (undefined :: Int)
> let e1 -+- e2  =  value "+" ((+)::Int->Int->Int) :$ e1 :$ e2
> (zero -+- one) `match` (xx -+- yy)
Just [(y :: Int,1 :: Int),(x :: Int,0 :: Int)]
> (zero -+- (one -+- two)) `match` (xx -+- yy)
Just [(y :: Int,1 + 2 :: Int),(x :: Int,0 :: Int)]
> (zero -+- (one -+- two)) `match` (xx -+- (yy -+- yy))
Nothing

In short:

          (zero -+- one) `match` (xx -+- yy)           =  Just [(xx,zero), (yy,one)]
(zero -+- (one -+- two)) `match` (xx -+- yy)           =  Just [(xx,zero), (yy,one-+-two)]
(zero -+- (one -+- two)) `match` (xx -+- (yy -+- yy))  =  Nothing

matchWith :: [(Expr, Expr)] -> Expr -> Expr -> Maybe [(Expr, Expr)] Source #

Like match but allowing predefined bindings.

matchWith [(xx,zero)] (zero -+- one) (xx -+- yy)  =  Just [(xx,zero), (yy,one)]
matchWith [(xx,one)]  (zero -+- one) (xx -+- yy)  =  Nothing

isInstanceOf :: Expr -> Expr -> Bool Source #

Given two Exprs, checks if the first expression is an instance of the second in terms of variables. (cf. hasInstanceOf)

> let zero = val (0::Int)
> let one  = val (1::Int)
> let xx   = var "x" (undefined :: Int)
> let yy   = var "y" (undefined :: Int)
> let e1 -+- e2  =  value "+" ((+)::Int->Int->Int) :$ e1 :$ e2
 one `isInstanceOf` one   =  True
  xx `isInstanceOf` xx    =  True
  yy `isInstanceOf` xx    =  True
zero `isInstanceOf` xx    =  True
  xx `isInstanceOf` zero  =  False
 one `isInstanceOf` zero  =  False
  (xx -+- (yy -+- xx)) `isInstanceOf`   (xx -+- yy)  =  True
  (yy -+- (yy -+- xx)) `isInstanceOf`   (xx -+- yy)  =  True
(zero -+- (yy -+- xx)) `isInstanceOf` (zero -+- yy)  =  True
 (one -+- (yy -+- xx)) `isInstanceOf` (zero -+- yy)  =  False

hasInstanceOf :: Expr -> Expr -> Bool Source #

Checks if any of the subexpressions of the first argument Expr is an instance of the second argument Expr.

isSubexprOf :: Expr -> Expr -> Bool Source #

O(n^2). Checks if an Expr is a subexpression of another.

> (xx -+- yy) `isSubexprOf` (zz -+- (xx -+- yy))
True
> (xx -+- yy) `isSubexprOf` abs' (yy -+- xx)
False
> xx `isSubexprOf` yy
False

Typeclasses

The Express typeclass

class Typeable a => Express a where Source #

Express typeclass instances provide an expr function that allows values to be deeply encoded as applications of Exprs.

expr False  =  val False
expr (Just True)  =  value "Just" (Just :: Bool -> Maybe Bool) :$ val True

The function expr can be contrasted with the function val:

  • val always encodes values as atomic Value Exprs -- shallow encoding.
  • expr ideally encodes expressions as applications (:$) between Value Exprs -- deep encoding.

Depending on the situation, one or the other may be desirable.

Instances can be automatically derived using the TH function deriveExpress.

The following example shows a datatype and its instance:

data Stack a = Stack a (Stack a) | Empty
instance Express a => Express (Stack a) where
  expr s@(Stack x y) = value "Stack" (Stack ->>: s) :$ expr x :$ expr y
  expr s@Empty       = value "Empty" (Empty   -: s)

To declare expr it may be useful to use auxiliary type binding operators: -:, ->:, ->>:, ->>>:, ->>>>:, ->>>>>:, ...

For types with atomic values, just declare expr = val

Methods

expr :: a -> Expr Source #

Instances

Instances details
Express Bool Source # 
Instance details

Defined in Data.Express.Express

Methods

expr :: Bool -> Expr Source #

Express Char Source # 
Instance details

Defined in Data.Express.Express

Methods

expr :: Char -> Expr Source #

Express Int Source # 
Instance details

Defined in Data.Express.Express

Methods

expr :: Int -> Expr Source #

Express Integer Source # 
Instance details

Defined in Data.Express.Express

Methods

expr :: Integer -> Expr Source #

Express Ordering Source # 
Instance details

Defined in Data.Express.Express

Methods

expr :: Ordering -> Expr Source #

Express () Source # 
Instance details

Defined in Data.Express.Express

Methods

expr :: () -> Expr Source #

Express a => Express [a] Source # 
Instance details

Defined in Data.Express.Express

Methods

expr :: [a] -> Expr Source #

Express a => Express (Maybe a) Source # 
Instance details

Defined in Data.Express.Express

Methods

expr :: Maybe a -> Expr Source #

(Integral a, Show a, Express a) => Express (Ratio a) Source # 
Instance details

Defined in Data.Express.Express

Methods

expr :: Ratio a -> Expr Source #

(Express a, Express b) => Express (Either a b) Source # 
Instance details

Defined in Data.Express.Express

Methods

expr :: Either a b -> Expr Source #

(Express a, Express b) => Express (a, b) Source # 
Instance details

Defined in Data.Express.Express

Methods

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

(Express a, Express b, Express c) => Express (a, b, c) Source # 
Instance details

Defined in Data.Express.Express

Methods

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

(Express a, Express b, Express c, Express d) => Express (a, b, c, d) Source # 
Instance details

Defined in Data.Express.Express

Methods

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

(Express a, Express b, Express c, Express d, Express e) => Express (a, b, c, d, e) Source # 
Instance details

Defined in Data.Express.Express

Methods

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

(Express a, Express b, Express c, Express d, Express e, Express f) => Express (a, b, c, d, e, f) Source # 
Instance details

Defined in Data.Express.Express

Methods

expr :: (a, b, c, d, e, f) -> Expr Source #

(Express a, Express b, Express c, Express d, Express e, Express f, Express g) => Express (a, b, c, d, e, f, g) Source # 
Instance details

Defined in Data.Express.Express

Methods

expr :: (a, b, c, d, e, f, g) -> Expr Source #

(Express a, Express b, Express c, Express d, Express e, Express f, Express g, Express h) => Express (a, b, c, d, e, f, g, h) Source # 
Instance details

Defined in Data.Express.Express

Methods

expr :: (a, b, c, d, e, f, g, h) -> Expr Source #

(Express a, Express b, Express c, Express d, Express e, Express f, Express g, Express h, Express i) => Express (a, b, c, d, e, f, g, h, i) Source # 
Instance details

Defined in Data.Express.Express

Methods

expr :: (a, b, c, d, e, f, g, h, i) -> Expr Source #

(Express a, Express b, Express c, Express d, Express e, Express f, Express g, Express h, Express i, Express j) => Express (a, b, c, d, e, f, g, h, i, j) Source # 
Instance details

Defined in Data.Express.Express

Methods

expr :: (a, b, c, d, e, f, g, h, i, j) -> Expr Source #

(Express a, Express b, Express c, Express d, Express e, Express f, Express g, Express h, Express i, Express j, Express k) => Express (a, b, c, d, e, f, g, h, i, j, k) Source # 
Instance details

Defined in Data.Express.Express

Methods

expr :: (a, b, c, d, e, f, g, h, i, j, k) -> Expr Source #

(Express a, Express b, Express c, Express d, Express e, Express f, Express g, Express h, Express i, Express j, Express k, Express l) => Express (a, b, c, d, e, f, g, h, i, j, k, l) Source # 
Instance details

Defined in Data.Express.Express

Methods

expr :: (a, b, c, d, e, f, g, h, i, j, k, l) -> Expr Source #

deriveExpress :: Name -> DecsQ Source #

Derives an Express instance for the given type Name.

This function needs the TemplateHaskell extension.

If -:, ->:, ->>:, ->>>:, ... are not in scope, this will derive them as well.

deriveExpressCascading :: Name -> DecsQ Source #

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

deriveExpressIfNeeded :: Name -> DecsQ Source #

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

The Name typeclass

class Name a where Source #

If we were to come up with a variable name for the given type what name would it be?

An instance for a given type Ty is simply given by:

instance Name Ty where name _ = "x"

Examples:

> name (undefined :: Int)
"x"
> name (undefined :: Bool)
"p"
> name (undefined :: [Int])
"xs"

This is then used to generate an infinite list of variable names:

> names (undefined :: Int)
["x", "y", "z", "x'", "y'", "z'", "x''", "y''", "z''", ...]
> names (undefined :: Bool)
["p", "q", "r", "p'", "q'", "r'", "p''", "q''", "r''", ...]
> names (undefined :: [Int])
["xs", "ys", "zs", "xs'", "ys'", "zs'", "xs''", "ys''", ...]

Minimal complete definition

Nothing

Methods

name :: a -> String Source #

O(1).

Returns a name for a variable of the given argument's type.

> name (undefined :: Int)
"x"
> name (undefined :: [Bool])
"ps"
> name (undefined :: [Maybe Integer])
"mxs"

The default definition is:

name _ = "x"

Instances

Instances details
Name Bool Source #
name (undefined :: Bool) = "p"
names (undefined :: Bool) = ["p", "q", "r", "p'", "q'", ...]
Instance details

Defined in Data.Express.Name

Methods

name :: Bool -> String Source #

Name Char Source #
name (undefined :: Char) = "c"
names (undefined :: Char) = ["c", "d", "e", "c'", "d'", ...]
Instance details

Defined in Data.Express.Name

Methods

name :: Char -> String Source #

Name Double Source #
name (undefined :: Double) = "x"
names (undefined :: Double) = ["x", "y", "z", "x'", ...]
Instance details

Defined in Data.Express.Name

Methods

name :: Double -> String Source #

Name Float Source #
name (undefined :: Float) = "x"
names (undefined :: Float) = ["x", "y", "z", "x'", ...]
Instance details

Defined in Data.Express.Name

Methods

name :: Float -> String Source #

Name Int Source #
name (undefined :: Int) = "x"
names (undefined :: Int) = ["x", "y", "z", "x'", "y'", ...]
Instance details

Defined in Data.Express.Name

Methods

name :: Int -> String Source #

Name Integer Source #
name (undefined :: Integer) = "x"
names (undefined :: Integer) = ["x", "y", "z", "x'", ...]
Instance details

Defined in Data.Express.Name

Methods

name :: Integer -> String Source #

Name Ordering Source #
name (undefined :: Ordering) = "o"
names (undefined :: Ordering) = ["o", "p", "q", "o'", ...]
Instance details

Defined in Data.Express.Name

Methods

name :: Ordering -> String Source #

Name Word Source # 
Instance details

Defined in Data.Express.Name

Methods

name :: Word -> String Source #

Name () Source #
name (undefined :: ()) = "u"
names (undefined :: ()) = ["u", "v", "w", "u'", "v'", ...]
Instance details

Defined in Data.Express.Name

Methods

name :: () -> String Source #

Name a => Name [a] Source #
names (undefined :: [Int]) = ["xs", "ys", "zs", "xs'", ...]
names (undefined :: [Bool]) = ["ps", "qs", "rs", "ps'", ...]
Instance details

Defined in Data.Express.Name

Methods

name :: [a] -> String Source #

Name a => Name (Maybe a) Source #
names (undefined :: Maybe Int) = ["mx", "mx1", "mx2", ...]
nemes (undefined :: Maybe Bool) = ["mp", "mp1", "mp2", ...]
Instance details

Defined in Data.Express.Name

Methods

name :: Maybe a -> String Source #

Name (Ratio a) Source #
name (undefined :: Rational) = "q"
names (undefined :: Rational) = ["q", "r", "s", "q'", ...]
Instance details

Defined in Data.Express.Name

Methods

name :: Ratio a -> String Source #

Name (a -> b) Source #
names (undefined :: ()->()) = ["f", "g", "h", "f'", ...]
names (undefined :: Int->Int) = ["f", "g", "h", ...]
Instance details

Defined in Data.Express.Name

Methods

name :: (a -> b) -> String Source #

(Name a, Name b) => Name (Either a b) Source #
names (undefined :: Either Int Int) = ["exy", "exy1", ...]
names (undefined :: Either Int Bool) = ["exp", "exp1", ...]
Instance details

Defined in Data.Express.Name

Methods

name :: Either a b -> String Source #

(Name a, Name b) => Name (a, b) Source #
names (undefined :: (Int,Int)) = ["xy", "zw", "xy'", ...]
names (undefined :: (Bool,Bool)) = ["pq", "rs", "pq'", ...]
Instance details

Defined in Data.Express.Name

Methods

name :: (a, b) -> String Source #

(Name a, Name b, Name c) => Name (a, b, c) Source #
names (undefined :: (Int,Int,Int)) = ["xyz","uvw", ...]
names (undefined :: (Int,Bool,Char)) = ["xpc", "xpc1", ...]
Instance details

Defined in Data.Express.Name

Methods

name :: (a, b, c) -> String Source #

(Name a, Name b, Name c, Name d) => Name (a, b, c, d) Source #
names (undefined :: ((),(),(),())) = ["uuuu", "uuuu1", ...]
names (undefined :: (Int,Int,Int,Int)) = ["xxxx", ...]
Instance details

Defined in Data.Express.Name

Methods

name :: (a, b, c, d) -> String Source #

(Name a, Name b, Name c, Name d, Name e) => Name (a, b, c, d, e) Source # 
Instance details

Defined in Data.Express.Name

Methods

name :: (a, b, c, d, e) -> String Source #

(Name a, Name b, Name c, Name d, Name e, Name f) => Name (a, b, c, d, e, f) Source # 
Instance details

Defined in Data.Express.Name

Methods

name :: (a, b, c, d, e, f) -> String Source #

(Name a, Name b, Name c, Name d, Name e, Name f, Name g) => Name (a, b, c, d, e, f, g) Source # 
Instance details

Defined in Data.Express.Name

Methods

name :: (a, b, c, d, e, f, g) -> String Source #

(Name a, Name b, Name c, Name d, Name e, Name f, Name g, Name h) => Name (a, b, c, d, e, f, g, h) Source # 
Instance details

Defined in Data.Express.Name

Methods

name :: (a, b, c, d, e, f, g, h) -> String Source #

(Name a, Name b, Name c, Name d, Name e, Name f, Name g, Name h, Name i) => Name (a, b, c, d, e, f, g, h, i) Source # 
Instance details

Defined in Data.Express.Name

Methods

name :: (a, b, c, d, e, f, g, h, i) -> String Source #

(Name a, Name b, Name c, Name d, Name e, Name f, Name g, Name h, Name i, Name j) => Name (a, b, c, d, e, f, g, h, i, j) Source # 
Instance details

Defined in Data.Express.Name

Methods

name :: (a, b, c, d, e, f, g, h, i, j) -> String Source #

(Name a, Name b, Name c, Name d, Name e, Name f, Name g, Name h, Name i, Name j, Name k) => Name (a, b, c, d, e, f, g, h, i, j, k) Source # 
Instance details

Defined in Data.Express.Name

Methods

name :: (a, b, c, d, e, f, g, h, i, j, k) -> String Source #

(Name a, Name b, Name c, Name d, Name e, Name f, Name g, Name h, Name i, Name j, Name k, Name l) => Name (a, b, c, d, e, f, g, h, i, j, k, l) Source # 
Instance details

Defined in Data.Express.Name

Methods

name :: (a, b, c, d, e, f, g, h, i, j, k, l) -> String Source #

names :: Name a => a -> [String] Source #

Returns na infinite list of variable names from the given type: the result of variableNamesFromTemplate after name.

> names (undefined :: Int)
["x", "y", "z", "x'", "y'", "z'", "x''", "y''", "z''", ...]
> names (undefined :: Bool)
["p", "q", "r", "p'", "q'", "r'", "p''", "q''", "r''", ...]
> names (undefined :: [Int])
["xs", "ys", "zs", "xs'", "ys'", "zs'", "xs''", "ys''", ...]

variableNamesFromTemplate :: String -> [String] Source #

Returns an infinite list of variable names based on the given template.

> variableNamesFromTemplate "x"
["x", "y", "z", "x'", "y'", ...]
> variableNamesFromTemplate "p"
["p", "q", "r", "p'", "q'", ...]
> variableNamesFromTemplate "xy"
["xy", "zw", "xy'", "zw'", "xy''", ...]

deriveName :: Name -> DecsQ Source #

Derives a Name instance for the given type Name.

This function needs the TemplateHaskell extension.

deriveNameCascading :: Name -> DecsQ Source #

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

deriveNameIfNeeded :: Name -> DecsQ Source #

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

Typeclass instances as Exprs

reifyEq :: (Typeable a, Eq a) => a -> [Expr] Source #

O(1). Reifies an Eq instance into a list of Exprs. The list will contain == and /= for the given type. (cf. mkEq, mkEquation)

> reifyEq (undefined :: Int)
[ (==) :: Int -> Int -> Bool
, (/=) :: Int -> Int -> Bool ]
> reifyEq (undefined :: Bool)
[ (==) :: Bool -> Bool -> Bool
, (/=) :: Bool -> Bool -> Bool ]
> reifyEq (undefined :: String)
[ (==) :: [Char] -> [Char] -> Bool
, (/=) :: [Char] -> [Char] -> Bool ]

reifyOrd :: (Typeable a, Ord a) => a -> [Expr] Source #

O(1). Reifies an Ord instance into a list of Exprs. The list will contain compare, <= and < for the given type. (cf. mkOrd, mkOrdLessEqual, mkComparisonLE, mkComparisonLT)

> reifyOrd (undefined :: Int)
[ (<=) :: Int -> Int -> Bool
, (<) :: Int -> Int -> Bool ]
> reifyOrd (undefined :: Bool)
[ (<=) :: Bool -> Bool -> Bool
, (<) :: Bool -> Bool -> Bool ]
> reifyOrd (undefined :: [Bool])
[ (<=) :: [Bool] -> [Bool] -> Bool
, (<) :: [Bool] -> [Bool] -> Bool ]

reifyEqOrd :: (Typeable a, Ord a) => a -> [Expr] Source #

O(1). Reifies Eq and Ord instances into a list of Expr.

reifyName :: (Typeable a, Name a) => a -> [Expr] Source #

O(1). Reifies a Name instance into a list of Exprs. The list will contain name for the given type. (cf. mkName, lookupName, lookupNames)

> reifyName (undefined :: Int)
[name :: Int -> [Char]]
> reifyName (undefined :: Bool)
[name :: Bool -> [Char]]

mkEq :: Typeable a => (a -> a -> Bool) -> [Expr] Source #

O(1). Builds a reified Eq instance from the given == function. (cf. reifyEq)

> mkEq ((==) :: Int -> Int -> Bool)
[ (==) :: Int -> Int -> Bool
, (/=) :: Int -> Int -> Bool ]

mkOrd :: Typeable a => (a -> a -> Ordering) -> [Expr] Source #

O(1). Builds a reified Ord instance from the given compare function. (cf. reifyOrd, mkOrdLessEqual)

mkOrdLessEqual :: Typeable a => (a -> a -> Bool) -> [Expr] Source #

O(1). Builds a reified Ord instance from the given <= function. (cf. reifyOrd, mkOrd)

mkName :: Typeable a => (a -> String) -> [Expr] Source #

O(1). Builds a reified Name instance from the given name function. (cf. reifyName, mkNameWith)

mkNameWith :: Typeable a => String -> a -> [Expr] Source #

O(1). Builds a reified Name instance from the given String and type. (cf. reifyName, mkName)

isEq :: [Expr] -> Expr -> Bool Source #

O(n+m). Returns whether an Eq instance exists in the given instances list for the given Expr.

> isEq (reifyEqOrd (undefined :: Int)) (val (0::Int))
True
> isEq (reifyEqOrd (undefined :: Int)) (val ([[[0::Int]]]))
False

Given that the instances list has length m and that the given Expr has size n, this function is O(n+m).

isOrd :: [Expr] -> Expr -> Bool Source #

O(n+m). Returns whether an Ord instance exists in the given instances list for the given Expr.

> isOrd (reifyEqOrd (undefined :: Int)) (val (0::Int))
True
> isOrd (reifyEqOrd (undefined :: Int)) (val ([[[0::Int]]]))
False

Given that the instances list has length m and that the given Expr has size n, this function is O(n+m).

isEqOrd :: [Expr] -> Expr -> Bool Source #

O(n+m). Returns whether both Eq and Ord instance exist in the given list for the given Expr.

Given that the instances list has length m and that the given Expr has size n, this function is O(n+m).

isEqT :: [Expr] -> TypeRep -> Bool Source #

O(n). Returns whether an Eq instance exists in the given instances list for the given TypeRep.

> isEqT (reifyEqOrd (undefined :: Int)) (typeOf (undefined :: Int))
True
> isEqT (reifyEqOrd (undefined :: Int)) (typeOf (undefined :: [[[Int]]]))
False

Given that the instances list has length n, this function is O(n).

isOrdT :: [Expr] -> TypeRep -> Bool Source #

O(n). Returns whether an Ord instance exists in the given instances list for the given TypeRep.

> isOrdT (reifyEqOrd (undefined :: Int)) (typeOf (undefined :: Int))
True
> isOrdT (reifyEqOrd (undefined :: Int)) (typeOf (undefined :: [[[Int]]]))
False

Given that the instances list has length n, this function is O(n).

isEqOrdT :: [Expr] -> TypeRep -> Bool Source #

O(n). Returns whether both Eq and Ord instance exist in the given list for the given TypeRep.

Given that the instances list has length n, this function is O(n).