Hi Kuniaki,
Yes indeed, managing state is another good application of delimited
continuations. A few comments below..
> On 7 Sep 2018, at 13:21, Kuniaki Mukai <
kuniak...@gmail.com> wrote:
>
> % ?- continue(test([a, a, b, b, c, c], R), []).
>
> %@ catch_ball(update(a,1),[],[a-2])
> %@ catch_ball(update(a,2),[a-2],[a-3])
> %@ catch_ball(update(b,1),[a-3],[b-2,a-3])
> %@ catch_ball(update(b,2),[b-2,a-3],[b-3,a-3])
> %@ catch_ball(update(c,1),[b-3,a-3],[c-2,b-3,a-3])
> %@ catch_ball(update(c,2),[c-2,b-3,a-3],[c-3,b-3,a-3])
> %@ catch_ball(update(c,3),[c-3,b-3,a-3],[c-4,b-3,a-3])
> %@ R = [1, 2, 1, 2, 1, 2] .
>
> test([], []):-!.
> test([A|As], [X|Bs]):- shift(update(A, X)),
> test(As, Bs).
>
> %
> continue(true, _).
> continue(0, _).
> continue(Cont, S):- reset(Cont, Ball, Cont0),
> catch_ball(Ball, S, S0),
> writeln(catch_ball(Ball, S, S0)),
> continue(Cont0, S0).
This is another case where the defaulty interface to reset/3
has lead to a potential problem — here if Cont completes without
calling shift/1, then Cont0 is unified with 0 and Ball is left as
a variable. This means that catch_ball/3 is called with an unintended
mode, and by a quirk of its internal implementation, succeeds
unifying Ball with update(c,3) and applying the action ‘increment counter
c’, even though no such action was requested. It so happens that
the incorrect resulting S0 is discarded on calling continue(0, S0), so
it doesn’t matter, but if continue had been written to return the final state
S0 (ie like a real DCG) that final state would be wrong.
Let’s re-write it using reset/2 from delimcc. First, the effect:
% effect is 'get and increment named counter’, like a++ in C.
get_and_inc(A, X) :- shift(get_and_inc(A, X)).
Now the handler:
:- use_module(library(delimcc)).
run_multi_counter(G, S) :- reset(G, Status), continue(Status, S).
continue(done, _).
continue(susp(get_and_inc(Nm, Val), Cont), S1) :-
(select(Nm-Val, S1, S2) -> true; Val=1, S1=S2),
succ(Val, NewVal),
run_multi_counter(Cont, [Nm-NewVal|S2]).
In continue/2, it is not possible to process Nm and Val unless
shift was called in the goal G. Finally, the test
?- run_multi_counter(maplist(get_and_inc,[a,a,b,b,c,c], R), []).
R = [1, 2, 1, 2, 1, 2].
This idea can be generalised into a handler of stateful computations
that allows any binary predicate to be applied to the state and that
also returns the final state, just like phrase/3 or call_dcg/3. The handler
itself can be written very neatly in DCG notation:
app(P) :- shift(app(P)). % should apply P with state, as in call(P,S1,S2).
run_state(G) —> {reset(G, Status)}, continue(Status).
continue(done) —> [].
continue(susp(app(P), Cont)) —> call_dcg(P), run_state(Cont).
Using app/1, we can define a typical set of state manipulating predicates:
get(S, S, S). put(S, _, S). % orinary predicates
get(S) :- app(get(S)). put(S) :- app(put(S)). % effectful, must be used inside run_state//1
app_and_get(P, S) :- app(P), get(S).
?- run_state(maplist(app_and_get, [succ, succ, put(10), plus(-1)], States), 0, Final).
States = [1, 2, 10, 9],
Final = 9.
You can build a multi-state handler on top of this without worrying about shift
and reset any more, eg using rbtrees instead of lists, for faster access when there
are many accumulators (but probably slower for just a few):
:- use_module(library(rbutils), [rb_app/3, rb_add/4]) % in pack genutils
app(Nm, P) :- app(rb_app(Nm, P)). % apply P to named accumulator
new(Nm, Val) :- app(rb_add(Nm, Val)). % add a new accumulator, fail if already exists.
run_multi_state(Goal) :- rb_empty(E), run_state(Goal, E, _).
Let’s use it to build a little sequence transducer that repeats each element twice.
repeat(_).
repeat(T) :- call(T), repeat(T).
transduce(Transducer, In, Out) :-
new(in, In), new(out, Out), % set up two accumulators
repeat(Transducer),
get(in, []), get(out, []). % unify final state of accumulators with [], like phrase/2
double :- app(in, [X]), app(out, [X,X]). % using DCG notation for action on in/out
?- run_multi_state(transduce(double, [1,2,3], Out)).
Out = [1, 1, 2, 2, 3, 3] .
cheers,
Samer
> %
> catch_ball(update(A, X), S, [A-X0|S0]):- select(A-X, S, S0),!,
> X0 is X+1.
> catch_ball(update(A, 1), S, [A-2|S]).
>