1/* 2Program describing the Mendelian rules of inheritance of the color of pea 3plants. It considers a family of two parents and a child. 4The problem is, given the alleles of the parents, predict the 5probability of the color (or of its alleles) of a pea plant. 6From 7H. Blockeel. Probabilistic logical models for mendel's experiments: 8An exercise. 9In Inductive Logic Programming (ILP 2004), Work in Progress Track, 2004. 10*/ 11:- use_module(library(pitaind)). 12 13:- if(current_predicate(use_rendering/1)). 14:- use_rendering(c3). 15:- endif. 16 17:- pitaind. 18:- set_pitaind(or,exc). 19:- set_pitaind(depth_bound,true). 20:- set_pitaind(depth,5). 21 22:- begin_lpad. 23 24mother(m,s). 25father(f,s). 26% family with 3 members: m is the mother of s and f is the father of s 27 28% cg(I,C,A) means that individual I has color allele A on chromosome C 29% the color alleles are p and w and the chromosomes are 1 and 2 30% color(I,Col) means that individual I has color Col 31% Col can be purple or white 32 33cg(m,1,p). 34cg(m,2,w). 35cg(f,1,w). 36cg(f,2,p). 37% we know with certainty the alleles of the parants of s 38 39cg(X,1,A):0.5 ; cg(X,1,B):0.5 :- mother(Y,X),cg(Y,1,A), cg(Y,2,B). 40% the color allele of an individual on chromosome 1 is inherited from its 41% mother. The two alleles of the mother have equal probability of being 42% transmitted 43 44cg(X,2,A):0.5 ; cg(X,2,B):0.5 :- father(Y,X),cg(Y,1,A), cg(Y,2,B). 45% the color allele of an individual on chromosome 2 is inherited from its 46% father. The two alleles of the mother have equal probability of being 47% transmitted 48 49 50color(X,purple) :- cg(X,1,p). 51% if an individual has a p allele its color is purple, i.e., purple is 52% dominant 53color(X,purple) :- cg(X,1,w),cg(X,2,p). 54 55color(X,white) :- cg(X,1,w), cg(X,2,w). 56% if an individual has two w alleles its color is white, i.e., white is 57% recessive 58 59:- end_lpad.
?-
prob(color(s,purple),Prob)
. % what is the probability that the color of s' flowers is purple? % expected result 0.75 ?-prob(color(s,white),Prob)
. % what is the probability that the color of s' flowers is white? % expected result 0.25 ?-prob(cg(s,1,p),Prob)
. % what is the probability that the color allele on chromosme 1 of s is p? % expected result 0.5 ?-prob(cg(s,1,w),Prob)
. % what is the probability that the color allele on chromosme 1 of s is w? % expected result 0.5 ?-prob(cg(s,2,p),Prob)
. % what is the probability that the color allele on chromosme 2 of s is p? % expected result 0.5 ?-prob(cg(s,2,w),Prob)
. % what is the probability that the color allele on chromosme 2 of s is w? % expected result 0.5 ?-prob_bar(color(s,purple),Prob)
. % what is the probability that the color of s' flowers is purple? % expected result 0.75 ?-prob_bar(color(s,white),Prob)
. % what is the probability that the color of s' flowers is white? % expected result 0.25 ?-prob_bar(cg(s,1,p),Prob)
. % what is the probability that the color allele on chromosme 1 of s is p? % expected result 0.5 ?-prob_bar(cg(s,1,w),Prob)
. % what is the probability that the color allele on chromosme 1 of s is w? % expected result 0.5 ?-prob_bar(cg(s,2,p),Prob)
. % what is the probability that the color allele on chromosme 2 of s is p? % expected result 0.5 ?-prob_bar(cg(s,2,w),Prob)
. % what is the probability that the color allele on chromosme 2 of s is w? % expected result 0.5*/