
Tic Tac Toe Simulation: The Intelligent Minimax Algorithm

Peter Prevos |
1113 words | 6 minutes
Share this content
One of my favourite movies is WarGames. One of the most memorable scenes is where the protagonist tries to teach the out-of-control AI that a nuclear war is unwinnable with a Tic Tac Toe simulation.
Tic Tac Toe might be a futile children's game but it can also teach us about artificial intelligence. Tic Tac Toe, or Noughts and Crosses, is a zero-sum game with perfect information. Both players have full information about each other. When nobody makes a mistake, the game always ends in a draw.
This article describes how to self-playing game of Tic Tac Toe, complete with a graphical interface, in the R language. This article is part of a series about computer games in the R Language.
The first two parts of the article describe how to create the user interface and add a human player. The second part delves into creating computer players. My ultimate aim is to recreate this iconic scene in the WarGames movie.
The Game Board
This first code snippet draws the Tic Tac Toe simulation board. The variable xo
holds the identity of the pieces and the vector board
holds the current game. The game board is a vector of length nine consisting of either -1 (X), 0 (empty field) or 1 (O). The vector indices correspond with locations on the game board:
1 2 3
4 5 6
7 8 9
The second part of the code checks for three in a row and draws the corresponding line.
## Tic Tac Toe Simulation in the R language
## Peter Prevos
## lucidmanager.org
draw.board <- function(game) {
xo <- c("X", " ", "O") # Symbols
par(mar = rep(1,4))
plot.new()
plot.window(xlim = c(0,30), ylim = c(0,30))
abline(h = c(10, 20), col = "darkgrey", lwd = 4)
abline(v = c(10, 20), col = "darkgrey", lwd = 4)
text(rep(c(5, 15, 25), 3), c(rep(25, 3), rep(15,3), rep(5, 3)),
xo[game + 2], cex = 4)
# Identify location of any three in a row
square <- matrix(game, nrow = 3, byrow = TRUE)
hor <- abs(rowSums(square))
if (any(hor == 3))
hor <- (4 - which(hor == 3)) * 10 - 5
else
hor <- 0
ver <- abs(colSums(square))
if (any(ver == 3))
ver <- which(ver == 3) * 10 - 5
else
ver <- 0
diag1 <- sum(diag(square))
diag2 <- sum(diag(t(apply(square, 2, rev))))
# Draw winning lines
if (all(hor > 0))
for (i in hor)
lines(c(0, 30), rep(i, 2), lwd = 10, col="red")
if (all(ver > 0))
for (i in ver)
lines(rep(i, 2), c(0, 30), lwd = 10, col="red")
if (abs(diag1) == 3)
lines(c(2, 28), c(28, 2), lwd = 10, col = "red")
if (abs(diag2) == 3)
lines(c(2, 28), c(2, 28), lwd = 10, col = "red")
}
Human Player
This second code snippet lets a human player move by clicking anywhere on the graphic display using the locator function. The click location is converted to a number to denote the position on the board. The entered field is only accepted if it has not yet been used (the empty
variable contains the available fields).
move.human <- function(game) {
text(4, 0, "Click on screen to move", col = "grey", cex=.7)
empty <- which(game == 0)
move <- 0
while (!move %in% empty) {
coords <- locator(n = 1) # add lines
coords$x <- floor(abs(coords$x) / 10) + 1
coords$y <- floor(abs(coords$y) / 10) + 1
move <- coords$x + 3 * (3 - coords$y)
}
return(move)
}
Computer Player
The computer uses a modified Minimax Algorithm to determine its next move. This article from the Never Stop Building blog explains this method in great detail.
If the computer moves first, the algorithm takes a while because of the large number of permutations. There are 255,168 possible legal games in Tic Tac Toe, 46,080 (18%) of which end in a draw.
The code for this part is contributed by a reader (see comments below). I originally made a mistake in the recurring function and Alberto was so kind to contribute a correct version.
The ganador (Spanish for winning) function assesses the board condition by assigning -10 or + 10 for a winning game and 0 for any other situation.
The minimax function returns a list with the move and its valuation through the ganador function. The function calls itself until it has filled the board and retains the best scoring move using the minimax method. Random variables are added to avoid the computer always playing the same move in the same situation.
## Minimax code by Alberto C.
ganador <- function(juego, player) {
game <- matrix(juego, nrow = 3, byrow = T)
hor <- rowSums(game)
ver <- colSums(game)
diag <- c(sum(diag(game)), sum(diag(apply(game, 1, rev))))
if (-3 %in% c(hor, ver, diag))
return(-10)
if (3 %in% c(hor, ver, diag))
return(10)
else
return(0)
}
minimax <- function(juego, player) {
free <- which(juego == 0)
if(length(free) == 1) {
juego[free] <- player
return(list(move = free, U = ganador(juego, player)))
}
poss.results <- rep(0, 9)
for(i in free) {
game <- juego
game[i] <- player
poss.results[i] <- ganador(game, player)
}
mm <- ifelse(player == -1, "which.min", "which.max")
if(any(poss.results == (player * 10))) {
move <- do.call(mm, list(poss.results))
return(list(move = move, U = poss.results[move]))
}
for(i in free) {
game <- juego
game[i] <- player
poss.results[i] <- minimax(game, -player)$U
}
random <- runif(9, 0, 0.1)
poss.results[-free] <- 100 * -player
poss.results <- poss.results + (player * random)
move <- do.call(mm, list(poss.results))
return(list(move = move, U = poss.results[move]))
}
Play Tic Tac Toe
The last bit of code defines a function to play the game. Each layer can be either a human or a computer. The function loops while there are still empty spots on the board and no winner is declared.
tic.tac.toe <- function(player1 = "human", player2 = "computer") {
game <- rep(0, 9) # Empty board
winner <- 0 # Define winner
player <- 1 # First player
players <- c(player1, player2)
draw.board(game)
while (0 %in% game & winner == 0) { # Keep playing until win or full board
if (players[(player + 3) %% 3] == "human") # Human player
move <- move.human(game)
else { # Computer player
move <- minimax(game, player)[[1]]
}
game[move] <- player # Change board
draw.board(game)
winner <- ganador(game, player)
player <- -player # Change player
}
if (winner == 0)
text(15, 15 , "DRAW", col = "red", cex = 10)
}
tic.tac.toe()
Share this content