1/*
    2Program describing the Mendelian rules of inheritance of the color of pea 
    3plants. It considers a family of four grandparents, two parents and a child.
    4The problem is, given the alleles of the grandparents, predict the
    5probability of the color (or of its alleles) of a pea plant.
    6From
    7H. Blockeel. Probabilistic logical models for mendel's experiments: An exercise.
    8In Inductive Logic Programming (ILP 2004), Work in Progress Track, 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
   20mother(m,s).
   21mother(mm,m).
   22mother(mf,f).
   23father(f,s).
   24father(fm,m).
   25father(ff,f).
   26% family with 7 members: grandparents, partents and 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
   33
   34
   35cg(mm,1,p).
   36cg(mm,2,w).
   37cg(fm,1,p).
   38cg(fm,2,p).
   39cg(mf,1,w).
   40cg(mf,2,w).
   41cg(ff,1,w).
   42cg(ff,2,p).
   43% we know with certainty the alleles of the grandparants of s
   44
   45
   46cg(X,1,A):0.5 ; cg(X,1,B):0.5 :- mother(Y,X),cg(Y,1,A), cg(Y,2,B).
   47% the color allele of an individual on chromosome 1 is inherited from its 
   48% mother. The two alleles of the mother have equal probability of being
   49% transmitted
   50 
   51cg(X,2,A):0.5 ; cg(X,2,B):0.5 :- father(Y,X),cg(Y,1,A), cg(Y,2,B).
   52% the color allele of an individual on chromosome 2 is inherited from its 
   53% father. The two alleles of the mother have equal probability of being
   54% transmitted
   55
   56
   57color(X,purple) :- cg(X,_,p).
   58% if an individual has a p allele its color is purple, i.e., purple is
   59% dominant
   60
   61color(X,white) :- cg(X,1,w), cg(X,2,w).
   62% if an individual has two w alleles its color is white, i.e., white is
   63% recessive
   64
   65:- end_lpad.

?- prob(color(s,purple),Prob). % what is the probability that the color of s' flowers is purple? % expected result 0.8125 ?- prob(color(s,white),Prob). % what is the probability that the color of s' flowers is white? % expected result 0.1875 ?- prob(cg(s,1,p),Prob). % what is the probability that the color allele on chromosme 1 of s is p? % expected result 0.75 ?- prob(cg(s,1,w),Prob). % what is the probability that the color allele on chromosme 1 of s is w? % expected result 0.25 ?- prob(cg(s,2,p),Prob). % what is the probability that the color allele on chromosme 2 of s is p? % expected result 0.25 ?- prob(cg(s,2,w),Prob). % what is the probability that the color allele on chromosme 2 of s is w? % expected result 0.75 ?- prob(color(s,purple),Prob),bar(Prob,C). % what is the probability that the color of s' flowers is purple? % expected result 0.8125 ?- prob(color(s,white),Prob),bar(Prob,C). % what is the probability that the color of s' flowers is white? % expected result 0.1875 ?- prob(cg(s,1,p),Prob),bar(Prob,C). % what is the probability that the color allele on chromosme 1 of s is p? % expected result 0.75 ?- prob(cg(s,1,w),Prob),bar(Prob,C). % what is the probability that the color allele on chromosme 1 of s is w? % expected result 0.25 ?- prob(cg(s,2,p),Prob),bar(Prob,C). % what is the probability that the color allele on chromosme 2 of s is p? % expected result 0.25 ?- prob(cg(s,2,w),Prob),bar(Prob,C). % what is the probability that the color allele on chromosme 2 of s is w? % expected result 0.75 */