-
Notifications
You must be signed in to change notification settings - Fork 2
Iteration 1
Previous: The Groundwork
The source code for this iteration can be found here.
All the changes from the previous iteration can be viewed in diff format here.
So far, we've written all our code in the single file main.hs
, but because
we'll be adding quite a bit of new code in this iteration, it's time to start
splitting the code into separate modules.
Although the aim of this iteration is rather simple, we'll also add a lot of foundation code for our state and rendering system. We'll start by defining some useful types for storing and defining location information in the file Haskeroids/Geometry.hs.
module Haskeroids.Geometry where
-- | Type alias for the value of vector components
type VecVal = Float
-- | Type alias for a 2D vector
type Vec2 = (VecVal, VecVal)
-- | Line segment between two points
newtype LineSegment = LineSegment (Vec2, Vec2)
We could have defined these as data
too, but I opted for type
and newtype
for efficiency and simplicity, since we are dealing with such basic types.
The basis for our rendering engine is in Haskeroids/Render.hs.
Since we are aiming for the kind of retro-look used in the original Asteroids, all our objects will consist of line segments. So lets define a type class for renderable objects:
module Haskeroids.Render (LineRenderable(..)) where
import Graphics.Rendering.OpenGL
import Haskeroids.Geometry
-- | Object that can be rendered as a group of lines
class LineRenderable r where
lineSegments :: r -> [LineSegment]
render :: r -> IO ()
render = renderLines . lineSegments
So, as long as an object can give us a list of LineSegments, we can render it using the general purpose render method. The helper methods for actually performing the OpenGL calls are below:
-- | Render a list of line segments using OpenGL
renderLines :: [LineSegment] -> IO ()
renderLines lns = do
currentColor $= Color4 0.9 0.9 0.9 1.0
renderPrimitive Lines $ mapM_ lineVertices lns
-- | Generate the OpenGL vertices of a line segment
lineVertices :: LineSegment -> IO ()
lineVertices (LineSegment (p,p')) = do
ptVertex p
ptVertex p'
-- | Generate an OpenGL vertex from a point
ptVertex :: Vec2 -> IO ()
ptVertex = vertex . uncurry Vertex2
The data type for tracking player state is defined in Haskeroids/Player.hs.
module Haskeroids.Player (Player(..)) where
import Haskeroids.Geometry
import Haskeroids.Render (LineRenderable(..))
-- | Data type for tracking current player state
data Player = Player { playerPos :: Vec2 }
At this point, the only thing a player has is a position on the screen, but we'll be adding new fields to this type in later iterations.
Before implementing the actual drawing for the player ship, let's add some helper methods into the Geometry-module.
-- | Conversion from polar to cartesian coordinates
polar :: VecVal -- ^ radial coordinate
-> VecVal -- ^ anglular coordinate
-> Vec2 -- ^ cartesian point
polar m a = (m * sin a, m * (-cos a))
For many symmetrical objects, like the ship, it'll be easier to define the shape in polar coordinates, so we define a function to do this conversion. The polar coordinate system I've selected has radian 0 pointing upwards, pi/2 to the right and so on.
The next function lets us define a shape as a list of points, and then convert that to a list of line segments for the rendering engine.
-- | Transform a list of points into a list of connected line segments
pointsToSegments :: [Vec2] -> [LineSegment]
pointsToSegments (p:p':[]) = [LineSegment (p,p')]
pointsToSegments (p:t@(p':ps)) = (LineSegment (p,p')) : pointsToSegments t
Finally, we define two functions to translate points and line segments to new coordinates. Now we have all the helpers we need to define how the player's ship should be drawn.
-- | Translate a point
translate :: Vec2 -- ^ (x,y) delta
-> Vec2 -- ^ original point
-> Vec2 -- ^ translated point
translate (x,y) (x',y') = (x+x', y+y')
-- | Translate a line segment
translateLine :: Vec2 -> LineSegment -> LineSegment
translateLine p (LineSegment (l,l')) = LineSegment (t l, t l')
where t = translate p
instance LineRenderable Player where
lineSegments (Player p) = map (translateLine p) $ shipLines
-- | Constant for the ship size
shipSize = 12.0 :: Float
-- | List of lines that make up the ship hull
shipLines :: [LineSegment]
shipLines = pointsToSegments points
where points = [polar shipSize 0,
polar shipSize (0.7*pi),
polar (shipSize*0.2) pi,
polar shipSize (1.3*pi),
polar shipSize 0]
The shipLines
list is built only once, and when the player state is rendered,
we translate those lines to the current player position.
The state data for the whole game is defined in Haskeroids/State.hs.
-- | Data type for tracking game state
data GameState = GameState { statePlayer :: Player }
The game state is also a renderable object, which generates the line segments of all existing game objects (which at this point is just the single ship).
instance LineRenderable GameState where
lineSegments = stateLines
-- | List of all renderable lines in the given state
stateLines :: GameState -> [LineSegment]
stateLines = lineSegments . statePlayer
We'll also define the game state as it exists in the beginning of the game.
-- | Generate the initial game state
initialGameState :: GameState
initialGameState = GameState {
statePlayer = initialPlayerState
}
-- | Initial state for the player ship at center of the screen
initialPlayerState :: Player
initialPlayerState = Player (400, 300)
Now we just need a couple of changes to our GLUT callbacks, and we are done.
-- | Set up GLUT callbacks
initializeCallbacks = do
displayCallback $= renderViewport initialGameState
-- | Render the viewport using the given renderable and swap buffers
renderViewport :: LineRenderable r => r -> IO ()
renderViewport r = do
clear [ColorBuffer]
render r
swapBuffers
When you compile and run the code for this iteration, you should see this:
That's a lot of code just to draw a couple of lines! But don't despair, now that we have the basic engine code in place, the next iterations will be a lot shorter.
Next: Iteration 2: Rotating the Ship