express-0.2.0: Dynamically-typed expressions involving function application 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.Fixtures

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 polymorphic 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

implies :: Expr Source #

The ==> operator encoded as an Expr

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 infixr 2 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 infixr 3 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 infixr 0 Source #

The function ==> lifted over Exprs.

> false -==>- true
False ==> True :: Bool
> evl $ false -==>- true :: Bool
True

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

Constructs an equation between two Exprs.

> xx -==- zero
x == 0 :: Bool
> cc -==- dee
c == 'd' :: Bool

This works for the Int, Bool, Char argument types and their lists.

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

Constructs an inequation between two Exprs.

> xx -/=- zero
x /= 0 :: Bool
> cc -/=- ae
c /= 'a' :: Bool

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

Constructs a less-than-or-equal inequation between two Exprs.

> xx -<=- zero
x <= 0 :: Bool
> cc -<=- ae
c <= 'a' :: Bool

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

Constructs a less-than inequation between two Exprs.

> xx -<- zero
x < 0 :: Bool
> cc -<- bee
c < 'b' :: Bool

compare' :: Expr -> Expr -> Expr Source #

Constructs an Expr-encoded compare operation between two Exprs.

> xx `compare'` zero
compare x 0 :: Ordering
> compare' ae bee
compare 'a' 'b' :: Ordering

if' :: Expr -> Expr -> Expr -> Expr Source #

A virtual function if :: Bool -> a -> a -> a lifted over the Expr type. This is displayed as an if-then-else.

> if' pp zero xx
(if p then 0 else x) :: Int
> zz -*- if' pp xx yy
z * (if p then x else y) :: Int
> if' pp false true -||- if' qq true false
(if p then False else True) || (if q then True else False) :: Bool
> evl $ if' true (val 't') (val 'f') :: Char
't'

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

ii :: Expr Source #

A variable i of Int type.

> ii
i :: Int

jj :: Expr Source #

A variable j of Int type.

> jj
j :: Int

kk :: Expr Source #

A variable k of Int type.

> kk
k :: Int

ii' :: Expr Source #

A variable i' of Int type.

> ii'
i' :: Int

ll :: Expr Source #

A variable l of Int type.

> ll
l :: Int

mm :: Expr Source #

A variable m of Int type.

> mm
m :: Int

nn :: Expr Source #

A variable n of Int type.

> nn
n :: 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

four :: Expr Source #

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

> four
4 :: Int

five :: Expr Source #

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

> five
5 :: Int

six :: Expr Source #

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

> six
6 :: Int

seven :: Expr Source #

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

> seven
7 :: Int

eight :: Expr Source #

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

> eight
8 :: Int

nine :: Expr Source #

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

> nine
9 :: Int

ten :: Expr Source #

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

> ten
10 :: Int

eleven :: Expr Source #

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

> eleven
11 :: Int

twelve :: Expr Source #

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

> twelve
12 :: 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

signumE :: Expr Source #

signum over the Int type encoded as an Expr.

> signumE
signum :: 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

const' :: Expr -> Expr -> Expr Source #

The const function lifted over the Expr type.

> const' zero one
const 0 1 :: Int

This works for the argument types Int, Char, Bool and their lists.

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

signum' :: Expr -> Expr Source #

signum over the Int type lifted over the Expr type.

> signum' xx'
signum x' :: Int
> evl (signum' minusTwo) :: Int
-1

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

minus :: Expr Source #

The subtraction - operator encoded as an Expr.

> minus :$ one
(1 -) :: Int -> Int
> minus :$ one :$ zero
1 - 0 :: 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 infixl 7 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

hh :: Expr -> Expr Source #

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

> hh zz
h z :: Int

hhE :: Expr Source #

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

> hhE
h :: 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 #

$ lifted over Exprs

> absE -$- one
abs $ 1 :: Int

Works for Int, Bool, Char argument types and their lists.

odd' :: Expr -> Expr Source #

odd with an Int argument lifted over the Expr type.

> odd' (xx -+- one)
odd (x + 1) :: Bool
> evl (odd' two) :: Bool
False

even' :: Expr -> Expr Source #

even with an Int argument lifted over the Expr type.

> even' (xx -+- two)
even (x + 2) :: Bool
> evl (even' two) :: Bool
True

Chars

c_ :: Expr Source #

A hole of Char type encoded as an Expr.

> c_
_ :: Char

cs_ :: Expr Source #

A hole of String type encoded as an Expr.

> cs_
_ :: [Char]

cc :: Expr Source #

A variable named c of type Char encoded as an Expr.

> cc
c :: Char

dd :: Expr Source #

A variable named c of type Char encoded as an Expr.

> dd
d :: Char

ccs :: Expr Source #

A variable named cs of type String encoded as an Expr.

> ccs
cs :: [Char]

ae :: Expr Source #

The character 'a' encoded as an Expr.

> ae
'a' :: Char
> evl ae :: Char
'a'

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'

zed :: Expr Source #

The character 'z' encoded as an Expr

> zed
'z' :: Char
> evl zed :: Char
'z'

(cf. zee)

zee :: Expr Source #

The character 'z' encoded as an Expr

> zee
'z' :: Char
> evl zee :: Char
'z'

(cf. zed)

space :: Expr Source #

The space character encoded as an Expr

> space
' ' :: Char

lineBreak :: Expr Source #

The line break character encoded as an Expr

> lineBreak
'\n' :: Char

ord' :: Expr -> Expr Source #

The ord function lifted over Expr

> ord' bee
ord 'b' :: Int
> evl (ord' bee)
98

ordE :: Expr Source #

The ord function encoded as an Expr

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]

zzs :: Expr Source #

A variable named zs 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]

null' :: Expr -> Expr Source #

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

> null' $ unit one
null [1] :: Bool
> null' $ nil
null [] :: Bool
> evl $ null' nil :: Bool
True

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

elem' :: Expr -> Expr -> Expr Source #

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

> elem' false (false -:- unit true)
elem False [False,True] :: Bool
> evl $ elem' false (false -:- unit true) :: Bool
True

sort' :: Expr -> Expr Source #

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

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

insert' :: Expr -> Expr -> Expr Source #

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

> insert' zero nilInt
insert 0 [] :: [Int]
> insert' false (false -:- unit true)
insert False [False,True] :: [Bool]

bs_ :: Expr Source #

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

> bs_
_ :: [Bool]

pps :: Expr Source #

Expr representing a variable p' :: `[Bool]`.

> pps
ps :: [Bool]

qqs :: Expr Source #

A typed hole of '[Bool]' type

> qqs
qs :: [Bool]

and' :: Expr -> Expr Source #

and lifted over the Expr type.

> and' pps
and ps :: Bool
> evl (and' $ expr [False,True]) :: Bool
False

or' :: Expr -> Expr Source #

or lifted over the Expr type.

> or' pps
or ps :: Bool
> evl (or' $ expr [False,True]) :: Bool
True

sum' :: Expr -> Expr Source #

sum of Int elements lifted over the Expr type.

> sum' xxs
sum xs :: Int
> evl (sum' $ expr [1,2,3::Int]) :: Int
6

product' :: Expr -> Expr Source #

product of Int elements lifted over the Expr type.

> product' xxs
product xs :: Int
> evl (product' $ expr [1,2,3::Int]) :: Int
6

appendInt :: Expr Source #

Append for list of Ints encoded as an Expr.

Maybes

nothing :: Expr Source #

Nothing bound to the Maybe Int type encoded as an Expr.

This is an alias to nothingInt.

nothingInt :: Expr Source #

Nothing bound to the Maybe Int type encoded as an Expr.

nothingBool :: Expr Source #

Nothing bound to the Maybe Bool type encoded as an Expr.

just :: Expr -> Expr Source #

The Just constructor lifted over the Expr type.

This works for the Bool and Int argument types.

> just zero
Just 0 :: Maybe Int
> just false
Just False :: Maybe Bool

justInt :: Expr Source #

The Just constructor of the Int element type encoded as an Expr.

justBool :: Expr Source #

The Just constructor of the Bool element type encoded as an Expr.

Tuples

comma :: Expr Source #

The pair constructor ( :: ... -> (Int,Int) ) encoded as an Expr.

pair :: Expr -> Expr -> Expr Source #

The pair constructor lifted over Exprs.

This works for the Int and Bool element types by differently from foldPair by returning a well-typed expression.

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

An infix synonym of pair.

triple :: Expr -> Expr -> Expr -> Expr Source #

The triple/trio constructor lifted over Exprs.

This only works for the Int element type.

quadruple :: Expr -> Expr -> Expr -> Expr -> Expr Source #

The quadruple constructor lifted over Exprs.

This only works for the Int element type.

quintuple :: Expr -> Expr -> Expr -> Expr -> Expr -> Expr Source #

The quintuple constructor lifted over Exprs.

This only works for the Int element type.

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

The sixtuple constructor lifted over Exprs.

This only works for the Int element type.

Higher order

compose :: Expr Source #

Function composition encoded as an Expr:

> compose
(.) :: (Int -> Int) -> (Int -> Int) -> Int -> Int

mapE :: Expr Source #

map over the Int element type encoded as an Expr

> mapE
map :: (Int -> Int) -> [Int] -> [Int]

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

Function composition . lifted over Expr.

> absE -.- negateE
abs . negate :: Int -> Int
> absE -.- negateE :$ one
(abs . negate) 1 :: Int

This works for Int, Bool, Char and their lists.

map' :: Expr -> Expr -> Expr Source #

map lifted over Exprs.

> map' absE (unit one)
map abs [1] :: [Int]

Enum

enumFrom' :: Expr -> Expr Source #

enumFrom lifted over Exprs.

> enumFrom' zero
enumFrom 0 :: [Int]

Works for Ints, Bools and Chars.

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

enumFrom lifted over Exprs named as ".." for pretty-printing.

> (-..) one
[1..] :: [Int]

Works for Ints, Bools and Chars.

enumFromTo' :: Expr -> Expr -> Expr Source #

enumFromTo lifted over Exprs

> enumFromTo' zero four
enumFromTo 0 4 :: [Int]

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

enumFromTo lifted over Exprs but named as ".." for pretty-printing.

> zero -..- four
[0..4] :: [Int]

enumFromThen' :: Expr -> Expr -> Expr Source #

enumFromThen lifted over Exprs

> enumFromThen' zero ten
enumFromThen 0 10 :: [Int]

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

enumFromThen lifted over Exprs but named as ",.." for pretty printing.

> zero -... ten
[0,10..] :: [Int]

enumFromThenTo' :: Expr -> Expr -> Expr -> Expr Source #

enumFromThenTo lifted over Exprs.

> enumFromThenTo' zero two ten
enumFromThenTo 0 2 10 :: [Int]

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

enumFromThenTo lifted over Exprs but named as ",.." for pretty-printing.

> (zero -...- two) ten
[0,2..10] :: [Int]