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                  ]).

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).

To be done
- I'm not happy with the state of this module (no pun intended... no wait a minute, that's a pretty good pun actually: the state representation is one of the problems). The use of an untagged union is not good, and the stuff trying to compute marginals doesn't really belong in a low level module like this. */
   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)).
 strand is det
Start a DCG shell (see dcgshell//0) with an empty store and the current state of the plrand random generator.
   42strand :- 
   43   context_module(M),
   44   strand:strand(strand:shell_in(M)).
   45
   46shell_in(M, S1, S2) :- @(dcgshell(strand, S1, S2), M).
 strand(+Cmd:dcg(strand)) is det
Run Cmd in a DCG where the state is of type strand = pair(store,plrand:state).
   50strand(Cmd) :- with_rnd_state(strand(Cmd)).
 strand(+Cmd:dcg(strand), +RS1:plrand:state, -RS2:plrand:state) is det
Run Cmd in a DCG where the state is of type strand = pair(store,plrand:state), taking and returning initial and final states of plrand generator.
   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,_).
 pure(+Dist:tagged_dist(A), -X:A, +S1:pair(store,number), -S2:pair(store,number)) is det
pure(+Dist:tagged_dist(A), -X:A, +S1:pair(store,rndstate), -S2:pair(store,rndstate)) is det
Samples or gets probability of value X with tagged distribution Dist. NB: 2nd half of DCG state type is an UNTAGGED union of numbers (probabilities) and random states.
   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)