1/*
    2Probabilistic context-free grammar. The grammar is left-recursive, depth bounded
    3inference is necessary to ensure termination.
    40.4:S->SS
    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:- set_pita(depth_bound,true).   20:- set_pita(depth,5).   21
   22:- begin_lpad.   23
   24% pcfg(LT): LT is string of terminals accepted by the grammar
   25% pcfg(L,LT,LT0) L is a tring of terminals and not terminals that derives
   26% the list of terminals in LT-LT0
   27
   28pcfg(L):- pcfg(['S'],[],_Der,L,[]).
   29% L is accepted if it can be derived from the start symbol S and an empty
   30% string of previous terminals
   31
   32pcfg([A|R],Der0,Der,L0,L2):-
   33  grammar_rule(A,Der0,RHS),
   34  pcfg(RHS,[rule(A,RHS)|Der0],Der1,L0,L1),
   35  pcfg(R,Der1,Der,L1,L2).
   36% if there is a rule for A (i.e. it is a non-terminal), expand A using the rule
   37% and continue with the rest of the list
   38
   39pcfg([A|R],Der0,Der,[A|L1],L2):-
   40  terminal(A),
   41  pcfg(R,Der0,Der,L1,L2).
   42% if A is a terminal, move it to the output string
   43
   44pcfg([],Der,Der,L,L).
   45% there are no more symbols to expand
   46
   47grammar_rule('S',Der,['S','S']):0.4; grammar_rule('S',Der,[a]):0.3; 
   48  grammar_rule('S',Der,[b]):0.3.
   49% encodes the three rules of the grammar
   50
   51terminal(a).
   52terminal(b).
   53
   54:- end_lpad.

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

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

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

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

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

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

*/