1/*
    2A prefix parser for a probabilistic left-corner grammar.
    3From
    4T. Sato, P. Meyer, Tabling for infinite probability computation, in:
    5Intnational Confence on Logic Programming, Vol. 17 of LIPIcs, 2012,
    6pp.  348-358.
    7T. Sato, P. Meyer, Infinite probability computation by cyclic explanation
    8graphs, Theory and Practice of Logic Programming 14 (2014) 909-937.
    9doi:10.1017/S1471068413000562.
   10*/
   11
   12
   13:- use_module(library(mcintyre)).   14
   15:- if(current_predicate(use_rendering/1)).   16:- use_rendering(c3).   17:- endif.   18
   19:- mc.   20
   21:- begin_lpad.   22% grammar
   23% S->SS
   24% S->a
   25% S->b
   26pre_plc(Ws) :- g_call(['S'] ,Ws,[], [],_Der).
   27
   28g_call([],L,L,Der,Der). 
   29
   30g_call([G|R], [G|L],L2,Der0,Der) :- % shift
   31  terminal(G),
   32  g_call(R,L,L2,Der0,Der).
   33
   34g_call([G|_R], [Wd|L] ,[],Der0,Der) :-
   35  \+ terminal(G),
   36  first(G,Der0,Wd),
   37  lc_call(G,Wd,L,[],[first(G,Wd)|Der0],Der). % pseudo success
   38
   39g_call([G|R], [Wd|L] ,L2,Der0,Der) :-
   40  \+ terminal(G),
   41  first(G,Der0,Wd),
   42  lc_call(G,Wd,L,L1,[first(G,Wd)|Der0],Der1),
   43  g_call(R,L1,L2,Der1,Der).
   44
   45lc_call(G,B,L,L1,Der0,Der) :- % attach
   46  lc(G,B,Der0,rule(G, [B|RHS2])),
   47  attach_or_project(G,Der0,attach),
   48  g_call(RHS2,L,L1,[lc(G,B,rule(G, [B|RHS2])),attach|Der0],Der).
   49
   50lc_call(G,B,L,L2,Der0,Der) :- % project 
   51  lc(G,B,Der0,rule(A, [B|RHS2])),
   52  attach_or_project(G,Der0,project),
   53  g_call(RHS2,L,L1,[lc(G,B,rule(A, [B|RHS2])),project|Der0],Der1),
   54  lc_call(G,A,L1,L2,Der1,Der).
   55
   56lc_call(G,B,L,L2,Der0,Der) :- 
   57  \+ lc(G,B,Der0,rule(G,[B|_])),
   58  lc(G,B,Der0,rule(A, [B|RHS2])),
   59  g_call(RHS2,L,L1,[lc(G,B,rule(A, [B|RHS2]))|Der0],Der1),
   60  lc_call(G,A,L1,L2,Der1,Der).
   61
   62
   63attach_or_project(A,Der,Op) :-
   64  lc(A,A,Der,_),
   65  attach(A,Der,Op).
   66
   67attach_or_project(A,Der,attach) :-
   68  \+ lc(A,A,Der,_).
   69
   70
   71lc('S','S',_Der,rule('S',['S','S'])). 
   72
   73lc('S',a,_Der,rule('S',[a])).
   74
   75lc('S',b,_Der,rule('S',[b])). 
   76
   77first('S',Der,a):0.5; first('S',Der,b):0.5.
   78
   79
   80attach('S',Der,attach):0.5; attach('S',Der,project):0.5.
   81
   82terminal(a).
   83terminal(b).
   84
   85
   86
   87:- end_lpad.

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

*/