This repository has been archived on 2025-03-03. You can view files and clone it, but cannot push or open issues or pull requests.
htanks/HTanks.hs

95 lines
2.2 KiB
Haskell
Raw Normal View History

{-# LANGUAGE PatternGuards, GeneralizedNewtypeDeriving #-}
2010-02-22 22:25:06 +01:00
2010-02-22 16:50:42 +01:00
import Game
import Level
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
import System.Time
2010-02-22 18:27:18 +01:00
data MainState = MainState
{ driver :: !SomeDriver
, time :: !ClockTime
}
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
when (initialized gl) $ do
clockTime <- getClockTime
let mainState = MainState {driver = SomeDriver gl, time = clockTime}
gameState = GameState {level = testLevel, tanks = [Tank 0.0 0.0 0]}
2010-02-23 20:51:30 +01:00
setup 800 600
runGame gameState $ runMain mainState $ mainLoop
deinitGL gl
minFrameTime :: Integer
minFrameTime = 10
2010-02-22 16:50:42 +01:00
mainLoop :: Main ()
mainLoop = do
gl <- gets driver
t <- gets time
2010-02-22 18:27:18 +01:00
run <- liftIO $ handleEvents gl
lift render
liftIO $ swapBuffers gl
newTime <- liftIO getClockTime
let td = timeDiff newTime t
when (td < minFrameTime) $
liftIO $ threadDelay $ fromIntegral $ 1000*(minFrameTime - td)
newTime <- liftIO getClockTime
let td = timeDiff newTime t
lift $ modify $ \state -> state {tanks = (Tank ((posx . head . tanks $ state)+0.0001*(fromIntegral td)) 0.0 0):(tail . tanks $ state)}
--liftIO $ print $ timeDiff newTime t
modify $ \state -> state {time = newTime}
when run $ mainLoop
timeDiff :: ClockTime -> ClockTime -> Integer
timeDiff (TOD s1 ps1) (TOD s2 ps2) = (s1-s2)*1000 + (ps1-ps2)`div`1000000000
2010-02-22 18:27:18 +01:00
handleEvents :: Driver a => a -> IO Bool
handleEvents gl = do
event <- nextEvent gl
if (isJust event)
then
handleEvent $ fromJust event
else
return True
handleEvent :: SomeEvent -> IO Bool
2010-02-22 22:25:06 +01:00
handleEvent ev
2010-02-23 20:51:30 +01:00
| Just (ResizeEvent w h) <- fromEvent ev = do
resize w h
return True
| Just QuitEvent <- fromEvent ev = return False
2010-02-22 22:25:06 +01:00
| otherwise = return True