1:- module(strand, [ strand/0
2 , strand/1
3 , strand//1
4 , clear//0
5 , hold_store//1
6 , pure//2
7 , pure1//2
8 , marginal_prob//2
9 , marginal_prob//3
10 ]).
23:- meta_predicate strand(//), strand(//,+,-)
24 , hold_store(//,?,?)
25 , pure(3,-,+,-)
. 27
28:- module_transparent strand/0. 29
30:- use_module(library(plrand)). 31:- use_module(library(dcg_shell)). 32:- use_module(library(dcg_core)). 33:- use_module(library(dcg_pair)). 34:- use_module(library(callutils)). 35:- use_module(library(data/store)).
42strand :-
43 context_module(M),
44 strand:strand(strand:shell_in(M)).
45
46shell_in(M, S1, S2) :- @(dcgshell(strand, S1, S2), M).
50strand(Cmd) :- with_rnd_state(strand(Cmd)).
55strand(Cmd) --> {store_new(H0)}, run_left(Cmd,H0,_).
56
57%% clear// is det.
58% Clear everything out of the store. Runs in strand DCG.
59clear --> \< set_with(store_new).
60
61%% hold_store(+Cmd:dcg(strand))// is det.
62% Runs Cmd leaving the store unchanged.
63hold_store(Cmd) --> \< get(H), \> run_left(Cmd,H,_).
69pure(Base,X,H-P1,H-P2) :- number(P1), !, call(Base,X,p(P1),p(P2)).
70pure(Base,X,H-S1,H-S2) :- call(Base,X,rs(S1),rs(S2)).
71
72:- meta_predicate pure1(3,?,?,?). 73pure1(Dist, X) --> \> call(Dist,X).
74
75:- meta_predicate marginal_prob(//,-,+,-). 76:- meta_predicate marginal_prob(3,?,-,+,-). 77marginal_prob(G,Prob,S1-P1,S1-P1) :-
78 aggregate(sum(P), S2^call_dcg(G, S1-p(1), S2-p(P)), Prob).
79
80marginal_prob(G,X,Prob,S1-P1,S1-P1) :-
81 aggregate(sum(P), S2^call(G, X, S1-p(1), S2-p(P)), Prob)
Stateful random generation DCG
This module provides tools for working in a sort of random generator plus store of mutable references monad (using DCG lanugage to manage state threading).