14
SOFTWARE—PRACTICE AND EXPERIENCE, VOL. 27(1), 49–62 (JANUARY 1997) An Experiment in Abstract Machine Design stephan diehl FB 14-Informatik, Universita ¨t des Saarlandes, Postfach 15 11 50, 66041 Saarbru ¨cken, Germany (email: diehlKcs.uni-sb.de) SUMMARY In this article we present Typed Feature Structures as an extension of Prolog, and show how to come up with a compilation scheme and an abstract machine using a design methodology based on partial evaluation. First we define the transformations used by our partial evaluator. Then we present the design methodology which we will use later. Next, we clarify the notion of Typed Feature Structures that underlies our work, and formally define the unification of such structures. Based on this definition, we develop a unification procedure with explicit heap representation. By partially evaluating this procedure with respect to some example programs, we show how to come up with the machine instructions and translation schemes. Finally, we briefly address coreferences, cyclic structures and the unification of types. key words : logic programming; typed feature structures; abstract machines; WAM; compiler design; partial evalu- ation INTRODUCTION The more programming languages are freed from the ‘Von-Neumann style’, the more important are abstract machines. Abstract machines provide an intermediate target language for compilation. First, the compiler generates code for the abstract machine, then this code can be further compiled into real machine code or it can be interpreted. By dividing compilation into two stages, abstract machines increase the portability and maintainability of compilers. For compiling Prolog, and as a basis for compilers of other logic programming languages, the Warren Abstract Machine (WAM) is widely used. Peter Kursawe 1 shows how some of the WAM instructions for unifi- cation, originally invented by Warren, 2 can be reinvented by using partial evaluation. Later, Nilsson 3,4 derived some of the control instructions of the WAM in a similar way. To our knowledge, we are the first to use this methodology to ‘invent’ WAM- like instructions, not ‘reinvent’ WAM instructions. Moreover, the methodology both guides the design and relates source language constructs to machine instructions. Although the methodology has only been applied in the context of logic programming, we are convinced that it can be applied to other languages, too. For example, it is not difficult to design some of the P-machine instructions by applying the methodology to an interpreter for arithmetic expressions. In the following sections we apply the methodology to come up with machine instructions for Typed Feature Structures. These are an extension of first-order terms in Prolog. Basically, we allow structures and predicates to have typed and labelled CCC 0038–0644/97/010049–14 Received 25 May 1994 1997 by John Wiley & Sons, Ltd. Revised 22 May 1996

An Experiment in Abstract Machine Design - Uni Trierdiehl/pubs/speAM.pdf · An Experiment in Abstract Machine Design stephan diehl FB 14-Informatik, Universita¨t des Saarlandes,

  • Upload
    lyxuyen

  • View
    214

  • Download
    0

Embed Size (px)

Citation preview

SOFTWARE—PRACTICE AND EXPERIENCE, VOL. 27(1), 49–62 (JANUARY 1997)

An Experiment in Abstract Machine Design

stephan diehlFB 14-Informatik, Universita¨t des Saarlandes, Postfach 15 11 50, 66041 Saarbru¨cken,

Germany (email: diehlKcs.uni-sb.de)

SUMMARY

In this article we present Typed Feature Structures as an extension of Prolog, and show how tocome up with a compilation scheme and an abstract machine using a design methodology basedon partial evaluation. First we define the transformations used by our partial evaluator. Then wepresent the design methodology which we will use later. Next, we clarify the notion of TypedFeature Structures that underlies our work, and formally define the unification of such structures.Based on this definition, we develop a unification procedure with explicit heap representation. Bypartially evaluating this procedure with respect to some example programs, we show how to comeup with the machine instructions and translation schemes. Finally, we briefly address coreferences,cyclic structures and the unification of types.

key words: logic programming; typed feature structures; abstract machines; WAM; compiler design; partial evalu-ation

INTRODUCTION

The more programming languages are freed from the ‘Von-Neumann style’, the moreimportant are abstract machines. Abstract machines provide an intermediate targetlanguage for compilation. First, the compiler generates code for the abstract machine,then this code can be further compiled into real machine code or it can be interpreted.By dividing compilation into two stages, abstract machines increase the portabilityand maintainability of compilers. For compiling Prolog, and as a basis for compilersof other logic programming languages, the Warren Abstract Machine (WAM) iswidely used. Peter Kursawe1 shows how some of the WAM instructions for unifi-cation, originally invented by Warren,2 can be reinvented by using partial evaluation.Later, Nilsson3,4 derived some of the control instructions of the WAM in a similarway. To our knowledge, we are the first to use this methodology to ‘invent’ WAM-like instructions, not ‘reinvent’ WAM instructions. Moreover, the methodology bothguides the design and relates source language constructs to machine instructions.Although the methodology has only been applied in the context of logic programming,we are convinced that it can be applied to other languages, too. For example, it is notdifficult to design some of the P-machine instructions by applying the methodology toan interpreter for arithmetic expressions.

In the following sections we apply the methodology to come up with machineinstructions for Typed Feature Structures. These are an extension of first-order termsin Prolog. Basically, we allow structures and predicates to have typed and labelled

CCC 0038–0644/97/010049–14 Received 25 May 1994 1997 by John Wiley & Sons, Ltd. Revised 22 May 1996

50 s. diehl

arguments similar to records in Pascal. Via types, a certain kind of inheritance isadded to the language. Typed Feature Structures have been used as knowledgerepresentation formalisms in AI and computational linguistics for a number of years.

PARTIAL EVALUATION

In logic programming there are several program transformation techniques which canbe used in a partial evaluator. Some of these are unfolding and folding, forwardunification, backward unification, deletion of unification, computation of standardpredicates, disjunction elimination and many other source-to-source transformations.5–8

Next, we define those transformations used in our partial evaluator.

Unfolding: a literal in the intermediate code is replaced by the corresponding instanceof the body of one or more of its defining clauses.

Let L be a literal andLi : −Gi all variants of clauses forL. Then replaceL bythe disjunction (G9

1, %, G9k), whereG9

i = (t01 = ti1, %, t0n = tin, Gi) and L = p(t01,%, t0n) and Li = p(ti1, %, tin).Folding: if a part of the intermediate code matches a defining clause of a predicate,that part is replaced by the corresponding instance of the predicate. Note that thistransformation should only be applied if the predicate has only one defining clause.

Let C = L1: −G1, %, Gk be a clause andL2: −Gi1, %, Gin

a variant of anotherclause, such that {Gi1

, %, Gin} # { G1, %, Gk}. Then delete all occurrences ofGij

in C and add the goalL2 to the body of the clauseC.Evaluation of a predicate: if the evaluation of a predicate succeeds, it is replacedby true and the corresponding bindings take place; otherwise it is replaced byfail.Syntactic Transformations:

(p1, %, true, %, pn) -- . (p1, %, pn)(p1, %, fail, %, pn) -- . fail(p1; %; true; %; pn) -- . true(p1; %; fail; %; pn) -- . (p1; %, pn)(true- .alt1;alt2) -- . alt1(fail- .alt1;alt2) -- . alt2(true- .alt1) -- . alt1(fail- .alt1) -- . true

Our partial evaluator is based on the work of Lakhotia and Sterling.9 The heart ofthe partial evaluator consists of the following definitions:

peval(Head,BodyResidue) :-

should unfold(Head),!,clause(Head,Body),peval(Body,BodyResidue).

peval(Goal,true) :- evaluable(Goal),call(Goal).

peval(Goal,fail) :- evaluable(Goal),!.

The predicateshould unfold provides us with the ability to control unfolding, i.e.,the user of the partial evaluator can define this predicate depending on the interpreterthat is going to be partially evaluated. In this way, meta-knowledge about theinterpreter can be provided. The predicateevaluable decides whether or not aliteral should be evaluated.

51an experiment in abstract machine design

DESIGN METHODOLOGY FOR ABSTRACT MACHINES

Kursawe1 derived the unification instructions of the WAM by partially evaluating aunification procedure written in Prolog. Nilsson3,4 used the same approach to derivesome of the control instructions of the WAM. He also expounds the view thatpartial evaluation and other program transformations are part of a methodology todesign abstract machines for logic programming.

Kursawe introduced special unification predicates, and used these to make unifi-cation explicit in Prolog clauses. Then he partially evaluated these clauses withrespect to the definition of the unification predicates. Next he replaced recurringpatterns in the resulting partially evaluated clauses by ‘machine instructions’. Thefollowing example shows this process for the simple case of the clauseappend([],L,L):

append([],L,L).↓ make unification explicit

append(A1,A2,A3) :— unipp([],A1),unipp(L,A2),unipp(L,A3).↓ partial evaluation

append(A1,A2,A3) :— (var(A1), A1 = []; [] == A1), unipp(A2,A3).↓ define ‘machine instructions’

append(A1,A2,A3) :— unipp constant([],A1),unipp(A2,A3).

Note that the result of this method is twofold: (1) compilation of a program intomachine code; and (2) design of an abstract machine by defining its machine instruc-tions.

In this paper, we use the following similar methodology, which consists of thefollowing steps.*

1. Define an interpreter.2. Change the interpreter by making the heap representation and the unifications

explicit.3. Partially evaluate the interpreter with respect to some example inputs.4. Look for patterns in the intermediate code and define corresponding machine

instructions.5. Fold the result of the partial evaluation using the machine instructions.6. If the resulting code contains predicates or Prolog constructs which are not

machine instructions, or the machine instructions are not deterministic or areunsuitable for conventional computer architectures, then repeat the design loop(steps 2 to 5).

TYPED FEATURE STRUCTURES

In computational linguistics, Typed Feature Structures and extensions thereof areused to write grammars for natural language processing. In AI, Typed FeatureStructures are at the heart of frame-like knowledge representation formalisms. Firstwe give the syntax of Typed Feature Structures, which we will use throughout thispaper. Basically, a Typed Feature Structure consists of its type and a list ofattribute/value pairs (AVPAIRS ). The types are organized in a type hierarchy, which

* Here the interpreter is a procedure for unifying Typed Feature Structures.

52 s. diehl

has to be defined by the user. Typed Feature Structures as we present them hereare similar to thec-terms in LOGIN.10

TFS → TYPE:[AVPAIRS ]uTYPE:[] uSYMBOL = TFSuTERM

AVPAIRS → SYMBOL TFS uSYMBOL TFS, AVPAIRS (1)

The following are two unit clauses in Prolog and Typed Feature Structures:

person:[name arthur, office address:[street park ave, no 14,city boston]].homeworker:[office X =address:[], home X].

In the Typed Feature Structure of typehomeworker above, the coreferenceX denotesthat the attributesoffice and home share the same valueaddress:[] . Here [] doesnot denote the empty list, but a typed feature structure without attribute/value pairs,i.e., address:[] unifies with every Typed Feature Structure of typeaddress .Coreferences are closely related to Prolog’s logic variables. Actually, we will treatthem as syntactic sugar. In Prolog the notion of types and inheritance can beimplemented using chain rules:animal(X) :- mammal(X). mammal(X) :- dog(X) .

These rules state that every dog is an animal, thus all rules for animals can beapplied for dogs. This is a very inefficient way in which to express subtype relations.If types and inheritance hierarchies are explicit, then we can use typed unificationinstead of standard Prolog unification. In the following, we assume that there issuch an explicit hierarchy (directed acyclic graph), and that we can compute thegreatest lower boundglb(t1,t2) and test inheritancet1 # t2 of two types t1 and t2 inthat hierarchy. In Prolog each predicate has a fixed arity and arguments are positional.The following example shows how the use of labels and types differs from theProlog notation:

in Prolog: person(name(john,X),Y).using labels and types: person:[name name:[first john, last X],

address Y].person:[address Y, name name:[last X,first john]].person:[address Y].

The main difference is that in Typed Feature Structures, neither the order in whicharguments occur nor the number of arguments is fixed (cf. keyword parameter inLISP). Typed Feature Structures have been essential parts of recently proposedlinguistic formalisms.11 Some of these are Functional Unification Grammar (FUG),Parse and Translate II (PATR-II), Lexical Functional Grammar (LFG) and Head-driven Phrase Structure Grammar (HPSG). In HPSG rules, principles and lexiconentries are represented as Typed Feature Structures. The following is an example ofan HPSG-like feature structure:

53an experiment in abstract machine design

Figure 1. Different representations for Typed Feature Structures

reflexive-verb

SY N/LOC/HEAD

SEM/CONT

vhead[ ]

basic-circumstance

RELN

AGENT

PATIENT

n1n1

(2)

Using our notation, this could be written as

reflexiv-verb:[syn syntax:[loc local:[head vhead:[]]] ,

sem semantic:[cont basic-circumstance:[agent X,

patient X]]].

Unification of acyclic Typed Feature Structures

Before we formally define the unification of Typed Feature Structures, we givean example, which covers many of the interesting cases:

X = person:[name X, office address:[street main street], age 35],Y = person:[office home address:[number 4], name john].

Assuming thathome address is a subtype ofaddress , the unification ofX andY yields:

person: [name john,office home address:[street main street, number 4],age 35]

Readers interested in the methodology and not so much in the details of theunification of Typed Feature Structures might skip the rest of this section.

For the following definitions we translate coreferences into path equations. Further-

54 s. diehl

more, we will use a special symbolÁ (top), which unifies with every other value.The notation 2A denotes the powerset ofA, i.e. the set of all subsets of the setA.We will write e to denote the symmetric, transitive closure of the relatione.Furthermore, the domain of a function is dom(f) = { a : f(a) is defined} and therestriction of a functionf to a setA is defined asfuA = {( a,f(a)) : a P A and f(a)is defined}.

Every Typed Feature Structure can be regarded as a triple comprising its type, apartial mapping from attributes to values, and a set of path equations.

Definition

7^6 = 7=3%6 × (!775(@87%6 → 9!+8%6) × %49!+8%6 = 7^6 < !72}6 < { Á} (3)%4 = 23!7*×3!7*

3!7* = 1 → !775(@87%6

The value of a pathp in a given Typed Feature Structure (t,f,e) is denoted byc(p,(t,f,e),0), which is formally defined as:

c(p,v,n) =

c(p,f(p(n)),n+1)

v

Á

if p(n) is defined

andv = (t,f,e) P 7^6

if p(n) is undefined

if v = Á

(4)

We call a Typed Feature Structure well-formed if it does not violate any of its pathequations, i.e., a Typed Feature Structure (t,f,e) is well-formed iff, for every (p,q)P e, we havec(p,(t,f,e),0) ; c(q,(t,f,e),0) and for everya P !775(@87%6the valuef(a) is well-formed.

Now we have to define the congruence (;) of two Typed Feature Structures

a ; a if a P !72}6Á ; v if v P 9!+8%6v ; Á if v P 9!+8%6 (5)(t1,f1,e1) ; (t2,f2,e2) if t1 v t2 or t2 v t1

and∀a P dom(f1) < dom(f2): f1(a) ; f2(a)

The unification of two Typed Feature Structures basically consists of the greatestlower bound of their types, the unification of their attribute/value lists and the unionof their path equations. In addition, the resulting Typed Feature Structure must bewell-formed:

a t a = a

(t1,f1,e1)t(t2,f2,e2) = (glb(t1,t2),f1tf2, e1<e2)

if glb(t1,t2) ± ',

f1tf2 is defined

and (glb(t1,t2), f1tf2, e1<e2)

is well-formed

(6)

55an experiment in abstract machine design

f1tf2 = f1udom(f1)−dom(f2) < f2udom(f2)−dom(f1)

<{( a,f1(a)tf2(a)) : a P dom(f1)>dom(f2)}

Note thatatb is not defined for two atomsa, b and a ± b. In this case, we saythe unification fails. Furthermore, iff1(a) t f2(a) is undefined for some attributeaP dom(f1) > dom(f2), then f1 t f2 is undefined, i.e., the unification fails. Last butnot least, if glb(t1,t2) = ', then (t1,f1,e1) t (t2,f2,e2) is not defined, and as beforethe unification fails.

THE METHODOLOGY AT WORK

The above definition of the unification of two Typed Feature Structures was thebasis for a unification procedure based on Prolog structures and lists. Next we madeunifications and the heap representation explicit using the following predicates:

heap(Addr,Tag,Value) reads the Tag and Value at Addr

heap entry(Addr,Tag,Value) writes the Tag and Value on top of the

heap and returns that Addr

heap change(Addr,Tag,Value) writes the Tag and Value at Addr

Some of the properties of the representation shown inFigure 2are:

(i) Nodes can point to newer ones, i.e., after unifying two nodes, one node pointsto the other, which represents the result of the unification.

(ii) The heap cells subsequent to the node always contain the first element of theattribute value list.

(iii) Four heap cells above the node, the type entry is stored.(iv) Type entries can point to newer ones, i.e., when two nodes with incomparable

types are unified, the type entry points to a new type entry for the unified type.(v) Attribute value list elements can point to the next attribute value list element.(vi) The value of an attribute value list is always a variable (REF), which can

point to the actual value.(vii) The end of the attribute value list or the empty attribute value list always

allocates two heap cells for the attribute and the value, which might be storedthere later. This is necessary to merge the attribute value lists of two structures.

When executing a Prolog program, arguments of a goal are unified with thearguments of a head of a program clause. If this unification succeeds, the literals ofthe body of the clause become new goals. Now the idea is that goals are alreadystored on the heap, whereas the program clauses are represented as Prolog terms.After unification of the goal on the heap and the Prolog term in the program clause,the result is stored on the heap and can be unified with another argument.

Thus, in our unification procedure we have to make the way in which the featurestructure is stored on the heap explicit. Furthermore unifications, and thus the useof logical variables, have to be made explicit and replaced by assignments or simpleunifications. Last but not least, we have to strive for determinism, because theWAM-like instructions we are going to derive should be deterministic and suitablefor conventional computer architectures. As a result, we actually use a sublanguageof Prolog, which can be given a different interpretation as an imperative language

56 s. diehl

Figure 2. Heap representation of Typed Feature Structures

with pattern matching. In this setting the predicate=/2 is read as assignment andpattern matching,= =/2 as an equality test and(X- .Y;Z) as conditional (nobacktracking). After many iterations of the design loop, we obtained the finalinterpreter. The excerpts of the source code (Figure 3) show the low level ofabstraction which is used to write the interpreter. We use the prefixuniph forpredicates, which unifyProlog terms with terms stored on theheap.

Meta-knowledge

To guide partial evaluation we had to provide some meta-knowledge. First, allpredicates with the prefixuniph should be unfolded if their first argument is

57an experiment in abstract machine design

Figure 3. Final version of interpreter

58 s. diehl

bound. Furthermore, the predicate= =/2 can be evaluated if its arguments are bound.The predicate=/2 can be evaluated if its first argument is bound, and the predicatesvar/1 and nonvar/1 have to be evaluated whatever their argument might be.

Intermediate code produced by partial evaluation

In the following sections, we only considerread mode. For details onwrite modesee elsewhere.5 The intermediate code, as we present it here, is difficult to readbecause of the heavy use of parentheses. These indicate the tree structure of thecode, which is important for the later folding phase.

Partial evaluation ofyields the code inFigure 4.

Figure 4. Intermediate code

The intermediate code is not very readable, but the parentheses make the treestructure of the intermediate code explicit. This tree structure is important for thepattern matching, which takes place when we try to fold the intermediate code.

After partially evaluating some example programs with respect to the unificationprocedureuniph tfs and flattening the resulting code, we found recurring patterns.These have been the basis for the definition of WAM-like instructions for TypedFeature Structures. All variables which occur in a pattern but are not local to thatpattern have to be passed in registers in the resulting machine instruction. In addition,the instructions are defined in such a way that all disjunctions and implications inthe intermediate code are within a single instruction. In other words, after folding

59an experiment in abstract machine design

we want the resulting code to be a conjunction of machine instructions. To achievethis goal we had to find out which parts of the interpreter caused problems fordefining such instructions. Then we had to solve these problems and change theinterpreter accordingly. Based on this experience, the following restrictions shouldbe satisfied for an interpreter to be suitable for our methodology:

(i) The clauses should be tail-recursive. If we allow general recursion, in theresulting abstract machine the content of variables would have to be storedon a stack, in order to be available after returning from recursive calls.

(ii) The number of arguments passed touniph calls has to be as small aspossible, because these arguments have to be passed in registers in the resultingabstract machine.

Looking at the intermediate code produced by partial evaluation of some examples,we defined the instructions shown inFigure 5.

Code produced by partial evaluation and folding

After folding the above code (Figure 4) by using our machine instructions(Figure 5), i.e., replacing patterns, which match the definition of a machine instruction

Figure 5. Definitions of abstract machine instructions

60 s. diehl

by that instruction, we obtained the ‘compiled’ program inFigure 6. Next weoptimized the instructions slightly. We combinedget node and get type toget typed node and saved one register. Furthermore, inget attribute , thepurpose of the last two arguments can be combined. Finally we got the followingfunctionality:

(a) get typed node t X1 X2If X1 points to an unbound variable, this instructions creates a new node withan empty attribute value list and saves its address in the unbound variablepointed to byX1 and the address of the empty attribute value list inX2. IfX1 is bound to a Typed Feature Structure, thenX2 gets bound to its attributevalue list and its type is unified witht .

(b) get attribute a X1 X2X2 points to an attribute value list. This instruction looks for the attributeain that attribute value list and bindsX1 to the value of the attribute valuepair found. If there is no such attribute in the attribute value list, a newattribute value pair is created at the end of the attribute value list, andX1points to its value (an unbound variable). The binding ofX2 is changed onlyif the first element in the attribute value list has the attributea. In this case,X2 gets bound to the next element in the list.

Translation schemes

A closer look at the WAM code generated above, and similar examples, revealsthe translation schemes inTable I, where kt l stands for a type name,kav1 l for anattribute value list,kal for an attribute andkv l for a value.

Coreferences, cycles and types

In our implementation coreferences are treated as syntactic sugar, e.g.

person:[name bill, home X =address: [], office X].

can be rewritten as

person:[name bill, home X, office X] :- unify(X,address:[]).

Figure 6. A ‘compiled’ unification call

61an experiment in abstract machine design

Table I. Translation schemes in READ mode

TFS construct Abstract machine code

kt l:[] get typed node kt l X1 X2get empty av1 X2

kt l:[ kav1 l] get typed node kt l X1 X2kGET instructions for kav1 l and the av1 stored in X2 l

kal kv l, kav1 l get attribute kal X3 X1kGET instructions for kv l and the value stored in X3 lkGET instructions for kav1 l and the av1 stored in X1 l

Our version of the WAM can also handle cyclic bindings. First, the modificationsfor Typed Feature Structures work as well for cyclic ones. In addition, we had tochange the way in which Prolog structures are represented in the WAM. Now insteadof one cell, two cells are allocated for the head of each structure. InTable II, weshow the heap after the structures at address 45 and 56 have been unified.

The STR cell is handled like a REF cell. Finally, the computation of greatestlower bounds of types in the inheritance hierarchy is based on a bit encoding ofthe inheritance relation.12

CONCLUSIONS

Using a methodology for the design of abstract machines, we invented WAM-likeinstructions for Typed Feature Structures. The methodology both guides the designand relates source language constructs to machine instructions. Finally, we optimizedthe new machine instructions slightly, and came up with compilation schemes forTyped Feature Structures.

Partial evaluation has been done fully automatically using the partial evaluatordescribed in the author’s thesis.5 The abstract machine has been implemented in Cwithout any problems, since the definitions inFigure 5 can be translated into Cusing macros forheap entry , deref , etc. Integrating the compilation schemes ofTable I into an existing Prolog compiler13 was not difficult. This is not surprising,because when we wrote the unification algorithmuniph tfs we tried to adopt theWAM principles.14

We feel that our use of the design methodology is very promising, and that it is

Table II. Modified WAM representation of Prolog structures

Address Tag Value

45 STR 5646 STRNAME f%

56 STR 5657 STRNAME f%

62 s. diehl

a very interesting question as to whether it scales up. Can we use the methodologyto derive instructions for extensions of Typed Feature Structures (e.g., disjunctions,functional uncertainty,%), or can we even use the methodology to derive newcontrol instructions for a totally different search algorithm which would replace theProlog depth-first search? Looking at current knowledge representation formalismsin AI (e.g., KL-ONE, LOOM, CLASSIC, TDL) and recently developed hybridprogramming languages (e.g., LIFE, OZ), we find that logic becomes more and moreimportant. We expect that the use of a methodology to design abstract machinesand code generation schemes will make it much easier and less error-prone to writecompilers for such AI formalisms and programming languages. Although we havepresented the methodology in the context of logic programming, we are convincedthat it is applicable to other language paradigms as well. Usually, abstract machinesare designed in anad hoc manner, often based on experience with other abstractmachines. In contrast, the methodology provides some guidance. Basically, what wesuggest is: (i) write an interpreter, (ii) partially evaluate it with respect to exampleprograms, (iii) find recurring patterns, and (iv) generalize the patterns as machineinstructions.

acknowledgement

I wish to thank Ulf Nilsson for his comments on a draft of this paper, StanleySelkow for many discussions, and the Fulbright Commission for making my stay atWPI possible.

REFERENCES

1. P. Kursawe, ‘How to invent a Prolog machine’,Proc. Third International Conference on LogicProgramming, Lecture Notes in Computer Science 255, Springer-Verlag, Berlin, 1986, pp. 134–148.

2. D. H. D. Warren, ‘Implementing Prolog – compiling predicate logic programs’,D.A.I. Research ReportNo. 40, Edinburgh, 1977.

3. U. Nilsson, ‘Abstract interpretation & abstract machines: contributions to a methodology for theimplementation of logic programs’,PhD thesis, Linkoping University, Sweden, 1992.

4. U. Nilsson, ‘Towards a methodology for the design of abstract machines’,J. Logic Programming,16,163–189 (1993).

5. S. Diehl, ‘Prolog and typed feature structures: a compiler for parallel computers’,Master’s Thesis,Worcester Polytechnic Institute, Worcester, MA, 1993.

6. D. Sahlin, ‘The MIXTUS approach to automatic partial evaluation of full Prolog’,Proc. North AmericanConference on Logic Programming, MIT Press, 1990.

7. A. Lakhotia and L. Sterling, ‘ProMix: a Prolog partial evaluation system’, in L. Sterling (ed),ThePractice of Prolog, MIT Press, 1990, pp. 137–179.

8. M. Hanus, ‘Implementierung logischer Programmiersprachen’, Lecture Notes, Max-Planck-Institut fu¨rInformatik, Saarbru¨cken, Germany, 1992.

9. A. Lakhotia and L. Sterling, ‘How to control unfolding when specializing interpreters’,Technical ReportCES-88-08, Case Western Reserve University, Cleveland, OH, 1988.

10. H. Ait-Kaci and R. Nasr, ‘LOGIN: A logic programming language with built-in inheritance’,Journalof Logic Programming,3, 185–215 (1986).

11. S. Shieber,An Introduction to Unification-Based Approaches to Grammar, Center for the Study ofLanguage and Information, Stanford University, 1986.

12. H. Aıt-Kaci, R. Boyer, P. Lincoln and R. Nasr, ‘Efficient implementation of lattice operations’,ACMTrans. Programming Languages and Systems,11(1), 115–146 (January 1989).

13. D. M. Russinoff, ‘A verified Prolog compiler for the Warren Abstract Machine’,Journal of LogicProgramming,13, 367–412 (1992).

14. H. Aıt-Kaci, Warren’s Abstract Machine – A Tutorial Reconstruction, MIT Press, 1991.