Reorganized code to add Debris class
This commit is contained in:
parent
e85dc20a48
commit
90b8d87e02
11 changed files with 57 additions and 25 deletions
|
@ -14,7 +14,7 @@ data-files: tex/*.png
|
|||
executable: HTanks
|
||||
hs-source-dirs: src
|
||||
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
|
||||
ghc-options: -threaded -O2
|
||||
extra-libraries: glpng
|
||||
|
|
|
@ -1,7 +1,7 @@
|
|||
module Collision ( collisionTankBorder
|
||||
) where
|
||||
|
||||
import Game
|
||||
import Tank
|
||||
|
||||
import Data.Fixed
|
||||
import Data.Ratio
|
||||
|
|
21
src/Debris.hs
Normal file
21
src/Debris.hs
Normal 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
|
|
@ -9,7 +9,7 @@ import Data.Fixed
|
|||
import Data.Ratio ((%))
|
||||
import Data.Typeable
|
||||
|
||||
import Game (Tank(..))
|
||||
import Tank
|
||||
import GLDriver
|
||||
import Player
|
||||
|
||||
|
|
17
src/Game.hs
17
src/Game.hs
|
@ -1,13 +1,13 @@
|
|||
{-# LANGUAGE GeneralizedNewtypeDeriving #-}
|
||||
|
||||
module Game ( Tank(..)
|
||||
, Bullet(..)
|
||||
module Game ( Bullet(..)
|
||||
, GameState(..)
|
||||
, Game
|
||||
, runGame
|
||||
) where
|
||||
|
||||
import Level
|
||||
import Tank
|
||||
import Texture
|
||||
|
||||
import Control.Monad
|
||||
|
@ -16,19 +16,6 @@ import Data.Fixed
|
|||
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
|
||||
{ bulletX :: !Micro
|
||||
, bulletY :: !Micro
|
||||
|
|
|
@ -8,6 +8,7 @@ import Player
|
|||
import CPUPlayer
|
||||
import DefaultPlayer
|
||||
import Simulation
|
||||
import Tank
|
||||
|
||||
import GLDriver
|
||||
import GLX
|
||||
|
|
|
@ -4,15 +4,19 @@ module Level ( Level(..)
|
|||
|
||||
import Data.List
|
||||
|
||||
import Debris
|
||||
|
||||
data Level = Level
|
||||
{ levelWidth :: !Int
|
||||
, levelHeight :: !Int
|
||||
, debris :: ![SomeDebris]
|
||||
} deriving (Show)
|
||||
|
||||
|
||||
|
||||
testLevel :: Level
|
||||
testLevel = Level
|
||||
{ levelWidth = 10
|
||||
, levelHeight = 10
|
||||
{ levelWidth = 14
|
||||
, levelHeight = 8
|
||||
, debris = []
|
||||
}
|
|
@ -7,7 +7,7 @@ module Player ( Player(..)
|
|||
import Data.Fixed
|
||||
import Data.Typeable
|
||||
|
||||
import Game (Tank(..))
|
||||
import Tank
|
||||
import GLDriver (SomeEvent)
|
||||
|
||||
|
||||
|
|
|
@ -6,6 +6,7 @@ module Render ( setup
|
|||
import Paths_htanks
|
||||
import Game
|
||||
import Level
|
||||
import Tank
|
||||
import Texture
|
||||
|
||||
import Control.Monad.State
|
||||
|
@ -89,13 +90,13 @@ render = do
|
|||
texCoord $ TexCoord2 (0 :: GLfloat) (0 :: GLfloat)
|
||||
vertex $ Vertex2 0 lh
|
||||
|
||||
texCoord $ TexCoord2 lw 0
|
||||
texCoord $ TexCoord2 (lw/2) 0
|
||||
vertex $ Vertex2 lw lh
|
||||
|
||||
texCoord $ TexCoord2 lw lh
|
||||
texCoord $ TexCoord2 (lw/2) (lh/2)
|
||||
vertex $ Vertex2 lw 0
|
||||
|
||||
texCoord $ TexCoord2 0 lh
|
||||
texCoord $ TexCoord2 0 (lh/2)
|
||||
vertex $ Vertex2 (0 :: GLfloat) (0 :: GLfloat)
|
||||
|
||||
forM_ tanklist $ \tank -> preservingMatrix $ do
|
||||
|
|
|
@ -6,6 +6,7 @@ import Game
|
|||
import Level
|
||||
import MainLoop
|
||||
import Player
|
||||
import Tank
|
||||
|
||||
import Control.Monad.State
|
||||
import Data.Fixed
|
||||
|
|
17
src/Tank.hs
Normal file
17
src/Tank.hs
Normal 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
|
Reference in a new issue