Spring Cleaning: Parameters and Saving!
Our game is a lot more interesting after the changes we made last week. But there's still lots of room for improvement. There are many things that could make the game more or less interesting, depending how we tune things. For instance, how many enemies is too many? What's a good stun duration? How quickly does the game get harder if we tweak these parameters?
Right now, it would be hard for us to answer these questions in a systematic way. We've baked many of these parameters directly into the code. So we would have to recompile everything if we wanted to test out another version of the game. This is a bad sign. We should be able to run the same binary with different sets of parameters.
Another issue with our game is that the only real "flow" is to start off with a random arrangement. We don't know what the map will be or where the enemies start. But if we want to test how well certain concepts work, we'll want true re-playability. In other words, we'll want to be able to start the game from a certain state we've established.
This week, we'll start to clean these things up. The first job will be to move a lot of our magic numbers into the World
type. Then we'll devise a way to serialize the complete world state. We've already done the hard work of ensuring we can serialize the map. The rest will be pretty straightforward using JSON instances. We'll wrap up this week by adding the option to save the game in the middle of the action. Then next week, we'll add some options to our game so we can load a particular starting state from a file.
As with each of the different phases of this projects, you can take a look at our Github repository to see how we do everything. For this article, you should be following the part-8
branch. We'll also provide a couple commit links for so you can follow along step-by-step.
As you get better at using Haskell, you'll be able to use it for more and more types of projects. Download our Production Checklist for some ideas!
Parameterizing the App
There are a lot of "magic numbers" floating around our app right now. Some of these have to do with game-play logic. How many enemies are there? What's their cool-down time? How long is our player's stun timer? Then there are other parameters that have to do with how we draw the game. For instance, what colors do we use? How big are the cells?
We make this distinction because we should be able to run our game without any render information. At some point, we'll run simulations of this game that don't get drawn at all. So it would be useless to have drawing information around. Thus we'll have GameParameters
types that will live in the World
. Then we'll have RenderParameters
types for drawing everything.
With that said, let's starting devising what information these types contain. We'll start out with types describing the player and enemy parameters:
data PlayerGameParameters = PlayerGameParameters
{ initialStunTimer :: Word
, stunTimerIncrease :: Word
, stunTimerMax :: Word
, stunRadius :: Int
}
data EnemyGameParameters = EnemyGameParameters
{ initialStunTime :: Word
, stunTimeDecrease :: Word
, minStunTime :: Word
, enemyRandomMoveChance :: Word
, initialLagTime :: Word
, minLagTime :: Word
}
Now we can use these to populate a bigger type with more generic game parameters:
data GameParameters = GameParameters
{ numRows :: Int
, numColumns :: Int
, numEnemies :: Int
, tickRate :: Int
, playerGameParameters :: PlayerGameParameters
, enemyGameParameters :: EnemyGameParameters
, randomGeneratorSeed :: Maybe Int
}
Notice the random seed is a Maybe
value. In the normal circumstances of running the program, we don't want to fix the random generator. But there are cases where we'll want to load from a specific stored state. If we fix the generator seed value, gameplay will be deterministic. This could be a desirable property in some circumstances. In most cases though, this will be Nothing
.
With all these types in place, we'll now add the game parameters to our World
:
data World = World
{ …
, worldParameters :: GameParameters
}
We'll go through a similar process with RenderParameters
. The main difference will be that we will not attach the type to the World
. There will also be a CellRenderParameters
type as well as types for the Player
and Enemy
. This gives us information about how individual cells get displayed on our screen. Here's a quick sample of this code. You can see the other types at the bottom as an appendix.
data RenderParameters = RenderParameters
{ screenWidth :: Float
, screenHeight :: Float
, screenOffsetX :: Float
, screenOffsetY :: Float
, textOffset :: (Float, Float)
, textScale :: (Float, Float)
, playerRenderParameters :: PlayerRenderParameters
, enemyRenderParameters :: EnemyRenderParameters
, cellRenderParameters :: CellRenderParameters
}
data CellRenderParameters = CellRenderParameters
{ cellWallColor :: Color
, cellStunColor :: Color
, cellWallWidth :: Float
}
No More Magic
Once we have these types in place, our next step is to replace the magic numbers (and colors) in our application. We'll need to add the parameters as arguments in a few places. Most of all, the drawingFunc
will need the RenderParameters
argument.
drawingFunc :: RenderParameters -> World -> Picture
...
This process isn't too much of a challenge, as all our important functions take the World
as an input. Then for now, we'll pass our default parameter packs as arguments when running the program. Here's a quick look at changes to our main
function:
main :: IO ()
main = do
gen <- getStdGen
let gameParams = defaultGameParameters
renderParams = defaultRenderParameters
(maze, gen') = generateRandomMaze
gen (numRows gameParams, numColumns gameParams)
(randomLocations, gen'') = runState
(replicateM
(numEnemies gameParams)
(generateRandomLocation
(numRows gameParams, numColumns gameParams)))
gen'
enemies = (mkNewEnemy
(enemyGameParameters gameParams)) <$> randomLocations
endCell = (numColumns gameParams - 1, numRows gameParams - 1)
initialWorld = World
(newPlayer (playerGameParameters gameParams))
(0,0) endCell maze GameInProgress gen'' enemies [] 0
gameParams
play
(windowDisplay renderParams)
white
(tickRate gameParams)
initialWorld
(drawingFunc renderParams)
inputHandler
updateFunc
Take a look at this commit for a longer look at all our parameter changes.
Serializing Our World
Now that we've updated our World
type, we'll want to determine how we can serialize it. For simplicity's sake we'll use JSON serialization. This is mostly a matter of creating (or, if you wish, deriving), a bunch of ToJSON
and FromJSON
instances. Check out this article for a refresher on the Data.Aeson library.
Most of this code is pretty simple. With game parameters, a lot of the instances are a simple matter of creating and parsing pairs. Here's an example with Player
:
instance FromJSON Player where
parseJSON = withObject "Player" $ \o -> do
location <- o .: "location"
currentStunDelay <- o .: "currentStunDelay"
nextStunDelay <- o .: "nextStunDelay"
return $ Player location currentStunDelay nextStunDelay
instance ToJSON Player where
toJSON p = object
[ "location" .= playerLocation p
, "currentStunDelay" .= playerCurrentStunDelay p
, "nextStunDelay" .= playerNextStunDelay p
]
But there are a few caveats. To start, we need to make a separate file for these instances. We'll need our maze parsing code for the World
type, and this depends on the Types
module. We have to avoid the resulting dependency cycle.
It's generally a bad practice to separate instances from the type declarations. We call these "orphan" instances and you'll get a compiler warning about them in other projects. A way around this is to create wrapper types. This is a little tedious, so we won't do it for all the types. But we will show the concept for the Color
type from Graphics.Gloss
. Let's start with a wrapper type:
newtype ColorWrapper = ColorWrapper { unColor :: Color }
Now we can create instances on this wrapper, and they're considered valid. To cover all cases of color, we'd use RGB arrays. But we'll color cover the 9 or so colors we care about and parse them as strings. Here's what the instances look like. Notice how we wrap and unwrap the actually library functions for the colors:
instance ToJSON ColorWrapper where
toJSON (ColorWrapper c) = Ae.String colorStr
where
colorStr
| c == blue = "blue"
| c == red = "red"
| c == yellow = "yellow"
| c == green = "green"
| c == cyan = "cyan"
| c == orange = "orange"
| c == magenta = "magenta"
| c == rose = "rose"
| c == black = "black"
instance FromJSON ColorWrapper where
parseJSON = withText "ColorWrapper" parseText
where
parseText "blue" = return (ColorWrapper blue)
parseText "red" = return (ColorWrapper red)
parseText "yellow" = return (ColorWrapper yellow)
parseText "green" = return (ColorWrapper green)
parseText "cyan" = return (ColorWrapper cyan)
parseText "orange" = return (ColorWrapper orange)
parseText "magenta" = return (ColorWrapper magenta)
parseText "rose" = return (ColorWrapper rose)
parseText "black" = return (ColorWrapper black)
parseText _ = error "Couldn't parse color!"
Then we can use these instances within other parsers for render parameters. The other caveat now is to parse out our World
in two stages. We'll get all the basic fields and parameters first:
instance FromJSON World where
parseJSON = withObject "World" $ \o -> do
player <- o .: "player"
startLoc <- o .: "startLocation"
endLoc <- o .: "endLocation"
result <- o .: "result"
enemies <- o .: "enemies"
stunCells <- o .: "stunCells"
time <- o .: "time"
params <- o .: "gameParameters"
...
Now we'll get the boundaries as a Text
item. We'll parse the maze boundaries out using our parser as well as the number of rows and columns.
instance FromJSON World where
parseJSON = withObject "World" $ \o -> do
...
(boundaryString :: Text) <- o .: "boundaries"
let (rs, cs) = (numRows params, numColumns params)
let boundaries =
case runParser (mazeParser (rs, cs)) "" boundaryString of
Right result -> result
_ -> error "Map parse failed!"
As a last trick, we'll check what the random seed is within our parameters. If it's Nothing
, we'll fix the generator with a seed of 1 and rely on other code to change it:
instance FromJSON World where
parseJSON = withObject "World" $ \o -> do
...
let gen = case randomGeneratorSeed params of
Just i -> mkStdGen i
_ -> mkStdGen 1
return $ World player startLoc endLoc boundaries
result gen enemies stunCells time params
Take a look at this commit to see the full code for these instances. Now let's see how we use them!
Saving Our World
We'd like to make it so that our user can save their game-state by hitting the s
key at any point in the game. This idea starts out simple enough. We add a handler for the key in our inputHandler
.
inputHandler :: Event -> World -> World
inputHandler event w
| worldResult w == GameWon = ...
| worldResult w == GameLost = ...
| otherwise = case event of
...
(EventKey (Char 's') Down _ _) -> ...
But now we're a little stuck! We want to write out to a file, but our handler is a pure function! There miiight be a way to do this without breaking functional purity. Perhaps we could keep a list of saved world states and add a handler to save them at the end of our program. But Gloss wasn't made for that. So we're going to break the rules a bit and resort to unsafePerformIO
. This allows us to run an IO
computation from a seemingly pure context. Here's the basic layout:
inputHandler :: Event -> World -> World
inputHandler event w
...
(EventKey (Char 's') Down _ _) -> unsafeSaveWorldToFile w
unsafeSaveWorldToFile :: World -> World
unsafeSaveWorldToFile w = unsafePerformIO $ do
…
return w
Since we have a JSON instance for our World
, we'll lean on the encodeFile
function. The rest of the work here comes from generating a filename using the current time, for uniqueness:
unsafeSaveWorldToFile :: World -> World
unsafeSaveWorldToFile w = unsafePerformIO $ do
timeAsString <- show . floor <$> getPOSIXTime
currentDir <- getCurrentDirectory
let filename = currentDir ++ "/maze_game_save_" ++ timeAsString
encodeFile filename w
return w
And that's all it takes for us to save some game files! Perhaps you've heard the phrase "don't try this at home." When it comes to unsafePerformIO
, feel free to try it at home, but don't try it at work! Take a look at this commit for details on saving the state.
Conclusion
In spite of unsafePerformIO
, our game feel like a much more "grown-up" program now. The code quality is much better with our parameters. We now have a lot more options of what to do when it comes to improving it. Saving the world state is the first step towards solving some interesting problems. Next week, we'll explore how we can load the saved game states we've created.
As we move forward, we'll keep trying to turn this game into a more mature program. Eventually though, you should think about using Haskell for more common production use cases. To learn about different libraries you can use, download our Production Checklist!
Appendix: Render Parameter Types
data RenderParameters = RenderParameters
{ screenDimen :: Int
, screenOffsetX :: Int
, screenOffsetY :: Int
, textOffset :: (Float, Float)
, textScale :: (Float, Float)
, playerRenderParameters :: PlayerRenderParameters
, enemyRenderParameters :: EnemyRenderParameters
, cellRenderParameters :: CellRenderParameters
}
data PlayerRenderParameters = PlayerRenderParameters
{ playerIndicatorSize :: Float
, playerIndicatorColor :: Color
, playerStunIndicatorSize :: Float
, playerStunIndicatorColor :: Color
}
data EnemyRenderParameters = EnemyRenderParameters
{ enemySize :: Float
, enemyBaseColor :: Color
, enemyStunnedColor :: Color
}
data CellRenderParameters = CellRenderParameters
{ cellWallColor :: Color
, cellStunColor :: Color
, cellWallWidth :: Float
}
defaultRenderParameters :: RenderParameters
defaultRenderParameters = RenderParameters
625 10 10 (-275, 0) (0.12, 0.25) playerParams enemyParams cellParams
where
playerParams = PlayerRenderParameters 10 black 5 red
enemyParams = EnemyRenderParameters 10 orange yellow
cellParams = CellRenderParameters blue cyan 2