1/*
    2A PLCG is a probabilistic version of left-corner grammar which uses the same set
    3of CFG rules as a PCFG but models a shift-reduce parser with probabilities assigned to shift-reduce operations.
    4From
    5Sato, Taisuke, Yoshitaka Kameya, and Kenichi Kurihara. "Variational Bayes via propositionalized probability computation in PRISM." Annals of Mathematics and Artificial Intelligence 54.1-3 (2008): 135-158.
    6*/
    7
    8
    9:- use_module(library(mcintyre)).   10
   11:- if(current_predicate(use_rendering/1)).   12:- use_rendering(c3).   13:- endif.   14
   15:- mc.   16
   17:- begin_lpad.   18% grammar
   19% S->SS
   20% S->a
   21% S->b
   22plc(Ws) :- g_call(['S'] ,Ws,[], [],_Der).
   23
   24g_call([],L,L,Der,Der). 
   25
   26g_call([G|R], [G|L],L2,Der0,Der) :- % shift
   27  terminal(G),
   28  g_call(R,L,L2,Der0,Der).
   29
   30g_call([G|R], [Wd|L] ,L2,Der0,Der) :-
   31  \+ terminal(G),
   32  first(G,Der0,Wd),
   33  lc_call(G,Wd,L,L1,[first(G,Wd)|Der0],Der1),
   34  g_call(R,L1,L2,Der1,Der).
   35
   36lc_call(G,B,L,L1,Der0,Der) :- % attach
   37  lc(G,B,Der0,rule(G, [B|RHS2])),
   38  attach_or_project(G,Der0,attach),
   39  g_call(RHS2,L,L1,[lc(G,B,rule(G, [B|RHS2])),attach|Der0],Der).
   40
   41lc_call(G,B,L,L2,Der0,Der) :- % project 
   42  lc(G,B,Der0,rule(A, [B|RHS2])),
   43  attach_or_project(G,Der0,project),
   44  g_call(RHS2,L,L1,[lc(G,B,rule(A, [B|RHS2])),project|Der0],Der1),
   45  lc_call(G,A,L1,L2,Der1,Der).
   46
   47lc_call(G,B,L,L2,Der0,Der) :- 
   48  \+ lc(G,B,Der0,rule(G,[B|_])),
   49  lc(G,B,Der0,rule(A, [B|RHS2])),
   50  g_call(RHS2,L,L1,[lc(G,B,rule(A, [B|RHS2]))|Der0],Der1),
   51  lc_call(G,A,L1,L2,Der1,Der).
   52
   53attach_or_project(A,Der,Op) :-
   54  lc(A,A,Der,_),
   55  attach(A,Der,Op).
   56
   57attach_or_project(A,Der,attach) :-
   58  \+ lc(A,A,Der,_).
   59
   60
   61lc('S','S',_Der,rule('S',['S','S'])). 
   62
   63lc('S',a,_Der,rule('S',[a])).
   64
   65lc('S',b,_Der,rule('S',[b])). 
   66
   67first('S',Der,a):0.5; first('S',Der,b):0.5.
   68
   69
   70attach('S',Der,attach):0.5; attach('S',Der,project):0.5.
   71
   72terminal(a).
   73terminal(b).
   74
   75
   76
   77:- end_lpad.

?- mc_prob(plc([a,b]),P). % what is the probability of sentence [a,b]? % expecte result ~ 0.031

?- mc_sample(plc([a,b]),1000,T,F,P). % take 1000 samples of plc([a,b])

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

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

?- mc_sample_arg(plc(L),20,L,O),argbar(O,C). % take 20 samples of L in % findall(S,pls(S),L) */