Skip to content

Latest commit

 

History

History

about_continuations

Folders and files

NameName
Last commit message
Last commit date

parent directory

..
 
 
 
 
 
 
 
 
 
 

Delimited Continuations

This is additional material for the page Delimited Continuations of the SWI-Prolog manual.

TOC

Errata

The manual says:

Delimited continuation for Prolog is described in Schrijvers et al., 2013 (preprint PDF).

  • The link for "Schrijvers et al., 2013" just leads to the bibliography page where one is stranded because there are no live links to continue.
  • The link for "preprint PDF" leads to a preprint of the ISO Standardization effort for the C language. Shurely some mistake?

The correct link to the paper is:

The PDF says it has been written in 2003, but it has really been written in 2013. It's a preprint.

It has been published in Theory and Practice of Logic Programming in 2013.

Reading

Some Wikipedia entries

"Delimited continuations for Prolog" (2013)

As given in the SWI-Prolog manual.

From that paper:

Delimited continuations enable the definition of new high-level language features at the program level (e.g. in libraries) rather than at the meta-level as program transformations. As a consequence, feature extensions based on delimited continuations are more light-weight, more robust with respect to changes and do not require pervasive changes to existing code bases.

The publication page of that paper has a lot of live links to the the references.

"Delimited continuations in Prolog: semantics, use, and implementation in the WAM" (2013)

Technical Report. This is an excellent resource, IMHO better than the one above.

Abstract:

An implementation of a delimited continuations, known in the functional programming world, is shown in the context of the WAM, and more particular in hProlog. Three new predicates become available to the user: reset/3 and shift/1 for delimiting and capturing the continuation, and call continuation/1 for calling it. The underlying low-level built-ins and modifications to the system are described in detail. While these do not turn continuations into first-class Prolog citizens, their usefulness is shown in a series of examples. The idea behind this implementation can be adapted to other Prolog implementations. The constructs are compared with similar ones in BinProlog and Haskell. Their interaction with other parts of Prolog is discussed.

Section 7.6:

7.6 The Origin of Delimited Continuations

Felleisen introduced reset and shift (“prompt applications”) using the untyped lambda-calculus [The theory and practice of first-class prompts, 1988]. He defined the semantics via translation to a stack-machine, but did notprovide an actual implementation. One of his examples was a yield-mechanism on a tree. Felleisen already pointed out the relation of continuations to stream-programming, although he did not distinguish yield as a separate operator. Dubaet al. added first-class continuations to the statically typed ML language [Typing first-class continuations in ML, POPL '91].
Flattet al.implementeda production version in Scheme [Adding delimited and composable control to a production programming environment, 2007]

"Call with current continuation patterns" (2001)

The paper explores patterns in Scheme that employ call-with-current-continuation (aka. call/cc), not patterns in Prolog that use reset/shift but once one notices the relationship between call/cc and reset that becomes less important. Plus it provides an excellent intro.

Patterns explored:

  1. Loop
  2. Escape from recursion
  3. Loop via continuations
  4. Escape from and reentry into recursion
  5. Coroutines
  6. Non-blind backtracking
  7. Multitasking

In particular the chapter on Non-blind Backtracking on pages 20 ff. seems to apply to reset/shift operations:

In [FHK84: Friedman, Haynes, Kohlbecker: "Programming with Continuations" (In P. Pepper, editor, Program Transformation and Programming Environments), 1984.] the concept of devils, angels and milestones is presented.

A devil will return us to the context in which the last milestone was created. The devil will pass to the continuation the value that was passed to it. Now this value is used as if it were the result of the original milestone expression, possibly allowing us to follow a different path.

...sounds like shift.

An angel will send the computation forward to the last encounter with a devil. Again, the value passed to the angel will be given to the devil’s continuation allowing us to return to the context of the devil with this value replacing the value returned by the devil. This will allow us to move to more advanced states.

...sounds like calling the continuation obtained from a reset. Although we cannot pass a value "forwards" to the point where the shift occurred via the continuation obtained from reset, we can bind to some value an unbound variable communicated to the point of reset via the term shifted by shift.

A milestone will record the current context to be used by any encountered devils.

...sounds like reset.

As a metaphor, we can take the example given in the introduction of this pattern language. We begin by reading the first paper and we reach a point where we realize that we need further knowledge. We set a milestone (remembering where we were in this first paper) and begin reading the references and other material. When we feel that we have sufficient knowledge to continue with the original paper, we return to that paper (equivalent to invoking a devil). Possibly, we didn’t read all the references and other related material before we went back to this original paper. If this is the case, after finishing the original paper we decide to go back to reading the remaining references and other material. This is equivalent to invoking an angel.

"Abstracting Control" (1990)

This one introduces shift and reset operations but it's a very technical paper (I don't get it ... yet).

We read:

Shift abstracts the current context as an ordinary, composable procedure and reset delimits the scope of such a context. Shift also differs from escape by not duplicating the current continuation. (...) While the effects of these operators are very similar to operators control and prompt of [Felleisen 88: The Theory and Practice of First-Class Prompts], there is a significant semantical difference between shift/reset and control/prompt: the context abstracted by shift is determined statically by the program text, while control captures the context up to the nearest dynamically enclosing prompt. In general, this leads to different behavior.

Programming with continuations has appeared as an intriguing possibility offered by control operators such as Landin's J, Reynolds's escape, and call-with-current-continuation in Scheme. Such first-class continuations are more general than MacLisp's catch/throw mechanism and ML's exceptions since they allow a previous scope to be restored, just like applying a functional value reestablishes an earlier environment. First-class continuations have been investigated mainly as powerful, but unstructured devices requiring a deep intuition and operational skill [Friedman, Haynes, & Kohlbecker 84] [Haynes & Friedman 87]. However, some progress has been made towards a more declarative view of them, based on a category-theoretical duality between values and continuations [Filinski 89].

Ok, this needs more study.

"Capturing the Future by Replaying the Past - Functional Pearl" (2018)

Delimited continuations are the mother of all monads! So goes the slogan inspired by Filinski’s 1994 paper,which showed that delimited continuations can implement any monadic effect, letting the programmer usean effect as easily as if it was built into the language. It’s a shame that not many languages have delimited continuations. Luckily, exceptions and state are also the mother of all monads! In this Pearl, we show how to implement delimited continuations in terms of exceptions and state, a construction we call thermometer continuations. While traditional implementations of delimited continuations require some way of "capturing" an intermediate state of the computation, the insight of thermometer continuations is to reach this intermediate state by replaying the entire computation from the start, guiding it using a recording so that the same thing happens until the captured point. Along the way, we explain delimited continuations and monadic reflection, show how the Filinski construction lets thermometer continuations express any monadic effect, share an elegant special-case for nondeterminism, and discuss why our construction is not prevented by theoretical results that exceptions and state cannot macro-express continuations.

Similar ideas

Similarity of reset/shift to catch/throw

Note the similarity between exception handling and delimited continuations. This is not an accident:

  • catch(:Goal, +Catcher, :Recover) (catch/3) and
  • throw(+Exception) (throw/1)

vs

  • reset(:Goal, ?Ball, -Continuation) (reset/3) and
  • shift(+Ball) (shift/1)

Indeed, the exception handling operations are a specialization of the delimited continuation operations whereby the Recover goal is called if Goal calls shift/1 with an exception term. The Continuation is discarded.

Similarly, if the call stack contains several points where reset/3 was called (i.e. there are nested reset/3 calls) and the currently executing procedure calls shift/1 with a term T, then execution flow goes to the nearest reset/3 call point that has a unifying Ball - in the same way as as execution flow goes to the nearest catch/3 that unifies Catcher with E, where E is the term thrown by throw/1.

Relationship between call/cc and reset/3

The Scheme function call/cc is called with a "receiver" function that takes one continuation argument. call/cc invokes the receiver with the continuation which continues after call/cc. The receiver function is meant to call that continuation to "get out" of some nested computation.

The counterpart is reset(Goal, Ball, Continuation). It actually creates a continuation "behind the scenes" which can be retrieved and called by a shift/1 called from Goal (the argument to shift/1 just needs to match Ball to retrieve the appropriate continuation somewhere on the call stack). So unlike for call/cc the continuation at the call/cc point stays invisible. However, you get the continuation for the shift/1 point for free. With call/cc you have to pass through some hoops to obtain it.

Empirical research

The "continuation" term is a compound term

At least in the current implementation. If you run the following on a continuation Cont:

compound_name_arity(Cont,Name,Arity),
format("The continuation has name '~q' and ~d arguments ~q\n",[Name,Arity]).

you get:

The continuation has name 'call_continuation' and 1 arguments

which is why a valid continuation is guaranteed distinguishable from 0.

It is actually an atomic goal: a call to call_continuation/1 with 1 argument prefilled. That predicate is not documented but it evidently calls the continuation.

This is also why reset/3 can take both an atomic goal on the first round and a continuation returned by a previous reset/3.

Calling shift/1 is not like backtracking

It's just continuing with the "instruction stream" at another place. Variables that have been bound during the procedure called by reset/3 stay bound after a shift/1:

:- debug(changee).

changee :-
   debug(changee,"Changee says the variable is ~q",[N]),
   reset(changer(N),changed_it,_),
   debug(changee,"Changee now says the variable is ~q",[N]).
   
changer(N) :-
   N = foo,            % bind the passed N to 'foo'
   shift(changed_it).

And so:

?- changee.
% Changee says the variable is _10566
% Changee now says the variable is foo
true.

There is proper backtracking over the goal called by reset/3

See further below for more on this.

:- debug(multi).
 
multi :-   
   debug(multi,"Calling 'possible' through 'reset'",[]),
   reset(possible,mine,_),
   debug(multi,"Back in 'multi'",[]).
       
possible :-
   debug(multi,"In 'possible'",[]).
   
possible :-   
   debug(multi,"In alternate 'possible'",[]).

And so:

?- multi.
% Calling 'possible' through 'reset'
% In 'possible'
% Back in 'multi'
true ;
% In alternate 'possible'
% Back in 'multi'
true.

Bidirectional wormholes and the Byrd Box

For more on the Byrd Box model, see: About Byrd Box Model

If you align the Byrd Boxes of the predicate activation in the "master" (the coroutine that calls "reset/3") and the "slave" (the coroutine that calls "shift/1"), then you see that their ports are connected like this:

back and forth

  • If execution stream is at the "master" side, and it enters the call port of a reset/3 activation (with the latest continuation obtained), it will exit at the succ port of the of shift/1 at the "slave" side, but a "back connection" is established so that a backtracking execution stream at the "slave" side, entering the redo port at shift/1 will exit at the fail port of the reset/3 activation that called it at the "master" side.

  • If execution stream is at the "slave" side, and it enters the call port of a shift/1 activation, it will exit at the succ port of the of reset/3 activation that called it at the "master" side, but a "back connection" is established so that a backtracking execution stream at the "master" side, entering the redo port at reset/3 will exit at the fail port of the shift/1 activation that called it at the "slave" side.

This also means both master and slave will "advance" and "backtrack" at the same time. If the "slave" starts to backtrack, the execution stream will emerge from the fail port on "old reset calls" in the master. If the "master" starts to backtrack, the execution stream will emerge from the fail port on "old shift calls" in the slave. You cannot have an architecture where the "master" advances whereas the "slave" backtracks (I tried to write a failure-driven loop for the "slave", emitting results to the "master" via shift/1 at various points but that just didn't work - the backtracking "slave" would cause the execution stream to emerge from reset/3 calls left long behind in the "master" ... disconcerting!)

Here is code to test this behaviour. It ends badly!

start :-
   master(generator,'*').
   
% ---
% Master "loop". As it proceeds, its old activations with "short LocId"
% will be reactivated and appear in the output.
% ---

master(Cont,LocId) :-
   reset_surround(LocId,Cont,ContNext),
   (Cont==0 
    -> true                               % success w/o choicepoints of the generator; we are done
    ;  (atom_concat(LocId,'*',LocIdNext), % recursive call with new LocId, which is used for indentation
        master(ContNext,LocIdNext))).

% ---
% Failure-driven loop generating lists of length 3.
% It reactivates old master activations when backtracking into shift/1.
% ---

generator :-
   member(X0,[a0,a1]),   
   shift_surround([X0]),   
   member(X1,[b0,b1]),   
   shift_surround([X0,X1]),   
   member(X2,[c0,c1]),
   shift_surround([X0,X1,X2]),      
   format("generator is at the end~n",[]),
   fail.

% The second clause always succeeds!

generator :-   
   format("generator is in the second close, which always succeeds~n").
   
% ---   
% Helper surrounding master's reset/3, printing about what's going on
% ---

reset_surround(LocId,Cont,ContNext) :-
   format("~q master calls reset/3~n",[LocId]),
   (true;(format("~q master backtracks out of reset/3 (fail port)~n",[LocId]),fail)),
   reset(Cont,Shifted,ContNext),
   (true;(format("~q master backtracks into reset/3 (redo port)~n",[LocId]),fail)),
   format("~q master exits from reset/3, received ~q~n",[LocId,Shifted]).

% ---   
% Helper surrounding generators' shift/1, printing about what's going on
% ---

shift_surround(Solution) :-
   format("generator calls shift/1 with ~q~n",[Solution]),   
   (true;(format("generator backtracks of shift/1 (fail port) with ~q~n",[Solution]),fail)),
   shift(data(Solution)),
   (true;(format("generator backtracks into shift/1 (redo port) with ~q~n",[Solution]),fail)),   
   format("generator exits from shift/1 with ~q~n",[Solution]).

Running this, we see things like:

?- start.
* master calls reset/3
generator calls shift/1 with [a0]
* master exits from reset/3, received data([a0])
** master calls reset/3
generator exits from shift/1 with [a0]
generator calls shift/1 with [a0,b0]
** master exits from reset/3, received data([a0,b0])
*** master calls reset/3
generator exits from shift/1 with [a0,b0]
generator calls shift/1 with [a0,b0,c0]
*** master exits from reset/3, received data([a0,b0,c0])
**** master calls reset/3
generator exits from shift/1 with [a0,b0,c0]
generator is at the end
generator backtracks into shift/1 (redo port) with [a0,b0,c0]
**** master backtracks out of reset/3 (fail port)
*** master backtracks into reset/3 (redo port)     <--- 4 stars become 3!! back at an old activation!

The reset point behaves as a resource on the call stack

The reset point behaves as a resource: You can only emerge from it (via shift/1) once.

Here is a faulty program that calls the continuation instead of performing another reset/3 with the continuation. There are two "reset points" on the stack. The first call uses up one, the second call uses up the other. The third call has nowhere to go:

upper :-
   reset(middle,A,Cont),
   format("Back in upper with A = ~q\n",[A]),
   ((Cont == 0) -> true ; call(Cont)).

middle :-
   reset(lower([a,b,c,d]),A,Cont),
   format("Back in middle with A = ~q\n",[A]),
   ((Cont == 0) -> true ; call(Cont)).

lower([X|Xs]) :-
   format("Sending ~q\n",[X]),
   shift(X),
   format("Back in lower\n",[]),
   lower(Xs).

And so:

?- upper.
Sending a
Back in middle with A = a
Back in lower
Sending b
Back in upper with A = b
Back in lower
Sending c
ERROR: reset/3 `c' does not exist
ERROR: In:
ERROR:   [14] shift(c)
ERROR:   [13] lower([c,d]) at user://1:18

Illustrated, a bit informally (I have no real formal way to depict this):

reset points as resources

Or even more informally, the call stack:

reset points as resources call stack

This works for limited cases of course:

upper :-
   reset(middle,A,Cont),
   format("Back in upper with A = ~q\n",[A]),
   ((Cont == 0) -> true ; call(Cont)).

middle :-
   reset(lower([a,b,c,d]),A,Cont),
   format("Back in middle with A = ~q\n",[A]),
   ((Cont == 0) -> true ; call(Cont)).

lower([X|_Xs]) :-
   format("Sending ~q\n",[X]),
   shift(X),
   format("Back in lower\n",[]).

And so:

?- upper.
Sending a
Back in middle with A = a
Back in lower
Back in upper with A = _6052
true.

limited application

Correct switching using (tail) recursion to generate new reset points

To switch continually between two branches of the call stack (created at the first reset/3 call), you need to use recursion to perform new reset/3 calls:

go :- middle(lower([a,b])).
  
middle(Goal) :-
   reset(Goal,A,Cont),
   format("Back in middle with A = ~q\n",[A]),
   ((Cont == 0) -> true ; middle(Cont)).

lower([X|Xs]) :-
   format("Sending ~q\n",[X]),
   shift(X),
   format("Back in lower\n",[]),
   lower(Xs).

And thus:

?- go.
Sending a
Back in middle with A = a
Back in lower
Sending b
Back in middle with A = b
Back in lower
false.

Successfully switching between 2 branches on the stack

Correct switching using a "failure-driven loop" in the "lower" predicate

Alternatively, using backtracking (failure-driven loop) in lower/1. Note that backtracking into shift/1 means that we backtrack out of the corresponding reset/3!

go :- middle(0,lower([a,b])).

middle(Count,Goal) :-
   (true;(format("B/T out of reset with Count = ~d\n",[Count]),fail)),
   reset(Goal,A,Cont),
   format("Back in middle with A = ~q, Count = ~d\n",[A,Count]),
   CountP is Count+1,
   ((Cont == 0) -> true ; middle(CountP,Cont)).

lower(L) :-
   member(X,L),
   format("Sending ~q\n",[X]),
   shift(X),
   format("Back in lower\n",[]),
   fail.

And thus:

?- go.
Sending a
Back in middle with A = a, Count = 0
Back in lower
B/T out of reset with Count = 1
Sending b
Back in middle with A = b, Count = 0
Back in lower
B/T out of reset with Count = 1
B/T out of reset with Count = 0
false.

Weirdness: Using a failure-driven loop in the "upper" predicate

This one just backtracks over the goal called by reset/3. Here, we still emerge only once from a reset/3 - it's just that backtracking into reset/3 emerges from the preceding shift/1. This is actually amazing.

go :- middle(lower([a,b])).

middle(Goal) :-
   reset(Goal,A,Cont),                                 % Backtracking into this, we emerge from the shift
   format("Back in middle with A = ~q\n",[A]),
   ((Cont == 0) -> true ; fail).                       % Failure-driven loop if Cont \== 0

lower(L) :-
   format("Calling member\n"),
   member(X,L),    
   format("Sending ~q\n",[X]),
   (true;(format("B/T out of shift(~q)\n",[X]),fail)),
   shift(X),                                           % Called twice; brings us back to the reset/3 point
   format("Back in lower\n"),                          % Never reached
   fail.

And thus:

?- go.
Calling member
Sending a
Back in middle with A = a
B/T out of shift(a)
Sending b
Back in middle with A = b
B/T out of shift(b)
false.

Edge cases

There is nothing to do for the continuation of shift/1 itself:

?- reset(shift(mine),mine,C).
C = call_continuation([]).

?- reset(shift(mine),mine,C), call(C).
C = call_continuation([]).

The above brings about the idea that in case a predicate calls shift/1 on the last position, one could have reset/3 just yield 0 on the continuation parameter place instead of call_continuation([]) but this brings unknown complications for little gain: issue#788.

There is something to do if there is a true following the shift/1, namely, succeed:

?- reset((shift(mine),true),mine,C).
C = call_continuation(['$cont$'(<clause>(0x23a5510), 15, '<inactive>', user, 125, '<inactive>', true)]).

?- reset((shift(mine),true),mine,C), call(C).
C = call_continuation(['$cont$'(<clause>(0x23a5510), 15, '<inactive>', user, 125, '<inactive>', true)]).

There is something to do if there is a false following the shift/1, namely, fail:

?- reset((shift(mine),false),mine,C).
C = call_continuation(['$cont$'(<clause>(0x23a5510), 15, '<inactive>', user, 125, '<inactive>', false)]).

?- reset((shift(mine),false),mine,C), call(C).
false.

Examples

Hands-on testing

  • jumping_around.pl: jumping around between reset/3 points on the call stack by emitting the appropriate shift/1 calls.
  • trial.pl: The predicate-to-call takes a list, the elements of which are then "generated" (i.e. emitted) one-by-one by an "iterator" and printed to stdout by the with_write/1 "master". However, certain elements make the from_list/1 goal behave in unruly ways. Basically tests what happens at the reset/3 point.

Simple patterns

  • looping.pl: in an unexiting development, we can build a loop that calls reset/3 to activate a loop-worker-predicate on each loop passage instead of just calling the predicate. directly. To make things more interesting, we can store the continuations of loop-worker-predicate obtained from reset/3 and call them for finalization at the end.
  • appender_observer.pl: an appender-observer pair communicating via an open list.
  • producer_consumer_master.pl: a producer-consumer (coroutine) example with a central "master" that dishes out the reset/3 calls. There seems no way to make the producer and consumer subroutines look symmetric using reset/shift and not having a "master" makes the code and unholy mess, so ... we have a "master"!

Iterator inspired by Schrijvers et al., 2013

  • iterator: An implementation of "iterators" (which are apparently "generators", which are "semi-coroutines") that generate output on behalf of a "master predicate". The "master predicate" sends the output to a user-selectable destination (in this case, stdout).

Effect handler inspired by Schrijvers et al., 2013

  • effect handler: An implementation of an "effect handler" (state handler?) keeping track of state on behalf of client code. State (now behind the curtain) is accessed by get/set commands which are terms passed to shift/1. This comes with two examples: a Markov Network visitor and a counter-to-zero. This works only for a single "thread" of client code. Once you have producer/consumer coroutines accessing the same state, the "get" no longer works and you need to use global variables or something similar.

Adapting the patterns from "Call with current continuation patterns"

As said earlier, the paper

explores patterns in Scheme that employ call-with-current-continuation (aka. call/cc), not patterns in Prolog that use reset/shift.

Let's try to recode them!

  • Loop
  • Escape from recursion (TBD)
  • Loop via continuations (TBD)
  • Escape from and reentry into recursion (TBD)
  • Coroutines (TBD)
  • Non-blind backtracking (TBD)
  • Multitasking (TBD)