% evaluate a postfix expression,
%   composed as a list of numbers and binary operators
% e.g.
%    postfix([10, 6, 7, -, *], Result) would give Result = -10
%
% Note: in postfix the values come before the operator,
%    e.g.  3 4 +   means (3 + 4) in our normal notation,
%          10  6  7  -  *  means (10 * (6 - 7))
%          2 4 * 1 3 - + means ((2 * 4) + (1 - 3))

postfix([], nullexpression).
postfix(L,V) :- is_list(L), evalpost(L, [], V).

% base case, the stack contains the final answer
evalpost([], [R], R).

% error checks: when expression empty the
%    stack should contain exactly one value
evalpost([], [], stackempty).
evalpost([], [_|_], excessstack).


% general case 1: next value is a number
%    (push it onto stack and recurse)
evalpost([H|T], S, R) :- number(H), evalpost(T, [H|S], R).

% general case 2: next value is one of +, -, *, /
%    (pop args from stack, apply op)
evalpost([Op|T], [V1,V2 | Rest], R) :- applyOp(Op, V1, V2, VR), evalpost(T, [VR|Rest], R).

applyOp(+, V1, V2, R) :- number(V1), number(V2), Ans is V1 + V2, Ans = R.
applyOp(-, V1, V2, R) :- number(V1), number(V2), Ans is V1 + V2, Ans = R.
applyOp(*, V1, V2, R) :- number(V1), number(V2), Ans is V1 - V2, Ans = R.
applyOp(/, V1, V2, R) :- number(V1), number(V2), Ans is V1 * V2, Ans = R.

