summaryrefslogtreecommitdiffstats
diff options
context:
space:
mode:
authorMatthias Schiffer <matthias@gamezock.de>2010-03-09 06:08:42 +0100
committerMatthias Schiffer <matthias@gamezock.de>2010-03-09 06:08:42 +0100
commit89e87826a8b5874cee1ce370315e0af4b9297000 (patch)
tree7dc300a4b99cb35a09f7a9e81268c0d612a347a3
parent7327695ca3d9aee5da1d0bc98572d877dd8c8546 (diff)
downloadhtanks-89e87826a8b5874cee1ce370315e0af4b9297000.tar
htanks-89e87826a8b5874cee1ce370315e0af4b9297000.zip
Renamed shoot to bullet
-rw-r--r--src/Game.hs24
-rw-r--r--src/HTanks.hs38
-rw-r--r--src/Render.hs10
3 files changed, 36 insertions, 36 deletions
diff --git a/src/Game.hs b/src/Game.hs
index b31009e..9aef422 100644
--- a/src/Game.hs
+++ b/src/Game.hs
@@ -1,7 +1,7 @@
{-# LANGUAGE GeneralizedNewtypeDeriving #-}
module Game ( Tank(..)
- , Shoot(..)
+ , Bullet(..)
, GameState(..)
, Game
, runGame
@@ -24,24 +24,24 @@ data Tank = Tank
, tankSpeed :: !Micro
, tankTurnspeed :: !Micro
, tankMoving :: !Bool
- , tankShootSpeed :: !Micro
- , tankShootBounces :: !Int
- , tankShootsLeft :: !Int
+ , tankBulletSpeed :: !Micro
+ , tankBulletBounces :: !Int
+ , tankBulletsLeft :: !Int
} deriving Show
-data Shoot = Shoot
- { shootX :: !Micro
- , shootY :: !Micro
- , shootDir :: !Micro
- , shootSpeed :: !Micro
- , shootBouncesLeft :: !Int
- , shootTank :: !Int
+data Bullet = Bullet
+ { bulletX :: !Micro
+ , bulletY :: !Micro
+ , bulletDir :: !Micro
+ , bulletSpeed :: !Micro
+ , bulletBouncesLeft :: !Int
+ , bulletTank :: !Int
} deriving Show
data GameState = GameState
{ level :: !Level
, tanks :: ![Tank]
- , shoots :: ![Shoot]
+ , bullets :: ![Bullet]
, textures :: !(M.Map Texture TextureObject)
} deriving (Show)
diff --git a/src/HTanks.hs b/src/HTanks.hs
index 6d07cb6..4557809 100644
--- a/src/HTanks.hs
+++ b/src/HTanks.hs
@@ -49,7 +49,7 @@ main = do
]}
gameState = GameState {level = theLevel, tanks = [ Tank 5.0 5.0 0 0 2 270 False 3 2 5
, Tank 5.0 3.5 0 0 2 270 False 3 2 5
- ], shoots = [], textures = M.empty}
+ ], bullets = [], textures = M.empty}
runGame gameState $ do
setup
@@ -147,14 +147,14 @@ updateTank angle move aangle = do
modify $ \tank -> tank {tankMoving = False}
-updateShoot :: State Shoot ()
-updateShoot = do
- angle <- gets shootDir >>= return . (/180) . (*pi) . fromRational . toRational
- speed <- gets shootSpeed
+updateBullet :: State Bullet ()
+updateBullet = do
+ angle <- gets bulletDir >>= return . (/180) . (*pi) . fromRational . toRational
+ speed <- gets bulletSpeed
let dx = speed * fromRational (round ((cos angle)*1000)%1000000)
dy = speed * fromRational (round ((sin angle)*1000)%1000000)
- modify $ \shoot -> shoot {shootX = dx + shootX shoot, shootY = dy + shootY shoot}
+ modify $ \bullet -> bullet {bulletX = dx + bulletX bullet, bulletY = dy + bulletY bullet}
simulationStep :: Main ()
@@ -164,24 +164,24 @@ simulationStep = do
let (p, t, s) = unzip3 $ map updateTank' $ zip oldplayers oldtanks
ts = zip3 t s [0..]
- shootingtanks = map (\(tank, _, n) -> (tank, n)) $ filter (\(tank, shoot, _) -> shoot && (tankShootsLeft tank) > 0) $ ts
- newtanks = map (\(tank, shoot, _) -> if shoot then tank {tankShootsLeft = (tankShootsLeft tank) - 1} else tank) $ ts
- newshoots = map (\(tank, n) -> Shoot
- { shootX = tankX tank
- , shootY = tankY tank
- , shootDir = tankAim tank
- , shootSpeed = tankShootSpeed tank
- , shootBouncesLeft = tankShootBounces tank
- , shootTank = n
- }) shootingtanks
+ bulletingtanks = map (\(tank, _, n) -> (tank, n)) $ filter (\(tank, bullet, _) -> bullet && (tankBulletsLeft tank) > 0) $ ts
+ newtanks = map (\(tank, bullet, _) -> if bullet then tank {tankBulletsLeft = (tankBulletsLeft tank) - 1} else tank) $ ts
+ newbullets = map (\(tank, n) -> Bullet
+ { bulletX = tankX tank
+ , bulletY = tankY tank
+ , bulletDir = tankAim tank
+ , bulletSpeed = tankBulletSpeed tank
+ , bulletBouncesLeft = tankBulletBounces tank
+ , bulletTank = n
+ }) bulletingtanks
modify $ \state -> state {players = p}
- lift $ modify $ \state -> state {tanks = newtanks, shoots = map (execState updateShoot) (shoots state ++ newshoots)}
+ lift $ modify $ \state -> state {tanks = newtanks, bullets = map (execState updateBullet) (newbullets ++ bullets state)}
where
- updateTank' (player, tank) = let (p, angle, move, aangle, shoot) = playerUpdate player tank
+ updateTank' (player, tank) = let (p, angle, move, aangle, bullet) = playerUpdate player tank
t = execState (updateTank angle move aangle) tank
- in (p, t, shoot)
+ in (p, t, bullet)
handleEvents :: Main ()
diff --git a/src/Render.hs b/src/Render.hs
index d1276a3..fddfbcb 100644
--- a/src/Render.hs
+++ b/src/Render.hs
@@ -70,7 +70,7 @@ setup = do
render :: Game ()
render = do
tanklist <- gets tanks
- shootlist <- gets shoots
+ bulletlist <- gets bullets
textureWood <- getTexture TextureWood
textureTank <- getTexture TextureTank
@@ -139,10 +139,10 @@ render = do
texCoord $ TexCoord2 (1 :: GLfloat) (0 :: GLfloat)
vertex $ Vertex2 (0.5 :: GLfloat) (-0.5 :: GLfloat)
- forM_ shootlist $ \shoot -> preservingMatrix $ do
- let x = fromReal . shootX $ shoot
- y = fromReal . shootY $ shoot
- rotDir = fromReal . shootDir $ shoot
+ forM_ bulletlist $ \bullet -> preservingMatrix $ do
+ let x = fromReal . bulletX $ bullet
+ y = fromReal . bulletY $ bullet
+ rotDir = fromReal . bulletDir $ bullet
translate $ Vector3 x y (0 :: GLfloat)
rotate rotDir $ Vector3 0 0 (1 :: GLfloat)