Building a Bigger World

maze.png

Last week we looked at some of the basic components of the Gloss library. We made simple animations and simulations, as well as a very simple "game" taking player input. This week, we're going to start making a more complex game!

Our game will involve navigating a maze, from start to finish. In fact, this week, we're not even going to make it very "mazy". We're just going to set up an open grid to navigate around with our player. But over the course of these next few weeks, we'll add more and more features, like enemies and hazards. At some point, we'll have so many features that we'll need a more organized scheme to keep track of everything. At that point, we'll discuss game architecture. You can take a look at the code for this game on our Github repository. For this part, you'll want to look at the part-1 branch.

Game programming is only one of the many interesting ways we can use Haskell. Take a look at our Production Checklist for some more ideas!

Making Our World

As we explored in the last part, the World type is central to how we define our game. It is a parameter to all the important functions we'll write. Before we define our World though, let's define a couple helper types. These will clarify many of our other functions.

-- Defined in Graphics.Gloss
-- Refers to (x, y) within the drawable coordinate system
type Point = (Float, Float)

-- Refers to discrete (x, y) within our game grid.
type Location = (Int, Int)

data GameResult = InProgress | PlayerWin | PlayerLoss

Let's start our World type now with a few simple elements. We'll imagine the game board as a grid with a fixed size, with the tiles having coordinates like (0,0) in the bottom left. We'll want a start location and an ending location for the maze. We'll also want to track the player's current location as well as the current "result" of the game:

data  World = World
  { playerLocation :: Location
  , startLocation :: Location
  , endLocation :: Location
  , gameResult :: GameResult
  …
  }

Now we need to represent the "maze". In other words, we want to be able to track where the "walls" are in our grid. We'll make a data type to represent to boundaries for any particular cell. Then we'll stick a mapping from each location in our grid to its boundaries:

data BoundaryType = WorldBoundary | Wall | AdjacentCell Location

data CellBoundaries = CellBoundaries
  { upBoundary :: BoundaryType
  , rightBoundary :: BoundaryType
  , downBoundary :: BoundaryType
  , leftBoundary :: BoundaryType
  }

data  World = World
  { …
  , worldBoundaries :: Map Location CellBoundaries
  }

Populating Our World

Next week we'll look into how we can generate interesting mazes. But for now, our grid will only have "walls" on the outside, not in the middle. To start, we'll define a function that takes the number of rows and columns in our grid and a particular location. It will return the "boundaries" of the cell at that location. Each boundary tells us if there is a wall in one direction, or if we are clear to move to a different cell. All we need to check is if we're about to exceed the boundary in that direction.

simpleBoundaries :: (Int, Int) -> Location -> CellBoundaries
simpleBoundaries (numColumns, numRows) (x, y) = CellBoundaries
  (if y + 1 < numRows
    then AdjacentCell (x, y+1)
    else WorldBoundary)
  (if x + 1 < numColumns
    then AdjacentCell (x+1, y)
    else WorldBoundary)
  (if y > 0 then AdjacentCell (x, y-1) else WorldBoundary)
  (if x > 0 then AdjacentCell (x-1, y) else WorldBoundary)

Our main function now will loop through all the different cells in our grid and make a map out of them:

boundariesMap :: (Int, Int) -> Map.Map Location CellBoundaries
boundariesMap (numColumns, numRows) = Map.fromList
  (buildBounds <$> (range ((0,0), (numColumns, numRows))))
  where
    buildBounds :: Location -> (Location, CellBoundaries)
    buildBounds loc =
      (loc, simpleBoundaries (numColumns, numRows) loc)

Now we have all the tools we need to populate our initial world:

main = play
  windowDisplay
  white
  20
  (World (0, 0) (0,0) (24, 24) InProgress (boundariesMap (25, 25))
  drawingFunc ...
  inputHandler …
  updateFunc ...

Drawing Our World

Now we need to draw our world. We'll begin by passing a couple new parameters to our drawing function. We'll need offset values that will tell us the Point in our geometric coordinate system for the Location (0,0). We'll also take a floating point value for the cell size. Then we will also, of course, take the World as a parameter:

drawingFunc :: (Float, Float) -> Float -> World -> Picture
drawingFunc (xOffset, yOffset) cellSize world = …

Before we do anything else, let's define a type called CellCoordinates. This will contain the Points for the center and four corners of a cell in our grid.

data CellCoordinates = CellCoordinates
  { cellCenter :: Point
  , cellTopLeft :: Point
  , cellTopRight :: Point
  , cellBottomLeft :: Point
  , cellBottomRight :: Point
  }

Next, let's define a conversion function from a Location to one of the coordinate objects. This will take the offsets, cell size, and the desired location.

locationToCoords ::
  (Float, Float) -> Float -> Location -> CellCoordinates
locationToCoords (xOffset, yOffset) cellSize (x, y) = CellCoordinates
  (centerX, centerY) -- Center
  (centerX - halfCell, centerY + halfCell) -- Top Left
  (centerX + halfCell, centerY + halfCell) -- Top Right
  (centerX - halfCell, centerY - halfCell) -- Bottom Left
  (centerX + halfCell, centerY - halfCell) -- Bottom Right
  where
    (centerX, centerY) =
      ( xOffset + (fromIntegral x) * cellSize
      , yOffset + (fromIntegral y) * cellSize)
    halfCell = cellSize / 2.0

Now we can go ahead and make the first few simple pictures in our game. We'll have colored polygons for the start and end locations, and a circle for the player token. The player marker is easiest:

drawingFunc (xOffset, yOffset) cellSize world =
  Pictures [startPic, endPic, playerMarker]
  where
    conversion = locationToCoords (xOffset, yOffset) cellSize
    (px, py) = cellCenter (conversion (playerLocation world))
    playerMarker = translate px py (Circle 10)
    startPic = …
    endPic = ...

We find its coordinates through our conversion, and then translate a circle. For our start and end points, we'll want to do something similar, except we want the corners, not the center. We'll use the corners as the points in our polygons and draw these polygons in appropriate colors.

drawingFunc (xOffset, yOffset) cellSize world =
  Pictures [startPic, endPic, playerMarker]
  where
    conversion = locationToCoords (xOffset, yOffset) cellSize
    ...
    startCoords = conversion (startLocation world)
    endCoords = conversion (endLocation world)
    startPic = Color blue (Polygon
      [ cellTopLeft startCoords
      , cellTopRight startCoords
      , cellBottomRight startCoords
      , cellBottomLeft startCoords
      ])
    endPic = Color green (Polygon
      [ cellTopLeft endCoords
      , cellTopRight endCoords
      , cellBottomRight endCoords
      , cellBottomLeft endCoords
      ])

Now we need to draw the wall lines. So we'll have to loop through the wall grid, drawing the relevant lines for each individual cell.

drawingFunc (xOffset, yOffset) cellSize world = Pictures
  [mapGrid, startPic, endPic, playerMarker]
  where
  …
    mapGrid = Pictures $concatMap makeWallPictures
      (Map.toList (worldBoundaries world))

    makeWallPictures :: (Location, CellBoundaries) -> [Picture]
    makeWallPictures ((x, y), CellBoundaries up right down left) = ...

When drawing the lines for an individual cell, we'll use thin lines when there is no wall. We can make these with the Line constructor and the two corner points. But we want a separate color and thickness to distinguish an impassable wall. In this second case, we'll want two extra points that are offset so we can draw a polygon. Here's a helper function we can use:

drawingFunc (xOffset, yOffset) cellSize world = ...
  where
   ...
    drawEdge :: (Point, Point, Point, Point) ->
                 BoundaryType -> Picture
    drawEdge (p1, p2, _, _) (AdjacentCell _) = Line [p1, p2]
    drawEdge (p1, p2, p3, p4) _ =
      Color blue (Polygon [p1, p2, p3, p4])

Now to apply this function, we'll need to do a little math to dig out all the individual coordinates out of this cell.

drawingFunc (xOffset, yOffset) cellSize world =
  Pictures [mapGrid, startPic, endPic, playerMarker]
  where
    ...
    makeWallPictures :: (Location, CellBoundaries) -> [Picture]
    makeWallPictures ((x,y), CellBoundaries up right down left) =
      let coords = conversion (x,y)
          tl@(tlx, tly) = cellTopLeft coords
          tr@(trx, try) = cellTopRight coords
          bl@(blx, bly) = cellBottomLeft coords
          br@(brx, bry) = cellBottomRight coords
      in  [ drawEdge (tr, tl, (tlx, tly - 2), (trx, try - 2)) up
          , drawEdge (br, tr, (trx-2, try), (brx-2, bry)) right
          , drawEdge (bl, br, (brx, bry+2), (blx, bly+2)) down
          , drawEdge (tl, bl, (blx+2, bly), (tlx+2, tly)) left
          ]

But that's all we need! Now our drawing function is complete!

Player Input

The last thing we need is our input function. This is going to look a lot like it did last week. We'll only be looking at the arrow keys. And we'll be updating the player's coordinates if the move they entered is valid. To start, let's figure out how we get the bounds for the player's current cell (we'll assume the location is in our map).

inputHandler :: Event -> World -> World
inputHandler event w = case event of
  (EventKey (SpecialKey KeyUp) Down _ _) -> ...
  (EventKey (SpecialKey KeyDown) Down _ _) -> ...
  (EventKey (SpecialKey KeyRight) Down _ _) -> ...
  (EventKey (SpecialKey KeyLeft) Down _ _) -> ...
  _ -> w
  where
    cellBounds = fromJust $ Map.lookup (playerLocation w) (worldBoundaries w)

Now we'll define a function that will take an access function to the CellBoundaries. It will determine what our "next" location is.

inputHandler :: Event -> World -> World
inputHandler event w = case event of
  ...
  where
    nextLocation :: (CellBoundaries -> BoundaryType) -> Location
    nextLocation boundaryFunc = case boundaryFunc cellBounds of
      (AdjacentCell cell) -> cell
      _ -> playerLocation w

Finally, we pass the proper access function for the bounds with each direction, and we're done!

inputHandler :: Event -> World -> World
inputHandler event w = case event of
  (EventKey (SpecialKey KeyUp) Down _ _) ->
    w { playerLocation = nextLocation upBoundary }
  (EventKey (SpecialKey KeyDown) Down _ _) ->
    w { playerLocation = nextLocation downBoundary }
  (EventKey (SpecialKey KeyRight) Down _ _) ->
    w { playerLocation = nextLocation rightBoundary }
  (EventKey (SpecialKey KeyLeft) Down _ _) ->
    w { playerLocation = nextLocation leftBoundary }
  _ -> w
  where
    ...

Tidying Up

Now we can put everything together in our main function with a little bit of glue.

main :: IO ()
main = play
  windowDisplay
  white
  20
  (World (0, 0) (0,0) (24,24) (boundariesMap (25, 25)))
  (drawingFunc (globalXOffset, globalYOffset) globalCellSize)
  inputHandler
  updateFunc

updateFunc :: Float -> World -> World
updateFunc _ = id

Note that for now, we don't have much of an "update" function. Our world doesn't change over time. Yet! We'll see in the coming weeks what other features we can add that will make use of this.

Conclusion

So we've finished stage 1 of our simple game! You can explore the part-1 branch on our Github repository to look at the code if you want! Come back next week and we'll explore how we can actually create a true maze, instead of an open grid. This will involve some interesting algorithmic challenges!

For some more ideas of advanced Haskell libraries, check out our Production Checklist. You can also read our Web Skills Series for a more in-depth tutorial on some of those ideas.

Previous
Previous

Generating More Difficult Mazes!

Next
Next

Making a Glossy Game! (Part 1)