1/*
    2Distributional Clauses example.
    3From Example 4 of 
    4Davide Nitti, Tinne De Laet, and Luc De Raedt. Probabilistic logic programming for hybrid relational domains. Machine Learning 103(3), 407-449, 2016.
    5http://link.springer.com/article/10.1007/s10994-016-5558-8/fulltext.html
    6"We have an urn, where the number of balls n is a random variable and each ball 
    7X has a color, material, and size with a known distribution. 
    8The i-th ball drawn with replacement from the
    9urn is named drawn(i)."
   10See also
   11https://github.com/davidenitti/DC/blob/master/examples/tutorial.pl
   12*/
   13:- use_module(library(mcintyre)).   14
   15:- if(current_predicate(use_rendering/1)).   16:- use_rendering(c3).   17:- endif.   18:- mc.   19:- begin_lpad.   20
   21% define another discrete random variable (categorical) with uniform distribution
   22nballs ~ uniform([1,2,3,4,5,6,7,8,9,10]).
   23
   24ball(X) := nballs ~= N, between(1,N,X). % read as: for each X and N, if nballs=N and X is between 1 and N then ball(X) is true. nballs=N will succeed for N equals to the value of the number of balls. For example, if nballs=3 then ball(1),ball(2),ball(3) are true.
   25
   26% define a random variable for each ball
   27material(X) ~ finite([0.3:wood,0.7:metal]) := ball(X). % read as: for each X if ball(X) is true then the random variable material(X) has a given distribution. For example, if ball(1) and ball(2) are true, then material(1) and material(2) are 2 i.i.d. random variables.
   28
   29% define the color of each ball: the color distribution depends on the material.
   30color(X) ~ uniform([grey,blue,black]) := material(X) ~= metal. % read as: for each X if the material(X) is metal then color(X) has a given uniform distribution.
   31color(X) ~ uniform([black,brown]) := material(X) ~= wood. % read as: for each X if the material(X) is wood then color(X) has a given uniform distribution (different from the previous one).
   32
   33% define draws with replacement. The ball drawn has a uniform distribution over the number of balls. However, the number of balls is a random variable itself.
   34drawn(_) ~ uniform(Balls) := nballs ~= N, findall(X,between(1,N,X),Balls).
   35
   36% define the size of each ball with a beta distribution. The size distribution depends on the material
   37size(X) ~ beta(2,3) := material(X) ~= metal.
   38size(X) ~ beta(4,2) := material(X) ~= wood.
   39:- end_lpad.

?- mc_sample(drawn(1,1),1000,T,F,P). %T = 285, %F = 715, %P = 0.285.

?- mc_sample(drawn(1,1),1000,T,F,P). %T = 290, %F = 710, %P = 0.29.

?- mc_sample(drawn(1,1),1000,T,F,P). %T = 283, %F = 717, %P = 0.283.

?- mc_sample((drawn(1,1),material(1,wood)),1000,T,F,P). %T = 86, %F = 914, %P = 0.086.

?- mc_sample((drawn(1,1),material(1,wood),color(1,black)),1000,T,F,P). %T = 44, %F = 956, %P = 0.044.

*/