1:- module(ccnbref, [run_nb_ref/1, nbref_new/2, with_nbref/2, nbref_new/3,
2 nbref_app/2, nbref_get/2, nbref_add_with/3]).
6:- use_module(library(delimcc), [p_reset/3, p_shift/2]). 7
8:- meta_predicate nbref_app(+,2), nbref_add_with(+,3,+), run_nb_ref(0), with_nbref(-,0).
13run_nb_ref(Goal) :- with_nbref(E, run(Goal, E)).
14
15run(Goal, E) :- p_reset(nbref, Goal, Status), cont(Status, E).
16cont(susp(X-Ref,Cont), E) :- nbref_new(E, X, Ref), run(Cont, E).
17cont(done, _).
22nbref_new(X, Ref) :- p_shift(nbref, X-Ref).
28with_nbref(E, Goal) :- setup_call_cleanup(setup(E), Goal, cleanup(E)).
29
30setup(E) :- gensym(nbref,ID), atom_concat(ID,'.',E), nb_setval(E, 0).
31cleanup(E) :- nb_getval(E, N), nb_delete(E), forall(between(1,N,I), delete(E,I)).
32delete(E,I) :- atomic_concat(E,I,Ref), nb_delete(Ref).
35nbref_new(E, Value, Ref) :-
36 nb_getval(E, I), J is I+1, atomic_concat(E, J, Ref),
37 nb_setval(Ref, Value), nb_setval(E,J).
40nbref_app(Ref, P) :- nb_getval(Ref, X1), call(P,X1,X2), nb_setval(Ref, X2).
43nbref_get(Ref, X) :- nb_getval(Ref, X).
51nbref_add_with(Ref,Pred,X) :-
52 duplicate_term(X,X1),
53 nb_getval(Ref, Y1), call(Pred,X1,Y1,Y2),
54 nb_linkval(Ref, Y2)
Context providing allocation and release of nb_ mutable variables
*/