CSE301

Lab 6 (laziness and infinite objects)

General instructions

Some header magic

-- setting the "warn-incomplete-patterns" flag asks GHC to warn you
-- about possible missing cases in pattern-matching definitions
{-# OPTIONS_GHC -fwarn-incomplete-patterns #-}

-- see https://wiki.haskell.org/Safe_Haskell
{-# LANGUAGE Safe #-}

module Lab6 where

import Data.List
import Data.Tree

import System.Random

import Types
-- import DomViz
{- Uncomment the above line if you want to use the visualization routines. -}

Background

The game of Domineering

Domineering is a two-player strategy game that can be played over any shape board composed out of some collection of squares. Players alternate taking turns placing dominoes on the board to cover up a pair of squares, with one player (which we will refer to as “H”) always placing them horizontally, and the other player (“V”) always placing them vertically. The first player who cannot make a move loses.

For example, below is the full record of a game played on a 4x4 board, with H playing first in round 1 and winning in round 8, since V has nowhere left to place a domino.

Here is another example of a game on a 5x5 board, where this time H loses in round 13. (We give only the abbreviated transcript of the game, showing the final position and the labelling of the moves by round.)

A Domineering board does not necessarily have to be square. For example, here we see the transcript of a game on a board with two columns and nine rows.

Nor does the board have to be contiguous. Here are some games played on crosshatch-shaped boards of different sizes:

Recent developments

In 2019, one of the most remarkable games in Domineering history was played between Alpha Dom and Lee Sedom (as recounted in this award-winning documentary). Below we show the transcript of this historic game (where Alpha Dom claimed victory in round 28), as well as the transcript of another game demonstrating Alpha Dom’s mastery over a much lower-skilled opponent.

Alpha Dom vs Lee Sedom (2019):

Alpha Dom vs Ran Dom (2019):

Representing the game

In this lab, you will be tasked with writing various functions related to playing the game of Domineering.

Let’s begin by establishing the basic representation for players, moves, and boards.

data Player = H | V
  deriving (Eq, Ord, Show)

type Cell = (Int, Int)

data Board = Board { turn :: Player, free :: [Cell], hist :: [Cell] }
  deriving (Eq, Show)

A board is represented by a record containing three fields:

We do not make any type distinction between “squares” and “moves”: both are represented by values of type Cell, this being a synonym for the type (Int, Int) of two-dimensional integer coordinates. However, when we indicate a move by a cell, this is always interpreted as referring to the coordinate of the lower left corner of the domino.

For example, consider this board:

board4x4_3 = Board { turn = H,
                     free = [(1,1),(1,2),(2,2),(2,3),(2,4),(3,2),(3,3),(3,4),(4,1),(4,2),(4,3),(4,4)],
                     hist = [(1,3),(2,1)] }

Here we have assigned coordinates to the cells ranging from (1,1) for the lower left square to (4,4) for the upper right square. In round 1, H plays a horizontal domino at (2,1), which also occupies the cell (3,1). In round 2, V plays a vertical domino at (1,3), which also occupies the cell (1,4). (Note our visualization conventions are that the x coordinate increases as we move rightwards across the board, and the y coordinate increases as we move upwards across the board.)

The following utility functions will be useful:

-- given a cell c and a player p, compute the adjacent cell c'
-- that is also occupied if p plays a domino at c
adjCell :: Cell -> Player -> Cell
adjCell (x,y) H = (x+1,y)
adjCell (x,y) V = (x,y+1)

-- compute the opponent of a player
opp :: Player -> Player
opp H = V
opp V = H

-- determine whether a move is valid in a given board
valid :: Board -> Cell -> Bool
valid b c = c `elem` free b && adjCell c (turn b) `elem` free b

You may also wish to experiment using the following functions that construct boards of different shapes.

-- create an empty board from an arbitrary list of cells
empty :: [Cell] -> Board
empty cs = Board { turn = H, free = cs, hist = [] }

-- create a rectangular board of arbitrary dimensions
board :: Int -> Int -> Board
board maxx maxy = empty [(x,y) | x <- [1..maxx], y <- [1..maxy]]

-- create a crosshatch-shaped square board of arbitrary dimension
hatch :: Int -> Board
hatch n = empty [(x,y) | x <- [1..2*n+1], y <- [1..2*n+1], odd y || x == 1 || x == (2*n+1) || odd x]

Visualization

As already mentioned, you can uncomment the line import DomViz in order to get some functions for visualizing Domineering games, which were programmed using the diagrams library for Haskell. You are not obligated to use this module, but if you want to understand what it provides the following is a description. The file DomViz.hs begins with the following lines:

{-# LANGUAGE Trustworthy #-}

module DomViz (boardSVG, boardSVG', gametreeSVG, gametreeSVG') where

The first line is just a language pragma asserting that it is okay to import this module in Safe Haskell. The second (non-empty) line is more important: it gives a name to the module and tells the compiler to export four of the definitions from the file. If we had instead written

module DomViz where

then the compiler would export all of the definitions in the file, and we would see them whenever we do an import DomViz. Thus, giving an explicit list of exports when defining a module helps to provide a bit of encapsulation.

Anyways, the pair of functions

boardSVG :: Board -> FilePath -> IO ()
gametreeSVG :: Tree Board -> FilePath -> IO ()

behave as follows. Given a board b and a file path (= string) basename, the command boardSVG b basename creates an SVG file named basename ++ ".svg" containing a graphical representation of b. For example, after introducing the definitions:

alphaDom_vs_LeeSedom =
  Board { turn = V,
          free = [(-4,1),(-4,3),(-2,0),(-2,4),(2,1),(2,4),(3,-4),(3,4),(4,-2),(4,0)],
          hist = [(0,4),(4,1),(0,-4),(-4,-3),(-1,-2),(2,-1),(-2,-4),(-4,-1),(-1,2),(4,3),(1,2),(-2,2),(-4,-4),(-2,-2),(2,-2),(4,-4),(-3,1),(2,-4),(-4,4),(-1,3),(-4,2),(-3,-2),(3,-1),(1,-3),(-2,-3),(3,1),(1,3)] }

alphaDom_vs_RanDom =
  Board { turn = V,
          free = [(-4,-3),(-4,0),(-2,-4),(-2,-2),(-1,-4),(-1,-2),(-1,2),(-1,4),(0,-4),(0,-2),(0,2),(0,4),(1,-4),(1,-2),(1,2),(1,4),(2,-4),(2,-2),(2,4),(3,-4),(4,0),(4,3)],
          hist = [(-3,4),(2,-1),(-3,2),(4,-2),(-4,-4),(-4,3),(3,4),(2,1),(-3,1),(3,1),(-4,-1),(-2,-1),(-2,3),(-4,1),(1,3),(4,-4),(-4,-2),(4,1),(1,-3),(3,-2),(-2,-3)] }

visualizations for the two recent victories by Alpha Dom that we mentioned above can be created by running the following commands:

> boardSVG alphaDom_vs_LeeSedom "alphadom-vs-leesedom"
> boardSVG alphaDom_vs_RanDom "alphadom-vs-random"

Similarly, given a game tree t and a string basename, the command gametreeSVG t basename creates an SVG file named basename ++ ".svg" containing a graphical representation of t. We will give a demonstration of this below.

The DomViz module also exports a related pair of functions:

boardSVG' :: Double -> Board -> String -> IO ()
gametreeSVG' :: Double -> Tree (Board, String) -> String -> IO ()

Both take an extra scale factor as first input, in case you want to grow or shrink the SVG graphics, and gametreeSVG' takes a game tree where each node has been annotated with a label. Note that boardSVG and gametreeSVG are defined by boardSVG = boardSVG' 1 and gametreeSVG = gametreeSVG' 1 . fmap (\b -> (b,"")) respectively.


Implementing basic gameplay

The first group of questions involves determining what moves are legal, performing legal moves, and “undoing” moves to recover the full record of a game.

Write a function

-- Exercise 1a
legalMoves :: Player -> Board -> [Cell]
legalMoves = undefined

that returns the list of all legal moves for a player on a given board. Note that here we mean the legal moves for either player, regardless of whether it is that player’s turn to play.

> legalMoves H board4x4_3
[(1,2),(2,2),(2,3),(2,4),(3,2),(3,3),(3,4)]
> legalMoves V board4x4_3
[(1,1),(2,2),(2,3),(3,2),(3,3),(4,1),(4,2),(4,3)]

Write a function

-- Exercise 1b
moveLegal :: Board -> Cell -> Board
moveLegal = undefined

that takes a board and a legal move for the player whose turn it is to play, and returns the new board resulting from executing that play. If the move is actually illegal for the current player, then the behavior of moveLegal is unspecified.

> moveLegal board4x4_3 (2,3)
Board {turn = V, free = [(1,1),(1,2),(2,2),(2,4),(3,2),(3,4),(4,1),(4,2),(4,3),(4,4)], hist = [(2,3),(1,3),(2,1)]}

Write a function

-- Exercise 1c
replay :: Board -> [Board]
replay = undefined

that takes a board with some possibly non-empty history of moves, and returns the full record of the game leading up to that position, starting from an initially empty board.

> replay board4x4_3
[Board {turn = H, free = [(1,1),(1,2),(2,2),(2,3),(2,4),(3,2),(3,3),(3,4),(4,1),(4,2),(4,3),(4,4),(1,3),(1,4),(2,1),(3,1)], hist = []},Board {turn = V, free = [(1,1),(1,2),(2,2),(2,3),(2,4),(3,2),(3,3),(3,4),(4,1),(4,2),(4,3),(4,4),(1,3),(1,4)], hist = [(2,1)]},Board {turn = H, free = [(1,1),(1,2),(2,2),(2,3),(2,4),(3,2),(3,3),(3,4),(4,1),(4,2),(4,3),(4,4)], hist = [(1,3),(2,1)]}]

Game trees and strategies

The second group of questions are about playing optimally using the minimax rule on game trees.

Representing game trees

A game tree is a mathematical representation of all possible evolutions of a game starting from an initial position. For example, the following is a depiction of the first two levels of the game tree for Tic Tac Toe starting from the empty grid (taken from Wikipedia):

tic tac toe game tree
tic tac toe game tree

We will represent game trees as trees with only one kind of node, with a label representing the state of the game, and an arbitrary number of children representing the possible moves from that state. The standard library module Data.Tree already contains such a type Tree a of trees, defined in mutual recursion with a type Forest a of forests, so for convenience we import the module. Here is the definition from Data.Tree:

type Forest a = [Tree a]
data Tree a = Node {rootLabel :: a, subForest :: Forest a}

Note this uses record syntax, but if you prefer you can simply ignore the field labels and the type synonym, treating Tree as though it were defined by:

data Tree a = Node a [Tree a]

Now that you’ve implemented legalMoves and moveLegal, game trees for Domineering can be defined very easily:

gametree :: Board -> Tree Board
gametree b = Node b [gametree (moveLegal b c) | c <- legalMoves (turn b) b]

In Haskell, this definition is interpreted lazily, in the sense that the full game tree is not computed right away. Rather, different parts of the game tree are only computed as they are needed for evaluation.

This is important, because game trees can grow quite large! For example, the full game tree for the 5x5 board has 2103584601 nodes. Indeed, we may sometimes need to prune game trees down to a given depth:

prune :: Int -> Tree a -> Tree a
prune 0 (Node x _)  = Node x []
prune n (Node x ts) = Node x [prune (n-1) t | t <- ts]

Note that, once again, this definition is interpreted lazily in Haskell, in the sense that pieces of the pruned game tree are only computed as they are needed.

You can visualize game trees using the gametreeSVG function mentioned above. For example, the command

gametreeSVG (gametree (board 3 3)) "board3x3-full"

will generate a rendering of the full game tree for the 3x3 board with H to start, while the command

gametreeSVG (prune 2 (gametree (board 3 3))) "board3x3-depth2"

will generate a rendering of the depth 2 pruned game tree from the same initial position.

The minimax rule is a way of assigning a value to each node of a game tree starting from values (or “scores”) for the leaves, based on the principle that the value of a node for a given player is equal to the value of the child node representing their best move. If we assign negative values to one player and positive values to the other, then the process of scoring the full game tree involves an alternation between minimizing and maximizing values.

To implement minimax scoring of Domineering game trees in Haskell, let us first introduce the following type for scores:

data Score = Win Player | Heu Int  deriving (Show,Eq)

The idea is that either we already know that some player p has a winning strategy from a given board, in which case we can assign it the score Win p, or else we can assign it some heuristic integer value Heu x, with negative values favoring H and positive values favoring V. Values of type Score are therefore naturally ordered, with

Win H <= Heu x <= Win V

for all x, and Heu x <= Heu y just in case x <= y. There is a corresponding instance of Ord Score provided in the file Types.hs.

Write a scoring function

-- Exercise 2a
score :: Board -> Score
score = undefined

implementing the following heuristic: if it is p’s turn to play, return a win for p’s opponent if p has no legal moves, and otherwise return a heuristic value based on the formula

#(legal moves for V) - #(legal moves for H) - sign(p)

where sign(H) = -1 and sign(V) = 1.

Example:

> score board4x4_3
Heu 2

Write a function

-- Exercise 2b
minimax :: (Board -> Score) -> Tree Board -> Tree (Board, Score)
minimax = undefined

that annotates every node of a game tree with a minimax score, computed relative to an arbitrary scoring function for the leaves. It should leave the tree untouched other than annotating each node with a score: in other words, it should satisfy that fmap fst (minimax sfn t) = t where the operation fmap :: (a -> b) -> Tree a -> Tree b is defined in the Functor instance of Tree.

Click here to see the minimax scoring for the full game tree and for the depth 2 pruned game tree for the 3x3 board, respectively, using the scoring function score from above. These diagrams were generated with the following command:

> gametreeSVG' 1 (fmap (\(b,v) -> (b,show v)) $ minimax score $ gametree (board 3 3)) "board3x3-full-minimax"
> gametreeSVG' 1 (fmap (\(b,v) -> (b,show v)) $ minimax score $ prune 2 $ gametree (board 3 3)) "board3x3-depth2-minimax"

Write a function

-- Exercise 2c
bestmoves :: Int -> (Board -> Score) -> Board -> [Cell]
bestmoves = undefined

which takes a depth d and a scoring function scorefn as parameters, and defines a function from boards to lists of optimal moves. Each move returned should be optimal in the sense that it has the best minimax score for the current player relative to the scoring function scorefn applied to the game tree pruned to depth d, although it may not be the only move with the best score. The list returned by bestmoves should be the complete list of optimal moves, but they can be returned in any order.

Take notice that an optimal move is not necessarily a winning move, in the case where the player has no better options.

Examples:

> bestmoves 4 score (board 3 3)
[(1,2),(2,2)]
> bestmoves 4 score (moveLegal (board 3 3) (1,2))
[(3,1),(3,2)]

Enjoying a good game

Now that you’ve implemented bestmoves, we can combine it with an operation selectSafe implemented using the SelectMonad (our old friend from Lab 5) to get a player who selects optimal moves at random, and compare it against a player who selects legal moves at random.

selectSafe :: SelectMonad m => [a] -> m (Maybe a)
selectSafe [] = return Nothing
selectSafe xs = select xs >>= \x -> return (Just x)
   
randomBestPlay :: SelectMonad m => Int -> (Board -> Score) -> Board -> m (Maybe Cell)
randomBestPlay d sfn = selectSafe . bestmoves d sfn

randomPlay :: SelectMonad m => Board -> m (Maybe Cell)
randomPlay b = selectSafe (legalMoves (turn b) b)

Note we have to use selectSafe here, which returns a Maybe type, since it is possible that the list of optimal/legal moves is empty.

Write a function

-- Exercise 3a
runGame :: SelectMonad m => (Board -> m (Maybe Cell)) -> (Board -> m (Maybe Cell)) -> Board -> m Board
runGame = undefined

that takes two players playH and playV of type Board -> m (Maybe Cell), and plays them off against each other starting from some initial board to produce a final board. It should run in any selection monad, and it should stop and return the current board as soon as either player gives up (i.e., returns Nothing) or makes an illegal move.

For example, here are three games on a 4x4 board produced by setting randomBestPlay 8 score vs randomBestPlay 8 score, randomPlay vs randomBestPlay 8 score, and randomPlay vs randomPlay, respectively.

At last, now that we have a good supply of Domineering players, we need some more interesting boards!

Write a function

-- Exercise 3b (optional)
carpets :: [Board]
carpets = undefined

that generates an infinite sequence of empty boards, corresponding to the successive iterations of the Sierpinski carpet, where player H starts on even-numbered carpets and V starts on odd-numbered carpets. Here’s what the first few look like (we omit carpets !! 0, which is a pretty boring board):

carpets !! 1 = carpet1

carpets !! 2 = carpet2

carpets !! 3 = carpet3

Alpha-beta pruning (optional)

-- alpha-beta pruning (optional)

As we mentioned, game trees in Domineering can get very large very quickly, with the full game tree for the 5x5 board already containing over two billion nodes. An important general technique for reducing the size of game trees is called alpha-beta pruning. The basic idea is that very often, large subtrees can be automatically eliminated from consideration, since they cannot possibly contribute to an optimal strategy for the player starting at the root.

You can find a basic description of alpha-beta pruning at Wikipedia, including pseudocode. One way to think about this in Haskell is to refine the type of the minimax function, so that it returns a slightly more sophisticated kind of scoring:

data ABScore = Exact Score | Bound Score

alphabeta :: (Board -> Score) -> Tree Board -> Tree (Board, Maybe ABScore)
alphabeta = undefined

The idea is that given a scoring function, alphabeta annotates every board b of the game tree with one of three possible values:

  1. a score of Just (Exact v) indicates that the optimal strategy for the player starting at b has value v;
  2. a score of Just (Bound v) indicates that the optimal strategy for the player starting at b has value at least as good as v, although the player may have an even better strategy;
  3. a score of Nothing indicates nothing, and is used to prune the node b when we don’t care about its value.

Click here to see the alpha-beta scoring of the depth 2 game tree for the 3x3 board, where the nodes have been visited from left to right, and where we’ve indicated pruned nodes with an “X”. Here’s another, smaller version where the pruned nodes have been removed altogether:

board3x3-alpha2-pruned.svg
board3x3-alpha2-pruned.svg

Observe that some of the nodes are marked with lower bounds, e.g., ≥Heu 2 and ≥Heu 0. In both these two cases, the true minimax value of the nodes is actually higher, namely Win V, but this is irrelevant to the minimax value of the root, since we can already tell that playing either of these moves will lead to a worse position (for player H) than playing their sibling node marked Heu (-2).

With alpha-beta pruning, often it’s the case that increasing the overall pruning depth can actually decrease the size of the tree. For example, here is the left-to-right alpha-beta pruning of the full game tree for the 3x3 board:

board3x3-alpha4-pruned.svg
board3x3-alpha4-pruned.svg

Since we can already tell that H has a winning strategy, there is no point (from H’s perspective) in further exploring the game tree.

For the 4x4 board, the size of the game tree is reduced from 65081 nodes (without alpha-beta pruning) to 1362 (with pruning), and for the 5x5 board, the size goes down from 2103584601 nodes to a much more manageable 3634155 nodes!

Implement a function alphabeta of the type described above. Also implement a function

alphaprune :: Tree (a, Maybe b) -> Maybe (Tree (a,b))

that prunes off entire subtrees of the game tree whose root has score Nothing. Finally, use these together with the functions gametree and prune defined above to define a new function

alphamoves :: Int -> (Board -> Score) -> Board -> [Cell]

such that alphamoves d score implements optimal play according to the alpha-beta pruned, depth-d pruned game tree. It should run much faster than bestmoves d score for a given value of d, which makes it feasible to try larger values of d, and you can try matching the alpha-beta minimax player against the simple minimax player in a runGame competition.

There are many other possibilities for improving the efficiency of minimax search. Memoization of previously explored nodes can significantly reduce the time needed to explore the game tree, as can exploiting symmetries in the problem. Also, alpha-beta pruning can be improved by using some more rational criterion to guide the order in which the nodes are visited, rather than simply scanning them from left to right, so as to increase the chances of finding good strategies early on.

You can find out more about strategies specific to Domineering at the Wikipedia page, as well as at this site by Nathan Bullock. Finally, you may also enjoy watching this video series on Domineering by the late Elwyn Berlekamp.