1:- module(ccp_macros, [op(1150,fx,cctable), op(1200,xfx,+->), head_worker/2]).
11:- op(1150,fx,cctable).
17foldl_clist(P,(A,B)) --> !, call(P,A), foldl_clist(P,B).
18foldl_clist(P,A) --> call(P,A).
19
20head_worker(Head, Worker) :-
21 Head =.. [H|As], atom_concat(H,'#',W),
22 Worker =.. [W|As].
23
24decl(F//A) --> !, {A2 is A+2}, decl(F/A2).
25decl(F/A) -->
26 { functor(Head, F, A), head_worker(Head, Work)},
27 [ (:- discontiguous('$cctabled'/2))
28 , '$cctabled'(F, A)
29 , (Head :- cctabled(Head,Work))
30 ].
31
32rename_tabled(Extra, Head, Work) :-
33 prolog_load_context(module, M),
34 current_predicate(M:'$cctabled'/2),
35 functor(Head, F, A), A2 is A+Extra,
36 M:'$cctabled'(F,A2),
37 head_worker(Head, Work).
38
39expand((:- cctable(Specs)), Clauses) :- !, foldl_clist(decl, Specs, Clauses, []).
40expand((Head, P --> Body), (Head2, P --> Body)) :- !, rename_tabled(2, Head, Head2).
41expand((Head --> Body), (Head2 --> Body)) :- !, rename_tabled(2, Head, Head2).
42expand((Head :- Body), (Head2 :- Body)) :- !, rename_tabled(0, Head, Head2).
43expand(Head, Head2) :- rename_tabled(0, Head, Head2).
44
45system:term_expansion(T1, T2) :- expand(T1, T2).
46
55:- op(1200,xfx,+->). 56system:term_expansion(Lab +-> Body, Clause) :-
57 prolog_load_context(module,Module),
58 Lab =.. Args, append(Args, [Module:Lab], Args1),
59 Head =.. Args1, dcg_translate_rule(Head --> Body, Clause)
Term expansions to support tabling and switches
This module implements a shallow program transformation to support tabling. Predicates decalared
cctabled
are renamed (by a appending a '#' to their given name) and the original predicate name defined as a metacall of the renamed predicate via cctable/2, which is assumed to be available in the module where the tabled predicate is defined. */