1/*
    2Program describing the Monty Hall puzzle which gets its name from the TV game 
    3show hosted by Monty Hall. A player is given the opportunity to
    4select one of three closed doors, behind one of which there is a prize. 
    5Behind the other two doors are empty rooms.
    6Once the player has made a selection, Monty is obligated to open one of the 
    7remaining closed doors which does not contain the prize, showing that the room 
    8behind it is empty. He then asks the player if he would like to switch
    9his selection to the other unopened door, or stay with his original choice. 
   10Here is the problem: Does it matter if he switches?
   11From
   12Chitta Baral, Michael Gelfond, and Nelson Rushton. "Probabilistic reasoning with answer sets." Theory and Practice of Logic Programming 9.01 (2009): 57-144.
   13*/
   14:- use_module(library(pita)).   15
   16:- if(current_predicate(use_rendering/1)).   17:- use_rendering(c3).   18:- endif.   19
   20:- pita.   21
   22:- begin_lpad.   23
   24% prize(A): the prize is behind door A, with A in {1,2,3}
   25% selected(A): the player selects door A
   26% open_door(A): Monty opens door A
   27% win_keep: the player wins in case he keeps his selection
   28% win_switch: the player wins in case he switches door
   29
   30
   31prize(1):1/3; prize(2):1/3; prize(3):1/3.
   32% the prize is behind each door with probability 1/3
   33
   34selected(1).
   35% the player selected door 1
   36
   37open_door(A):0.5; open_door(B):0.5:- 
   38  member(A,[1,2,3]),
   39  member(B,[1,2,3]),
   40  A<B,
   41  \+ prize(A),
   42  \+ prize(B),
   43  \+ selected(A),
   44  \+ selected(B).
   45% Monty opens door A with probability 0.5 and door B with probability 0.5 if
   46% A and B are different doors, the prize is not behind any of them and the
   47% player did not select any of them
   48
   49open_door(A):-
   50  member(A,[1,2,3]),
   51  \+ prize(A),
   52  \+ selected(A),
   53  member(B,[1,2,3]),
   54  prize(B),
   55  \+ selected(B).
   56% Monty opens door A with probability 1 if the prize is not behind it, it is
   57% not selected by the player and the prize is behind another door A that is
   58% not selected
   59
   60win_keep:- 
   61  selected(A), 
   62  prize(A).
   63% the player keeps his choice and wins if he has selected a door with the prize
   64
   65win_switch:- 
   66  member(A,[1,2,3]),
   67  \+ selected(A), 
   68  prize(A), 
   69  \+ open_door(A).
   70% the player switches and wins if the prize is behind the door that he has 
   71% not selected and that Monty did not open
   72
   73:- end_lpad.

?- prob(win_keep,Prob). % what is the probability that the player wins if he keeps his choice? % expcted result 0.3333333333333333 ?- prob(win_switch,Prob). % what is the probability that the player wins if he switches door? % expcted result 0.6666666666666667 % the probability if the player switches grows from 1/3 to 1/2 ?- prob(win_keep,Prob),bar(Prob,C). % what is the probability that the player wins if he keeps his choice? % expcted result 0.3333333333333333 ?- prob(win_switch,Prob),bar(Prob,C). % what is the probability that the player wins if he switches door? % the probability if the player switches grows from 1/3 to 1/2 % expcted result 0.6666666666666667 */