1/* 2Flexible probabilities: variable probabilistic annotations. 3The example models drawing a person at random from a population and 4computing the probability that it is a male or a female. 5From 6J. Vennekens, S. Verbaeten, and M. Bruynooghe. Logic programs with annotated 7disjunctions. In International Conference on Logic Programming, 8volume 3131 of LNCS, pages 195-209. Springer, 2004. 9*/ 10:- use_module(library(pita)). 11 12:- if(current_predicate(use_rendering/1)). 13:- use_rendering(c3). 14:- endif. 15 16:- pita. 17 18:- begin_lpad. 19 20male:M/P; female:F/P:- 21 findall(Male,male(Male),LM), 22 findall(Female,female(Female),LF), 23 length(LM,M), 24 length(LF,F), 25 P is F+M. 26 27:- end_lpad. 28 29male(john). 30male(david). 31 32female(anna). 33female(elen). 34female(cathy).
?-
prob(male,Prob)
. % what is the probability of sampling a male from the % population? % expected result 0.4 ?-prob(female,Prob)
. % what is the probability of sampling a female from the % population? % expected result 0.6 ?-prob(male,Prob)
,bar(Prob,C)
. % what is the probability of sampling a male from the % population? % expected result 0.4 ?-prob(female,Prob)
,bar(Prob,C)
. % what is the probability of sampling a female from the % population? % expected result 0.6 */