1:- module(ccp_effects, [ ccstore/2, ccstored/1, cctabled/2, uniform/2, dist/2, dist/3, (:=)/2, sample/2, factor/1 ]).
5:- use_module(library(listutils), [zip/3]). 6:- use_module(library(delimcc), [p_shift/2]). 7 8:- meta_predicate :=( , ), ccstore( , ), ccstored( ), cctabled( , ), sample( , ).
14dist(Dist,X) :- zip(Ps,Xs,Dist), p_shift(prob,dist(Ps,Xs,X)). 15dist(Ps,Xs,X) :- p_shift(prob,dist(Ps,Xs,X)).
19uniform(Xs,X) :- p_shift(prob,uniform(Xs,X)).
24sample(P,X) :- p_shift(prob,sample(P,X)).
switch(A) == pred(-switch(A), -X1:list(A), X2:list(A))
such that call(SW,ID,X1,X2)
unifies ID with a canonical callable form of the
switch and X1-X2 with a difference list of the switch's possible value.
33SW := X :- p_shift(prob,sw(SW,X)). 34 35% arbitrary factor 36factor(F) :- p_shift(prob, factor(F)).
ccprism/macros.pl
for an automatic program transformation to
manage tabled predicates.
42cctabled(Head,Work) :- p_shift(tab, tcall(Head,Work,Inj)), call(Inj).
once(Work)
is stored under the variant form Head.
Thus, Work is expected to bind the variables in Head which represent the
result of the tabled computation. Stored results should be retrieved using
ccstored/1, not cctabled/2.
50ccstore(Head,Work) :- copy_term(Head-Work,H-W), p_shift(tab, tcall(H,once(W),_)).
55ccstored(Head) :- p_shift(tab, tcall(Head,throw(not_stored(Head)),_))
Computational effects for supporting probabilistic models */