I have an implementation of a BrickBreaker-like game where instead of pieces being just removed from the ceiling, each impact results in a new ball being released, gradually building up to a pretty chaotic game.
The SDL related code that actually draws the game is not included here.
This is my second "big" project using Haskell, so I'd appreciate some critique, specifically concerning the approach
and collisionBlock
functions. First in approach
I zip Data.Map.lookup
over a list of keys, and then use msum to get the first successful lookup. Then in collisionBlock
I use Data.Map.updateLookupWithKey
again on the key I already know is successful and had already performed a lookup with. I'd like to be able to eliminate this extra lookup or otherwise improve the approach
function.
{-# LANGUAGE BangPatterns #-}
module BrickBreaker where
import Control.Monad
import Data.List
import qualified Data.Map as M
import System.Random
width = 640 :: Int
height = 420 :: Int
blockW = width
blockH = height `quot` 3
data Particle = Particle { partX, partY, partDX, partDY :: !Int }
data Paddle = Paddle { paddleX, paddleW, paddleH :: !Int }
data GameState = GS ![Particle] !Block
data CollisionResult = Miss | Hit Particle Block
type Block = M.Map Pos Particle
type Pos = (Int, Int)
getPos, getSpeed :: Particle -> Pos
getPos pt = (partX pt, partY pt)
getSpeed pt = (partDX pt, partDY pt)
genBlock :: Block
genBlock = mkMap [Particle w h 0 0 | w <- [1..blockW], h <- [1..blockH]]
where mkMap = M.fromList . map (\pt -> (getPos pt, pt))
approach :: Particle -> Block -> Maybe Particle
approach pt bs = msum $ zipWith ((flip M.lookup bs .) . addSpeed) (enum dx) (enum dy)
where (x, y) = getPos pt; (dx, dy) = getSpeed pt
addSpeed dx dy = (x + dx, y + dy)
enum 0 = repeat 0
enum n = let i = if n < 0 then (-1) else 1 in enumFromThenTo i (i+i) n
collisionBlock :: Particle -> Block -> CollisionResult
collisionBlock pt bs
| dy > 0 && y > blockH = Miss
| dy < 0 && y > blockH - dy = Miss
| otherwise =
case approach pt bs of
Just pt -> let ~(Just pt', bs') = searchRemove pt in Hit pt' bs'
Nothing -> Miss
where y = partY pt; dy = partDY pt
searchRemove = flip (M.updateLookupWithKey (\_ _ -> Nothing)) bs . getPos
collisionPaddle :: Paddle -> Particle -> Bool
collisionPaddle pd pt =
y >= height - paddleH pd && x `between` (padX, padX + paddleW pd) && dy > 0
where n `between` (a, b) = n >= a && n <= b
(x, y) = getPos pt; dy = partDY pt
padX = paddleX pd
checkCollisions :: Paddle -> GameState -> GameState
checkCollisions pd (GS ps bs) = foldl go (GS [] bs) ps
where go (GS ps bs) pt
| collisionPaddle pd pt = GS (bar:ps) bs
| otherwise =
case collisionBlock pt bs of
Hit pt bs' -> GS (blk:(randomParticle pt:ps)) bs'
Miss -> GS (pt:ps) bs
where (x, y) = getPos pt; (dx, dy) = getSpeed pt
bar = Particle x (min y height) dx (-dy)
blk = Particle x y dx (abs dy)
randomParticle :: Particle -> Particle
randomParticle pt = Particle x y (ceiling $ dx * 10) (ceiling $ dy * 9 + 1)
where (x, y) = getPos pt
(dx, g) = randomR ((-1.0), 1.0) (mkStdGen $ x + y) :: (Double, StdGen)
(dy, _) = randomR (0.1, 1.0) g :: (Double, StdGen)
updateParticle :: Particle -> Particle
updateParticle pt = Particle (x + dx') (y + dy') dx' dy'
where (x, y) = getPos pt; (dx, dy) = getSpeed pt
dx' = if (x > width && dx > 0) || (x < 0 && dx < 0) then (-dx) else dx
dy' = if y < 0 && dy < 0 then (-dy) else dy
updateGame :: Paddle -> GameState -> GameState
updateGame pd gs = GS (map updateParticle $ filter inBounds ps) bs
where GS ps bs = checkCollisions pd gs
inBounds = (<= height) . partY
Here is the main loop in the SDL related code that calls the drawing functions and updates the GameState
:
updateWorld :: Surface -> Paddle -> GameState -> IO ()
updateWorld screen pd gs = do
ticks <- getTicks
quit <- whileEvents
drawGame screen pd gs
(x, _, _) <- getMouseState
ticks' <- getTicks
let pd' = Paddle x (paddleW pd) (paddleH pd)
delta = ticks' - ticks
when (delta < (fromIntegral secsPerFrame)) $
delay $ fromIntegral secsPerFrame - delta
unless (quit || gameOver gs) (updateWorld screen pd' $ updateGame pd' gs)
where whileEvents = do
event <- pollEvent
case event of
KeyDown (Keysym key _ _) ->
case key of
SDLK_q -> return True
_ -> return False
_ -> return False
2 Answers 2
One comment on your modelling...
Consider making the paddle position part of your GameState
. Regardless of how you are going to control the paddle, conceptually it is part of the state. In particular, it is required in order to draw the game screen. Your game loop will look something like:
gameLoop :: GameState -> IO ()
gameLoop s = if stillPlaying s
then do drawScreen s
e <- getEvent
gameLoop $ nextState s e
else return ()
drawScreen :: GameState -> IO ()
...
getEvent :: IO Event
...
stillPlaying
has the signature GameState -> Bool
and returns false when the game is over.
nextState
has the signature GameState -> Event -> GameState
and creates the next state by applying the effects of an event.
One of the events could be "move the paddle left" or "move the paddle right" which would affect the position of the paddle.
Also, don't forget to put a random number generator into your GameState
- I'm sure you will want to have some randomness in your game eventually.
Update: It's a good idea to think in alternative use cases when defining the roles and responsibilities of your functions.
For instance, one possible definition of drawScreen
is to simply putStrLn $ show s
- assuming that you've derived a Show
instance for GameState
. And getEvent
could simply read a number from stdin and create the Event
value. Then you can test your game code without using SDL.
-
\$\begingroup\$ The SDL code that actually draws the game is in a seperate module. It has simlar functions to the ones you've mentioned. My rationale for keeping the paddle out of the
GameState
is that the paddle is controlled by the user (ie. it has to be updated in the IO monad), whereas the currentGameState
can be used with complete purity. Specifically, the paddle is moved by updating the padX field with the X co-ord of SDL.getMouseState \$\endgroup\$cdk– cdk2012年11月08日 21:29:41 +00:00Commented Nov 8, 2012 at 21:29 -
\$\begingroup\$ You can run
SDL.getMouseState
as part of thegetEvent
function.getEvent
is anIO Event
so it can callSDL.getMouseState
. \$\endgroup\$ErikR– ErikR2012年11月08日 21:47:16 +00:00Commented Nov 8, 2012 at 21:47 -
\$\begingroup\$ okay, but i already have the entire drawing/user input part of the game worked out in a separate module. I'll add the main update loop to the question. \$\endgroup\$cdk– cdk2012年11月08日 22:35:12 +00:00Commented Nov 8, 2012 at 22:35
You can use let i = signum n
in enum
instead of if
.
randomParticle
generates particles moving in any direction, butapproach
only checks diagonal paths. Is it a mistake or an approximation? \$\endgroup\$approach
function, the particles can "tunnel" into the block, and if the new particle generated fromrandomParticle
doesnt have enough y velocity to get out of the block it sets off a chain reaction and the entire block is gone in seconds. \$\endgroup\$