-- the main game loop module Game where import Data.Maybe import StaticInterface import Static import States import RenderInterface import Render import UInputInterface import UInputUtils import Utilities import Options import Debug startGame :: Options -> IO () startGame opts = do -- initialise static data debug_msg opts "loading graphical data ..." static <- initStatic opts -- enter the main game loop debug_msg opts "entering main game loop ..." runGameWrapper opts static return () -- | Wrapper around the 'runGame' function -- (using the concrete engines for rendering and input handling) runGameWrapper :: Options -> Static -> IO () runGameWrapper opts static = runGame opts (standardRenderEngine static) (standardUInputEngine (options static)) getTicks -- | The length of a "tick" in ms (i.e., the state is updated -- approximately every @1000/tick_length@ times per second. tick_length :: Int tick_length = 30 ----------------------------------------------------------- -- * Game loop ----------------------------------------------------------- runGame :: Options -> RenderEngine -> UInputEngine -> IO Int -> IO () runGame opts rengine iengine getTime = do -- init State let s = initState -- wait/quit q <- inputWaitQ if q then return () else do -- call the runGameLoop with the right arguments t <- getTime s' <- runGameLoop t s -- restart the game runGame opts rengine iengine getTime where -- unpack the rendering engine renderR = render_running rengine renderE = render_end rengine -- unpack the input handling engine inputHandle = input_handleRunning iengine inputWait = input_waitForAnyKey iengine inputWaitQ = waitOrQuit inputWait -- the game loop runGameLoop :: Int -> State -> IO State runGameLoop tu s = do -- player still alive? let st = status s case st of Alive -> runGameLoopAlive tu s Dead -> do renderE s return s runGameLoopAlive :: Int -> State -> IO State runGameLoopAlive tu s = do -- has enough time passed since the last update of the state to update again? t <- getTime let dt = t - tu debug_msg opts (show t ++ " - " ++ show tu ++ " = " ++ show dt) if dt >= tick_length then -- update do -- get user input ui <- inputHandle (input s) -- did the player quit? if hasQuit ui then return s else do -- update the state according to input -- debug_msg "update state" s' <- updateState s ui dt -- render the state renderR 0 s' -- re-enter the loop runGameLoop t s' else -- render interpolated state do -- render the state renderR dt s -- re-enter the loop runGameLoopAlive tu s