Week 2: Graphics and Dungeon Basics

This Week's Music

Reddit

This week we will

  • Display an '@' can that move around with the arrow keys.
  • Make a Dungeon type that tracks where walls are, so that the '@' can bump into walls.

Part 1: Graphics

Getting running with Haskell, and Hexes specifically, is pretty similar to other frame-based graphical applications:

  • We'll do some initial setup to get things in place
  • Then we enter a "main loop" that handles control for the rest of the program
    • Gather user input.
    • Update the program state.
    • Render the program state to a backbuffer.
    • Flip the backbuffer and frontbuffer.

With this in mind, let's go over what's in the Main.hs file for our basic demo.

Boilerplate

{-# LANGUAGE TemplateHaskell #-}

module Main where

First, the thing at the top is a pragma, which specifies that we'll be using a compiler extension of some sort. In this case it's an extension that lets us do a little bit of meta-programming. In the Haskell world the main compiler (GHC) develops quite a bit faster than the language standard itself, so it's very common to see pragmas at the top of files enabling all sorts of special features.

The next part just says that this is the Main module, which is where GHC looks for the main action when it compiles our program.

-- base
import Control.Monad (when)
import System.Exit (die)
import Data.Char
import Data.IORef
-- bytestring
import Data.ByteString (ByteString)
-- JuicyPixels
import Codec.Picture
-- transformers
import Control.Monad.IO.Class
-- embed-file
import Data.FileEmbed
-- hexes
import Hexes

Now we've got a big pile of imports. I'm using a comment above each section of imports to say what package the appropriate modules are from. This is not necessary, it just helps me to remember where to look when I need to look up docs.

-- | The data for our display system. It gets embedded into our binary during
-- the compilation process, so we won't have to distribute any support files.
imageBytes :: ByteString
imageBytes = $(embedFile "font-data/FixedSysExcelsior.png")

A ByteString is a series of bytes, and this embedFile thing is using Template Haskell to embed our font image data directly into the final binary during compilation. This way we won't have to distribute anything other than the exe itself once our program is compiled. I like that a lot more than having image files and dlls you have to bundle up with the program. This general technique is not actually unique to Haskell, you can pull the same sort of trick in other languages such as Rust and Java.

-- | Converts any pixel that is a fully opaque green into a transparent black
-- pixel instead. Any other kind of pixel is unaffected.
greenToAlpha :: PixelRGBA8 -> PixelRGBA8
greenToAlpha (PixelRGBA8 0 255 0 255) = PixelRGBA8 0 0 0 0
greenToAlpha p = p

This will be used with our image loading in just a second so that we can have a "transparency color" in our image. That makes for easier editing without needing advanced editing programs. Since I'm just using MS Paint, that's handy.

Main

main :: IO ()
main = do
    baseImage <- pixelMap greenToAlpha <$> either die (pure . convertRGBA8) (decodeImage imageBytes)
    posRef <- newIORef (5,5)
    let rows = 24
        cols = 80
    runHexes rows cols baseImage $ do
        setKeyCallback $ Just $ \key scanCode keyState modKeys -> liftIO $ do
            case keyState of
                KeyState'Released -> pure ()
                _ -> modifyIORef posRef $ case key of
                    Key'Up -> \(px,py) -> (px, min (py+1) (rows-1))
                    Key'Down -> \(px,py) -> (px, max (py-1) 0)
                    Key'Left -> \(px,py) -> (max (px-1) 0, py)
                    Key'Right -> \(px,py) -> (min (px+1) (cols-1), py)
                    _ -> id
        mainLoop posRef

Here's where we get to a part of the program that's actually a whole lot at once to a beginner. We'll go through it in extra detail this first time around.

main :: IO ()
main = do

The main action of a program must always be in the Main module, and it must always have the type IO (), similar to the int main() function in C or the public static void main(String[] args) in Java. Our main will have many sub steps, so on the first line we just say do and then continue the definition by indenting on the next line.

baseImage <- pixelMap greenToAlpha <$> either die (pure . convertRGBA8) (decodeImage imageBytes)

This is an unfortunately long line of code, but it keeps all of our image prep within a single line so we don't have to think about it too much later on. It can just be "that one line that loads the image data".

You have to kinda read it from right to left.

First we use decodeImage on our imageBytes literal, it parses a ByteString into an Either String DynamicImage. Either is a type where the actual value can be, like the name implies, either one of two different options. The two cases are called Left and Right, and by convention the left type is used for an "error" situation and the right type is used for a "success" situation. Haskell does have exceptions and exception handling, but most of the time that's way overkill and you can just have a function return an Either value when you expect there to be errors. With decodeImage we will either have a problem parsing the bytes into an image and get an error message back as a String, or we'll have a successful parse and get a DynamicImage back.

However, this introduces an unfortunate branch into our program. We don't know if our Either value is the Left or Right case. We could use a case expression to match on the to branches directly, but there's a slightly better way.

either :: (a -> c) -> (b -> c) -> Either a b -> c

This function takes one function to convert each case of the Either into some final type c, and then does the case match and application for us. We can do default values, error recovery, whatever the situation calls for. The thing is... we don't actually have any possible recovery strategy if the image doesn't decode properly. We don't have a way to load up an alternate image or anything like that. Worse, since the bytes were embedded into our binary, a failure to parse them probably means that something drastically is wrong with the program. Since there's nothing to lose at this point, we'll just abort the program and print an error message. The die function can do that.

die :: String -> IO a

You might wonder, "How dies die give an a value back?" An a in a type variable means any type at all. It only took in a String, so how can it know to turn that String into any type we'd ever ask for? The answer is that it cheats a bit. Since die knows that it's going to kill the program, it can make the claim that it will give you back a value of any type. It will never fail to live up to that promise, because it will never give you back a value. It's like saying that you can fly whenever it's the 31st of Feburary. So we mix either with die, and we check the type of what we have so far in ghci:

RL-tut> :t either die
either die :: (b -> IO a) -> Either String b -> IO a

The letters of the type variables are a little jumbled around because they don't actually matter themselves. a -> a and b -> b are equivalent types, just written two different ways (this is called "alpha equivalence", if you care). Still, it's telling us that we need a function to convert the Right case. Since die runs in IO, and since the whole expression needs to unify to a single type, then our Right conversion will also need to end up being an IO value as well. Hexes is expecting a Image PixelRGBA8 value, which we can get from a DynamicImage with convertRGBA8. That give us b -> a, but we need IO a. For that we use a function called pure, which takes any value, and "lifts" it into a minimal context. It works for any Applicative, which includes IO. With IO, it just makes an IO that doesn't actually do anything and just gives back the result. There's a similar function called return, but we'll use pure because that helps avoid confusion with the "return" keyword most other languages have.

We can compose convertRGBA8 and pure with the (.) operator:

(.) :: (b -> c) -> (a -> b) -> a -> c
(f . g) x = f (g x)

And now we can check that in ghci too

RL-tut> :t either die (pure . convertRGBA8)
either die (pure . convertRGBA8)
  :: Either String DynamicImage -> IO (Image PixelRGBA8)

Nice. The final part uses (<$>), which is the infix version of fmap, to apply pixelMap greenToAlpha to the Image PixelRGBA8 that is "inside" (in a sense) the IO (Image PixelRGBA8) value. That converts all of our green pixels into alpha pixels. We'll probably be using a lot of fmap and (<$>) as we go I'm sure.

    posRef <- newIORef (5,5)

This makes an IORef called posRef, with an initial value of (5,5). An IORef is one of several "ref types" that exists within Haskell. They're kinda like pointers/references in other languages. An IORef is the "basic" ref type when you're working in IO, and we will go into the other types if they come up later.

Normally we might not use a ref at all, but because Hexes is based on GLFW, and GLFW handles user events via callbacks, we'll need a way to share our game state between the callbacks and the drawing loop. Putting our gamestate inside a reference that they can both read and write does that for us.

    let rows = 24
        cols = 80

Here we're just naming some literals because it's usually better to have names for your numbers instead of just having a bunch of random seeming numbers that you forget what they're for later on.

    runHexes rows cols baseImage $ do

This part marks where the hexes library takes over control flow. Given a number of rows and columns to run with, an imagemap to use for display, and a Hexes action to run, runHexes will run that action in IO. A Hexes action is a lot like a normal IO action, but it has extra functions that automatically take the display context into account when you use them. That's where all our drawing and user interaction stuff will come from. The actual Hexes action that we're passing is an inner do-block. The ($) operator is a very simple operator that we'll be using all the time. It's defined like this:

($) :: (a -> b) -> a -> b
f $ x = f x

That looks like just normal function application! f is applied to x without anything else happening, so why use ($) at all? Well, the secret is that it's got the lowest possible precedence and it's right associative. That means that when we write

putStrLn $ foo bar baz

The whole foo bar baz part becomes x. So it's the same as writing

putStrLn (foo bar baz)

Except that we don't need to manually balance our parens at the end. Once you're used to it things become a lot easier to read just because there's less line noise. So in our program here, with runHexes, our entire Hexes do-block will be the final argument to runHexes, and all the stuff in that do-block will now be indented one level more than before. The ($) prevents us from having to write a bunch of messy closing parens at the end like some sort of lisp programmer would.

        setKeyCallback $ Just $ \key scanCode keyState modKeys -> liftIO $ do

Our first step within the Hexes context is to set our callback for when the user presses, releases, or repeats a key. Technically we're passing it a Maybe action, where a Nothing value lets us clear the current callback without setting a new one. We don't want that, so we pass it Just and then a lambda. Note how we can use ($) over and over and it all works out like you expect, with each one wrapping up "the rest of the line after it" into a parenthesis group.

The arguments to the callback are the information about the key event.

  • key is a Key, which is just a big enum type with a bunch of abstract keyboard keys. The Key value represent the "meaning" of a physical key, as interpreted by the user's keyboard layout.
  • scanCode is an Int, the scancode of a physical button on the keyboard.
  • keyState is a KeyState, one of KeyState'Pressed, KeyState'Released, or KeyState'Repeating. GLFW-b enums all have their type and a single quote and then the "actual" name because it's a FFI library over the C version, and in the C version it was named stuff like "GLFW_PRESS", which is about as bland. At least this way you're reminded what type the enum is part of, instead of only being reminded that it has something to do with GLFW somehow.
  • mods is a record of the modifier keys that were held down during this key press event. Shift, Alt, that sort of stuff.

So our callback accepts the information, then uses liftIO on yet another nested do-block. What's that all about? Well, that "lifts" the inner value (which is IO) into being the type that setKeyCallback expects (which is Hexes). Hexes callbacks are all Hexes actions so that you can be aware of you display environment while you're responding to events. The thing is that modifyIORef, which we'll get to in a moment, does't know about Hexes at all. It's part of the base library, and doesn't know about any of our types, so we can't use it directly with Hexes. However, Hexes has an instance of a typeclass called MonadIO which lets you "lift" any IO value into being a Hexes value by just using liftIO on it.

If the above paragraph doesn't make sense right away, don't worry about it. "It makes the types line up so that the program compiles" is all that a beginner really needs to know.

            case keyState of

We use a case expression to determine what key sort of key event we're dealing with. That's actually going to be the only thing we do in this block, everything else is inside this case expression, so the use of do in the line above was a little unnecessary, but it doesn't harm anything. We might want to add other steps later, and it lets our nesting blocks look a little more similar in style, so we'll leave it there.

                KeyState'Released -> pure ()

If a key was released, we don't do anything.

                _ -> modifyIORef posRef $ case key of

The underscore is a special kind of pattern that will match anything but not assign it a name. This gives us a "catch all" case. Since we know that Pressed, Released, and Repeating are the only possibilities for keyState to have, and since we eliminated the Released possibility already, then we've either got a Pressed or Repeating key event on our hands. For now, we don't care about the difference. What we'll do is modify our position reference. modifyIORef takes an IORef a and an a -> a function, then updates the contents of the IORef with the function. Here, the function that gets passed to modifyIORef depends on what key was pressed.

                    Key'Up -> \(px,py) -> (px, min (py+1) (rows-1))
                    Key'Down -> \(px,py) -> (px, max (py-1) 0)
                    Key'Left -> \(px,py) -> (max (px-1) 0, py)
                    Key'Right -> \(px,py) -> (min (px+1) (cols-1), py)

All four of these are essentially the same, so we'll deal with them all at once. In each case, when an arrow key is pressed we step one location in that direction. Right now there's no walls to prevent us walking too far so we'll just use min and max to keep us in bounds. I actually think that I wrote Hexes to wrap out of bounds locations around, but if you were using curses in Python or C you'd write it more like this with the bounds checks, so that's how we'll do it here

                    _ -> id

Once again we have a catch-all case. If any key other than an arrow key is pressed we'll do nothing to the position. id is the identity function, it just returns the value it was given. Sounds kinda useless on its own, but in situations like this it turns out to be perfect.

        gameLoop posRef

Note that we're several indentation levels back to the right now, so this is at the Hexes level. Once we've set our callback, we transfer control to the gameLoop function, passing it our IORef.

Game Loop

gameLoop :: IORef (Int,Int) -> Hexes ()
gameLoop posRef = do
    enterLoop <- not <$> windowShouldClose
    when enterLoop $ do
        -- update game state
        pollEvents
        -- draw to the screen
        (px,py) <- liftIO $ readIORef posRef
        setGridChar ' '
        setCharXY '@' px py
        -- "blit"
        refresh
        -- loop
        gameLoop posRef

This is much simpler than the things in main I think.

Every time we do a gameLoop, first we use windowShouldClose to read the value of the same name (which you can set yourself, or GLFW will set when the user clicks the 'X' in the corner of the window or presses Alt+F4 or things like that). Because we're going to be using this result with when, and when uses True to mean proceed, we'll apply not to the windowShouldClose value before we bind it as enterLoop. We could also use unless instead of when and avoid the use of not, but I like when more.

when isn't a special language keyword, it's just a normal function that we imported. It takes a Bool and an action, and evaluates to that action if the Bool is True, otherwise it evaluates to an action that does nothing at all. There's no magic going on, in fact you could have written it yourself using just what I've talked about so far, something like this:

when p s = if p then s else return ()

The official definition is a little more general than that, but you get the idea.

If enterLoop is true, we'll actually do the loop body.

First we run pollEvents, which causes all the pending events to be responded to and the appropriate callbacks to fire. This will keep eating up events until all the events are handled and then return. If no events are available then it will return without blocking. In other words, this is more like the "real time" version of the Py+libtcod tutorial. However, if you don't actaully look at the clock and you only change the game state in response to key events then it's effectively the same as being turn based anyway.

Next we read the value of our IORef to get our current game state. Well, it's just a position tuple, but it's all the game state we have at the moment.

We set the entire grid to be the space character, then draw our '@' at the player's position.

Once we're done we use refresh to make the changes appear on the screen. As with other sorts of double-buffered graphical libraries, nothing gets shown to the user if you don't call refresh.

With that done, we just call gameLoop again with the exact same IORef as before.

Now, I think I know what some of you are about to ask: "Isn't that a recursive call, and won't your stack overflow after just a bit of time?" I glossed over it a bit in the "minimal primer", so you might have missed it, something about "haskell can make recursive calls into tight loops at the machine code level". If you're familiar with a particular few languages you might think, "Ah, yes, of course, it's performing a tail-call elimination."

Well, heh, let me tell you, the answer is a lot weirder than that. The final line of gameLoop is not a tail call elimination... because Haskell doesn't even have a function call stack except for with foreign calls. Weird, very weird, I know.

No Function Call Stack?

Haskell is a non-strict language, and GHC implements it with a particular form of non-strictness called lazyness. If you've heard that "Haskell is a lazy language", that's because GHC is basically the only Haskell compiler in town so it's close enough for most people, even though they are technically distinct things.

What this ultimately means is that every time you write a function call, what happens right there is that Haskell makes what's called a thunk, which is the computation that will happen if you end up needing to compute that value. The only time that you actually compute any values is when you need to do a case match (remember that function cases and the case expression are compiled into the same thing). A case "forces" a thunk, causing it to be evaluated, so that it can know what branch to follow. If a thunk depends on the result of another thunk, then forcing it will force the thunk it depends on, and so on. For example, in 2 * x + 3, the addition depends on the multiplication having been done, so forcing the addition also forces the multiplication.

During the forcing process, the minimal amount of work is done to achieve a pattern match, working outside in. This is where those Constructors that I talked about in the primer really come into play, since you pattern match using constructors. Once the correct case branch has been selected, that branch becomes the program's expression, and then GHC continues the evaluation. So, there's a thunk evaluation stack, which can run out of memory if too many computations are deferred during a particular pattern match, but recursion on its own doesn't kill your RAM. A big part of what GHC's optimization process does is called Strictness Analysis, where it determines if a value will be depended on unconditionally in a situation, and it skips the intermediate thunk step in those situations. You can also add strictness annotations of your own if you like, and we'll do that in a few places in our game.

It's certainly all a little strange if you're used to other programming languages, so we'll come back to the subject later. For now we'll move on.

Part 2: Dungeon Basics

So now we're going to upgrade our little tuple holding the player position into an actual "GameState" type that holds all our data, including a Dungeon value to reprisent the current dungeon level. Next week will be the random dungeon generation, so our dungeon will just be a box until then.

data GameState = GameState {
    playerPos :: (Int,Int),
    rowCount :: Int,
    colCount :: Int
    } deriving (Read, Show)

To start, let's define a data type to hold all our game state. It doesn't hold a dungeon yet, just a width and a height. This data type declaration uses what's called "record syntax". We declare the type name, =, the record constructor's name, then an opening brace and the fields of the record with their types (comma seperated). Like with a list literal ([1,2,3]), the final field doesn't have a comma after it. When you declare a data type with record syntax, GHC automatically generates an accessor function for each field with the same name as the field, and it also allows you to use "record update syntax" to make a new record with just a few changes from an old record. We'll see that in a moment.

The part about "deriving" tells GHC to automatically generate instances for the Read and Show typeclasses. Show lets you turn your data into a String, and Read lets you parse a String back into your data. Makes it easy to save the game to disk or whatever. Of course, Read and Show can only be automatically derived if all the fields inside our new type already support Read and Show, but Int does, and tuples to do if they're made up of elements that do. Our tuple is just holding more Int values, so it's good too.

Now that we have a type for our game's state, let's update main to match

main :: IO ()
main = do
    baseImage <- pixelMap greenToAlpha <$> either die (return . convertRGBA8) (decodeImage imageBytes)
    let rows = 24
        cols = 80
    gameRef <- newIORef $ GameState (5,5) rows cols
    runHexes rows cols baseImage $ do
        setKeyCallback $ Just $ \key scanCode keyState modKeys -> liftIO $ do
            case keyState of
                KeyState'Released -> return ()
                _ -> modifyIORef gameRef (gameUpdate key)
        gameLoop gameRef

Very similar to before, but we're putting a GameState into the IORef instead of a tuple, and we've split out the update code into it's own gameUpdate method. Let's take a look at that.

gameUpdate :: Key -> GameState -> GameState
gameUpdate key game = let
    px = fst $ playerPos game
    py = snd $ playerPos game
    rows = rowCount game
    cols = colCount game
    in case key of
        Key'Up -> game {playerPos= (px, min (py+1) (rows-1))}
        Key'Down -> game {playerPos= (px, max (py-1) 0)}
        Key'Left -> game {playerPos= (max (px-1) 0, py)}
        Key'Right -> game {playerPos= (min (px+1) (cols-1), py)}
        _ -> game

This is using the "record update syntax" that I talked about. game is the old record to base the new value on, then inside the braces you can name one or more fields and give them new values. Any field not named simply carries the old value forward.

Since we're in a separate function, we have to carry around rows and cols in our GameState and get them back out during updates instead of them always being available from an outer scope. It's not a big deal, and it's just temporary too. Once we have actual terrain we can forget about using rows and cols directly, and just check for walls and creatures when the player takes a step instead. Since the IORef holds a new data type, we need to update gameLoop to match. We just change the type signature and a tiny bit where the drawing is.

gameLoop :: IORef GameState -> Hexes ()
...
       -- draw to the screen
       gameState <- liftIO $ readIORef posRef
       let (px,py) = playerPos gameState
       setGridChar ' '
       setCharXY '@' px py

So, our refactor should compile at this point, and the '@' can still walk around, but we have yet to put a Dungeon into our GameState.

The exact details of what makes up a dungeon can vary from game to game. I don't want to go crazy on the game design with our game here because I think that the point is more to learn about Haskell than to try and come up with the best game. So we'll have a simple 2d dungeon with terrain tiles to start. The terrain tiles will also be their own little data type, so first we'll put that into our program.

data Terrain = Open
             | Wall
             | StairsDown
             | StairsUp
             deriving (Read, Show)

This is a new type of data declaration. The | character separates your options for what a Terrain value can be, any one of Open, Wall, StairsDown, or StairsUp. Since we'll have Terrain in a Dungeon, and the Dungeon needs to support Read and Show, we'll have Terrain also implement Read and Show.

We've got some terrain, we need a way to store it all.

  • We've already seen tuples, but that's only for when you've got a very low number of values. More than four is probably pushing it. We want to have at least 1920 terrain tiles (24*80), and possibly support bigger maps as well. So tuples are out.
  • We could also use a [Terrain] (remember the [ ] mean "list of"), but that's a linked list, so indexing will be O(n), which isn't so good. Lists in Haskell a lot better when you think about them as being part of control structures (the elements of a loop) than as being about a way to hold data all by itself.
  • What we want is a way to have a bunch of data with constant time lookup. Haskell provides this in two main ways.
    • The most general possible data type is the array library, which lets you use anything with an Ix instance as your index type, and you can pick your own lower and upper bounds when you make the array. That's pretty cool, but that's also more power than we need right now.
    • Instead we'll use the vector library, which always uses Int values for the indexing, and always from 0 to n-1. In exchange for limiting what you index with, you get a much nicer API that's a lot easier to work with. We'll have to convert (x,y) coordinates into index values ourselves, but that's fine.

The vector package has several related vector types, and if you're going for the best performance you might need to pick one or another, depending on your program's needs. In our case, we're just going to use the basic immutable vector to start because it's the most general. Avoid too much premature optimization, and all that.

So with that in mind we have an idea of what our Dungeon type will look like to start:

{- extra imports at the top of the file -}

-- vector
import Data.Vector (Vector)
import qualified Data.Vector as V

{- in the main portion of the file -}

data Dungeon = Dungeon {
    dungeonWidth :: Int,
    dungeonHeight :: Int,
    dungeonTiles :: Vector Terrain
    } deriving (Read, Show)

I didn't talk about it before, but the bit in parens means that we're importing just a subset of a module, in this case the Vector type and that's it. The part about a "qualified" import meant that any time you use things from that import you must prefix it with the qualifier, and the "as V" means we'll prefix it with "V" instead of prefixing "Data.Vector". So with types we can just write Vector but for everything else we write V.func. Takes a bit to get used to, but this is a really common pattern in Haskell.

Except that if we start making Dungeon values in more than one place going to be kinda awkward always ensuring that the width and height match up with the length of the tiles vector and all that. Perfect thing to write a function for. In Haskell the informal term for this sort of thing is a "smart contructor", and the conventional name for a smart constructor is mk (short for "make") followed by the data type's name.

mkDungeon :: Int -> Int -> Dungeon
mkDungeon rows cols = Dungeon rows cols $
    V.generate (rows*cols) (\i -> let
        (r,c) = i `divMod` cols
        in if r == 0 || r == rows-1 || c == 0 || c == cols-1
            then Wall
            else Open)

So you give it rows and cols, and it makes a Dungeon with those values and a Vector of the right size. generate is from the vector library, and it takes a size for the new vector, and a function that turns each index into the intial value. Our size is rows*cols of course, and the function is a lambda that puts Wall values at the outer edges and Open terrain in all the other locations. divMod is a function that's just div and mod in a single step, with the answers returned as a tuple, and it's perfect for our situation.

Let's test it out!

D:\dev\roguelike-tutorial-hs>stack ghci
roguelike-tutorial-hs-0.0.0: initial-build-steps (exe)
Configuring GHCi with the following packages: roguelike-tutorial-hs
Using main module: 1. Package `roguelike-tutorial-hs' component exe:game with ma
in-is file: D:\dev\roguelike-tutorial-hs\app\Main.hs
GHCi, version 8.0.2: http://www.haskell.org/ghc/  :? for help
Loaded GHCi configuration from D:\dev\roguelike-tutorial-hs\.ghci
[1 of 1] Compiling Main             ( D:\dev\roguelike-tutorial-hs\app\Main.hs,
interpreted )
Ok, modules loaded: Main.
Loaded GHCi configuration from C:\Users\Daniel\AppData\Local\Temp\ghci7484\ghci-
script
RL-tut> mkDungeon 3 3
Dungeon {dungeonWidth = 3, dungeonHeight = 3, dungeonTiles = [Wall,Wall,Wall,Wal
l,Open,Wall,Wall,Wall,Wall]}
RL-tut> mkDungeon 4 5
Dungeon {dungeonWidth = 4, dungeonHeight = 5, dungeonTiles = [Wall,Wall,Wall,Wal
l,Wall,Wall,Open,Open,Open,Wall,Wall,Open,Open,Open,Wall,Wall,Wall,Wall,Wall,Wal
l]}

That's a little tricky to read. Let's manually move around where those line breaks are just a bit and look again...

RL-tut> mkDungeon 3 3
Dungeon {dungeonWidth = 3, dungeonHeight = 3, dungeonTiles = [
    Wall,Wall,Wall,
    Wall,Open,Wall,
    Wall,Wall,Wall]}

RL-tut> mkDungeon 4 5
Dungeon {dungeonWidth = 4, dungeonHeight = 5, dungeonTiles = [
    Wall,Wall,Wall,Wall,Wall,
    Wall,Open,Open,Open,Wall,
    Wall,Open,Open,Open,Wall,
    Wall,Wall,Wall,Wall,Wall]}

Whoops! The vector data is correct, but the width and height got passed in the wrong order. Let's just flip them around and reload our file.

RL-tut> :r
[1 of 1] Compiling Main             ( D:\dev\roguelike-tutorial-hs\app\Main.hs,
interpreted )
Ok, modules loaded: Main.
RL-tut> mkDungeon 4 5
Dungeon {dungeonWidth = 5, dungeonHeight = 4, dungeonTiles = [
    Wall,Wall,Wall,Wall,Wall,
    Wall,Open,Open,Open,Wall,
    Wall,Open,Open,Open,Wall,
    Wall,Wall,Wall,Wall,Wall]}

It still feels weird to ever be thinking in terms of rows and cols when the Dungeon should really only be considering things in terms of (x,y) locations. That's easy enough to fix, mostly we just rename stuff. The catch is that we need to remember that divMod gives our results back in the reverse of how we're using them now, so we have to change our pattern there.

mkDungeon :: Int -> Int -> Dungeon
mkDungeon xMax yMax = Dungeon xMax yMax $
    V.generate (xMax*yMax) (\i -> let
        (y,x) = i `divMod` xMax
        in if x == 0 || x == xMax-1 || y == 0 || y == yMax-1
            then Wall
            else Open)

Check once more to be sure,

RL-tut> :r
[1 of 1] Compiling Main             ( D:\dev\roguelike-tutorial-hs\app\Main.hs, interpreted )
Ok, modules loaded: Main.
RL-tut> mkDungeon 5 4
Dungeon {dungeonWidth = 5, dungeonHeight = 4, dungeonTiles = [
    Wall,Wall,Wall,Wall,Wall,
    Wall,Open,Open,Open,Wall,
    Wall,Open,Open,Open,Wall,
    Wall,Wall,Wall,Wall,Wall]}

Wonderful. Now let's get one going for GameState too,

mkGameState :: Int -> Int -> GameState
mkGameState xMax yMax = GameState (5,5) yMax xMax (mkDungeon xMax yMax)

and update how we start off our IORef,

    gameRef <- newIORef $ mkGameState cols rows

Now comes the hardest part: we update our drawing. Unfortunately, my library is a little clumsy at the moment, so the most efficient way to update the whole screen is with setAllByID, which takes a list of (Word8, V3 GLfloat, V4 GLfloat) values and then does the whole update at once. The first pass looks pretty ugly,

gameLoop :: IORef GameState -> Hexes ()
gameLoop gameRef = do
    enterLoop <- not <$> windowShouldClose
    when enterLoop $ do
        -- update game state
        pollEvents
        -- draw to the screen
        gameState <- liftIO $ readIORef gameRef
        let playerID = fromIntegral $ ord '@'
            playerBG = V3 0 0 0
            playerFG = V4 1 1 1 1
            openID = fromIntegral $ ord ' '
            openBG = V3 0 0 0
            openFG = V4 0 0 0 0
            wallID = fromIntegral $ ord '#'
            wallBG = V3 0 0 0
            wallFG = V4 0.388 0.152 0.027 1
            (px,py) = playerPos gameState
            terrainList = V.toList $ dungeonTiles $ dungeon gameState
            width = dungeonWidth $ dungeon gameState
            enumeratedTerrain = zip [0..] terrainList
            updateList = map (\(i,t) -> let
                (y,x) = i `divMod` width
                in if px == x && py == y
                    then (playerID, playerBG, playerFG)
                    else case t of
                        Open -> (openID, openBG, openFG)
                        Wall -> (wallID, wallBG, wallFG)
                        _ -> (1, playerBG, playerFG)) enumeratedTerrain
        setAllByID updateList
        -- "blit"
        refresh
        -- loop
        gameLoop gameRef

Yeah, very ugly. It compiles though. So what's going on here? Well a lot of that is just labeling the player, open, and wall display values. They each need a tileID, foreground, and backgroud. We also pick out the player's location and the dungeon terrain and the dungeon width. enumeratedTerrain is where it starts to get interesting. We're using a function called zip that turns two lists into a list of tuples, and it stops as soon as either list runs out. The [0..] syntax makes an infinite list that starts at 0 and then goes up by 1 each element. Put together we can do things like this:

RL-tut> zip [1,2,3] [4,5,6]
[(1,4),(2,5),(3,6)]
RL-tut> zip [1,2,3] [4,5,6,7,8,9]
[(1,4),(2,5),(3,6)]
RL-tut> zip [1,2,3] [0..]
[(1,0),(2,1),(3,2)]

Now we can track what element we're looking at when we go through all our terrain. This lets us figure out the (X,Y) so that we know when to insert the player's info instead of the terrain info. Then we map our lambda over enumeratedTerrain to turn the (Int,Terrain) pairs into the (Word8, V3 GLfloat, V4 GLfloat) values that setAllByID expects.

Testing it out, there's one minor problem: North and South are reversed! The screen is updating with rows increasing as you go down the screen, but our Y coordinates are assuming that Y decreases as you go down the screen. We just have to flip our lookup location by getting the height and then inverting the Y value.

                (y',x) = i `divMod` width
                y = height - (1+y')

Now we can draw the dungeon and player, and move the player properly, but our movement bounds are all out of sorts. We have to stop trying to simulate walls and actually check the walls. To do that, we'll want a much better way to get the terrain at a particular location.

getTerrainAt :: (Int,Int) -> Dungeon -> Terrain
getTerrainAt (x,y) d = let
    width = dungeonWidth d
    height = dungeonHeight d
    index = y * width + x
    in if y < 0 || x < 0 || y >= height || x >= width
        then Wall
        else V.unsafeIndex (dungeonTiles d) index

So first we determine if the coordinates requested are within bounds. If it's not in bounds we just don't worry and say it's a Wall. If it is in bounds we convert the (X,Y) into an index and check our vector. Since we already did a bounds check once we can use unsafeIndex, which prevents a second bounds check.

In terms of other ways to handle what to do when there's an out of bounds location, we could add a separate Terrain value like Void, or we could return a Maybe Terrain value to say that you might or might not get a Terrain value back. At the moment though we'll just say that any out of bounds location is a Wall and not worry too much.

  • If the player later gets the ability to walk through walls we'll still be fine, nothing is intrinsically bad about the player standing at (-1,-1), though unless the camera follows them they'd go off screen.
  • If the player gets the ability to alter the terrain, then we will have to update our thinking, because we currently can't update out of bounds locations. Then we'd need something like a Void value or using Maybe to reprisent when the player really can't go past some artificial edge.

Either way, that won't be for a while.

Now that we can get the terrain, we can easily bump the player around the dungeon

data Direction = North
               | South
               | East
               | West
               deriving Show

bumpPlayer :: Direction -> GameState -> GameState
bumpPlayer dir game = let
    px = fst $ playerPos game
    py = snd $ playerPos game
    targetx = px + case dir of
        East -> 1
        West -> -1
        _ -> 0
    targety = py + case dir of
        North -> 1
        South -> -1
        _ -> 0
    in case getTerrainAt (targetx,targety) (dungeon game) of
        Wall -> game
        _ -> game { playerPos = (targetx,targety) }

and we update the gameUpdate function to use this function,

gameUpdate :: Key -> GameState -> GameState
gameUpdate key = case key of
    Key'Up -> bumpPlayer North
    Key'Down -> bumpPlayer South
    Key'Left -> bumpPlayer West
    Key'Right -> bumpPlayer East
    _ -> id

And our hero can move on the screen and bump into the walls. Success!

Here's the git commit for this week.

results matching ""

    No results matching ""