Monty Hall problem
You are encouraged to solve this task according to the task description, using any language you may know.
Run random simulations of the Monty Hall game. Show the effects of a strategy of the contestant always keeping his first guess so it can be contrasted with the strategy of the contestant always switching his guess.
- Suppose you're on a game show and you're given the choice of three doors. Behind one door is a car; behind the others, goats. The car and the goats were placed randomly behind the doors before the show. The rules of the game show are as follows: After you have chosen a door, the door remains closed for the time being. The game show host, Monty Hall, who knows what is behind the doors, now has to open one of the two remaining doors, and the door he opens must have a goat behind it. If both remaining doors have goats behind them, he chooses one randomly. After Monty Hall opens a door with a goat, he will ask you to decide whether you want to stay with your first choice or to switch to the last remaining door. Imagine that you chose Door 1 and the host opens Door 3, which has a goat. He then asks you "Do you want to switch to Door Number 2?" Is it to your advantage to change your choice? (Krauss and Wang 2003:10)
Note that the player may initially choose any of the three doors (not just Door 1), that the host opens a different door revealing a goat (not necessarily Door 3), and that he gives the player a second choice between the two remaining unopened doors.
Simulate at least a thousand games using three doors for each strategy and show the results in such a way as to make it easy to compare the effects of each strategy.
Ada
<Ada> -- Monty Hall Game
with Ada.Text_Io; use Ada.Text_Io; with Ada.Float_Text_Io; use Ada.Float_Text_Io; with ada.Numerics.Discrete_Random;
procedure Monty_Stats is
Num_Iterations : Positive := 100000; type Action_Type is (Stay, Switch); type Prize_Type is (Goat, Pig, Car); type Door_Index is range 1..3; package Random_Prize is new Ada.Numerics.Discrete_Random(Door_Index); use Random_Prize; Seed : Generator; Doors : array(Door_Index) of Prize_Type; procedure Set_Prizes is Prize_Index : Door_Index; Booby_Prize : Prize_Type := Goat; begin Reset(Seed); Prize_Index := Random(Seed); Doors(Prize_Index) := Car; for I in Doors'range loop if I /= Prize_Index then Doors(I) := Booby_Prize; Booby_Prize := Prize_Type'Succ(Booby_Prize); end if; end loop; end Set_Prizes; function Play(Action : Action_Type) return Prize_Type is Chosen : Door_Index := Random(Seed); Monty : Door_Index; begin Set_Prizes; for I in Doors'range loop if I /= Chosen and Doors(I) /= Car then Monty := I; end if; end loop; if Action = Switch then for I in Doors'range loop if I /= Monty and I /= Chosen then Chosen := I; exit; end if; end loop; end if; return Doors(Chosen); end Play; Winners : Natural; Pct : Float;
begin
Winners := 0; for I in 1..Num_Iterations loop if Play(Stay) = Car then Winners := Winners + 1; end if; end loop; Put("Stay : count" & Natural'Image(Winners) & " = "); Pct := Float(Winners * 100) / Float(Num_Iterations); Put(Item => Pct, Aft => 2, Exp => 0); Put_Line("%"); Winners := 0; for I in 1..Num_Iterations loop if Play(Switch) = Car then Winners := Winners + 1; end if; end loop; Put("Switch : count" & Natural'Image(Winners) & " = "); Pct := Float(Winners * 100) / Float(Num_Iterations); Put(Item => Pct, Aft => 2, Exp => 0); Put_Line("%");
end Monty_Stats; </Ada> Results
Stay : count 34308 = 34.31% Switch : count 65695 = 65.69%
AWK
#!/bin/gawk -f # Monty Hall problem BEGIN { srand() doors = 3 iterations = 10000 # Behind a door: EMPTY = "empty"; PRIZE = "prize" # Algorithm used KEEP = "keep"; SWITCH="switch"; RAND="random"; # } function monty_hall( choice, algorithm ) { # Set up doors for ( i=0; i<doors; i++ ) { door[i] = EMPTY } # One door with prize door[int(rand()*doors)] = PRIZE chosen = door[choice] del door[choice] #if you didn't choose the prize first time around then # that will be the alternative alternative = (chosen == PRIZE) ? EMPTY : PRIZE if( algorithm == KEEP) { return chosen } if( algorithm == SWITCH) { return alternative } return rand() <0.5 ? chosen : alternative } function simulate(algo){ prizecount = 0 for(j=0; j< iterations; j++){ if( monty_hall( int(rand()*doors), algo) == PRIZE) { prizecount ++ } } printf " Algorithm %7s: prize count = %i, = %6.2f%%\n", \ algo, prizecount,prizecount*100/iterations } BEGIN { print "\nMonty Hall problem simulation:" print doors, "doors,", iterations, "iterations.\n" simulate(KEEP) simulate(SWITCH) simulate(RAND) }
Sample output:
bash$ ./monty_hall.awk Monty Hall problem simulation: 3 doors, 10000 iterations. Algorithm keep: prize count = 3411, = 34.11% Algorithm switch: prize count = 6655, = 66.55% Algorithm random: prize count = 4991, = 49.91% bash$
BASIC
<qbasic>RANDOMIZE TIMER DIM doors(3) '0 is a goat, 1 is a car CLS switchWins = 0 stayWins = 0 FOR plays = 0 TO 32767 winner = INT(RND * 3) + 1 doors(winner) = 1'put a winner in a random door choice = INT(RND * 3) + 1'pick a door, any door DO shown = INT(RND * 3) + 1 'don't show the winner or the choice LOOP WHILE doors(shown) <> 1 AND shown <> choice stayWins = stayWins + doors(choice) 'if you won by staying, count it 'could have switched to win IF doors(choice) = 0 THEN switchWins = switchWins + 1 END IF doors(winner) = 0 'clear the doors for the next test NEXT plays PRINT "Switching wins"; switchWins; "times." PRINT "Staying wins"; stayWins; "times."</qbasic> Output:
Switching wins 21805 times. Staying wins 10963 times.
Fortran
PROGRAM MONTYHALL IMPLICIT NONE INTEGER, PARAMETER :: trials = 10000 INTEGER :: i, choice, prize, remaining, show, staycount = 0, switchcount = 0 LOGICAL :: door(3) REAL :: rnum CALL RANDOM_SEED DO i = 1, trials door = .FALSE. CALL RANDOM_NUMBER(rnum) prize = INT(3*rnum) + 1 door(prize) = .TRUE. ! place car behind random door CALL RANDOM_NUMBER(rnum) choice = INT(3*rnum) + 1 ! choose a door DO CALL RANDOM_NUMBER(rnum) show = INT(3*rnum) + 1 IF (show /= choice .AND. show /= prize) EXIT ! Reveal a goat END DO SELECT CASE(choice+show) ! Calculate remaining door index CASE(3) remaining = 3 CASE(4) remaining = 2 CASE(5) remaining = 1 END SELECT IF (door(choice)) THEN ! You win by staying with your original choice staycount = staycount + 1 ELSE IF (door(remaining)) THEN ! You win by switching to other door switchcount = switchcount + 1 END IF END DO WRITE(*, "(A,F6.2,A)") "Chance of winning by not switching is", real(staycount)/trials*100, "%" WRITE(*, "(A,F6.2,A)") "Chance of winning by switching is", real(switchcount)/trials*100, "%" END PROGRAM MONTYHALL
Sample Output
Chance of winning by not switching is 32.82% Chance of winning by switching is 67.18%
Haskell
import System.Random (StdGen, getStdGen, randomR) trials :: Int trials = 10000 data Door = Car | Goat deriving Eq play :: Bool -> StdGen -> (Door, StdGen) play switch g = (prize, new_g) where (n, new_g) = randomR (0, 2) g d1 = [Car, Goat, Goat] !! n prize = case switch of False -> d1 True -> case d1 of Car -> Goat Goat -> Car cars :: Int -> Bool -> StdGen -> (Int, StdGen) cars n switch g = f n (0, g) where f 0 (cs, g) = (cs, g) f n (cs, g) = f (n - 1) (cs + result, new_g) where result = case prize of Car -> 1; Goat -> 0 (prize, new_g) = play switch g main = do g <- getStdGen let (switch, g2) = cars trials True g (stay, _) = cars trials False g2 putStrLn $ msg "switch" switch putStrLn $ msg "stay" stay where msg strat n = "The " ++ strat ++ " strategy succeeds " ++ percent n ++ "% of the time." percent n = show $ round $ 100 * (fromIntegral n) / (fromIntegral trials)
With a State monad, we can avoid having to explicitly pass around the StdGen so often. play and cars can be rewritten as follows:
import Control.Monad.State play :: Bool -> State StdGen Door play switch = do i <- rand let d1 = [Car, Goat, Goat] !! i return $ case switch of False -> d1 True -> case d1 of Car -> Goat Goat -> Car where rand = do g <- get let (v, new_g) = randomR (0, 2) g put new_g return v cars :: Int -> Bool -> StdGen -> (Int, StdGen) cars n switch g = (numcars, new_g) where numcars = length $ filter (== Car) prize_list (prize_list, new_g) = runState (replicateM n (play switch)) g
Sample output (for either implementation):
The switch strategy succeeds 67% of the time. The stay strategy succeeds 34% of the time.
Java
<java>import java.util.Random; public class Monty{ public static void main(String[] args){ int[] doors = {0,0,0};//0 is a goat, 1 is a car int switchWins = 0; int stayWins = 0; Random gen = new Random(); for(int plays = 0;plays < 32768;plays++ ){ doors[gen.nextInt(3)] = 1;//put a winner in a random door int choice = gen.nextInt(3); //pick a door, any door int shown; //the shown door do{ shown = gen.nextInt(3); //don't show the winner or the choice }while(doors[shown] != 1 && shown != choice);
stayWins += doors[choice];//if you won by staying, count it
//could have switched to win switchWins += (doors[choice] == 0)? 1: 0; doors = new int[3];//clear the doors for the next test } System.out.println("Switching wins " + switchWins + " times."); System.out.println("Staying wins " + stayWins + " times."); } }</java> Output:
Switching wins 21924 times. Staying wins 10844 times.
MAXScript
fn montyHall choice switch = ( doors = #(false, false, false) doors[random 1 3] = true chosen = doors[choice] if switch then chosen = not chosen chosen ) fn iterate iterations switched = ( wins = 0 for i in 1 to iterations do ( if (montyHall (random 1 3) switched) then ( wins += 1 ) ) wins * 100 / iterations as float ) iterations = 10000 format ("Stay strategy:%\%\n") (iterate iterations false) format ("Switch strategy:%\%\n") (iterate iterations true)
Output:
Stay strategy:33.77% Switch strategy:66.84%
OCaml
<ocaml>let trials = 10000
type door = Car | Goat
let play switch =
let n = Random.int 3 in let d1 = [|Car; Goat; Goat|].(n) in if not switch then d1 else match d1 with Car -> Goat | Goat -> Car
let cars n switch =
let total = ref 0 in for i = 1 to n do let prize = play switch in if prize = Car then incr total done; !total
let () =
let switch = cars trials true and stay = cars trials false in let msg strat n = Printf.printf "The %s strategy succeeds %f%% of the time.\n" strat (100. *. (float n /. float trials)) in msg "switch" switch; msg "stay" stay</ocaml>
Perl
<perl>my $trials = 10_000;
sub play
- Takes a boolean saying whether to swtich doors; returns
- a boolean saying whether the result was a car.
{my $door1 = !int(rand 3); $_[0] ? !$door1 : $door1;}
sub msg
{print "The $_[0] strategy succeeds ", 100 * $_[1]/$trials, "% of the time.\n";}
sub count {scalar @_}
msg 'switch', count grep({$_} map {play 1} (1 .. $trials)); msg 'stay', count grep({$_} map {play 0} (1 .. $trials));</perl>
Sample output:
The switch strategy succeeds 66.44% of the time. The stay strategy succeeds 32.13% of the time.
Python
<python> I could understand the explanation of the Monty Hall problem but needed some more evidence
References:
http://www.bbc.co.uk/dna/h2g2/A1054306 http://en.wikipedia.org/wiki/Monty_Hall_problem especially: http://en.wikipedia.org/wiki/Monty_Hall_problem#Increasing_the_number_of_doors
from random import randrange, shuffle
doors, iterations = 3,100000 # could try 100,1000
def monty_hall(choice, switch=False, doorCount=doors):
# Set up doors door = [False]*doorCount # One door with prize door[randrange(0, doorCount)] = True
chosen = door[choice]
unpicked = door del unpicked[choice]
# Out of those unpicked, the alternative is either: # the prize door, or # an empty door if the initial choice is actually the prize. alternative = True in unpicked
if switch: return alternative else: return chosen
print "\nMonty Hall problem simulation:" print doors, "doors,", iterations, "iterations.\n"
print "Not switching allows you to win", print [monty_hall(randrange(3), switch=False)
for x in range(iterations)].count(True),
print "out of", iterations, "times." print "Switching allows you to win", print [monty_hall(randrange(3), switch=True)
for x in range(iterations)].count(True),
print "out of", iterations, "times.\n" </python> Sample output:
Monty Hall problem simulation: 3 doors, 100000 iterations. Not switching allows you to win 33337 out of 100000 times. Switching allows you to win 66529 out of 100000 times.
R
# Since R is a vector based language that penalizes for loops, we will avoid # for-loops, instead using "apply" statement variants (like "map" in other # functional languages). set.seed(19771025) # set the seed to set the same results as this code N <- 10000 # trials true_answers <- sample(1:3, N, replace=TRUE) # We can assme that the contestant always choose door 1 without any loss of # generality, by equivalence. That is, we can always relabel the doors # to make the user-chosen door into door 1. # Thus, the host opens door '2' unless door 2 has the prize, in which case # the host opens door 3. host_opens <- 2 + (true_answers == 2) other_door <- 2 + (true_answers != 2) ## if always switch summary( other_door == true_answers ) ## if we never switch summary( true_answers == 1) ## if we randomly switch random_switch <- other_door random_switch[runif(N) >= .5] <- 1 summary(random_switch == true_answers)
## To go with the exact parameters of the Rosetta challenge, complicating matters.... ## Note that the player may initially choose any of the three doors (not just Door 1), ## that the host opens a different door revealing a goat (not necessarily Door 3), and ## that he gives the player a second choice between the two remaining unopened doors. N <- 10000 #trials true_answers <- sample(1:3, N, replace=TRUE) user_choice <- sample(1:3, N, replace=TRUE) ## the host_choice is more complicated host_chooser <- function(user_prize) { # this could be cleaner bad_choices <- unique(user_prize) # in R, the x[-vector] form implies, choose the indices in x not in vector choices <- c(1:3)[-bad_choices] # if the first arg to sample is an int, it treats it as the number of choices if (length(choices) == 1) { return(choices)} else { return(sample(choices,1))} } host_choice <- apply( X=cbind(true_answers,user_choice), FUN=host_chooser,MARGIN=1) not_door <- function(x){ return( (1:3)[-x]) } # we could also define this # directly at the FUN argument following other_door <- apply( X = cbind(user_choice,host_choice), FUN=not_door, MARGIN=1) ## if always switch summary( other_door == true_answers ) ## if we never switch summary( true_answers == user_choice) ## if we randomly switch random_switch <- user_choice change <- runif(N) >= .5 random_switch[change] <- other_door[change] summary(random_switch == true_answers)
## AUTHOR: Gregg Lind <gregg.lind @ gmail.com> ## Date: 9/13/2008 ## Purpose: Two variations on the Monty Hall problem written in R
Results: > ## if always switch > summary( other_door == true_answers ) Mode FALSE TRUE logical 3298 6702 > ## if we never switch > summary( true_answers == 1) Mode FALSE TRUE logical 6702 3298 > ## if we randomly switch > summary(random_switch == true_answers) Mode FALSE TRUE logical 5028 4972 > ## if always switch > summary( other_door == true_answers ) Mode FALSE TRUE logical 3295 6705 > ## if we never switch > summary( true_answers == user_choice) Mode FALSE TRUE logical 6705 3295 > ## if we randomly switch > summary(random_switch == true_answers) Mode FALSE TRUE logical 4986 5014
Scheme
<scheme> (define (random-from-list list) (list-ref list (random (length list)))) (define (random-permutation list)
(if (null? list) '() (let* ((car (random-from-list list)) (cdr (random-permutation (remove car list)))) (cons car cdr))))
(define (random-configuration) (random-permutation '(goat goat car))) (define (random-door) (random-from-list '(0 1 2)))
(define (trial strategy)
(define (door-with-goat-other-than door strategy) (cond ((and (not (= 0 door)) (equal? (list-ref strategy 0) 'goat)) 0) ((and (not (= 1 door)) (equal? (list-ref strategy 1) 'goat)) 1) ((and (not (= 2 door)) (equal? (list-ref strategy 2) 'goat)) 2))) (let* ((configuration (random-configuration)) (players-first-guess (strategy `(would-you-please-pick-a-door?))) (door-to-show-player (door-with-goat-other-than players-first-guess configuration)) (players-final-guess (strategy `(there-is-a-goat-at/would-you-like-to-move? ,door-to-show-player)))) (if (equal? (list-ref configuration players-final-guess) 'car) 'you-win! 'you-lost)))
(define (stay-strategy message)
(let ((first-choice (random-door))) (case (car message) ((would-you-please-pick-a-door?) first-choice) ((there-is-a-goat-at/would-you-like-to-move?) first-choice))))
(define (switch-strategy message)
(let ((first-choice (random-door))) (case (car message) ((would-you-please-pick-a-door?) first-choice) ((there-is-a-goat-at/would-you-like-to-move?) (car (remove first-choice (remove (cadr message) '(0 1 2))))))))
(define-syntax repeat
(syntax-rules () ((repeat <n> <body> ...) (let loop ((i <n>)) (if (zero? i) '() (cons ((lambda () <body> ...)) (loop (- i 1))))))))
(define (count element list)
(if (null? list) 0 (if (equal? element (car list)) (+ 1 (count element (cdr list))) (count element (cdr list)))))
(define (prepare-result strategy results)
`(,strategy won with probability ,(exact->inexact (* 100 (/ (count 'you-win! results) (length results)))) %))
(define (compare-strategies times)
(append (prepare-result 'stay-strategy (repeat times (trial stay-strategy))) '(and) (prepare-result 'switch-strategy (repeat times (trial switch-strategy)))))
- > (compare-strategies 1000000)
- (stay-strategy won with probability 33.3638 %
- and switch-strategy won with probability 51.8763 %)
</scheme>