1/*
    2Probabilistic context-free grammar. The grammar is left-recursive, MCINTYRE
    3is necessary to ensure termination.
    4Grammar:
    50.4:S->SS
    60.3:S->a
    70.3:S->b
    8From
    9 Taisuke Sato and Keiichi Kubota. Viterbi training in PRISM. 
   10Theory and Practice of Logic Programming,  doi:10.1017/S1471068413000677. 
   11*/
   12:- use_module(library(mcintyre)).   13
   14:- if(current_predicate(use_rendering/1)).   15:- use_rendering(c3).   16:- endif.   17
   18:- mc.   19
   20:- begin_lpad.   21% pcfg(LT): LT is string of terminals accepted by the grammar
   22% pcfg(L,LT,LT0) L is a string of terminals and not terminals that derives
   23% the list of terminals in LT-LT0
   24
   25pcfg(L):- pcfg(['S'],[],_Der,L,[]).
   26% L is accepted if it can be derived from the start symbol S and an empty
   27% string of previous terminals
   28
   29pcfg([A|R],Der0,Der,L0,L2):-
   30  rule(A,Der0,RHS),
   31  pcfg(RHS,[rule(A,RHS)|Der0],Der1,L0,L1),
   32  pcfg(R,Der1,Der,L1,L2).
   33% if there is a rule for A (i.e. it is a non-terminal), expand A using the rule
   34% and continue with the rest of the list
   35
   36pcfg([A|R],Der0,Der,[A|L1],L2):-
   37  \+ rule(A,_,_),
   38  pcfg(R,Der0,Der,L1,L2).
   39% if A is a terminal, move it to the output string
   40
   41pcfg([],Der,Der,L,L).
   42% there are no more symbols to expand
   43
   44rule('S',Der,['S','S']):0.4; rule('S',Der,[a]):0.3; 
   45  rule('S',Der,[b]):0.3.
   46
   47% encodes the three rules of the grammar
   48
   49:- end_lpad.

?- mc_prob(pcfg([a]),Prob). % expected result ~ 0.2986666666666667.

?- mc_prob(pcfg([b]),Prob). % expected result ~ 0.2976666666666667.

?- mc_prob(pcfg([a,a]),Prob). % expected result ~ 0.035666666666666666.

?- mc_prob(pcfg([b,b]),Prob). % expected result ~ 0.036833333333333336.

?- mc_prob(pcfg([a,b]),Prob). % expected result ~ 0.035833333333333335.

?- mc_prob(pcfg([a,b,a]),Prob). % expected result ~ 0.009.

?- mc_sample(pcfg([a,a]),1000,Prob,[successes(T),failures(F)]). % take 1000 samples of pcfg([a,a])

?- mc_sample(pcfg([a,a]),1000,Prob),bar(Prob,C). % take 1000 samples of pcfg([a,a])

?- mc_sample_arg(pcfg(S),20,S,Values). % take 20 samples of S in % findall(S,pcfg(S),L)

?- mc_sample_arg(pcfg(L),20,L,Values),argbar(Values,C). % take 20 samples of S in % findall(S,pcfg(S),L)

*/