% a simple dcg expression evaluator
%    checks the validity of expressions on integer
%       values using the binary operators + - * /
%       and allowing the use of parentheses () around subexpressions
%    if the expression is valid then the result of the
%       expression is returned, following standard rules
%       for precedence and using accumulators to 
%       achieve left-to-right associativity for the operators
%
% the query format is:  evaluate(Expression, Result)
%     e.g.  evaluate("3+44*6", Result).
% and the query response will be false if the syntax is invalid,
%     or (if valid) will unify Result with the expression result
%
% -----------------------------------------------------------------------
% evaluate(Expression, Result)
% ----------------------------
% attempts to evaluate the given expression
evaluate(Expression, Result) :- string_codes(Expression, L), phrase(expr(Result), L, []).

% -----------------------------------------------------------------------

% an expression is either simple subexpression
%    or an addition/subtraction of other terms
expr(Result) --> addexpr(Result).

% an addition expression can actually be a multiplication expression,
%    or it could be a multiplication expression followed by +/- then 
%       another addition expression
% we evaluate the expressions left to right as we go,
%    storing the result so far in an accumulator
addexpr(Result) --> mulexpr(Result).
addexpr(Result) --> mulexpr(Prod), addtail(Prod,Result).
addtail(Result,Result).
addtail(SoFar, Result) --> "+", mulexpr(Prod), 
                           { Tmp is SoFar + Prod,  Result = Tmp }.
addtail(SoFar, Result) --> "+", mulexpr(Prod), 
                           { Tmp is SoFar + Prod }, 
                           addtail(Tmp, Result).
addtail(SoFar, Result) --> "-", mulexpr(Prod), 
                           { Tmp is SoFar - Prod,  Result = Tmp }.
addtail(SoFar, Result) --> "-", mulexpr(Prod), 
                           { Tmp is SoFar - Prod },  
                           addtail(Tmp, Result).

% a multiplication expression is either an a basic value 
%   or a basic value followed by */ then another multiplication expression
%   of other terms
% again we accumulate the value so far as we go left to right through the expression
mulexpr(Result) --> basic(Result).
mulexpr(Result) --> basic(N), multail(N, Result).
multail(Result, Result).
multail(SoFar, Result) --> "*", basic(N), 
                           { Tmp is SoFar * N, Result = Tmp }.
multail(SoFar, Result) --> "*", basic(N), 
                           { Tmp is SoFar * N }, 
                           multail(Tmp, Result).
multail(SoFar, Result) --> "/", basic(N), 
                           { Tmp is SoFar / N, Result = Tmp }.
multail(SoFar, Result) --> "/", basic(N), 
                           { Tmp is SoFar / N }, 
                           multail(Tmp, Result).

% an basic expression is either an integer or an expression in brackets
basic(Result) --> integer(Result).
basic(Result) --> "(", expr(Result), ")".

% an integer is one or more digits
integer(Result) --> digits(0,Result).

% recognize digit sequences, tallying their cumulative value
%    as we traverse them left-to-right
digits(SoFar,Result) -->  digit(D), { Result is 10 * SoFar + D }.
digits(SoFar, Result) --> digit(D), { Temp is 10 * SoFar + D }, 
                          digits(Temp, Result).

% a single digit is any character in the ascii range 48 to 57
digit(Result) --> [ C ], { integer(C), C >= 48, C =< 57, Result is C - 48 }. 

