Computer Science 3 - 2003

Programming Language Translation


Practical for Weeks 25 - 26, beginning 13 October 2003 - solutions

Sources of full solutions for these problems may be found on the course web page as the file PRAC25A.ZIP.


Task 2 - Better use of the debugging pragma

The extra pragmas needed in the refined Parva compiler are easily introduced. We need some static fields:

  public static boolean
    debug = false,
    optimize = false,
    listCode = false,
    warnings = true;

The definitions of the pragmas are done in terms of these:

  PRAGMAS
    WarnOn      = "$W+" .         (. warnings = true; .)
    WarnOff     = "$W-" .         (. warnings = false; .)
    CodeOn      = "$C+" .         (. listCode = true; .)
    CodeOff     = "$C-" .         (. listCode = false; .)

It is convenient to be able to set the options with command line parameters as well. This involves a straightforward change to the Parva.frame file:

  for (int i = 0; i < args.length; i++) {
    if (args[i].toLowerCase().equals("-l") && !mergeErrors) {
      mergeErrors = true;
      ErrorHandler = new MergeErrors(); // Merge error messages in listing
      Trace.Init();
    }
    else if (args[i].toLowerCase().equals("-d")) {
      Parser.debug = true;
    }
    else if (args[i].toLowerCase().equals("-w")) {
      Parser.warnings = false;                          // Addition
    }
    else if (args[i].toLowerCase().equals("-c")) {
      Parser.listCode = true;                           // Addition
    }
    else inputName = args[i];
  }

Finally, the following change to the frame file gives the option of suppressing the generation of the .COD listing.

  if (Parser.listCode) PVM.listCode(codeName, codeLength);


Task 3 - How long is a piece of string?

The prac sheet asked why languages generally impose a restriction that a literal string must be contained on a single line of code. The reason is quite simple - it becomes difficult to see or track the control characters and spaces that would otherwise be buried in the string. It is easier and safer for language designers to use the escape sequence idea if they need to cater for non-graphic characters in strings and character literals.

Concatenating strings is simple. The place to do it is in the StringConst production which calls on a OneString parser to obtain the substrings (which have had their leading quotes and internal escape characters processed by the time the concatenation takes place):

  StringConst<^String str>              (. String str2; .)
  = OneString<^str>
    { [ "+" ] OneString<^str2>          (. str = str + str2; .)
    } .

  OneString<^String str>
  =  stringLit                          (. str = token.str;
                                           str = unescape(str.substring(1, str.length()-1)); .)
  .


Task 4 - Things are not always what they seem


Task 5 - Detecting other meaningless forms of code

A joint answer seems in order. Spotting the empty statement in the form of a stray semicolon is only part of the solution. Detecting blocks that really have no effect might be handled in several ways. The suggestion below counts the executable statements in a Block. This means that the Statement parser has to be attributed so as to return this count, and this has a knock-on effect in various other productions as well. Since we might have all sorts of nonsense like

    { { int k; } { { int j; } int i; } }

counting has to proceed carefully. Once you have started seeing how stupid some code can be, you can probably develop a flare for writing stupid code suitable for testing compilers without asking your friends in CSC 102 to do it for you!

  Statement<^int execCount, StackFrame frame>
                                        (. execCount = 0; .)
  =  SYNC (   Block<^execCount, frame>
            | ConstDeclarations
            | VarDeclarations<frame>
            | ";"                       (. if (warnings) Warning("empty statement"); .)
            |                           (. execCount = 1; .)
              ( Assignment
                | IfStatement<frame>
                | WhileStatement<frame>
                | DoWhileStatement<frame>
                | ForStatement<frame>
                | BreakStatement
                | ContinueStatement
                | HaltStatement
                | ReturnStatement
                | ReadStatement
                | WriteStatement
                | "stackdump" ";"       (. if (debug) CodeGen.dump(); .)
              )
          ) .

  Block<^int execCount, StackFrame frame>
  =                                     (. int count = 0;
                                           execCount = 0;
                                           Table.openScope(); .)
     "{"
     { Statement<^count, frame>         (. execCount += count; .)
     }
     WEAK "}"                           (. if (execCount == 0 && warnings)
                                             Warning("no executable statements in block");
                                           if (debug) Table.printTable(OutFile.StdOut);
                                           Table.closeScope(); .)
  .

A similar modification is needed in the Parva production, which you can study in the full source code.


Task 6 - Suppressing some error messages

The suggestion was made that when an identifier was not found in the symbol table, a suitable entry could quietly be inserted into the table in the hope of reducing the number of irritating "undeclared identifier" messages that might otherwise pop up. This is quite easily done from within the production for Designator. Note the way in which we modify the newly inserted entry if we establish that the undeclared identifier appears to be of a reference type.

  Designator<^DesType des>              (. String name;
                                           int indexType; .)
  =  Ident<^name>                       (. Entry entry = Table.find(name);
                                           boolean notDeclared = !entry.found;
                                           if (notDeclared) {
                                             SemError("undeclared identifier");
                                             entry = new Entry(); // new is critical
                                             entry.name = name;
                                             entry.kind = Entry.Var;
                                             entry.type = Entry.noType;
                                             entry.offset = 0;
                                             Table.insert(entry);
                                           }
                                           des = new DesType(entry);
                                           if (entry.kind == Entry.Var)
                                             CodeGen.loadAddress(entry); .)
     [  "["                             (. if (notDeclared) entry.type++;
                                           else if (isRef(des.type)) des.type--;
                                           else SemError("unexpected subscript");
                                           if (entry.kind != Entry.Var)
                                             SemError("unexpected subscript");
                                           CodeGen.dereference(); .)
            Expression<^indexType>      (. if (!isArith(indexType))
                                             SemError("invalid subscript type");
                                           CodeGen.index(); .)
        "]"
     ] .


Task 7 - Some simple statement extensions

The extensions to the WriteStatement and HaltStatement are very simple:

  WriteStatement                        (. boolean addLineMark = false; .)
  = (   "write"
      | "writeLine"                     (. addLineMark = true; .)
    ) "(" WriteElement
    { WEAK "," WriteElement }
    ")" WEAK ";"                        (. if (addLineMark) CodeGen.writeLine(); .)
    .

  HaltStatement                         (. String str; .)
  =  "halt"
     [ "(" StringConst<^str>            (. CodeGen.writeString(str); .)
       ")" ]                            (. CodeGen.leaveProgram(); .)
     WEAK ";" .


Task 8 - Let's operate like C

This was the biggest "hack" in this practical, but was hopefully straightforward, since you had been given the unattributed grammar in which the required operator precedence levels had already been sorted out for you. The code follows:

  Expression<^int type>                 (. int type2;
                                           Label shortcircuit = new Label(!known); .)
  =  AndExp<^type>
     { "||"                             (. CodeGen.booleanOp(shortcircuit, CodeGen.or); .)
       AndExp<^type2>                   (. if (!isBool(type) || !isBool(type2))
                                             SemError("boolean operands required");
                                           type = Entry.boolType; .)
     }                                  (. shortcircuit.here(); .)
  .


  AndExp<^int type>                     (. int type2;
                                           Label shortcircuit = new Label(!known); .)
  =  EqlExp<^type>
     { "&&"                             (. CodeGen.booleanOp(shortcircuit, CodeGen.and); .)
       EqlExp<^type2>                   (. if (!isBool(type) || !isBool(type2))
                                             SemError("boolean operands required");
                                           type = Entry.boolType; .)
     }                                  (. shortcircuit.here(); .)
  .


  EqlExp<^int type>                     (. int type2;
                                           int op; .)
  =  RelExp<^type>
     { EqualOp<^op>
       RelExp<^type2>                   (. if (!compatible(type, type2))
                                             SemError("incomparable operands");
                                           type = Entry.boolType; CodeGen.comparison(op); .)
     } .

  RelExp<^int type>                     (. int type2;
                                           int op; .)
  =  AddExp<^type>
     [ RelOp<^op>
       AddExp<^type2>                   (. if (!isArith(type) || !isArith(type2))
                                             SemError("incomparable operands");
                                           type = Entry.boolType; CodeGen.comparison(op); .)
     ] .

  AddExp<^int type>                     (. int type2;
                                           int op; .)
  =  MultExp<^type>
     { AddOp<^op>
       MultExp<^type2>                  (. if (!isArith(type) || !isArith(type2)) {
                                             SemError("arithmetic operands required");
                                             type = Entry.noType;
                                           }
                                           CodeGen.binaryOp(op); .)
     } .

  MultExp<^int type>                    (. int type2;
                                           int op; .)
  =  Factor<^type>
     { MulOp<^op>
       Factor<^type2>                   (. if (!isArith(type) || !isArith(type2)) {
                                             SemError("arithmetic operands required");
                                             type = Entry.noType;
                                           }
                                           CodeGen.binaryOp(op); .)
     } .

  Factor<^int type>                     (. type = Entry.noType; .)
  =    Primary<^type>
     | "+" Factor<^type>                (. if (!isArith(type)) {
                                             SemError("arithmetic operand required");
                                             type = Entry.noType;
                                           } .)
     | "-" Factor<^type>                (. if (!isArith(type)) {
                                             SemError("arithmetic operand required");
                                             type = Entry.noType;
                                           }
                                           CodeGen.negateInteger(); .)
     | "!" Factor<^type>                (. if (!isBool(type))
                                             SemError("boolean operand required");
                                           type = Entry.boolType; CodeGen.negateBoolean(); .)
  .

  Primary<^int type>                    (. int value = 0;
                                           type = Entry.noType;
                                           int size;
                                           DesType des;
                                           ConstRec con; .)
  =    Designator<^des>                 (. type = des.type;
                                           switch (des.entry.kind) {
                                             case Entry.Var:
                                               CodeGen.dereference();
                                               break;
                                             case Entry.Con:
                                               CodeGen.loadConstant(des.entry.value);
                                               break;
                                             default:
                                               SemError("wrong kind of identifier");
                                               break;
                                           } .)
     | Constant<^con>                   (. type = con.type;
                                           CodeGen.loadConstant(con.value); .)
     | "new" BasicType<^type>           (. type++; .)
       "[" Expression<^size>            (. if (!isArith(size))
                                             SemError("array size must be integer");
                                           CodeGen.allocate(); .)
       "]"
     | "(" Expression<^type> ")"
  .

Notice carefully how the detection of a type incompatibility in some cases is accompanied by forcing the expression or sub-expression to be of the noType type, and sometimes of the boolType type. This has been done to try to minimize the number of error messages thereafter. You might like to think whether this is a good strategy, or whether it could be improved still further.

We have to refactor the productions defining the various operators in a slightly different way as well:

  AddOp<^int op>                        (. op = CodeGen.nop; .)
  =    "+"                              (. op = CodeGen.add; .)
     | "-"                              (. op = CodeGen.sub; .)
   .

  MulOp<^int op>                        (. op = CodeGen.nop; .)
  =    "*"                              (. op = CodeGen.mul; .)
     | "/"                              (. op = CodeGen.div; .)
     | "%"                              (. op = CodeGen.rem; .)
  .

  EqualOp<^int op>                      (. op = CodeGen.nop; .)
  =    "=="                             (. op = CodeGen.ceq; .)
     | "!="                             (. op = CodeGen.cne; .)
     | "="                              (. SemError("== intended?"); .)
     | "<>"                             (. SemError("!= intended?"); .)
  .

  RelOp<^int op>                        (. op = CodeGen.nop; .)
  =    "<"                              (. op = CodeGen.clt; .)
     | "<="                             (. op = CodeGen.cle; .)
     | ">"                              (. op = CodeGen.cgt; .)
     | ">="                             (. op = CodeGen.cge; .)
  .


Task 9 - You had better do this one or else....

Adding an else option to the IfStatement is easy once you see the trick! Note that the "no else part" option in the grammar is associated with an action, even in the absence of any terminals or non-terminals. This is a very useful trick to remember.

  IfStatement<StackFrame frame>         (. int count;
                                           Label falseLabel = new Label(!known); .)
  =  "if" "(" Condition ")"             (. CodeGen.branchFalse(falseLabel); .)
     Statement<^count, frame>           (. if (count == 0 && warnings)
                                             Warning("empty statement part"); .)
     (   "else"                         (. Label outLabel = new Label(!known);
                                           CodeGen.branch(outLabel);
                                           falseLabel.here(); .)
         Statement<^count, frame>       (. if (count == 0 && warnings)
                                             Warning("empty statement part");
                                           outLabel.here(); .)
       | /* no else part */             (. falseLabel.here(); .)
     ) .


Task 10 - Something to do - while you wait for a tutor

Adding the basic DoWhile loop to Parva is very easy too, since all that is needed is a "backward" branch. Note the use of the negateBoolean method, as the PVM does not have a BNZ opcode (although it would be easy enough to add one):

  DoWhileStatement<StackFrame frame>    (. int count;
                                           Label startLoop = new Label(known); .)
  =  "do"
       Statement<^count, frame>         (. if (count == 0 && warnings)
                                             Warning("empty statement part"); .)
     WEAK "while"
     "(" Condition ")" WEAK ";"         (. CodeGen.negateBoolean();
                                           CodeGen.branchFalse(startLoop); .)
  .


Task 11 - This has gone on long enough - time for a break


Task 12 - Break over, let's continue

The syntax of the BreakStatement and of the ContinueStatement is, of course, trivial. The catch is that one has to allow these statements only in the context of loops. To find a context-free grammar with this restriction is not worth the effort. As with nested comments in languages that allow them, it is easier just to have a (global) counter that is incremented and decremented as parsing of loops starts and finishes.

However, loops must be handled in a way that allows them to be nested, with all the breaks and continues in each loop directed at the correct place for that loop - and many of these involve forward references. As it happens, the Label class we already use allows for this to be handled neatly, and we can get away with using two global labels (one for each kind of statement). However, we need a little local stack to be introduced in each loop parsing production, so that these global labels can be kept up to date. Once you have seen the solution it probably looks almost obvious!

The extra static fields in the parser (declared at the top of the ATG file are;

  static int loopLevel = 0;                      // = 0 outside of loops, > 0 inside loops
  static Label
    loopExit = new Label(!known),                // current target for "break" statements
    loopContinue = new Label(!known);            // current target for "continue" statements

and the productions for the BreakStatement and ContinueStatement follow as:

  BreakStatement
  =  "break"                            (. if (loopLevel == 0) SemError("break is not within a loop");
                                           CodeGen.branch(loopExit); .)
     WEAK ";" .

  ContinueStatement
  =  "continue"                         (. if (loopLevel == 0) SemError("continue is not within a loop");
                                           CodeGen.branch(loopContinue); .)
     WEAK ";" .

The WhileStatement and DoWhileStatement productions now have quite a lot of extra actions:

  WhileStatement<StackFrame frame>      (. int count;
                                           loopLevel++;
                                           Label oldContinue = loopContinue;
                                           Label oldExit = loopExit;
                                           loopExit = new Label(!known);
                                           loopContinue = new Label(known); .)
  =  "while" "(" Condition ")"          (. CodeGen.branchFalse(loopExit); .)
     Statement<^count, frame>           (. if (count == 0 && warnings)
                                             Warning("empty statement part");
                                           CodeGen.branch(loopContinue);
                                           loopExit.here();
                                           loopExit = oldExit;
                                           loopContinue = oldContinue;
                                           loopLevel--; .)
  .


  DoWhileStatement<StackFrame frame>    (. int count;
                                           loopLevel++;
                                           Label oldContinue = loopContinue;
                                           Label oldExit = loopExit;
                                           loopContinue = new Label(!known);
                                           Label startLoop = new Label(known);
                                           loopExit = new Label(!known); .)
  =  "do"
       Statement<^count, frame>         (. if (count == 0 && warnings)
                                             Warning("empty statement part"); .)
     WEAK "while"                       (. loopContinue.here(); .)
     "(" Condition ")" WEAK ";"         (. CodeGen.negateBoolean();
                                           CodeGen.branchFalse(startLoop);
                                           loopExit.here();
                                           loopExit = oldExit;
                                           loopContinue = oldContinue;
                                           loopLevel--; .)
  .


Task 13 - Make the change; enjoy life; upgrade now to Parva++ (Ta-ra!)


Task 14 - Other cute assignment operators

It might not at first have been obvious, but hopefully everyone eventually saw that all these extensions are handled by clever modifications to the Assignment production, which has to be factorized in such a way as to avoid LL(1) conflicts. As posed in the practical sheet you were expected to handle only the +=, -=, *=, /= and %= assignments. The code below achieves all this (including the tests for compatibility that some students omitted) by assuming the existence of a few new machine opcodes, as suggested in the textbook.

  Assignment                            (. int expType;
                                           DesType des;
                                           int op; .)
  =  Designator<^des>                   (. if (des.entry.kind != Entry.Var)
                                             SemError("invalid assignment"); .)
     (   AssignOp<^op>                  (. switch (op) {
                                             case CodeGen.nop:
                                               break;
                                             default:
                                               if (!isArith(des.type))
                                                 SemError("arithmetic destination required");
                                               CodeGen.duplicate();
                                               CodeGen.dereference();
                                               break;
                                           } .)
         Expression<^expType>           (. if (!compatible(des.type, expType))
                                             SemError("incompatible types in assignment");
                                           CodeGen.binaryOp(op);  // if nop, generates no code
                                           CodeGen.assign(des.type); .)
       | "++"                           (. if (!isArith(des.type))
                                             SemError("arithmetic type required");
                                           CodeGen.increment(des.type); .)
       | "--"                           (. if (!isArith(des.type))
                                             SemError("arithmetic type required");
                                           CodeGen.decrement(des.type); .)
     )
     WEAK ";" .

It is not all that difficult to allow for the boolean assignment operators &= and |=. There is no real change needed to the context-free grammar, but we have to make sure that we generate "short circuit" operations. This adds a bit to the apparent complexity of the production, as you can see below:

  Assignment                            (. int expType;
                                           DesType des;
                                           int op;
                                           Label shortcircuit = new Label(!known);.)
  =  Designator<^des>                   (. if (des.entry.kind != Entry.Var)
                                             SemError("invalid assignment"); .)
     (  AssignOp<^op>                   (. switch (op) {
                                             case CodeGen.nop:
                                               break;
                                             case CodeGen.add:
                                             case CodeGen.sub:
                                             case CodeGen.mul:
                                             case CodeGen.div:
                                             case CodeGen.rem:
                                               if (!isArith(des.type))
                                                 SemError("arithmetic destination required");
                                               CodeGen.duplicate();
                                               CodeGen.dereference();
                                               break;
                                             case CodeGen.and:
                                             case CodeGen.or:
                                               if (!isBool(des.type))
                                                 SemError("boolean destination required");
                                               CodeGen.duplicate();
                                               CodeGen.dereference();
                                               CodeGen.booleanOp(shortcircuit, op);
                                               break;
                                           } .)
        Expression<^expType>            (. if (!compatible(des.type, expType))
                                             SemError("incompatible types in assignment");
                                           switch (op) {
                                             case CodeGen.nop:
                                               break;
                                             case CodeGen.and:
                                             case CodeGen.or:
                                               shortcircuit.here();
                                               break;
                                             case CodeGen.add:
                                             case CodeGen.sub:
                                             case CodeGen.mul:
                                             case CodeGen.div:
                                             case CodeGen.rem:
                                               CodeGen.binaryOp(op);
                                               break;
                                           }
                                           CodeGen.assign(des.type); .)
       | "++"                           (. if (!isArith(des.type))
                                             SemError("arithmetic type required");
                                           CodeGen.increment(des.type); .)
       | "--"                           (. if (!isArith(des.type))
                                             SemError("arithmetic type required");
                                           CodeGen.decrement(des.type); .)
     )
     WEAK ";" .

The AssignOp production is rather more complex than before. It returns the associated binary operation that will be needed in the compound assignment operations.

  AssignOp<^int op>                     (. op = CodeGen.nop; .)
  =    "="
     | ":="                             (. SemError("= intended?"); .)
     | "+="                             (. op = CodeGen.add; .)
     | "-="                             (. op = CodeGen.sub; .)
     | "*="                             (. op = CodeGen.mul; .)
     | "/="                             (. op = CodeGen.div; .)
     | "%="                             (. op = CodeGen.rem; .)
     | "&="                             (. op = CodeGen.and; .)
     | "|="                             (. op = CodeGen.or;  .)
  .

The extra code generation routines are straightforward:

    public static void duplicate() {
    // Generates code to push another copy of top of stack
      emit(PVM.dup);
    }

    public static void increment(int type) {
    // Generates code to increment the value found at the address currently
    // stored at the top of the stack.
      emit(PVM.inc);
    }

    public static void decrement(int type) {
    // Generates code to decrement the value found at the address currently
    // stored at the top of the stack.
      emit(PVM.dec);
    }

As usual, the extra opcodes in the PVM make all this easy to achieve at run time. Many submission forgot to include the check that the address was "in bounds". I suppose one could argue that if the source program were correct, then the addresses could not go out of bounds, but if the interpreter were to be used in conjunction with a rather less fussy assembler (as we had in earlier practicals) it would make sense to be cautious.

    case PVM.inc:           // increment ++
      if (inBounds(mem[cpu.sp])) {
        mem[mem[cpu.sp]]++; cpu.sp++;
      }
      break;

    case PVM.dec:           // decrement --
      if (inBounds(mem[cpu.sp])) {
        mem[mem[cpu.sp]]--; cpu.sp++;
      }
      break;

    case PVM.dup:           // duplicate top of stack
      cpu.sp--;
      if (inBounds(cpu.sp)) mem[cpu.sp] = mem[cpu.sp + 1];
      break;


Task 15 - Generating slightly better code

The changes to the code generating routines to produce the special one-word opcodes like LDA_0 and LDC_3 are very simple:

    public static void loadConstant(int number) {
    // Generates code to push number onto evaluation stack
      switch (number) {
        case -1: emit(PVM.ldc_m1); break;
        case 0:  emit(PVM.ldc_0); break;
        case 1:  emit(PVM.ldc_1); break;
        case 2:  emit(PVM.ldc_2); break;
        case 3:  emit(PVM.ldc_3); break;
        default: emit(PVM.ldc); emit(number); break;
      }
    }

    public static void loadAddress(Entry var) {
    // Generates code to push address of variable var onto evaluation stack
      switch (var.offset) {
        case 0:  emit(PVM.lda_0); break;
        case 1:  emit(PVM.lda_1); break;
        case 2:  emit(PVM.lda_2); break;
        case 3:  emit(PVM.lda_3); break;
        default: emit(PVM.lda); emit(var.offset); break;
      }
    }

Of course, with the Parva grammar as it was defined for this practical one would never be in a position to generate the ldc_m1 opcode, since the grammar made no provision for negative constants. It would not have been hard to extend it to do so, and you might like to puzzle out how and where this could be done.


The For Loop - addition suggested in the last tutorial

As promised in the tutorial, here is a solution to the problem of adding a ForStatement loop to Parva:

  ForStatement<StackFrame frame>        (. boolean up = true;
                                           int count, expType;
                                           String name;
                                           loopLevel++;
                                           Label oldContinue = loopContinue;
                                           Label oldExit = loopExit;
                                           loopContinue = new Label(!known);
                                           loopExit = new Label(!known); .)
  =  "for" Ident<^name>                 (. Entry control = Table.find(name);
                                           if (!control.found) {
                                             SemError("undeclared identifier");
                                             control = new Entry(); // new is critical
                                             control.name = name;
                                             control.kind = Entry.Var;
                                             control.type = Entry.noType;
                                             control.offset = 0;
                                             Table.insert(control);
                                           }
                                           if (isRef(control.type) || control.kind != Entry.Var)
                                             SemError("illegal control variable");
                                           CodeGen.loadAddress(control); .)
     "=" Expression<^expType>           (. if (!compatible(expType, control.type))
                                             SemError("incompatible with control variable"); .)
     ( "to" | "downto"                  (. up = false; .)
     )
     Expression<^expType>               (. if (!compatible(expType, control.type))
                                             SemError("incompatible with control variable");
                                           CodeGen.startForLoop(up, loopExit);
                                           Label startLoop = new Label(known); .)
     "do" Statement<^count, frame>      (. if (count == 0 && warnings)
                                             Warning("empty statement part");
                                           loopContinue.here();
                                           CodeGen.endForLoop(up, startLoop);
                                           loopExit.here();
                                           CodeGen.pop3();
                                           loopExit = oldExit;
                                           loopContinue = oldContinue;
                                           loopLevel--; .)
  .

This solution restricts the control variable to a simple variable, and includes the possibility of the loop body incorporating one or more BreakStatements or ContinueStatements.

The extra code generating methods are as follows:

    public static void startForLoop(boolean up, Label destination) {
    // Generates prologue test for a for loop (either up or down)
      if (up) emit(PVM.sfu); else emit(PVM.sfd);
      emit(destination.address());
    }

    public static void endForLoop(boolean up, Label destination) {
    // Generates epilogue test and increment/decrement for a for loop (either up or down)
      if (up) emit(PVM.efu); else emit(PVM.efd);
      emit(destination.address());
    }

    public static void pop3() {
    // Generates code to discard top three elements from the stack
      emit(PVM.pop3);
    }

and, finally, the magic that makes this all work efficiently is achieved with the new opcodes that are interpreted as follows:

    case PVM.sfu:           // start for loop "to"
      if (mem[cpu.sp] < mem[cpu.sp + 1]) cpu.pc = mem[cpu.pc];
      else {
        mem[mem[cpu.sp + 2]] = mem[cpu.sp + 1]; cpu.pc++;
      }
      break;

    case PVM.sfd:           // start for loop "downto"
      if (mem[cpu.sp] > mem[cpu.sp + 1]) cpu.pc = mem[cpu.pc];
      else {
        mem[mem[cpu.sp + 2]] = mem[cpu.sp + 1]; cpu.pc++;
      }
      break;

    case PVM.efu:           // end for loop "to"
      if (mem[mem[cpu.sp + 2]] < mem[cpu.sp]) {
        mem[mem[cpu.sp + 2]]++; cpu.pc = mem[cpu.pc];
      } else cpu.pc++;
      break;

    case PVM.efd:           // end for loop "downto"
      if (mem[mem[cpu.sp + 2]] > mem[cpu.sp]) {
        mem[mem[cpu.sp + 2]]--; cpu.pc = mem[cpu.pc];
      } else cpu.pc++;
      break;

    case PVM.pop3:          // discard 3 elements from top of stack
      cpu.sp += 3;
      break;


Home  © P.D. Terry