1/*
    2Throwing two coins with uncertainty on their fairness.
    3J. Vennekens, S. Verbaeten, and M. Bruynooghe. Logic programs with annotated 
    4disjunctions. In International Conference on Logic Programming, 
    5volume 3131 of LNCS, pages 195-209. Springer, 2004.
    6*/
    7:- use_module(library(pita)).    8
    9:- if(current_predicate(use_rendering/1)).   10:- use_rendering(c3).   11:- endif.   12
   13:- pita.   14
   15:- begin_lpad.   16
   17heads(Coin): 0.5; tails(Coin) : 0.5:-toss(Coin),fair(Coin).
   18% if we toss a Coin that is not biased then it lands heads with probability 1/2
   19% and tails with probability 1/2
   20heads(Coin): 0.6 ; tails(Coin) : 0.4:-toss(Coin),biased(Coin).
   21% if we toss a Coin that is biased then it lands heads with probability 0.6
   22% % and tails with probability 0.4
   23fair(Coin):0.9 ; biased(Coin):0.1.
   24% a Coin is fair with probability 0.9 and biased with probability 0.1
   25toss(coin1).
   26% coin1 is certainly tossed
   27toss(coin2).
   28% coin2 is certainly tossed
   29
   30:- end_lpad.

?- prob(heads(coin2),Prob). % what is the probability that coin1 lands heads? % expected result 0.51 ?- prob(tails(coin2),Prob). % what is the probability that coin1 lands tails? % expected result 0.49 ?- prob(heads(coin1),Prob). % what is the probability that coin2 lands heads? % expected result 0.51 ?- prob(tails(coin1),Prob). % what is the probability that coin2 lands tails? % expected result 0.49 ?- prob(heads(coin2),Prob),bar(Prob,C). % what is the probability that coin1 lands heads? % expected result 0.51 ?- prob(tails(coin2),Prob),bar(Prob,C). % what is the probability that coin1 lands tails? % expected result 0.49 ?- prob(heads(coin1),Prob),bar(Prob,C). % what is the probability that coin2 lands heads? % expected result 0.51 ?- prob(tails(coin1),Prob),bar(Prob,C). % what is the probability that coin2 lands tails? % expected result 0.49

*/