Optimizing a maze with graph theory, genetic algorithms, and Haskell

Chris Smith
Analytics Vidhya
Published in
20 min readMar 1, 2020

Lately, I’ve been working on a side project that became a fun exercise in both graph theory and genetic algorithms. This is the story of that experience.

Beginnings

I recently took a break from my job to recover my excitement and sense of wonder about the world. During this break, I ended up building a board game. In this game, players navigate a maze built out of maze pieces on hexagon tiles, so that when these tiles are shuffled and connected at random, they build a complete maze, on a grid like this:

I wasn’t at all sure that I could build a very good maze by the random placement of tiles. Still, I figured that I could wing it and see what happened, so I did.

Attempt #1: Doing the Simplest Thing

Mazes are almost the ideal application of graph theory. A graph (and here I always mean an undirected graph) is a bunch of vertices connected by edges. A maze, on the other hand, is a bunch of locations connected by paths. Same thing, different words!

In this case, my original idea was that the hexagon tiles were the locations (i.e., vertices), and each of the six sides of the tile would either be open or blocked, potentially making a path to the adjacent tile. The question, then, was which of these edges should be blocked. I was guided by two concerns:

  1. It should be possible to solve the maze. That is, there should be (at least with high probability) an open path from the start to the finish.
  2. It should not be trivial to solve the maze. That is, it should not be the case that moving in any direction at all gets you from the start to the finish.

A key insight here is that adding an edge in a graph always does one of two things: it either connects two previously unconnected components of the graph, or it creates a cycle (a path from a vertex back to itself without repeating an edge) by connecting two previously connected vertices in a second way. The two concerns, then, say that we want to do the first if at all possible, but avoid the second. Unfortunately, since our edges are pointing in random directions, it’s not clear how we can distinguish between the two!

But, at the very least, we can try to get about the right number of edges in our graph. We want the graph to be acyclic (i.e., not contain any cycles), but connected. Such a graph is called a tree. We’ll use the following easy fact several times:

Proposition: In any acyclic graph, the number of edges is always equal to the number of vertices minus the number of connected components. (Proof: By induction on the number of edges: if there are no edges, then each vertex is its own connected component. If there are edges, removing any edge keeps the graph acyclic, so the equality holds, but re-adding that edge adds one edge and removes one connected component, preserving the equality.)

Corollary: A tree has one fewer edge than it has vertices. (Proof: the entire tree is one connected component. Apply the proposition above.)

So, I thought to myself, I have twenty hex tiles, because that’s how many blank tiles came in the box. If I treat each of them as a vertex, then I need 19 connections between them.

There’s one further complication. In order for a path to be open, it has to not be blocked on either side, and the outside boundary of the maze is always blocked. So not every open edge of a tile adds a vertex to the graph. This is easily solved with a slight change of perspective. Instead of counting the number of edges, one could count the desired probability of an edge being open.

In my chosen configuration of tiles, there were 43 internal borders between tiles, not counting the outer boundary of the whole maze. So I wanted about a 19/43 (or about 43%) probability of an edge on each of these boundaries. Because both tiles need an open side to make that edge, if each edge is chosen independently, the probability of a tile having an open edge should be the square root of that, or about 66%. Since each of the 20 tiles has 6 edges on each of 2 sides, there are 240 edges, and a random 160 of them (that’s 240 * sqrt(19/43)) should be open, and the remaining 80 should be blocked.

You can see a simulation of this here. This simple simulation doesn’t choose tiles. Unfortunately, this experiment failed. if you try this several times, you’ll notice:

  1. The mazes are just too simple. Twenty spaces in the maze are just not enough.
  2. It’s far too frequent that the open edges are in the wrong places, and you cannot get from start to finish.

Now, it’s not imperative that a maze be acyclic, so I could (and, in practice, would) increase the probability of an open edge to solve the second problem… but that would just make the first problem even worse. There is no choice of probability that fixes both problems at once.

Attempt #2: More Interesting Tiles

To be honest, I expected this first attempt to fail. I never even drew the tiles, but just simulated enough to be confident that it would not work. Clearly, I needed more structure within the map tiles.

One thing that would have made the result look more compelling would be to draw interesting (but static) mazes onto each tile, which are all connected themselves, and have exits in all directions with the appropriate probabilities. This is all smoke and mirrors, though. Ultimately, it reduces to the same system as above. With a sufficiently increased probability of an open edge, this would satisfy my requirements.

Faking a better maze with static tiles

But it feels like cheating. I want the high-level structure of the maze to be interesting in its own right. And no matter how clever I get with the tiles, the previous section showed that’s not possible in this model.

The remaining option, then, is to consider that each tile, instead of being one location with a number of exits, actually contains multiple locations, with varied connectivity. Since I don’t want to add artificial complexity inside the tiles, they will simply connect the edges as desired. Some of the tiles now look like this:

Tiles with (potentially) multiple locations per tile

At first glance, the analysis for connecting the maze becomes trickier, because the number of vertices in the graph changes! Three of the tiles above have two locations, but the last one has only one. There are even tiles with three different paths.

But never fear: another change of perspective simplifies the matter. Instead of considering the graph where each tile or path is a vertex, we will consider the dual graph, where each border is a vertex, like this:

The dual of the maze graph

Now we once again have a fixed number of vertices (77 of them), and tiles that determine the edges between those vertices. To connect this graph, then, requires at least 76 edges spread across 20 tiles, or about 3.8 edges per tile. Maybe even a few more, since the resulting graph is sure to contain some cycles, after all, so let’s call it 4 per tile.

Here’s the mistake I made when I first considered this graph. The last tile in the set of four examples above connects five different vertices together, so that it’s possible to pass directly between any pair of them. Naively, you might think that corresponds to 10 edges: one for each pair of vertices that are connected. That fit my intuition that connecting five out of the six sides should be way above average, as far as connections on a tile. I thought this, and I worked out a full set of tiles on this assumption before realizing that the resulting mazes were not nearly connected enough.

Here’s the problem: those 10 edges will contain a rather large number of cycles. The requirement for at least 76 edges was intended for an acyclic graph. We will inevitably end up with some cycles between tiles, but we should at least avoid counting cycles within a tile. To connect those five vertices with an acyclic graph requires four edges rather than ten. It doesn’t matter to us which four edges those are; they only exist in theory, and don’t change how the tile is drawn. But it’s important to only count them as four.

Now, 76 edges feels like an exorbitant number of edges! If we must average connecting nearly five out of the six sides of each tile, it seems it will be possible to move almost anywhere. But on further reflection, this isn’t unreasonable. Nearly half of those vertices are on the outside boundary of the maze! All it takes is one blocked path in an unfortunate place to isolate one of those vertices. Even a one-in-six chance will isolate about six of them. Those six edges that are not being used to connect the graph will then go to adding excess paths in the remaining pieces!

The fact that vertices on the edges of the graph are so likely to be isolated is a problem. I decided to mitigate that problem creatively, by adding some of those 76 edges not on the tiles, but on the board. Something like this:

Exterior edges on the maze

With these 14 edges on the exterior of the maze (remember that connecting three vertices only counts as two edges), we need only 64 on the interior, which is barely more than 3 per tile. Not only that, but the tiles on the edge are considerably less likely to be isolated in the resulting maze.

At this point, I drew a set of tiles, iterated on them for a bit by laying out mazes and getting a sense for when they were too easy, too hard, etc. I ended up with a mechanic that I was mostly happy with. Here is the actual game board with a random maze laid out. The layout is a little different from the examples above because of the need to work in other game play elements, but the idea is essentially the same.

The actual game board

If you look closely, you’ll see that the resulting maze isn’t entirely connected: there are two short disconnected sections on the bottom-left and bottom-right tiles. It definitely contains cycles, both because the disconnected components free up edges that cause cycles, and because I’ve included more than the minimum number of edges needed to connect the maze anyway.

But it is non-trivial, visually interesting, and generally in pretty good shape. It appears fairly easy when all laid out like this, but in the actual game, players only uncover tiles when they reach them, and the experience is definitely much like navigating a maze, where you’re not sure where a trail will lead until you follow it. All in all, it’s a success.

Attempt #3: Using Genetic Algorithms

I wasn’t unhappy with this attempt, but I suspected that I could do better with some computer simulation. I little bit of poking around turned up a Haskell library called moo that provides the building blocks for genetic algorithms.

The idea behind genetic algorithms is simple: you begin with an initial population of answers, which are sometimes randomly generated, and evaluate them according to a fitness function. You take the best answers in that set, and then expand it by generating random mutations and crosses of that population. This provides a new population, which is evaluated, mutated, cross-bred, etc.

Let’s start with some imports:

import Algebra.Graph.AdjacencyMap.Algorithm (scc)
import Algebra.Graph.ToGraph
import qualified Algebra.Graph.Undirected as U
import Control.Monad
import Data.Containers.ListUtils
import Data.Function (on)
import Data.List
import Moo.GeneticAlgorithm.Binary
import System.IO.Unsafe
import System.Random
import System.Random.Shuffle

And some types:

data Direction = N | NE | SE | S | SW | NW
deriving (Show, Eq, Ord, Enum)
type Trail = [Direction]data Tile = Tile [Trail] [Trail]
deriving (Show, Eq)

A Direction is one of the six cardinal directions in a hex world, arranged in clockwise order. A Trail is a single trail from one of the tile designs. It’s represented as a list of directions from which one can exit the tile by that trail. Everything but that is just visual design. And finally, a Tile has a top and bottom side, and each of those has some list of Trails.

The moo library requires some way to encode or decode values into bit strings, which play the role of DNA in the genetic algorithm. The framework will make somewhat arbitrary modifications to these bit strings, and you’re expected to be able to read these modified strings and get reasonable values. In fact, it’s expected that small modifications to a bit string will yield similarly small changes to the encoded value.

Here’s what I did. Each side of a tile is encoded into six numbers, each of which identifies the trail connected to a direction of the tile. If a tile does not have a trail leaving in some direction, then that direction will have a unique trail number, so essentially it becomes a dead end. Assuming we don’t want a trail with only a single non-branching path (and we don’t!), it suffices to leave room for four trail numbers, which requires only two bits in the string. Then a side needs 12 bits, a two-sided tile needs 24 bits, and a full set of 20 tiles needs 480 bits.

Here’s the code to encode a stack of tiles this way starting from the earlier representation:

encodeTile :: Tile -> [Bool]
encodeTile (Tile a b) =
concat
[ encodeBinary (0 :: Int, 3) (trailNum side dir)
| side <- [a, b],
dir <- [N .. NW]
]
where
trailNum trails d =
case [i | (t, i) <- zip trails [0 .. 3], d `elem` t] of
[i] -> i
_ -> error "Duplicate or missing dir on tile"
encodeTiles :: [Tile] -> [Bool]
encodeTiles = concat . map encodeTile

The encodeBinary function is part of moo, and just encodes a binary number into a list of bools, given a range. The rest of this just matches trails with trail numbers and concatenates their encodings.

Decoding is a little more complex, mainly because we want to do some normalization that will come in handy down the road. A helper function first:

clockwise :: Direction -> Direction
clockwise N = NE
clockwise NE = SE
clockwise SE = S
clockwise S = SW
clockwise SW = NW
clockwise NW = N

Now the decoding:

decodeTile :: [Bool] -> Tile
decodeTile bs = Tile (postproc a) (postproc b)
where
trailNums =
map
(decodeBinary (0 :: Int, 3))
(splitEvery trailSize bs)
trail nums n = [d | (d, i) <- zip [N .. NW] nums, i == n]
a = map (trail (take 6 trailNums)) [0 .. 3]
b = map (trail (drop 6 trailNums)) [0 .. 3]
postproc :: [Trail] -> [Trail]
postproc = normalize . filter (not . null)
where
normalize trails =
minimum
[ simplify ts
| ts <- take 6 (iterate (map (map clockwise)) trails)
]
simplify = sort . map sort
decodeTiles :: [Bool] -> [Tile]
decodeTiles = map decodeTile . splitEvery tileSize
trailSize :: Int
trailSize = bitsNeeded (0 :: Int, 3)
tileSize :: Int
tileSize = 12 * trailSize

Again, some of the functions (such as decodeBinary, bitsNeeded, and splitEvery) are utility functions provided by moo. The postproc function applies a bit of normalization to the tile design. Since reordering of the exits of a trail, the trails, and the rotation of the tile do not change its meaning, we simply make a consistent choice here, so that equal tiles will compare equal.

The next thing we need is a way to score a set of tiles, so the best can be chosen. From the beginning, we know that the scoring will involve shuffling the tiles, which actually includes three kinds of randomization:

  • Moving the tiles to different places on the board.
  • Rotating the tiles to a random orientation.
  • Flipping the tiles so either side is equally likely to be visible.

Here’s that code:

rotateTile :: Int -> Tile -> Tile
rotateTile n
| n > 0 = rotateTile (n - 1) . rot
| n < 0 = rotateTile (n + 6)
| otherwise = id
where
rot (Tile top bottom) =
Tile (map (map clockwise) top) bottom
flipTile :: Tile -> Tile
flipTile (Tile top bottom) = Tile bottom top
randomizeTile :: RandomGen g => g -> Tile -> (g, Tile)
randomizeTile g t
| flipped = (g3, rotateTile rots (flipTile t))
| otherwise = (g3, rotateTile rots t)
where
(flipped, g2) = random g
(rots, g3) = randomR (0, 5) g2
shuffleTiles :: RandomGen g => g -> [Tile] -> (g, [Tile])
shuffleTiles g tiles = (g3, result)
where
(g1, g2) = split g
shuffledTiles = shuffle' tiles (length tiles) g1
(g3, result) = mapAccumL randomizeTile g2 shuffledTiles

In order to score the random arrangements of tiles, it’s useful to have a graph library. In this case, I chose Alga for the task, mainly because it allows for graphs with an arbitrary node type (which I want here), it seems to be garnering some excitement, and I haven’t had a chance to play with it yet. Alga represents undirected graphs with a different Graph type (annoyingly called the same thing) in a subpackage, hence the qualified import.

In order to share actual code, I’m switching to now work with the real game board, from the photo above. There are certain fixed locations that I care about because players will need to reach them in the game: the witch’s hut, the wishing well, the monster’s lair, the orchard, the spring, and the exit. These get their own named nodes. The tiles are named “1” through “20”. And finally, because each tile can have multiple trails, a node consists of a name and a trail number (which is always 0 for the built-in locations). Here’s the code to build a graph from a list of tiles:

topSide :: Tile -> [[Direction]]
topSide (Tile top _) = top
tileGraph :: [Tile] -> U.Graph (String, Int)
tileGraph tiles =
U.edges $
[ ((show a, trailNum a dira), (show b, trailNum b dirb))
| (a, dira, b, dirb) <- connections
]
++ [ (("Well", 0), (show c, trailNum c dir))
| (c, dir) <-
[ (6, SE),
(7, NE),
(10, S),
(11, N),
(14, SW),
(15, NW)
]
]
++ [ (("Hut", 0), (show c, trailNum c dir))
| (c, dir) <- [(1, NE), (5, N), (9, NW)]
]
++ [ (("Spring", 0), (show c, trailNum c dir))
| (c, dir) <- [(4, S), (8, SW)]
]
++ [ (("Orchard", 0), (show c, trailNum c dir))
| (c, dir) <- [(13, NE), (17, N)]
]
++ [ (("Lair", 0), (show c, trailNum c dir))
| (c, dir) <- [(12, SE), (16, S), (20, SW)]
]
++ [ (("Exit", 0), (show c, trailNum c dir))
| (c, dir) <- [(19, SE), (20, NE), (20, SE)]
]
where
trailNum n dir =
head
[ i
| (exits, i) <- zip (topSide (tiles !! (n - 1))) [0 ..],
dir `elem` exits
]
connections =
[ (1, S, 2, N),
(1, SW, 2, NW),
(1, SE, 5, NW),
(2, NE, 5, SW),
(2, SE, 6, NW),
(2, S, 3, N),
(2, SW, 3, NW),
(3, NE, 6, SW),
(3, SE, 7, NW),
(3, S, 4, N),
(3, SW, 4, NW),
(4, NE, 7, SW),
(4, SE, 8, NW),
(5, NE, 9, SW),
(5, SE, 10, NW),
(5, S, 6, N),
(6, NE, 10, SW),
(6, S, 7, N),
(7, SE, 11, NW),
(7, S, 8, N),
(8, NE, 11, SW),
(8, SE, 12, NW),
(8, S, 12, SW),
(9, NE, 13, N),
(9, SE, 13, NW),
(9, S, 10, N),
(10, NE, 13, SW),
(10, SE, 14, NW),
(11, NE, 15, SW),
(11, SE, 16, NW),
(11, S, 12, N),
(12, NE, 16, SW),
(13, SE, 17, NW),
(13, S, 14, N),
(14, NE, 17, SW),
(14, SE, 18, NW),
(14, S, 15, N),
(15, NE, 18, SW),
(15, SE, 19, NW),
(15, S, 16, N),
(16, NE, 19, SW),
(16, SE, 20, NW),
(17, SE, 18, NE),
(17, S, 18, N),
(18, SE, 19, NE),
(18, S, 19, N),
(19, S, 20, N)
]

Tedious, but it works! I can now score one of these graphs. There are two kinds of things I care about: the probability of being able to get between any two of the built-in locations, and the number of “excess” edges that create multiple paths.

hasPath :: String -> String -> U.Graph (String, Int) -> Bool
hasPath a b g =
(b, 0) `elem` reachable (a, 0 :: Int) (U.fromUndirected g)
extraEdges :: Ord a => U.Graph a -> Int
extraEdges g = edges - (vertices - components)
where
vertices = U.vertexCount g
edges = U.edgeCount g
components =
vertexCount (scc (toAdjacencyMap (U.fromUndirected g)))
scoreGraph :: U.Graph (String, Int) -> [Double]
scoreGraph g =
[ -0.1 * fromIntegral (extraEdges g),
if hasPath "Hut" "Well" g then 1.0 else 0.0,
if hasPath "Hut" "Spring" g then 1.0 else 0.0,
if hasPath "Hut" "Lair" g then 1.0 else 0.0,
if hasPath "Hut" "Orchard" g then 1.0 else 0.0,
if hasPath "Hut" "Exit" g then 1.0 else 0.0,
if hasPath "Well" "Spring" g then 1.0 else 0.0,
if hasPath "Well" "Lair" g then 1.0 else 0.0,
if hasPath "Well" "Orchard" g then 1.0 else 0.0,
if hasPath "Well" "Exit" g then 1.0 else 0.0,
if hasPath "Spring" "Lair" g then 1.0 else 0.0,
if hasPath "Spring" "Orchard" g then 1.0 else 0.0,
if hasPath "Spring" "Exit" g then 1.0 else 0.0,
if hasPath "Lair" "Orchard" g then 1.0 else 0.0,
if hasPath "Lair" "Exit" g then 1.0 else 0.0,
if hasPath "Orchard" "Exit" g then 1.0 else 0.0
]

The result of scoring is a list of individual scores, which will be added together to determine the overall fitness. I’ve added a low negative weight to the extra edges, in order to express the fact that they are bad, but far less so than not being able to reach an important game location. (Unreachability isn’t fatal, though, since the game also has mechanisms by which the maze changes over time… that’s my backup plan.)

Now, I just need to score the tiles themselves by generating a bunch of random game board graphs, and averaging the scores for those graphs. When I did so, though, I found that there were other things that went wrong with the optimized tiles:

  • The algorithm reused the same designs over and over again, making the game less random. To fix this, I added a small cost associated with the sum of the squares of the number of each unique tile design. This is why it was convenient to normalize the tiles, so I could find duplicates. Some duplicates are okay, but by the time we get to four or five of the same design, adding more duplicates becomes very costly.
  • The algorithm generated a lot of tiles that need bridges. Like salt, bridges make the map more interesting in small quantities, such as the five bridges in the photo above, out of 20 tiles in all. But I was getting tile sets that needed bridges on nearly every tile, and sometimes even stacks of them! To fix this, I added a small cost for each bridge in the final tile set.
  • The tiles included a tile with all six directions connected to each other. For aesthetic reasons, I wanted the wishing well to be the only location on the map with that level of connectivity. So I added a large negative cost associated with using that specific tile design.

Here’s the resulting code.

needsBridge :: [Trail] -> Bool
needsBridge trails =
or [conflicts a b | a <- trails, b <- trails, a /= b]
where
conflicts t1 t2 =
or [d > minimum t1 && d < maximum t1 | d <- t2]
&& or [d > minimum t2 && d < maximum t2 | d <- t1]
numBridges :: [Tile] -> Int
numBridges tiles =
length
[ () | Tile a _ <- tiles ++ map flipTile tiles, needsBridge a
]
dupScore :: [Tile] -> Int
dupScore tiles =
sum (map ((^ 2) . length) (group (sort sides)))
where
sides = map topSide tiles ++ map (topSide . flipTile) tiles
numFullyConnected :: [Tile] -> Int
numFullyConnected tiles =
length [() | Tile a b <- tiles, length a == 1 || length b == 1]
scoreTiles :: RandomGen g => g -> Int -> [Tile] -> [Double]
scoreTiles g n tiles =
[ -0.05 * fromIntegral (numBridges tiles),
-0.02 * fromIntegral (dupScore tiles),
-1 * fromIntegral (numFullyConnected tiles)
]
++ map (/ fromIntegral n) graphScores
where
(graphScores, _) = foldl' next (repeat 0, g) (replicate n tiles)
next (soFar, g1) tiles =
let (g2, shuffled) = shuffleTiles g1 tiles
in (zipWith (+) soFar (scoreGraph (tileGraph shuffled)), g2)

That’s basically all the pieces. From here, I simply ask the moo library to run the optimization. I was too lazy to figure out how to pipe random number generation through moo, so I cheated with an unsafePerformIO there. I realize that means I’m kicked out of the Haskell community, but I’ll take my chances that no one reads this far down.

Here’s the rest of the boilerplate. Much of it is copied without understanding from examples distributed with moo. Perhaps there’s some hyper-parameter tuning that would improve things, but I’m happy with what I got!

main :: IO ()
main = do
void $ runIO initialize $
loopIO
[DoEvery 10 logStats, TimeLimit (12 * 3600)]
(Generations maxBound)
nextGen
initialize =
return (replicate popsize (encodeTiles originalTiles))
logStats n pop = do
let best =
decodeTiles
$ head
$ map takeGenome
$ bestFirst Maximizing pop
putStrLn $ show n ++ ":"
mapM_ print best
g <- newStdGen
print $ scoreTiles g 500 best
nextGen =
nextGeneration
Maximizing
objective
select
elitesize
(onePointCrossover 0.5)
(pointMutate 0.5)
select = tournamentSelect Maximizing 2 (popsize - elitesize)popsize = 20
elitesize = 5
objective :: Genome Bool -> Double
objective gen = unsafePerformIO $ do
g <- newStdGen
return $ sum $ scoreTiles g 500 $ decodeTiles gen

The Final Result

Using moo, I was able to maintain or improve on all components of the scoring.

For the tiles I drew in attempt #2:

  • 13 bridges were needed across the 40 tile designs.
  • The duplicate score (sum of squares of the count of each unique design) was 106, indicating several designs that were duplicated four and five times.
  • There was an average of 9.1 extra edges creating cycles in the maze.
  • Probabilities of a path to key locations was about 93%.

For the newly optimized tiles:

  • There were only 11 bridges needed, saving two bridges over the original design.
  • The duplicate score was 72, indicating many fewer copies of the same design, and never more than three copies of a design.
  • There was an average of 8.4 extra edges creating cycles in the maze, nearly one less than in the original.
  • Probabilities of a path to key locations was about 92%, which is essentially the same as the original.

For the most part, though, I think I learned that the tiles I’d previously devised were pretty well chosen, but I did get an incremental improvement in making the maze more challenging without compromising much on the possibility of success.

The art for the new tile set is not yet as pretty as the old one, but here’s a maze laid out with the new tiles.

A maze laid out with genetically optimized tiles

So what about the rest of the game? It’s been a lot of work! The maze generation was actually a pretty small part. There are a bunch of details around character-building (each player chooses one of six characters with a unique personality, story, and abilities), other mechanics (there’s a monster who moves randomly around the maze, quests that take characters to various locations to collect items, a magical fog that hides and changes parts of the maze as you play, etc.), and artwork.

Unfortunately, I return to my full-time job tomorrow and may not have the free time to pursue frivolous goals. But who knows… perhaps I’ll find the time, hit Kickstarter, and finish the job. In any case, I’ve learned some things and had a good time, and I hope you enjoyed the story.

--

--

Chris Smith
Analytics Vidhya

Software engineer, volunteer K-12 math and computer science teacher, author of the CodeWorld platform, amateur ring theorist, and Haskell enthusiast.