Datatypes and Case

In this exercise you will specialise an interpreter for a simple functional language with case expressions. Once again, you will need to think about how to improve the binding-times before you will be able to achieve good specialisations.

Here is the interpreter, along with test data (the append function). Your goal is to generate a residual program as close to the usual definition of append as possible. The parameters of eval are the program to be interpreted (a list of function definitions), the expression to evaluate, and the environment. You will need to make prog and e static, and the structure of the environment static.

module ADT where

data E = Var String | Con String [E] | Case E [(String,([String],E))]
       | Call String [E]
data V = V String [V]

eval prog e env =
  case e of
    Var s -> look s env
    Con c es -> V c (evals prog es env)
    Case e bs -> case eval prog e env of
                   V c vs -> 
		     case look c bs of
		       (ns,e) ->
		         eval prog e (bind ns vs env)
    Call f es -> case look f prog of
                   (ns,e) ->
		     eval prog e (bind ns (evals prog es env) [])

evals prog es env =
  case es of
    [] -> []
    e:es -> eval prog e env:evals prog es env

bind ns vs env =
  case ns of
    [] -> env
    n:ns ->
      case vs of
        v:vs ->
	  (n,v):bind ns vs env

look z xys =
  case xys of
    xy:xys ->
      case xy of
        (x,y) ->
	  if x==z then y else look z xys

test = 
  eval [("app",(["xs","ys"],
                Case (Var "xs")
		  [("Nil",([],Var "ys")),
		   ("Cons",(["x","xs"],
		            Con "Cons"
			      [Var "x",
			       Call "app"
			         [Var "xs",Var"ys"]]))]))]
       (Call "app"
         [Con "Cons" [Con "A" [],Con "Nil" []],
	  Con "Cons" [Con "B" [],Con "Nil" []]])
       []

Last modified: Sun Sep 21 16:39:04 MEST 1997