DEV Community

Cover image for F# Squirrel Brains: Adding Actors and Getting Functional
Matt Eland
Matt Eland

Posted on

F# Squirrel Brains: Adding Actors and Getting Functional

This is part two of a tutorial series on using F# to build a genetic algorithm in .NET Core.

By the end of the article you'll learn a lot more about the specifics of F# and we'll have a player controlled squirrel that can move around the game world.

Player Input

By the end of the series, the application will use genetic algorithms to evolve a squirrel capable of getting an acorn and returning it to its tree without being eaten by the dog, but the intent of this series is to introduce you to various parts of the .NET Core ecosystem as well as the F# programming language.

Last time we set up a F# library and console application that rendered a 2D grid with a single squirrel on it and allowed the player to regenerate the grid by pressing R or exit by pressing X.

In this article, we'll:

  • Explore additional functional concepts as we incorporate feedback from a popular F# author
  • Introduce the Dog, Rabbit, Acorn, and Tree Actors
  • Refine the level generation to make sure actors start in valid spots
  • Allow the player to move the Squirrel around the game grid
  • Clean up the main game loop's input code

On that first point, Isaac Abraham, author of the fantastic book Get Programming with F# came across my last article and sent me a merge request with some terrific feedback.

I'll be sprinkling in this feedback as we go to help you understand the lessons I'm learning as we go.

Let's get started.

Smarter World Positions

Let's start with something small. Previously I had been using both namespace and module declarations like the following:

namespace MattEland.FSharpGeneticAlgorithm.Logic

module WorldPos =

  type WorldPos = {X: int32; Y:int32}

  let newPos x y = {X = x; Y = y}
Enter fullscreen mode Exit fullscreen mode

That works, but it's inefficient. You can actually merge them together into the module declaration like the following:

module MattEland.FSharpGeneticAlgorithm.Logic.WorldPos

type WorldPos = {X: int32; Y:int32}

let newPos x y = {X = x; Y = y}

let isAdjacentTo (posA: WorldPos) (posB: WorldPos): bool =
  let xDiff = abs (posA.X - posB.X)
  let yDiff = abs (posA.Y - posB.Y)
  let result = xDiff <= 1 && yDiff <= 1
  result
Enter fullscreen mode Exit fullscreen mode

This reduces nesting and keeps logic concise.

You'll also note that we added an isAdjacentTo method. This isn't anything extremely new, though it uses the built-in abs function to grab the absolute value of a number.

We'll make use of this method later on in world generation.

Adding New Actor Types

Ultimately our simulation will contain the following actors:

  • Squirrel - The squirrel is the actor we will be evolving. It need to get an acorn and return to its tree without being eaten before time runs out.
  • Acorn - The acorn is the squirrel's objective. It does nothing on its own and disappears once the squirrel enters its tile.
  • Tree - The tree does nothing. If the squirrel enters the tree tile once it has the acorn, the simulation ends with a win for the squirrel.
  • Doggo - The dog sits still until the rabbit or squirrel enter a nearby tile. Once that happens, the dog will eat the rabbit or squirrel. This is a hazard our squirrel must avoid.
  • Rabbit - The rabbit wanders around the simulation at random. It effectively does nothing except create chaos.

Our actor definition file looks like the following:

module MattEland.FSharpGeneticAlgorithm.Logic.Actors

open MattEland.FSharpGeneticAlgorithm.Logic.WorldPos

type ActorKind =
  | Squirrel of hasAcorn:bool
  | Tree
  | Acorn
  | Rabbit
  | Doggo

type Actor =
  { Pos : WorldPos
    ActorKind : ActorKind }

let getChar actor =
  match actor.ActorKind with
  | Squirrel _ -> 'S'
  | Tree _ -> 't'
  | Acorn _ -> 'a'
  | Rabbit _ -> 'R'
  | Doggo _ -> 'D'
Enter fullscreen mode Exit fullscreen mode

Previously I was using inheritance for the Actor and Squirrel classes since F# wasn't allowing me to use different types of discriminated unions in the same collection.

Isaac Abraham pointed out that I could define a single Actor type and have that type define a specific kind that indicated which kind of actor it was. As we see above, this still allows us to have custom state on specific kinds of actors - such as the squirrel having the acorn.

The getChar method uses discriminated unions to very good effect here. The ActorKind type is a discriminated union that says that an ActorKind can be either a Squirrel, Doggo, Acorn, Tree, or Rabbit. The getChar method uses match to respond to various ActorKind values on actor, returning the appropriate character (since each match clause is the last statement run in the method).

The nice thing about this, is that if we add a new ActorKind later on, F# will complain that we didn't add a match case for it in getChar, helping us avoid mistakes and maintain a high level of quality.

World

World is a longer file, so let's go over it section by section:

module MattEland.FSharpGeneticAlgorithm.Logic.World

open MattEland.FSharpGeneticAlgorithm.Logic.Actors
open MattEland.FSharpGeneticAlgorithm.Logic.WorldPos

type World =
  { MaxX : int
    MaxY : int
    Squirrel : Actor
    Tree : Actor
    Doggo : Actor
    Acorn : Actor
    Rabbit : Actor }

  member this.Actors = [| this.Squirrel; this.Tree; this.Doggo; this.Acorn; this.Rabbit |]
Enter fullscreen mode Exit fullscreen mode

Here we define the World type that contains an array of actors and contains basic dimensional information.

The [| and |] syntax indicates an array with ; separators between elements. The array here just refers to the constant entities associated with the various actor types. Note again that nothing is mutable, so the World instance will never change.


Next we introduce some random generation logic:

let getRandomPos(maxX:int32, maxY:int32, getRandom): WorldPos =
  let x = getRandom maxX
  let y = getRandom maxY
  newPos x y

let buildItemsArray (maxX:int32, maxY:int32, getRandom): Actor array =
  [| { Pos = getRandomPos(maxX, maxY, getRandom); ActorKind = Squirrel false }
     { Pos = getRandomPos(maxX, maxY, getRandom); ActorKind = Tree }
     { Pos = getRandomPos(maxX, maxY, getRandom); ActorKind = Doggo }
     { Pos = getRandomPos(maxX, maxY, getRandom); ActorKind = Acorn }
     { Pos = getRandomPos(maxX, maxY, getRandom); ActorKind = Rabbit }
  |]
Enter fullscreen mode Exit fullscreen mode

getRandomPos is largely unchanged and still grabs a random position within the acceptable range.

buildItemsArray is new and builds our array of randomly-positioned entities. Here we're repeatedly generating random positions, then specifying he ActorKind of the entity. Note that for the squirrel we pass in false indicating that the Squirrel does not have the acorn initially.


Next let's look at a function that is at the core of the world generation mechanism:

let hasInvalidlyPlacedItems (items: Actor array, maxX: int32, maxY: int32): bool =
  let mutable hasIssues = false

  for itemA in items do
    // Don't allow items to spawn in corners
    if (itemA.Pos.X = 1 || itemA.Pos.X = maxX) && (itemA.Pos.Y = 1 || itemA.Pos.Y = maxY) then
      hasIssues <- true

    for itemB in items do
      if itemA <> itemB then

        // Don't allow two objects to start next to each other
        if isAdjacentTo itemA.Pos itemB.Pos then
          hasIssues <- true

  hasIssues
Enter fullscreen mode Exit fullscreen mode

The hasInvalidlyPlacedItems function searches all actors to see if any rules are violated. Specifically, after generation, no actor can start in a corner and no actor can start adjacent to any other actor.

The syntax here shouldn't be anything new, but is included for completeness.


Now, let's look at our core generation code:

let generate (maxX:int32, maxY:int32, getRandom): Actor array =
  let mutable items: Actor array = buildItemsArray(maxX, maxY, getRandom)

  // It's possible to generate items in invalid starting configurations. Make sure we don't do that.
  while hasInvalidlyPlacedItems(items, maxX, maxY) do
    items <- buildItemsArray(maxX, maxY, getRandom)

  items

let makeWorld maxX maxY random =
  let actors = generate(maxX, maxY, random)
  { MaxX = maxX
    MaxY = maxY
    Squirrel = actors.[0]
    Tree = actors.[1]
    Doggo = actors.[2]
    Acorn = actors.[3]
    Rabbit = actors.[4] }
Enter fullscreen mode Exit fullscreen mode

The generate method builds a candidate set of arranged actors. Since the random positioning logic can result in actors placed in invalid locations, the hasInvalidlyPlacedItems function is called and the items collection will be replaced until a group of actors is chosen that have valid positions.

makeWorld is a simple function that grabs the list of actors and returns a World instance with those actors. Our calling code can call makeWorld with basic dimensions and a Random instance and get back a world in a valid initial state.

Simulator

Now let's get into some new territory. We're going to start allowing for simulation of the game world starting in this article with controlling the squirrel via player input.

module MattEland.FSharpGeneticAlgorithm.Logic.Simulator

open MattEland.FSharpGeneticAlgorithm.Logic.WorldPos
open MattEland.FSharpGeneticAlgorithm.Logic.World
open MattEland.FSharpGeneticAlgorithm.Logic.Actors

type GameState = { World : World; Player : Actor }

let isValidPos pos (world: World): bool = 
  pos.X >= 1 && pos.Y >= 1 && pos.X <= world.MaxX && pos.Y <= world.MaxY

let hasObstacle pos (world: World) : bool =
  world.Actors
  |> Seq.exists(fun actor -> pos = actor.Pos)
Enter fullscreen mode Exit fullscreen mode

GameState is a standard object used to represent the game's state at a specific point in time.

isValidPos is nothing special and just does a boundaries check.

hasObstacle uses the pipe forward operator (|>) to invoke Seq.exists with world.Actors as the first parameter of the seq.Exists function call.

seq.Exists is one of many functions associated with sequences. This checks all actors to determine if any exists at the specified position by using a matching function on each actor.


Next let's look at our code to move an actor around:

let moveActor world actor xDiff yDiff = 
  let pos = newPos (actor.Pos.X + xDiff) (actor.Pos.Y + yDiff)

  if (isValidPos pos world) && not (hasObstacle pos world) then
    let actor = { actor with Pos = pos }
    match actor.ActorKind with
    | Squirrel _ -> { world with Squirrel = actor }
    | Tree -> { world with Tree = actor }
    | Acorn -> { world with Acorn = actor }
    | Rabbit -> { world with Rabbit = actor }
    | Doggo -> { world with Doggo = actor }
  else
    world
Enter fullscreen mode Exit fullscreen mode

First we calculate the new position by looking at xDiff and yDiff to calculate a new candidate position. Next we check our two utility positions to make sure the position is unoccupied and is within the bounds of the game world.

If the position is valid, then we create actor which is a clone identical to the old actor parameter, but using the new Position via the with keyword.

Tip: If you come from a JavaScript background, you can think of **with* as similar to the JavaScript / TypeScript rest operator (...)*

Next we create a clone of the world, only using the new version of the appropriate actor kind instead of the old version.

Finally, if the position was invalid, we just return the existing instance of the world without modification.


Simulator also has a function to help with presentation:

let getCharacterAtCell(x, y) (world:World) =
  let actorAtCell =
    world.Actors
    |> Seq.tryFind(fun actor -> actor.Pos.X = x && actor.Pos.Y = y)

  match actorAtCell with
  | Some actor -> getChar actor
  | None -> '.'

Enter fullscreen mode Exit fullscreen mode

This uses Seq.tryFind to search the world.Actors array for an actor at the specified position. This can either return a match or not. Put another way, this either returns some actor or none. This is an interesting opportunity to look at F# and how it can handle nullable values.

Because the actorAtCell variable is effectively an optional value, we can match on it using the Some and None keywords. Here we say that if Some actor is there, we'll return the result of the getChar function, otherwise if there is None present, we'll just use . to indicate empty space.

This is an important functional concept and a good way to deal with null values. If you're curious about this concept in C# code, take a look at my article on using the Language-Ext library to avoid nulls in C#.


Finally, we have some pieces of logic in this file related to handling player input:

type GameCommand =
  | MoveLeft | MoveRight
  | MoveUp | MoveDown
  | MoveUpLeft | MoveUpRight
  | MoveDownLeft | MoveDownRight
  | Wait
  | Restart

let playTurn state player getRandomNumber command =
  let world = state.World
  match command with 
  | MoveLeft -> { state with World = moveActor world player -1 0 }
  | MoveRight -> { state with World = moveActor world player 1 0 } 
  | MoveUp -> { state with World = moveActor world player 0 -1 } 
  | MoveDown -> { state with World = moveActor world player 0 1 }
  | MoveUpLeft  -> { state with World = moveActor world player -1 -1 }
  | MoveUpRight -> { state with World = moveActor world player 1 -1 }
  | MoveDownLeft -> { state with World = moveActor world player -1 1 } 
  | MoveDownRight -> { state with World = moveActor world player 1 1 }
  | Wait ->
    printfn "Time Passes..."
    state
  | Restart ->
    let world = makeWorld 13 13 getRandomNumber
    { World = world; Player = world.Squirrel }
Enter fullscreen mode Exit fullscreen mode

The GameCommand is a simple discriminated union containing all types of player input except the Exit command. We'll talk more about that later, but for now let's focus on the playTurn function.

The playTurn function takes in a prior state and a Command, then matches it based on the command and returns the new state. If you're wondering about the moveActor calls and the numbers at the end, those are the deltas for the squirrel's position. Overall, playTurn should be extremely familiar if you've ever worked with a reducer or patterns like Redux.

Console Application

To finish off this article, let's modify the console application to make use of our new capabilities.

We showed the GameCommand type earlier. Let's look at how it fits into the main application:

type Command =
  | Action of GameCommand
  | Exit
Enter fullscreen mode Exit fullscreen mode

A Command can either be an action that the simulator should respond to or a client command to Exit the game. Structuring things inside of effectively nested discriminated unions helps focus responsibilities for the main input loop.


Next, let's look at how we map from keyboard input to a Command instance:

let tryParseInput (info:ConsoleKeyInfo) =
    match info.Key with
    | ConsoleKey.LeftArrow -> Some (Action MoveLeft)
    | ConsoleKey.RightArrow -> Some (Action MoveRight)
    | ConsoleKey.UpArrow -> Some (Action MoveUp)
    | ConsoleKey.DownArrow -> Some (Action MoveDown)
    | ConsoleKey.NumPad7 | ConsoleKey.Home  -> Some (Action MoveUpLeft)
    | ConsoleKey.NumPad9 | ConsoleKey.PageUp -> Some (Action MoveUpRight)
    | ConsoleKey.NumPad1 | ConsoleKey.End -> Some (Action MoveDownRight)
    | ConsoleKey.NumPad3 | ConsoleKey.PageDown -> Some (Action MoveDownRight)
    | ConsoleKey.NumPad5 | ConsoleKey.Spacebar | ConsoleKey.Clear -> Some (Action Wait) 
    | ConsoleKey.X -> Some Exit
    | ConsoleKey.R -> Some (Action Restart)
    | _ -> None
Enter fullscreen mode Exit fullscreen mode

Like the seq.tryFind method we used earlier, we're returning either a Some Command or None here, depending on if the player entered something expected or unexpected. The syntax should be largely familiar by now, but it's worth noting how you follow this pattern in custom methods.


Okay, let's finish up by looking at the main game loop:

[<EntryPoint>]
let main argv =
  printfn "F# Console Application Tutorial by Matt Eland"

  let getRandomNumber =
    let r = Random()
    fun max -> (r.Next max) + 1

  let world = makeWorld 13 13 getRandomNumber

  let mutable state = { World = world; Player = world.Squirrel }
  let mutable simulating: bool = true

  while simulating do
    let player = state.World.Squirrel
    let userCommand = getUserInput(state.World) |> tryParseInput

    match userCommand with
    | None -> printfn "Invalid input"
    | Some command -> 
      match command with 
      | Exit -> simulating <- false
      | Action gameCommand -> state <- playTurn state player getRandomNumber gameCommand

  0 // return an integer exit code
Enter fullscreen mode Exit fullscreen mode

A lot of this is familiar from last article, but now makes use of the match keyword.

Specifically, we pipe the result of getUserInput into the tryParseInput method to get Some GameCommand or None.

Finally, we match the mapped command to find if it was something known or unknown. If it's know, we match on the type of command and either exit the game loop or execute the game command and update the game's state.

End Result and Next Steps

The end result of the application up to this point is the following:

Player Input

It's nothing pretty, but we can see how functional programming works in practice.

The complete code for this article is available on GitHub in the Article2 branch.


Next time, we'll spruce this up a bit by moving to a .NET Core 3.0 WPF Desktop Application with actual visuals (gasp!) and implement the game logic for the squirrel to win and lose the game.


Cover Photo by Caleb Martin on Unsplash

Top comments (2)

Collapse
 
vasar007 profile image
Vasily Vasilyev • Edited

Thanks for the great series! Keep up the good work.

By the way, I found a little issue in the current implementation. It's related to GameState record and how it's used.

First of all, additional player value actually isn't needed here:

while simulating do
  let player = state.World.Squirrel // <- ???
  let userCommand = getUserInput(state.World) |> tryParseInput

state value already has Player value and we could use it. However, there is a problem because playTurn method may create new world but doesn't update Player value.

I think GameState record should be implemented as:

type GameState =
  {
    World: World
  }

  member this.Player = this.World.Squirrel

Such version won't cause problems with incorrect references to the actual player. Finally, we can remove player parameter from playTurn method and simplify a liitle bit main:

let mutable state = {
  World = world
}
let mutable simulating = true

while simulating do
  let userCommand =
    getUserInput state.World
    |> tryParseInput

    match userCommand with
      | None -> printfn "Invalid input"
      | Some command ->
        match command with
          | Exit ->
            simulating <- false
          | Action gameCommand ->
            state <- playTurn state getRandomNumber gameCommand
Collapse
 
integerman profile image
Matt Eland

Love the detailed suggestion. I'm aiming to get the game simulation further along and have a unit-test focused article up this weekend.

On the GameState.Player suggestion - yeah, I did find that issue in my article3 branch I'm working on for the next article and have made a fix for that issue.