1/* 2A simple Bayesian network from Figure 2 in 3J. Vennekens, S. Verbaeten, and M. Bruynooghe. Logic programs with annotated 4disjunctions. In International Conference on Logic Programming, 5volume 3131 of LNCS, pages 195.209. Springer, 2004. 6*/ 7:- use_module(library(pita)). 8 9:- if(current_predicate(use_rendering/1)). 10:- use_rendering(c3). 11:- endif. 12 13:- pita. 14 15:- begin_lpad. 16 17burg(t):0.1; burg(f):0.9. 18% there is a burglary with probability 0.1 19earthq(t):0.2; earthq(f):0.8. 20% there is an eartquace with probability 0.2 21alarm(t):-burg(t),earthq(t). 22% if there is a burglary and an earthquake then the alarm surely goes off 23alarm(t):0.8 ; alarm(f):0.2:-burg(t),earthq(f). 24% it there is a burglary and no earthquake then the alarm goes off with probability 0.8 25alarm(t):0.8 ; alarm(f):0.2:-burg(f),earthq(t). 26% it there is no burglary and an earthquake then the alarm goes off with probability 0.8 27alarm(t):0.1 ; alarm(f):0.9:-burg(f),earthq(f). 28% it there is no burglary and no earthquake then the alarm goes off with probability 0.1 29 30:- end_lpad.
?-
prob(alarm(t),Prob)
. % what is the probability that the alarm goes off? % expected result 0.30000000000000004 ?-prob(alarm(f),Prob)
. % what is the probability that the alarm doesn't go off? % expected result 0.7000000000000002 ?-prob(alarm(t),Prob)
,bar(Prob,C)
. % what is the probability that the alarm goes off? % expected result 0.30000000000000004 ?-prob(alarm(f),Prob)
,bar(Prob,C)
. % what is the probability that the alarm doesn't go off? % expected result 0.7000000000000002*/