{-# OPTIONS_HADDOCK hide #-}
{-# LANGUAGE RankNTypes #-}
module Graphics.Gloss.Internals.Interface.Simulate.Idle
( callback_simulate_idle )
where
import Graphics.Gloss.Data.ViewPort
import Graphics.Gloss.Internals.Interface.Callback
import qualified Graphics.Gloss.Internals.Interface.Backend as Backend
import qualified Graphics.Gloss.Internals.Interface.Animate.State as AN
import qualified Graphics.Gloss.Internals.Interface.Simulate.State as SM
import Data.IORef
import Control.Monad
import GHC.Float (double2Float)
callback_simulate_idle
:: IORef SM.State
-> IORef AN.State
-> IO ViewPort
-> IORef world
-> (ViewPort -> Float -> world -> IO world)
-> Float
-> IdleCallback
callback_simulate_idle simSR animateSR viewSA worldSR worldAdvance _singleStepTime backendRef
= {-# SCC "callbackIdle" #-}
do simulate_run simSR animateSR viewSA worldSR worldAdvance backendRef
simulate_run
:: IORef SM.State
-> IORef AN.State
-> IO ViewPort
-> IORef world
-> (ViewPort -> Float -> world -> IO world)
-> IdleCallback
simulate_run simSR _ viewSA worldSR worldAdvance backendRef
= do viewS <- viewSA
simS <- readIORef simSR
worldS <- readIORef worldSR
elapsedTime <- fmap double2Float $ Backend.elapsedTime backendRef
simTime <- simSR `getsIORef` SM.stateSimTime
let thisTime = elapsedTime - simTime
resolution <- simSR `getsIORef` SM.stateResolution
let timePerStep = 1 / fromIntegral resolution
let thisSteps_ = truncate $ fromIntegral resolution * thisTime
let thisSteps = if thisSteps_ < 0 then 0 else thisSteps_
let newSimTime = simTime + fromIntegral thisSteps * timePerStep
let nStart = SM.stateIteration simS
let nFinal = nStart + thisSteps
(_,world')
<- untilM (\(n, _) -> n >= nFinal)
(\(n, w) -> liftM (\w' -> (n+1,w')) ( worldAdvance viewS timePerStep w))
(nStart, worldS)
world' `seq` writeIORef worldSR world'
modifyIORef' simSR $ \c -> c
{ SM.stateIteration = nFinal
, SM.stateSimTime = newSimTime }
Backend.postRedisplay backendRef
getsIORef :: IORef a -> (a -> r) -> IO r
getsIORef ref fun
= liftM fun $ readIORef ref
untilM :: (Monad m) => (a -> Bool) -> (a -> m a) -> a -> m a
untilM test op i = go i
where
go x | test x = return x
| otherwise = op x >>= go