1:- module(delimcc, [reset/2, p_shift/2, p_reset/3, pr_shift/2, pr_reset/3, ccshell/0]).

Three alternative interfaces to delimited continuations

This module builds on the interface provided by reset/3 and shift/1 to provide higher level facilities, including multiple prompts (p_reset/3 and p_shift/2) and a more functional style shift operator with automatic reinstallation of the prompt in the signal handler with pr_reset/3.

reset/2 and p_reset/2 both return a value of type cont(A) to describe the status of the computation, where A is the type of the term that was thrown by shift/1 or p_shift/2. pr_reset/3 expects the shifted term to contain a handler predicate, which is invoked immediately with the continuation as a unary predicate and is expected to produce a result. Hence, pr_reset/3 never produces a cont(_) term.

cont(A) ---> done; susp(A,pred)
handler(A) == pred(pred(-A),-A).

None of these shift produce continuations that reinstall the control context that was created by the original reset. Hence, if the continuation is expecting to capture more continuations, it should be called inside another reset. pr_reset/3 does, however, resintall the context before calling the continuation handler, so the continuation can be called inside the handler, but if it is instead returned to the wider program context, the context should again be created before calling the continuation. There are other ways of handling the removal and replacing of contexts, as described by Shan (2004).

[1] Chung-chieh Shan. Shift to control. In Proceedings of the 5th workshop on Scheme and Functional Programming, pages 99–107, 2004. */

   33:- use_module(library(typedef)).   34:- use_module(library(lambdaki)).   35
   36:- set_prolog_flag(generate_debug_info, false).   37
   38:- type cont(A) ---> done; susp(A,pred).
   39
   40:- meta_predicate reset(0,-).
 reset(+G:pred, -C:cont(_)) is det
Calls goal G as in reset/3, but combines the result into a single algebraic data type cont(_).
   45reset(G,S) :- reset(G,B,C), continue(C,B,S).
   46
   47continue(0,_,done) :- !.
   48continue(Cont,Sig,susp(Sig,Cont)).
   49
   50% --------------------------------------------------
   51% Multiprompt control
 p_reset(Pr:prompt(A), P:pred, -C:cont(A)) is det
Execution context for catching shifts directed to the given prompt. If a p_shift/2 targets another prompt, the signal is passed up, taking care to reinstate this prompt inside the continuation that the outer reset will receive.
   60:- meta_predicate p_reset(+,0,-).   61
   62:- if((current_prolog_flag(version, VER), VER =< 70511)).   63
   64p_reset(Prompt, Goal, Result) :-
   65   reset(Goal, Ball, Cont),
   66   p_cont(Cont, Ball, Prompt, Result).
   67
   68p_cont(0, _, _, done) :- !.
   69p_cont(Cont, Prompt-Signal, Prompt, susp(Signal, Cont)) :- !.
   70p_cont(Cont, Prompt1-Signal1, Prompt, Result) :-
   71   shift(Prompt1-Signal1),
   72   p_reset(Prompt, Cont, Result).
   73
   74:- else.   75
   76p_reset(Prompt, Goal, Result) :-
   77   reset(Goal, Prompt-Signal, Cont),
   78   (Cont==0 -> Result=done; Result=susp(Signal, Cont)).
   79
   80:- endif.
 p_shift(Pr:prompt(A), S:A) is det
Send the term S to the inner-most p_reset/3 with a matching prompt.
   84p_shift(Prompt, Signal) :- shift(Prompt-Signal).
   85
   86% ---------------------------------------------------
   87% Functional style multiprompt
   88
   89:- type handler(A) == pred(pred(-A),-A).
 pr_reset(+Pr:prompt(handler(A)), +P:pred(-A), -X:A) is det
Call generative unary predicate P in a context delimited by the given prompt. The value produced by P is returned in X. If pr_shift/2 is used inside P, the continuation is captured as a unary predicate that would have produced the result X, and passed to the binary handler predicate given to pr_shift/2, which should then return the final return value X. The prompt is reinstated before calling the handler.
   99:- meta_predicate pr_reset(+,1,-).  100pr_reset(Prompt, Pred, Result) :-
  101   p_reset(Prompt, call(Pred, X), Status),
  102   pr_cont(Status, Prompt, X, Result).
 pr_cont(+S:cont(handler(A)), +Pr:prompt(handler(A)), X:A, Y:A)
  105pr_cont(done, _, X, X).
  106pr_cont(susp(Handler, K), Prompt, X, Result) :-
  107   pr_reset(Prompt, call(Handler, delimcc:pr_reset(Prompt, \X^K)), Result).
 pr_shift(Pr:prompt(handler(A)), +H:handler(A)) is det
Send the given continuation handler to the innermost reset with a matching prompt. The handler will be called immediately with the captured continuation as a unary predicate. The handler will be called with the prompt reinstated around it. The continuation does not install the prompt.
  116:- meta_predicate pr_shift(+,2).  117pr_shift(Prompt, Handler) :- shift(Prompt-Handler).
  118
  119:- module_transparent ccshell/0.  120ccshell :-
  121   '$toplevel':read_expanded_query(1, Query, Bindings),
  122   (   Query == end_of_file
  123   ->  print_message(query, query(eof))
  124   ;   '$toplevel':'$execute'(Query, Bindings),
  125		 ccshell
  126   )