1/*
    2Program describing the three-prisoners puzzle. 
    3Of three prisoners a, b, and c, two are to be executed, but a does not know
    4which. Thus, a thinks that the probability that i will be executed is 2/3 for
    5i in {a, b, c}. He says to the jailer, "Since either b or c is certainly going 
    6to be executed, you will give me no information about my own chances if you give
    7the name of one man, either b or c, who is going to be executed." But then, no
    8matter what the jailer says, naive conditioning leads a to believe that his 
    9chance of execution went down from 2/3 to 1/2.
   10From
   11Peter D. Grunwald and Joseph Y. Halpern. "Updating Probabilities." Journal of Artificial Intelligence Research 19 (2003): 243-278.
   12*/
   13:- use_module(library(pita)).   14
   15:- if(current_predicate(use_rendering/1)).   16:- use_rendering(c3).   17:- endif.   18
   19:- pita.   20
   21:- begin_lpad.   22
   23% safe(A): prisoner A is not going to be executed, with A in {a,b,c}
   24% tell_executed(A): the jailer tells a that A is going to be executed
   25% safe_after_tell: a is safe after the jailer has spoken
   26
   27safe(a):1/3; safe(b):1/3; safe(c):1/3.
   28% a, b and c are safe with probability 1/3
   29
   30tell_executed(b):1/2; tell_executed(c):1/2:-
   31  safe(a).
   32% the jailer says that b will be executed with probability 1/2 or c will be
   33% executed with probability 1/2 if a is safe
   34
   35
   36tell_executed(A):-
   37  select(B, [b,c], [A]),
   38  safe(B).
   39% the jailer says that A will be executed with certainty if there is a prisoner
   40% B in {b,c} different from A that is safe
   41
   42tell:-
   43  tell_executed(_).
   44% the jailers speaks if there is a prisoner for which he says that he will be
   45% executed
   46
   47:- end_lpad.

?- prob(safe(a),tell,Prob). % what is the probability that a is not executed after the jailer has spoken % expected result 1/3, means that the jailer communication did not change the % probability of a being safe ?- prob(safe(a),Prob). % what is the probability that a is not executed % expcted result 0.3333333333333333 ?- prob(tell_executed(b),Prob). % what is the probability that the jailer says b is going to be executed? % expcted result 0.5 ?- prob(tell_executed(c),Prob). % what is the probability that the jailer says b is going to be executed? % expcted result 0.5 ?- prob(safe(c),tell_executed(b),Prob). % what is the probability that c is safe % given that he has told b to a % expected result 0.6666 ?- prob(safe(c),Prob). % what is the probability that c is not executed % expcted result 0.3333333333333333 ?- prob(safe(a),tell,Prob),bar(Prob,C). % what is the probability that a is not executed after the jailer has spoken % expected result 1/3, means that the jailer communication did not change the % probability of a being safe ?- prob(safe(a),Prob),bar(Prob,C). % what is the probability that a is not executed % expcted result 0.3333333333333333 ?- prob(tell_executed(b),Prob),bar(Prob,C). % what is the probability that the jailer says b is going to be executed? % expcted result 0.5 ?- prob(tell_executed(c),Prob),bar(Prob,C). % what is the probability that the jailer says b is going to be executed? % expcted result 0.5 ?- prob(safe(c),tell_executed(b),Prob),bar(Prob,C). % what is the probability that c is safe % given that he has told b to a % expected result 0.6666 ?- prob(safe(c),Prob),bar(Prob,C). % what is the probability that c is not executed % expcted result 0.3333333333333333

*/