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(viterbi)). 12 13:- if(current_predicate(use_rendering/1)). 14:- use_rendering(c3). 15:- endif. 16 17:- viterbi. 18 19:- begin_lpad. 20 21mother(m,s). 22father(f,s). 23% family with 3 members: m is the mother of s and f is the father of s 24 25% cg(I,C,A) means that individual I has color allele A on chromosome C 26% the color alleles are p and w and the chromosomes are 1 and 2 27% color(I,Col) means that individual I has color Col 28% Col can be purple or white 29 30cg(m,1,p). 31cg(m,2,w). 32cg(f,1,w). 33cg(f,2,p). 34% we know with certainty the alleles of the parants of s 35 36cg(X,1,A):0.5 ; cg(X,1,B):0.5 :- mother(Y,X),cg(Y,1,A), cg(Y,2,B). 37% the color allele of an individual on chromosome 1 is inherited from its 38% mother. The two alleles of the mother have equal probability of being 39% transmitted 40 41cg(X,2,A):0.5 ; cg(X,2,B):0.5 :- father(Y,X),cg(Y,1,A), cg(Y,2,B). 42% the color allele of an individual on chromosome 2 is inherited from its 43% father. The two alleles of the mother have equal probability of being 44% transmitted 45 46 47color(X,purple) :- cg(X,_,p). 48% if an individual has a p allele its color is purple, i.e., purple is 49% dominant 50 51color(X,white) :- cg(X,1,w), cg(X,2,w). 52% if an individual has two w alleles its color is white, i.e., white is 53% recessive 54 55:- end_lpad.
?-
viterbi(color(s,purple),Prob,Exp)
. Prob = 0.5, Exp = [rule(0, cg(s, 1, p), [cg(s, 1, p):0.5, cg(s, 1, w):0.5], [mother(m, s), cg(m, 1, p), cg(m, 2, w)])
].?-
viterbi(color(s,white),Prob,Exp)
. Prob = 0.25, Exp = [rule(0, cg(s, 1, w), [cg(s, 1, p):0.5, cg(s, 1, w):0.5], [mother(m, s), cg(m, 1, p), cg(m, 2, w)])
,rule(1, cg(s, 2, w), [cg(s, 2, w):0.5, cg(s, 2, p):0.5], [father(f, s), cg(f, 1, w), cg(f, 2, p)])
].*/