1/*
    2Throwing a coin with uncertainty on its fairness, from
    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.
    6PRISM syntax.
    7*/
    8:- use_module(library(mcintyre)).    9
   10:- if(current_predicate(use_rendering/1)).   11:- use_rendering(c3).   12:- endif.   13
   14:- mc.   15
   16
   17:- begin_lpad.   18values(throw(_),[heads,tails]).
   19:- set_sw(throw(fair),[0.5,0.5]).   20:- set_sw(throw(biased),[0.6,0.4]).   21values(fairness,[fair,biased]).
   22:- set_sw(fairness,[0.9,0.1]).   23
   24res(Coin,R):- toss(Coin),fairness(Coin,Fairness),msw(throw(Fairness),R).
   25fairness(_Coin,Fairness):-msw(fairness,Fairness).
   26toss(coin).
   27
   28:- end_lpad.

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

*/