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.
    6*/
    7:- use_module(library(mcintyre)).    8
    9:- if(current_predicate(use_rendering/1)).   10:- use_rendering(c3).   11:- endif.   12:- mc.   13:- begin_lpad.   14
   15heads(Coin): 1/2; tails(Coin) : 1/2:-toss(Coin),\+biased(Coin).
   16% if we toss a Coin that is not biased then it lands heads with probability 1/2
   17% and tails with probability 1/2
   18heads(Coin): 0.6 ; tails(Coin) : 0.4:-toss(Coin),biased(Coin).
   19% if we toss a Coin that is biased then it lands heads with probability 0.6
   20% % and tails with probability 0.4
   21fair(Coin):0.9 ; biased(Coin):0.1.
   22% a Coin is fair with probability 0.9 and biased with probability 0.1
   23toss(coin).
   24% coin is certainly tossed
   25
   26:- end_lpad.

?- mc_prob(heads(coin),Prob). % what is the probability that coin lands heads? % expected result 0.51 ?- mc_prob(tails(coin),Prob). % what is the probability that coin lands tails? % expected result 0.49 ?- mc_prob(heads(coin),Prob,[bar(C)]). % what is the probability that coin lands heads? % expected result 0.51 ?- mc_prob(tails(coin),Prob),bar(Prob,C). % what is the probability that coin lands tails? % expected result 0.49 ?- mc_sample(heads(coin),1000,Prob,[successes(T),failures(F)]),bar(T,F,C). % take 1000 sample of heads(coin) and return the number of successes (T), % the number of failures (F) and the probability

?- mc_sample(tails(coin),1000,Prob,[successes(T),failures(F)]). % take 1000 sample of tails(coin) and return the number of successes (T), % the number of failures (F) and the probability

?- mc_sample(heads(coin),1000,Prob). % take 1000 sample of heads(coin) and return the probability

?- mc_sample(tails(coin),1000,Prob). % take 1000 sample of tails(coin) and return the probability

?- mc_sample(heads(coin),1000,Prob),bar(Prob,C). % take 1000 sample of heads(coin) and chart the number of successes and % faliures

?- mc_sample(tails(coin),1000,Prob),bar(Prob,C). % take 1000 sample of tails(coin) and chart the number of successes and % faliures

?- mc_rejection_sample(heads(coin),biased(coin),1000,P,[successes(S),failures(F)]). % take 1000 sample of heads(coin) given that biased(coin) is true % Use rejection sampling % F = 387, % P = 0.613, % S = 613 */