PLACE
spec
solutions
Oberon

RPN Calculator in Oberon

The program is written in Oberon-2, currently the most widely implemented version of the language. It is contained in a module, which is the compilation unit in Oberon. The very first line is a pseudo-comment marking the module's body as an entry point of a (the) program's execution.

The module's body, which is the main part of the program (near its end) calls the procedure readln to obtain a text line from the standard input. The line is stored in a dynamically allocated buffer pointed to by p. If non-empty, it is processed by the function evalrpn, which returns TRUE or FALSE to distinguish a successfully computed RPN expression from one that turns to be syntactically erroneous.

As Oberon has no standard library and no built-in I/O facilities, for communicating with the console the program makes use of the modules In and Out, defined in the so called ‘Oakwood guidelines for Oberon-2’. Among other things, the said document provides, albeit unofficially, a ‘standard’ library for the language which is indeed present in most Oberon-2 implementations.

The readln procedure accepts the input a character at a time. Tab characters (09X) are changed to spaces. If the size of the current input buffer becomes insufficient, a twice as large buffer is allocated, the contents of the current buffer are copied into it, and p is pointed at the new buffer, while the old one gets garbage-collected. Upon end-of-line, which is signified by the character 0AX (ASCII Line Feed), the procedure returns. It is made sure that if only whitespace was input, the character count nc is 0, so that the main program knows that the line was empty. If no more input at all is available (In.Done is false), the built-in procedure HALT is called to terminate the program. Note that the loop in the main program is itself infinite: it is readln through calling HALT that ensures the program's termination.

The function procedure evalrpn extracts tokens in sequence, examines each one to determine whether it is an arithmetic operator or a number, and takes corresponding actions. It maintaines a stack stk in which it places the numeric value of a token or the result of an operation. The stack is a dynamically allocated array of sufficiently large size, based on the length of the input line being processed. The array is being reused across invocations of evalrpn for different RPN expressions: a new array is only allocated when there is a risk that the current one is not large enough to accomodate the amount of intermediate values for some new expression.

The individual tokens are not actually being extracted in evalrpn. A ‘token’ is just a portion of the character sequence pointed at by p, starting at position i and ending at position j-1 in that sequence. The function procedure getNumber which tells evalrpn whether a token is a number and computes that number, being local to evalrpn uses the values of i and j directly rather than receiving them as parameter values. getNumber processes a token by accumulating a numeric value from the digits in it and accounting for whether and where there are a decimal dot and an arithmetic sign. The result is stored in the evalrpn's variable x. That variable's value eventually gets stored onto the stack as evalrpn calls push (which also happens with x being the result of an arithmetic operator evaluation).

For character sequences that do not parse as numbers getNumber returns FALSE, which evalrpn re-sends to its own caller. evalrpn also returns FALSE if stk lacks one or both needed arguments for an arithmetic operator, or if it stores more than one number when the expression evaluation ends. Thus all cases of incorrect RPN expression syntax are properly detected and the main program gets informed that the expression evaluation failed.

•   •   •

As Oberon descends from Pascal, it is not unreasonable to draw parallels between the implementations of the RPN calculator in the two languages. In several ways the one in Oberon is simpler and its structure better reflects the problem than that in Pascal, due to the higher expressive level of the more recent language. Still, the two programs are of very similar size, in fact being among the largest in this collection. The level of verbosity seems to have somehow remained constant through the evolution of Pascal.

<* MAIN+ *>
MODULE rpn;
IMPORT In,Out;

TYPE PString = POINTER TO ARRAY OF CHAR;

VAR p: PString;
    stk: POINTER TO ARRAY OF REAL;
    bufsz,nc,stksz: INTEGER;

PROCEDURE readln;
  VAR c: CHAR;
      i: INTEGER;
      q: PString;
BEGIN
  nc := 0;
  LOOP
    In.Char(c);
    IF ~In.Done THEN HALT(0)
    ELSIF c=0AX THEN RETURN
    ELSIF c=09X THEN c := " "
    END;
    IF (nc>0) OR (c#" ") THEN
      IF nc=bufsz THEN
        bufsz := 2*bufsz;
        NEW(q,bufsz);
        FOR i:= 0 TO nc-1 DO q^[i] := p^[i] END;
        p := q
      END;
      p^[nc] := c;
      INC(nc)
    END
  END
END readln;

PROCEDURE evalrpn(): BOOLEAN;
  VAR nstk,i,j: INTEGER;
      x,y: REAL;
      c: CHAR;

PROCEDURE getNumber(): BOOLEAN;
  VAR k,s,dp: INTEGER;
BEGIN
  s := 1;
  IF (c="+") OR (c="-") THEN
    IF c="-" THEN s := -1 END;
    INC(i)
  END;
  x := 0.;  dp := -1;
  FOR k:=i TO j-1 DO
    CASE p^[k] OF
      "0".."9": x := 10*x+ORD(p^[k])-ORD("0")
    |      ".": IF dp=-1 THEN dp := k ELSE RETURN FALSE END
    ELSE RETURN FALSE
    END
  END;
  k := j-i;  IF dp>=0 THEN DEC(k) END;
  IF k=0 THEN RETURN FALSE END;
  IF dp>=0 THEN
    FOR k:=1 TO j-dp-1 DO x := x/10 END
  END;
  x := s*x;
  RETURN TRUE
END getNumber;

PROCEDURE push;
BEGIN stk^[nstk] := x;  INC(nstk) END push;

PROCEDURE pop(): REAL;
BEGIN DEC(nstk);  RETURN stk[nstk] END pop;

BEGIN  (* evalrpn *)
  i := 1 + nc DIV 2;
  IF stksz<i THEN stksz := i;  NEW(stk,stksz) END;
  nstk := 0;
  i := 0;
  LOOP
    WHILE (i<nc) & (p^[i]=" ") DO INC(i) END;
    IF i=nc THEN RETURN nstk=1 END;
    j := i;
    WHILE (j<nc) & (p^[j]#" ") DO INC(j) END;
    c := p^[i];
    IF (j=i+1) & ((c="+") OR (c="-") OR (c="*") OR (c="/")) THEN
      IF nstk<2 THEN RETURN FALSE END;
      y := pop();  x := pop();
      CASE c OF "+": x := x+y | "-": x := x-y
              | "*": x := x*y | "/": x := x/y END
    ELSIF ~getNumber() THEN
      RETURN FALSE
    END;
    push;
    i := j
  END
END evalrpn;

BEGIN  (* main *)
  bufsz := 100;  NEW(p,bufsz);
  stksz := 0;
  In.Open;  Out.Open;
  LOOP
    readln;
    IF nc>0 THEN
      IF evalrpn() THEN Out.Real(stk[0],0) ELSE Out.String("error") END;
      Out.Ln
    END
  END
END rpn.

boykobbatgmaildotcom