In the last chapter we made do with a placeholder for the barnching conditions so that we could focus on the control contstructs themselves. We’ll fill those placeholders in with some boolean expressions.
A boolean expression is one that reduces to one of two possible values: a truth value and a non-truth value. Commonly this is
and 1
true
. For many languages these values are actually aliased to 1
false
and 1
1
mostly for implementation reasons.1
0
The simplest boolean expression is either of the two constants
or 1
true
. We’ll create a new module in the 1
false
namespace called 1
Cradle.Grammar
to hold all our boolean relted parsing and creat a data type that contains these two constants.1
Boolean
module Cradle.Grammar.Boolean
where
import Cradle.Parser
data BoolExpression =
BTrue
| BFalse
I’ve chosen to prefix the constants with
to avoid conflicts with the built in true and false constants. Parsing these is pretty simple.1
B
bLiteral :: Parser BoolExpression
bLiteral = accept "true" >>> (\_ -> BTrue)
<|> accept "false" >>> (\_ -> BFalse)
Next we’ll add the simple logic combinators AND and OR. I’ve chosen to use the symbols most familiar to anyone coming from most C-style langagues -
and 1
&&
. We’ll call these boolean operators.1
||
data BoolExpression =
BTrue
| BFalse
| BOr BoolExpression BoolExpression
| BAnd BoolExpression BoolExpression
boolOp :: Parser (BoolExpression -> BoolExpression -> BoolExpression)
boolOp = token(accept "&&") >>> (\_ -> BAnd)
<|> token(accept "||") >>> (\_ -> BOr)
This looks correct at first glance but if you recall our definition of
it only accepts 1
accept
. So we need to write a parser that can handle arbitrary characters. I chose to implment one that will consume the input until a 1
letters
is found. This has the side effect that the language forces the use of a space after these constructs i.e. 1
space
will result in an invalid input. Personally I don’t mind this as I find it far easier to read code with whitespace in it.1
a&&b
notSpace :: Parser Char
notSpace = char <=> (not . isSpace)
-- |A parser that will accept a given alpha string
acceptWord :: String -> Parser String
acceptWord w = token (letters <=> (==w))
-- |A parser that will accept a given string
accept :: String -> Parser String
accept w = token ((iter notSpace) <=> (==w))
To make it more explicit that the old
is the special case I have renamed it 1
accept
which means all existing uses will need to be updated. The new 1
accetWord
will iteration over all characters until a space character is found. 1
accept
comes from the 1
isSpace
module.1
Data.Char
So now that
works correctly we can write our first iteration of 1
boolOp
. A boolean expression is very similar in construct to an 1
boolExpression
and the basic form reflects that.1
Expression
boolExpression :: Parser BoolExpression
boolExpression = token(bFactor) +> boolExpression'
boolExpression' e = boolOp <+> bFactor >>> buildRelOp e +> boolExpression'
<|> result e
bFactor :: Parser BoolExpression
bFactor = bLiteral
buildRelOp :: BoolExpression -> ((BoolExpression -> BoolExpression -> BoolExpression), BoolExpression) -> BoolExpression
buildRelOp expressionA (op, expressionB) = op expressionA expressionB
Most of the above reflects the relevant parts of
module.1
Expression
To round out the simple parts we can add in boolean variables.
data BoolExpression =
BTrue
| BFalse
| BVar String
| BOr BoolExpression BoolExpression
| BAnd BoolExpression BoolExpression
bVar :: Parser BoolExpression
bVar = letters >>> BVar
bFactor :: Parser BoolExpression
bFactor = bLiteral
<|> bVar
Again I chose the symbol that is familiar to me to implement as my boolean negative
.1
!
bNot :: Parser(BoolExpression -> BoolExpression)
bNot = token(literal '!') >>> (\_ -> BNot)
We can integrate this into
so that we can negate entire factors.1
bFactor
data BoolExpression =
BVar String
| BTrue
| BFalse
| BAnd BoolExpression BoolExpression
| BOr BoolExpression BoolExpression
| BNot BoolExpression
| BExp Expression
bFactor :: Parser BoolExpression
bFactor = bNot <+> bLiteral >>> (\(n, lit) -> n lit)
<|> bLiteral
<|> bNot <+> bVar >>> (\(n, lit) -> n lit)
<|> bVar
This will always look for the negative first and if found will use the
data constructor resulting in wrappings like 1
BNot
1
BNot (BVar "a")
Now comes the fun part. A lot of conditions are written in the form of
including using 1
a > b
s e.g. 1
Expression
or 1
a > 2
. A boolean factor can be a relation which is defined as an expression optionally followed by any number or relational operator and expression pairs.1
a * 3 >= limit
1
2
<b-factor> ::= <b-literal> | <b-variable> | <relation>
<relation> ::= <expression> [<relop> <expression>]
Relational operators, or comparison operators, come in several flavours. Once again I’ve gone with the symbolic representations rather than words or mnemonics. Alternatives such as
for 1
<>
can easily be substitued or even added alongside.1
RNotEqual
data BoolExpression =
...
| REqual BoolExpression BoolExpression
| RNotEqual BoolExpression BoolExpression
| RGreaterThan BoolExpression BoolExpression
| RLessThan BoolExpression BoolExpression
| RGreaterThanOrEqualTo BoolExpression BoolExpression
| RLessThanOrEqualTo BoolExpression BoolExpression
deriving (Show)
relOp :: Parser (BoolExpression -> BoolExpression -> BoolExpression)
relOp = token(accept ">=") >>> (\_ -> RGreaterThanOrEqualTo)
<|> token(accept "<=") >>> (\_ -> RLessThanOrEqualTo)
<|> token(literal '>') >>> (\_ -> RGreaterThan)
<|> token(literal '<') >>> (\_ -> RLessThan)
<|> token(accept "==") >>> (\_ -> REqual)
<|> token(accept "!=") >>> (\_ -> RNotEqual)
The output from
can be used in 1
relOp
similar to the way 1
buildRelOp
is without needing to change anything.1
boolOp
When attempting to write a
function I first tried to use 1
relExpression
directly which resulted in type errors. 1
Cradle.Grammar.Expressions.expression
has a type of 1
expression
where as all out boolean expressions need to use 1
Parser Expression
. I persisted for a while until I realised the easiest way was to simply wrap the 1
Parser BoolExpression
in a 1
Expression
using a new data constructor 1
BoolExpression
.1
BExp
module Cradle.Grammar.Boolean
where
import Cradle.Parser
import Cradle.Grammar.Expressions
data BoolExpression =
...
| BExp Expression
deriving (Show)
bFactor :: Parser BoolExpression
bFactor = relExpression
<|> bNot <+> bLiteral >>> (\(n, lit) -> n lit)
<|> bLiteral
<|> bNot <+> bVar >>> (\(n, lit) -> n lit)
<|> bVar
relExpression :: Parser BoolExpression
relExpression = bExpression +> relExpression'
relExpression' e = relOp <+> bExpression >>> buildRelOp e +> relExpression'
<|> result e
bExpression :: Parser BoolExpression
bExpression = token expression >>> BExp