1/*
    2Probabilistic context-free grammar implemented as a Stochastic Logic Program.
    3The grammar
    40.2:S->aS
    50.2:S->bS
    60.3:S->a
    70.3:S->b
    8can be represented with the SLP
    90.2::s([a|R]):-
   10  s(R).
   110.2::s([b|R]):-
   12  s(R).
   130.3::s([a]).
   140.3::s([b]).
   15SLPs define a distribution over the argument of goals: the above program 
   16defines a distribution over the values of S in for which s(S) succeeds.
   17This SLP can be written as an LPAD/ProbLog program by 
   18recalling that in SLPs the probabilities of all rules with the same head predicate sum to one and define a mutually exclusive choice on how to continue a proof.
   19Furthermore, repeated choices are independent, i.e., no stochastic memoization
   20is done. Therefore, a counter argument is added to the predicate s/1 to
   21keep track of the derivation step.
   22*/
   23:- use_module(library(mcintyre)).   24
   25:- if(current_predicate(use_rendering/1)).   26:- use_rendering(c3).   27:- endif.   28:- mc.   29:- begin_lpad.   30
   31s_as(N):0.2;s_bs(N):0.2;s_a(N):0.3;s_b(N):0.3.
   32s([a|R],N0):-
   33  s_as(N0),
   34  N1 is N0+1,
   35  s(R,N1).
   36s([b|R],N0):-
   37  s_bs(N0),
   38  N1 is N0+1,
   39  s(R,N1).
   40s([a],N0):-
   41  s_a(N0).
   42s([b],N0):-
   43  s_b(N0).
   44
   45s(L):-s(L,0).
   46:- end_lpad.

?- mc_sample_arg(s(S),100,S,L). % sample 100 sentences from the language ?- mc_sample_arg(s(S),100,S,P),argbar(P,C). % sample 100 sentences from the language and draw a bar chart

*/