1% BEGIN LICENSE BLOCK
2% Version: CMPL 1.1
3%
4% The contents of this file are subject to the Cisco-style Mozilla Public
5% License Version 1.1 (the "License"); you may not use this file except
6% in compliance with the License.  You may obtain a copy of the License
7% at www.eclipse-clp.org/license.
8% 
9% Software distributed under the License is distributed on an "AS IS"
10% basis, WITHOUT WARRANTY OF ANY KIND, either express or implied.  See
11% the License for the specific language governing rights and limitations
12% under the License. 
13% 
14% The Original Code is  The ECLiPSe Constraint Logic Programming System. 
15% The Initial Developer of the Original Code is  Cisco Systems, Inc. 
16% Portions created by the Initial Developer are
17% Copyright (C) 2006 Cisco Systems, Inc.  All Rights Reserved.
18% 
19% Contributor(s): 
20% 
21% END LICENSE BLOCK
22
23
24%----------------------------------------------------------------------
25\section{Overview}
26
27\index{abstract machine}
28\index{Warren Abstract Machine}
29\index{WAM}
30\eclipse's abstract machine is a variant of the Warren Abstract
31Machine \cite{warren83}. Familiarity with its concepts will help
32understanding this section.
33
34The main differences between the original WAM and our machine's
35corresponding features are
36\begin{itemize}
37\item Separate machine words used for tag and value.
38\item Separate choicepoint ("control") and environment ("local") stacks.
39\item No CP (continuation pointer) register. The return address
40        is passed via the local stack.
41\item Allocation of temporaries on the local stack rather than in
42        (argument) registers.
43\item A different scheme (\cite{compnd}) for the compiled
44        unification and construction of compound terms.
45\item Separate calling conventions for Prolog predicates and external
46        predicates (written in the implementation language C).
47\item A weaker form of environment trimming.
48\end{itemize}
49The main additional functionality of the {\eclipse} abstract machine
50consists in
51\begin{itemize}
52\item support for attributed variables
53\item support for goal suspension and resuming
54\item support for cut and block/exit_block.
55\item support for dynamic and parallel choicepoints.
56\item support for synchronous event handling, including
57        triggering of garbage collection.
58\item hooks for a box-model tracer.
59\end{itemize}
60\index{sepia}
61Note that, for historical reasons, the name {\bf sepia} is sometimes
62used when talking about the {\eclipse} kernel.
63
64
65%----------------------------------------------------------------------
66\section{Storage Model/Memory Organisation}
67
68\subsection{Stacks}
69{\eclipse} stores information in the following memory areas, see figure
70\ref{figstacks}:
71\index{shared heap}
72\index{stack}
73\begin{description}
74\item[abstract machine descriptor] the abstract machine registers\index{registers}
75        (argument registers, stack pointers, etc)
76\item[shared heap] abstract machine code, shared ground terms,
77        heap copied terms (setval, record, etc)
78\item[local stack] return addresses, environment frames
79\item[control stack] choice points (copies of parts of the
80        abstract machine state)
81\item[trail stack] undo information (pointers into the stacks, possibly
82        with associated data)
83\item[global stack] most variable-sized data (lists, structures,
84        strings, bignums, suspended goal descriptors, etc)
85\end{description}
86\begin{figure}
87\epsfbox{stacks.eps}
88\label{figstacks}
89\caption{{\eclipse} memory areas}
90\end{figure}
91The following choices have been made in the current implementation:
92\begin{itemize}
93\item Each stack occupies a consecutive memory area.
94\item Stacks are paired (control-local and global-trail) and each pair
95        grows towards each other.
96        Therefore there is only a common size limit for each pair,
97        not for each individual stack.
98\item A maximum amount of virtual address space is reserved for each
99        stack pair, physical memory is mapped (in reasonably large increments)
100        into the virtual space as the stacks grow, and unmapped as they
101        shrink.
102\end{itemize}
103To simplify address comparisons, the abstract machine requires that
104\index{local stack}
105\index{global stack}
106\begin{itemize}
107\item the local stack is at higher addresses than the global stack
108\item the local stack grows from high to low addresses
109\item the global stack grows from low to high addresses
110\end{itemize}
111
112
113
114\subsection{Data Representation}
115\label{chapdatarep}
116
117{\eclipse} uses a tagged\index{tagged}  data representation.
118The basic data unit in {\eclipse} is the {\bf pword}\index{pword}.
119It consists of a value and tag field, both are the size of a machine
120{\bf word} (32 bit or 64 bit, by which we mean the size of
121a pointer on that machine). In more detail, the layout of a pword is:
122\begin{verbatim}
12332-bit:   31   30   29   28           7 6 5 4 3 2 1 0
12464-bit:   63   62   61   60           7 6 5 4 3 2 1 0
125        +---+----+----+----+---------+---------------+
126        |REF|MARK|LINK|MISC|   ...   |      TXXX     |
127        +---+----+----+----+---------+---------------+
128        |              pointer-sized value           |
129        +--------------------------------------------+
130
131        typedef struct s_pword
132        {
133            value val;                      /* value part first */
134            type tag;                       /* then tag part */
135        } pword;
136\end{verbatim}
137The conceptual tag is made up of the REF-bit and the 8-bit-tag TXXX
138(where TXXX is TINT for integers, TFLOAT for floats etc).
139The MARK\index{MARK}  and LINK\index{LINK}  bits are used by the garbage collector (the MARK
140bits also temporarily in routines like term copying).
141The MISC bit is used for different purposes with different kinds of tags,
142see below.
143The remainder of the space in the tag word is reserved, and currently
144only used for some variables (to store the variable name),
145and dictionary string buffers (to store a reference count).
146
147Other frequently used data type on the implementation level are:
148\begin{verbatim}
149word             pointer-sized signed integer
150uword            pointer-sized unsigned integer
151value            a word-sized union of types for values
152type             a word-sized union of integers for tags
153int32            32-bit signed integer
154uint32           32-bit unsigned integer
155dident           dictionary identifier (pointer to descriptor)
156pri*             procedure identifier (pointer to descriptor)
157\end{verbatim}
158
159
160\subsubsection{Atomic Types, Boxed and Unboxed}
161Figure \ref{figatomic} gives an overview of the atomic data types of
162{\eclipse}.
163\begin{figure}
164\epsfbox{ecatomic.eps}
165\label{figatomic}
166\caption{{\eclipse} atomic data types}
167\end{figure}
168\index{boxed}
169Constants whose value does not fit into a word are {\it boxed}, i.e. the
170value part of the pword contains a pointer to a buffer, which in turn
171holds the constant's value. The buffer\index{buffer}  is usually on the global stack,
172but may also be in the heap (e.g. for constants\index{constants}  occurring in program code).
173Stack buffers have a pword-sized
174header, consisting of a TBUFFER\index{TBUFFER}  tag and a value indicating the number of
175valid bytes in the buffer (minus 1).  The physical size of the buffer is
176this content size rounded up to a multiple of a pword.
177
178\subsubsection{Small Integers}
179Signed two's complement integers\index{integers}  up to the machine's wordsize are an
180atomic types and are represented with a TINT\index{TINT}  tag.  Larger integers are
181represented as {\em bignums}.
182
183\subsubsection{Atoms}
184Atoms\index{Atoms}  are represented with a TDICT\index{TDICT}  tag, the value part being a 
185pointer to their dictionary entry (dident, see \ref{chapdictionary}).
186An exception is the nil atom '[]', which has its own tag TNIL\index{TNIL}  and
187an undefined value part. The reason to have the TNIL tag is to speed
188up list operations by having only to deal with TLIST and TNIL tags.
189
190\subsubsection{Floats/Doubles}
191Older {\eclipse} versions supported both single and double precisions floats.
192This is no longer the case, the single float type has been dropped.
193On 64-bit machines, doubles\index{doubles}  are represented like small integers, with
194a TDBL tag, and the value part consisting of the actual double value.
195On 32-bit machines, doubles are {\it boxed}, i.e. the value part contains
196a pointer to a global stack buffer which then holds the actual double value.
197A boxed double therefore occupies 3 pwords: the TDBL\index{TDBL}-tagged pointer, the
198TBUFFER-tagged buffer header, and a pword-sized buffer holding the double
199value itself.
200The implementation uses the UNBOXED_DOUBLES\index{UNBOXED_DOUBLES}  macro to distinguish between
201the two possible representations.
202In the boxed case, the TDBL tag may have the PERSISTENT\index{PERSISTENT}  bit set (see
203ground constant optimisation \ref{secgroundconst}).
204
205\subsubsection{Bounded Reals}
206Bounded reals (breals\index{breals}) are an {\eclipse} specific data type consisting
207of two doubles representing an interval.  The are stored like
208boxed doubles, except that the buffer contains two doubles.
209The tag is TIVL\index{TIVL}.  Normally, the breal is canonical, i.e.\ the lower bound
210is not larger that the upper bound.  If this is not the case, the
211RAW_IVL\index{RAW_IVL}  (=MISC) bit  is set in the buffer tag (the lexical analyser can
212produce such objects).
213The TIVL tag may have the PERSISTENT bit set (see ground constant optimisation
214\ref{secgroundconst}).
215
216\subsubsection{Strings}
217Unlike many Prolog system, {\eclipse} has true strings.
218Strings\index{Strings}  are always {\it boxed}. The tag is TSTRG\index{TSTRG}, and the value is a pointer
219to a global stack buffer holding the actual string.
220Even though the buffer header contains an explicit length field,
221strings are additionally zero-terminated in order to be
222downward-compatible with C strings\index{strings}.  As long as the strings are only
223manipulated using {\eclipse}'s own string primitives, strings may
224contain embedded NUL\index{NUL}  bytes.  {\eclipse} strings are conceptually
225sequences of bytes, not characters in a particular encoding\index{encoding}.
226The TSTRG tag may have the PERSISTENT bit set (see ground constant optimisation
227\ref{secgroundconst}).
228The string buffer may have the IN_DICT\index{IN_DICT}  (=MISC) bit set, meaning that the
229string is part of the dictionary (see \ref{chapdictionary}).
230
231
232\subsubsection{Bignums}
233The main pword for a bignum has a TBIG\index{TBIG}  tag and a value pointing to a
234standard global stack buffer. 
235Bignum\index{Bignum}  (and rational) computations are delegated to the Gmp\index{Gmp}  (Gnu
236multi-precision, www.swox.com/gmp) library.  Gmp's limb array is stored
237in the global stack buffer. The number's sign is stored as the BIGSIGN\index{BIGSIGN}  (=MISC)
238bit in the buffer header tag. The library's MP_INT\index{MP_INT}  or MP_RAT\index{MP_RAT}  structure only
239gets created temporarily in order to pass the number to a gmp
240function.  Normally, computation results are always normalised such that
241word-sized integers are stored as small (TINT) integers, and bignums are
242always too large to fit into a word.  This rule is only violated
243temporarily (the bignum/2\index{bignum/2} predicate can create a short bignum in order
244to convert a TINT x TBIG operation into a TBIG x TBIG one, see arithmetic
245type coercion).
246The TBIG tag may have the PERSISTENT bit set (see ground constant optimisation
247\ref{secgroundconst}).
248
249\subsubsection{Rationals}
250Rationals\index{Rationals}  have a TRAT\index{TRAT}  tag and a consecutive pair of TBIG pwords on the
251global stack, representing the numerator\index{numerator}  and denominator\index{denominator}  (these
252bignums can actually be small integers, since it is probably not worth
253optimising this case).  Rational computations are delegated to the Gmp
254library, whose MP_RAT structure only gets created temporarily in order
255to pass the number to a gmp function.
256The TRAT tag may have the PERSISTENT bit set (see ground constant optimisation
257\ref{secgroundconst}).
258
259\subsubsection{External Data Handles}
260The handle type is intended to store references to non-{\eclipse} data.
261It consists of a THANDLE-tagged pointer to a pair of pwords on the global
262stack. The first on has a TEXTERN tag and a pointer to a type descriptor
263(struct t_ext_type) as specified in the Embedding Manual. The second one
264has a TPTR tag and pointer to arbitrary user-defined data.
265
266\subsubsection{Compound types (Lists and Structures)}
267Figure \ref{figcompound} shows the compound data types.
268\begin{figure}
269\epsfbox{eccomp.eps}
270\label{figcompound}
271\caption{{\eclipse} compound data types}
272\end{figure}
273Lists\index{Lists}  are represented by a TLIST\index{TLIST}-tagged pointer, pointing to a consecutive
274pair of pwords on the global stack, representing the list head\index{head}  and tail\index{tail}.
275
276General structures\index{structures}  are represented by a TCOMP\index{TCOMP}-tagged pointer pointing to
277consecutive pwords on the global stack, of which the first one represents
278the functor\index{functor}, and the following ones are the arguments from 1 to n (arity).
279The functor pword is similar to an atom, it has a TDICT\index{TDICT}  tag and a dident
280value.  The arity\index{arity}  can be looked up from the dident dictionary entry.
281While the arity for atoms is always 0, the arity for compound terms is
282always greater than 0.  There is no artificial upper limit for the arity.
283
284Both TLIST and TCOMP tags may have the PERSISTENT\index{PERSISTENT}  bit set when they point
285to ground data structures (see ground constant optimisation \ref{secgroundconst}).
286
287\subsubsection{Variables and References}
288\begin{figure}
289\epsfbox{ecvars.eps}
290\caption{{\eclipse} variable and reference types}
291\end{figure}
292References are distinguished from free variables\index{variables}  only by their value part:
293A self reference\index{self reference}  is a free variable\index{variable}, otherwise a reference\index{reference}  (an indirection)
294pointing to another word.
295All variable tags have the TREFBIT\index{TREFBIT}  (REF in the picture) set\footnote{
296This holds as of version 5.2. Previously, only the simple variable had
297the TREFBIT set}.
298
299In the reference (non-self-reference) case the rest of the tag is
300irrelevant.  In the self-reference case, the rest of the tag indicates
301the kind of variable (simple, named\index{named variable}, attributed, etc).
302Note that this scheme has the advantage that pwords can be copied
303regardless of their content: when copied, a variable automatically
304turns into a reference to the original variable (rather than creating
305a new, different variable).
306
307Variables with TNAME\index{TNAME}  and TMETA\index{TMETA}  tags reserve a 19-bit field in the tag
308for storing a variable name\index{variable name}  (mainly for debugging purposes).
309
310
311\subsubsection{Attributed Variables}
312
313Attributed variables\index{attributed variables}  consist of a TMETA\index{TMETA}-tagged self-reference pword,
314followed by a TCOMP-tagged pword representing a compound term with
315functor meta/N, which holds the N attributes.
316
317The HIDE_ATTR\index{HIDE_ATTR}  (=MISC) bit in TMETA tags is used as a marking bit to
318avoid looping during printing of attributes.
319
320
321
322\subsection{Creating Data}
323
324Data is created either by executing suitable abstract machine
325instructions, or by external (C, C++) code using the external
326interface macros/functions.
327
328\index{put instruction}
329\index{get instruction}
330The data-creating abstract machine instructions are essentially the
331{\bf Put} family, the {\bf Get} family in write mode and the
332{\bf Out_get} family.
333\begin{description}
334\item[Put/Get_constant] creates any atomic type in one of the
335        machine's argument registers.
336        There are a number of specialised instructions
337        (Get/Put_integer/atom/nil/...) for the most common data types.
338        In case of the types that don't
339        fit into a single word (strings, bignums), the data buffer is
340        located on the shared heap. The instruction just loads a pointer
341        to this shared buffer into the argument register, rather than
342        copying the buffer onto the global stack.
343\item[Put/Get_list/structure]
344        Structures and lists get created according to
345        \cite{compnd}. The head unification uses Get_list/structure
346        instructions followed by separate read and write sequences
347        ({\bf Read} and {\bf Write} instructions), the body
348        argument construction uses Put_list/structure instructions
349        followed by instructions of the {\bf Push} family.
350\end{description}
351
352
353%----------------------------------------------------------------------
354\section{Abstract Machine Registers}
355%----------------------------------------------------------------------
356
357The `registers' of the abstract machine\index{abstract machine}  are fields in the global
358data structure {\tt ec_.m} of type {\tt struct machine}.
359While the emulator\index{emulator}  is running, some of these conceptual registers
360are cached in local variables of the emulator function ec_emulate().
361
362\subsection{Basic Stack Management}
363\index{SP}
364\index{B}
365\index{TT}
366\index{TG}
367\index{SP_LIMIT}
368\index{B_LIMIT}
369\index{TT_LIMIT}
370\index{TG_LIMIT}
371\begin{sloppypar}
372\begin{description}
373\item[SP] top of local stack. The stacks grows towards lower addresses,
374        SP points to the top word. Word-aligned, contains a mixture
375        of pwords, saved E and saved PP registers.
376\item[B] top of control stack. The stack grows towards higher addresses.
377        B points to the first free word. Word-aligned, contains a mixture
378        of pwords and saved engine registers.
379\item[TT] top of trail stack. The stacks grows towards lower addresses,
380        TT points to the top word. Word-aligned, contains a mixture
381        of pwords and addresses and other words.
382\item[TG] top of global stack. The stack grows towards higher addresses.
383        TG points to the first free pword, the stack is pword-aligned.
384        Contains only items listed in \ref{chapdatarep}.
385\item[SP_LIMIT] allocation limit for the local stack. When SP crosses this
386        boundary, the local stack needs to be expanded immediately.
387        There is only a small margin of LOCAL_CONTROL_GAP between SP_LIMIT
388        and the end of the mapped memory.
389\item[B_LIMIT] allocation limit for the local stack. When B crosses this
390        boundary, the control stack needs to be expanded immediately.
391        There is only a small margin of LOCAL_CONTROL_GAP between B_LIMIT
392        and the end of the mapped memory.
393\item[TT_LIMIT] allocation limit for the trail stack. When TT crosses this
394        boundary, the trail stack needs to be expanded immediately.
395        There is only a small margin of TRAIL_GAP between TT_LIMIT
396        and the end of the mapped memory.
397\item[TG_LIMIT]
398	allocation limit for the global stack. When TG crosses this
399        boundary, the global stack needs to be expanded immediately.
400        There is only a small margin of GLOBAL_TRAIL_GAP between TG_LIMIT
401        and the end of the mapped memory.
402\end{description}
403\end{sloppypar}
404
405
406\subsection{Deterministic execution}
407\index{PP}
408\index{E}
409\index{A1..An}
410\index{S}
411\index{EXPORTED}
412\begin{description}
413\item[PP] program (code) pointer, points to next abstract machine instruction.
414\item[A1..A256] argument registers. Their number limits the maximum
415        arity of a predicate in \eclipse (but not the arity of
416        compound terms!).
417\item[E] current environment, points into the local stack.
418\item[S] structure pointer, used during unification and creation of
419        compound terms.
420\item[EXPORTED flag] abstract machine registers are exported from emulator,
421        i.e.\ they are not cached in emulator registers.
422\end{description}
423
424
425\subsection{Nondeterministic execution}
426\index{B}
427\index{TT}
428\index{EB}
429\index{GB}
430\index{LCA}
431\index{DET}
432\begin{description}
433\item[B] top of control stack. The stack grows towards higher addresses.
434        B points to the first free word. Word-aligned, contains a mixture
435        of pwords and saved engine registers.
436\item[TT] top of trail stack. The stacks grows towards lower addresses,
437        TT points to the top word. Word-aligned, contains a mixture
438        of pwords and addresses and other words.
439\item[EB] environment backtrack pointer, points into the local stack.
440        caches the value of E in the topmost choice point.
441\item[GB] global stack backtrack pointer, points into the global stack.
442        caches the value of TG in the topmost choice point.
443\item[LCA] last cut action. Top of a conceptual stack of {\it cut action}
444        descriptors, implemented as a list threaded into the global stack.
445\item[DET flag] no-choicepoint-flag: flag that indicates that
446        no choicepoint was created since procedure entry. It becomes invalid
447        after the first subgoal call.
448\end{description}
449
450\subsection{Suspend/Resume mechanism}
451In the following, `volatile' means that the register contents is short-lived
452and never gets saved and restored.
453\index{LD}
454\index{MU}
455\index{DE}
456\index{SV}
457\index{WL}
458\index{WP}
459\begin{description}
460\item[LD] top of the list of all suspended goals. This is a conceptual stack,
461        threaded into the global stack (i.e.\ it is a linked list of frames
462        with the links going strictly from newer to older frames in the stack).
463\item[MU] list of meta-unifications. A volatile register that passes a list
464        of attribute-value-pairs from the unification routine to the subsequent
465        meta-unify event handler.
466\item[DE] current suspension, volatile register to pass the address of
467        a suspension that needs re-suspending or waking.
468\item[SV] list of suspending variables. A volatile register that passes
469        a list from a C-builtin to the emulator code that created a
470        suspension for the builtin.
471\item[WL] points to the array (1..SUSP_MAX_PRIO) of woken lists
472        (a structure on the global stack).
473\item[WP,WP_STAMP] current execution priority. Only suspensions with higher
474        priority can interrupt the execution. WP is a tagged 
475        pword, and is paired with the WP_STAMP because it gets
476        value-trailed on change.
477\end{description}
478
479
480\subsection{Events and garbage collection}
481\index{GCTG}
482\index{TG_SL}
483\index{TG_SLS}
484\index{IFOFLAG}
485\index{GLOBVAR}
486\index{ALLREFS}
487\index{GLOBAL_NO_IT}
488\index{NO_EXIT}
489\index{WAS_EXIT}
490\index{EVENT_POSTED}
491\index{DEL_IRQ_POSTED}
492\begin{description}
493\item[GCTG] indicates the global stack address corresponding to the
494        topmost choicecpoint which already existed
495        during the last garbage collection. Everything older than this
496        does not need to be garbage collected again.
497\item[TG_SL] (TG soft limit) garbage collection and general event trigger.
498        This register normally points above the global stack top
499        (but within the already memory-mapped area). When the global stack
500        top TG crosses this boundary, a garbage collection is triggered.
501        The mechanism is also abused to trigger all other synchronous
502        engine events (by forcing TG_SL to zero).
503        This has the advantage that the execution overhead
504        for event handling is restricted to a simple $TG >= TG_SL$ test.
505        Unless when it is zero, TG_SL is always between TG and TG_LIMIT.
506\item[TG_SLS] (TG_SL shadow) when TG_SL is nonzero, TG_SLS has the same value.
507        When TG_SL is zero (a fake overflow, i.e.\ a general synchronous event),
508        TG_SLS keeps its original value, which is then used to reset TG_SL
509        after event handling.
510\item[IFOFLAG] a synchronisation flag used for mutual exclusion when
511        TG_SL is changed asynchronously from within an interrupt (signal)
512        handler.
513\item[GLOBVAR] points to the array (1..GLOBAL_VARS_NO) of \eclipse\
514        "global references" (a structure on the global stack).
515\item[ALLREFS] points to a list of eclipse_ref_ data structures, i.e.\
516        objects holding additional potential references to {\eclipse} data
517        from within code written using the embedding interface
518        (see ec_refs in the Embedding Manual).
519\item[GLOBAL_NO_IT flag] means that interrupts are currently disabled.
520\item[NO_EXIT flag] means that preemption via exit_block/1 is currently
521        prohibited (e.g.\ because the gc is running).
522\item[WAS_EXIT flag] an exit_block was attempted while NO_EXIT was set
523\item[EVENT_POSTED flag] the synchronous event-queue contains events
524\item[DEL_IRQ_POSTED flag] there is possibly a delayed interrupt among
525        posted events
526\end{description}
527
528
529\subsection{Parallelism}
530A number of additional registers can be found in the code.
531They are mainly related to parallelism\index{parallelism}, which is currently unsupported.
532
533
534%----------------------------------------------------------------------
535\section{Instruction Set}
536%----------------------------------------------------------------------
537
538The arguments of the instructions\index{instructions}  are denoted as follows:
539
540\begin{tabular}{|l|l|l|}
541\hline
542a(A)            & address & argument register A (1..255)\\
543y(Y)            & offset & environment slot Y (offset from E register)\\
544t(X)            & offset & temporary X (offset from SP register)\\
545ref(L)          & address & reference to code address L\\
546N               & integer & environment size\\
547I               & integer & number, e.g. arity\\
548F               & dident & functor (dictionary identifier)\\
549C               & pword & simple tagged Prolog word\\
550V               & value & value part of Prolog word only\\
551P               & proc & procedure identifier\\
552D               & bool & debug flag\\
553T               & tag & tag (possibly including variable name) \\
554\hline
555\end{tabular}
556
557\subsubsection{Simple Moves}
558These move\index{move}  one pword from a source location to a destination.
559
560%\begin{tabular}{|l|l|}
561\begin{tabular}{|p{0.35\textwidth}|p{.6\textwidth}|}
562\hline
563move(a(A))              & push a(A) onto local stack \\
564move(a(A1),a(A2))       & move from argument to argument  \\
565move(a(A),y(Y))         & move from argument to environment       \\
566move(y(Y),a(A))         & move from environment to argument      \\
567move(t(X),a(A))         & move from temporary to argument      \\
568move(y(Y),y(Y))         & move from environment to environment      \\
569\hline
570get_variable(N,a(A),y(Y))& allocate(N) + move(a(A),y(Y))        \\
571\hline
572\end{tabular}
573
574\subsubsection{General Unification}
575These access two general pwords and invoke the general unification\index{unification}  routine.
576As a result, failure can occur.  In case of success, the MU\index{MU}  register may
577hold a list of attributed variable that were unified. If so, this will
578trigger a meta-unify\index{meta-unify}  event at the next synchronous point
579(see \ref{seceventhandling}).
580\index{get instruction}
581
582%\begin{tabular}{|l|l|}
583\begin{tabular}{|p{0.35\textwidth}|p{.6\textwidth}|}
584\hline
585get_value(a(A1),a(A2))          & unify two argument registers             \\
586get_value(a(A),y(Y))            & unify argument and environment slot                \\
587get_value(a(A),t(X))            & unify argument and temporary                \\
588get_value(y(Y),y(Y))            & unify two environment slots               \\
589\hline
590\end{tabular}
591
592\subsubsection{Simple Unification}
593Unify argument register content with a constant:
594\index{get instruction}
595
596%\begin{tabular}{|l|l|}
597\begin{tabular}{|p{0.35\textwidth}|p{.6\textwidth}|}
598\hline
599get_constant(a(A),C)    & unify argument with arbitrary constant \\
600get_nil(a(A))           & unify argument with nil (the atom '[]') \\
601get_integer(a(A),V)     & unify argument with a (short) integer constant \\
602get_float(a(A),V)       & unify argument with a float constant \\
603get_atom(a(A),V)        & unify argument with an atom \\
604get_string(a(A),V)      & unify argument with a string constant \\
605\hline
606in_get_constant(a(A),C) & special case for input mode (a(A) instantiated) \\
607in_get_nil(a(A))        & special case for input mode (a(A) instantiated) \\
608in_get_integer(a(A),V)  & special case for input mode (a(A) instantiated) \\
609in_get_float(a(A),V)    & special case for input mode (a(A) instantiated) \\
610in_get_atom(a(A),V)     & special case for input mode (a(A) instantiated) \\
611in_get_string(a(A),V)   & special case for input mode (a(A) instantiated) \\
612\hline
613out_get_constant(a(A),C)& special case for output mode (a(A) uninstantiated) \\
614out_get_nil(a(A))       & special case for output mode (a(A) uninstantiated) \\
615out_get_integer(a(A),V) & special case for output mode (a(A) uninstantiated) \\
616out_get_float(a(A),V)   & special case for output mode (a(A) uninstantiated) \\
617out_get_atom(a(A),V)    & special case for output mode (a(A) uninstantiated) \\
618out_get_string(a(A),V)  & special case for output mode (a(A) uninstantiated) \\
619\hline
620\end{tabular}
621
622\subsubsection{Structure Unification}
623Compilation of compound\index{compound}  term unification is described in some more
624detail in section \ref{secstructunify}. The compiler generated a code sequence
625for unification of a possibly nested structure. The instructions starting
626these sequences are:
627\index{get instruction}
628
629%\begin{tabular}{|l|p{0.6\textwidth}|}
630\begin{tabular}{|p{0.35\textwidth}|p{.6\textwidth}|}
631\hline
632get_structure(a(A),F,ref(L))    & If argument is variable, push new structure
633        frame, set S register, and continue. If nonvariable, check if
634        structure with functor F, set S and jump to label L. Otherwise fail \\
635\hline
636get_list(a(A),ref(L))           & special case for list   \\
637in_get_structure(a(A),F,ref(L))         &        special case for input mode      \\
638in_get_list(a(A),ref(L))        & special case for list in input mode             \\
639out_get_structure(a(A),F)       & special case for output mode                    \\
640out_get_list(a(A))              &  special case for list in output mode           \\
641get_structure_arguments(a(A))   & special case input mode after switch            \\
642get_list_arguments(a(A))        & special case input mode after switch            \\
643\hline
644\end{tabular}
645
646If the input argument is instantiated to a structure, the structure
647arguments are matched or deconstructed with read instructions:
648\index{read instruction}
649
650%\begin{tabular}{|l|l|}
651\begin{tabular}{|p{0.35\textwidth}|p{.6\textwidth}|}
652\hline
653read_constant(C)          & match constant with location S++ \\
654read_nil                  & match nil constant with location S++ \\
655read_integer(C)           & match integer constant with location S++ \\
656read_float(C)             & match float constant with location S++ \\
657read_atom(C)              & match atom constant with location S++ \\
658read_string(C)            & match string constant with location S++ \\
659read_void                 & increment S \\
660read_void(N)              & increment S by N \\
661read_variable(a(A))       & move content of location S++ to argument \\
662read_variable(y(Y))       & move content of location S++ to environment \\
663read_variable(N,y(Y))     & move content of location S++ to new environment \\
664read_variable             & move content of location S++ to new temporary  \\
665read_value(a(A))          & unify argument with location S++ \\
666read_value(y(Y))          & unify environment slot with location S++ \\
667read_value(t(X))          & unify temporary with location S++ \\
668read_reference(a(A))      & create reference to S++ in argument \\
669read_reference(y(Y))      & create reference to S++ in environment \\
670read_reference(N,y(Y))    & create reference to S++ in new environment \\
671read_reference            & create reference to S++ in new temporary \\
672\hline
673\end{tabular}
674
675If the input argument is uninstantiated, the structure arguments get
676constructed by a sequence of write instructions. It is assumed that the
677preceding get/write/read_structure/list instruction has constructed the
678structure frame, and set the S register pointing to the arguments that
679need to be filled in by the write sequence:
680\index{write instruction}
681
682%\begin{tabular}{|l|l|}
683\begin{tabular}{|p{0.35\textwidth}|p{.6\textwidth}|}
684\hline
685write_constant(C)          & write constant to S++ \\
686write_nil                  & write nil constant to S++ \\
687write_integer(C)           & write integer constant to S++ \\
688write_float(C)             & write float constant to S++ \\
689write_atom(C)              & write atom constant to S++ \\
690write_string(C)            & write string constant to S++ \\
691write_void                 & create free variable at S++ \\
692write_variable             & create free variable at S++, put reference in new temporary  \\
693write_variable(a(A))       & create variable at S++, put reference in argument \\
694write_variable(y(Y))       & create variable at S++, put reference in environment \\
695write_variable(N,y(Y))     & create variable at S++, put reference in new environment \\
696write_value(a(A))          & move argument to location S++ \\
697write_value(y(Y))          & move environment slot to location S++ \\
698write_value(t(X))          & move argument to location S++ \\
699write_named_void(T)             & create named free variable at S++ \\
700write_named_variable(T)         & create named free variable at S++, put reference in new temporary  \\
701write_named_variable(a(A),T)    & create named variable at S++, put reference in argument \\
702write_named_variable(y(Y),T)    & create named variable at S++, put reference in environment \\
703write_named_variable(N,y(Y),T)  & create named variable at S++, put reference in new environment \\
704write_local_value(a(A))         & move argument to location S++, globalising if necessary \\
705write_local_value(y(Y))         & move environment slot to location S++, globalising if necessary \\
706write_local_value(t(X))         & move temporary to location S++, globalising if necessary \\
707\hline
708\end{tabular}
709
710Since nested structures are handled depth-first, a mechanism is required
711to keep track of the nesting level. Moreover, it is possible that a subterm
712of a read-mode structure is in write mode, so the mode may need to be changed
713when switching level up or down. Both these information bits are held in
714a per level temporary register.
715The read mode instructions are:
716
717%\begin{tabular}{|l|l|}
718\begin{tabular}{|p{0.35\textwidth}|p{.6\textwidth}|}
719\hline
720read_structure(F,ref(L))        & unify first compound subterm at a nesting level \\
721read_structure(F,t(X),ref(L))   & unify compound subterm after simple subterm \\
722read_next_structure(F,t(X),ref(L)) & unify compound subterm after compound subterm \\
723read_last_structure(F,ref(L))   & unify compound subterm which is last in term \\
724\hline
725read_list(ref(L))               & unify first list subterm at a nesting level \\
726read_list(t(X),ref(L))          & unify list subterm after simple subterm \\
727read_next_list(x(X),ref(L))     & unify list subterm after compound subterm \\
728read_last_list(ref(L))          & unify list subterm which is last in term \\
729%\hline
730%read_meta(T,ref(L))             & unify first attr variable at a nesting level \\
731%read_next_meta(t(X),T,ref(L))   & unify attr variable after simple subterm \\
732%read_meta(t(X),T,ref(L))        & unify attr variable after compound subterm \\
733%read_last_meta(T,ref(L))        & unify attr variable which is last in term \\
734\hline
735mode(t(X))                      & continue at higher nesting level \\
736\hline
737\end{tabular}
738
739And the write mode instructions are:
740
741%\begin{tabular}{|l|l|}
742\begin{tabular}{|p{0.35\textwidth}|p{.6\textwidth}|}
743\hline
744write_structure(F)              & write reference to new structure frame, and continue there \\
745write_list                      & write reference to new list cell, and continue there \\
746write_meta(T)                   & write reference to attr variable, and continue there \\
747\hline
748first                           & prefix for write first subterm at a nesting level \\
749next(t(X))                      & prefix for write subterm after compound subterm \\
750next(t(X),ref(L))               & prefix for write subterm after compound subterm \\
751mode(t(X),ref(L))               & continue at higher nesting level, maybe read mode \\
752\hline
753\end{tabular}
754
755
756\subsubsection{Head Matching}
757These are used (together with the in_get family and the read
758instructions) to compile matching clauses, i.e.\ one-way unification
759that do not instantiate anything in the caller arguments.
760\index{matching instruction}
761
762%\begin{tabular}{|l|l|}
763\begin{tabular}{|p{0.35\textwidth}|p{.6\textwidth}|}
764\hline
765get_matched_value(a(A1),a(A2))  & match two arguments \\
766get_matched_value(a(A),y(Y))    & match argument and environment slot \\
767get_matched_value(a(A),t(X))    & match argument and temporary \\
768read_test_var                   & fail if location S holds a variable \\
769\hline
770\end{tabular}
771
772Matching clauses are the only way to match and access the attributes of
773attributed variables. Special instructions are used to implement this:
774
775%\begin{tabular}{|l|l|}
776\begin{tabular}{|p{0.35\textwidth}|p{.6\textwidth}|}
777\hline
778in_get_meta(a(A),ref(L))        & check for attr variable in argument, set S \\
779%read_next_meta(t(X),T,ref(L))   &                         \\
780%read_meta(t(X),T,ref(L))        &                         \\
781%%read_last_meta(T,ref(L))        &                         \\
782%read_matched_value(a(A))        &                         \\
783%read_matched_value(y(Y))        &                         \\
784%read_matched_value(t(X))        &                         \\
785match_meta                      & check for attr variable at nesting level \\
786match_next_meta(t(X))           & check for attr variable after simple subterm \\
787match_meta(t(X))                & check for attr variable after compound subterm \\
788match_last_meta                 & check for attr variable which is last in term \\
789%read_meta(T,ref(L))             &                 \\
790read_attribute(At)              & expect attribute structure at S, set S to requested attribute \\
791\hline
792\end{tabular}
793
794
795\subsubsection{Regular subgoal argument construction}
796The arguments for regular predicate calls (calling convention requires
797arguments in arguments registers) are loaded using the Put family of
798instructions:
799\index{put instruction}
800
801%\begin{tabular}{|l|p{10cm}|}
802\begin{tabular}{|p{0.35\textwidth}|p{.6\textwidth}|}
803\hline
804put_variable(a(A),y(Y))         & move y(Y) to a(A)               \\
805put_variable(a(A))              & set a(A) to new free variable on global  \\
806put_unsafe_value(a(A),t(X))     & move t(X) to a(A), globalise if needed                          \\
807put_unsafe_value(a(A),y(Y))     & move y(Y) to a(A), globalise if needed                          \\
808put_constant(a(A),C)            & move constant to a(A)           \\
809put_nil(a(A))                   & move nil constant to a(A)              \\
810put_integer(a(A),C)             & move small integer constant to a(A)              \\
811put_float(a(A),C)               & move float constant to a(A)              \\
812put_atom(a(A),C)                & move atom constant to a(A)              \\
813put_string(a(A),C)              & move string constant to a(A)              \\
814put_list(a(A))                  & push list skeleton, pointed to by a(A) and S          \\
815put_structure(a(A),F)           & push structure skeleton with functor F,
816                                let a(A) point to it, let S point to first argument\\
817%\hline
818%\multicolumn{2}{|c|}{the next 2 are strange...}\\
819\hline
820put_reference(a(A),O,T) & push O bytes onto global, init first pword
821            with self reference with tag T, refer to it from a(A) and S\\
822put_reference(a(A),y(Y),O,T) & push O bytes onto global, init first
823            pword with self reference with tag T, refer to it from
824            a(A),y(Y) and leave S pointing behind it\\
825\hline
826\end{tabular}
827
828Arguments of structures constructed with Put-instructions are created
829with Push instructions. Many of these are alias of the corresponding
830Write instructions, they construct data at the location pointed to by the
831S register.
832\index{push instruction}
833
834%\begin{tabular}{|l|l|}
835\begin{tabular}{|p{0.35\textwidth}|p{.6\textwidth}|}
836\hline
837push_void                       & same as write_void \\
838push_variable(a(A))             & same as write_variable \\
839push_variable(y(Y))             & same as write_variable \\
840push_init_variable(y(Y))        & create variable at S++, put reference in environment (trailed) \\
841push_variable                   & same as write_variable \\
842push_self_reference(I)          & create named variable at S++ \\
843push_void_reference(O)          & push new nonstandard variable frame, write reference to S++ \\
844push_reference(O)               & push new nonstandard variable frame, write reference to S++ and new temporary \\
845push_reference(a(A),O)          & push new nonstandard variable frame, write reference to S++ and argument \\
846push_reference(y(Y),O)          & push new nonstandard variable frame, write reference to S++ and environment slot \\
847push_init_reference(y(Y),O)     & push new nonstandard variable frame, write reference to S++ and environment slot (trailed) \\
848push_value(a(A))                & same as write_value \\
849push_value(y(Y))                & same as write_value \\
850push_value(t(X))                & same as write_value \\
851push_value(G)                   & write reference to S+G \\
852push_local_value(a(A))          & like write_local_value, but no occur check test \\
853push_local_value(y(Y))          & like write_local_value, but no occur check test \\
854push_local_value(t(X))          & like write_local_value, but no occur check test \\
855push_constant                   & same as write_constant \\
856push_nil                        & same as write_nil \\
857push_integer(C)                 & same as write_integer \\
858push_float(C)                   & same as write_float \\
859push_string(C)                  & same as write_string \\
860push_list                       & create new list frame, write pointer to S++ \\
861push_structure(I)               & create new structure frame, write pointer to S++ \\
862\hline
863\end{tabular}
864
865
866\subsubsection{Simple subgoal argument construction}
867The Puts family of instructions prepares arguments for calls to predicates
868using the external calling conventions, i.e.\ the arguments are dereferenced
869and passed over the local stack.
870Arguments of constructed structures use the same push instructions as above.
871\index{puts instruction}
872
873%\begin{tabular}{|l|l|}
874\begin{tabular}{|p{0.35\textwidth}|p{.6\textwidth}|}
875\hline
876puts_variable           & push free variable on local stack \\
877puts_variable(y(Y))     & init environment slot and push reference onto local stack \\
878puts_reference(O,T)     & create new nonstandard variable with tag T, push reference onto local stack, set S to it \\
879puts_reference(y(Y),O,T)& create new nonstandard variable with tag T, push reference onto local stack and environment slot, set S to it \\
880puts_value(a(A))        & push dereferenced content of argument onto local stack \\
881puts_value(y(Y))        & push dereferenced content of environment slot onto local stack \\
882puts_value(t(X))        & push dereferenced content of temporary onto local stack \\
883puts_value(G)           & push reference to S+G onto local stack \\
884puts_constant           & push constant onto local stack \\
885puts_nil                & push nil constant onto local stack \\
886puts_integer(C)         & push small integer constant onto local stack \\
887puts_float(C)           & push float constant onto local stack \\
888puts_atom(C)            & push atom constant onto local stack \\
889puts_string(C)          & push string constant onto local stack \\
890puts_list               & create new list frame, push pointer onto local stack, set S \\
891puts_structure(D)       & create new list frame, push pointer onto local stack, set S \\
892puts_proc(P)            & push a tagged procedure identifier \\
893\hline
894\end{tabular}
895
896
897
898\subsubsection{Choicepoints}
899The basic set of choicepoint instructions is for clause choicepoints.
900The variants are for the different cases of the current clause, the
901alternative, or none of them following inline.
902Some more detail is in section \ref{secnondet}.
903\index{try instruction}
904
905%\begin{tabular}{|l|l|}
906\begin{tabular}{|p{0.35\textwidth}|p{.6\textwidth}|}
907\hline
908try_me_else(D,I,ref(L))         & create choicepoint, first alternative follows inline, next at L \\
909try(D,I,ref(L))                 & create choicepoint, first alternative at L, next follows inline \\
910try(D,I,ref(La),ref(L))         & create choicepoint, first alternative at La, next at L \\
911retry_me_else(D,ref(L))         & restore choicepoint, this alternative follows inline, next at L \\
912retry(D,ref(L))                 & restore choicepoint, this alternative at L, next follows inline \\
913retry(D,ref(La),ref(L))         & restore choicepoint, this alternative at La, next at L \\
914trust_me(D)                     & restore and pop choicepoint, last alternative follows inline \\
915trust(D,ref(L))                 & restore and pop choicepoint, last alternative at L \\
916\hline
917failure                 & goto failure continuation \\
918refail                  & pop one choicepoint and fail again \\
919\hline
920\end{tabular}
921
922Choicepoints for inlined disjunctions have an environment size parameter
923instead of predicate arity.
924
925\begin{tabular}{|p{0.35\textwidth}|p{.6\textwidth}|}
926\hline
927try_me_inline(D,ref(L),N)       & like try_me_else\\
928retry_me_inline(D,ref(L),N)     & like retry_me_else\\
929trust_me_inline(D,N)            & like trust_me\\
930\hline
931\end{tabular}
932
933If the condition is simple, the if-then-else construct is compiled with
934small choicepoints, consisting only a the BP and PB field. These are
935manipulated using 3 instructions:
936
937\begin{tabular}{|p{0.35\textwidth}|p{.6\textwidth}|}
938\hline
939set_bp(ref(L))          & save failure continuation (push small choicepoint) \\
940restore_bp              & restore failure continuation (pop small choicepoint) \\
941new_bp(ref(L))          & update failure continuation (modify small choicepoint) \\
942\hline
943\end{tabular}
944
945Dynamic predicates have special choicepoint instructions, to allow for
946runtime modification and garbage collection of dead clauses.
947
948\begin{tabular}{|p{0.35\textwidth}|p{.6\textwidth}|}
949\hline
950try_me_dynamic(Tb,Td,ref(L),I)  & create dynamic predicate choicepoint \\
951retry_me_dynamic(Tb,Td,ref(L),I)& restore from dynamic predicate choicepoint \\
952\hline
953\end{tabular}
954
955
956\subsubsection{Switches}
957Compared to a basic WAM, {\eclipse} employs a list_switch instruction
958(a simpler form of switch_on_type for the common case of list
959processing predicates), and the integer_range_switch which has cases
960for lower and upper bounds. All switch instructions refer to an associated
961value-label table elsewhere in memory, except switch_on_type and list_switch,
962where the small fixed-size table is part of the instruction.
963All switch instructions continue inline when the argument is a variable
964(except for switch_on_type, which has a special label for attributed
965variables).
966\index{switch instruction}
967
968%\begin{tabular}{|l|l|}
969\begin{tabular}{|p{0.5\textwidth}|p{.45\textwidth}|}
970\hline
971switch_on_type(a(A),Labels...)           & branch according to tag \\
972list_switch(a(A),ref(Ll),ref(Ln),ref(Ld))& branch according to tag \\
973integer_switch(a(A),Table,ref(Ld))       & branch according to integer value \\
974integer_range_switch(a(A),Table,ref(Le),ref(Ld)) & branch according to integer value \\
975atom_switch(a(A),Table,ref(Ld))          & branch according to atom value \\
976functor_switch(a(A),Table,ref(Ld))       & branch according to functor value \\
977\hline
978\end{tabular}
979
980\subsubsection{Call/Return}
981Instructions for predicate call and return. These exist in several
982variants and combinations. See also section \ref{seccallret}.
983\index{call instruction}
984\index{ret instruction}
985\index{jmp instruction}
986
987%\begin{tabular}{|l|p{10cm}|}
988\begin{tabular}{|p{0.35\textwidth}|p{.6\textwidth}|}
989\hline
990call(ref(L),N)          & predicate call via label \\
991call(P,N)               & predicate call via procedure desc \\
992callf(ref(L),N)         & predicate call via label (first subgoal), sets DET flag \\
993callf(P,N)              & predicate call via procedure id (first subgoal), sets DET flag \\
994jmp(ref(L))             & predicate tail call via label \\
995jmp(P)                  & predicate tail call via procedure id \\
996jmpd(ref(L))            & predicate tail call (assume DET still set) \\
997jmpd(P)                 & predicate tail call via procedure id (assume DET still set) \\
998jmpd(I,ref(L))          & space + jmpd \\
999ret                     & return (when no environment) \\
1000retd                    & return (when no environment, no choicepoint) \\
1001retn                    & return (when no environment, with choicepoint) \\
1002\hline
1003\end{tabular}
1004
1005Calls via label are currently only used for recursive calls, in order to
1006make it possible to recompile individual predicates without having to
1007re-link the corresponding calls.
1008
1009A number of common instruction combinations are supported as well:
1010\index{chain instruction}
1011\index{exit instruction}
1012
1013\begin{tabular}{|p{0.35\textwidth}|p{.6\textwidth}|}
1014\hline
1015chain(ref(L))           & deallocate + jmp \\
1016chain(P)                & deallocate + jmp \\
1017chainc(ref(L))          & cut + deallocate + jmp \\
1018chainc(P)               & cut + deallocate + jmp \\
1019chaind(ref(L))          & deallocate + jmpd \\
1020chaind(P)               & deallocate + jmpd \\
1021exit                    & deallocate + ret \\
1022exitd                   & deallocate + retd \\
1023exitc                   & cut + deallocate + ret \\
1024\hline
1025\end{tabular}
1026
1027
1028
1029\subsubsection{Other Control Transfer}
1030In addition, there are simple inter-procedural control transfer instructions.
1031They are used to skip the read-mode sequence in nested unification code, or
1032to skip alternatives of disjunctions.
1033\index{branch instruction}
1034
1035\begin{tabular}{|p{0.35\textwidth}|p{.6\textwidth}|}
1036\hline
1037branch(ref(L))          & intra-procedural control transfer \\
1038branchs(I,L)            & branch L + space I \\
1039\hline
1040\end{tabular}
1041
1042
1043\subsubsection{Environment and Local Stack Temporaries}
1044Instructions for allocating, deallocating and initialising environment frames
1045on the local stack. Note that there are compound instructions that include
1046allocation or deallocation functionality. Also, temporaries are often
1047pushed onto the local stack as a side effect of other instructions, rather
1048than by calling space(I).
1049\index{allocate instruction}
1050\index{deallocate instruction}
1051\index{initialize instruction}
1052\index{space instruction}
1053
1054\begin{tabular}{|p{0.35\textwidth}|p{.6\textwidth}|}
1055\hline
1056allocate(N)             & allocate an environment \\
1057deallocate              & deallocate topmost environment \\
1058initialize(y(VList))    & initialise several environment slots with free variables \\
1059initialize_named(y(NVList))     & initialise several environment slots with named variables \\
1060space(I)                & adjust local stack pointer \\
1061\hline
1062\end{tabular}
1063
1064\subsubsection{Cut}
1065The cut instructions save pointers to choice points, or pop the choice point
1066stack up to a previously stored position. Note that {\eclipse} does not
1067clean up the trail stack on this occasion (although removing choice points
1068can render trail entries redundant), but leaves this to the garbage collector.
1069Note that there are compound instructions (chainc, exitc) which contain
1070cut functionality.
1071\index{cut instruction}
1072\index{savecut instruction}
1073
1074%\begin{tabular}{|l|l|}
1075\begin{tabular}{|p{0.35\textwidth}|p{.6\textwidth}|}
1076\hline
1077savecut         & save cut point in y(1) \\
1078savecut(a(A))   & save cut point in a(A) \\
1079savecut(y(Y))   & save cut point in y(Y) \\
1080neckcut         & pop topmost choicepoint \\
1081cut(N)          & cut to point in y(1), trim environment to N slots \\
1082cut(y(Y),N)     & cut to point in y(Y), trim environment to N slots \\
1083cut(a(A))       & cut to point in a(A) \\
1084softcut(y(Y))   & disable (deep) choicepoint referred to by y(Y) \\
1085cut_single      & cut to point in y(1) iff there is exactly one choicepoint to cut \\
1086\hline
1087\end{tabular}
1088
1089
1090\subsubsection{Checkpoints}
1091The purpose of these instructions is to insert additional points for global
1092stack overflow checks, or event handling (e.g.\ waking).
1093\index{res instruction}
1094\index{gc_test instruction}
1095
1096%\begin{tabular}{|l|p{10cm}|}
1097\begin{tabular}{|p{0.35\textwidth}|p{.6\textwidth}|}
1098\hline
1099res(Na,Ne)      & handle events if any \\
1100ress(Nt,Na,Ne)  & space Nt + res Na,Ne \\
1101gc_test(M)      & make sure M pwords can be pushed onto global stack
1102                 (expand if necessary, but don't garbage collect)\\
1103\hline
1104\end{tabular}
1105
1106\subsubsection{External Predicate invocation}
1107External predicates\index{external predicates}  are predicate implemented in the implementation
1108language, or via the embedding interface.  Their procedure descriptor
1109holds their function address, and they are invoked from the abstract
1110machine using dedicated external-instructions.
1111Arguments are passed in argument registers, as for regular Prolog
1112predicates.
1113\index{external instruction}
1114
1115A number of built-ins are implemented within the emulator and
1116invoked via the escape instruction, passing arguments via the
1117local stack\footnote{it is intended to drop this calling convention
1118in release 6}.
1119\index{escape instruction}
1120
1121%\begin{tabular}{|l|l|}
1122\begin{tabular}{|p{0.35\textwidth}|p{.6\textwidth}|}
1123\hline
1124external(P,Addr)        & invoke a C function at Addr \\
1125external0(P,Addr)        & special case arity 0 \\
1126external1(P,Addr)        & special case arity 1 \\
1127external2(P,Addr)        & special case arity 2 \\
1128external3(P,Addr)        & special case arity 3 \\
1129escape(P)               & execute one of the built-ins
1130                        that are implemented inside the emulator function\\
1131\hline
1132\end{tabular}
1133
1134\subsubsection{Metacalls}
1135See also section \ref{secmetacall}). These instructions are generated by
1136the compiler or used in handcoded sequences to support metacalling
1137(the invocation of non-compiled goals represented as runtime data structures).
1138\index{metacall}
1139\index{metacall instruction}
1140
1141%\begin{tabular}{|l|l|}
1142\begin{tabular}{|p{0.35\textwidth}|p{.6\textwidth}|}
1143\hline
1144metacall(N)     & for the call/1 and @/2 built-in \\
1145meta_jmp        & for the call/1 and @/2 built-in \\
1146explicit_jmp    & for the :/2 built-in \\
1147\hline
1148\end{tabular}
1149
1150\subsubsection{Debugging}
1151Debug instructions are inserted by the compiler when compiling code in
1152debug mode.  They call-port generating ones are prefixed to the normal
1153calling instructions.  The exit port generating instruction is part of
1154a code sequence which gets dynamically inserted into the success
1155continuation of a traced predicate.
1156\index{debug instruction}
1157
1158%\begin{tabular}{|l|l|}
1159\begin{tabular}{|p{0.35\textwidth}|p{.6\textwidth}|}
1160\hline
1161debug_call(P,Port)      & generates tracer port for regular call \\
1162debug_esc(P,Port)      & generates tracer port for external call \\
1163debug_exit              & generates tracer EXIT port \\
1164\hline
1165\end{tabular}
1166
1167\subsubsection{Special purpose instructions}
1168These are only used in handcoded code sequences:
1169\index{catch instruction}
1170\index{throw instruction}
1171\index{fastcall instruction}
1172\index{handler_call instruction}
1173\index{undefined instruction}
1174\index{continue_after instruction}
1175\index{suspension_call instruction}
1176\index{wake instruction}
1177\index{nop instruction}
1178\index{exit_emulator instruction}
1179
1180%\begin{tabular}{|l|p{10cm}|}
1181\begin{tabular}{|p{0.35\textwidth}|p{.6\textwidth}|}
1182\hline
1183catch           & for the block/3 (catch/3) built-in predicate \\
1184throw           & for the exit_block/1 (throw/1) built-in predicate \\
1185\hline
1186fastcall(I,N)           & invoke handler for exception I \\
1187handler_call(I,N)       & invoke handler for interrupt I \\
1188undefined(P)            & raise UNDEFINED exception for predicate P \\
1189continue_after_exception& restore state after exception \\
1190\hline
1191continue_after_event            & restore after synchronous event \\
1192continue_after_event_debug      & \\
1193\hline
1194suspension_call(N)      & for call_suspension/1 \\
1195suspension_jmp          & for call_suspension/1 \\
1196\hline
1197wake_init(N)            & for the wake/0 built-in \\
1198wake                    & for the wake/0 built-in \\
1199\hline
1200nop                     & no operation \\
1201\hline
1202ret_nowake              & ret without event check \\
1203retd_nowake             & retd without event check \\
1204exitd_nowake            & exitd without event check \\
1205\hline
1206exit_emulator(I)        & exit emulator with return code I \\
1207\hline
1208\end{tabular}
1209
1210
1211%----------------------------------------------------------------------
1212\section{Procedure Call and Return}
1213\label{seccallret}
1214%----------------------------------------------------------------------
1215
1216Regular predicates are called by
1217\index{argument passing}
1218\begin{enumerate}
1219\item loading their arguments into the
1220first N argument registers A1..An, where N is the arity of the callee.
1221This is usually achieved by a sequence of instructions of the Put family,
1222\index{put instruction}
1223but can also be done e.g.\ by the generic metacall code (see \ref{secmetacall}).
1224\item transferring control by either a {\bf Call} instruction or
1225a {\bf Jmp/Chain} instruction. Call instructions push a return address\index{return address}
1226(CP in the diagrams) onto the global stack and set PP to the first
1227instruction of the called predicate's code.
1228Jmp/Chain instructions only set PP (they are used for tail calls and
1229don't return). Chain instructions in addition deallocate an environment.
1230\end{enumerate}
1231\begin{figure}
1232\epsfbox{localframes.eps}
1233\label{localframes}
1234\caption{{\eclipse} local stack frames}
1235\end{figure}
1236A Call instruction requires that the caller has allocated an
1237environment\index{environment}  (see figure \ref{localframes}).
1238The last word of the Call instruction is an environment
1239size, i.e.\ the number of environment slots that are still needed
1240during the execution of the subgoal (see figure \ref{callinstr}). 
1241\begin{figure}
1242\epsfbox{callinstr.eps}
1243\label{callinstr}
1244\caption{Call instruction, return address and environment size}
1245\end{figure}
1246Environment slots are sorted according to their lifetimes\index{lifetimes}, so that the
1247ones that become useless first have the highest numbers.  This is a
1248\index{trimming} form of {\bf environment trimming}, although not the
1249classical one:  the environments are not physically shortened, and the
1250variables that have their last occurrence in the current subgoal are
1251still considered active.
1252The environment size field in the call instructions is used by the
1253garbage collector only, in order to know which of the environment
1254slots should still be considered active.
1255
1256The abstract machine has a DET\index{DET}  flag, which is always set when a procedure
1257is entered, and cleared when a choicepoint is created. It is used by
1258\begin{itemize}
1259\item 
1260the neckcut\index{neckcut}  instruction to detect whether the procedure has created
1261a choicepoint that need to be cut.
1262\item 
1263the savecut instruction to detect which choicepoint address to save.
1264\item 
1265the ret and tail call instructions to know whether to pop the return
1266address from the local stack or not.
1267\end{itemize}
1268
1269
1270
1271%----------------------------------------------------------------------
1272\section{Nondeterminism}
1273\label{secnondet}
1274%----------------------------------------------------------------------
1275Nondeterminism\index{Nondeterminism}  relies on choicepoints\index{choicepoints}  and trailing\index{trailing}  to reset the machine
1276to an earlier state.  The layout of choicepoints is depicted in figure
1277\ref{figchp}.
1278\subsection{Choicepoints}
1279\begin{figure}
1280\epsfbox{controlframes.eps}
1281\caption{{\eclipse} control stack frames}
1282\label{figchp}
1283\end{figure}
1284A number of variants of the standard choicepoint exist that store more
1285state (for exceptions\index{exceptions}  and invoking a recursive engine\index{engine}), or less (small
1286choicepoints, only BP and PB field, for shallow backtracking\index{shallow backtracking}).
1287
1288\index{try instruction}
1289The choice point creation instructions (try) simply store a subset of the
1290abstract machine registers in the choicepoint frame, and set GB and EB
1291registers, which will lead to future trailing of any modification to data
1292older than the new choicepoint.
1293
1294\index{retry instruction}
1295\index{trust instruction}
1296The retry/trust instructions restore this information and transfer control
1297to the alternative clause or disjunctive branch (the trust instruction
1298also discard the choicepoint). In addition, untrailing is performed, i.e.\
1299all changes recorded since choicepoint creation (or restoration) are
1300undone.  A number of abstract machine registers are reinitialised
1301(EB\index{EB}, GB\index{GB}, GCTG\index{GCTG}, TG_SL\index{TG_SL}, MU\index{MU}, DE\index{DE}). 
1302Furthermore, these instructions include
1303unconditional hooks for the debugger\index{debugger}, because it is possible that
1304execution fails out of a traced portion of the execution, and we want
1305to trace this event even if the failure continuation is within code
1306that has been compiled without tracing support.
1307
1308
1309\subsection{Timestamps}
1310\label{sectimestamps}
1311For some purposes, e.g.\ the avoidance of unnecessary trailing\index{trailing!unnecessary},
1312we need unique identifiers for choicepoints. Choicepoint addresses
1313cannot serve this purpose, since choicepoints may be cut or popped,
1314and new ones re-created at the same address.
1315We therefore would like to use global stack addresses as timestamps\index{timestamps},
1316namely the value the stack pointer had when the choicepoint was created.
1317To make this safe, we must guarantee that there is always something
1318pushed on the global stack between two choicepoints, otherwise timestamps
1319could become identical when they really belong to different choicepoints.
1320
1321Our solution is to push a "witness" word with every choicepoint. 
1322Their addresses are used as the time stamps.
1323The GB\index{GB}  register always points to the current witness\index{witness}.
1324A stamp looks like a [] (a ref to a TNIL\index{TNIL}  of the proper age).
1325
1326An advantage compared with other timestamping schemes is that the
1327witness (ie. the timestamp value) can be garbage collected once
1328the choicepoint and all timestamps have disappeared.
1329Compared to the scheme used in setarg, we hopefully use less memory
1330since an extra word is pushed per choicepoint rather than per trailed
1331modification.
1332Unfortunately, the timestamps don't collapse once the choicepoint between
1333them is cut.
1334
1335Locations that need timestamped modifications need to have space for
1336a pointer.
1337
1338
1339%----------------------------------------------------------------------
1340\section{Trailing}
1341%----------------------------------------------------------------------
1342\subsection{Binding and Value Trail}
1343\index{trailing}
1344The trail stack records modifications to memory locations which must be
1345undone on backtracking. There are two forms of trail for variable bindings
1346(with and without tag), and a general value trail\index{value trail}, see figure
1347\ref{figtrailframes}.
1348\begin{figure}
1349\epsfbox{trailframes.eps}
1350\caption{{\eclipse} trail stack frames}
1351\label{figtrailframes}
1352\end{figure}
1353The tagged binding trail is needed to trail bindings to non-standard
1354variables, e.g.\ attributed variables\index{attributed variables}.
1355The value trail is used in particular for setarg/3\index{setarg/3}.
1356
1357
1358\subsection{Undo Trail}
1359A more general undo mechanism is implemented by the undo trail\index{undo trail}  frames.
1360This is used e.g.\ in interfacing\index{interfacing}  code to {\eclipse} that is not backtracking
1361aware. We support a simple form and a timestamped form. Timestamping
1362is a mechanism to avoid multiple trails of modifications to the same
1363object, when there was no choicepoint in between modifications.
1364\index{timestamps}
1365
1366Simple and stamped undo frame
1367(see \ref{figundotrail})
1368differ only in that the stamped frame has two extra fields, the stamp
1369address and the old stamp value.
1370Both frames have a pointer to an "item" which is the related data
1371structure that determines the lifetime of the frame.
1372\begin{figure}
1373\hfill
1374\begin{minipage}[t]{.45\textwidth}
1375\begin{tiny}
1376\begin{verbatim}
1377+--------+--------+--------+--------+    \
1378|               data                |     |
1379.                                   .     |
1380.                                   .      > size + 1 32 bit words
1381.                                   .     |
1382|               data                |     |
1383+--------+--------+--------+--------+    /
1384|         & untrail_function        |
1385+--------+--------+--------+--------+
1386|           item address            |
1387+--------+--------+--------+--------+
1388|            frame size    |0000tt11|
1389+--------+--------+--------+--------+   <-- TT
1390\end{verbatim}
1391\end{tiny}
1392\end{minipage}
1393\hfill
1394\begin{minipage}[t]{.45\textwidth}
1395\begin{tiny}
1396\begin{verbatim}
1397+--------+--------+--------+--------+    \
1398|               data                |     |
1399.                                   .     |
1400.                                   .      > size + 1 32 bit words
1401.                                   .     |
1402|               data                |     |
1403+--------+--------+--------+--------+    /
1404|          old stamp value          |
1405+--------+--------+--------+--------+
1406|           stamp address           |
1407+--------+--------+--------+--------+
1408|         & untrail_function        |
1409+--------+--------+--------+--------+
1410|           item address            |
1411+--------+--------+--------+--------+
1412|            frame size    |0001tt11|
1413+--------+--------+--------+--------+   <-- TT
1414\end{verbatim}
1415\end{tiny}
1416\end{minipage}
1417\hfill
1418\caption{Simple and timestamped undo trail frame}
1419\label{figundotrail}
1420\end{figure}
1421The tt field indicates the type of trailed data, as in the value trail.
1422The frames are created by a single function:
1423\begin{verbatim}
1424ec_trail_undo(&function, &item, &stamp,
1425                        &data, data_size_in_words, trail_flags)
1426\end{verbatim}
1427The arguments are
1428\begin{description}
1429\item[function] 
1430    address of the undo function
1431\item[item] 
1432    address of the data structure to which the undo applies.
1433                This can be a global stack address (in which case it must
1434                point to a properly tagged pword) or an arbitrary heap
1435                address (in which case the content does not matter), or
1436                it can be NULL. If item is a global stack item, and this item
1437                is about to be garbage collected, the undo function will be
1438                called early. If item is NULL or outside the global stack,
1439                the undo function will only be called on failure.
1440
1441\item[stamp] 
1442    address of a timestamp (see \ref{sectimestamps}).
1443    This should be NULL if you don't want
1444                to use timestamping. Using timestamping implies that multiple
1445                trails within the same choicepoint segment are redundant, and
1446                the system will suppress all but the first. The location of
1447                the timestamp is immaterial. It can be part of the item or not.
1448                It will be kept alive by the existence of the trail frame.
1449\item[data,size] 
1450    address and size (in words) of data to be passed to the
1451                undo function. This data will be copied into the trail frame.
1452\item[trail_flags]      the type of the data (TRAILED_PWORD or TRAILED_WORD)
1453\end{description}
1454The undo function is called as follows:
1455\begin{verbatim}
1456undo(pword *item, word *data, int data_size_in_words, int undo_context)
1457\end{verbatim}
1458Untrailing is done in
1459    undo_context == UNDO_FAIL\index{UNDO_FAIL}
1460        on failure (unless redundant according to stamp), or in 
1461    undo_context == UNDO_GC\index{UNDO_GC}
1462        on gc, when the untrail can be done early (when the item is
1463        inaccessible in the post-trailed state).
1464
1465If the data consists of pwords, early untrailing during garbage
1466collection is tricky:  the data may be marked (and thus unusable)
1467at the time the untrail function is called. If the undo function
1468needs to look at the data even for redundant untrails, we must make
1469sure at trail time that the data that is referenced by the trail
1470frame is not referenced by anybody else.
1471
1472CAUTION1: The data fields are blindly copied and when the untrail
1473function is executed, the data may not be properly aligned if they
1474require >4 byte boundary alignment\index{alignment}  (e.g. doubles). Accessing these
1475misaligned field directly can cause a segmentation violation on some
1476architectures. In these cases, the data should be copied (using memcpy()) 
1477to a properly aligned data structure first.
1478
1479CAUTION2:  The GC does NOT mark the data pointed to by the item
1480address field.  This item is only used to determine the lifetime
1481of the trail frame.  In particular, this undo-trail CANNOT be used
1482to implement a general value-trail because it does not assume
1483(during GC) that the item has been modified at trailing time, so
1484the current value would not be marked and updated properly during
1485GC.  It is in principle a pure side-effect trail.  However, simple
1486modifications in the item, like resetting counters or bits, should
1487be ok.
1488
1489Another difference between a reset-trail and side-effect trail is that
1490the reset-trail is redundant when the item is about to disappear anyway
1491during failure. The side effect still needs to be done in that case
1492(e.g. cleanup/deallocation for external handles\index{handles}).
1493
1494
1495%----------------------------------------------------------------------
1496\section{Destructive Assignment}
1497
1498\index{setarg/3}
1499The builtin setarg/3 and several other destructive assignment operations
1500use the single C function \verb.ec_assign(pword *arg, value v, tag t).
1501\index{ec_assign}
1502which backtrackably overwrites the location arg with the new value v/t.
1503The code uses the macros \verb.NewLocation(pword*).
1504which means the address is younger than the most recent choicepoint\index{choicepoint},
1505and \verb.NewValue(value,tag).
1506which means the pword is younger than the most recent choicepoint
1507(when it is a constant, it is assumed to be old).
1508
1509Assume the location to be assigned to is Arg, its old value Old and
1510its new value New.  Then there are the following different cases.
1511
1512\begin{enumerate}
1513\item NewLocation(Arg) - 
1514    Simply overwrite without trailing, regardless of old or new value,
1515    because the everything will disappear an backtracking.
1516\item !NewLocation(Arg), NewValue(New) and NewValue(Old)  -
1517    Simply overwrite without trailing,
1518    because the old value is unaccessible after backtracking anyway.
1519\item !NewLocation(Arg, NewValue(New) and !NewValue(Old) -
1520    overwrite with trailing.
1521\item !NewLocation(Arg) and !NewValue(New) -
1522Copy new value to top of stack, and assign a reference to it,
1523   instead of the new value itself (like 2).
1524    This is done so that the next time an assignment is attempted, the
1525    (then old) value's address indicates how old the assignment is,
1526    and trailing can hopefully be avoided.  This trick avoids the need
1527    for an explicit timestamp.
1528\end{enumerate}
1529The actual ec_assign() function also checks for the New value being
1530a variable on the local stack. Since references from global to local
1531are not allowed, the variable gets first globalised\index{globalised}  and the result
1532is assigned instead (leading then to case 1, 2 or 3).
1533
1534
1535
1536%----------------------------------------------------------------------
1537\section{Attributed Variables}
1538
1539\index{attributed variables}
1540Attributed Variables are described in \cite{meier92} and
1541\cite{metaterms95}, where they are referred to as
1542metaterms\index{metaterms} - some of the {\eclipse} documentation and
1543implementation uses these terms interchangeably.  One can think of
1544them as a variable with (one or more) attached attributes.  In
1545{\eclipse} syntax we can write e.g. X\{Attribute\}.  Attributed
1546variables behave in some respects like variables, but in most respects
1547their behaviour is user-definable (e.g.  what happens with them on
1548unification\index{unification}, copy_term\index{copy_term} etc). 
1549Also, they can be decomposed into their components (variable and
1550attributes) via matching clauses, emphasising their meta-level aspect.
1551
1552The idea that something like "attributed variables" is needed for the
1553implementation of coroutining\index{coroutining}  Prologs and CLP\index{CLP}  languages is rather obvious
1554and has been used in implementations long before anybody invented a
1555special name for it. However, they were usually not accessible as such
1556for the Prolog/CLP programmer.
1557We can credit Ulrich Neumerkel and Christian Holzbaur for suggesting
1558that adding the metaterm primitive to a Prolog machine is in principle
1559all that's needed to build constraint solvers on top.
1560
1561In {\eclipse} we have gone a step further and made an effort to fully
1562integrate attributed variables into our language as first class citizens.
1563I.e.\ they have their own syntax, they are integrated in unification
1564and indexing of the abstract machine, they are handled appropriately
1565by almost all builtin predicates, etc. Another important point is that
1566{\eclipse} attributed variables can have multiple independent
1567attributes, which makes it possible to use several constraint solvers
1568at the same time, for example.  The variety of {\eclipse}'s constraint\index{constraint}
1569solver libraries demonstrates this.
1570
1571
1572
1573%----------------------------------------------------------------------
1574\section{Metacalls}
1575\label{secmetacall}
1576%----------------------------------------------------------------------
1577
1578\index{metacall}
1579Basically, metacalling is very simple:  Given a structure, load its
1580arguments into the argument\index{argument}  registers and jump to the predicate code
1581specified by the structure's functor.  The actual implementation is
1582more complex because of handling the cut, modules, and different call
1583protocols for externals and prolog predicates.
1584
1585The central piece is the Metacall/Metajmp instruction.
1586It expects the argument registers to be loaded as follows:
1587\begin{description}
1588\item[A1] the goal structure to be metacalled
1589\item[A2] the caller module
1590\item[A3] the lookup module
1591\item[A4] the cut pointer
1592\end{description}
1593\index{"@/3}
1594\index{"@/2}
1595Apart from the cut\index{cut}  pointer, these are the arguments of @/3, which is
1596the tool body (see User Manual chapter on the module system) of @/2.
1597The abstract code sequence of @/3 is simply the following:
1598\begin{verbatim}
1599@/3:
1600        SavecutAM       A4
1601        Meta_jmp
1602\end{verbatim}
1603and the code of call/2 (the tool body of call/1) is
1604\begin{verbatim}
1605call/2:
1606        Move            A2 A3
1607        SavecutAM       A4
1608        Meta_jmp
1609\end{verbatim}
1610In order to handle cuts inside the metacalled goal, the value of the B
1611register at the beginning of the metacall is loaded into an argument
1612and passed to the instruction.
1613
1614The Metacall/Metajmp instruction first does the necessary dereferencing
1615and type checks on arguments 1 and 3.
1616Then the visible predicate is found by calling
1617the procedure table lookup function visible_procedure\index{visible_procedure}().
1618
1619The next point is to check for goals that must be handled in a special
1620way because they are defined as being transparent to cuts.
1621These are conjuction, disjunction, implication, if-then-else\index{if-then-else}  and cut.
1622They are all translated into a predicate that takes an additional
1623argument which is the cut pointer. This cut pointer is the value of the
1624B stack pointer at the beginning of the metacall.
1625\begin{verbatim}
1626Goal in Module                  Translated goal
1627--------------                  ---------------
1628Goal1 , Goal2                   ','(Goal1, Goal2, Module, Cut)
1629Goal1 ; Goal2                   ';'(Goal1, Goal2, Module, Cut)
1630Goal1 -> Goal2                  '->'(Goal1, Goal2, Module, Cut)
1631Goal1 -> Goal2 ; Goal3          ';'(Goal1, Goal2, Module, Cut, Goal3)
1632!                               cut_to(Cut)
1633\end{verbatim}
1634The transformed predicates could be defined as follows (although
1635in reality they are implemented by abstract code sequences in code.c):
1636\begin{verbatim}
1637    ','(Goal1, Goal2, Module, Cut) :-
1638            call(Goal1, Module, Module, Cut),
1639            call(Goal2, Module, Module, Cut).
1640
1641    '->'(Goal1, Goal2, Module, Cut) :-
1642            call(Goal1, Module, Module, []).
1643            !,
1644            call(Goal2, Module, Module, Cut).
1645
1646    ;(Goal1, Goal2, Module, Cut) :-
1647            call(Goal1, Module, Module, Cut).
1648    ;(Goal1, Goal2, Module, Cut) :-
1649            call(Goal2, Module, Module, Cut).
1650
1651    ;(Goal1, Goal2, Module, Cut, Goal3) :-
1652            call(Goal1, Module, Module, []).
1653            !,
1654            call(Goal2, Module, Module, Cut).
1655    ;(Goal1, Goal2, Module, Cut, Goal3) :-
1656            call(Goal3, Module, Module, Cut).
1657\end{verbatim}
1658We have written the Metacall/Metajmp instruction as call/4.
1659Note also that the Cut pointer is not passed into the conditions
1660of implication and if-then-else: these are not transparent to the
1661cut, as this could interfere with the subsequent cut of the condition
1662itself.
1663
1664After this goal transformation, the goal arguments are moved to the
1665appropriate locations, i.e. the argument registers (when the goal is a
1666regular Prolog procedure) or dereferenced and pushed on the local
1667stack (when the goal is an external).  When the goal is a tool
1668interface, the module argument is also added.  The last step is to
1669actually jump to the code of the prolog goal or to call the external,
1670respectively.
1671
1672
1673
1674%----------------------------------------------------------------------
1675\section{Structure unification}
1676\label{secstructunify}
1677%----------------------------------------------------------------------
1678\index{structure unification}
1679\index{compound term compilation}
1680Structure unification is compiled differently from the WAM, and is
1681quite involved. The information in this section is intended as
1682supplement to Micha's paper on the issue \cite{compnd}.
1683
1684\subsection{Head unification}
1685
1686\index{read sequence}
1687\index{write sequence}
1688\index{get instruction}
1689The basic scheme is to have separate read- and write-sequences,
1690for deconstructing/unifying an existing structure, and for constructing
1691a new structure. The get_structure type instructions dispatch according
1692to the instantiation of their argument:
1693\begin{verbatim}
1694        get_structure a(A) F ref(Lr)
1695        write_...
1696        ...
1697        write_...
1698        branch Le
1699Lr:
1700        read_...
1701        ...
1702        read_...
1703Le:
1704\end{verbatim}
1705For unification of nested structures, it may be necessary to jump back
1706and forth between read and write sequences, depending on whether substructures
1707are present in the runtime term or not.
1708
1709   The basic idea is to unify nested compound terms top-down and
1710   left-to-right. Unlike the WAM scheme, this method does not require
1711   temporaries to hold structure arguments, but needs a stack instead.
1712   However, since the depth of the nested term in the head is known
1713   at compile time, this stack can be built from temporaries (every
1714   nesting level is assigned one temporary\index{temporary}, except the bottom level).
1715   These temporaries contain a read/write mode flag and a copy of the
1716   S register, indicating how and where to continue after having
1717   finished the unification of a compound subterm.
1718   This method is better than the WAM scheme especially for wide,
1719   flat structures and for right-balanced structures like lists.
1720
1721   Read and write-mode are in separate code sequences, and there
1722   are conditional jumps back and forth between the sequences.
1723   If a read-instruction discovers a variable in the input, it
1724   creates a structure frame and jumps into the write-sequence to
1725   construct the structure arguments. The 'return address' in form
1726   of a read-flag and the next value of S is saved in a temporary.
1727   At the end of a write sequence for all arguments of a subterm,
1728   the temporary is tested and possibly control is transferred back
1729   to the read mode. This is all further complicated by a 'last-call'
1730   optimisation, ie. dropping the temporary before the last subterm.
1731
1732   Compared to the presentation in Micha's paper, in the actual
1733   implementation instructions are merged and specialised:
1734\begin{verbatim}
1735Write mode:                     Read mode:
1736
1737First                           (part of Read_structure WLabel)
1738    allocate Ti                     allocate Ti
1739    down (save S+1|WRITE)           down (save S+1|READ)
1740                                      possibly goto write mode
1741
1742Next Ti RLabel                  (part of Read_next_struct Ti WLabel)
1743    possibly goto read mode         up (restore S)
1744    up (restore S)                  down (save S+1)
1745    down (save S+1)                 possibly goto write mode
1746                      
1747Mode Ti RLabel                  Mode Ti
1748    up (restore S)                  up (restore S)
1749    possibly goto read mode
1750
1751Next Ti                         (part of Read_structure Ti WLabel)
1752    down (save S+1)                 down (save S+1)
1753                                    possibly goto write mode
1754\end{verbatim}
1755
1756
1757\subsection{Body subgoal arguments}
1758
1759\index{put instruction}
1760    The terms are built breadth-first, top-down, using two pointers.
1761    TG is the allocation pointer and S is the write-pointer, lagging
1762    behind and filling the allocated space.
1763
1764
1765
1766%----------------------------------------------------------------------
1767\section{Exceptions}
1768%----------------------------------------------------------------------
1769
1770\index{exception}
1771\index{block/3}
1772\index{exit_block/1}
1773Exception handling corresponds to the builtins block/3 and exit_block/1.
1774block/3 is a tool and block/4 is its tool body.
1775They are implemented via the following handcoded abstract instruction
1776sequences:
1777\begin{verbatim}
1778block/4:             // block(Goal, Catcher, Recovery, Module)
1779        Catch                           // special instruction
1780        Allocate        1
1781        Savecut
1782        Move            A2 A3           // call(Goal)
1783        Savecut         A4
1784        Metacall        1
1785        Cut_single      0               // clean up catch frame
1786        Exit
1787
1788exit_block/1:   % exit_block(Ball)
1789        Throw                           // special instruction
1790        Move            A2 A3           // call(Recovery)
1791        Savecut         A4
1792        Meta_jmp
1793\end{verbatim}
1794These use special-purpose instructions:
1795\begin{description}
1796\item[Catch] 
1797    \begin{itemize}
1798    \item checks the Catcher argument in A[2] for simple type or variable
1799    \item moves the module argument from A[4] to A[2] (for subsequent call/2)
1800    \item builds a catch frame on the control stack, containing:
1801                sp, tg, tt, e, Catcher, Recovery, Module
1802    \end{itemize}
1803\item[Throw] 
1804    \begin{itemize}
1805    \item check the "Ball" argument in A[1] for simple type or variable
1806    \item pop frames off the control stack until a catch frame is found, whose
1807          Catcher entry would unify with Ball.
1808          If an invocation frame is encountered while popping, we have to exit
1809          an emulator invocation and continue executing the BIThrow in the
1810          previous emulator.
1811    \item If the corresponding catch frame is found:
1812        \begin{itemize}
1813        \item restore sp, tg, e from catch frame, untrail
1814        \item pop the catch frame
1815        \item reset EB, GB from the choicepoint below the catch frame
1816        \item pop the catch frame
1817        \item load A[1] with the Recovery goal, A[2] with the Module
1818          (for subsequent call/2)
1819        \item unify Catcher and Ball
1820        \end{itemize}
1821    \end{itemize}
1822\item[Cut_single] 
1823    Will cut the catch frame if it is on top of the stack, i.e.\ if the
1824    goal has not left any choicepoints itself.
1825\end{description}
1826We guarantee that a catch frame is always found by enclosing
1827the toplevel loop with
1828\begin{verbatim}
1829    block(loop, Tag, notag(Tag))
1830\end{verbatim}
1831This serves as a "catch-all" for exit_block's.
1832
1833The corresponding ISO Prolog primitives catch/3 and throw/1 are similar
1834but allow complex terms to be thrown. {\eclipse} should eventually migrate
1835to support that (but preferably without full heap copying).
1836
1837
1838
1839%----------------------------------------------------------------------
1840\section{Suspension Mechanism}
1841%----------------------------------------------------------------------
1842
1843{\eclipse} can deal with delayed goals, i.e. goals that are part of the
1844resolvent\index{resolvent}, but are not part of the current continuation. They will only
1845be reactivated by certain wakeup events. Once reactivated, they enter
1846a priority-based scheduler, and are executed as soon as there are no
1847higher-priority goals scheduled (see priority mechanism \ref{chappriority}).
1848
1849Delayed goals can be in 3 states, SLEEPING\index{SLEEPING}, SCHEDULED\index{SCHEDULED}  and DEAD\index{DEAD}.
1850The transitions are depicted in figure \ref{figsuspstates}.
1851\begin{figure}
1852\hfill
1853\begin{minipage}[t]{.45\textwidth}
1854\begin{tiny}
1855\begin{verbatim}
1856Non-demon:
1857                schedule
1858       SLEEPING --------> SCHEDULED
1859           |                 |
1860      kill |                 | execute/kill
1861           \                 /
1862            ----> DEAD <-----
1863\end{verbatim}
1864\end{tiny}
1865\end{minipage}
1866\hfill
1867\begin{minipage}[t]{.45\textwidth}
1868\begin{tiny}
1869\begin{verbatim}
1870Demon:          schedule
1871                -------->
1872       SLEEPING           SCHEDULED
1873           |    <--------    |
1874           |     execute     |
1875      kill |                 | kill
1876           \                 /
1877            ----> DEAD <-----
1878\end{verbatim}
1879\end{tiny}
1880\end{minipage}
1881\hfill
1882\caption{States in the life of a suspension}
1883\label{figsuspstates}
1884\end{figure}
1885Every delayed goal is represented by a so-called suspension
1886\index{suspension}
1887\index{delayed goal}
1888which is created by the make_suspension/3,4 builtin.
1889Immediately after creation, the suspension is in the SLEEPING state.
1890Two transitions are possible from this state, towards the SCHEDULED state
1891via the schedule_suspension/1,2 builtin, or towards the DEAD state via
1892the kill_suspension/1 builtin.
1893\index{make_suspension/3}
1894\index{schedule_suspension/2}
1895\index{kill_suspension/1}
1896
1897Once scheduled, the goal will eventually be ready for execution, as
1898soon as all higher-priority goals, and all previous goals in the queue for
1899the same priority are finished executing.  Then, just before execution starts,
1900the state changes to either of DEAD (for standard predicates), or back
1901to SLEEPING (for predicates with the demon-property, see demon/1 declaration).
1902For demons, the only way to reach the DEAD state is to be killed explicitly
1903via kill_suspension/1.
1904
1905
1906\subsection{Suspension Descriptor}
1907
1908A delayed goal is represented by a TSUSP\index{TSUSP}-tagged pointer
1909to a suspension descriptor on the global stack (see figure \ref{figsuspension}).
1910This descriptor is created by the make_suspension/3,4
1911built-in (implemented within the emulator).
1912\begin{figure}
1913\hfill
1914\begin{minipage}[t]{.9\textwidth}
1915\begin{tiny}
1916\begin{verbatim}
1917|-----------------|
1918|                 |
1919|- - - MODULE  - -|
1920|                 |
1921|-----------------|
1922|                 |
1923|- - -  GOAL - - -|
1924|                 |
1925|-----------------|
1926|     PRIO  S TREF| <= these are mutable fields
1927|- - - STATE - - -|
1928|    timestamp    |
1929|-----------------|                                  |-----------------|
1930|      INVOC      |     <= CAUTION: no tag!          |      INVOC      |     <= CAUTION: no tag!
1931|- - - - - - - - -|                                  |- - - - - - - - -|
1932|       PRI       |                                  |       PRI       |
1933|-----------------|       |---------|                |-----------------|       |---------|
1934|0--       XD TDE |       |  TSUSP  |                |0--       1D TDE |       |  TSUSP  |
1935|- - - - - - - - -|       |- - - - -|                |- - - - - - - - -|       |- - - - -|
1936|       LD        |    /-------     |                |      NULL       |    /-------     |
1937|-----------------|<--/   |---------|                |-----------------|<--/   |---------|
1938\end{verbatim}
1939\end{tiny}
1940\end{minipage}
1941\hfill
1942\caption{The suspension descriptor (live and dead)}
1943\label{figsuspension}
1944\end{figure}
1945The fields are:
1946\index{LD}
1947\index{TDE}
1948\begin{description}
1949\item[LD] used to chain all live suspensions together. The chain starts
1950with the LD abstract machine register. This list is used to implement the
1951built-ins suspensions/1, current_suspension/1, delayed_goals/1 and subcall/2.
1952\item[D (demon-flag)] indicates whether the goal is a demon and can be
1953re-suspended.
1954\item[X (dead-flag)] indicates that the goal is dead.
1955\item[TDE] The tag marking the suspension descriptor (for the garbage collector).
1956\item[PRI] pointer to the goal's procedure descriptor, to speed up the
1957waking process.
1958\item[INVOC] debugger invocation number.
1959\item[S (scheduled-flag)] indicates that the goal has been scheduled for
1960execution, but has not yet been executed. While set, the suspension is in the
1961waking list.
1962\item[timestamp] used to optimize trailing of the scheduled-flag.
1963\item[PRIO] goal waking priority.
1964\item[GOAL] the goal as a compound term (or atom).
1965\item[MODULE] context module of the delayed goal.
1966\end{description}
1967When the suspension is dead, then the descriptor may be partially
1968garbage collected, i.e. goal and module may no longer be present and
1969it may be removed from the LD list.
1970
1971
1972\subsection{Suspension Lists}
1973\index{suspension list}
1974Suspensions are usually entered into lists that are an argument of a structure,
1975typically one argument of an attribute structure.
1976The builtins
1977init_suspension_list/2,
1978enter_suspension_list/3,
1979merge_suspension_lists/4
1980and 
1981insert_suspension/4
1982are dealing with this. There are no explicit removal operations for suspensions
1983in these lists. however, dead suspensions are removed opportunistically
1984when a lists is traversed for the purpose of scheduling, and dead
1985suspensions at the head of the list are removed when new suspensions are
1986prefixed.
1987
1988
1989\subsection{Waking scheduler and priority system}
1990\label{chappriority}
1991
1992\index{wake}
1993\index{call_priority/2}
1994{\eclipse} currently supports a system of 12 fixed priorities.
1995Initially, a program runs at priority\index{priority}  12. The running priority can be raised
1996either explicitly by call_priority/2, or it is raised implicitly when
1997a higher priority goal interrupts the execution of a lower-priority one.
1998Delayed goals have a waking-priority attached, which is either derived
1999from the predicate's priority setting, specified explicitly when the
2000suspension is created, or can be modified via set_suspensions_data/3.
2001
2002The scheduler for suspensions consists of:
2003\begin{itemize}
2004\item An array of woken suspension lists, one for each priority.  Each
2005        scheduled goal gets inserted into the list according to its
2006        priority by schedule_suspensions/2.
2007        Once a suspension is scheduled into a list, its
2008        priority cannot be changed any longer.
2009
2010\item The scheduling loop implemented by the builtin wake/0 (Wake instruction),
2011        \index{wake instruction}
2012        which is usually invoked implicitly, e.g. by
2013        attributed variable unification handlers.  This loop scans the
2014        array of woken lists, and executes the corresponding goals one
2015        by one, in order of priority.
2016\end{itemize}
2017The scheduler makes sure each goal executes `at its own priority' by setting
2018the machine's WP\index{WP}  register accordingly. This makes sure that only higher
2019priority goals can wake up inside the just woken one.
2020
2021%----------------------------------------------------------------------
2022\section{Event Handling}
2023\label{seceventhandling}
2024%----------------------------------------------------------------------
2025\index{event}
2026{\eclipse} has a notion of synchronous\index{synchronous event}  events, which can be posted to
2027the abstract machine.  There is a queue for posted events, they can be
2028either atoms (symbolic events), integers (for synchronous signal
2029handling), or event handles\index{handle!event}  (anonymous events).  Their corresponding
2030handlers are then executed as soon as the engine reaches a trigger
2031point.  Such points are those where the abstract machine is in a well
2032known state:
2033\begin{itemize}
2034\item CALL: When a (regular) predicate is about to be called (at the end of
2035a Call, Chain or Jmp instruction): PP points to start of procedure, return
2036address on top of local stack, arguments registers hold arity arguments.
2037\item Return: When a (regular) predicate is about to return:
2038No argument registers are valid, return address just popped from stack.
2039\item Res: At an explicit Res (resume) instruction: return address on top
2040of local stack, arity argument registers valid.
2041\end{itemize}
2042In order to minimise the overhead of the event test in the abstract machine, 
2043the event handling mechanism is triggered in the same way as a stack
2044garbage collection. Stack overflow is triggered by the global stack pointer
2045(TG\index{TG}) growing beyond a limit register (TG_SL\index{TG_SL}).  For event handling, such an
2046overflow is simulated by manipulating the limit register.
2047When the machine detects such an overflow, it first checks for a true stack
2048overflow, if this is not the case, the MU\index{MU}  register is checked for a
2049attributed variable (metaterm) unification\index{unification}  event, and if that is not set,
2050the general event queue is checked.
2051
2052The event handler itself is either looked up in a table (for numeric events),
2053as a property of an atom (for symbolic events), or copied from a heap term
2054(for anonymous events). A corresponding goal is then constructed and called.
2055
2056
2057%----------------------------------------------------------------------
2058\section{Abstract Machine Emulator}
2059%----------------------------------------------------------------------
2060
2061The abstract machine\index{abstract machine}  emulator\index{emulator}  is at the heart of \eclipse's runtime system. 
2062It is written in C with optional use of GCC features to implement
2063threaded code.
2064
2065The emulator is quite a large (but flat) piece of code and consists of the single
2066function ec_emulate().  The decision to have it as a single function
2067is due to technical reasons, especially the need to use register
2068variables for efficiency.  If it were distributed over several
2069functions, the state of the abstract machine would have to be stored
2070in global variables or passed as arguments.
2071
2072The main part of the emulator is an endless loop (in the non-threaded
2073version) that reads one instruction code from the location the program
2074pointer (PP) points to, and executes a switch to go to the piece of
2075code that implements the instruction.
2076\begin{small}
2077\begin{verbatim}
2078while(1)
2079{
2080
2081    switch((pp++)->inst)
2082    {
2083        case MoveAM:
2084            <code for instruction>
2085            Next-Pp;
2086
2087        case MoveAMAN:
2088            <code for instruction>
2089            Next-Pp;
2090
2091        ...
2092
2093        default:
2094            <undefined instruction>
2095    }
2096}
2097\end{verbatim}
2098\end{small}
2099Apart from the loop with the abstract machine instructions, the
2100emulator contains some pseudo-subroutines (entered by goto-
2101statements), e.g. for general unification\index{unification}, error handling etc. 
2102Moreover, a number of builtin predicates are coded inside the emulator. 
2103This is done because they need access to abstract machine registers
2104that would not be available outside the emulator, or just for improved
2105efficiency (e.g.\ basic arithmetic),
2106
2107%Here is a rough map of the emulator file {\bf emu.c}:
2108%\begin{verbatim}
2109% 800 lines      declarations and macro definitions
2110% 100 lines      Initialization
2111% 350 lines      general unify and difference routines
2112% 500 lines      error and event handling code
2113%3500 lines      instructions
2114%1000 lines      built-ins
2115%\end{verbatim}
2116%
2117
2118Closely related code is in the files:
2119\begin{description}
2120\item[code.c]
2121        Hand-coded sequences of abstract machine code, which implement
2122        certain built-in predicates, support event handling, etc.
2123\item[emu_util.c and emu_c_env.c]
2124        Supporting functions to execute low-level operations related
2125        to the abstract machine. Also debugging support.
2126\item[opcode.h] definition of the opcodes
2127\item[sepia.h] macros
2128\item[types.h] types
2129\item[emu_export.h] internal macros and definitions
2130\item[error.h] error codes
2131\end{description}
2132
2133
2134\subsection{Threaded Code}
2135
2136\index{threaded code}
2137When {\eclipse} is built with the THREADED option, a threaded code
2138system is built. This is the usual configuration for releases.
2139However, it relies on a GCC feature for taking the address of
2140a code label (\&\&). The differences are summarised in the following
2141table. We consider the abstract machine instruction MoveAML:
2142\begin{small}
2143\begin{verbatim}
2144Non-threaded:                       Threaded:
2145-------------                       ---------
2146
2147#define MoveAML 3                   #define MoveAML 3            
2148                                                                 
2149#define OpValue(x)  x               #define OpValue(x)  op_addr[x]
2150
2151                                    op_addr[MoveAML] = &&I_MoveAML;    
2152                                                                 
2153
2154Emulator code:                      Emulator code:
2155
2156_loop_:
2157  switch (PP++->inst)
2158  {                                   {
2159        ...                                 ...
2160
2161    case MoveAML:                       I_MoveAML:                   
2162        <code for instruction>              <code for instruction>       
2163        goto _loop_;                        goto *PP++->emu_addr;       
2164
2165        ...                                 ...
2166  }                                   }
2167\end{verbatim}
2168\end{small}
2169OpValue() is a macro that is used by the code generator and
2170defines which actual op-code value is inserted into the generated code.
2171In the non-threaded case this is simply the instruction number,
2172in the threaded case, the value is the address of the emulator
2173code that implements the instruction.
2174
2175Performance is significantly improved because the threaded transition
2176from one instruction to the next consists just in an indirect jump.
2177
2178
2179\subsection{Emulator Debugging}
2180
2181The emulator\index{emulator}  code contains a few simple features that help debugging\index{debugging}
2182on the abstract machine level:
2183\begin{enumerate}
2184\item A circular buffer that records
2185the last MAX_BACKTRACE addresses of executed abstract instructions.
2186The backtrace can be printed by calling the C function lastpp(n).
2187\item A flag TRACE that will enable printing of abstract machine
2188instructions before they are being executed.
2189\item A variable stop_address that can be set (via c C debugger)
2190to an abstract code address where one wants to stop execution
2191(the emulator calls the function emu_break()).
2192\item A STATISTICS flag that enables counting of each
2193type of instruction.
2194\end{enumerate}
2195Theses facilities rely on an emulator loop being present and
2196are only available in the non-threaded version.
2197
2198