[Haskell-cafe] threadDelay granularity
Duane Johnson
duane.johnson at gmail.com
Tue Apr 7 12:09:18 EDT 2009
The Hipmunk 2D physics engine comes with a "playground" app which
includes the following function:
> -- | Advances the time.
> advanceTime :: IORef State -> Double -> KeyButtonState -> IO Double
> advanceTime stateVar oldTime slowKey = do
> newTime <- get time
>
> -- Advance simulation
> let slower = if slowKey == Press then slowdown else 1
> mult = frameSteps / (framePeriod * slower)
> framesPassed = truncate $ mult * (newTime - oldTime)
> simulNewTime = oldTime + toEnum framesPassed / mult
> advanceSimulTime stateVar $ min maxSteps framesPassed
>
> -- Correlate with reality
> newTime' <- get time
> let diff = newTime' - simulNewTime
> sleepTime = ((framePeriod * slower) - diff) / slower
> when (sleepTime > 0) $ sleep sleepTime
> return simulNewTime
I think the "get time" is provided by GLFW.
-- Duane Johnson
On Apr 7, 2009, at 9:25 AM, Ulrik Rasmussen wrote:
> On Tue, Apr 07, 2009 at 04:34:22PM +0200, Peter Verswyvelen wrote:
>> Do you want to cap the rendering framerate at 60FPS or the animation
>> framerate?
>> Because when you use OpenGL and GLFW, you can just
>>
>> GLFW.swapInterval $= 1
>>
>> to cap the rendering framerate at the refresh rate of your monitor
>> or LCD
>> screen (usually 60Hz)
>
> I just want to cap the rendering framerate. The game logic is
> running in
> other threads, and sends rendering information via a Chan to the
> renderer.
>
> I'm using GLUT, and have never heard of GLFW. However, that seems to
> be
> a better tool to get the job done. I'll check it out, thanks :).
>
> /Ulrik
>
>>
>>
>> On Tue, Apr 7, 2009 at 1:41 PM, Ulrik Rasmussen <haskell at utr.dk>
>> wrote:
>>
>>> Hello.
>>>
>>> I am writing a simple game in Haskell as an exercise, and in the
>>> rendering loop I want to cap the framerate to 60fps. I had planned
>>> to do
>>> this with GHC.Conc.threadDelay, but looking at it's documentation, I
>>> discovered that it can only delay the thread in time spans that are
>>> multiples of 20ms:
>>>
>>>
>>> http://www.haskell.org/ghc/docs/6.4/html/libraries/base/Control.Concurrent.html
>>>
>>> I need a much finer granularity than that, so I wondered if it is
>>> possible to either get a higher resolution for threadDelay, or if
>>> there
>>> is an alternative to threadDelay?
>>>
>>> I noticed that the SDL library includes the function "delay", which
>>> indeed works with a resolution down to one millisecond. However,
>>> since
>>> I'm using HOpenGL and GLUT, I think it would be a little overkill to
>>> depend on SDL just for this :).
>>>
>>>
>>> Thanks,
>>>
>>> Ulrik Rasmussen
>>> _______________________________________________
>>> Haskell-Cafe mailing list
>>> Haskell-Cafe at haskell.org
>>> http://www.haskell.org/mailman/listinfo/haskell-cafe
>>>
> _______________________________________________
> Haskell-Cafe mailing list
> Haskell-Cafe at haskell.org
> http://www.haskell.org/mailman/listinfo/haskell-cafe
More information about the Haskell-Cafe
mailing list