13:- use_module(library(pita)). 14
15:- if(current_predicate(use_rendering/1)). 16:- use_rendering(c3). 17:- endif. 18
19:- pita. 20
21:- begin_lpad. 22
28
31mchrom(Person,a):0.90 ; mchrom(Person,b):0.05 ; mchrom(Person,null):0.05 :- mother(Mother,Person), pchrom(Mother,a ), mchrom(Mother,a ).
35mchrom(Person,a):0.49 ; mchrom(Person,b):0.49 ; mchrom(Person,null):0.02 :- mother(Mother,Person), pchrom(Mother,b ), mchrom(Mother,a ).
36mchrom(Person,a):0.49 ; mchrom(Person,b):0.02 ; mchrom(Person,null):0.49 :- mother(Mother,Person), pchrom(Mother,null), mchrom(Mother,a ).
37mchrom(Person,a):0.49 ; mchrom(Person,b):0.49 ; mchrom(Person,null):0.02 :- mother(Mother,Person), pchrom(Mother,a ), mchrom(Mother,b ).
38mchrom(Person,a):0.05 ; mchrom(Person,b):0.90 ; mchrom(Person,null):0.05 :- mother(Mother,Person), pchrom(Mother,b ), mchrom(Mother,b ).
39mchrom(Person,a):0.02 ; mchrom(Person,b):0.49 ; mchrom(Person,null):0.49 :- mother(Mother,Person), pchrom(Mother,null), mchrom(Mother,b ).
40mchrom(Person,a):0.49 ; mchrom(Person,b):0.02 ; mchrom(Person,null):0.49 :- mother(Mother,Person), pchrom(Mother,a ), mchrom(Mother,null).
41mchrom(Person,a):0.02 ; mchrom(Person,b):0.49 ; mchrom(Person,null):0.49 :- mother(Mother,Person), pchrom(Mother,b ), mchrom(Mother,null).
42mchrom(Person,a):0.05 ; mchrom(Person,b):0.05 ; mchrom(Person,null):0.90 :- mother(Mother,Person), pchrom(Mother,null), mchrom(Mother,null).
43
46pchrom(Person,a):0.90 ; pchrom(Person,b):0.05 ; pchrom(Person,null):0.05 :- father(Father,Person), pchrom(Father,a ), mchrom(Father,a ).
50pchrom(Person,a):0.49 ; pchrom(Person,b):0.49 ; pchrom(Person,null):0.02 :- father(Father,Person), pchrom(Father,b ), mchrom(Father,a ).
51pchrom(Person,a):0.49 ; pchrom(Person,b):0.02 ; pchrom(Person,null):0.49 :- father(Father,Person), pchrom(Father,null), mchrom(Father,a ).
52pchrom(Person,a):0.49 ; pchrom(Person,b):0.49 ; pchrom(Person,null):0.02 :- father(Father,Person), pchrom(Father,a ), mchrom(Father,b ).
53pchrom(Person,a):0.05 ; pchrom(Person,b):0.90 ; pchrom(Person,null):0.05 :- father(Father,Person), pchrom(Father,b ), mchrom(Father,b ).
54pchrom(Person,a):0.02 ; pchrom(Person,b):0.49 ; pchrom(Person,null):0.49 :- father(Father,Person), pchrom(Father,null), mchrom(Father,b ).
55pchrom(Person,a):0.49 ; pchrom(Person,b):0.02 ; pchrom(Person,null):0.49 :- father(Father,Person), pchrom(Father,a ), mchrom(Father,null).
56pchrom(Person,a):0.02 ; pchrom(Person,b):0.49 ; pchrom(Person,null):0.49 :- father(Father,Person), pchrom(Father,b ), mchrom(Father,null).
57pchrom(Person,a):0.05 ; pchrom(Person,b):0.05 ; pchrom(Person,null):0.90 :- father(Father,Person), pchrom(Father,null), mchrom(Father,null).
58
59
62bloodtype(Person,a):0.90 ; bloodtype(Person,b):0.03 ; bloodtype(Person,ab):0.03 ; bloodtype(Person,null):0.04 :- pchrom(Person,a ),mchrom(Person,a ).
66bloodtype(Person,a):0.03 ; bloodtype(Person,b):0.03 ; bloodtype(Person,ab):0.90 ; bloodtype(Person,null):0.04 :- pchrom(Person,b ),mchrom(Person,a ).
67bloodtype(Person,a):0.90 ; bloodtype(Person,b):0.04 ; bloodtype(Person,ab):0.03 ; bloodtype(Person,null):0.03 :- pchrom(Person,null),mchrom(Person,a ).
68bloodtype(Person,a):0.03 ; bloodtype(Person,b):0.03 ; bloodtype(Person,ab):0.90 ; bloodtype(Person,null):0.04 :- pchrom(Person,a ),mchrom(Person,b ).
69bloodtype(Person,a):0.04 ; bloodtype(Person,b):0.90 ; bloodtype(Person,ab):0.03 ; bloodtype(Person,null):0.03 :- pchrom(Person,b ),mchrom(Person,b ).
70bloodtype(Person,a):0.03 ; bloodtype(Person,b):0.09 ; bloodtype(Person,ab):0.04 ; bloodtype(Person,null):0.03 :- pchrom(Person,null),mchrom(Person,b ).
71bloodtype(Person,a):0.90 ; bloodtype(Person,b):0.03 ; bloodtype(Person,ab):0.03 ; bloodtype(Person,null):0.04 :- pchrom(Person,a ),mchrom(Person,null).
72bloodtype(Person,a):0.03 ; bloodtype(Person,b):0.90 ; bloodtype(Person,ab):0.04 ; bloodtype(Person,null):0.03 :- pchrom(Person,b ),mchrom(Person,null).
73bloodtype(Person,a):0.03 ; bloodtype(Person,b):0.04 ; bloodtype(Person,ab):0.03 ; bloodtype(Person,null):0.90 :- pchrom(Person,null),mchrom(Person,null).
74
76mchrom(p_m,a):0.3 ; mchrom(p_m,b):0.3 ; mchrom(p_m,null):0.4.
79pchrom(p_m,a):0.3 ; pchrom(p_m,b):0.3 ; pchrom(p_m,null):0.4.
80mchrom(p_f,a):0.3 ; mchrom(p_f,b):0.3 ; mchrom(p_f,null):0.4.
81pchrom(p_f,a):0.3 ; pchrom(p_f,b):0.3 ; pchrom(p_f,null):0.4.
82
84father(p_f, p).
85mother(p_m, p).
86
87:- end_lpad.
?-
prob(bloodtype(p,a),Prob)
. % what is the probability that the p's bloodtype is a? % expected result 0.3186942939999999 ?-prob(bloodtype(p,b),Prob)
. % what is the probability that the p's bloodtype is b? % expected result 0.2239874943000002 ?-prob(bloodtype(p,ab),Prob)
. % what is the probability that the p's bloodtype is ab? % expected result 0.19329257700000035 ?-prob(bloodtype(p,null),Prob)
. % what is the probability that the p's bloodtype is 0? % expected result 0.16751706690000012 ?-prob(bloodtype(p,a),Prob)
,bar(Prob,C)
. % what is the probability that the p's bloodtype is a? % expected result 0.3186942939999999 ?-prob(bloodtype(p,b),Prob)
,bar(Prob,C)
. % what is the probability that the p's bloodtype is b? % expected result 0.2239874943000002 ?-prob(bloodtype(p,ab),Prob)
,bar(Prob,C)
. % what is the probability that the p's bloodtype is ab? % expected result 0.19329257700000035 ?-prob(bloodtype(p,null),Prob)
,bar(Prob,C)
. % what is the probability that the p's bloodtype is 0? % expected result 0.16751706690000012 */