Guide to Prolog Programming

© Roman Barták, 1998

Home
Prolog in Examples
Prolog Data Structures

Previous | Contents | Next

Arithmetic Expressions

[evaluating] [compiling] [optimizing]

In this lecture, we will work with arithmetic expressions in a symbolic manner which is natural for Prolog. First we write a program for evaluating arithmetic expressions and then we develop a simple compiler which translates the arithmetic expression into a linear code of stack machine.


Evaluating

We can easily evaluate the arithmetic expression using Prolog build-in evaluator.

naive_eval(Expr,Res):-Res is Expr.

However, for purposes of this tutorial we prefer the following evaluator which traverses the structure of the evaluated term. Notice, the natural decomposition of term via unification and build-in functors +,-,*. To simplify the problem, we omit the division (/) operator.

eval(A+B,CV):-eval(A,AV),eval(B,BV),CV is AV+BV.
eval(A-B,CV):-eval(A,AV),eval(B,BV),CV is AV-BV.
eval(A*B,CV):-eval(A,AV),eval(B,BV),CV is AV*BV.
eval(Num,Num):-number(Num).

Now, we can easily extend the above program to allow "variables" in the evaluated term. These variables are represented by Prolog atoms like a, b or c, so they do not correspond to Prolog variables. Ofcourse, we have to notify the values of the variables to the evaluating program. Thus, the list of pairs variable/value as well as the evaluated expression is passed to the evaluator. To get the value of given variable we utilize the function member that is defined in one of previous lectures.

eval_v(A+B,CV,Vars):-eval_v(A,AV,Vars),eval_v(B,BV,Vars),CV is AV+BV.
eval_v(A-B,CV,Vars):-eval_v(A,AV,Vars),eval_v(B,BV,Vars),CV is AV-BV.
eval_v(A*B,CV,Vars):-eval_v(A,AV,Vars),eval_v(B,BV,Vars),CV is AV*BV.
eval_v(Num,Num,Vars):-number(Num).
eval_v(Var,Value,Vars):-atom(Var),member(Var/Value,Vars).

Try ?-eval_v(2*a+b,Val,[a/1,b/5]) to test the above program.


Compiling

Evaluating arithmetic expressions can be easily extended into generating linear code for some abstract stack machine. We use stack machine with following intructions:

Note, that we use the accumulator to collect the code and that the code is actually generated from the end to the beginning.

gen_expr(A+B,InCode,OutCode):-
   gen_expr(B,[pop(X),pop(Y),plus(X,Y,Z),push(Z)|InCode],TempCode),
   gen_expr(A,TempCode,OutCode).
gen_expr(A-B,InCode,OutCode):-
   gen_expr(B,[pop(X),pop(Y),minus(X,Y,Z),push(Z)|InCode],TempCode),
   gen_expr(A,TempCode,OutCode).
gen_expr(A*B,InCode,OutCode):-
   gen_expr(B,[pop(X),pop(Y),times(X,Y,Z),push(Z)|InCode],TempCode),
   gen_expr(A,TempCode,OutCode).
gen_expr(Num,InCode,[push(Num)|InCode]):-number(Num).
gen_expr(Var,InCode,[get_value(Var,Value),push(Value)|InCode]):-atom(Var).

If we can generate the code for evaluating expressions it is easy to add generator for assignment. The compiled program is a list of assignments then.

gen_prog([A=Expr|Rest],InCode,Code):-
   atom(A),
   gen_prog(Rest,InCode,TempCode),
   gen_expr(Expr,[pop(X),set_value(A,X)|TempCode],Code).
gen_prog([],Code,Code).

Now, we write an interpreter of generated machine code. The interpreter uses Stack to evaluate arithmetic expressions and Memory to remember values of variables. The Prolog code of the interpreter follows naturally the sematics of used instructions: pop, push, plus, minus, times, get_value and set_value.

eval_prog([push(X)|Code],Stack,Memory):-
   eval_prog(Code,[X|Stack],Memory).
eval_prog([pop(X)|Code],[X|Stack],Memory):-
   eval_prog(Code,Stack,Memory).
eval_prog([plus(X,Y,Z)|Code],Stack,Memory):-
   Z is X+Y,
   eval_prog(Code,Stack,Memory).
eval_prog([minus(X,Y,Z)|Code],Stack,Memory):-
   Z is X-Y,
   eval_prog(Code,Stack,Memory).
eval_prog([times(X,Y,Z)|Code],Stack,Memory):-
   Z is X*Y,
   eval_prog(Code,Stack,Memory).
eval_prog([get_value(X,Value)|Code],Stack,Memory):-
   member(X/Value,Memory),
   eval_prog(Code,Stack,Memory).
eval_prog([set_value(X,Value)|Code],Stack,Memory):-
   set_value(X,Value,Memory,NewMemory)
   eval_prog(Code,Stack,NewMemory).
eval_prog([],Stack,Memory):-
   print_memory(Memory).

The setting value of the variable is not so straightforward as getting the value of the variable using member. If the variable is in the memory, its value has to be changed, otherwise a new pair variable/value is added to the memory.

set_value(X,Value,[X/_|T],[X/Value|T]).
set_value(X,Value,[Y/V|T],[Y/V|NewT):-
   X\=Y,set_value(X,Value,T,NewT).
set_value(X,Value,[],[X/Value]).

Finally, when the interpreter eval_prog finds the end of the code which is indicated by empty list, it prints the contents of the memory, i.e., the values of all variables which are used in the program.

print_memory([X/Value|T]):-
   write(X=Value),nl,print_memory(T).
print_memory([]):-nl.

To encapsulate the compiler/code generator and interpreter/code evaluator, we introduce the following clause.

run(Prog):-
   gen_prog(Prog,[],Code),
   eval_prog(Code,[],[]).

You can try ?-run([a=5,b=a+2,a=3*a+b]) to test the program. But, what if one uses the variable vith undefined value, e.g., ?-run([a=b+2])? The program fails. Improve the program in such a way that it will print a message notifying undefined variables during interpretaion or, better, it will detect the undefined variables during compilation.


Optimizing

Look at the code generated by gen_prog. Is it possible to optimize the code in some way? Ofcourse, it is possible. Here is an example of such trivial optimizer which removes all successive pairs push-pop and unifies their arguments. It is clear that if one element is pushed to a stack and the other element is poped from the same stack immediately then both elements are same (therefore unification).

optimize([push(X),pop(Y)|T],OptCode):-
   X=Y,
   optimize(T,OptCode).
optimize([H|T],[H|OptCode]):-
   optimize(T,OptCode).
optimize([],[]).

Now, we insert optimizer between generator and executor to get optimized program runner.

opt_run(Prog):-
   gen_prog(Prog,[],Code),
   optimize(Code,OptCode),
   eval_prog(OptCode,[],[]).


Do you like the above presented application? If so, you can further extend it to develop a complete compiler and executor of chosen programming language. For example, think about incorporating if-then-else construct into the above language.


PROLOG is perfect programming language for handling symbolic data.

[evaluating] [compiling] [optimizing]


Designed and maintained by Roman Barták

Previous | Contents | Next