Interpreting an Imperative Language

In this exercise you will specialise an interpreter for a very simple imperative language. The interpreter defines a function exec that maps a statement and environment before its execution, to the environment afterwards, containing possibly modified values. Your goal for specialisation is to remove the overhead of interpreting the source program, of course, but also to remove the structure of the environment and the overhead of environment lookups. To meet that goal you will need to make some binding-time improvements to the interpreter. [Hint: think about continuation passing style].

Here is the interpreter:

module Imperative where

data E = Con Int | Var String | Prim String E E
data S = Skip | Assign String E | Block String S | Seq S S |
         While E S

eval e env =
  case e of
    Con n -> n
    Var s -> look s env
    Prim op e1 e2 -> prim op (eval e1 env) (eval e2 env)

prim s v1 v2 =
  if s=="+" then v1+v2
  else if s=="-" then v1-v2
  else if s=="*" then v1*v2
  else error ("Bad operator "++s)

exec s env =
  case s of
    Skip -> env
    Assign x e -> assign x (eval e env) env
    Block x s -> tail (exec s ((x,0):env))
    Seq s1 s2 -> exec s2 (exec s1 env)
    While e s -> while e s env

while e s env =
  if eval e env==0 then env else while e s (exec s env)

look s env = 
  case env of
    nv:env' ->
      case nv of
        (n,v) -> if s==n then v else look s env'

assign x y env =
  case env of
    nv:env' ->
      case nv of
        (n,v) -> if x==n then (n,y):env' else nv:assign x y env'

test = exec (Block "n"
              (Seq (Assign "n" (Con 6))
	           (Seq (Assign "ans" (Con 1))
		        (While (Var "n")
			  (Seq (Assign "ans" (Prim "*" (Var "ans") (Var "n")))
			       (Assign "n" (Prim "-" (Var "n") (Con 1))))))))
            [("ans",0)]
To save you a little effort, the source code includes some test data (the factorial program). It's sufficient just to give test as the initial call to the specialiser.
Last modified: Sun Sep 21 15:16:52 MEST 1997