Ewok is a variant of Jedi 1.0.
In Jedi 1 we represented expressions as subclasses of an Expression trait. In Prolog structures are the closest analogy to classes, so here we represent Ewok expressions as Prolog structures:
Expression ::= Literal | Identifier | FunCall | Declaration | Conditional | Conjunction | Disjunction
Literal ::= lit(Value)
Value ::= any simple Prolog literal (number, Boolean, or String)
Identifier ::= id(Constant)
Constant ::= any alpha numeric beginning with a lowercase letter
FunCall ::= call(Operator, Operands)
Operator ::= add | mul | sub | div | same | less
Operands ::= [(Expression ~ ("," ~ Expression)*)?]
Declaration ::= def(Identifier, Expression)
Conditional ::= if(Expression, Expression, Expression?)
Conjunction ::= conj(Operands)
Disjunction ::= disj(Operands)
The relationship "executing expression e produces result r" is expressed by the expression predicate:
exec(Expression, Result) // Result = the result of executing Expression
The Ewok alu and environment are also predicates:
alu(Operator, Args, Result) // applying Identifier to a list of values (args) produces Result
globalEnv(Constant, Value) // Constant is bound to Value
?- exec(def(id(pi), lit(3.14)), X). // def pi = 3.14
X = done.
?- exec(id(pi), V).
V = 3.14.
?- exec(def(id(e), lit(2.7)), X).
X = done.
?- globalEnv(X, Y).
X = pi,
Y = 3.14 ;
X = e,
Y = 2.7.
?- exec(call(add, [lit(2), id(e), id(pi)]), V).
V = 7.84 ;
false.
?- alu(add, [1, 2, 3], V).
V = 6 ;
false.
?- exec(if(lit(true), lit(1), id(blah)), V).
V = 1 ;
false.
We represent Ewok's global environment with the globalEnv predicate, where
globalEnv(pi, 3.14)
asserts that pi is bound to 3.14.
When executing a declaration such as
exec(def(id(pi), lit(3.14)), X).
use Prolog's power to add and remove clauses from its own knowledgebase with assert and retract.
Complete the implementations of the exec, alu, and globalEnv predicates in Prolog. All of the Ewok expressions should be executable.