Preparing for Simulation: Player AI

two_brains.jpg

Our goal for the next couple of weeks will be to run our game as a simulation, without any kind of player input. This means we'll be able to run through rapid iterations of the game and see the results. We can tune parameters and see what makes the game more competitive. But if we don't have player input, we have to move the main character somehow!

This means writing an AI for our player like we have for the enemies. The "player" has more possible actions and inputs, so it will be a little more complicated. We'll restructure our code a bit to make this easier. As with previous parts, take a look at our Github repository for more details. Refer to the player-ai branch for this article.

If you've never programmed in Haskell before, take a look at our Beginners Checklist and read our Liftoff Series! They'll help you get going so you can understand some of the concepts in these articles!

Basic Rules

For the first iteration of our AI, we won't use the drill power up at all. Each "move" will consist of two things. First, we'll pick a direction to move (or stand still). Second, we'll return a boolean for whether to activate the stun power-up.

data MoveChoice =
  MoveUp |
  MoveRight |
  MoveDown |
  MoveLeft |
  StandStill

data PlayerMove = PlayerMove
  {  moveChoice :: MoveChoice
  , activateStun :: Bool
  }

The choice depends on the state of the world. So our final goal is a function like:

makePlayerMove :: World -> PlayerMove
...

Once we have the player's move, we'll leave it up to the main update function to determine the result. We could also return a Location instead of a MoveChoice. This might seem more natural at times. But there are a couple reasons we want to stick with this approach.

One long-term goal is to machine-learn this function. So it will help a lot to limit the scope of the output space as much as possible. This means we're much more likely to come up with legal moves. We also want to leave it up to the game engine to determine that our move can't corrupt the game state. So we'll make our "choice" and devise other functions to manipulate the world.

Now that we know our basic types, let's come up with some simple rules to dictate our behavior.

  1. Determine the shortest path to the destination
  2. If there is an enemy on that path within the stun radius, activate the stun, if we can.
  3. If we don't have our stun, choose any move away from the enemy.

So we can see some specific elements we'll need to code up. Step 1 is the simplest. We've already written out a function for finding the shortest path to our destination. Determining if there's an enemy on that path will be simple as well. The last part will be a little trickier, but manageable. Before we write this function though, we want to update our game infrastructure a bit to support to AI. We'll try to keep this section somewhat light on details.

Game Infrastructure

First, we'll need a couple new parameters for our game. Our player now needs a lagTime parameter like what the Enemy type has. We also need a boolean on our parameter object indicating whether we're using the AI or human input. As always, we'll update JSON instances to reflect these new fields:

data GameParameters = GameParameters
  { …
  , usePlayerAI :: Bool
  }

data PlayerGameParameters = PlayerGameParameters
  { …
  , lagTime :: Word
  }

For a default lag time, we'll use 5. This gives the player 4 moves for ever enemy move. We'll add an extra command line parser that will look for the argument --use-player-ai. We'll use this to fill in the parameter value.

usePlayerAIInfo :: Parser Bool
usePlayerAIInfo = switch
  (long "use-player-ai" <>
    help "Whether to use the AI version of the player")

There are also some structural changes we want to make in the game. Both the player and enemies can now move on the same update cycle, so we have to decide how they interact.

We'll now have a series of discrete update functions for each part of the game. Each of these functions changes the world in some particular way. So they all have the same type signature. We'll structure our update function by composing these different functions. Here's what it might look like:

updateFunc :: Float -> World -> World
updateFunc _ w
  | … -- Win/Lose Conditions
  | otherwise = newWorld -- Normal Game Tick
  where
    afterPlayerMoveWorld = if usePlayerAI . worldParameters $ w
      then
        updateWorldForPlayerMove .
        clearStunCells .
        incrementWorldTime $ w
      else clearStunCells . incrementWorldTime $ w

    newWorld :: World
    newWorld =
      updateWorldForEnemyTicks .
      updateWorldForPlayerTick .
      updateWorldForEnemyMoves .
      updateWorldForPlayerMove .
      clearStunCells .
      incrementWorldTime $
      w

-- Reduce Stun Timers, etc.
updateWorldForEnemyTicks :: World -> World
updateWorldForPlayerTick :: World -> World

-- Update Locations
updateWorldForEnemyMoves :: World -> World

-- Update Location, Pickup Drills, Activate Stun if necessary
updateWorldForPlayerMove :: World -> World

incrementWorldTime :: World -> World

clearStunCells :: World -> World

Note though that we do want to account for the case where the player isn't AI controlled. So the final product actually looks like this:

updateFunc :: Float -> World -> World
updateFunc _ w
  ...
  | otherwise = newWorld
  where
    afterPlayerMoveWorld = if usePlayerAI . worldParameters $ w
      then
        updateWorldForPlayerMove .
        clearStunCells .
        incrementWorldTime $ w
      else clearStunCells . incrementWorldTime $ w

    newWorld :: World
    newWorld =
      updateWorldForEnemyTicks .
      updateWorldForPlayerTick .
      updateWorldForEnemyMoves $
      afterPlayerMoveWorld

We won't go over most of these changes in depth right here, as they're purely refactoring. In future articles we'll definitely look a bit more at how the enemy movement code changed. We'll want it to look as much as possible like the player AI code so we can machine . In the next section, we'll look at the player move function in a little more detail before writing our AI. Before that though, it's worth noting that we should also disable our input handler when using the AI:

inputHandler :: Event -> World -> World
inputHandler event w
  ...
  | usePlayerAI . worldParameters $ w = w -- No updates when AI is on!

Wrapping the Player Move

Above, we can see a mutator function updateWorldForPlayerMove. This will mainly be a wrapper around our primary AI function, makePlayerMove. But we'll establish a general pattern with it. This wrapper will first handle the game logic of determining whether we should move or not.

updateWorldForPlayerMove :: World -> World
updateWorldForPlayerMove w = if shouldMovePlayer
  then worldAfterMove
  else w
  where
    shouldMovePlayer =
      (worldTime w)
      `mod`
      (lagTime . playerGameParameters . worldParameters $ w) == 0
    worldAfterMove = ...

Then it will call the AI function. It will use the results to figure out what world changes are necessary and apply them. The object is to separate the "brain" from the game logic as much as possible. Note that we update the world for the stun first, and then the player's move.

updateWorldForPlayerMove :: World -> World
updateWorldForPlayerMove w = if shouldMovePlayer
  then worldAfterMove
  else w
  where
    shouldMovePlayer =
      (worldTime w) `mod`
      (lagTime . playerGameParameters . worldParameters $ w) == 0
    move = makePlayerMove w
    player = worldPlayer w
    currentLoc = playerLocation player

    worldAfterStun = if activateStun move
      then modifyWorldForStun w
      else w

    newLocation = nextLocationForMove
      (worldBoundaries w Array.! currentLoc)
      currentLoc   
      (playerMoveChoice move)
    worldAfterMove = modifyWorldForPlayerMove
      worldAfterStun newLocation

-- Stun enemies and change parameters as needed
modifyWorldForStun :: World -> World
...

-- Changes the player's location, track drill pickups
modifyWorldForPlayerMove :: World -> Location -> World
…

-- Take a move direction and give the location
nextLocationForMove ::
  CellBoundaries -> Location -> MoveChoice -> Location

Note we can apply more game logic and rules in our World modifier functions. Suppose, for some reason, the AI function returns True to stun enemies when our stun is on cooldown. It's the job of modifyWorldForStun to ensure nothing actually happens.

Shortest Path

Now that that's done, we can start writing our AI function at last! Let's start simple, and find the shortest path to the end.

makePlayerMove w = …
  where
    currentPlayer = worldPlayer w
    playerLoc = playerLocation currentPlayer
    maze = worldBoundaries w

    shortestPath = getShortestPath maze playerLoc (endLocation w)

Now we'll derive a PlayerMoveChoice based on that path. As mentioned above, it's tempting to return the location on the path. But remember, we want to limit the output scope as much as we can. Let's make a function for getting the direction out of two locations.

getMoveChoice :: Location -> Location -> MoveChoice
getMoveChoice (x1, y1) (x2, y2)
  | y2 == y1 + 1 = MoveUp
  | x2 == x1 + 1 = MoveRight
  | y2 == y1 - 1 = MoveDown
  | x2 == x1 - 1 = MoveLeft
  | otherwise = StandStill

So now we could, if we were naive, simply get out our move choice from the path:

makePlayerMove w = PlayerMove moveChoice False
  where
    …
    shortestPath = getShortestPath maze playerLoc (endLocation w)
    moveChoice = if null shortestPath then StandStill else getMoveChoice playerLoc (head shortestPath)

At this point, we should be able to run our game! The player will boldly walk towards the destination square through the maze. But if we have any enemies in our path, we're toast! Let's determine how we can use our stun!

Stunning Enemies

To determine when to use our stun, let's first get a set of the active enemy locations.

makePlayerMove w =
  where
    …
    shortestPath = …
    activeEnemyLocs = Set.fromList
      (enemyLocation <$>
        (filter (\e -> enemyCurrentStunTimer e == 0)
          (worldEnemies w)))

Now let's truncate the path to only include spots that might be in our stun radius. Then we can find if an enemy is there:

makePlayerMove w = (moveChoice, useStun)
  where
    …
    shortestPath = …
    enemyLocs = Set.fromList (enemyLocation <$> (worldEnemies w))
    radius = stunRadius . playerGameParameters . worldParameters $ w
    enemyClose = any
      (\l -> Set.member l activeEnemyLocs)
      (take radius shortestPath)
    canStun = playerCurrentStunDelay currentPlayer == 0
    useStun = enemyClose && canStun

We're getting closer now! We'll find that our player can stun enemies as long as it's ready. But if the stun isn't ready, we'll run straight into them! We don't want that! So let's figure out how to make a good retreat in case we don't have our stun ready.

Retreating

This leaves us with our last bit of logic. If an enemy stands between us and our shortest path, is close by, and we don't have our stun ready, we should run away. We'll make this as simple as possible by picking the first adjacent location that isn't on our shortest path. This doesn't always work that well. But it'll do for now. We need a list of adjacent locations, and then we select one that isn't on our shortest path. Here's how that logic pans out:

makePlayerMove :: World -> PlayerMove
makePlayerMove w = PlayerMove finalMoveChoice useStun
  where
    ...
    shortestPath = getShortestPath maze playerLoc (endLocation w)
    shortestPathMoveLocation = if null shortestPath
      then playerLoc
      else (head shortestPath)
    shortestPathMoveChoice = getMoveChoice
      playerLoc shortestPathMoveLocation

    activeEnemyLocs = ...
    radius = ...
    enemyClose = ...

    canStun = playerCurrentStunDelay currentPlayer == 0

    possibleMoves = getAdjacentLocations maze playerLoc

    (finalMoveChoice, useStun) = if not enemyClose
      then (shortestPathMoveChoice, False)
      else if canStun
        then (shortestPathMoveChoice, True)
        else case find (/= shortestPathMoveLocation) possibleMoves of
          Nothing -> (StandStill, False)
          Just l -> (getMoveChoice playerLoc l, False)

And now our AI actually works quite well! It can navigate the maze and stun enemies when it needs to. When it has to wait for its stun to re-charge, it'll back away from enemies as needed until the stun is ready.

Conclusion

Next week, we'll use some more advanced tactics to navigate the maze. Specifically, we'll look into how we can use our drill powerup. We'll need to re-think how we calculate the shortest path. We won't be using pure maze distance any more, since we can change the maze! So that will be an interesting problem. After we wrap that up, we'll look into separating the game from the GUI component so we can run simulations.

As always, check out our Github repository for full implementation details. This article uses the player-ai branch, so make sure you select that one!

And for more tips on getting better at Haskell, you should subscribe to our mailing list! You'll get access to all our subscriber resources. This includes our Beginners Checklist and our Production Checklist!

Previous
Previous

Advanced Search with Drilling!

Next
Next

Gloss Review!