⚠️ Warning: This is a draft ⚠️
This means it might contain formatting issues, incorrect code, conceptual problems, or other severe issues.
If you want to help to improve and eventually enable this page, please fork RosettaGit's repository and open a merge request on GitHub.
{{task}}
;Task: Create a stack-based evaluator for an expression in [[wp:Reverse Polish notation|reverse Polish notation (RPN)]] that also shows the changes in the stack as each individual token is processed ''as a table''.
-
Assume an input of a correct, space separated, string of tokens of an RPN expression
-
Test with the RPN expression generated from the [[Parsing/Shunting-yard algorithm]] task:
<big><big><code> 3 4 2 * 1 5 - 2 3 ^ ^ / + </code></big></big>
-
Print or display the output here
;Notes:
- '''^''' means exponentiation in the expression above.
- '''/''' means division.
;See also:
- [[Parsing/Shunting-yard algorithm]] for a method of generating an RPN from an infix expression.
- Several solutions to [[24 game/Solve]] make use of RPN evaluators (although tracing how they work is not a part of that task).
- [[Parsing/RPN to infix conversion]].
- [[Arithmetic evaluation]].
360 Assembly
{{trans|FORTRAN}} For concision, only integer arithmetic is handled, but input numbers can be of any length. The formal task is not completed, but the spirit of it is.
* RPN calculator RC 25/01/2019
REVPOL CSECT
USING REVPOL,R13 base register
B 72(R15) skip savearea
DC 17F'0' savearea
STM R14,R12,12(R13) save previous context
ST R13,4(R15) link backward
ST R15,8(R13) link forward
LR R13,R15 set addressability
XPRNT TEXT,L'TEXT print expression !?
L R4,0 js=0 offset in stack
LA R5,0 ns=0 number of stack items
LA R6,0 jt=0 offset in text
LA R7,TEXT r7=@text
MVC CC,0(R7) cc first char of token
DO WHILE=(CLI,CC,NE,X'00') do while cc<>'0'x
MVC CTOK,=CL5' ' ctok=''
MVC CTOK(1),CC ctok=cc
CLI CC,C' ' if cc=' '
BE ITERATE then goto iterate
IF CLI,CC,GE,C'0',AND,CLI,CC,LE,C'9' THEN
MVC DEED,=C'Load' deed='Load'
XDECI R2,0(R7) r2=cint(text); r1=@text
ST R2,STACK(R4) stack(js)=cc
SR R1,R7 lt length of token
BCTR R1,0 lt-1
EX R1,MVCV MVC CTOK("R1"),0(R7)
AR R6,R1 jt+=lt-1
AR R7,R1 @text+=lt-1
LA R4,4(R4) js+=4
LA R5,1(R5) ns++
ELSE , else
MVC DEED,=C'Exec' deed='Exec'
LA R9,STACK-8(R4) @stack(j-1)
IF CLI,CC,EQ,C'+' THEN if cc='+' then
L R1,STACK-8(R4) stack(j-1)
A R1,STACK-4(R4) stack(j-1)+stack(j)
ST R1,0(R9) stack(j-1)=stack(j-1)+stack(j)
ENDIF , endif
IF CLI,CC,EQ,C'-' THEN if cc='-' then
L R1,STACK-8(R4) stack(j-1)
S R1,STACK-4(R4) stack(j-1)-stack(j)
ST R1,0(R9) stack(j-1)=stack(j-1)-stack(j)
ENDIF , endif
IF CLI,CC,EQ,C'*' THEN if cc='*' then
L R3,STACK-8(R4) stack(j-1)
M R2,STACK-4(R4) stack(j-1)*stack(j)
ST R3,0(R9) stack(j-1)=stack(j-1)*stack(j)
ENDIF , endif
IF CLI,CC,EQ,C'/' THEN if cc='/' then
L R2,STACK-8(R4) stack(j-1)
SRDA R2,32 for sign propagation
D R2,STACK-4(R4) stack(j-1)/stack(j)
ST R3,0(R9) stack(j-1)=stack(j-1)/stack(j)
ENDIF , endif
IF CLI,CC,EQ,C'^' THEN if cc='^' then
LA R3,1 r3=1
L R0,STACK-4(R4) r0=stack(j) [loop count]
EXPONENT M R2,STACK-8(R4) r3=r3*stack(j-1)
BCT R0,EXPONENT if r0--<>0 then goto exponent
ST R3,0(R9) stack(j-1)=stack(j-1)^stack(j)
ENDIF , endif
S R4,=F'4' js-=4
BCTR R5,0 ns--
ENDIF , endif
MVC PG,=CL80' ' clean buffer
MVC PG(4),DEED output deed
MVC PG+5(5),CTOK output cc
MVC PG+11(6),=C'Stack:' output
LA R2,1 i=1
LA R3,STACK @stack
LA R9,PG+18 @buffer
DO WHILE=(CR,R2,LE,R5) do i=1 to ns
L R1,0(R3) stack(i)
XDECO R1,XDEC edit stack(i)
MVC 0(5,R9),XDEC+7 output stack(i)
LA R2,1(R2) i=i+1
LA R3,4(R3) @stack+=4
LA R9,6(R9) @buffer+=6
ENDDO , enddo
XPRNT PG,L'PG print
ITERATE LA R6,1(R6) jt++
LA R7,1(R7) @text++
MVC CC,0(R7) cc next char
ENDDO , enddo
L R1,STACK stack(1)
XDECO R1,XDEC edit stack(1)
MVC XDEC(4),=C'Val=' output
XPRNT XDEC,L'XDEC print stack(1)
L R13,4(0,R13) restore previous savearea pointer
LM R14,R12,12(R13) restore previous context
XR R15,R15 rc=0
BR R14 exit
MVCV MVC CTOK(0),0(R7) patern mvc
TEXT DC C'3 4 2 * 1 5 - 2 3 ^ ^ / +',X'00'
STACK DS 16F stack(16)
DEED DS CL4
CC DS C
CTOK DS CL5
PG DS CL80
XDEC DS CL12
YREGS
END REVPOL
{{out}}
3 4 2 * 1 5 - 2 3 ^ ^ / +
Load 3 Stack: 3
Load 4 Stack: 3 4
Load 2 Stack: 3 4 2
Exec * Stack: 3 8
Load 1 Stack: 3 8 1
Load 5 Stack: 3 8 1 5
Exec - Stack: 3 8 -4
Load 2 Stack: 3 8 -4 2
Load 3 Stack: 3 8 -4 2 3
Exec ^ Stack: 3 8 -4 8
Exec ^ Stack: 3 8 65536
Exec / Stack: 3 0
Exec + Stack: 3
Val= 3
Ada
with Ada.Text_IO, Ada.Containers.Vectors;
procedure RPN_Calculator is
package IIO is new Ada.Text_IO.Float_IO(Float);
package Float_Vec is new Ada.Containers.Vectors
(Index_Type => Positive, Element_Type => Float);
Stack: Float_Vec.Vector;
Input: String := Ada.Text_IO.Get_Line;
Cursor: Positive := Input'First;
New_Cursor: Positive;
begin
loop
-- read spaces
while Cursor <= Input'Last and then Input(Cursor)=' ' loop
Cursor := Cursor + 1;
end loop;
exit when Cursor > Input'Last;
New_Cursor := Cursor;
while New_Cursor <= Input'Last and then Input(New_Cursor) /= ' ' loop
New_Cursor := New_Cursor + 1;
end loop;
-- try to read a number and push it to the stack
declare
Last: Positive;
Value: Float;
X, Y: Float;
begin
IIO.Get(From => Input(Cursor .. New_Cursor - 1),
Item => Value,
Last => Last);
Stack.Append(Value);
Cursor := New_Cursor;
exception -- if reading the number fails, try to read an operator token
when others =>
Y := Stack.Last_Element; Stack.Delete_Last; -- pick two elements
X := Stack.Last_Element; Stack.Delete_Last; -- from the stack
case Input(Cursor) is
when '+' => Stack.Append(X+Y);
when '-' => Stack.Append(X-Y);
when '*' => Stack.Append(X*Y);
when '/' => Stack.Append(X/Y);
when '^' => Stack.Append(X ** Integer(Float'Rounding(Y)));
when others => raise Program_Error with "unecpected token '"
& Input(Cursor) & "' at column" & Integer'Image(Cursor);
end case;
Cursor := New_Cursor;
end;
for I in Stack.First_Index .. Stack.Last_Index loop
Ada.Text_IO.Put(" ");
IIO.Put(Stack.Element(I), Aft => 5, Exp => 0);
end loop;
Ada.Text_IO.New_Line;
end loop;
Ada.Text_IO.Put("Result = ");
IIO.Put(Item => Stack.Last_Element, Aft => 5, Exp => 0);
end RPN_Calculator;
{{out}}
3 4 2 * 1 5 - 2 3 ^ ^ / +
3.00000
3.00000 4.00000
3.00000 4.00000 2.00000
3.00000 8.00000
3.00000 8.00000 1.00000
3.00000 8.00000 1.00000 5.00000
3.00000 8.00000 -4.00000
3.00000 8.00000 -4.00000 2.00000
3.00000 8.00000 -4.00000 2.00000 3.00000
3.00000 8.00000 -4.00000 8.00000
3.00000 8.00000 65536.00000
3.00000 0.00012
3.00012
Result = 3.00012
ALGOL 68
{{works with|ALGOL 68G|Any - tested with release 2.8.win32}}
# RPN Expression evaluator - handles numbers and + - * / ^ #
# the right-hand operand for ^ is converted to an integer #
# expression terminator #
CHAR end of expression character = REPR 12;
# evaluates the specified rpn expression #
PROC evaluate = ( STRING rpn expression )VOID:
BEGIN
[ 256 ]REAL stack;
INT stack pos := 0;
# pops an element off the stack #
PROC pop = REAL:
BEGIN
stack pos -:= 1;
stack[ stack pos + 1 ]
END; # pop #
INT rpn pos := LWB rpn expression;
# evaluate tokens from the expression until we get the end of expression #
WHILE
# get the next token from the string #
STRING token type;
REAL value;
# skip spaces #
WHILE rpn expression[ rpn pos ] = " "
DO
rpn pos +:= 1
OD;
# handle the token #
IF rpn expression[ rpn pos ] = end of expression character
THEN
# no more tokens #
FALSE
ELSE
# have a token #
IF rpn expression[ rpn pos ] >= "0"
AND rpn expression[ rpn pos ] <= "9"
THEN
# have a number #
# find where the nmumber is in the expression #
INT number start = rpn pos;
WHILE ( rpn expression[ rpn pos ] >= "0"
AND rpn expression[ rpn pos ] <= "9"
)
OR rpn expression[ rpn pos ] = "."
DO
rpn pos +:= 1
OD;
# read the number from the expression #
FILE number f;
associate( number f
, LOC STRING := rpn expression[ number start : rpn pos - 1 ]
);
get( number f, ( value ) );
close( number f );
token type := "number"
ELSE
# must be an operator #
CHAR op = rpn expression[ rpn pos ];
rpn pos +:= 1;
REAL arg1 := pop;
REAL arg2 := pop;
token type := op;
value := IF op = "+"
THEN
# add the top two stack elements #
arg1 + arg2
ELIF op = "-"
THEN
# subtract the top two stack elements #
arg2 - arg1
ELIF op = "*"
THEN
# multiply the top two stack elements #
arg2 * arg1
ELIF op = "/"
THEN
# divide the top two stack elements #
arg2 / arg1
ELIF op = "^"
THEN
# raise op2 to the power of op1 #
arg2 ^ ENTIER arg1
ELSE
# unknown operator #
print( ( "Unknown operator: """ + op + """", newline ) );
0
FI
FI;
TRUE
FI
DO
# push the new value on the stack and show the new stack #
stack[ stack pos +:= 1 ] := value;
print( ( ( token type + " " )[ 1 : 8 ] ) );
FOR element FROM LWB stack TO stack pos
DO
print( ( " ", fixed( stack[ element ], 8, 4 ) ) )
OD;
print( ( newline ) )
OD;
print( ( "Result is: ", fixed( stack[ stack pos ], 12, 8 ), newline ) )
END; # evaluate #
main: (
# get the RPN expresson from the user #
STRING rpn expression;
print( ( "Enter expression: " ) );
read( ( rpn expression, newline ) );
# add a space to terminate the final token and an expression terminator #
rpn expression +:= " " + end of expression character;
# execute the expression #
evaluate( rpn expression )
)
{{out}}
Enter expression: 3 4 2 * 1 5 - 2 3 ^ ^ / +
number +3.0000
number +3.0000 +4.0000
number +3.0000 +4.0000 +2.0000
* +3.0000 +8.0000
number +3.0000 +8.0000 +1.0000
number +3.0000 +8.0000 +1.0000 +5.0000
- +3.0000 +8.0000 -4.0000
number +3.0000 +8.0000 -4.0000 +2.0000
number +3.0000 +8.0000 -4.0000 +2.0000 +3.0000
^ +3.0000 +8.0000 -4.0000 +8.0000
^ +3.0000 +8.0000 +65536.0
/ +3.0000 +0.0001
+ +3.0001
Result is: +3.00012207
ANSI Standard BASIC
1000 DECLARE EXTERNAL SUB rpn
1010 PUBLIC NUMERIC R(64) ! stack
1020 PUBLIC STRING expn$ ! for keyboard input
1030 PUBLIC NUMERIC i, lenn, n, true, false ! global values
1040 LET true = -1
1050 LET false = 0
1060 DO
1070 PRINT "enter an RPN expression:"
1080 INPUT expn$
1090 IF LEN( expn$ ) = 0 THEN EXIT DO
1100 PRINT "expn: ";expn$
1110 CALL rpn( expn$ )
1120 LOOP
1130 END
1140 !
1150 ! interpret reverse polish (postfix) expression
1160 EXTERNAL SUB rpn( expn$ )
1170 DECLARE EXTERNAL FUNCTION is_digit, get_number
1180 DECLARE EXTERNAL SUB print_stack
1190 DECLARE STRING ch$
1200 LET expn$ = expn$ & " " ! must terminate line with space
1210 LET lenn = LEN( expn$ )
1220 LET i = 0
1230 LET n = 1
1240 LET R(n) = 0.0 ! push zero for unary operations
1250 DO
1260 IF i >= lenn THEN EXIT DO ! at end of line
1270 LET i = i + 1
1280 IF expn$(i:i) <> " " THEN ! skip white spaces
1290 IF is_digit( expn$(i:i) ) = true THEN ! push number onto stack
1300 LET n = n + 1
1310 LET R(n) = get_number
1320 CALL print_stack
1330 ELSEIF expn$(i:i) = "+" then ! add and pop stack
1340 IF n < 2 THEN
1350 PRINT "stack underflow"
1360 ELSE
1370 LET R(n-1) = R(n-1) + R(n)
1380 LET n = n - 1
1390 CALL print_stack
1400 END IF
1410 ELSEIF expn$(i:i) = "-" then ! subtract and pop stack
1420 IF n < 2 THEN
1430 PRINT "stack underflow"
1440 ELSE
1450 LET R(n-1) = R(n-1) - R(n)
1460 LET n = n - 1
1470 CALL print_stack
1480 END IF
1490 ELSEIF expn$(i:i) = "*" then ! multiply and pop stack
1500 IF n < 2 THEN
1510 PRINT "stack underflow"
1520 ELSE
1530 LET R(n-1) = R(n-1) * R(n)
1540 LET n = n - 1
1550 CALL print_stack
1560 END IF
1570 ELSEIF expn$(i:i) = "/" THEN ! divide and pop stack
1580 IF n < 2 THEN
1590 PRINT "stack underflow"
1600 ELSE
1610 LET R(n-1) = R(n-1) / R(n)
1620 LET n = n - 1
1630 CALL print_stack
1640 END IF
1650 ELSEIF expn$(i:i) = "^" THEN ! raise to power and pop stack
1660 IF n < 2 THEN
1670 PRINT "stack underflow"
1680 ELSE
1690 LET R(n-1) = R(n-1) ^ R(n)
1700 LET n = n - 1
1710 CALL print_stack
1720 END IF
1730 ELSE
1740 PRINT REPEAT$( " ", i+5 ); "^ error"
1750 EXIT DO
1760 END IF
1770 END IF
1780 LOOP
1790 PRINT "result: "; R(n) ! end of main program
1800 END SUB
1810 !
1820 ! extract a number from a string
1830 EXTERNAL FUNCTION get_number
1840 DECLARE EXTERNAL FUNCTION is_digit
1850 LET j = 1 ! start of number string
1860 DECLARE STRING number$ ! buffer for conversion
1870 DO ! get integer part
1880 LET number$(j:j) = expn$(i:i)
1890 LET i = i + 1
1900 LET j = j + 1
1910 IF is_digit( expn$(i:i) ) = false THEN
1920 IF expn$(i:i) = "." then
1930 LET number$(j:j) = expn$(i:i) ! include decimal point
1940 LET i = i + 1
1950 LET j = j + 1
1960 DO WHILE is_digit( expn$(i:i) ) = true ! get fractional part
1970 LET number$(j:j) = expn$(i:i)
1980 LET i = i + 1
1990 LET j = j + 1
2000 LOOP
2010 END IF
2020 EXIT DO
2030 END IF
2040 LOOP
2050 LET get_number = VAL( number$ )
2060 END FUNCTION
2070 !
2080 ! check for digit character
2090 EXTERNAL FUNCTION is_digit( ch$ )
2100 IF "0" <= expn$(i:i) AND expn$(i:i) <= "9" THEN
2110 LET is_digit = true
2120 ELSE
2130 LET is_digit = false
2140 END IF
2150 END FUNCTION
2160 !
2170 EXTERNAL SUB print_stack
2180 PRINT expn$(i:i);" ";
2190 FOR ptr=n TO 2 STEP -1
2200 PRINT USING "-----%.####":R(ptr);
2210 NEXT ptr
2220 PRINT
2230 END SUB
ANTLR
[[File:Rpn.png|left|rpnC]]
[[File:rpnCNum.png|left|rpnC]]
[[File:RpnCop.png|left|rpnC]]
Java
grammar rpnC ; // // rpn Calculator // // Nigel Galloway - April 7th., 2012 // @members { Stack<Double> s = new Stack<Double>(); } rpn : (WS* (num|op) (WS | WS* NEWLINE {System.out.println(s.pop());}))*; num : '-'? Digit+ ('.' Digit+)? {s.push(Double.parseDouble($num.text));}; Digit : '0'..'9'; op : '-' {double x = s.pop(); s.push(s.pop() - x);} | '/' {double x = s.pop(); s.push(s.pop() / x);} | '*' {s.push(s.pop() * s.pop());} | '^' {double x = s.pop(); s.push(Math.pow(s.pop(), x));} | '+' {s.push(s.pop() + s.pop());}; WS : (' ' | '\t'){skip()}; NEWLINE : '\r'? '\n';
Produces:
>java Test
3 4 2 * 1 5 - 2 3 ^ ^ / +
^Z
3.0001220703125
AutoHotkey
{{works with|AutoHotkey_L}} Output is in clipboard.
evalRPN("3 4 2 * 1 5 - 2 3 ^ ^ / +")
evalRPN(s){
stack := []
out := "For RPN expression: '" s "'`r`n`r`nTOKEN`t`tACTION`t`t`tSTACK`r`n"
Loop Parse, s
If A_LoopField is number
t .= A_LoopField
else
{
If t
stack.Insert(t)
, out .= t "`tPush num onto top of stack`t" stackShow(stack) "`r`n"
, t := ""
If InStr("+-/*^", l := A_LoopField)
{
a := stack.Remove(), b := stack.Remove()
stack.Insert( l = "+" ? b + a
:l = "-" ? b - a
:l = "*" ? b * a
:l = "/" ? b / a
:l = "^" ? b **a
:0 )
out .= l "`tApply op " l " to top of stack`t" stackShow(stack) "`r`n"
}
}
r := stack.Remove()
out .= "`r`n The final output value is: '" r "'"
clipboard := out
return r
}
StackShow(stack){
for each, value in stack
out .= A_Space value
return subStr(out, 2)
}
{{out}}
For RPN expression: '3 4 2 * 1 5 - 2 3 ^ ^ / +'
TOKEN ACTION STACK
3 Push num onto top of stack 3
4 Push num onto top of stack 3 4
2 Push num onto top of stack 3 4 2
* Apply op * to top of stack 3 8
1 Push num onto top of stack 3 8 1
5 Push num onto top of stack 3 8 1 5
- Apply op - to top of stack 3 8 -4
2 Push num onto top of stack 3 8 -4 2
3 Push num onto top of stack 3 8 -4 2 3
^ Apply op ^ to top of stack 3 8 -4 8
^ Apply op ^ to top of stack 3 8 65536
/ Apply op / to top of stack 3 0.000122
+ Apply op + to top of stack 3.000122
The final output value is: '3.000122'
BBC BASIC
@% = &60B
RPN$ = "3 4 2 * 1 5 - 2 3 ^ ^ / +"
DIM Stack(1000)
SP% = 0
FOR i% = 1 TO LEN(RPN$)
Token$ = MID$(RPN$,i%,1)
IF Token$ <> " " THEN
PRINT Token$ " :";
CASE Token$ OF
WHEN "+": PROCpush(FNpop + FNpop)
WHEN "-": PROCpush(-FNpop + FNpop)
WHEN "*": PROCpush(FNpop * FNpop)
WHEN "/": n = FNpop : PROCpush(FNpop / n)
WHEN "^": n = FNpop : PROCpush(FNpop ^ n)
WHEN "0","1","2","3","4","5","6","7","8","9":
PROCpush(VALMID$(RPN$,i%))
WHILE ASCMID$(RPN$,i%)>=48 AND ASCMID$(RPN$,1)<=57
i% += 1
ENDWHILE
ENDCASE
FOR j% = SP%-1 TO 0 STEP -1 : PRINT Stack(j%); : NEXT
PRINT
ENDIF
NEXT i%
END
DEF PROCpush(n)
IF SP% > DIM(Stack(),1) ERROR 100, "Stack full"
Stack(SP%) = n
SP% += 1
ENDPROC
DEF FNpop
IF SP% = 0 ERROR 100, "Stack empty"
SP% -= 1
= Stack(SP%)
{{out}}
3 : 3
4 : 4 3
2 : 2 4 3
* : 8 3
1 : 1 8 3
5 : 5 1 8 3
- : -4 8 3
2 : 2 -4 8 3
3 : 3 2 -4 8 3
^ : 8 -4 8 3
^ : 65536 8 3
/ : 0.00012207 3
+ : 3.00012
Bracmat
( ( show
= line a
. \n:?line
& whl
' (!arg:%?a ?arg&!a " " !line:?line)
& put$(str$!line)
)
& :?stack
& map
$ ( (
= a b
. show$(!arg !stack)
& ( !arg
: ( "+"
| "-"
| "*"
| "/"
| "^"
)
& !stack:%?a %?b ?stack
& ( !arg:"+"&!a+!b
| !arg:"-"&-1*!a+!b
| !arg:"*"&!a*!b
| !arg:"/"&!a*!b^-1
| !a^!b
)
| !arg
)
!stack
: ?stack
)
. vap$((=.!arg).get'(,STR)." ")
)
& out$!stack
)
Input from keyboard:
3 4 2 * 1 5 - 2 3 ^ ^ / +
Output:
3
3 4
3 4 2
3 4 2 *
3 8 1
3 8 1 5
3 8 1 5 -
3 8 -4 2
3 8 -4 2 3
3 8 -4 2 3 ^
3 8 -4 9 ^
3 8 1/6561 /
3 1/52488 +
157465/52488
{!} 157465/52488
C
#include <stdio.h> #include <stdlib.h> #include <string.h> #include <math.h> void die(const char *msg) { fprintf(stderr, "%s", msg); abort(); } #define MAX_D 256 double stack[MAX_D]; int depth; void push(double v) { if (depth >= MAX_D) die("stack overflow\n"); stack[depth++] = v; } double pop() { if (!depth) die("stack underflow\n"); return stack[--depth]; } double rpn(char *s) { double a, b; int i; char *e, *w = " \t\n\r\f"; for (s = strtok(s, w); s; s = strtok(0, w)) { a = strtod(s, &e); if (e > s) printf(" :"), push(a); #define binop(x) printf("%c:", *s), b = pop(), a = pop(), push(x) else if (*s == '+') binop(a + b); else if (*s == '-') binop(a - b); else if (*s == '*') binop(a * b); else if (*s == '/') binop(a / b); else if (*s == '^') binop(pow(a, b)); #undef binop else { fprintf(stderr, "'%c': ", *s); die("unknown oeprator\n"); } for (i = depth; i-- || 0 * putchar('\n'); ) printf(" %g", stack[i]); } if (depth != 1) die("stack leftover\n"); return pop(); } int main(void) { char s[] = " 3 4 2 * 1 5 - 2 3 ^ ^ / + "; printf("%g\n", rpn(s)); return 0; }
It's also possible to parse RPN string backwards and recursively; good luck printing out your token stack ''as a table'': there isn't one.
#include <stdio.h> #include <stdlib.h> #include <ctype.h> #include <string.h> #include <math.h> #define die(msg) fprintf(stderr, msg"\n"), abort(); double get(const char *s, const char *e, char **new_e) { const char *t; double a, b; for (e--; e >= s && isspace(*e); e--); for (t = e; t > s && !isspace(t[-1]); t--); if (t < s) die("underflow"); #define get2(expr) b = get(s, t, (char **)&t), a = get(s, t, (char **)&t), a = expr a = strtod(t, (char **)&e); if (e <= t) { if (t[0] == '+') get2(a + b); else if (t[0] == '-') get2(a - b); else if (t[0] == '*') get2(a * b); else if (t[0] == '/') get2(a / b); else if (t[0] == '^') get2(pow(a, b)); else { fprintf(stderr, "'%c': ", t[0]); die("unknown token"); } } #undef get2 *(const char **)new_e = t; return a; } double rpn(const char *s) { const char *e = s + strlen(s); double v = get(s, e, (char**)&e); while (e > s && isspace(e[-1])) e--; if (e == s) return v; fprintf(stderr, "\"%.*s\": ", e - s, s); die("front garbage"); } int main(void) { printf("%g\n", rpn("3 4 2 * 1 5 - 2 3 ^ ^ / +")); return 0; }
C++
#include <vector> #include <string> #include <sstream> #include <iostream> #include <cmath> #include <algorithm> #include <iterator> #include <cstdlib> double rpn(const std::string &expr){ std::istringstream iss(expr); std::vector<double> stack; std::cout << "Input\tOperation\tStack after" << std::endl; std::string token; while (iss >> token) { std::cout << token << "\t"; double tokenNum; if (std::istringstream(token) >> tokenNum) { std::cout << "Push\t\t"; stack.push_back(tokenNum); } else { std::cout << "Operate\t\t"; double secondOperand = stack.back(); stack.pop_back(); double firstOperand = stack.back(); stack.pop_back(); if (token == "*") stack.push_back(firstOperand * secondOperand); else if (token == "/") stack.push_back(firstOperand / secondOperand); else if (token == "-") stack.push_back(firstOperand - secondOperand); else if (token == "+") stack.push_back(firstOperand + secondOperand); else if (token == "^") stack.push_back(std::pow(firstOperand, secondOperand)); else { //just in case std::cerr << "Error" << std::endl; std::exit(1); } } std::copy(stack.begin(), stack.end(), std::ostream_iterator<double>(std::cout, " ")); std::cout << std::endl; } return stack.back(); } int main() { std::string s = " 3 4 2 * 1 5 - 2 3 ^ ^ / + "; std::cout << "Final answer: " << rpn(s) << std::endl; return 0; }
{{out}}
Input Operation Stack after
3 Push 3
4 Push 3 4
2 Push 3 4 2
* Operate 3 8
1 Push 3 8 1
5 Push 3 8 1 5
- Operate 3 8 -4
2 Push 3 8 -4 2
3 Push 3 8 -4 2 3
^ Operate 3 8 -4 8
^ Operate 3 8 65536
/ Operate 3 0.00012207
+ Operate 3.00012
Final answer: 3.00012
C#
using System; using System.Collections.Generic; using System.Linq; using System.Globalization; using System.Threading; namespace RPNEvaluator { class RPNEvaluator { static void Main(string[] args) { Thread.CurrentThread.CurrentCulture = CultureInfo.InvariantCulture; string rpn = "3 4 2 * 1 5 - 2 3 ^ ^ / +"; Console.WriteLine("{0}\n", rpn); decimal result = CalculateRPN(rpn); Console.WriteLine("\nResult is {0}", result); } static decimal CalculateRPN(string rpn) { string[] rpnTokens = rpn.Split(' '); Stack<decimal> stack = new Stack<decimal>(); decimal number = decimal.Zero; foreach (string token in rpnTokens) { if (decimal.TryParse(token, out number)) { stack.Push(number); } else { switch (token) { case "^": case "pow": { number = stack.Pop(); stack.Push((decimal)Math.Pow((double)stack.Pop(), (double)number)); break; } case "ln": { stack.Push((decimal)Math.Log((double)stack.Pop(), Math.E)); break; } case "sqrt": { stack.Push((decimal)Math.Sqrt((double)stack.Pop())); break; } case "*": { stack.Push(stack.Pop() * stack.Pop()); break; } case "/": { number = stack.Pop(); stack.Push(stack.Pop() / number); break; } case "+": { stack.Push(stack.Pop() + stack.Pop()); break; } case "-": { number = stack.Pop(); stack.Push(stack.Pop() - number); break; } default: Console.WriteLine("Error in CalculateRPN(string) Method!"); break; } } PrintState(stack); } return stack.Pop(); } static void PrintState(Stack<decimal> stack) { decimal[] arr = stack.ToArray(); for (int i = arr.Length - 1; i >= 0; i--) { Console.Write("{0,-8:F3}", arr[i]); } Console.WriteLine(); } } }
{{out}}
3 4 2 * 1 5 - 2 3 ^ ^ / +
3.000
3.000 4.000
3.000 4.000 2.000
3.000 8.000
3.000 8.000 1.000
3.000 8.000 1.000 5.000
3.000 8.000 -4.000
3.000 8.000 -4.000 2.000
3.000 8.000 -4.000 2.000 3.000
3.000 8.000 -4.000 8.000
3.000 8.000 65536.000
3.000 0.000
3.000
Result is 3.0001220703125
Ceylon
ArrayList
}
shared void run() {
value ops = map { "+" -> plus<Float>, "*" -> times<Float>, "-" -> ((Float a, Float b) => a - b), "/" -> ((Float a, Float b) => a / b), "^" -> ((Float a, Float b) => a ^ b) }; void printTableRow(String|Float token, String description, {Float*} stack) { print("``token.string.padTrailing(8)````description.padTrailing(30)````stack``"); } function calculate(String input) { value stack = ArrayList<Float>(); value tokens = input.split().map((String element) => if(ops.keys.contains(element)) then element else parseFloat(element)); print("Token Operation Stack"); for(token in tokens.coalesced) { if(is Float token) { stack.push(token); printTableRow(token, "push", stack); } else if(exists op = ops[token], exists first = stack.pop(), exists second = stack.pop()) { value result = op(second, first); stack.push(result); printTableRow(token, "perform ``token`` on ``formatFloat(second, 1, 1)`` and ``formatFloat(first, 1, 1)``", stack); } else { throw Exception("bad syntax"); } } return stack.pop(); } print(calculate("3 4 2 * 1 5 - 2 3 ^ ^ / +"));
}
{{out}}
```txt
Token Operation Stack
3.0 push { 3.0 }
4.0 push { 3.0, 4.0 }
2.0 push { 3.0, 4.0, 2.0 }
* perform * on 4.0 and 2.0 { 3.0, 8.0 }
1.0 push { 3.0, 8.0, 1.0 }
5.0 push { 3.0, 8.0, 1.0, 5.0 }
- perform - on 1.0 and 5.0 { 3.0, 8.0, -4.0 }
2.0 push { 3.0, 8.0, -4.0, 2.0 }
3.0 push { 3.0, 8.0, -4.0, 2.0, 3.0 }
^ perform ^ on 2.0 and 3.0 { 3.0, 8.0, -4.0, 8.0 }
^ perform ^ on -4.0 and 8.0 { 3.0, 8.0, 65536.0 }
/ perform / on 8.0 and 65536.0 { 3.0, 1.220703125E-4 }
+ perform + on 3.0 and 0.0 { 3.0001220703125 }
3.0001220703125
Clojure
This would be a lot simpler and generic if we were allowed to use something other than ^ for exponentiation. ^ isn't a legal clojure symbol.
(ns rosettacode.parsing-rpn-calculator-algorithm (:require clojure.math.numeric-tower clojure.string clojure.pprint)) (def operators "the only allowable operators for our calculator" {"+" + "-" - "*" * "/" / "^" clojure.math.numeric-tower/expt}) (defn rpn "takes a string and returns a lazy-seq of all the stacks" [string] (letfn [(rpn-reducer [stack item] ; this takes a stack and one item and makes a new stack (if (contains? operators item) (let [operand-1 (peek stack) ; if we used lists instead of vectors, we could use destructuring, but stacks would look backwards stack-1 (pop stack)] ;we're assuming that all the operators are binary (conj (pop stack-1) ((operators item) (peek stack-1) operand-1))) (conj stack (Long. item))))] ; if it wasn't an operator, we'll assume it's a long. Could choose bigint, or even read-line (reductions rpn-reducer [] (clojure.string/split string #"\s+")))) ;reductions is like reduce only shows all the intermediate steps (let [stacks (rpn "3 4 2 * 1 5 - 2 3 ^ ^ / +")] ;bind it so we can output the answer separately. (println "stacks: ") (clojure.pprint/pprint stacks) (print "answer:" (->> stacks last first)))
{{out}} stacks: ([] [3] [3 4] [3 4 2] [3 8] [3 8 1] [3 8 1 5] [3 8 -4] [3 8 -4 2] [3 8 -4 2 3] [3 8 -4 8] [3 8 65536] [3 1/8192] [24577/8192]) answer: 24577/8192
Common Lisp
(setf (symbol-function '^) #'expt) ; Make ^ an alias for EXPT (defun print-stack (token stack) (format T "~a: ~{~a ~}~%" token (reverse stack))) (defun rpn (tokens &key stack verbose ) (cond ((and (not tokens) (not stack)) 0) ((not tokens) (car stack)) (T (let* ((current (car tokens)) (next-stack (if (numberp current) (cons current stack) (let* ((arg2 (car stack)) (arg1 (cadr stack)) (fun (car tokens))) (cons (funcall fun arg1 arg2) (cddr stack)))))) (when verbose (print-stack current next-stack)) (rpn (cdr tokens) :stack next-stack :verbose verbose)))))
{{Out}}
>(defparameter *tokens* '(3 4 2 * 1 5 - 2 3 ^ ^ / +))
*TOKENS*
> (rpn *tokens*)
24577/8192
> (rpn *tokens* :verbose T)
3: 3
4: 3 4
2: 3 4 2
*: 3 8
1: 3 8 1
5: 3 8 1 5
-: 3 8 -4
2: 3 8 -4 2
3: 3 8 -4 2 3
^: 3 8 -4 8
^: 3 8 65536
/: 3 1/8192
+: 24577/8192
24577/8192
EchoLisp
;; RPN (postfix) evaluator
(lib 'hash)
(define OPS (make-hash))
(hash-set OPS "^" expt)
(hash-set OPS "*" *)
(hash-set OPS "/" //) ;; float divide
(hash-set OPS "+" +)
(hash-set OPS "-" -)
(define (op? op) (hash-ref OPS op))
;; algorithm : https://en.wikipedia.org/wiki/Reverse_Polish_notation#Postfix_algorithm
(define (calculator rpn S)
(for ((token rpn))
(if (op? token)
(let [(op2 (pop S)) (op1 (pop S))]
(unless (and op1 op2) (error "cannot calculate expression at:" token))
(push S ((op? token) op1 op2))
(writeln op1 token op2 "→" (stack-top S)))
(push S (string->number token))))
(pop S))
(define (task rpn)
(define S (stack 'S))
(calculator (text-parse rpn) S ))
{{out}}
(task "3 4 2 * 1 5 - 2 3 ^ ^ / +")
4 * 2 → 8
1 - 5 → -4
2 ^ 3 → 8
-4 ^ 8 → 65536
8 / 65536 → 0.0001220703125
3 + 0.0001220703125 → 3.0001220703125
→ 3.0001220703125
;; RATIONAL CALCULATOR
(hash-set OPS "/" /) ;; rational divide
(task "3 4 2 * 1 5 - 2 3 ^ ^ / +")
4 * 2 → 8
1 - 5 → -4
2 ^ 3 → 8
-4 ^ 8 → 65536
8 / 65536 → 1/8192
3 + 1/8192 → 24577/8192
→ 24577/8192
Ela
open string generic monad io
type OpType = Push | Operate
deriving Show
type Op = Op (OpType typ) input stack
deriving Show
parse str = split " " str
eval stack [] = []
eval stack (x::xs) = op :: eval nst xs
where (op, nst) = conv x stack
conv "+"@x = operate x (+)
conv "-"@x = operate x (-)
conv "*"@x = operate x (*)
conv "/"@x = operate x (/)
conv "^"@x = operate x (**)
conv x = \stack ->
let n = gread x::stack in
(Op Push x n, n)
operate input fn (x::y::ys) =
let n = (y `fn` x) :: ys in
(Op Operate input n, n)
print_line (Op typ input stack) = do
putStr input
putStr "\t"
put typ
putStr "\t\t"
putLn stack
print ((Op typ input stack)@x::xs) lv = print_line x `seq` print xs (head stack)
print [] lv = lv
print_result xs = do
putStrLn "Input\tOperation\tStack after"
res <- return $ print xs 0
putStrLn ("Result: " ++ show res)
res = parse "3 4 2 * 1 5 - 2 3 ^ ^ / +" |> eval []
print_result res ::: IO
{{out}}
Input Operation Stack after
3 Push [3]
4 Push [4,3]
2 Push [2,4,3]
* Operate [8,3]
1 Push [1,8,3]
5 Push [5,1,8,3]
- Operate [-4,8,3]
2 Push [2,-4,8,3]
3 Push [3,2,-4,8,3]
^ Operate [8,-4,8,3]
^ Operate [65536,8,3]
/ Operate [0.0001220703f,3]
+ Operate [3.000122f]
Result: 3.000122f
D
{{trans|Go}}
import std.stdio, std.string, std.conv, std.typetuple; void main() { auto input = "3 4 2 * 1 5 - 2 3 ^ ^ / +"; writeln("For postfix expression: ", input); writeln("\nToken Action Stack"); real[] stack; foreach (tok; input.split()) { auto action = "Apply op to top of stack"; switch (tok) { foreach (o; TypeTuple!("+", "-", "*", "/", "^")) { case o: mixin("stack[$ - 2]" ~ (o == "^" ? "^^" : o) ~ "=stack[$ - 1];"); stack.length--; break; } break; default: action = "Push num onto top of stack"; stack ~= to!real(tok); } writefln("%3s %-26s %s", tok, action, stack); } writeln("\nThe final value is ", stack[0]); }
{{out}}
For postfix expression: 3 4 2 * 1 5 - 2 3 ^ ^ / +
Token Action Stack
3 Push num onto top of stack [3]
4 Push num onto top of stack [3, 4]
2 Push num onto top of stack [3, 4, 2]
* Apply op to top of stack [3, 8]
1 Push num onto top of stack [3, 8, 1]
5 Push num onto top of stack [3, 8, 1, 5]
- Apply op to top of stack [3, 8, -4]
2 Push num onto top of stack [3, 8, -4, 2]
3 Push num onto top of stack [3, 8, -4, 2, 3]
^ Apply op to top of stack [3, 8, -4, 8]
^ Apply op to top of stack [3, 8, 65536]
/ Apply op to top of stack [3, 0.00012207]
+ Apply op to top of stack [3.00012]
The final value is 3.00012
Erlang
-module(rpn). -export([eval/1]). parse(Expression) -> parse(string:tokens(Expression," "),[]). parse([],Expression) -> lists:reverse(Expression); parse(["+"|Xs],Expression) -> parse(Xs,[fun erlang:'+'/2|Expression]); parse(["-"|Xs],Expression) -> parse(Xs,[fun erlang:'-'/2|Expression]); parse(["*"|Xs],Expression) -> parse(Xs,[fun erlang:'*'/2|Expression]); parse(["/"|Xs],Expression) -> parse(Xs,[fun erlang:'/'/2|Expression]); parse(["^"|Xs],Expression) -> parse(Xs,[fun math:pow/2|Expression]); parse([X|Xs],Expression) -> {N,_} = string:to_integer(X), parse(Xs,[N|Expression]). %% The expression should be entered as a string of numbers and %% operators separated by spaces. No error handling is included if %% another string format is used. eval(Expression) -> eval(parse(Expression),[]). eval([],[N]) -> N; eval([N|Exp],Stack) when is_number(N) -> NewStack = [N|Stack], print(NewStack), eval(Exp,NewStack); eval([F|Exp],[X,Y|Stack]) -> NewStack = [F(Y,X)|Stack], print(NewStack), eval(Exp,NewStack). print(Stack) -> lists:map(fun (X) when is_integer(X) -> io:format("~12.12b ",[X]); (X) when is_float(X) -> io:format("~12f ",[X]) end, Stack), io:format("~n").
{{out}}
145> rpn:eval("3 4 2 * 1 5 - 2 3 ^ ^ / +").
3
4 3
2 4 3
8 3
1 8 3
5 1 8 3
-4 8 3
2 -4 8 3
3 2 -4 8 3
8.000000 -4 8 3
65536.000000 8 3
0.000122 3
3.000122
3.0001220703125
=={{header|F_Sharp|F#}}== {{trans|OCaml}}
As interactive script
let reduce op = function | b::a::r -> (op a b)::r | _ -> failwith "invalid expression" let interprete s = function | "+" -> "add", reduce ( + ) s | "-" -> "subtr", reduce ( - ) s | "*" -> "mult", reduce ( * ) s | "/" -> "divide", reduce ( / ) s | "^" -> "exp", reduce ( ** ) s | str -> "push", (System.Double.Parse str) :: s let interp_and_show s inp = let op,s'' = interprete s inp printf "%5s%8s " inp op List.iter (printf " %-6.3F") (List.rev s'') printf "\n"; s'' let eval str = printfn "Token Action Stack"; let ss = str.ToString().Split() |> Array.toList List.fold interp_and_show [] ss
{{out}}
> eval "3 4 2 * 1 5 - 2 3 ^ ^ / +";;
Token Action Stack
3 push 3.000
4 push 3.000 4.000
2 push 3.000 4.000 2.000
* mult 3.000 8.000
1 push 3.000 8.000 1.000
5 push 3.000 8.000 1.000 5.000
- subtr 3.000 8.000 -4.000
2 push 3.000 8.000 -4.000 2.000
3 push 3.000 8.000 -4.000 2.000 3.000
^ exp 3.000 8.000 -4.000 8.000
^ exp 3.000 8.000 65536.000
/ divide 3.000 0.000
+ add 3.000
val it : float list = [3.00012207]
Factor
Factor is a stack-based evaluator for an expression in reverse Polish notation. In the listener:
IN: scratchpad 3 4 2 * 1 5 - 2 3 ^ ^ / +
--- Data stack:
3+1/8192
To show intermediate steps:
{ 3 4 2 * 1 5 - 2 3 ^ ^ / + } [ 1quotation ] map
[ dup pprint bl call datastack . ] each
{{out}}
[ 3 ] { 3 }
[ 4 ] { 3 4 }
[ 2 ] { 3 4 2 }
[ * ] { 3 8 }
[ 1 ] { 3 8 1 }
[ 5 ] { 3 8 1 5 }
[ - ] { 3 8 -4 }
[ 2 ] { 3 8 -4 2 }
[ 3 ] { 3 8 -4 2 3 }
[ ^ ] { 3 8 -4 8 }
[ ^ ] { 3 8 65536 }
[ / ] { 3 1/8192 }
[ + ] { 3+1/8192 }
Fortran
Since the project is to demonstrate the workings of the scheme to evaluate a RPN text sequence, and the test example contains only single-digit numbers and single-character operators, there is no need to escalate to reading full integers or floating-point numbers, the code for which would swamp the details of the RPN evaluator. As a result, it is easy to scan the text via a DO-loop that works one character at a time since there is no backstepping, probing ahead, nor multi-symbol items that must be combined into a single "token" with states that must be remembered from one character to the next. With multi-character tokens, the scan would be changed to invocations of NEXTTOKEN that would lurch ahead accordingly.
The method is simple (the whole point of RPN) and the function prints a schedule of actions at each step. Possibly this semi-tabular output is what is meant by "as a table". Conveniently, all the operators take two operands and return one, so the SP accountancy can be shared. Unlike ! for example.
The source style is essentially F77 except for the trivial use of the PARAMETER statement, and CYCLE to GO TO the end of the loop when a space is encountered. With the introduction of unfixed-format source style came also the possible use of semicolons to cram more than one statement part on a line so that the CASE and its action statement can be spread across the page rather than use two lines in alternation: for this case a tabular layout results that is easier to read and check. Because the F90 MODULE protocol is not used, the function's type should be declared in the calling routine but the default type suffices.
REAL FUNCTION EVALRP(TEXT) !Evaluates a Reverse Polish string.
Caution: deals with single digits only.
CHARACTER*(*) TEXT !The RPN string.
INTEGER SP,STACKLIMIT !Needed for the evaluation.
PARAMETER (STACKLIMIT = 6) !This should do.
REAL*8 STACK(STACKLIMIT) !Though with ^ there's no upper limit.
INTEGER L,D !Assistants for the scan.
CHARACTER*4 DEED !A scratchpad for the annotation.
CHARACTER*1 C !The character of the moment.
WRITE (6,1) TEXT !A function that writes messages... Improper.
1 FORMAT ("Evaluation of the Reverse Polish string ",A,// !Still, it's good to see stuff.
1 "Char Token Action SP:Stack...") !Such as a heading for the trace.
SP = 0 !Commence with the stack empty.
STACK = -666 !This value should cause trouble.
DO L = 1,LEN(TEXT) !Step through the text.
C = TEXT(L:L) !Grab a character.
IF (C.LE." ") CYCLE !Boring.
D = ICHAR(C) - ICHAR("0") !Uncouth test to check for a digit.
IF (D.GE.0 .AND. D.LE.9) THEN !Is it one?
DEED = "Load" !Yes. So, load its value.
SP = SP + 1 !By going up one.
IF (SP.GT.STACKLIMIT) STOP "Stack overflow!" !Or, maybe not.
STACK(SP) = D !And stashing the value.
ELSE !Otherwise, it must be an operator.
IF (SP.LT.2) STOP "Stack underflow!" !They all require two operands.
DEED = "XEQ" !So, I'm about to do so.
SELECT CASE(C) !Which one this time?
CASE("+"); STACK(SP - 1) = STACK(SP - 1) + STACK(SP) !A + B = B + A, so it is easy.
CASE("-"); STACK(SP - 1) = STACK(SP - 1) - STACK(SP) !A is in STACK(SP - 1), B in STACK(SP)
CASE("*"); STACK(SP - 1) = STACK(SP - 1)*STACK(SP) !Again, order doesn't count.
CASE("/"); STACK(SP - 1) = STACK(SP - 1)/STACK(SP) !But for division, A/B becomes A B /
CASE("^"); STACK(SP - 1) = STACK(SP - 1)**STACK(SP) !So, this way around.
CASE DEFAULT !This should never happen!
STOP "Unknown operator!" !If the RPN script is indeed correct.
END SELECT !So much for that operator.
SP = SP - 1 !All of them take two operands and make one.
END IF !So much for that item.
WRITE (6,2) L,C,DEED,SP,STACK(1:SP) !Reveal the state now.
2 FORMAT (I4,A6,A7,I4,":",66F14.6) !Aligned with the heading of FORMAT 1.
END DO !On to the next symbol.
EVALRP = STACK(1) !The RPN string being correct, this is the result.
END !Simple enough!
PROGRAM HSILOP
REAL V
V = EVALRP("3 4 2 * 1 5 - 2 3 ^ ^ / +") !The specified example.
WRITE (6,*) "Result is...",V
END
Output...
Evaluation of the Reverse Polish string 3 4 2 * 1 5 - 2 3 ^ ^ / +
Char Token Action SP:Stack...
1 3 Load 1: 3.000000
3 4 Load 2: 3.000000 4.000000
5 2 Load 3: 3.000000 4.000000 2.000000
7 * XEQ 2: 3.000000 8.000000
9 1 Load 3: 3.000000 8.000000 1.000000
11 5 Load 4: 3.000000 8.000000 1.000000 5.000000
13 - XEQ 3: 3.000000 8.000000 -4.000000
15 2 Load 4: 3.000000 8.000000 -4.000000 2.000000
17 3 Load 5: 3.000000 8.000000 -4.000000 2.000000 3.000000
19 ^ XEQ 4: 3.000000 8.000000 -4.000000 8.000000
21 ^ XEQ 3: 3.000000 8.000000 65536.000000
23 / XEQ 2: 3.000000 0.000122
25 + XEQ 1: 3.000122
Result is... 3.000122
FunL
def evaluate( expr ) =
stack = []
for token <- expr.split( '''\s+''' )
case number( token )
Some( n ) ->
stack = n : stack
println( "push $token: ${stack.reversed()}" )
None ->
case {'+': (+), '-': (-), '*': (*), '/': (/), '^': (^)}.>get( token )
Some( op ) ->
stack = op( stack.tail().head(), stack.head() ) : stack.tail().tail()
println( "perform $token: ${stack.reversed()}" )
None -> error( "unrecognized operator '$token'" )
stack.head()
res = evaluate( '3 4 2 * 1 5 - 2 3 ^ ^ / +' )
println( res + (if res is Integer then '' else " or ${float(res)}") )
{{out}}
push 3: [3]
push 4: [3, 4]
push 2: [3, 4, 2]
perform *: [3, 8]
push 1: [3, 8, 1]
push 5: [3, 8, 1, 5]
perform -: [3, 8, -4]
push 2: [3, 8, -4, 2]
push 3: [3, 8, -4, 2, 3]
perform ^: [3, 8, -4, 8]
perform ^: [3, 8, 65536]
perform /: [3, 1/8192]
perform +: [24577/8192]
24577/8192 or 3.0001220703125
Go
No error checking.
package main import ( "fmt" "math" "strconv" "strings" ) var input = "3 4 2 * 1 5 - 2 3 ^ ^ / +" func main() { fmt.Printf("For postfix %q\n", input) fmt.Println("\nToken Action Stack") var stack []float64 for _, tok := range strings.Fields(input) { action := "Apply op to top of stack" switch tok { case "+": stack[len(stack)-2] += stack[len(stack)-1] stack = stack[:len(stack)-1] case "-": stack[len(stack)-2] -= stack[len(stack)-1] stack = stack[:len(stack)-1] case "*": stack[len(stack)-2] *= stack[len(stack)-1] stack = stack[:len(stack)-1] case "/": stack[len(stack)-2] /= stack[len(stack)-1] stack = stack[:len(stack)-1] case "^": stack[len(stack)-2] = math.Pow(stack[len(stack)-2], stack[len(stack)-1]) stack = stack[:len(stack)-1] default: action = "Push num onto top of stack" f, _ := strconv.ParseFloat(tok, 64) stack = append(stack, f) } fmt.Printf("%3s %-26s %v\n", tok, action, stack) } fmt.Println("\nThe final value is", stack[0]) }
{{out}}
For postfix "3 4 2 * 1 5 - 2 3 ^ ^ / +"
Token Action Stack
3 Push num onto top of stack [3]
4 Push num onto top of stack [3 4]
2 Push num onto top of stack [3 4 2]
* Apply op to top of stack [3 8]
1 Push num onto top of stack [3 8 1]
5 Push num onto top of stack [3 8 1 5]
- Apply op to top of stack [3 8 -4]
2 Push num onto top of stack [3 8 -4 2]
3 Push num onto top of stack [3 8 -4 2 3]
^ Apply op to top of stack [3 8 -4 8]
^ Apply op to top of stack [3 8 65536]
/ Apply op to top of stack [3 0.0001220703125]
+ Apply op to top of stack [3.0001220703125]
The final value is 3.0001220703125
Groovy
def evaluateRPN(expression) { def stack = [] as Stack def binaryOp = { action -> return { action.call(stack.pop(), stack.pop()) } } def actions = [ '+': binaryOp { a, b -> b + a }, '-': binaryOp { a, b -> b - a }, '*': binaryOp { a, b -> b * a }, '/': binaryOp { a, b -> b / a }, '^': binaryOp { a, b -> b ** a } ] expression.split(' ').each { item -> def action = actions[item] ?: { item as BigDecimal } stack.push(action.call()) println "$item: $stack" } assert stack.size() == 1 : "Unbalanced Expression: $expression ($stack)" stack.pop() }
Test
println evaluateRPN('3 4 2 * 1 5 - 2 3 ^ ^ / +')
{{out}}
3: [3]
4: [3, 4]
2: [3, 4, 2]
*: [3, 8]
1: [3, 8, 1]
5: [3, 8, 1, 5]
-: [3, 8, -4]
2: [3, 8, -4, 2]
3: [3, 8, -4, 2, 3]
^: [3, 8, -4, 8]
^: [3, 8, 65536]
/: [3, 0.0001220703125]
+: [3.0001220703125]
3.0001220703125
Haskell
Pure RPN calculator
calcRPN :: String -> [Double] calcRPN = foldl interprete [] . words interprete s x | x `elem` ["+","-","*","/","^"] = operate x s | otherwise = read x:s where operate op (x:y:s) = case op of "+" -> x + y:s "-" -> y - x:s "*" -> x * y:s "/" -> y / x:s "^" -> y ** x:s
λ> calcRPN "3 4 +"
[7.0]
λ> calcRPN "3 4 2 * 1 5 - 2 3 ^ ^ / +"
[3.0001220703125]
'''Calculation logging'''
''Pure logging''. Log as well as a result could be used as a data.
calcRPNLog :: String -> ([Double],[(String, [Double])]) calcRPNLog input = mkLog $ zip commands $ tail result where result = scanl interprete [] commands commands = words input mkLog [] = ([], []) mkLog res = (snd $ last res, res)
λ> calcRPNLog "3 4 +"
([7.0],[("3",[3.0]),("4",[4.0,3.0]),("+",[7.0])])
λ> mapM_ print $ snd $ calcRPNLog "3 4 2 * 1 5 - 2 3 ^ ^ / +"
("3",[3.0])
("4",[4.0,3.0])
("2",[2.0,4.0,3.0])
("*",[8.0,3.0])
("1",[1.0,8.0,3.0])
("5",[5.0,1.0,8.0,3.0])
("-",[-4.0,8.0,3.0])
("2",[2.0,-4.0,8.0,3.0])
("3",[3.0,2.0,-4.0,8.0,3.0])
("^",[8.0,-4.0,8.0,3.0])
("^",[65536.0,8.0,3.0])
("/",[1.220703125e-4,3.0])
("+",[3.0001220703125])
''Logging as a side effect.'' Calculator returns result in IO context:
import Control.Monad (foldM) calcRPNIO :: String -> IO [Double] calcRPNIO = foldM (verbose interprete) [] . words verbose f s x = write (x ++ "\t" ++ show res ++ "\n") >> return res where res = f s x
λ> calcRPNIO "3 4 +"
3 [3.0]
4 [4.0,3.0]
+ [7.0]
[7.0]
λ> calcRPNIO "3 4 2 * 1 5 - 2 3 ^ ^ / +"
3 [3.0]
4 [4.0,3.0]
2 [2.0,4.0,3.0]
* [8.0,3.0]
1 [1.0,8.0,3.0]
5 [5.0,1.0,8.0,3.0]
- [-4.0,8.0,3.0]
2 [2.0,-4.0,8.0,3.0]
3 [3.0,2.0,-4.0,8.0,3.0]
^ [8.0,-4.0,8.0,3.0]
^ [65536.0,8.0,3.0]
/ [1.220703125e-4,3.0]
+ [3.0001220703125]
[3.0001220703125]
Or even more general (requires FlexibleInstances and TypeFamilies extensions).
Some universal definitions:
Logger m where
write :: String -> m ()
instance Logger IO where write = putStr
instance a ~ String => Logger (Writer a) where write = tell
verbose2 f x y = write (show x ++ " " ++
show y ++ " ==> " ++
show res ++ "\n") >> return res
where res = f x y
The use case:
String -> m [Double]
calcRPNM = foldM (verbose interprete) [] . words
{{out}} in REPL
λ> calcRPNM "3 4 2 * 1 5 - 2 3 ^ ^ / +"
[] "3" ==> [3.0]
[3.0] "4" ==> [4.0,3.0]
[4.0,3.0] "2" ==> [2.0,4.0,3.0]
[2.0,4.0,3.0] "*" ==> [8.0,3.0]
[8.0,3.0] "1" ==> [1.0,8.0,3.0]
[1.0,8.0,3.0] "5" ==> [5.0,1.0,8.0,3.0]
[5.0,1.0,8.0,3.0] "-" ==> [-4.0,8.0,3.0]
[-4.0,8.0,3.0] "2" ==> [2.0,-4.0,8.0,3.0]
[2.0,-4.0,8.0,3.0] "3" ==> [3.0,2.0,-4.0,8.0,3.0]
[3.0,2.0,-4.0,8.0,3.0] "^" ==> [8.0,-4.0,8.0,3.0]
[8.0,-4.0,8.0,3.0] "^" ==> [65536.0,8.0,3.0]
[65536.0,8.0,3.0] "/" ==> [1.220703125e-4,3.0]
[1.220703125e-4,3.0] "+" ==> [3.0001220703125]
[3.0001220703125]
λ> runWriter $ calcRPNM "3 4 +"
([7.0],"[] \"3\" ==> [3.0]\n[3.0] \"4\" ==> [4.0,3.0]\n[4.0,3.0] \"+\" ==> [7.0]\n")
=={{header|Icon}} and {{header|Unicon}}==
procedure main()
EvalRPN("3 4 2 * 1 5 - 2 3 ^ ^ / +")
end
link printf
invocable all
procedure EvalRPN(expr) #: evaluate (and trace stack) an RPN string
stack := []
expr ? until pos(0) do {
tab(many(' ')) # consume previous seperator
token := tab(upto(' ')|0) # get token
if token := numeric(token) then { # ... numeric
push(stack,token)
printf("pushed numeric %i : %s\n",token,list2string(stack))
}
else { # ... operator
every b|a := pop(stack) # pop & reverse operands
case token of {
"+"|"-"|"*"|"^" : push(stack,token(a,b))
"/" : push(stack,token(real(a),b))
default : runerr(205,token)
}
printf("applied operator %s : %s\n",token,list2string(stack))
}
}
end
procedure list2string(L) #: format list as a string
every (s := "[ ") ||:= !L || " "
return s || "]"
end
{{libheader|Icon Programming Library}} [http://www.cs.arizona.edu/icon/library/src/procs/printf.icn printf.icn provides formatting]
{{out}}
pushed numeric 3 : [ 3 ]
pushed numeric 4 : [ 4 3 ]
pushed numeric 2 : [ 2 4 3 ]
applied operator * : [ 8 3 ]
pushed numeric 1 : [ 1 8 3 ]
pushed numeric 5 : [ 5 1 8 3 ]
applied operator - : [ -4 8 3 ]
pushed numeric 2 : [ 2 -4 8 3 ]
pushed numeric 3 : [ 3 2 -4 8 3 ]
applied operator ^ : [ 8 -4 8 3 ]
applied operator ^ : [ 65536 8 3 ]
applied operator / : [ 0.0001220703125 3 ]
applied operator + : [ 3.0001220703125 ]
J
This task's operations are all dyadic - having two arguments. So on each step we may either "shift" a number to the stack or "reduce" two topmost stack items to one.
Our implementation will be a monadic verb: it will take a single argument, which contains both the accumulated stack and the tokens to be processed. First, create initial state of the input:
a: , <;._1 ' ' , '3 4 2 * 1 5 - 2 3 ^ ^ / +'
┌┬─┬─┬─┬─┬─┬─┬─┬─┬─┬─┬─┬─┬─┐
││3│4│2│*│1│5│-│2│3│^│^│/│+│
└┴─┴─┴─┴─┴─┴─┴─┴─┴─┴─┴─┴─┴─┘
As an example, let's also add monadic operation _ which inverses the sign of the stack top element.
We're going to read tokens from input one by one. Each time we read a token, we're checking if it's a number - in this case we put the number to the stack - or an operation - in this case we apply the operation to the stack. The monad which returns 1 (true) for a token representing an operation and 0 (false) otherwise is "isOp". The dyad, which moves an input token to the stack, is "doShift". Applying the operation to the stack is "doApply".
There are 6 operations - one monadic "_" and five dyadic "+", "-", "*", "/", "^". For operation, we need to translate input token into operation and apply it to the stack. The dyad which converts the input token to the operation is "dispatch". It uses two miscellaneous adverbs, one for monadic operations - "mo" - and another for dyadic - "dy".
The RPN driver is the monad "consume", which handles one token. The output is the state of the program after the token was consumed - stack in the 0th box, and remaining input afterwards. As a side effect, "consume" is going to print the resulting stack, so running "consume" once for each token will produce intermediate states of the stack.
isOp=: '_+-*/^' e.~ {.@>@{.
mo=: 1 :'(}: , u@{:) @ ['
dy=: 1 :'(_2&}. , u/@(_2&{.)) @ ['
dispatch=: (-mo)`(+dy)`(-dy)`(*dy)`(%dy)`(^dy)@.('_+-*/^' i. {.@>@])
doShift=: (<@, ".@>@{.) , }.@]
doApply=: }.@] ,~ [ <@dispatch {.@]
consume=: [: ([ smoutput@>@{.) >@{. doShift`doApply@.(isOp@]) }.
consume ^: (<:@#) a: , <;._1 ' ' , '3 4 2 * 1 5 - 2 3 ^ ^ / +'
3
3 4
3 4 2
3 8
3 8 1
3 8 1 5
3 8 _4
3 8 _4 2
3 8 _4 2 3
3 8 _4 8
3 8 65536
3 0.00012207
3.00012
┌───────┐
│3.00012│
└───────┘
consume ^: (<:@#) a: , <;._1 ' ' , '3 _ 4 +'
3
_3
_3 4
1
┌─┐
│1│
└─┘
Alternate Implementation
rpn=: 3 :0
queue=. |.3 :'|.3 :y 0'::]each;: y
op=. 1 :'2 (u~/@:{.,}.)S:0 ,@]'
ops=. +op`(-op)`(*op)`(%op)`(^op)`(,&;)
choose=. ((;:'+-*/^')&i.@[)
,[email protected]/queue
)
Example use:
rpn '3 4 2 * 1 5 - 2 3 ^ ^ / +'
3.00012
To see intermediate result stacks, use this variant (the only difference is the definition of 'op'):
rpnD=: 3 :0
queue=. |.3 :'|.3 :y 0'::]each;: y
op=. 1 :'2 (u~/@:{.,}.)S:0 ,@([smoutput)@]'
ops=. +op`(-op)`(*op)`(%op)`(^op)`(,&;)
choose=. ((;:'+-*/^')&i.@[)
,[email protected]/queue
)
In other words:
rpnD '3 4 2 * 1 5 - 2 3 ^ ^ / +'
┌─────┐
│2 4 3│
└─────┘
5 1 8 3
3 2 _4 8 3
8 _4 8 3
65536 8 3
0.00012207 3
3.00012
Note that the seed stack is boxed while computed stacks are not. Note that top of stack here is on the left. Note also that adjacent constants are bundled in the parsing phase. Finally, note that the result of rpn (and of rpnD - lines previous to the last line in the rpnD example here are output and not a part of the result) is the final state of the stack - in the general case it may not contain exactly one value.
Java
{{works with|Java|1.5+}} Supports multi-digit numbers and negative numbers.
import java.util.LinkedList;
public class RPN{
public static void evalRPN(String expr){
String cleanExpr = cleanExpr(expr);
LinkedList<Double> stack = new LinkedList<Double>();
System.out.println("Input\tOperation\tStack after");
for(String token:cleanExpr.split("\\s")){
System.out.print(token+"\t");
Double tokenNum = null;
try{
tokenNum = Double.parseDouble(token);
}catch(NumberFormatException e){}
if(tokenNum != null){
System.out.print("Push\t\t");
stack.push(Double.parseDouble(token+""));
}else if(token.equals("*")){
System.out.print("Operate\t\t");
double secondOperand = stack.pop();
double firstOperand = stack.pop();
stack.push(firstOperand * secondOperand);
}else if(token.equals("/")){
System.out.print("Operate\t\t");
double secondOperand = stack.pop();
double firstOperand = stack.pop();
stack.push(firstOperand / secondOperand);
}else if(token.equals("-")){
System.out.print("Operate\t\t");
double secondOperand = stack.pop();
double firstOperand = stack.pop();
stack.push(firstOperand - secondOperand);
}else if(token.equals("+")){
System.out.print("Operate\t\t");
double secondOperand = stack.pop();
double firstOperand = stack.pop();
stack.push(firstOperand + secondOperand);
}else if(token.equals("^")){
System.out.print("Operate\t\t");
double secondOperand = stack.pop();
double firstOperand = stack.pop();
stack.push(Math.pow(firstOperand, secondOperand));
}else{//just in case
System.out.println("Error");
return;
}
System.out.println(stack);
}
System.out.println("Final answer: " + stack.pop());
}
private static String cleanExpr(String expr){
//remove all non-operators, non-whitespace, and non digit chars
return expr.replaceAll("[^\\^\\*\\+\\-\\d/\\s]", "");
}
public static void main(String[] args){
evalRPN("3 4 2 * 1 5 - 2 3 ^ ^ / +");
}
}
{{out}}
Input Operation Stack after
3 Push [3.0]
4 Push [4.0, 3.0]
2 Push [2.0, 4.0, 3.0]
* Operate [8.0, 3.0]
1 Push [1.0, 8.0, 3.0]
5 Push [5.0, 1.0, 8.0, 3.0]
- Operate [-4.0, 8.0, 3.0]
2 Push [2.0, -4.0, 8.0, 3.0]
3 Push [3.0, 2.0, -4.0, 8.0, 3.0]
^ Operate [8.0, -4.0, 8.0, 3.0]
^ Operate [65536.0, 8.0, 3.0]
/ Operate [1.220703125E-4, 3.0]
+ Operate [3.0001220703125]
Final answer: 3.0001220703125
JavaScript
var e = '3 4 2 * 1 5 - 2 3 ^ ^ / +' var s=[], e=e.split(' ') for (var i in e) { var t=e[i], n=+t if (n == t) s.push(n) else { var o2=s.pop(), o1=s.pop() switch (t) { case '+': s.push(o1+o2); break; case '-': s.push(o1-o2); break; case '*': s.push(o1*o2); break; case '/': s.push(o1/o2); break; case '^': s.push(Math.pow(o1,o2)); break; } } document.write(t, ': ', s, ' ') }
{{out}}
3: 3
4: 3,4
2: 3,4,2
*: 3,8
1: 3,8,1
5: 3,8,1,5
-: 3,8,-4
2: 3,8,-4,2
3: 3,8,-4,2,3
^: 3,8,-4,8
^: 3,8,65536
/: 3,0.0001220703125
+: 3.0001220703125
= With checks and messages =
var e = '3 4 2 * 1 5 - 2 3 ^ ^ / +' eval: { document.write(e, ' ') var s=[], e=e.split(' ') for (var i in e) { var t=e[i], n=+t if (!t) continue if (n == t) s.push(n) else { if ('+-*/^'.indexOf(t) == -1) { document.write(t, ': ', s, ' ', 'Unknown operator! ') break eval } if (s.length<2) { document.write(t, ': ', s, ' ', 'Insufficient operands! ') break eval } var o2=s.pop(), o1=s.pop() switch (t) { case '+': s.push(o1+o2); break case '-': s.push(o1-o2); break case '*': s.push(o1*o2); break case '/': s.push(o1/o2); break case '^': s.push(Math.pow(o1,o2)) } } document.write(t, ': ', s, ' ') } if (s.length>1) { document.write('Insufficient operators! ') } }
{{out}}
3 4 2 * 1 5 - 2 3 ^ ^ / +
3: 3
4: 3,4
2: 3,4,2
*: 3,8
1: 3,8,1
5: 3,8,1,5
-: 3,8,-4
2: 3,8,-4,2
3: 3,8,-4,2,3
^: 3,8,-4,8
^: 3,8,65536
/: 3,0.0001220703125
+: 3.0001220703125
Julia
(This code takes advantage of the fact that all of the operands and functions in the specified RPN syntax are valid Julia expressions, so we can use the built-in parse
and eval
functions to turn them into numbers and the corresponding Julia functions.)
function rpn(s) stack = Any[] for op in map(eval, map(parse, split(s))) if isa(op, Function) arg2 = pop!(stack) arg1 = pop!(stack) push!(stack, op(arg1, arg2)) else push!(stack, op) end println("$op: ", join(stack, ", ")) end length(stack) != 1 && error("invalid RPN expression $s") return stack[1] end rpn("3 4 2 * 1 5 - 2 3 ^ ^ / +")
{{out}}
3: 3
4: 3, 4
2: 3, 4, 2
*: 3, 8
1: 3, 8, 1
5: 3, 8, 1, 5
-: 3, 8, -4
2: 3, 8, -4, 2
3: 3, 8, -4, 2, 3
^: 3, 8, -4, 8
^: 3, 8, 65536
/: 3, 0.0001220703125
+: 3.0001220703125
(The return value is also 3.0001220703125
.)
Kotlin
// version 1.1.2 fun rpnCalculate(expr: String) { if (expr.isEmpty()) throw IllegalArgumentException("Expresssion cannot be empty") println("For expression = $expr\n") println("Token Action Stack") val tokens = expr.split(' ').filter { it != "" } val stack = mutableListOf<Double>() for (token in tokens) { val d = token.toDoubleOrNull() if (d != null) { stack.add(d) println(" $d Push num onto top of stack $stack") } else if ((token.length > 1) || (token !in "+-*/^")) { throw IllegalArgumentException("$token is not a valid token") } else if (stack.size < 2) { throw IllegalArgumentException("Stack contains too few operands") } else { val d1 = stack.removeAt(stack.lastIndex) val d2 = stack.removeAt(stack.lastIndex) stack.add(when (token) { "+" -> d2 + d1 "-" -> d2 - d1 "*" -> d2 * d1 "/" -> d2 / d1 else -> Math.pow(d2, d1) }) println(" $token Apply op to top of stack $stack") } } println("\nThe final value is ${stack[0]}") } fun main(args: Array<String>) { val expr = "3 4 2 * 1 5 - 2 3 ^ ^ / +" rpnCalculate(expr) }
{{out}}
For expression = 3 4 2 * 1 5 - 2 3 ^ ^ / +
Token Action Stack
3.0 Push num onto top of stack [3.0]
4.0 Push num onto top of stack [3.0, 4.0]
2.0 Push num onto top of stack [3.0, 4.0, 2.0]
* Apply op to top of stack [3.0, 8.0]
1.0 Push num onto top of stack [3.0, 8.0, 1.0]
5.0 Push num onto top of stack [3.0, 8.0, 1.0, 5.0]
- Apply op to top of stack [3.0, 8.0, -4.0]
2.0 Push num onto top of stack [3.0, 8.0, -4.0, 2.0]
3.0 Push num onto top of stack [3.0, 8.0, -4.0, 2.0, 3.0]
^ Apply op to top of stack [3.0, 8.0, -4.0, 8.0]
^ Apply op to top of stack [3.0, 8.0, 65536.0]
/ Apply op to top of stack [3.0, 1.220703125E-4]
+ Apply op to top of stack [3.0001220703125]
The final value is 3.0001220703125
Liberty BASIC
global stack$
expr$ = "3 4 2 * 1 5 - 2 3 ^ ^ / +"
print "Expression:"
print expr$
print
print "Input","Operation","Stack after"
stack$=""
token$ = "#"
i = 1
token$ = word$(expr$, i)
token2$ = " "+token$+" "
do
print "Token ";i;": ";token$,
select case
'operation
case instr("+-*/^",token$)<>0
print "operate",
op2$=pop$()
op1$=pop$()
if op1$="" then
print "Error: stack empty for ";i;"-th token: ";token$
end
end if
op1=val(op1$)
op2=val(op2$)
select case token$
case "+"
res = op1+op2
case "-"
res = op1-op2
case "*"
res = op1*op2
case "/"
res = op1/op2
case "^"
res = op1^op2
end select
call push str$(res)
'default:number
case else
print "push",
call push token$
end select
print "Stack: ";reverse$(stack$)
i = i+1
token$ = word$(expr$, i)
token2$ = " "+token$+" "
loop until token$ =""
res$=pop$()
print
print "Result:" ;res$
extra$=pop$()
if extra$<>"" then
print "Error: extra things on a stack: ";extra$
end if
end
'---------------------------------------
function reverse$(s$)
reverse$ = ""
token$="#"
while token$<>""
i=i+1
token$=word$(s$,i,"|")
reverse$ = token$;" ";reverse$
wend
end function
'---------------------------------------
sub push s$
stack$=s$+"|"+stack$ 'stack
end sub
function pop$()
'it does return empty on empty stack
pop$=word$(stack$,1,"|")
stack$=mid$(stack$,instr(stack$,"|")+1)
end function
{{out}}
Expression:
3 4 2 * 1 5 - 2 3 ^ ^ / +
Input Operation Stack after
Token 1: 3 push Stack: 3
Token 2: 4 push Stack: 3 4
Token 3: 2 push Stack: 3 4 2
Token 4: * operate Stack: 3 8
Token 5: 1 push Stack: 3 8 1
Token 6: 5 push Stack: 3 8 1 5
Token 7: - operate Stack: 3 8 -4
Token 8: 2 push Stack: 3 8 -4 2
Token 9: 3 push Stack: 3 8 -4 2 3
Token 10: ^ operate Stack: 3 8 -4 8
Token 11: ^ operate Stack: 3 8 65536
Token 12: / operate Stack: 3 0.12207031e-3
Token 13: + operate Stack: 3.00012207
Result:3.00012207
Lua
local stack = {} function push( a ) table.insert( stack, 1, a ) end function pop() if #stack == 0 then return nil end return table.remove( stack, 1 ) end function writeStack() for i = #stack, 1, -1 do io.write( stack[i], " " ) end print() end function operate( a ) local s if a == "+" then push( pop() + pop() ) io.write( a .. "\tadd\t" ); writeStack() elseif a == "-" then s = pop(); push( pop() - s ) io.write( a .. "\tsub\t" ); writeStack() elseif a == "*" then push( pop() * pop() ) io.write( a .. "\tmul\t" ); writeStack() elseif a == "/" then s = pop(); push( pop() / s ) io.write( a .. "\tdiv\t" ); writeStack() elseif a == "^" then s = pop(); push( pop() ^ s ) io.write( a .. "\tpow\t" ); writeStack() elseif a == "%" then s = pop(); push( pop() % s ) io.write( a .. "\tmod\t" ); writeStack() else push( tonumber( a ) ) io.write( a .. "\tpush\t" ); writeStack() end end function calc( s ) local t, a = "", "" print( "\nINPUT", "OP", "STACK" ) for i = 1, #s do a = s:sub( i, i ) if a == " " then operate( t ); t = "" else t = t .. a end end if a ~= "" then operate( a ) end print( string.format( "\nresult: %.13f", pop() ) ) end --[[ entry point ]]-- calc( "3 4 2 * 1 5 - 2 3 ^ ^ / +" ) calc( "22 11 *" )
{{out}}
INPUT OP STACK
3 push 3
4 push 3 4
2 push 3 4 2
* mul 3 8
1 push 3 8 1
5 push 3 8 1 5
- sub 3 8 -4
2 push 3 8 -4 2
3 push 3 8 -4 2 3
^ pow 3 8 -4 8
^ pow 3 8 65536
/ div 3 0.0001220703125
+ add 3.0001220703125
result: 3.0001220703125
INPUT OP STACK
22 push 22
11 push 22 11
* mul 242
result: 242.0000000000000
M2000 Interpreter
Module Rpn_Calc {
Rem Form 80,60
function rpn_calc(a$) {
def m=0
dim token$()
token$()=piece$(a$," ")
l=len(token$())
dim type(l)=0, reg(l)
where=-1
for i=0 to l-1
c=val(token$(i),"",m)
if m>-1 then
where++
reg(where)=c
else
reg(where-1)=eval(str$(reg(where-1))+token$(i)+str$(reg(where)))
where--
end if
inf=each(reg(),1, where+1)
while inf
export$<=token$(i)+" ["+str$(inf^,"")+"] "+ str$(array(inf))+{
}
token$(i)=" "
end while
next i
=reg(0)
}
Global export$
document export$
example1=rpn_calc("3 4 2 * 1 5 - 2 3 ^ ^ / +")
example2=rpn_calc("1 2 + 3 4 + ^ 5 6 + ^")
Print example1, example2
Rem Print #-2, Export$
ClipBoard Export$
}
Rpn_Calc
{{out}}
3 [0] 3 4 [0] 3 [1] 4 2 [0] 3 [1] 4 [2] 2 * [0] 3 [1] 8 1 [0] 3 [1] 8 [2] 1 5 [0] 3 [1] 8 [2] 1 [3] 5 - [0] 3 [1] 8 [2] -4 2 [0] 3 [1] 8 [2] -4 [3] 2 3 [0] 3 [1] 8 [2] -4 [3] 2 [4] 3 ^ [0] 3 [1] 8 [2] -4 [3] 8 ^ [0] 3 [1] 8 [2] 65536 / [0] 3 [1] .0001220703125 + [0] 3.0001220703125 1 [0] 1 2 [0] 1 [1] 2 + [0] 3 3 [0] 3 [1] 3 4 [0] 3 [1] 3 [2] 4 + [0] 3 [1] 7 ^ [0] 2187 5 [0] 2187 [1] 5 6 [0] 2187 [1] 5 [2] 6 + [0] 2187 [1] 11 ^ [0] 5.47440108942022E+36## Mathematica (This code takes advantage of the fact that all of the operands and functions in the specified RPN syntax can be used to form valid Mathematica expressions, so we can use the built-in ToExpression function to turn them into numbers and the corresponding Mathematica functions. Note that we need to add braces around arguments, otherwise "-4^8" would be parsed as "-(4^8)" instead of "(-4)^8".) ```Mathematica calc[rpn_] := Module[{tokens = StringSplit[rpn], s = "(" <> ToString@InputForm@# <> ")" &, op, steps}, op[o_, x_, y_] := ToExpression[s@x <> o <> s@y]; steps = FoldList[Switch[#2, _?DigitQ, Append[#, FromDigits[#2]], _, Append[#[[;; -3]], op[#2, #[[-2]], #[[-1]]]] ] &, {}, tokens][[2 ;;]]; Grid[Transpose[{# <> ":" & /@ tokens, StringRiffle[ToString[#, InputForm] & /@ #] & /@ steps}]]]; Print[calc["3 4 2 * 1 5 - 2 3 ^ ^ / +"]]; ``` {{out}} ```txt 3: 3 4: 3 4 2: 3 4 2 *: 3 8 1: 3 8 1 5: 3 8 1 5 -: 3 8 -4 2: 3 8 -4 2 3: 3 8 -4 2 3 ^: 3 8 -4 8 ^: 3 8 65536 /: 3 1/8192 +: 24577/8192 ``` ## Maxima ```Maxima rmod(i, j) := mod(j, i)$ rpow(x, y) := y^x$ rpn(sexpr) := ( operands: [], expr: charlist(sexpr), for token in expr do ( if token = "+" then ( push(pop(operands) + pop(operands), operands) ) elseif token = "-" then ( push(-1 * (pop(operands) - pop(operands)), operands) ) elseif token = "*" then ( push(pop(operands) * pop(operands), operands) ) elseif token = "/" then ( push(1 / (pop(operands) / pop(operands)), operands) ) elseif token = "%" then ( push(rmod(pop(operands), pop(operands)), operands) ) elseif token = "^" then ( push(rpow(pop(operands), pop(operands)), operands) ) elseif token # " " then ( push(parse_string(token), operands) ), if token # " " then ( print(token, " : ", operands) ) ), pop(operands) )$ rpn("3 4 2 * 1 5 - 2 3 ^ ^ / +"), numer; ``` ### Output
sed
and pipes the result back hither.
```parigp
estack = [];
epush(x) = {
estack = vector(#estack + 1, i, if(i <= #estack, estack[i], x));
return(#estack);
};
epop() = {
local(val = estack[#estack]);
estack = vector(#estack - 1, i, estack[i]);
return(val);
};
registerRPNToken(t) = {
local(o1, o2);
if(type(t) == "t_STR",
if(t == "+", o2 = epop(); o1 = epop(); epush(o1 + o2),
if(t == "-", o2 = epop(); o1 = epop(); epush(o1 - o2),
if(t == "*", o2 = epop(); o1 = epop(); epush(o1 * o2),
if(t == "/", o2 = epop(); o1 = epop(); epush(o1 / o2),
if(t == "%", o2 = epop(); o1 = epop(); epush(o1 % o2),
if(t == "^", o2 = epop(); o1 = epop(); epush(o1 ^ o2)
)))))),
if(type(t) == "t_INT" || type(t) == "t_REAL" || type(t) == "t_FRAC",
epush(t))
);
print(estack);
};
parseRPN(s) = {
estack = [];
for(i = 1, #s, registerRPNToken(s[i]));
if(#estack > 1, error("Malformed postfix expression."));
return(estack[1]);
};
parseRPN([3, 4, 2, "*", 1, 5, "-", 2, 3, "^", "^", "/", "+"]); \\ Our input expression
```
### Output
24577/8192
yields 3.0001220703125
as expected.
## Perl
```perl
use strict;
use warnings;
use feature 'say';
my $number = '[+-]?(?:\.\d+|\d+(?:\.\d*)?)';
my $operator = '[-+*/^]';
my @tests = ('3 4 2 * 1 5 - 2 3 ^ ^ / +');
for (@tests) {
while (
s/ \s* ((?^
, so we have to use **
instead. Note that this is not two separate stars, although that's what it looks like: you have to enter it by typing SHIFT
+H
.
No attempt is made to check for invalid syntax, stack overflow or underflow, etc.
```basic
10 DIM S(5)
20 LET P=1
30 INPUT E$
40 LET I=0
50 LET I=I+1
60 IF E$(I)=" " THEN GOTO 110
70 IF I*
within the argument string needs to be escaped or quoted, otherwise the shell will interpret and expand it.
Technically, this implementation uses a string to represent a stack and lines to delimit each item of the stack, not spaces as you might expect. However, the input is parsed pretty much as a space-separated argument string, but only with the asterisk quoted.
```bash
#!/bin/sh
exp() {
R=1
local i=1
while [ $i -le $2 ]; do
R=$(($R * $1))
i=$(($i + 1))
done
}
rpn() {
local O1 O2 stack
while [ $# -ge 1 ]; do
grep -iE '^-?[0-9]+$' <<< "$1" > /dev/null 2>&1
if [ "$?" -eq 0 ]; then
stack=`sed -e '$a'"$1" -e '/^$/d' <<< "$stack"`
else
grep -iE '^[-\+\*\/\%\^]$' <<< "$1" > /dev/null 2>&1
if [ "$?" -eq 0 ]; then
O2=`sed -n '$p' <<< "$stack"`
stack=`sed '$d' <<< "$stack"`
O1=`sed -n '$p' <<< "$stack"`
case "$1" in
'+')
stack=`sed -e '$a'"$(($O1 + $O2))" -e '/^$/d' -e '$d' \
<<< "$stack"`;;
'-')
stack=`sed -e '$a'"$(($O1 - $O2))" -e '/^$/d' -e '$d' \
<<< "$stack"`;;
'*')
stack=`sed -e '$a'"$(($O1 * $O2))" -e '/^$/d' -e '$d' \
<<< "$stack"`;;
'/')
stack=`sed -e '$a'"$(($O1 / $O2))" -e '/^$/d' -e '$d' \
<<< "$stack"`;;
'%')
stack=`sed -e '$a'"$(($O1 % $O2))" -e '/^$/d' -e '$d' \
<<< "$stack"`;;
'^')
exp $O1 $O2
stack=`sed -e '$a'"$(($R))" -e '/^$/d' -e '$d' <<< \
"$stack"`;;
esac
else
echo "Unknown RPN token \`\`$1''"
fi
fi
echo "$1" ":" $stack
shift
done
sed -n '1p' <<< "$stack"
if [ "`wc -l <<< "$stack"`" -gt 1 ]; then
echo "Malformed input expression" > /dev/stderr
return 1
else
return 0
fi
}
rpn 3 4 2 '*' 1 5 '-' 2 3 '^' '^' '/' '+'
```
### Output