RHODES UNIVERSITY

June Examinations - 1997 - Solutions

Computer Science 301 - Paper 2 - Solutions


Section A

A1 Briefly explain the differences between each pair of concepts below: [9]

Self-resident compilers generate code for the architecture of the machine on which they are running, while cross- compilers generate code for a different machine.

Phrase structure defines how tokens (words) are arranged into sentences; lexical structure defines how characters are arranged into tokens.

Scope defines the compile-time area of code in which an identifier can be recognised; extent defines the run-time period for which storage is assigned to, and associated with, an identifier.

A2 Draw a diagram outlining the relationship between the various phases that occur in compilation, and briefly describe the responsibility of each phase.

A full description of this is to be found in the text book on pages 13-19.

A3 Draw T-diagrams that represent the processes that are used in the compiler generator / compiler / interpreter system that you have developed in the practicals of this course. [8]

This was appallingly badly done (with a few exceptions). What I was looking for was something like this:

(a) Using Coco to generate the Clang compiler sources:

      +--------------------------+          +--------------------------+
      |         CLANG.ATG        |          |         CLANG.F          |
      | Clang  ----------> P-Code|          | Clang -----------> P-code|
      |                          |          |                          |
      +-------+          +-------+----------+-------+          +-------+
              |          |           CR.EXE         |          |
              |  Cocol   | Cocol  -------->  F-code |  F-code  |
              +----------+-------+          +-------+----------+
                                 |          |
                                 |  M-code  |
                                 |          |
                                 +----------+
                                 +----------+
                                 |M-machine |
                                 +----------+
(Here F-Code = Modula-2 or C++ depending on your preference)

(b) Using BC or M2 to compile the resulting Clang compiler:

      +--------------------------+          +--------------------------+
      |          CLANG.F         |          |         CLANG.EXE        |
      | Clang  ----------> P-Code|          | Clang -----------> P-code|
      |                          |          |                          |
      +-------+          +-------+----------+-------+          +-------+
              |          |           F.EXE          |          |
              |     F    | F      -------->  M-code |  M-code  |
              +----------+-------+          +-------+----------+
                                 |          |       +----------+
                                 |  M-code  |       |M-machine |
                                 |          |       +----------+
                                 +----------+
                                 +----------+
                                 |M-machine |
                                 +----------+
(c) Using BC or M2 (Modula or C++) to generate the interpreter:
      +--------------------------+          +--------------------------+
      |           STKMC.F        |          |          STKMC.EXE       |
      | P-code ----------> Result|          | P-code ----------> Result|
      | Data                     |          | Data                     |
      +-------+          +-------+----------+-------+          +-------+
              |          |           F.EXE          |          |
              |     F    | F      -------->  M-code |  M-code  |
              |          |                          |          |
              +----------+-------+          +-------+----------+
                                 |          |       +----------+
                                 |  M-code  |       |M-machine |
                                 |          |       +----------+
                                 +----------+
                                 +----------+
                                 |M-machine |
                                 +----------+
(d) Chaining compiler and interpreter together:
      +--------------------------+          +--------------------------+
      |          CLANG.EXE       |          |          STKMC.EXE       |
      | Clang  ----------> P-Code|          | P-code ----------> Result|
      |                          |          | Data                     |
      +-------+          +-------+          +-------+          +-------+
              |          |                          |          |
              |     F    |                          |  M-code  |
              |          |                          |          |
              +----------+                          +----------+
              +----------+                          +----------+
              |M-machine |                          |M-machine |
              +----------+                          +----------+
and so on. What I saw in most cases were simply random T diagrams with almost anything written in each of the arms!

A4 A grammar G may be described by a 4-tuple:

A5 What do you understand by the concepts "ambiguous grammars" and "equivalent grammars"? Illustrate your answer by giving a simple example of an ambiguous grammar, and of an equivalent non-ambiguous grammar. [8]

An ambiguous grammar is one in which there is at least one sentence that has two distinct parse trees. Two grammars are equivalent if they describe exactly the same language.

It is quite easy to write down ambiguous grammars, and there were some quite nice examples shown. But few students came up with equivalent unambiguous ones (ie ones that describe the same language). An easy example would be the one we discussed in class for Roman numerals:

   Ambiguous:

         Units =    [ "I" ] [ "I" ] [ "I" ]
                  | "IV" | "IX"
                  | "V" [ "I" ] [ "I" ] [ "I" ]

   Unambiguous:

         Units =    [ "I" [ "I" [ "I" ] ] ]
                  | "IV" | "IX"
                  | "V" [ "I" [ "I" [ "I" ] ] ]

A6 Explain what is meant by the FIRST and FOLLOW sets as applied to grammar analysis, and in terms of these state the rules that a grammar must obey for it to be LL(1).

Text book, pages 173 - 176

A7 You should be familiar with the use of the CASE statement in Modula-2. (A few examples of syntactically correct CASE statements appear in appendix A so as to refresh your memory.)

A8 Appendix B shows an extract from a simple recursive descent compiler that handles compilation of a simple if - then statement. Suppose the statement syntax were to be extended to

            IfStatement = "IF" Condition "THEN" StatementSequence
                       [ "ELSIF" Condition "THEN" StatementSequence ]
                       [ "ELSE" StatementSequence ]
                       "END" .

How would the IfStatement routine in the compiler have to be changed to accommodate this? [18]

Many students clearly had not appreciated the material in the last practical, and simply omitted to generate unconditional branch instructions where they were needed.

Here is a Modula-2 solution, using fairly good code generation.

  PROCEDURE IfStatement;
  (* IfStatement = "IF" Condition "THEN" StatementSequence
                   [ "ELSIF" Condition "THEN" StatementSequence" ]
                   [ "ELSE" StatementSequence" ] "END" . *)
    VAR
      Jump1, Jump2, TestLabel : CGEN.LABELS;
      Elsif : BOOLEAN;
    BEGIN
      Elsif := FALSE;
      SCAN.GetSYM; Condition(SYMSET{ThenSym, DoSym} + Followers);
      CGEN.JumpOnFalse(TestLabel, CGEN.undefined);
      IF SYM.Sym = ThenSym
        THEN SCAN.GetSYM
        ELSE Error(23); IF SYM.Sym = DoSym THEN SCAN.GetSYM END
      END;
      StatementSequence(SYMSET{ElseSym, ElsIfSym} + Followers);
      CGEN.BackPatch(TestLabel);
      IF (SYM.Sym = ElsIfSym) OR (SYM.Sym = ElseSym)
        THEN
          IF SYM.Sym = ElsIfSym THEN
            CGEN.Jump(Jump1, CGEN.undefined);
            CGEN.BackPatch(TestLabel);
            SCAN.GetSYM; Condition(SYMSET{ThenSym, DoSym} + Followers);
            CGEN.JumpOnFalse(TestLabel, CGEN.undefined);
            IF SYM.Sym = ThenSym
              THEN SCAN.GetSYM
              ELSE Error(23); IF SYM.Sym = DoSym THEN SCAN.GetSYM END
            END;
            StatementSequence(SYMSET{ElseSym} + Followers);
            Elsif := TRUE
          END;
          IF SYM.Sym = ElseSym
            THEN
              SCAN.GetSYM;
              CGEN.Jump(Jump2, CGEN.undefined);
              CGEN.BackPatch(TestLabel);
              StatementSequence(Followers);
              CGEN.BackPatch(Jump2)
            ELSE CGEN.BackPatch(TestLabel)
          END;
          IF Elsif THEN CGEN.BackPatch(Jump1) END
        ELSE CGEN.BackPatch(TestLabel)
      END;
      Accept(EndSym, 24)
    END IfStatement;
And here is the equivalent C++ version:
  void PARSER::IfStatement(symset followers)
  // IfStatement = "IF" Condition "THEN" StatementSequence "END" .
  { CGEN_labels jump1, jump2, testlabel;
    bool elsif = false;
    GetSym();
    Condition(symset(SCAN_thensym, SCAN_dosym) + followers);
    CGen->jumponfalse(testlabel, CGen->undefined);
    if (SYM.sym == SCAN_thensym)
      GetSym();
    else
      { Report->error(23); if (SYM.sym == SCAN_dosym) GetSym(); }
    StatementSequence(symset(elsifsym, elsesym) + followers);
    CGen->backpatch(testlabel);
    if (SYM.sym == SCAN_elsifsym || SYM.sym = SCAN_elsesym) {
      if SYM.sym = elsifsym {
        CGen->jump(jump1, CGen->undefined);
        CGen->backpatch(testlabel);
        GetSym(); Condition(symset{SCAN_thensym, SCAN_dosym} + followers);
        CGen->jumponfalse(testlabel, CGen->undefined);
        if (SYM.sym == SCAN_thensym)
          GetSym();
        else
          { Report->error(23); if (SYM.sym == SCAN_dosym); GetSym(); }
        StatementSequence(symset(SCAN_elsifsym, SCAN_elsesym) + followers);
        elsif = true;
      }
      if (SYM.sym == SCAN_elsesym) {
        GetSym();
        CGen->jump(jump2, CGen->undefined);
        CGen->backpatch(testlabel);
        StatementSequence(followers);
        CGen->backpatch(jump2);
      }
      else CGen->backpatch(testlabel);
      if (elsif) CGen->backpatch(jump1);
    }
    else CGen->backpatch(testlabel);
    Accept(SCAN_endsym, 24);
  }

A9 Appendix C shows a simple recursive Clang program for reading and sorting a list of 6 numbers using a selection sort algorithm.


Section B

This was really rather disappointing. Nobody at all seemed to appreciate that REAL and INTEGER types in a computer are totally different types, and have to be handled separately. I find this almost unbelievable, given that you are third year students and have programmed both in Modula-2 (where the distinction is enforced very rigidly) as well as in C++. There were several attempts made to track type information, but these were nearly all very naive, and often did nothing more than pass a parameter around that was not really used at all.

Here are the sorts of answers I had hoped for:

$CN
COMPILER CalcM
(* Four Function Calculator (mixed mode) with simple memory
   P.D. Terry, Rhodes University, 1997 *)

  FROM FileIO IMPORT
    StdOut, WriteLn, WriteString, WriteInt, WriteReal, Compare;
  FROM StringConversions IMPORT
    StrToInt, StrToReal;
  FROM Utils IMPORT
    IntToReal, RealToInt;

  TYPE
    TYPES = ( Real, Integer, Unknown );
    VALUE = RECORD
              CASE Type : TYPES OF
              | Real    : R : REAL;
              | Integer : I : INTEGER;
              | Unknown : (* nothing *)
              END
            END;
   CONST
     MaxMem = 100;
   TYPE
     INDEX = CARDINAL [0 .. MaxMem];
     NAME  = ARRAY [0 .. 25] OF CHAR;
   VAR
     Memory : ARRAY INDEX OF
                RECORD
                  Name  : NAME;
                  Value : VALUE
                END;
     Last : INDEX;

   PROCEDURE Retrieve (N : NAME; VAR V : VALUE);
   (* Use N to retrieve a value V from memory *)
     VAR
       I : INDEX;
     BEGIN
       Memory[0].Name := N (* sentinel *);
       I := Last (* linear search; must succeed *);
       WHILE Compare(N, Memory[I].Name) # 0 DO DEC(I) END;
       IF I # 0 (* we found it *)
         THEN V := Memory[I].Value (* we know its value *)
         ELSE V.Type := Unknown (* it was not there - error *)
       END
     END Retrieve;

   PROCEDURE Store (N : NAME; V : VALUE);
   (* Use N to store a value V in memory *)
     VAR
       I : INDEX;
     BEGIN
       Memory[Last+1].Name := N (* store at end, in case it is a new one *);
       I := 1 (* linear search, must succeed *);
       WHILE Compare(N, Memory[I].Name) # 0 DO INC(I) END;
       Memory[I].Value := V (* we must be able to store the value *);
       IF I > Last THEN (* it is effectively a new variable *)
         INC(Last);
         IF Last = MaxMem THEN (* crude, but effective *)
           WriteString(StdOut, "Memory overflow");
           HALT
         END
       END
     END Store;

(* ------------------------------------------------------------------- *)

CHARACTERS
  digit  =  "0123456789" .
  letter =  "ABCDEFGHIJKLMNOPQRSTUVWXYZabcdefghijklmnopqrstuvwxyz" .

IGNORE CHR(9) .. CHR(13)
IGNORE CASE

TOKENS
  integer  = digit { digit } .
  real     = digit { digit } "." { digit } .
  name     = letter { letter | digit } .

PRODUCTIONS
  CalcM
    =                           (. Last := 0 (* initialize memory table *) .)
    { Assignment | Print } "QUIT" .

  Assignment                    (. VAR
                                     Value : VALUE;
                                     Name : NAME; .)
    = name                      (. LexString(Name) .)
      ":=" Expression<Value>    (. Store(Name, Value) .) .

  Print
     = "PRINT" OneExp
       { WEAK "," OneExp }
                                (. WriteLn(StdOut) .) .

  OneExp                        (. VAR Value : VALUE; .)
     = Expression<Value>        (. CASE Value.Type OF
                                     | Integer : WriteInt(StdOut, Value.I, 0);
                                     | Real    : WriteReal(StdOut, Value.R, 0, 4);
                                     | Unknown : WriteString(StdOut, " undefined")
                                   END .) .

  Expression<VAR E : VALUE>     (. VAR T : VALUE; .)
    = (   Term<E>
        | "+" Term<E>
        | "-" Term<E>           (. CASE E.Type OF
                                   | Integer : E.I := - E.I
                                   | Real    : E.R := - E.R
                                   | Unknown : (* nothing *)
                                   END .)
      )
      {   "+" Term<T>           (. CASE E.Type OF
                                   | Integer :
                                       CASE T.Type OF
                                       | Integer : E.I := E.I + T.I
                                       | Real    : E.Type := Real;
                                                   E.R := IntToReal(E.I) + T.R
                                       | Unknown : E.Type := Unknown;
                                       END
                                   | Real :
                                       CASE T.Type OF
                                       | Integer : E.R := E.R + IntToReal(T.I)
                                       | Real    : E.R := E.R + T.R
                                       | Unknown : E.Type := Unknown;
                                       END
                                   | Unknown : (* nothing *)
                                   END .)
        | "-" Term<T>           (. CASE E.Type OF
                                   | Integer :
                                       CASE T.Type OF
                                       | Integer : E.I := E.I - T.I
                                       | Real    : E.Type := Real;
                                                   E.R := IntToReal(E.I) - T.R
                                       | Unknown : E.Type := Unknown;
                                       END
                                   | Real :
                                       CASE T.Type OF
                                       | Integer : E.R := E.R - IntToReal(T.I)
                                       | Real    : E.R := E.R - T.R
                                       | Unknown : E.Type := Unknown;
                                       END
                                   | Unknown : (* nothing *)
                                   END .)
      } .

  Term<VAR T : VALUE>           (. VAR F : VALUE; .)
    = Factor<T>
      {   "*" Factor<F>         (. CASE T.Type OF
                                   | Integer :
                                       CASE F.Type OF
                                       | Integer : T.I := T.I * F.I
                                       | Real    : T.Type := Real;
                                                   T.R := IntToReal(T.I) * F.R
                                       | Unknown : T.Type := Unknown;
                                       END
                                   | Real :
                                       CASE F.Type OF
                                       | Integer : T.R := T.R * IntToReal(F.I)
                                       | Real    : T.R := T.R * F.R
                                       | Unknown : T.Type := Unknown;
                                       END
                                   | Unknown : (* nothing *)
                                   END .)
        | "/" Factor<F>         (. CASE T.Type OF
                                   | Integer :
                                       CASE F.Type OF
                                       | Integer : T.Type := Real;
                                                   T.R := IntToReal(T.I) / IntToReal(F.I)
                                       | Real    : T.Type := Real;
                                                   T.R := IntToReal(T.I) / F.R
                                       | Unknown : T.Type := Unknown;
                                       END
                                   | Real :
                                       CASE F.Type OF
                                       | Integer : T.R := T.R / IntToReal(F.I)
                                       | Real    : T.R := T.R / F.R
                                       | Unknown : T.Type := Unknown;
                                       END
                                   | Unknown : (* nothing *)
                                   END .)
        | "DIV" Factor<F>       (. CASE T.Type OF
                                   | Integer :
                                       CASE F.Type OF
                                       | Integer : T.I := T.I DIV F.I
                                       | Real    : T.Type := Unknown; SemError(100)
                                       | Unknown : (* nothing *)
                                       END
                                   | Real :
                                       T.Type := Unknown; SemError(100)
                                   | Unknown : (* nothing *)
                                   END .)
      } .

  Factor<VAR F : VALUE>         (. VAR Str : NAME; .)
    = name                      (. LexName(Str);
                                   Retrieve(Str, F);
                                   IF F.Type = Unknown THEN SemError(101) END .)
      | Number<F>
      | "(" Expression<F> ")"
      | "INTEGER" "("
         Expression<F> ")"      (. CASE F.Type OF
                                   | Real :
                                       F.Type := Integer; F.I := RealToInt(F.R)
                                   | Integer : SemError(102)
                                   | Unknown : (* nothing *)
                                   END .)
      | "REAL" "("
         Expression<F> ")"      (. CASE F.Type OF
                                   | Real : SemError(103)
                                   | Integer :
                                       F.Type := Real; F.R := IntToReal(F.I)
                                   | Unknown : (* nothing *)
                                   END .) .

  Number<VAR C : VALUE>         (. VAR
                                     Okay : BOOLEAN;
                                     Str : ARRAY [0 .. 20] OF CHAR; .)
    = integer                   (. LexString(Str); C.Type := Integer;
                                   StrToInt(Str, C.I, Okay) .)
      | real                    (. LexString(Str); C.Type := Real;
                                   StrToReal(Str, C.R, Okay) .) .
END CalcM.

COMPILER CalcC $CX /* generate compiler, C++ classes */
/* Four Function Calculator (mixed mode) with simple memory
   P.D. Terry, Rhodes University, 1997 */

#include "misc.h"

/* ------------------------------------------------------------------- */

CHARACTERS
  digit  =  "0123456789" .
  letter =  "ABCDEFGHIJKLMNOPQRSTUVWXYZabcdefghijklmnopqrstuvwxyz" .

IGNORE CHR(9) .. CHR(13)
IGNORE CASE

TOKENS
  integer  = digit { digit } .
  real     = digit { digit } "." { digit } .
  name     = letter { letter | digit } .

PRODUCTIONS
  CalcC
    =                           (. Last = 0; // initialize memory table  .)
    { Assignment | Print } "QUIT" .

  Assignment
    =                           (. VALUE Value;
                                   char Name[25]; .)
      name                      (. LexString(Name, sizeof(Name) - 1); .)
      ":=" Expression<Value>    (. Store(Name, Value); .) .

  Print
     = "PRINT" OneExp
       { WEAK "," OneExp }
                                (. printf("\n"); .) .

  OneExp
     =                          (. VALUE Value; .)
       Expression<Value>        (. switch (Value.Type) {
                                     case Integer : printf(" %d", Value.I); break;
                                     case Real    : printf(" %f", Value.R); break;
                                     case Unknown : printf(" undefined");  break;
                                   } .) .

  Expression<VALUE &E>
    =                           (. VALUE T; .)
      (   Term<E>
        | "+" Term<E>
        | "-" Term<E>           (. switch (E.Type) {
                                     case Integer : E.I = - E.I; break;
                                     case Real    : E.R = - E.R; break;
                                     case Unknown : break; // nothing
                                   } .)
      )
      {   "+" Term<T>           (. switch (E.Type) {
                                     case Integer :
                                       switch (T.Type) {
                                         case Integer : E.I = E.I + T.I; break;
                                         case Real    : E.Type = Real; E.R = E.I + T.R; break;
                                         case Unknown : E.Type = Unknown; break;
                                       } break;
                                     case Real :
                                       switch (T.Type) {
                                         case Integer : E.R = E.R + T.I; break;
                                         case Real    : E.R = E.R + T.R; break;
                                         case Unknown : E.Type = Unknown; break;
                                       } break;
                                     case Unknown : break; // nothing
                                   } .)
        | "-" Term<T>           (. switch (E.Type) {
                                     case Integer :
                                       switch (T.Type) {
                                         case Integer : E.I = E.I - T.I; break;
                                         case Real    : E.Type = Real; E.R = E.I - T.R; break;
                                         case Unknown : E.Type = Unknown; break;
                                       } break;
                                     case Real :
                                       switch (T.Type) {
                                         case Integer : E.R = E.R - T.I; break;
                                         case Real    : E.R = E.R - T.R; break;
                                         case Unknown : E.Type = Unknown; break;
                                       } break;
                                     case Unknown : break; // nothing
                                   } .)
      } .

  Term<VALUE &T>
    =                           (. VALUE F; .)
      Factor<T>
      {   "*" Factor<F>         (. switch (T.Type) {
                                     case Integer :
                                       switch (F.Type) {
                                         case Integer : T.I = T.I * F.I; break;
                                         case Real    : T.Type = Real; T.R = T.I * F.R; break;
                                         case Unknown : T.Type = Unknown; break;
                                       } break;
                                     case Real :
                                       switch (F.Type) {
                                         case Integer : T.R = T.R * F.I; break;
                                         case Real    : T.R = T.R * F.R; break;
                                         case Unknown : T.Type = Unknown; break;
                                       } break;
                                     case Unknown : break; // nothing
                                   } .)
        | "/" Factor<F>         (. switch (T.Type) {
                                     case Integer :
                                       switch (F.Type) {
                                         case Integer :
                                                float t = T.I; float f = F.I;
                                                T.Type = Real; T.R = t / f; break;
                                         case Real    : T.Type = Real; T.R = T.I / F.R; break;
                                         case Unknown : T.Type = Unknown; break;
                                       } break;
                                     case Real :
                                       switch (F.Type) {
                                         case Integer : T.R = T.R / F.I; break;
                                         case Real    : T.R = T.R / F.R; break;
                                         case Unknown : T.Type = Unknown; break;
                                       } break;
                                     case Unknown : break; // nothing
                                   } .)
        | "DIV" Factor<F>       (. switch (T.Type) {
                                     case Integer :
                                       switch (F.Type) {
                                         case Integer : T.I = T.I / F.I; break;
                                         case Real    : T.Type = Unknown; SemError(100); break;
                                         case Unknown : break; // nothing
                                       } break;
                                     case Real :
                                       T.Type = Unknown; SemError(100); break;
                                     case Unknown : ; break; /* nothing */
                                   } .)
      } .

  Factor<VALUE &F>
    =                           (. char Str[25]; .)
      name                      (. LexName(Str, sizeof(Str) - 1);
                                   Retrieve(Str, F);
                                   if (F.Type == Unknown) SemError(101); .)
      | Number<F>
      | "(" Expression<F> ")"
      | "INTEGER" "("
         Expression<F> ")"      (. switch (F.Type) {
                                     case Real    : F.Type = Integer; F.I = F.R; break;
                                     case Integer : SemError(102); break;
                                     case Unknown : break; // nothing
                                   } .)
      | "REAL" "("
         Expression<F> ")"      (. switch (F.Type) {
                                     case Real    : SemError(103); break;
                                     case Integer : F.Type = Real; F.R = F.I; break;
                                     case Unknown : break; // nothing
                                   } .) .

  Number<VALUE &C>
    =                           (. char Str[100]; .)
      integer                   (. LexString(Str, sizeof(Str) - 1);
                                   C.Type = Integer; C.I = atoi(Str); .)
      | real                    (. LexString(Str, sizeof(Str) - 1);
                                   C.Type = Real; C.R = atof(Str); .) .
END CalcC.

// Various common items for calculator

#ifndef MISC_H
#define MISC_H

#include <stdio.h>
#include <stdlib.h>
#include <string.h>
#include <stdarg.h>
#include <ctype.h>
#include <limits.h>

#define  boolean  int
#define  bool     int
#define  true     1
#define  false    0
#define  TRUE     1
#define  FALSE    0
#define  maxint   INT_MAX

#if __MSDOS__ || MSDOS
#  define  pathsep '\\'
#else
#  define  pathsep '/'
#endif

static void appendextension (char *oldstr, char *ext, char *newstr)
// Changes filename in oldstr from PRIMARY.xxx to PRIMARY.ext in newstr
{ int i;
  char old[256];
  strcpy(old, oldstr);
  i = strlen(old);
  while ((i > 0) && (old[i-1] != '.') && (old[i-1] != pathsep)) i--;
  if ((i > 0) && (old[i-1] == '.')) old[i-1] = 0;
  if (ext[0] == '.') sprintf(newstr,"%s%s", old, ext);
    else sprintf(newstr, "%s.%s", old, ext);
}

typedef enum { Real, Integer, Unknown } TYPES;

struct VALUE {
  TYPES Type;
  float R;
  int I;
};

struct ENTRY {
  char Name[25];
  VALUE Value;
};

static ENTRY Memory[100];
static int Last;

static void Retrieve(char *N, VALUE &V) {
  strcpy(Memory[0].Name,N);
  int i = Last;
  while (strcmp(N, Memory[i].Name)) i--;
  if (i)
    V = Memory[i].Value;
  else
    V.Type = Unknown;
}

static void Store(char *N, VALUE V) {
  strcpy(Memory[Last+1].Name, N);
  int i = 1;
  while (strcmp(N, Memory[i].Name)) i++;
  Memory[i].Value = V;
  if ((i > Last)) {
    Last++;
    if (Last == 100) { printf("Memory Overflow"); exit(1); }
  }
}

#endif /* MISC_H */