1/*
    2Probabilistic contect-free grammar.
    30.2:S->aS
    40.2:S->bS
    50.3:S->a
    60.3:S->b
    7From
    8 Taisuke Sato and Keiichi Kubota. Viterbi training in PRISM. 
    9Theory and Practice of Logic Programming,  doi:10.1017/S1471068413000677. 
   10*/
   11:- use_module(library(pita)).   12
   13:- if(current_predicate(use_rendering/1)).   14:- use_rendering(c3).   15:- endif.   16
   17:- pita.   18
   19:- begin_lpad.   20
   21% pcfg(LT): LT is string of terminals accepted by the grammar
   22% pcfg(L,LT,LT0) L is a tring 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  grammar_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  terminal(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
   44grammar_rule('S',Der,[a,'S']):0.2; grammar_rule('S',Der,[b,'S']):0.2; 
   45  grammar_rule('S',Der,[a]):0.3; grammar_rule('S',Der,[b]):0.3.
   46% encodes the three rules of the grammar
   47
   48terminal(a).
   49terminal(b).
   50:- end_lpad.

?- prob(pcfg([a,b,a,a]),Prob). % what is the probability that the string abaa belongs to the language? % expected result 0.0024 ?- prob(pcfg([a,b,a,a]),Prob),bar(Prob,C). % what is the probability that the string abaa belongs to the language? % expected result 0.0024

*/