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% $Id: exthsusp.tex,v 1.7 2013/06/03 16:40:44 jschimpf Exp $
24%
25
26\chapter{Advanced Control Features}
27%HEVEA\cutdef[1]{section}
28\label{suspensions}
29
30%-------
31\section{Introduction}
32%-------
33This chapter introduces the control facilities that distinguish the
34{\eclipse} language from Prolog by providing a computation
35rule that is more flexible than simple left-to-right goal selection.
36The core feature is the ability to suspend the execution of a goal
37at some point during execution, and resume it under certain conditions
38at a later stage.
39Together with attributed variables, these facilities are the
40prerequisites for the implementation of constraint propagation
41and similar data-driven algorithms.
42
43% Concepts
44%       resolvent
45%       execution model
46%       floundering
47% Delaying built-in predicates
48% Support
49% Declarative delay clauses
50% The suspend predicate
51% waking conditions (inst/bound/constrained, libraries, user-defined, symbolic,
52% postponed)
53% Lower-level primitives
54%       The suspension
55%       making suspensions
56%       attaching suspensions to variables
57%       attaching suspensions to triggers
58% Demons
59% More about Priorities
60% details of waking, cut
61% simulating alternative suspension facilities
62%
63
64%-------
65\section{Concepts}
66\subsection{The Structured Resolvent}
67%-------
68\index{resolvent}
69The term \defnotion{resolvent} originates from Logic Programming.
70It is the set of all goals that must be satisfied.
71The computation typically starts with a resolvent consisting only of the
72top-level goal
73(the initial query).
74This then gets successively transformed (by substituting goals that
75match a clause head with an instance of the clause body, i.e., a
76sequence of sub-goals),
77and eventually terminates with one of the trivial goals
78\notation{true} or \notation{fail}.
79For example, given the program
80\begin{quote}
81\begin{verbatim}
82p :- q, r.    % clause 1
83q :- true.    % clause 2
84r :- q.       % clause 3
85\end{verbatim}
86\end{quote}
87and the goal p, the resolvent goes through the following states
88before the goal is proven (by reduction to true) and the computation terminates:
89\begin{quote}
90\begin{verbatim}
91p --1--> (q,r) --2--> (true,r) ----> (r) --3--> (q) --2--> true
92\end{verbatim}
93\end{quote}
94
95\index{Prolog}
96While in Prolog the resolvent is always processed from left to right
97like in this example,
98the resolvent in {\eclipse} is more structured, and can be manipulated
99in a much more flexible way.
100This is achieved by two basic mechanisms, \emph{suspension}
101and \emph{priorities}.
102
103\index{suspended goal}
104Suspended goals form the part of the resolvent which is
105currently not being considered. This is typically done when we
106know that we cannot currently infer any interesting information from them.
107
108\index{priority}
109The remaining goals are ordered according to their priority.
110At any time, the system attempts to solve the most urgent subgoal first.
111{\eclipse} currently supports a fixed range of 12 different priorities,
112priority 1 being the most urgent and 12 the least urgent.
113
114Figure \ref{figresolv} shows the structure of the resolvent.
115When a toplevel goal is launched, it has priority 12 and is the only
116member of the resolvent. As execution proceeds, active goals may be
117suspended, and suspended goals may be woken and scheduled with a
118particular priority.
119\begin{figure}
120% picture has been made with xfig and exported as encapsulated postscript
121\includegraphics{resolv.eps}
122\caption{Structure of the resolvent}
123\label{figresolv}
124\end{figure}
125
126\subsection{Floundering}
127\index{floundering}
128The case that a subgoal remains suspended (delayed) at the end of the
129computation
130\index{floundering} is sometimes referred to as \defnotion{floundering}.
131When floundering occurs, it means that the resolvent could not be reduced
132to true or fail, and that the answer bindings that have been found
133are valid only under the assumption that the remaining delayed goals
134are in fact true. Since such a conditional answer is normally not
135satisfactory (even though it may be correct), it is then necessary to change
136the control aspect of the program.  The solution would usually be to either
137make further variable instantiations or to change control annotations.
138The aim is to get the delayed goals out of the suspended state and
139into the scheduled state, where they will eventually be executed and reduced.
140As a rule of thumb, goals will not suspend when all their arguments are
141fully instantiated. Therefore, a program that makes sure that all its
142variables are instantiated at the end of computation will typically not
143suffer from floundering.
144
145
146%----------------------------------------------------------------------
147\section{Suspending Built-Ins and the Suspend-Library}
148%----------------------------------------------------------------------
149
150Basic {\eclipse} has two built-in predicates whose behaviour includes
151suspending: the sound negation built-in
152\txtbipref{\tld/1}{(~)/1}{../bips/kernel/control/T-1.html} and the sound disequality
153predicate \txtbipref{\tld=/2}{(~=)/2}{../bips/kernel/termcomp/TE-2.html}.
154Instead of succeeding or failing, they will suspend when their arguments
155are insufficiently instantiated to make a decision. For example
156\begin{quote}
157\begin{verbatim}
158?- X ~= 3.
159X = X
160There is 1 delayed goal.
161Yes (0.00s cpu)
162\end{verbatim}
163\end{quote}
164Here, the system does not have enough information to decide whether the
165query is true or false. The goal remains delayed and we have a case of
166floundering
167(the {\eclipse} toplevel indicates this situation by printing a message
168about delayed goals at the end of the computation).
169
170However, when the variable which was responsible for the suspension gets
171instantiated
172later, the delayed goal will be resumed (woken) and either succeed, fail, or
173suspend again. In the following example, the disequality predicate initially
174suspends, but wakes up later and succeeds or fails, respectively:
175\begin{quote}
176\begin{verbatim}
177?- X ~= 3, X = 4.
178X = 4
179Yes (0.00s cpu)
180?- X ~= 3, X = 3.
181No (0.00s cpu)
182\end{verbatim}
183\end{quote}
184
185
186\label{suspendsolver}
187Further predicate implementations with the same behaviour (delay until
188all arguments are ground) can be found in the \libspec{suspend} library
189\bipref{lib(suspend)}{../bips/lib/suspend/index.html}.
190In particular, it implements all common arithmetic predicates plus
191the constraints defined by the Common Arithmetic Solver Interface
192(see Constraint Library Manual), for instance
193\begin{verbatim}
194=:=/2, =\=/2,  >=/2,  =</2,  >/2,  </2,
195 $=/2, $\=/2, $>=/2, $=</2, $>/2, $</2,
196 #=/2, #\=/2, #>=/2, #=</2, #>/2, #</2,
197integers/1, reals/1
198\end{verbatim}
199The solver will suspend these predicates until all their arguments
200are ground.\footnote{
201Note that more powerful versions of these constraints exist in other
202solvers such as the interval solver lib(ic).}
203
204The suspend library is loaded into \eclipse\ on start-up, but the
205constraints associated with the suspend solver are not imported.
206To use them, either import the suspend library to the current module,
207or call the constraint qualified with the module:
208\begin{quote}
209\begin{verbatim}
210suspend:(X > 2), suspend:(X #=< 5)
211\end{verbatim}
212\end{quote}
213
214
215
216%----------------------------------------------------------------------
217\section{Development System Support}
218%----------------------------------------------------------------------
219
220As seen in the above example, the \index{top level loop} top level loop
221indicates floundering by printing a message about delayed goals.
222The command line toplevel then prompts and offers to print a list of
223all delayed goals.
224The Tkeclipse development environment provides better support in the form
225of the Delayed Goals Viewer, which can be used to look at all delayed goals
226or a filtered subset of them.
227
228The tracer supports advanced control features via
229the box-model ports DELAY and RESUME.
230It also shows goal priorities (if they deviate from the default priority)
231in angular brackets.
232
233
234%----------------------------------------------------------------------
235\section{Declarative Suspension: Delay Clauses}
236%----------------------------------------------------------------------
237
238For delaying calls to user-defined Prolog predicates, {\eclipse}
239 provides several alternatives, the first being \defnotion{delay clauses}.
240Delay clauses are a declarative means (they are in fact meta-clauses)
241to specify the conditions under which the predicate should delay.
242The semantics of delay clauses is thus cleaner than many alternative
243approaches to delay primitives.
244
245A delay clause is very similar to a normal Prolog clause. It has the form
246\begin{quote}
247\begin{verbatim}
248delay <Head> if <Body>.
249\end{verbatim}
250\end{quote}
251A predicate may have one or more delay clauses.
252They have to be textually \emph{before} and \emph{consecutive}
253with the normal clauses of the predicate they belong to.
254The simplest example for a delay clause is one that checks if a variable
255is instantiated:
256\begin{quote}
257\begin{verbatim}
258delay report_binding(X) if var(X).
259report_binding(X) :-
260        printf("Variable has been bound to %w\n", [X]).
261\end{verbatim}
262\end{quote}
263
264%----------------------------------------------------------------------
265The operational semantics of the delay clauses is as follows:
266when a procedure with delay clauses is called, then the delay
267clauses are executed before executing the procedure itself.
268If one of the delay clauses succeeds, the call is suspended,
269otherwise they are all tried in sequence and,
270if all delay clauses fail, the procedure is executed as usual.
271
272The mechanism of executing a delay clause is similar to normal Prolog
273clauses with two exceptions:
274\begin{itemize}
275\item the unification of the goal with the delay clause head is not the usual
276Prolog unification, but rather unidirectional pattern matching
277(see also section \ref{matching}).
278\index{pattern matching}
279\index{matching}
280This means that the variables in the call cannot be bound
281by the matching, if such a binding would be necessary to
282perform the unification, it will fail instead.
283For example, the head of the delay clause
284\begin{quote}
285\begin{verbatim}
286delay p(a, X) if var(X).
287\end{verbatim}
288\end{quote}
289does not match the goal \notation{p(A,~b)} but it matches the goal
290\notation{p(a,~b)}.
291
292\item the delay clauses are deterministic, they leave no choice points.
293If one delay clause succeeds, the call is delayed and the following delay
294clauses are not executed.
295As soon as the call is resumed, all delay clauses that may succeed
296are re-executed.
297\end{itemize}
298The reason for using pattern matching instead of unification
299is to avoid a possible mixing of meta-level control with the
300object level, similarly to \cite{dincbas84}.
301
302
303%----------------------------------------------------------------------
304The form of the head of a delay clause is not restricted.
305For the body, the following conditions hold:
306
307\begin{itemize}
308\item the body subgoals must not bind any variable in the call and they
309must not delay themselves.
310The system does not verify these conditions currently.
311
312\item it should contain at least one of the following subgoals:
313\begin{itemize}
314\item \bipref{var/1}{../bips/kernel/typetest/var-1.html}
315\item \bipref{nonground/1}{../bips/kernel/typetest/nonground-1.html}
316\item \predspec{nonground/2} (see
317  \bipref{nonground/3}{../bips/kernel/typetest/nonground-3.html})
318\item \predspec{\bsl==/2}
319\index{\bsl==/2@\bsl\notation{==/2}}
320\end{itemize}
321If this is not the case, then the predicate may delay without being linked
322to a variable, so it delays forever and cannot be woken again.
323Experience shows that the above four primitives suffice to express most
324usual conditions.
325\end{itemize}
326
327\subsubsection{More Examples}
328\begin{itemize}
329\item
330A predicate that checks if its argument is a proper list of integers.
331The delay conditions specify that the predicate should delay if the list
332is not terminated or if it contains variable elements.
333This makes sure that it will never generate list elements, but only
334acts as a test:
335\begin{quote}
336\begin{verbatim}
337delay integer_list(L) if var(L).
338delay integer_list([X|_]) if var(X).
339integer_list([]).
340integer_list([X|T]) :- integer(X), integer_list(T).
341\end{verbatim}
342\end{quote}
343
344\item
345Delay if the first two arguments are identical and the third is a variable:
346\begin{quote}
347\begin{verbatim}
348delay p(X, X, Y) if var(Y).
349\end{verbatim}
350\end{quote}
351
352\item
353Delay if the argument is a structure whose first subterm is not ground:
354\begin{quote}
355\begin{verbatim}
356delay p(X) if compound(X), arg(1, X, Y), nonground(Y).
357\end{verbatim}
358\end{quote}
359
360\item
361Delay if the argument term contains 2 or more variables:
362\begin{quote}
363\begin{verbatim}
364delay p(X) if nonground(2, X).
365\end{verbatim}
366\end{quote}
367
368\item
369The
370\predspec{\bsl==/2}
371\index{\bsl==/2@\bsl\notation{==/2}}
372predicate as a delaying condition is useful mainly
373in calls like \notation{X~+~Y~=~Z} which need not be delayed if
374\about{X}~\notation{==}~\about{Z}.
375\about{Y} can be directly bound to 0, provided that \about{X} is later bound to
376a number
377(or it is not bound at all)
378The condition \notation{X {\bsl}== Y} makes sense
379only if \about{X} or \about{Y} are nonground: a delay clause
380\begin{quote}
381\begin{verbatim}
382delay p(X, Y) if X \== Y.
383\end{verbatim}
384\end{quote}
385executed with the call \notation{?- p(a, b)} of course succeeds and the call
386delays
387forever, since no variable binding can wake it.
388\end{itemize}
389
390\textbf{CAUTION}: It may happen that the symbol \notation{:-} is erroneously
391used instead of \notation{if} in the delay clause. To indicate this error,
392the compiler complains about redefinition of the built-in predicate
393\predspec{delay/1}.
394
395
396%----------------------------------------------------------------------
397\section{Explicit suspension with \predspec{suspend/3}}
398%----------------------------------------------------------------------
399\label{suspend3}
400While delay-clauses are an elegant, declarative way of specifying how
401a program should execute, it is sometimes necessary to be more explicit
402about suspension and waking conditions.
403The built-in predicate
404\bipref{suspend/3}{../bips/kernel/suspensions/suspend-3.html}
405is provided for this purpose\footnote{
406\predspec{suspend/3} is itself based on the lower-level primitives
407\predspec{make_suspension/3}
408and \predspec{insert_suspension/4}, which are described below.}.
409It allows one to explicitly create a suspended goal, specify its priority
410and its exact waking conditions.
411
412When
413\begin{quote}
414\predspec{suspend(\pattern{Goal}, \pattern{Prio}, \pattern{CondList})}
415\end{quote}
416is called, \about{Goal} will be suspended with priority \about{Prio}
417and it will wake up
418as soon as one of the conditions specified in the \about{CondList}
419is satisfied.
420This list contains specifications of the form
421\begin{quote}
422\notation{\pattern{Vars} \notation{->} \pattern{Cond}}
423\end{quote}
424to denote that as soon as one of the variables in the term \about{Vars}
425satisfies the condition \about{Cond}, the suspended goal will
426be woken and then executed as soon as the program priority allows it.
427\about{CondList} can also be a single specification.
428
429The condition \about{Cond} can be the name of a system-defined waking condition,
430e.g.,
431\begin{quote}
432\begin{verbatim}
433[X,Y]->inst
434\end{verbatim}
435\end{quote}
436means that as soon as one (or both) of the variables \about{X}, \about{Y}
437is instantiated, the suspended goal will be woken.
438\index{suspending variables}
439These variables are also called the \defnotion{suspending variables} of the
440goal.
441
442
443\about{Cond} can also be the specification of a suspension list
444defined in one of currently loaded library attributes. For example, when the
445interval solver library lib(ic) is loaded, either of
446\begin{quote}
447\begin{verbatim}
448[A,B]->ic:min
449[A,B]->ic:(min of ic)
450\end{verbatim}
451\end{quote}
452triggers the suspended goal as soon as the minimum element
453of the domain of either \about{A} or \about{B} are updated
454(see Constraint Library Manual, IC Library).
455
456Another admissible form of condition \about{Cond} is
457\begin{quote}
458\begin{verbatim}
459trigger(Name)
460\end{verbatim}
461\end{quote}
462which suspends the goal on the global trigger condition \about{Name}
463(see section~\ref{trigger}).
464
465
466Using
467\bipref{suspend/3}{../bips/kernel/suspensions/suspend-3.html},
468we can rewrite our first delay-clause example from above as follows:
469\begin{quote}
470\begin{verbatim}
471report_binding(X) :-
472        ( var(X) ->
473            suspend(report_binding(X), 0, X->inst)
474        ;
475            printf("Variable has been bound to %w\n", [X])
476        ).
477\end{verbatim}
478\end{quote}
479Here, when the predicate is called with an uninstantiated argument,
480we explicitly suspend a goal with the condition that it be woken as
481soon as X becomes instantiated. The priority is given as 0, which indicates
482the default priority (0 is not a valid priority itself).
483Running this code produces the following:
484\begin{quote}
485\begin{verbatim}
486?- report_binding(X).
487X = X
488There is 1 delayed goal.
489Yes (0.00s cpu)
490\end{verbatim}
491\end{quote}
492When X is later instantiated, it will wake up and print the message:
493\begin{quote}
494\begin{verbatim}
495?- report_binding(X), writeln(here), X = 99.
496here
497Variable has been bound to 99
498X = 99
499Yes (0.00s cpu)
500\end{verbatim}
501\end{quote}
502
503
504
505%----------------------------------------------------------------------
506\section{Waking conditions}
507%----------------------------------------------------------------------
508The usual purpose of suspending a goal is to wait and resume it later
509when more information about its arguments is available.
510In Logic Programming, this is usually the case when certain events
511related to variables occur.
512When such an event occurs, the suspended goal is passed to the
513waking scheduler which puts it at the appropriate place
514in the priority queue of woken goals and as soon as it becomes
515first in the queue, the suspended goal is executed.
516
517The event which causes a suspended goal to be woken is usually
518related to one or more variables, for example
519variable instantiation, or a modification of a variable's
520attribute.
521However, it is also possible to trigger suspension with symbolic events
522not related to any variable.
523
524
525%----------------------------------------------------------------------
526\subsection{Standard Waking Conditions on Variables}
527%----------------------------------------------------------------------
528\label{suspend}
529\index{suspend}
530\index{coroutining}
531\label{coroutining}%
532There are three very general standard waking conditions which
533can be used with any variable. They are, in order of increasing generality:
534\begin{quote}
535\begin{description}
536\item[inst:] wake when a variable gets instantiated;
537\item[bound:] wake when a variable gets instantiated or bound to
538        another variable;
539\item[constrained:] wake when a variable gets instantiated or bound to
540        another variable or becomes otherwise constrained.
541\end{description}
542\end{quote}
543Each condition subsumes the preceding, more specific ones.
544
545
546% - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - -
547\subsubsection{Waking on Instantiation: inst}
548% - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - -
549
550To wake a goal when a variable gets instantiated, the \notation{inst}
551condition is used. For example the following code suspends a goal until
552variable \about{X} is instantiated:
553\begin{quote}
554\begin{verbatim}
555?- suspend(writeln(woken(X)), 0, X->inst).
556X = X
557There is 1 delayed goal.
558Yes (0.00s cpu)
559\end{verbatim}
560\end{quote}
561If this variable is later instantiated (bound to a non-variable),
562the goal executes in a data-driven way:
563\begin{quote}
564\begin{verbatim}
565?- suspend(writeln(woken(X)), 0, X->inst), X = 99.
566woken(99)
567X = 99
568Yes (0.00s cpu)
569\end{verbatim}
570\end{quote}
571If we specify several instantiation conditions for the same goal,
572the goal will wake up as soon as the first of them occurs:
573\begin{quote}
574\begin{verbatim}
575?- suspend(writeln(woken(X,Y)), 0, [X,Y]->inst), X = 99.
576woken(99, Y)
577X = 99
578Y = Y
579Yes (0.00s cpu)
580\end{verbatim}
581\end{quote}
582It is not possible to specify a conjunction of conditions directly!
583
584Let us now suppose we want to implement a predicate \predspec{succ/2}, such that
585\notation{succ(X,~Y)}
586is true when \about{Y} is the next integer after \about{X}. If we want the
587predicate
588to act as a lazy test, we must let it suspend until both variables
589are instantiated. This can be programmed as follows:
590\begin{quote}
591\begin{verbatim}
592succ_lazy(X, Y) :-
593        ( var(X) -> suspend(succ_lazy(X,Y), 0, X->inst)
594        ; var(Y) -> suspend(succ_lazy(X,Y), 0, Y->inst)
595        ; Y =:= X+1
596        ).
597\end{verbatim}
598\end{quote}
599The conjunctive condition ``wait until \about{X} and \about{Y} are
600instantiated''
601is
602implemented by first waiting for \about{X}'s instantiation, then waking up and
603re-suspending waiting for \about{Y}'s instantiation.
604
605A more eager implementation of \predspec{succ/2} would delay only until
606a single variable argument is left, and then compute the variable from
607the nonvariable argument:
608\begin{quote}
609\begin{verbatim}
610succ_eager(X, Y) :-
611        ( var(X) ->
612            ( var(Y) ->
613                suspend(succ_eager(X,Y), 0, [X,Y]->inst)
614            ;
615                X is Y-1
616            )
617        ;
618            Y is X+1
619        ).
620\end{verbatim}
621\end{quote}
622Here, we suspend only in the case that both arguments are variables,
623and wake up as soon as either of them gets instantiated.
624
625Waiting for groundness of a term can be done in a way similar to the
626way \predspec{succ_lazy/2} waited for both arguments to be instantiated: we
627pick
628any variable in the nonground term and wait for its instantiation.
629If this happens, we check whether other variables remain, and if yes,
630we re-suspend on one of the remaining variables. The following predicate
631waits for a term to become ground, and then calls arithmetic evaluation on it:
632\begin{quote}
633\begin{verbatim}
634eval_lazy(Expr, Result) :-
635        ( nonground(Expr, Var) ->
636            suspend(eval_lazy(Expr,Result), 0, Var->inst)
637        ;
638            Result is Expr
639        ).
640\end{verbatim}
641\end{quote}
642We have used the built-in predicate
643\bipref{nonground/2}{../bips/kernel/typetest/nonground-2.html}
644which tests a term for groundness and returns one of its variables
645if it is nonground. Note also that in this implementation the same
646\predspec{eval_lazy/2} goal gets woken and re-suspended possibly many times.
647See section \ref{secdemon} below for how to address this inefficiency.
648
649
650% - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - -
651\subsubsection{Waking on Binding: bound}
652% - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - -
653
654Sometimes it is interesting to wake a goal when the number of variables
655among its arguments is reduced. This happens not only when a variable
656disappears due to instantiation, but also when two variables get unified
657(the result being a single variable). Consider the \predspec{succ_eager/2}
658predicate
659above: we know that a goal like \notation{succ_eager(X,X)}. must always fail
660because an integer cannot be equal to its successor. However, the above
661implementation does not detect this case until X gets instantiated.
662
663The \notation{bound} waking condition subsumes the \notation{inst} condition,
664but
665also wakes when any two of the variables in the condition specification get
666unified with each other (aliased).
667Using this property, we can improve the implementation of
668\predspec{succ_eager/2}
669as follows:
670\begin{quote}
671\begin{verbatim}
672succ_eager1(X, Y) :-
673        ( var(X) ->
674            ( var(Y) ->
675                X \== Y,
676                suspend(succ_eager1(X,Y), 0, [X,Y]->bound)
677            ;
678                X is Y-1
679            )
680        ;
681            Y is X+1
682        ).
683\end{verbatim}
684\end{quote}
685This gives us the desirable behaviour of failing as soon as possible:
686\begin{quote}
687\begin{verbatim}
688?- succ_eager1(X, Y), X = Y.
689No (0.00s cpu)
690\end{verbatim}
691\end{quote}
692Note that the built-in predicate
693\txtbipref{\tld=/2}{(~=)/2}{../bips/kernel/termcomp/TE-2.html}
694is a similar case and uses the \notation{bound} waking condition for the
695same reason.
696
697
698
699% - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - -
700\subsubsection{Waking on Constraining: constrained}
701% - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - -
702
703In plain Prolog, variable instantiation is the only way in which a single
704variable can become more constrained.  In the presence of constraints,
705there are other ways. The most obvious example are variable domains:
706when a variable's domain gets reduced, the variable becomes more
707constrained. This means that a delayed goal that previously still had
708a chance to succeed, could now have become impossible to satisfy,
709and should therefore be checked again.
710
711The purpose of the \notation{constrained} waking condition is to make it
712possible to wake a suspended goal whenever a variable becomes more
713constrained in a general sense. Having this general notion
714of constrained-ness makes it possible to write generic libraries
715that do interesting things with constraints and constrained variables
716without their implementation having to be linked to a particular
717constraint-solver\footnote{%
718  Examples of such libraries are \libspec{branch_and_bound},
719  \libspec{changeset}, \libspec{chr}/\libspec{ech}, \libspec{propia},
720  \libspec{repair}, \libspec{visualisation}.}.
721
722The \notation{constrained} waking condition subsumes the \notation{bound}
723condition
724(which in turn subsumes the \notation{inst} condition).
725While goals suspended on the \notation{inst} and \notation{bound} conditions
726are woken implicitly by the unification routine, libaries which implement
727domain variables are responsible for notifying the system when they
728constrain a variable. They do so by invoking the built-ins
729\bipref{notify_constrained/1}{../bips/kernel/suspensions/notify_constrained-1.html}
730and \bipref{wake/0}{../bips/kernel/suspensions/wake-0.html}
731which is the generic way of telling the system that a variable has been
732constrained.
733
734The simplest application using the \notation{constrained} condition is a little
735debugging support predicate that prints a variable's current partial value
736(e.g., domain) whenever it changes:
737\begin{quote}
738\begin{verbatim}
739report(X) :-
740        ( var(X) ->
741            writeln(constrained(X)),
742            suspend(report(X), 1, X->constrained)  % (re)suspend
743        ;
744            writeln(instantiated(X))
745        ).
746\end{verbatim}
747\end{quote}
748This now works with any library that implements a notion of constrainedness,
749e.g., the interval solver library(ic):
750\begin{quote}
751\begin{verbatim}
752?- report(X), X :: 1..5, X #> 2, X #< 4.
753constrained(X)
754constrained(X{1 .. 5})
755constrained(X{3 .. 5})
756instantiated(3)
757X = 3
758Yes (0.01s cpu)
759\end{verbatim}
760\end{quote}
761The \predspec{report/1} predicate is woken when the domain is initally attached
762to X,
763whenever the domain gets reduced, and finally when X gets instantiated.
764
765
766
767%----------------------------------------------------------------------
768\subsection{Library-defined Waking Conditions on Variables}
769%----------------------------------------------------------------------
770
771Constraint-solver libraries typically define additional, specialised
772waking conditions for the type of variable that they implement.
773For instance, the interval solver lib(ic) defines the following
774conditions:
775\begin{quote}
776\begin{description}
777\item[min:] wake when the minimum domain value changes;
778\item[max:] wake when the maximum domain value changes;
779\item[hole:] wake when the domain gets a new hole;
780\item[type:] wake when the variable type changes from real to integer.
781\end{description}
782\end{quote}
783Obviously, these conditions only make sense for domain variables
784that are created by the lib(ic) library, and are mainly useful for
785implementing extensions to this library, e.g., new constraints.
786The library-defined waking conditions can be used with
787\bipref{suspend/3}{../bips/kernel/suspensions/suspend-3.html}
788by using one of the following syntactic forms:
789\begin{quote}
790\begin{verbatim}
791[A, B]->ic:min
792[A, B]->ic:(min of ic)
793\end{verbatim}
794\end{quote}
795Using these conditions, we can define a more specialised form of
796the above \predspec{report/1} predicate which only wakes up on the specified
797ic-domain changes:
798\begin{quote}
799\begin{verbatim}
800report_ic(X) :-
801        ( var(X) ->
802            writeln(newdomain(X)),
803            suspend(report_ic(X), 1, [X->ic:min,X->ic:max,X->ic:hole])
804        ;
805            writeln(instantiated(X))
806        ).
807\end{verbatim}
808\end{quote}
809The behaviour is similar to above, the predicate wakes up on every
810domain change:
811\begin{quote}
812\begin{verbatim}
813?- X::1..5, report_ic(X), X#> 2, X #< 4.
814newdomain(X{1 .. 5})
815newdomain(X{3 .. 5})
816instantiated(3)
817X = 3
818Yes (0.00s cpu)
819\end{verbatim}
820\end{quote}
821Note that we now have to set up the delayed goal \emph{after} the
822variable already has a domain. This is because the ic-specific waking
823conditions can only be used with ic-variables,\footnote{%
824  More precisely,
825  variables which have an ic-attribute, see chapter \ref{attrvars}.}
826not with domain-less generic variables.
827
828
829
830%----------------------------------------------------------------------
831\subsection{Global Symbolic Waking Conditions: Triggers}
832\label{trigger}
833%----------------------------------------------------------------------
834
835Although waking conditions for a goal are usually related to variables
836within the goal's arguments, it is also possible to specify symbolic
837waking conditions which are unrelated to variables.
838\index{trigger}\index{symbolic waking condition}%
839These are called \defnotion{triggers} and are identified simply by an
840arbitrary name (an atom). Goals can be suspended on such triggers,
841and the trigger can be pulled explicitly by program code in
842particular circumstances. By combining triggers with the event mechanism
843\index{events}
844(chapter \ref{chapexcept}) it is even possible to wake goals in
845response to synchronous or asynchronous events.
846
847A goal is suspended on a trigger using the syntax \pattern{trigger(Name)}
848in \bipref{suspend/3}{../bips/kernel/suspensions/suspend-3.html}
849as in the following example:
850\begin{quote}
851\begin{verbatim}
852?- suspend(writeln(woken), 0, trigger(happy)).
853There is 1 delayed goal.
854Yes (0.00s cpu)
855\end{verbatim}
856\end{quote}
857The built-in
858\bipref{trigger/1}{../bips/kernel/suspensions/trigger-1.html}
859can then be used to wake the goal:
860\begin{quote}
861\begin{verbatim}
862?- suspend(writeln(woken), 0, trigger(happy)), trigger(happy).
863woken
864Yes (0.00s cpu)
865\end{verbatim}
866\end{quote}
867Of course, symbolic triggers can be used together with other
868waking conditions to specify alternative reasons to wake a goal.
869
870
871
872% - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - -
873\subsubsection{Postponed Goals}
874% - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - -
875\index{postponed}
876There is one system-defined trigger called \defnotion{postponed}.%
877\index{postponed trigger}\index{trigger!postponed}
878It is provided as a way to postpone the triggering of a goal as much
879as possible. This trigger is pulled just before the end of
880certain encapsulated executions, like
881\begin{itemize}
882\item end of toplevel execution;
883\item inside all-solution predicates
884  (\bipref{findall/3}{../bips/kernel/allsols/findall-3.html},
885  \bipref{setof/3}{../bips/kernel/allsols/setof-3.html});
886\item inside \bipref{bb_min/3}{../bips/lib/branch_and_bound/bb_min-3.html} and
887  \bipref{minimize/2}{../bips/lib/branch_and_bound/minimize-2.html}.
888\end{itemize}
889A suspension should be attached to the \notation{postponed} trigger only when
890\begin{itemize}
891\item it might not have any other waking conditions left;
892\item and it might at the same time have other waking conditions left
893        that could make it fail during further execution;
894\item and one does not want to execute it now, e.g., because it is known
895        to succeed or re-suspend.
896\end{itemize}
897An example is a goal that originally woke on modifications of the upper
898bound of an interval variable. If the variable gets instantiated to its
899upper bound, there is no need to wake the goal (since the bound has not
900changed), but the variable (and with it the waking condition) disappears
901and the goal may be left orphaned.
902
903
904
905
906%----------------------------------------------------------------------
907\section{Lower-level Primitives}
908%----------------------------------------------------------------------
909
910Suspended goals are actually represented by a special
911opaque data type, called \defnotion{suspension}, which can be explicitly
912manipulated under program control using the primitives defined in
913this section.
914Although usually a suspended goal waits for some waking condition
915in order to be reactivated, the primitives for suspension handling
916do not enforce this. To provide maximum flexibility of use,
917the functionalities of suspending and waking/scheduling are
918separated from the trigger mechanisms that cause the waking.
919
920
921\index{suspension|(}
922
923\subsection{Suspensions and Suspension Lists}
924%-------
925A suspension represents a goal that is part of the resolvent.
926Apart from the goal structure proper, it holds information that
927is used for controlling its execution.
928The components of a suspension are:
929\begin{quote}
930\begin{description}
931\item[The goal structure]
932        A term representing the goal itself, e.g., \notation{X > Y}.
933\item[The goal module]
934        The module from which the goal was called.
935\item[The scheduling priority]
936        The priority with which the goal will be scheduled when
937        it becomes woken.
938\item[The run priority]
939        The priority under which the goal will eventually be executed.
940\item[The state]
941        This indicates the current position of the suspension within
942        the resolvent. It is either suspended (sleeping), scheduled
943	or executed (dead).
944\item[Additional data]
945	Debugging information etc.
946\end{description}
947\end{quote}
948
949Suspensions which should be woken by the same event are grouped
950together in a \defnotion{suspension list}.
951%This is a normal Prolog list which contains suspensions.
952Suspension lists are either stored in an attribute of
953an attributed variable or attached to a symbolic trigger.
954
955
956\subsection{Creating Suspended Goals}
957%-------
958\index{suspension!creating}
959The most basic primitive to create a suspension is
960\begin{quote}
961\biptxtrefni{make_suspension(\pattern{Goal},~\pattern{Priority},%
962~\pattern{Susp} \lbr, \pattern{Module}\rbr)}{make_suspension/3,4}{../bips/kernel/suspensions/make_suspension-3.html}%
963\indextt{make_suspension/3}\indextt{make_suspension/4}
964\end{quote}
965where \about{Goal} is the goal structure,
966\about{Priority} is a small integer denoting the priority with which
967the goal should be woken and \about{Susp} is the resulting suspension.
968
969Note that usually
970\biprefni{make_suspension/3,4}{../bips/kernel/suspensions/make_suspension-3.html}
971is not used directly, but implicitly via
972\biprefni{suspend/3,4}{../bips/kernel/suspensions/suspend-3.html}\indextt{suspend/3}\indextt{suspend/4}
973(described in section \ref{suspend3}) which in addition attaches the suspension
974to a
975trigger condition.
976
977A suspension which has not yet been scheduled
978for execution and executed, is called
979\defnotionni{sleeping},\index{sleeping suspension}\index{suspension!sleeping}
980a suspension which has already been executed is called
981\defnotionni{executed}\index{executed suspension}\index{suspension!executed}
982or
983\defnotionni{dead}\index{dead suspension}\index{suspension!dead}
984(since it disappears from the resolvent,
985but see section \ref{secdemon} for an exception).
986A newly created suspension is always sleeping, however
987note that due to backtracking, an executed suspension
988can become sleeping again.
989Sometimes we use the term
990\defnotion{waking},\index{waking suspension}\index{suspension!waking}
991which is less precise and
992denotes the process of both scheduling and eventual execution.
993
994
995By default, suspensions are printed as follows (the variants with invocation
996numbers are used when the debugger is active):
997\begin{center}
998\begin{tabular}{|c|l|}
999\hline
1000'SUSP-_78-susp'		&   sleeping suspension with id _78 \\
1001'SUSP-_78-sched'	&   scheduled suspension with id _78 \\
1002'SUSP-_78-dead'		&   dead suspension with id _78 \\
1003\hline
1004'SUSP-123-susp'		&   sleeping suspension with invocation number 123 \\
1005'SUSP-123-sched'	&   scheduled suspension with invocation number 123 \\
1006'SUSP-123-dead'		&   dead suspension with id invocation number 123 \\
1007\hline
1008\end{tabular}
1009\end{center}
1010It is possible to change the way suspensions are printed by defining a
1011\bipref{portray/3}{../bips/kernel/syntax/portray-3.html}
1012transformation for the term type \notation{goal}.
1013
1014
1015
1016\subsection{Operations on Suspensions}
1017%-------
1018The following summarises the predicates that can be used to create, test,
1019decompose and destroy suspensions.
1020\begin{quote}
1021\begin{description}
1022\item[\biptxtref{make_suspension(\pattern{Goal},~\pattern{Priority},~\pattern{Susp})}{make_suspension/3}{../bips/kernel/suspensions/make_suspension-3.html}]
1023\item[\biptxtref{make_suspension(\pattern{Goal},~\pattern{Priority},~\pattern{Susp},~\pattern{Module})}{make_suspension/4}{../bips/kernel/suspensions/make_suspension-4.html}]
1024Create a suspension with a given priority from a given goal.
1025The goal will subsequently show up as a delayed goal.
1026
1027\item[\biptxtref{is_suspension(\pattern{Susp})}{is_suspension/1}{../bips/kernel/typetest/is_suspension-1.html}]
1028Succeeds if \about{Susp} is a sleeping or scheduled suspension,
1029fails if it is not a suspension or a suspension that has been already executed.
1030
1031\item[\biptxtref{type_of(\pattern{S},~\pattern{goal})}{type_of/2}{../bips/kernel/typetest/type_of-2.html}]
1032Succeeds if \about{S} is a suspension, no matter if it is
1033sleeping, scheduled or executed.
1034
1035\item[\biptxtref{get_suspension_data(%
1036\pattern{Susp},~\pattern{Name},~\pattern{Value})}{get_suspension_data/3}{../bips/kernel/suspensions/get_suspension_data-3.html}]
1037Extract any of the information contained in the suspension:
1038\about{Name} can be one of
1039\notation{goal}, \notation{module}, \notation{priority}, \notation{state} or
1040\notation{invoc} (debugger invocation number).
1041
1042
1043\item[\biptxtref{set_suspension_data(%
1044\pattern{Susp},~\pattern{Name},~\pattern{Value})}{set_suspension_data/3}{../bips/kernel/suspensions/set_suspension_data-3.html}]
1045The \notation{priority} and \notation{invoc} (debugger invocation number) fields
1046of a suspension can be changed using this primitive.
1047If the priority of a sleeping suspension is changed,
1048this will only have an effect at the time the suspension gets
1049scheduled. If the suspension is already scheduled, changing
1050priority has no effect, except for future schedulings of demons
1051(see~\ref{secdemon}).
1052
1053
1054\item[\biptxtref{kill_suspension(\pattern{Susp})}{kill_suspension/1}{../bips/kernel/suspensions/kill_suspension-1.html}]
1055Convert the suspension \about{Susp} into an executed
1056one, i.e., remove the suspended goal from the resolvent.
1057This predicate is meta-logical as its use may
1058change the semantics of the program.
1059\end{description}
1060\end{quote}
1061
1062
1063
1064\subsection{Examining the Resolvent}
1065%-------
1066The system keeps track of all created suspensions and it
1067uses this data, e.g., in the built-in predicates
1068\bipref{delayed_goals/1}{../bips/kernel/suspensions/delayed_goals-1.html},
1069\bipref{suspensions/1}{../bips/kernel/suspensions/suspensions-1.html},
1070\bipref{current_suspension/1}{../bips/kernel/suspensions/current_suspension-1.html},
1071\bipref{subcall/2}{../bips/kernel/suspensions/subcall-2.html}
1072\index{floundering}
1073and to detect floundering of the query given to the {\eclipse} top-level loop.
1074
1075
1076
1077\subsection{Attaching Suspensions to Variables}
1078%---------
1079
1080
1081Suspensions are attached to variables by means of the attribute mechanism.
1082\index{attribute}
1083For this purpose, a variable attribute must have one or more slots
1084reserved for \defnotionni{suspension lists}.\index{suspension list}
1085Suspensions can then be inserted into one or several of those lists using
1086\begin{quote}
1087\begin{description}
1088\item[\biptxtref{insert_suspension(\pattern{Vars},~\pattern{Susp},~\pattern{Index})}{insert_suspension/3}{../bips/kernel/suspensions/insert_suspension-3.html}]
1089Insert the suspension \about{Susp} into the \about{Index}'th
1090suspension list of all attributed variables occurring in \about{Vars}.
1091The current module specifies which of the attributes will be taken.
1092
1093\item[\biptxtref{insert_suspension(\pattern{Vars},~\pattern{Susp},~\pattern{Index},~\pattern{Module})}{insert_suspension/4}{../bips/kernel/suspensions/insert_suspension-4.html}]
1094Similar to the above,
1095but it inserts the suspension into the attribute specified by \about{Module}.
1096\end{description}
1097\end{quote}
1098
1099For instance,
1100\begin{quote}
1101\begin{verbatim}
1102insert_suspension(Vars, Susp, inst of suspend, suspend)
1103\end{verbatim}
1104\end{quote}
1105inserts the suspension into the \notation{inst}
1106list of the (system-predefined) \notation{suspend}
1107attribute of all variables that occur in \about{Vars}, and
1108\begin{quote}
1109\begin{verbatim}
1110insert_suspension(Vars, Susp, max of fd, fd)
1111\end{verbatim}
1112\end{quote}
1113would insert the suspension into the \notation{max} list of the finite-domain
1114attribute of all variables in \about{Vars}.
1115
1116Note that both predicates
1117find all attributed variables which occur in the general term \about{Vars} and
1118for
1119each of them,
1120locate the attribute which corresponds to the current module or the
1121\about{Module} argument respectively.
1122This attribute must be a structure, otherwise an error
1123is raised, which means that the attribute has to be initialized
1124before calling
1125\biprefni{insert_suspension/4,3}{../bips/kernel/suspensions/insert_suspension-4.html}.%
1126\indextt{insert_suspension/3}\indextt{insert_suspension/4}
1127Finally, the \about{Index}'th argument of the attribute
1128is interpreted as a suspension list and the suspension
1129\about{Susp} is inserted at the beginning of this list.
1130%\bipref{insert_suspension/3}{../bips/kernel/suspensions/insert_suspension-3.html}
1131%also recognises suspension
1132%lists which are difference lists, i.e., terms {\it Start - Tail}.
1133A more user-friendly interface to access suspension lists is
1134provided by the
1135\bipref{suspend/3}{../bips/kernel/suspensions/suspend-3.html}
1136predicate.
1137
1138
1139\subsection{User-defined Suspension Lists}
1140
1141Many important attributes and suspension lists are either provided by
1142the suspend-attribute or by libraries like the interval solver library lib(ic).
1143For those suspension lists, initialization and waking is taken care of
1144by the library code.
1145
1146For the implementation of user-defined suspension lists,
1147the following low-level primitives are provided:
1148\begin{quote}
1149\begin{description}
1150\item[\biptxtref{init_suspension_list(+\pattern{Position},~+\pattern{Attribute})}{init_suspension_list/2}{../bips/kernel/suspensions/init_suspension_list-2.html}]
1151    Initializes argument \about{Position} of \about{Attribute} to an empty
1152    suspension list.
1153\item[\biptxtref{merge_suspension_lists(+\pattern{Pos1},~+\pattern{Attr},~+\pattern{Pos2},~+\pattern{Attr2})}{merge_suspension_lists/4}{../bips/kernel/suspensions/merge_suspension_lists-4.html}]
1154    Appends the first of two suspension lists (argument
1155    \about{Pos1} of
1156    \about{Attr1}) to
1157    the end of the second (argument \about{Pos2} of \about{Attr2}). NOTE: The
1158    append is destructive, i.e., the second list is modified.
1159\item[\biptxtref{enter_suspension_list(+\pattern{Pos},~+\pattern{Attr},~+\pattern{Susp})}{enter_suspension_list/3}{../bips/kernel/suspensions/enter_suspension_list-3.html}]
1160    Adds the suspension \about{Susp} to the suspension list in the
1161    argument position \about{Pos} of \about{Attr}. The suspension list can be
1162    pre-existing,
1163    or the argument could be uninstantiated, in which case a new suspension
1164    list will be created.
1165\item[\biptxtref{schedule_suspensions(+\pattern{Position},~+\pattern{Attribute})}{schedule_suspensions/2}{../bips/kernel/suspensions/schedule_suspensions-2.html}]
1166    Takes the suspension list on argument position \about{Position} within
1167    \about{Attribute}, and schedule them for execution.
1168    As a side effect, the suspension list within \about{Attribute} is updated,
1169    i.e., suspensions which are no longer useful are removed destructively.
1170    See section \ref{secwaking} for more details on waking.
1171\end{description}
1172\end{quote}
1173
1174
1175\subsection{Attaching Suspensions to Global Triggers}
1176%---------
1177\index{trigger}
1178\index{symbolic waking condition}
1179A single suspension or a list of suspensions can be attached to a
1180symbolic trigger by using
1181\biptxtref{attach_suspensions(+\pattern{Trigger},~+\pattern{Susps})}{attach_suspensions/2}{../bips/kernel/suspensions/attach_suspensions-2.html}.
1182A symbolic trigger can have an arbitrary name (an atom).
1183%To ``pull the trigger''
1184%\biptxtref{schedule_suspensions(+Trigger)}{schedule_suspensions/1}{../bips/kernel/suspensions/schedule_suspensions-1.html}
1185%is used which will submit all attached suspensions to the waking scheduler.
1186
1187
1188
1189
1190%-------
1191\subsection{Scheduling Suspensions for Waking}
1192%-------
1193\label{secwaking}\index{waking}%
1194Suspended goals are woken by submitting at least one of the suspension lists
1195in which they occur to the waking scheduler.
1196The waking scheduler which maintains a global priority queue inserts
1197them into this queue according to their scheduling priority (see figure \ref{figresolv}).
1198A suspension list can be passed to the scheduler by either of the predicates
1199\bipref{schedule_suspensions/1}{../bips/kernel/suspensions/schedule_suspensions-1.html}
1200(for triggers)
1201or
1202\bipref{schedule_suspensions/2}{../bips/kernel/suspensions/schedule_suspensions-2.html}
1203(for uder-defined suspension lists).
1204A suspension which has been scheduled in this way and awaits
1205its execution is called a
1206\defnotion{scheduled suspension}\index{suspension!scheduled}.
1207
1208Note, however, that scheduling a suspension by means of
1209\bipref{schedule_suspensions/1}{../bips/kernel/suspensions/schedule_suspensions-1.html}
1210or
1211\bipref{schedule_suspensions/2}{../bips/kernel/suspensions/schedule_suspensions-2.html}
1212alone does not implicitly start the waking scheduler.
1213Instead, execution continues normally with the next goal in sequence after
1214\predspec{schedule_suspensions/1,2}.
1215The scheduler must be explicitly invoked by calling
1216\bipref{wake/0}{../bips/kernel/suspensions/wake-0.html}.
1217Only then does it start to execute the woken suspensions.
1218
1219The reason for having \bipref{wake/0}{../bips/kernel/suspensions/wake-0.html}
1220is to be able to schedule several suspension lists before the
1221priority-driven execution begins.%
1222\footnote{This mechanism may be reconsidered in a future release.}
1223
1224\index{suspension|)}
1225
1226
1227%----------------------------------------------------------------------
1228\section{Demon Predicates}
1229%----------------------------------------------------------------------
1230\label{secdemon}%
1231A common pattern when implementing data-driven algorithms is the following
1232variant of the \predspec{report/1} example from above:
1233\begin{quote}
1234\begin{verbatim}
1235report(X) :-
1236      suspend(report1(X), 1, X->constrained).      % suspend
1237
1238report1(X) :-
1239        ( var(X) ->
1240            writeln(constrained(X)),
1241            suspend(report(X), 1, X->constrained)  % re-suspend
1242        ;
1243            writeln(instantiated(X))               % die
1244        ).
1245\end{verbatim}
1246\end{quote}
1247Here we have a goal that keeps monitoring changes to its variables.
1248To do so, it suspends on some or all of those variables.
1249When a change occurs, it gets woken, does something, and re-suspends.
1250The repeated re-suspending has two disadvantages: it can be inefficient,
1251and the goal does not have a unique identifying suspension that could be
1252easily referred to, because on every re-suspend a new suspension is created.
1253
1254To better support this type of goals, {\eclipse} provides a special type
1255of predicate, called a \defnotion{demon}. A predicate is turned into a
1256demon by annotating it with a
1257\bipref{demon/1}{../bips/kernel/compiler/demon-1.html}
1258declaration.
1259A demon goal differs from a normal goal only in its behaviour on
1260waking. While a normal goal disappears from the resolvent when it is
1261woken, the demon remains in the resolvent.
1262Declaratively, this corresponds to an implicit recursive call in
1263the body of each demon clause.
1264Or, in other words, the demon goal forks into one goal that remains in the
1265suspended part of the resolvent, and an identical one
1266that gets scheduled for execution.
1267
1268With this functionality, our above example can be done more
1269efficiently. One complication arises, however. Since the goal
1270implicitly re-suspends, it now has to be explicitly killed when
1271it is no longer needed. The easiest way to achieve this is to
1272let it remember its own suspension in one of its arguments.
1273This can then be used to kill the suspension when required:
1274\begin{quote}
1275\begin{verbatim}
1276% A demon that wakes whenever X becomes more constrained
1277report(X) :-
1278      suspend(report(X, Susp), 1, X->constrained, Susp).
1279
1280:- demon(report/2).
1281report(X, Susp) :-
1282      ( var(X) ->
1283          writeln(constrained(X))   % implicitly re-suspend
1284      ;
1285          writeln(instantiated(X)),
1286          kill_suspension(Susp)     % remove from the resolvent
1287      ).
1288\end{verbatim}
1289\end{quote}
1290
1291
1292%-------
1293\section{More about Priorities}
1294%-------
1295For the scheduled goals,
1296\eclipse\ uses an execution model which is based on goal priorities
1297and which guarantees that a scheduled goal with a higher priority
1298will be always executed before any goal with lower priority.
1299Priority is a small integer number ranging from 1 to 12,
13001 being the highest priority and 12 the lowest
1301(cf.\ figure~\ref{figresolv}).
1302Each goal which is being executed is executed under a current priority.
1303The priority of the currently executing goal can be determined
1304with \bipref{get_priority/1}{../bips/kernel/suspensions/get_priority-1.html}.
1305This priority is
1306\begin{itemize}
1307\item normally inherited from the caller
1308\item implicitly set to the goal's run_priority during waking
1309\item explicitly set using \biptxtref{call_priority(\pattern{Goal},~\pattern{Prio})}{call_priority/2}{../bips/kernel/suspensions/call_priority-2.html}
1310\end{itemize}
1311All goals started from the \eclipse\ top-level loop
1312or from the command line with the \notation{-e} option have priority 12.
1313
1314Priority-based execution is driven by a scheduler:
1315it picks up the scheduled suspension with the highest scheduling priority.
1316If its scheduling priority is higher than the priority of the currently
1317executing goal, then the execution of the current goal
1318is interrupted and the new suspension is executed under its run_priority
1319(which may be higher than the scheduling priority).
1320This is repeated until there are no suspensions
1321with priority higher than that of the current goal.
1322
1323Note that suspensions have two distinct priorities attached: the scheduling
1324priority determining the order of execution, and the run_priority determining
1325the atomicity of execution.
1326
1327
1328\subsection{Changing Priority Explicitly}
1329It is also possible to execute a goal with a given priority
1330by means of
1331\biptxtref{call_priority(\pattern{Goal},~\pattern{Prio})}{call_priority/2}{../bips/kernel/suspensions/call_priority-2.html}
1332which calls \about{Goal} with the priority \about{Prio}.
1333When a goal is called this way with high priority, it is effectively
1334made atomic, i.e., it will not be interrupted by goals with lower priority
1335that wake up while it executes.
1336Those goals will all be deferred until exit from
1337\bipref{call_priority/2}{../bips/kernel/suspensions/call_priority-2.html}.
1338This technique can sometimes improve efficiency.
1339Consider for example the following program:
1340\begin{quote}
1341\begin{verbatim}
1342p(1).
1343report(Term) :-
1344    writeln(term=Term),
1345    suspend(report(Term),3,Term->inst).
1346\end{verbatim}
1347\end{quote}
1348and the execution
1349\begin{quote}
1350\begin{verbatim}
1351[eclipse 2]: report(f(X,Y,Z)), p(X),p(Y),p(Z).
1352term = f(X, Y, Z)
1353term = f(1, Y, Z)
1354term = f(1, 1, Z)
1355term = f(1, 1, 1)
1356\end{verbatim}
1357\end{quote}
1358\predspec{report/1} is woken and executed three times, once for each variable
1359binding.
1360If instead we do the three bindings under high priority, it will only
1361execute once after all bindings have already been done:
1362\begin{quote}
1363\begin{verbatim}
1364[eclipse 3]: report(f(X,Y,Z)), call_priority((p(X),p(Y),p(Z)), 2).
1365term = f(X, Y, Z)
1366term = f(1, 1, 1)
1367\end{verbatim}
1368\end{quote}
1369
1370Note that woken goals are automatically executed under their run_priority
1371(default 2), which usually make the use of
1372\biptxtref{call_priority(\pattern{Goal},~\pattern{Prio})}{call_priority/2}{../bips/kernel/suspensions/call_priority-2.html}
1373unnecessary.
1374
1375
1376\subsection{Choice of Priorities}
1377Although the programmer is more or less free to specify
1378which priorities to use, we strongly recommend
1379to stick to the following scheme (from urgent to less urgent):
1380\begin{quote}
1381\begin{description}
1382\item [debugging (1)]  goals which don't contribute to the semantics
1383of the program and always succeed, e.g., display routines, consistency
1384checks or data breakpoints.
1385
1386\item [immediate]  goals which should be woken immediately
1387and which do not do any bindings or other updates.
1388Examples are quick tests which can immediately fail and
1389thus avoid redundant execution.
1390
1391\item [quick]  fast deterministic goals which may
1392propagate changes to other variables.
1393
1394\item [normal]  deterministic goals which should be woken
1395after the \notation{quick} class.
1396
1397\item [slow]  deterministic goals which require
1398a lot of processing, e.g., complicated disjunctive
1399constraints.
1400
1401\item [delayed]  nondeterministic goals
1402or goals which are extremely slow.
1403
1404\item [toplevel goal (12)]  the default priority of the user program.
1405\end{description}
1406\end{quote}
1407
1408
1409
1410
1411% %-------
1412% \section{Syntax}
1413% %-------
1414% There is no syntax for suspension, which means that by default
1415% they cannot be written out and read in. If it is necessary to do so,
1416% there are two possibilities: since suspensions can be stored in the
1417% BANG database, the database conversion predicates
1418% \bipref{term_to_bytes/2}{../bips/kernel/termmanip/term_to_bytes-2.html}
1419% and \bipref{bytes_to_term/2}{../bips/kernel/termmanip/bytes_to_term-2.html}
1420% (exported in {\bf sepia_kernel})
1421% can be used to convert the suspension to a string and back:
1422% \begin{quote}
1423% \begin{verbatim}
1424% [eclipse 9]: [user].
1425%  :- import sepia_kernel.
1426%
1427%  write_susp(Susp, File) :-
1428%     term_to_bytes(Susp, B),
1429%     open(File, write, M),
1430%     printf(M, "%QDvMTw.%n", [B]),
1431%     close(M).
1432%
1433% read_from(Susp, File) :-
1434%     open(File, read, M),
1435%     read(M, B),
1436%     bytes_to_term(B, Susp).
1437% user       compiled traceable 460 bytes in 0.00 seconds
1438%
1439% yes.
1440% [eclipse 10]: make_suspension(true, 2, S), write_susp(S, ss).
1441%
1442% S = 'GOAL'(true, eclipse)
1443%
1444% Delayed goals:
1445%       true
1446% yes.
1447% [eclipse 11]: read_from(S, ss).
1448%
1449% S = 'GOAL'(true, eclipse)
1450%
1451% Delayed goals:
1452%       true
1453% yes.
1454% \end{verbatim}
1455% \end{quote}
1456%
1457% The other possibility is to use a read macro to transform
1458% an input term to a suspension.
1459% For example, suppose we want to denote suspension by
1460% \latex{
1461% ${\bf <Goal, Priority>}$:
1462% }
1463% \html{
1464% {\bf <Goal, Priority>}:
1465% }
1466% \begin{quote}
1467% \begin{verbatim}
1468% [eclipse 9]: [user].
1469%  :- import make_suspension/4 from sepia_kernel.
1470% :- op(1090, fx, <).
1471% :- op(1100, xf, >).
1472%
1473% tr_susp(no_macro_expansion((<Goal, Prio>)), Susp, Module) :-
1474%     make_suspension(Goal, Prio, Susp, Module).
1475%
1476% :- define_macro((>)/1, tr_susp/3, []).
1477% :- set_error_handler(129, true/0).    % otherwise transformation flounders
1478%    user       compiled traceable 176 bytes in 0.42 seconds
1479%
1480% yes.
1481% [eclipse 10]: read(X).
1482%       <true, 2> .
1483%
1484% X = 'GOAL'(true, eclipse)
1485%
1486% Delayed goals:
1487%       true
1488% yes.
1489% \end{verbatim}
1490% \end{quote}
1491%
1492%
1493
1494
1495
1496%----------------------------------------------------------------------
1497\section{Details of the Execution Mechanism}
1498%----------------------------------------------------------------------
1499
1500%----------
1501\subsection{Particularities of Waking by Unification}
1502%----------
1503\index{waking}
1504Goals that are suspended on the \notation{inst} or \notation{bound} waking
1505conditions are woken by unifications of their
1506\defnotion{suspending variables}.
1507One suspending variable can be responsible for delaying several goals,
1508on the other hand one goal can be suspended on several
1509suspending variables (as alternative waking conditions).
1510This means that when one suspending variable is bound,
1511several delayed goals may be woken at once.
1512The order of executing woken suspended goals does not necessarily correspond
1513to the order of their suspending. It is in fact determined by their
1514priorities and is implementation-dependent within the same priority group.
1515
1516The waking process never interrupts unifications and/or a sequence
1517of simple goals.
1518\index{simple goals}
1519Simple goals are a subset of the built-ins and
1520can be recognised by their \notation{call_type}
1521flag as returned by
1522\bipref{get_flag/3}{../bips/kernel/compiler/get_flag-3.html},
1523simple goals having the type \notation{external}.
1524Note also that some predicates, e.g.,
1525\bipref{is/2}{../bips/kernel/arithmetic/is-2.html},
1526are normally in-line expanded and thus simple, but can be regular when
1527inlining is suppressed, e.g., by the \notation{pragma(noexpand)} directive.
1528
1529{\eclipse} treats simple predicates (including unification) always as a block.
1530Delayed goals are therefore woken only at the end of a successful
1531unification and/or a sequence of simple goals.
1532If a suspending variable is bound in a simple goal, the suspended
1533goals are woken only at the end of the last consecutive simple
1534goal or at the clause end.
1535If the clause contains simple goals at the beginning of its
1536body, they are considered part of the head (\defnotion{extended head})
1537and if a suspending variable is bound in the head unification or
1538in a simple predicate in the extended head, the corresponding
1539delayed goals are woken at the end of the extended head.
1540
1541A
1542\txtbiprefni{cut}{!/0}{../bips/kernel/control/I-0.html}\index{cut}\indextt{!/0}
1543is also considered a simple goal and is therefore
1544always executed \emph{before} waking any pending suspended goals.
1545This is important to know especially in the situations where the cut
1546acts like a guard, immediately after the clause neck or after
1547a sequence of simple goals.
1548If the goals woken by the head unification or by the extended head
1549are considered as constraints on the suspending variables,
1550the procedure will not behave as expected.
1551For example
1552\begin{quote}
1553\begin{verbatim}
1554filter(_P,[],[]) :- !.
1555filter(P,[N|LI],[N|NLI]) :-
1556        N mod P =\= 0,
1557        !,
1558        filter(P,LI,NLI).
1559filter(P,[N|LI],NLI) :-
1560        filter(P,LI,NLI).
1561
1562delay integers(_, List) if var(List).
1563integers(_, []).
1564integers(N, [N|Rest]) :-
1565        N1 is N + 1,
1566        integers(N1, Rest).
1567
1568?- integers(2, Ints), filter(2, Ints, [X1,X2]).
1569\end{verbatim}
1570\end{quote}
1571The idea here is that \predspec{integers/2} fills a list with integers on
1572demand,
1573i.e., whenever new list elements appear.
1574The predicated {filter/3} removes all integers that are a multiple
1575of \about{P}. In the example query, the call to \predspec{integers/2} initially
1576delays.
1577When \predspec{filter/3} is called, Ints gets instantiated in the head
1578unification
1579of the second clause of \predspec{filter/3}, which will wake up
1580\predspec{integers/2}. However,
1581since the second clause of \predspec{filter/3} has an extended head which
1582extends up to
1583the cut, \predspec{integers/2} will not actually be executed until after the
1584cut.
1585Therefore, \about{N} is not yet instantiated at the time of the arithmetic test
1586and causes an error message.
1587
1588The reason why delayed goals are woken \emph{after} the cut and not before
1589it is that neither of the two possibilities is always the intended
1590or the correct one, however when goals are woken \emph{before} the cut,
1591there is no way to escape it and wake them after, and so if
1592a nondeterministic goal is woken, it is committed by this cut
1593which was most probably not intended.
1594On the other hand, it is always possible to force waking before the cut
1595by inserting a regular goal before it, for example
1596\bipref{true/0}{../bips/kernel/control/true-0.html},
1597so the sequence
1598\begin{quote}
1599\notation{true, !}
1600\end{quote}
1601can be viewed as a special cut type.
1602
1603As a consequence, the example can be fixed by inserting \notation{true} at the
1604beginning of the second clause.
1605However, a preferable and more robust way is using the if-then-else
1606construct, which always forces waking suspended goals before
1607executing the condition.
1608This would also be more efficient by avoiding the creation of a choice point:
1609\begin{quote}
1610\begin{verbatim}
1611filter(_P,[],[]).
1612filter(P,[N|LI],LL) :-
1613        (N mod P =\= 0 ->
1614                LL = [N|NLI],
1615                filter(P, LI, NLI)
1616        ;
1617                filter(P,LI,LL)
1618        ).
1619\end{verbatim}
1620\end{quote}
1621
1622
1623
1624%----------
1625\subsection{Cuts and Suspended Goals}
1626%----------
1627\label{delaycut}%
1628%It is important to mention here the influence of non-logical predicates,
1629%especially the
1630%on the execution of delayed goals.
1631The
1632\txtbiprefni{cut}{!/0}{../bips/kernel/control/I-0.html}\index{cut}\indextt{!/0}
1633relies on a fixed order of goal execution in that it discards
1634some choice points if all goals preceding it in the clause body have
1635succeeded.
1636If some of these goals delay without being woken before the cut,
1637or if the head unification of the
1638clause with the cut wakes any nondeterministic delayed goal,
1639the completeness of the resulting program is lost
1640and there is no clean way to save it as long as the cut is used.
1641%In a restricted class of procedures the system raises an exception
1642%to signal that there has been an interaction of cut with delayed
1643%goals, e.g., in the clause
1644%\begin{quote}\begin{verbatim}
1645%p(X) :- q(X), !, r(X)\end{verbatim}\end{quote}
1646%if the call to {\bf q/1} delays, the system raises an exception
1647%when the cut is executed.
1648
1649\index{cut warnings}
1650The user is strongly discouraged to use non-local cuts together with
1651coroutining, or to be precisely aware of their scope.
1652The danger of a cut is twofold:
1653\begin{itemize}
1654\item Delaying \emph{out of} the scope of a cut:
1655a cut can be executed after some calls preceding it in the clause
1656(or children of these calls) delay. When they are then woken later,
1657they may cause the whole execution to fail instead of just the
1658guard before the cut.
1659
1660\item Delaying \emph{into} the scope of a cut:
1661the head unification of a clause with cuts can wake delayed goals.
1662If they are nondeterministic, the cut in the body of the waking clause
1663will commit even the woken goals
1664\end{itemize}
1665
1666%In order to detect these situations, the {\eclipse} debugger has an option
1667%to print a warning whenever a cut in one of the above two conditions
1668%is executed. These warnings can be toggled using the {\bf P} command.
1669
1670
1671
1672%----------------------------------------------------------------------
1673\section{Simulating the Delay-Primitives of other Systems}
1674%----------------------------------------------------------------------
1675It is relatively easy to simulate similar constructs from other
1676systems by using delay clauses,
1677for example, MU-Prolog's sound negation predicate \predspecidx{\tld/1}
1678can be in {\eclipse} simply implemented as
1679\begin{quote}
1680\begin{verbatim}
1681delay ~ X if nonground(X).
1682~ X :- \+ X .
1683\end{verbatim}
1684\end{quote}
1685MU-Prolog's wait declarations can be in most cases
1686simulated using delay clauses.
1687Although it is not possible to convert all wait declarations
1688to delay clauses, in the real life examples
1689this can usually be achieved.
1690The block declarations of SICStus Prolog can be easily expressed
1691as delay clauses with \bipref{var/1}{../bips/kernel/typetest/var-1.html} and
1692\bipref{nonground/1}{../bips/kernel/typetest/nonground-1.html} conditions.
1693The \predspecidx{freeze/2} predicate (e.g., from SICStus Prolog, same as
1694\predspec{geler/2} in Prolog-II) can be expressed as
1695\begin{quote}
1696\begin{verbatim}
1697delay freeze(X, _) if var(X).
1698freeze(_, Goal) :- call(Goal).
1699\end{verbatim}
1700\end{quote}
1701The transcription of ``when declarations'' from NU-Prolog
1702basically involves negating them:
1703\index{when declarations}
1704for instance, the when declarations
1705\begin{quote}
1706\begin{verbatim}
1707?- flatten([], _) when ever.
1708?- flatten(A._, _) when A.
1709\end{verbatim}
1710\end{quote}
1711can be rewritten as
1712\begin{quote}
1713\begin{verbatim}
1714delay flatten(A, _) if var(A).
1715delay flatten([A|_], _) if var(A).
1716\end{verbatim}
1717\end{quote}
1718Note that in contrast to when declarations,
1719there are no syntactic restrictions on the head of a delay clause,
1720in particular, it can contain any compound terms and repeated variables.
1721In the clause body, a delay clause allows more flexibility by supporting
1722programming with (a subset of) built-ins.
1723In general, it is a matter of taste whether specifying delay-conditions
1724or execute-conditions is more straightforward.
1725However, the semantics of delay clauses is certainly more intuitive in
1726that missing delay clauses simply imply no delay, while missing
1727when-declarations imply a most general \notation{when ever} declaration.
1728
1729%HEVEA\cutend
1730