1:- module(clambda, [run_lambda_compiler/1, clambda/2]).
3:- use_module(library(delimcc), [p_reset/3, p_shift/2]). 4
5clambda(Lambda, Pred) :- p_shift(clambda, compile(Lambda,Pred)).
6
7:- meta_predicate run_lambda_compiler(0). 8run_lambda_compiler(Goal) :- run(Goal, []).
9run(Goal,Used) :- p_reset(clambda, Goal, Status), cont(Status, Used).
10
11cont(done,Used) :- maplist(retractall, Used).
12cont(susp(compile(lambda(Args, Body), clambda:dpred(I)), Cont), Used) :-
13 flag(clambda, I, I+1), Head =.. [dpred, I|Args],
14 assert(Head :- Body), run(Cont, [Head | Used]).
15
20
Compiled lambdas */