Smarter Enemies with BFS!

brain.png

Last week we added enemies to our maze. These little squares will rove around the maze, and if they touch our character, we have to restart the maze. We made it so that these enemies moved around at random. Thus they're not particularly efficient at getting to us.

This week, we're going to make them much more dangerous! They'll use the breadth first search algorithm to find the shortest path towards our player. We'll use three kinds of data structures from the containers package. So if you want to get a little more familiar with that, this article is a great start! Take a look at our Github Repository to see the full code! Look at the part-6 branch for this article!

We'll also make use of the state monad throughout. If you're still a little uncomfortable with monads, make sure to read our series on them! It'll help you with the basics. By the end you'll know about the state monad and how to use it in conjunction with other monads! If you're new to Haskell, you should also take a look at our Beginners Checklist!

BFS Overview

The goal of our breadth first search will be to return the fastest path from one location to another. We'll be writing this function:

getShortestPath :: Maze -> Location -> Location -> [Location]

It will return all the locations on the path from the initial location to the target location. If there's no possible path, we'll return the empty list. In practice, we'll usually only want to take the first element of this list. But there are use cases for having the whole path that we'll explore later. Here's a basic outline of our algorithm:

  1. Keep a queue of locations that we'll visit in the future. At the start, this should contain our starting location.
  2. Dequeue the first location (if the queue is empty, return the empty list). Mark this location as visited. If it is our target location, skip to step 5.
  3. Find all adjacent locations that we haven't visited/enqueued yet. Put them into the search queue. Mark the dequeued location as the "parent" location for each of these new locations.
  4. Continue dequeuing elements and inserting their unvisited neighbors. Stop when we dequeue the target location.
  5. Once we have the target location, use the "parents" map to create the full path from start to finish.

Data Structures Galore

Now let's start getting into the details. As we'll see, there are several different data structures we'll need for this! We'll do some of the same things we did for depth first search (the first time around). We'll make a type to represent our current algorithm state. Then we'll make a recursive, stateful function over that type. In this case, we'll want three items in our search state.

  1. A set of "visited" cells
  2. A queue for cells we are waiting to visit
  3. A mapping of cells to their "parent"

And for all three of these, we'll want different structures. Data.Set will suffice for our visited cells. Then we'll want Data.Map for the parent map. For the search queue though, we'll use something that we haven't used on this blog before: Data.Sequence. This structure allows us to add to the back and remove from the front quickly. Here's our search state type:

data BFSState = BFSState
  { bfsSearchQueue :: Seq.Seq Location
  , bfsVisistedLocations :: Set.Set Location
  , bfsParents :: Map.Map Location Location
  }

Before we get carried away with our search function, let's fill in our wrapper function. This will initialize the state with the starting location. Then it will call evalState to get the result:

getShortestPath :: Maze -> Location -> Location -> [Location]
getShortestPath maze initialLocation targetLocation = evalState
  (bfs maze initialLocation targetLocation)
  (BFSState 
    (Seq.singleton initialLocation) 
    (Set.singleton initialLocation) 
    Map.empty)

bfs :: Maze -> Location -> Location -> State BFSState [Location]
bfs = ...

As with depth first search, we'll start by retrieving the current state. Then we'll ask if the search queue is empty. If it is, this means we've exhausted all possibilities, and should return the empty list. This indicates no path is possible:

bfs :: Maze -> Location -> Location -> State BFSState [Location]
bfs maze initialLocation targetLocation = do
  BFSState searchQueue visitedSet parentsMap <- get
  if Seq.null searchQueue
    then return []
    else do
      ...

Now let's consider the first element in our queue. If it's our target location, we're done. We'll write the exact helper for this part later. But first let's get into the meat of the algorithm:

bfs maze initialLocation targetLocation = do
  BFSState searchQueue visitedSet parentsMap <- get
  if Seq.null searchQueue
    then return []
    else do
      let nextLoc = Seq.index searchQueue 0
      if nextLoc == targetLocation
        then … -- Get results
        else do
          ...

Now our code will actually look imperative, to match the algorithm description above:

  1. Get adjacent cells and filter based on those we haven't visited
  2. Insert the current cell into the visited set
  3. Insert the new cells at the end of the search queue, but drop the current (first) element from the queue as well.
  4. Mark the current cell as the "parent" for each of these new cells. The new cell should be the "key", the current should be the value.

There's a couple tricky folds involved here, but nothing too bad. Here's what it looks like:

bfs :: Maze -> Location -> Location -> State BFSState [Location]
bfs maze initialLocation targetLocation = do
  BFSState searchQueue visitedSet parentsMap <- get
  ...
      if nextLoc == targetLocation
        then ...
        else do
              -- Step 1 (Find next locations)
          let adjacentCells = getAdjacentLocations maze nextLoc
              unvisitedNextCells = filter 
                (\loc -> not (Set.member loc visitedSet)) 
                adjacentCells

              -- Step 2 (Mark as visited)
              newVisitedSet = Set.insert nextLoc visitedSet

              -- Step 3 (Enqueue new elements)
              newSearchQueue = foldr
                (flip (Seq.|>))
                -- (Notice we remove the first element!)
                (Seq.drop 1 searchQueue)
                unvisitedNextCells

              -- Step 4
              newParentsMap = foldr
                (\loc -> Map.insert loc nextLoc)
                parentsMap
                unvisitedNextCells

Then once we're done, we'll insert these new elements into our search state. Then we'll make a recursive call to bfs to continue the process!

bfs :: Maze -> Location -> Location -> State BFSState [Location]
bfs maze initialLocation targetLocation = do
  BFSState searchQueue visitedSet parentsMap <- get
  ...
      if nextLoc == targetLocation
        then ...
        else do
              -- Step 1
          let adjacentCells = getAdjacentLocations maze nextLoc
              unvisitedNextCells = filter 
                (\loc -> not (Set.member loc visitedSet)) 
                adjacentCells
              -- Step 2
              newVisitedSet = Set.insert nextLoc visitedSet
              -- Step 3
              newSearchQueue = foldr
                (flip (Seq.|>))
                -- (Notice we remove the first element!)
                (Seq.drop 1 searchQueue)
                unvisitedNextCells
              -- Step 4
              newParentsMap = foldr
                (\loc -> Map.insert loc nextLoc)
                parentsMap
                unvisitedNextCells

          -- Replace the state and make recursive call!
          put (BFSState newSearchQueue newVisitedSet newParentsMap)
          bfs maze initialLocation targetLocation

For the last part of this, we need to consider what happens when we hit our target. In this case, we'll "unwind" the path using the parents map. We'll start with the target location in our path list. Then we'll look up its parent, and append it to the list. Then we'll look up the parent's parent. And so on. We do this recursion (of course).

bfs :: Maze -> Location -> Location -> State BFSState [Location]
bfs maze initialLocation targetLocation = do
  BFSState searchQueue visitedSet parentsMap <- get
  if Seq.null searchQueue
    then return []
    else do
      let nextLoc = Seq.index searchQueue 0
      if nextLoc == targetLocation
        then return (unwindPath parentsMap [targetLocation])
        ...
  where
    unwindPath parentsMap currentPath =
      case Map.lookup (head currentPath) parentsMap of
        Nothing -> tail currentPath
        Just parent -> unwindPath parentsMap (parent : currentPath)

The only cell we should find without a parent is the initial cell. So when we hit this case, we return the trail of the current path (so removing the current cell from it). And that's all!

Modifying the Game

All we have to do to wrap things up is call this function instead of our random function for the enemy movements. We'll keep things a little fresh by having them make a random move about 20% of the time. (We'll make this a tunable parameter in the future). Here's the bit where we keep some randomness, like what we have now:

updateEnemy :: Maze -> Location -> Enemy -> State StdGen Enemy
updateEnemy maze playerLocation e@(Enemy location) =
  if (null potentialLocs)
    then return e
    else do
      gen <- get
      let (randomMoveRoll, gen') = randomR (1 :: Int, 5) gen
      let (newLocation, newGen) = if randomMoveRoll == 1
            then
              let (randomIndex, newGen) =
                randomR (0, (length potentialLocs) - 1) gen'
              in  (potentialLocs !! randomIndex, newGen)
          ...
  where
    potentialLocs = getAdjacentLocations maze location

And in the rest of the cases, we'll call our getShortestPath function!

updateEnemy :: Maze -> Location -> Enemy -> State StdGen Enemy
updateEnemy maze playerLocation e@(Enemy location) =
  if (null potentialLocs)
    then return e
    else do
      gen <- get
      let (randomMoveRoll, gen') = randomR (1 :: Int, 5) gen
      let (newLocation, newGen) = if randomMoveRoll == 1
            then
              let (randomIndex, newGen) =
                randomR (0, (length potentialLocs) - 1) gen'
              in  (potentialLocs !! randomIndex, newGen)
            else
              let shortestPath =
                getShortestPath maze location playerLocation
              in  (if null shortestPath then location 
                     else head shortestPath, gen')
      put newGen
      return (Enemy newLocation)
    where
      potentialLocs = getAdjacentLocations maze location

And now the enemies will chase us around! They're hard to avoid!

Conclusion

With our enemies now being more intelligent, we'll want to allow our player to fight back against them! Next week, we'll create a mechanism to stun the ghosts to give ourselves a better chance! After, we'll look a some other ways to power up our player!

If you've never programmed in Haskell, hopefully this series is giving you some good ideas of the possibilities! We have a lot of resources for beginners! Check out our Beginners Checklist as well as our Liftoff Series!

Previous
Previous

Fighting Back!

Next
Next

Running From Enemies!