1/*
    2The Indian GPA Problem. From 
    3http://www.robots.ox.ac.uk/~fwood/anglican/examples/viewer/?worksheet=indian-gpa 
    4"This example was inspired by Stuart Russell...the problem is: if you observe 
    5that a student GPA is exactly 4.04.0 in a model of transcripts of students 
    6from the USA (GPA's from 0.00.0 to 4.04.0 and India (GPA's from 0.00.0 to 
    710.010.0) what is the probability that the student is from India?... 
    8As we know from statistics, given the mixture distribution and given the 
    9fact that his/her GPA is exactly 4.04.0, the probability that the student 
   10is American must be 1.01.0 
   11(i.e. zero probability that the student is from India)."
   12Probabilistic logic program from 
   13https://github.com/davidenitti/DC/blob/master/examples/indian-gpa.pl
   14*/
   15:- use_module(library(mcintyre)).   16
   17:- if(current_predicate(use_rendering/1)).   18:- use_rendering(c3).   19:- endif.   20:- mc.   21:- begin_lpad.   22
   23is_density_A:0.95;is_discrete_A:0.05.
   24% the probability distribution of GPA scores for American students is
   25% continuous with probability 0.95 and discrete with probability 0.05
   26
   27agpa(A): beta(A,8,2) :- is_density_A.
   28% the GPA of American students follows a beta distribution if the
   29% distribution is continuous
   30
   31american_gpa(G) : finite(G,[4.0:0.85,0.0:0.15]) :- is_discrete_A.
   32% the GPA of American students is 4.0 with probability 0.85 and 0.0 with 
   33% probability 0.15 if the
   34% distribution is discrete
   35american_gpa(A):- agpa(A0), A is A0*4.0.
   36% the GPA of American students is obtained by rescaling the value of agpa
   37% to the (0.0,4.0) interval
   38is_density_I : 0.99; is_discrete_I:0.01.
   39% the probability distribution of GPA scores for Indian students is
   40% continuous with probability 0.99 and discrete with probability 0.01
   41igpa(I): beta(I,5,5) :- is_density_I.
   42% the GPA of Indian students follows a beta distribution if the
   43% distribution is continuous
   44indian_gpa(I): finite(I,[0.0:0.1,10.0:0.9]):-  is_discrete_I.
   45% the GPA of Indian students is 10.0 with probability 0.9 and 0.0 with
   46% probability 0.1 if the
   47% distribution is discrete
   48indian_gpa(I) :- igpa(I0), I is I0*10.0.
   49% the GPA of Indian students is obtained by rescaling the value of igpa
   50% to the (0.0,4.0) interval
   51nation(N) : finite(N,[a:0.25,i:0.75]).
   52% the nation is America with probability 0.25 and India with probability 0.75
   53student_gpa(G):- nation(a),american_gpa(G).
   54% the GPA of the student is given by american_gpa if the nation is America
   55student_gpa(G) :- nation(i),indian_gpa(G).
   56% the GPA of the student is given by indian_gpa if the nation is India
   57
   58:- end_lpad.

?- mc_lw_sample(nation(a),student_gpa(4.0),1000,PPost). % probability that the nation is America given that the student got 4.0 % in his GPA % expected result: 1.0 ?- mc_sample(nation(a),1000,PPrior). % prior probability that the nation is America % expected result: 0.25

*/