2010-02-23 23:31:11 +01:00
|
|
|
{-# LANGUAGE PatternGuards, GeneralizedNewtypeDeriving #-}
|
2010-02-22 22:25:06 +01:00
|
|
|
|
2010-02-22 16:50:42 +01:00
|
|
|
import Game
|
|
|
|
import Level
|
2010-02-23 15:05:31 +01:00
|
|
|
import Render
|
2010-02-22 16:50:42 +01:00
|
|
|
import Tank
|
|
|
|
|
|
|
|
import GLDriver
|
|
|
|
import GLX
|
|
|
|
|
2010-02-22 18:27:18 +01:00
|
|
|
import Control.Concurrent (threadDelay)
|
|
|
|
import Control.Monad.State
|
|
|
|
import Data.Maybe
|
2010-02-24 03:40:06 +01:00
|
|
|
import Data.Ratio
|
|
|
|
import qualified Data.Set as S
|
2010-02-24 02:42:10 +01:00
|
|
|
import Data.Time.Clock
|
2010-02-22 18:27:18 +01:00
|
|
|
|
|
|
|
|
2010-02-23 23:31:11 +01:00
|
|
|
data MainState = MainState
|
2010-02-24 03:40:06 +01:00
|
|
|
{ run :: !Bool
|
|
|
|
, driver :: !SomeDriver
|
2010-02-24 02:42:10 +01:00
|
|
|
, time :: !UTCTime
|
2010-02-24 03:40:06 +01:00
|
|
|
, keyset :: !(S.Set Key)
|
2010-02-23 23:31:11 +01:00
|
|
|
}
|
|
|
|
|
|
|
|
newtype MainT m a = MainT (StateT MainState m a)
|
|
|
|
deriving (Monad, MonadState MainState, MonadIO, MonadTrans)
|
|
|
|
|
|
|
|
type Main = MainT Game
|
|
|
|
|
|
|
|
runMain :: MainState -> Main a -> Game (a, MainState)
|
|
|
|
runMain st (MainT a) = runStateT a st
|
|
|
|
|
|
|
|
|
2010-02-22 16:50:42 +01:00
|
|
|
main :: IO ()
|
|
|
|
main = do
|
2010-02-22 18:27:18 +01:00
|
|
|
gl <- initGL glxDriver
|
2010-02-22 16:50:42 +01:00
|
|
|
|
2010-02-23 15:05:31 +01:00
|
|
|
when (initialized gl) $ do
|
2010-02-24 02:42:10 +01:00
|
|
|
currentTime <- getCurrentTime
|
2010-02-24 03:40:06 +01:00
|
|
|
let mainState = MainState {run = True, driver = SomeDriver gl, time = currentTime, keyset = S.empty}
|
|
|
|
gameState = GameState {level = testLevel, tanks = [Tank 0.0 0.0 0 0]}
|
2010-02-23 20:51:30 +01:00
|
|
|
|
|
|
|
setup 800 600
|
2010-02-23 23:31:11 +01:00
|
|
|
runGame gameState $ runMain mainState $ mainLoop
|
2010-02-23 15:05:31 +01:00
|
|
|
|
|
|
|
deinitGL gl
|
|
|
|
|
2010-02-24 02:42:10 +01:00
|
|
|
minFrameTime :: NominalDiffTime
|
|
|
|
minFrameTime = 0.01
|
2010-02-22 16:50:42 +01:00
|
|
|
|
2010-02-23 23:31:11 +01:00
|
|
|
mainLoop :: Main ()
|
|
|
|
mainLoop = do
|
|
|
|
gl <- gets driver
|
|
|
|
t <- gets time
|
2010-02-24 03:40:06 +01:00
|
|
|
handleEvents
|
2010-02-22 18:27:18 +01:00
|
|
|
|
2010-02-23 23:31:11 +01:00
|
|
|
lift render
|
2010-02-23 15:05:31 +01:00
|
|
|
|
|
|
|
liftIO $ swapBuffers gl
|
|
|
|
|
2010-02-24 02:42:10 +01:00
|
|
|
rtime <- liftIO getCurrentTime
|
|
|
|
let drender = diffUTCTime rtime t
|
|
|
|
when (drender < minFrameTime) $
|
|
|
|
liftIO $ threadDelay $ truncate $ 1e6*(minFrameTime - drender)
|
2010-02-23 15:05:31 +01:00
|
|
|
|
2010-02-24 02:42:10 +01:00
|
|
|
currenttime <- liftIO getCurrentTime
|
|
|
|
let d = round $ 1e3*(diffUTCTime currenttime t)
|
2010-02-23 23:31:11 +01:00
|
|
|
|
2010-02-24 03:40:06 +01:00
|
|
|
replicateM_ d simulationStep
|
|
|
|
--liftIO $ print $ d
|
2010-02-23 15:05:31 +01:00
|
|
|
|
2010-02-24 02:42:10 +01:00
|
|
|
let newtime = addUTCTime ((1e-3)*(fromIntegral d)) t
|
|
|
|
|
|
|
|
modify $ \state -> state {time = newtime}
|
2010-02-23 15:05:31 +01:00
|
|
|
|
2010-02-24 03:40:06 +01:00
|
|
|
runnext <- gets run
|
|
|
|
when runnext mainLoop
|
|
|
|
|
|
|
|
|
|
|
|
simulationStep :: Main ()
|
|
|
|
simulationStep = do
|
|
|
|
keys <- gets keyset
|
|
|
|
|
|
|
|
let x = (if (S.member KeyLeft keys) then (-1) else 0) + (if (S.member KeyRight keys) then 1 else 0)
|
|
|
|
y = (if (S.member KeyDown keys) then (-1) else 0) + (if (S.member KeyUp keys) then 1 else 0)
|
|
|
|
|
|
|
|
let lengthsq = ((x*x)+(y*y))
|
|
|
|
|
|
|
|
when (lengthsq /= 0) $ do
|
|
|
|
let length = sqrt lengthsq
|
|
|
|
|
|
|
|
let dx = fromRational (round (x*1000/length)%1000000)
|
|
|
|
dy = fromRational (round (y*1000/length)%1000000)
|
|
|
|
|
|
|
|
oldtank <- lift $ gets (head . tanks)
|
|
|
|
let tank = oldtank {posx = dx + posx oldtank, posy = dy + posy oldtank}
|
|
|
|
|
|
|
|
lift $ modify $ \state -> state {tanks = tank:(tail . tanks $ state)}
|
2010-02-23 15:05:31 +01:00
|
|
|
|
|
|
|
|
2010-02-24 03:40:06 +01:00
|
|
|
handleEvents :: Main ()
|
|
|
|
handleEvents = do
|
|
|
|
event <- gets driver >>= liftIO . nextEvent
|
|
|
|
when (isJust event) $
|
|
|
|
handleEvent $ fromJust event
|
2010-02-22 18:27:18 +01:00
|
|
|
|
2010-02-24 03:40:06 +01:00
|
|
|
handleEvent :: SomeEvent -> Main ()
|
2010-02-22 22:25:06 +01:00
|
|
|
handleEvent ev
|
2010-02-24 03:40:06 +01:00
|
|
|
| Just (ResizeEvent w h) <- fromEvent ev = liftIO $ resize w h
|
|
|
|
| Just (KeyPressEvent key) <- fromEvent ev = modify $ \state -> state {keyset = S.insert key (keyset state)}
|
|
|
|
| Just (KeyReleaseEvent key) <- fromEvent ev = modify $ \state -> state {keyset = S.delete key (keyset state)}
|
|
|
|
| Just QuitEvent <- fromEvent ev = modify $ \state -> state {run = False}
|
|
|
|
| otherwise = return ()
|