1/*
    2This program models the occurrence of an earthquake depending on its possible 
    3causes.
    4From
    5F. Riguzzi and N. Di Mauro. Applying the information bottleneck to statistical 
    6relational learning. Machine Learning, 86(1):89-114, 2012
    7*/
    8:- use_module(library(pita)).    9
   10:- if(current_predicate(use_rendering/1)).   11:- use_rendering(c3).   12:- endif.   13
   14:- pita.   15
   16:- begin_lpad.   17
   18earthquake(X, strong) : 0.3 ; earthquake(X, moderate) : 0.5 :-
   19  fault_rupture(X).
   20% if an earthquake at a site X is caused only by the rupture of a 
   21% geological fault, we have a strong earthquake with probability 0.3, 
   22% a moderate earthquake with probability 0.5 and no earthquake with probability 
   23% 0.2
   24
   25earthquake(X, strong) : 0.2 ; earthquake(X, moderate) : 0.6 :-
   26  volcanic_eruption(X).
   27% if an earthquake at a site X is caused only by a volcanic eruption, 
   28% we have a strong earthquake with probability 0.2, 
   29% a moderate earthquake with probability 0.6 and no earthquake with probability 
   30% 0.2
   31
   32
   33fault_rupture(stromboli).
   34% there is a fault rupture at stromboli
   35
   36volcanic_eruption(stromboli).
   37% there is a volcanic eruption at stromboli
   38
   39volcanic_eruption(eyjafjallajkull).
   40% there is a volcanic eruption at eyjafjallajkull
   41
   42:- end_lpad.

?- prob(earthquake(stromboli,strong),Prob). % what is the probability of a strong % earthquake at stromboli? % expected result 0.43999999999999995 ?- prob(earthquake(stromboli,moderate),Prob). % what is the probability of a moderate % earthquake at stromboli? % expected result 0.7999999999999998 ?- prob(earthquake(eyjafjallajkull,strong),Prob). % what is the probability of a strong % earthquake at eyjafjallajkull? % expected result 0.2 ?- prob(earthquake(eyjafjallajkull,moderate),Prob). % what is the probability of a moderate % earthquake at eyjafjallajkull? % expected result 0.6 ?- prob(earthquake(stromboli,strong),Prob),bar(Prob,C). % what is the probability of a strong % earthquake at stromboli? % expected result 0.43999999999999995 ?- prob(earthquake(stromboli,moderate),Prob),bar(Prob,C). % what is the probability of a moderate % earthquake at stromboli? % expected result 0.7999999999999998 ?- prob(earthquake(eyjafjallajkull,strong),Prob),bar(Prob,C). % what is the probability of a strong % earthquake at eyjafjallajkull? % expected result 0.2 ?- prob(earthquake(eyjafjallajkull,moderate),Prob),bar(Prob,C). % what is the probability of a moderate % earthquake at eyjafjallajkull? % expected result 0.6

*/