1/*
    2Stochastic logic program defining a distribution over simple sentences with number agreement. The sentences are defined using a definite clause grammars.
    3Recall 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.
    4Furthermore, repeated choices are independent, i.e., no stochastic memoization
    5Form https://dtai.cs.kuleuven.be/problog/tutorial/various/06_slp.html#stochastic-logic-programs
    6*/
    7:- use_module(library(mcintyre)).    8
    9:- if(current_predicate(use_rendering/1)).   10:- use_rendering(c3).   11:- endif.   12:- mc.   13:- begin_lpad.   14% a stochastic logic program defining a distribution over simple sentences with number agreement
   15% recall 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
   16% furthermore, repeated choices are independent, i.e., no stochastic memoization
   17%
   18% 1.0 : s(List) :-
   19%    s(List,[]).
   20%
   21% 1.0 : s(List,Rest) :-
   22%    np(List,Mid,Number),
   23%    vp(Mid,Rest,Number).
   24%
   25% 0.4 : np(List,Rest,sing) :-
   26%    det(List,Mid,sing),
   27%    n(Mid,Rest,sing).
   28% 0.4 : np(List,Rest,pl) :-
   29%    n(List,Rest,pl).
   30% 0.2 : np(List,Rest,pl) :-
   31%    det(List,Mid,pl),
   32%    n(Mid,Rest,pl).
   33%
   34% 1.0 : vp(List,Rest,Num) :-
   35%    v(List,Mid,Num),
   36%    np(Mid,Rest,_).
   37%
   38% 1/3 : det([the|L],L,pl).
   39% 1/3 : det([the|L],L,sing).
   40% 1/3 : det([a|L],L,sing).
   41%
   42% 0.25 : n([cat|L],L,sing).
   43% 0.15 : n([mouse|L],L,sing).
   44% 0.1 : n([dog|L],L,sing).
   45% 0.25 : n([cats|L],L,pl).
   46% 0.15 : n([mice|L],L,pl).
   47% 0.1 : n([dogs|L],L,pl).
   48%
   49% 0.35 : v([chases|L],L,sing).
   50% 0.15 : v([sees|L],L,sing).
   51% 0.2 : v([chase|L],L,pl).
   52% 0.3 : v([see|L],L,pl).
   53
   54% use counter-based trial IDs for each head predicate with a stochastic choice, and explicit split rather than difference lists
   55
   56% s(Num) -> np(Num),vp(Num)
   57s(W,Num,np(N,NN),det(D,DD),n(M,MM),v(V,VV)) :-
   58     split(W,W1,W2),
   59     np(W1,Num,np(N,NI),det(D,DI),n(M,MI),v(V,VI)),
   60     vp(W2,Num,np(NI,NN),det(DI,DD),n(MI,MM),v(VI,VV)).
   61
   62% np(Num) -> 0.4:: det(sg),n(sg) | 0.4:: n(pl) | 0.2::det(pl),n(pl)
   630.4::np_to(N,sg_dn); 0.4::np_to(N,pl_n); 0.2::np_to(N,pl_dn).
   64%np_to(N,sg_dn):0.4; np_to(N,pl_n):0.4; np_to(N,pl_dn):0.2.
   65np(W,sg,np(N,NN),det(D,DD),n(M,MM),v(V,VV)) :-
   66     np_to(N,sg_dn),
   67     NI is N+1,
   68     split(W,W1,W2),
   69     det(W1,sg,np(NI,N1),det(D,D1),n(M,M1),v(V,V1)),
   70     n(W2,sg,np(N1,NN),det(D1,DD),n(M1,MM),v(V1,VV)).
   71np(W,pl,np(N,NN),det(D,DD),n(M,MM),v(V,VV)) :-
   72     np_to(N,pl_n),
   73     NI is N+1,
   74     n(W,pl,np(NI,NN),det(D,DD),n(M,MM),v(V,VV)).
   75np(W,pl,np(N,NN),det(D,DD),n(M,MM),v(V,VV)) :-
   76     np_to(N,pl_dn),
   77     NI is N+1,
   78     split(W,W1,W2),
   79     det(W1,pl,np(NI,N1),det(D,D1),n(M,M1),v(V,V1)),
   80     n(W2,pl,np(N1,NN),det(D1,DD),n(M1,MM),v(V1,VV)).
   81
   82% vp(Num) -> v(Num), np(_)
   83vp(W,Num,np(N,NN),det(D,DD),n(M,MM),v(V,VV)) :-
   84     split(W,W1,W2),
   85     v(W1,Num,np(N,NI),det(D,DI),n(M,MI),v(V,VI)),
   86     np(W2,_,np(NI,NN),det(DI,DD),n(MI,MM),v(VI,VV)).
   87
   88% det(Num) -> 1/3 the(pl) | 1/3 the(sg) | 1/3 a(sg)
   89% det_to(N,the_pl):1/3; det_to(N,the_sg):1/3; det_to(N,a_sg):1/3.
   901/3::det_to(N,the_pl); 1/3::det_to(N,the_sg); 1/3::det_to(N,a_sg).
   91det([the],pl,np(N,N),det(D,DD),n(M,M),v(V,V)) :-
   92     det_to(D,the_pl), DD is D+1.
   93det([the],sg,np(N,N),det(D,DD),n(M,M),v(V,V)) :-
   94     det_to(D,the_sg), DD is D+1.
   95det([a],sg,np(N,N),det(D,DD),n(M,M),v(V,V)) :-
   96     det_to(D,a_sg), DD is D+1.
   97
   98% n(Num) -> 0.25 cat(sg) | 0.15 mouse(sg) | 0.1 dog(sg) | 0.25 cats(pl) | 0.15 mice(pl) | 0.1 dogs(pl)
   990.25::n_to(N,cat_sg);  0.15::n_to(N, mouse_sg) ; 0.1::n_to(N, dog_sg) ; 0.25::n_to(N, cats_pl) ; 0.15::n_to(N, mice_pl) ; 0.1::n_to(N, dogs_pl).
  100%n_to(N,cat_sg):0.25;  n_to(N, mouse_sg):0.15 ; n_to(N, dog_sg):0.1 ; n_to(N, cats_pl):0.25 ; n_to(N, mice_pl):0.15 ; n_to(N, dogs_pl):0.1.
  101%n_to(N,cat_sg):0.5;  n_to(N, mouse_sg):0.3 ; n_to(N, dog_sg):0.2.
  102% n_to(N, cats_pl):0.5 ; n_to(N, mice_pl):0.3 ; n_to(N, dogs_pl):0.2.
  103n([cat],sg,np(N,N),det(D,D),n(M,MM),v(V,V)) :-
  104     n_to(M,cat_sg), MM is M+1.
  105n([mouse],sg,np(N,N),det(D,D),n(M,MM),v(V,V)) :-
  106     n_to(M,mouse_sg), MM is M+1.
  107n([dog],sg,np(N,N),det(D,D),n(M,MM),v(V,V)) :-
  108     n_to(M,dog_sg), MM is M+1.
  109n([cats],pl,np(N,N),det(D,D),n(M,MM),v(V,V)) :-
  110     n_to(M,cats_pl), MM is M+1.
  111n([mice],pl,np(N,N),det(D,D),n(M,MM),v(V,V)) :-
  112     n_to(M,mice_pl), MM is M+1.
  113n([dogs],pl,np(N,N),det(D,D),n(M,MM),v(V,V)) :-
  114     n_to(M,dogs_pl), MM is M+1.
  115
  116% v(Num) -> 0.35 chases(sg) | 0.15 sees(sg) | 0.2 chase(pl) | 0.3 see(pl)
  1170.35::v_to(N, chases_sg) ; 0.15::v_to(N, sees_sg) ; 0.2::v_to(N, chase_pl) ; 0.3::v_to(N, see_pl).
  118%v_to(N, chases_sg):0.35 ; v_to(N, sees_sg):0.15 ; v_to(N, chase_pl):0.2 ; v_to(N, see_pl):0.3.
  119v([chases],sg,np(N,N),det(D,D),n(M,M),v(V,VV)) :-
  120     v_to(V,chases_sg), VV is V+1.
  121v([sees],sg,np(N,N),det(D,D),n(M,M),v(V,VV)) :-
  122     v_to(V,sees_sg), VV is V+1.
  123v([chase],pl,np(N,N),det(D,D),n(M,M),v(V,VV)) :-
  124     v_to(V,chase_pl), VV is V+1.
  125v([see],pl,np(N,N),det(D,D),n(M,M),v(V,VV)) :-
  126     v_to(V,see_pl), VV is V+1.
  127
  128% initialize all counters to 0, and leave number open
  129word(L) :- s(L,_Num,np(0,_),det(0,_),n(0,_),v(0,_)).
  130
  131% split(+T,-P,-S) splits the list T into two non-empty sublists P(refix) and S(uffix)
  132% note that T needs to have fixed length for this to terminate
  133split([A,B|C],[A],[B|C]).
  134split([A,B|C],[A|D],E) :-
  135  split([B|C],D,E).
  136
  137% compute posteriors of correct sentences (or sample a correct sentence)
  138% we need to fix the length of the list to ensure split/3 has a finite number of solutions
  139query(X):-X=[_,_,_,_,_],word(X).
  140query(X):-X=[_,_,_,_],word(X).
  141query(X):-X=[_,_,_],word(X).
  142evidence(is_word).
  143
  144% this grammar can only produce words of length 3/4/5
  145% the probability of getting a word is 0.067222
  146is_word :- word([_,_,_]).
  147is_word :- word([_,_,_,_]).
  148is_word :- word([_,_,_,_,_]).
  149
  150:- end_lpad.

?- mc_sample(is_word,1000,P). % the probability of getting a word of length 3/4/5 % Expected result 0.067222

?- mc_mh_sample_arg(word([A,B,C]),word([_,_,_]),10,[A,B,C],V,[lag(1)]). % take 10 samples of 3 token words given that the length of the word is 3

?- mc_mh_sample_arg(word([A,B,C]),word([_,_,_]),10,[A,B,C],V,[lag(1)]),argbar(V,C). % take 10 samples of 3 token words given that the length of the word is 3 % and draw a bar chart of the results

?- mc_mh_sample_arg(query(X),is_word,10,X,V,[lag(1)]). % take 10 samples of 3, 4 or 5 token words given that the length of the word is % 3, 5 or 5

?- mc_gibbs_sample(word([mice,see,cats]),word([mice,_,_]),1000,V,[lag(1)]).

*/