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.   22coin ~ finite([0.95:true,0.05:false]).
   23agpa ~ beta(8,2) := coin~=true.
   24american_gpa ~ finite([0.85:4.0,0.15:0.0]) := coin~=false.
   25
   26american_gpa ~ val(V) := agpa ~=A, V is A*4.0.
   27
   28coin2 ~ finite([0.99:true,0.01:false]).
   29igpa ~ beta(5,5) := coin2~=true.
   30indian_gpa ~ finite([0.1:0.0,0.9:10.0]) := coin2~=false.
   31
   32indian_gpa ~ val(V) := igpa ~=A, V is A*10.0.
   33
   34nation ~ finite([0.25:a,0.75:i]).
   35
   36student_gpa ~ val(A) := nation~=a,american_gpa~=A.
   37student_gpa ~ val(I) := nation~=i,indian_gpa~=I.
   38
   39
   40:- 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 */