module Animate where import Data.IORef import Control.Concurrent.MVar import Data.Convertible import Data.Time.Clock import Control.Monad import FRP.Yampa import qualified Render import BasicTypes import Object import AL import States import Global import GameLoop animate' :: ReactHandle GameInput b -> Time -> IORef Time -> IORef Int -> MVar [RSEvent] -> IO Bool animate' rh t0 timeState frameCounter newInput = do t <- getCurrentTime let t' = convert t :: Double tLast <- readIORef timeState writeIORef timeState t' inp <- input' (t'-t0) (t'-tLast) frameCounter newInput react rh inp animateInit :: Param -> GraphicsData -> IORef (Bool, Int, Int) -> Time -> IORef Double -> IORef Int -> [(ObjId, Object, ObjOutput)] -> IO (ReactHandle GameInput (AL ObjId ObjOutput)) animateInit param graphData resultRef dt timeState frameCounter objs = do (_, Just gi0) <- input dt timeState frameCounter True reactInit (return gi0) (output' param graphData resultRef) (gameLoop param (AL $ map (\(idty, _, oo) -> (idty, oo)) objs) (AL $ map (\(idty, o, _) -> (idty, o)) objs)) input' :: Time -> Time -> IORef Int -> MVar [RSEvent] -> IO (DTime, Maybe GameInput) input' t dt counter newInput = do maybeEvents <- tryTakeMVar newInput putMVar newInput [] count <- readIORef counter let events = case maybeEvents of Nothing -> [] Just es -> es writeIORef counter (count + 1) return (dt, Just (t, events)) output' :: (Eq a, Num a) => --(Eq a, Num i, Num a, Ix i) => Param -> GraphicsData -> IORef (Bool, Int, Int) -> t -> t1 -> AL a ObjOutput -> IO Bool output' param graphData resultRef _ _ oal@(AL oos) = do Render.render param (map (ooObsObjState . snd) oos) graphData let ol = (AL.!) oal 1 let gs = (fst . oosGameState . ooObsObjState) ol let (homeGoals, awayGoals) = (oosGameScore . ooObsObjState) ol let aborted = (oosGameTime . ooObsObjState) ol > 120.0 let quit = gs == GSQuit when quit $ writeIORef resultRef (aborted, homeGoals, awayGoals) return quit -- neuer Kram endet hier -- reactimation IO ---------- input :: Time -> IORef Double -> IORef Int -> Bool -> IO (DTime, Maybe GameInput) input tInit stateTime counter _ = do count <- readIORef counter writeIORef counter (count + 1) let events = [] -- events <- unfoldWhileM (/= SDL.NoEvent) SDL.pollEvent t1 <- getCurrentTime let t1' = convert t1 :: Double t0 <- readIORef stateTime writeIORef stateTime t1' return (t1'-t0, Just (t1'-tInit, events))