Reorganized code to add Debris class

This commit is contained in:
Matthias Schiffer 2010-03-15 14:46:14 +01:00
parent e85dc20a48
commit 90b8d87e02
11 changed files with 57 additions and 25 deletions

View file

@ -14,7 +14,7 @@ data-files: tex/*.png
executable: HTanks executable: HTanks
hs-source-dirs: src hs-source-dirs: src
main-is: HTanks.hs main-is: HTanks.hs
other-modules: Collision, CPUPlayer, DefaultPlayer, Game, GLDriver, GLX, Level, MainLoop, Paths_htanks, Player, Render, Simulation, Texture, other-modules: Collision, CPUPlayer, DefaultPlayer, Game, GLDriver, GLX, Level, MainLoop, Paths_htanks, Player, Render, Simulation, Texture, Debris, Tank,
Bindings.GLX, Bindings.GLPng Bindings.GLX, Bindings.GLPng
ghc-options: -threaded -O2 ghc-options: -threaded -O2
extra-libraries: glpng extra-libraries: glpng

View file

@ -1,7 +1,7 @@
module Collision ( collisionTankBorder module Collision ( collisionTankBorder
) where ) where
import Game import Tank
import Data.Fixed import Data.Fixed
import Data.Ratio import Data.Ratio

21
src/Debris.hs Normal file
View file

@ -0,0 +1,21 @@
{-# LANGUAGE ExistentialQuantification #-}
module Debris ( Debris(..)
, SomeDebris(..)
) where
import Tank
class Show a => Debris a where
collideTank :: a -> Tank -> Tank
data SomeDebris = forall a. Debris a => SomeDebris a
instance Show SomeDebris
where
show (SomeDebris a) = show a
instance Debris SomeDebris
where
collideTank (SomeDebris a) = collideTank a

View file

@ -9,7 +9,7 @@ import Data.Fixed
import Data.Ratio ((%)) import Data.Ratio ((%))
import Data.Typeable import Data.Typeable
import Game (Tank(..)) import Tank
import GLDriver import GLDriver
import Player import Player

View file

@ -1,13 +1,13 @@
{-# LANGUAGE GeneralizedNewtypeDeriving #-} {-# LANGUAGE GeneralizedNewtypeDeriving #-}
module Game ( Tank(..) module Game ( Bullet(..)
, Bullet(..)
, GameState(..) , GameState(..)
, Game , Game
, runGame , runGame
) where ) where
import Level import Level
import Tank
import Texture import Texture
import Control.Monad import Control.Monad
@ -16,19 +16,6 @@ import Data.Fixed
import qualified Data.Map as M import qualified Data.Map as M
data Tank = Tank
{ tankX :: !Micro
, tankY :: !Micro
, tankDir :: !Micro
, tankAim :: !Micro
, tankSpeed :: !Micro
, tankTurnspeed :: !Micro
, tankMoving :: !Bool
, tankBulletSpeed :: !Micro
, tankBulletBounces :: !Int
, tankBulletsLeft :: !Int
} deriving Show
data Bullet = Bullet data Bullet = Bullet
{ bulletX :: !Micro { bulletX :: !Micro
, bulletY :: !Micro , bulletY :: !Micro

View file

@ -8,6 +8,7 @@ import Player
import CPUPlayer import CPUPlayer
import DefaultPlayer import DefaultPlayer
import Simulation import Simulation
import Tank
import GLDriver import GLDriver
import GLX import GLX

View file

@ -4,15 +4,19 @@ module Level ( Level(..)
import Data.List import Data.List
import Debris
data Level = Level data Level = Level
{ levelWidth :: !Int { levelWidth :: !Int
, levelHeight :: !Int , levelHeight :: !Int
, debris :: ![SomeDebris]
} deriving (Show) } deriving (Show)
testLevel :: Level testLevel :: Level
testLevel = Level testLevel = Level
{ levelWidth = 10 { levelWidth = 14
, levelHeight = 10 , levelHeight = 8
, debris = []
} }

View file

@ -7,7 +7,7 @@ module Player ( Player(..)
import Data.Fixed import Data.Fixed
import Data.Typeable import Data.Typeable
import Game (Tank(..)) import Tank
import GLDriver (SomeEvent) import GLDriver (SomeEvent)

View file

@ -6,6 +6,7 @@ module Render ( setup
import Paths_htanks import Paths_htanks
import Game import Game
import Level import Level
import Tank
import Texture import Texture
import Control.Monad.State import Control.Monad.State
@ -89,13 +90,13 @@ render = do
texCoord $ TexCoord2 (0 :: GLfloat) (0 :: GLfloat) texCoord $ TexCoord2 (0 :: GLfloat) (0 :: GLfloat)
vertex $ Vertex2 0 lh vertex $ Vertex2 0 lh
texCoord $ TexCoord2 lw 0 texCoord $ TexCoord2 (lw/2) 0
vertex $ Vertex2 lw lh vertex $ Vertex2 lw lh
texCoord $ TexCoord2 lw lh texCoord $ TexCoord2 (lw/2) (lh/2)
vertex $ Vertex2 lw 0 vertex $ Vertex2 lw 0
texCoord $ TexCoord2 0 lh texCoord $ TexCoord2 0 (lh/2)
vertex $ Vertex2 (0 :: GLfloat) (0 :: GLfloat) vertex $ Vertex2 (0 :: GLfloat) (0 :: GLfloat)
forM_ tanklist $ \tank -> preservingMatrix $ do forM_ tanklist $ \tank -> preservingMatrix $ do

View file

@ -6,6 +6,7 @@ import Game
import Level import Level
import MainLoop import MainLoop
import Player import Player
import Tank
import Control.Monad.State import Control.Monad.State
import Data.Fixed import Data.Fixed

17
src/Tank.hs Normal file
View file

@ -0,0 +1,17 @@
module Tank ( Tank(..)
) where
import Data.Fixed
data Tank = Tank
{ tankX :: !Micro
, tankY :: !Micro
, tankDir :: !Micro
, tankAim :: !Micro
, tankSpeed :: !Micro
, tankTurnspeed :: !Micro
, tankMoving :: !Bool
, tankBulletSpeed :: !Micro
, tankBulletBounces :: !Int
, tankBulletsLeft :: !Int
} deriving Show