express-0.1.2: Dynamically-typed expressions involving applications and variables.

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

Data.Express.Fixtures

Contents

Description

Defines some Expr fixtures to facilitate testing and playing around on the REPL (GHCI).

  • Instead of having to write:

    > value "&&" (&&) :$ (value "not" not :$ val True) :$ val False
    not True && False :: Bool

    Using this module, we can just write:

    > not' true -&&- false
    not True && False :: Bool
  • Instead of having to write:

    > value "+" ((+)::Int->Int->Int) :$ (value "*" ((*)::Int->Int->Int) :$ var "x" (undefined::Int) :$ var "y" (undefined::Int)) :$ (value "*" ((*)::Int->Int->Int) :$ val (1::Int) :$ val (2::Int))
    x * y + 1 * 2 :: Int

    Using this module, we can just write:

    > xx -*- yy -+- one -*- two
    x * y + 1 * 2 :: Int
  • Instead of having to write:

    > value "||" (||) :$ (value "==" ((==)::Int->Int->Bool) :$ val (3::Int) :$ (value "+" ((+)::Int->Int->Int) :$ var "y" (undefined::Int) :$ val (1::Int))) :$ (value "not" not :$ val False)
    3 == y + 1 || not False :: Bool

    We can just write:

    > (three -==- yy -+- one) -||- not' false
    x == y + 1 || not False :: Bool

This exports over a hundred symbols to be used mainly when writing unit tests or playing around on GHCi.

Since the Expr type only allows monomorphic values, encoded polimorphic values are monomorphized usually to the Int type.

Beware: lifted Expr functions sometimes work for different types. The current version does not have a rationale for types that are included: you have to either try around on the REPL or look at the source to really know.

Synopsis

Convenience re-export

Functions and values encoded as Expr or functions of Exprs

The naming rules are:

Unqualified polymorphic constructors and functions have their element types bound to Int.

There are exceptions to the above rules such as: when a name would conflict with a Prelude function. (e.g.: orE and andE)

Booleans

b_ :: Expr Source #

Expr representing a hole of Bool type.

> b_
_ :: Bool

pp :: Expr Source #

Expr representing a variable p :: Bool.

> pp
p :: Bool

qq :: Expr Source #

Expr representing a variable q :: Bool.

> qq
q :: Bool

rr :: Expr Source #

Expr representing a variable r :: Bool.

> rr
r :: Bool

pp' :: Expr Source #

Expr representing a variable p' :: Bool.

> pp'
p' :: Bool

false :: Expr Source #

False encoded as an Expr.

> false
False :: Bool

true :: Expr Source #

True encoded as an Expr.

> true
True :: Bool

notE :: Expr Source #

The function not encoded as an Expr.

> notE
not :: Bool -> Bool

orE :: Expr Source #

The function or encoded as an Expr.

> orE
(||) :: Bool -> Bool -> Bool

andE :: Expr Source #

The function and encoded as an Expr.

> andE
(&&) :: Bool -> Bool -> Bool

not' :: Expr -> Expr Source #

The function not lifted over the Expr type.

> not' false
not False :: Bool
> evalBool $ not' false
True
> not' pp
not p :: Bool

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

The function || lifted over the Expr type.

> pp -||- qq
p || q :: Bool
> false -||- true
False || True :: Bool
> evalBool $ false -||- true
True

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

The function && lifted over the Expr type.

> pp -&&- qq
p && q :: Bool
> false -&&- true
False && True :: Bool
> evalBool $ false -&&- true
False

(-==-) :: Expr -> Expr -> Expr infix 4 Source #

(-/=-) :: Expr -> Expr -> Expr infix 4 Source #

(-<=-) :: Expr -> Expr -> Expr infix 4 Source #

(-<-) :: Expr -> Expr -> Expr infix 4 Source #

Integers

i_ :: Expr Source #

A typed hole of Int type.

> i_
_ :: Int

xx :: Expr Source #

A variable x of Int type.

> xx
x :: Int

yy :: Expr Source #

A variable y of Int type.

> yy
y :: Int

zz :: Expr Source #

A variable z of Int type.

> zz
z :: Int

xx' :: Expr Source #

A variable x' of Int type.

> xx'
x' :: Int

zero :: Expr Source #

The value 0 bound to the Int type encoded as an Expr.

> zero
0 :: Int

one :: Expr Source #

The value 1 bound to the Int type encoded as an Expr.

> one
1 :: Int

two :: Expr Source #

The value 2 bound to the Int type encoded as an Expr.

> two
2 :: Int

three :: Expr Source #

The value 3 bound to the Int type encoded as an Expr.

> three
3 :: Int

minusOne :: Expr Source #

The value -1 bound to the Int type encoded as an Expr.

> minusOne
-1 :: Int

minusTwo :: Expr Source #

The value -2 bound to the Int type encoded as an Expr.

> minusOne
-2 :: Int

idE :: Expr Source #

The function id for the Int type encoded as an Expr. (See also id'.)

> idE :$ xx
id x :: Int
> idE :$ zero
id 0 :: Int
> evaluate $ idE :$ zero :: Maybe Int
Just 0

negateE :: Expr Source #

negate over the Int type encoded as an Expr

> negateE
negate :: Int -> Int

absE :: Expr Source #

abs over the Int type encoded as an Expr.

> absE
abs :: Int -> Int

idInt :: Expr Source #

The function id encoded as an Expr. (cf. id')

idBool :: Expr Source #

The function id encoded as an Expr. (cf. id')

idChar :: Expr Source #

The function id encoded as an Expr. (cf. id')

idInts :: Expr Source #

The function id encoded as an Expr. (cf. id')

idBools :: Expr Source #

The function id encoded as an Expr. (cf. id')

idString :: Expr Source #

The function id encoded as an Expr. (cf. id')

id' :: Expr -> Expr Source #

Constructs an application of id as an Expr. Only works for Int, Bool, Char, String, [Int], [Bool].

> id' yy
id yy :: Int
> id' one
id 1 :: Int
> evl (id' one) :: Int
1
> id' pp
id p :: Bool
> id' false
id' False :: Bool
> evl (id' true) :: Bool
True :: Bool

negate' :: Expr -> Expr Source #

negate over the Int type lifted over the Expr type.

> negate' xx
negate x :: Int
> evl (negate' one) :: Int
-1

abs' :: Expr -> Expr Source #

abs over the Int type lifted over the Expr type.

> abs' xx'
abs x' :: Int
> evl (abs' minusTwo) :: Int
2

plus :: Expr Source #

The operator + for the Int type. (See also -+-.)

> plus
(+) :: Int -> Int -> Int
> plus :$ one
(1 +) :: Int -> Int
> plus :$ xx :$ yy
x + y :: Int

times :: Expr Source #

The operator * for the Int type. (See also -*-.)

> times
(*) :: Int -> Int -> Int
> times :$ two
(2 *) :: Int -> Int
> times :$ xx :$ yy
x * y :: Int

(-+-) :: Expr -> Expr -> Expr infixl 6 Source #

The operator + for the Int type for use on Exprs. (See also plus.)

> two -+- three
2 + 3 :: Int
> minusOne -+- minusTwo -+- zero
((-1) + (-2)) + 0 :: Int
> xx -+- (yy -+- zz)
x + (y + z) :: Int

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

The operator * for the Int type lifted over the Expr type. (See also times.)

> three -*- three
9 :: Int
> one -*- two -*- three
(1 * 2) * 3 :: Int
> two -*- xx
2 * x :: Int

ff :: Expr -> Expr Source #

A variable function f of 'Int -> Int' type lifted over the Expr type.

> ff xx
f x :: Int
> ff one
f 1 :: Int

ffE :: Expr Source #

A variable f of 'Int -> Int' type encoded as an Expr.

> ffE
f :: Int -> Int

gg :: Expr -> Expr Source #

A variable function g of 'Int -> Int' type lifted over the Expr type.

> gg yy
g y :: Int
> gg minusTwo
gg (-2) :: Int

ggE :: Expr Source #

A variable g of 'Int -> Int' type encoded as an Expr.

> ggE
g :: Int -> Int

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

A variable binary operator ? lifted over the Expr type. Works for Int, Bool, Char, [Int] and String.

> xx -?- yy
x ? y :: Int
> pp -?- qq
p ? q :: Bool
> xx -?- qq
*** Exception: (-?-): cannot apply `(?) :: * -> * -> *` to `x :: Int' and `q :: Bool'.  Unhandled types?

(-$-) :: Expr -> Expr -> Expr infixl 6 Source #

Chars

c_ :: Expr Source #

A hole of Char type encoded as an Expr.

> c_
_ :: Char

bee :: Expr Source #

The character 'b' encoded as an Expr

> bee
'b' :: Char
> evl bee :: Char
'b'

cee :: Expr Source #

The character 'c' encoded as an Expr

> cee
'c' :: Char
> evl cee :: Char
'c'

dee :: Expr Source #

The character 'd' encoded as an Expr

> dee
'd' :: Char
> evl dee :: Char
'd'

Lists

is_ :: Expr Source #

A typed hole of [Int] type encoded as an Expr.

> is_
_ :: [Int]

xxs :: Expr Source #

A variable named xs of type [Int] encoded as an Expr.

> xxs
xs :: [Int]

yys :: Expr Source #

A variable named ys of type [Int] encoded as an Expr.

> yys
ys :: [Int]

nil :: Expr Source #

An empty list of type [Int] encoded as an Expr.

> nil
[] :: [Int]

emptyString :: Expr Source #

An empty String encoded as an Expr.

> emptyString
"" :: String

nilInt :: Expr Source #

The empty list '[]' encoded as an Expr.

nilBool :: Expr Source #

The empty list '[]' encoded as an Expr.

nilChar :: Expr Source #

The empty list '[]' encoded as an Expr.

cons :: Expr Source #

The list constructor with Int as element type encoded as an Expr.

> cons
(:) :: Int -> [Int] -> [Int]
> cons :$ one :$ nil
[1] :: [Int]

Consider using -:- and unit when building lists of Expr.

consInt :: Expr Source #

The list constructor : encoded as an Expr.

consBool :: Expr Source #

The list constructor : encoded as an Expr.

consChar :: Expr Source #

The list constructor : encoded as an Expr.

(-:-) :: Expr -> Expr -> Expr infixr 5 Source #

The list constructor lifted over the Expr type. Works for the element types Int, Char and Bool.

> zero -:- one -:- unit two
[0,1,2] :: [Int]
> zero -:- one -:- two -:- nil
[0,1,2] :: [Int]
> bee -:- unit cee
"bc" :: [Char]

unit :: Expr -> Expr Source #

unit constructs a list with a single element. This works for elements of type Int, Char and Bool.

> unit one
[1]
> unit false
[False]

(-++-) :: Expr -> Expr -> Expr infixr 5 Source #

List concatenation lifted over the Expr type. Works for the element types Int, Char and Bool.

> (zero -:- one -:- nil) -:- (two -:- three -:- nil)
[0,1] -++- [2,3] :: [Int]
> (bee -:- unit cee) -:- unit dee
"bc" -++- "c" :: [Char]

head' :: Expr -> Expr Source #

List head lifted over the Expr type. Works for the element types Int, Char and Bool.

> head' $ unit one
head [1] :: Int
> head' $ unit bee
head "b" :: Char
> head' $ zero -:- unit two
head [0,2] :: Int
> evl $ head' $ unit one :: Int
1

tail' :: Expr -> Expr Source #

List tail lifted over the Expr type. Works for the element types Int, Char and Bool.

> tail' $ unit one
tail [1] :: [Int]
> tail' $ unit bee
tail "b" :: [Char]
> tail' $ zero -:- unit two
tail [0,2] :: [Int]
> evl $ tail' $ zero -:- unit two :: [Int]
[2]

length' :: Expr -> Expr Source #

List length lifted over the Expr type. Works for the element types Int, Char and Bool.

> length' $ unit one
length [1] :: Int
> length' $ unit bee
length "b" :: Int
> length' $ zero -:- unit two
length [0,2] :: Int
> evl $ length' $ unit one :: Int
1

Maybes

Tuples

sixtuple :: Expr -> Expr -> Expr -> Expr -> Expr -> Expr -> Expr Source #