Rafael Cunha de Almeida <almeida...@gmail.com> writes:

> My main function goes like this:
>     (...)
>     rotX <- newIORef (0.0::GLfloat)
>     rotY <- newIORef (0.0::GLfloat)
>     pos <- newIORef (0.0::GLfloat, 0.0, 0.0)
>
>     displayCallback $= display (map f range) rotX rotY pos
>
>     keyboardMouseCallback $= Just (keyboardMouse rotX rotY pos)
>     (...)
>
> ...
>
> In a state-based language I would place display and keyboardMouse in one
> module and let them communcate to each other like they want. In haskell,
> I'm not quite sure how to do it except by that parameter passing style.

You could try something like this: (and apologies in advance for any
typoes)

------------------------------------------------------------------------
import Control.Concurrent.MVar

data MyState = MyState {
    rotX :: GLFloat
  , rotY :: GLFloat
  , pos  :: (GLFloat,GLFloat)
}


myDisplayCallback :: MVar MyState -> IO ()
myDisplayCallback =
    flip modifyMVar_ $ \(MyState rx ry p) -> do
        (newRx, newRy, newP) <- yourCodeGoesHere
        return $ MyState newRx newRy newP
        

main = do
    mvar <- newMVar $ MyState 0 0 (0,0)
    displayCallback $= myDisplayCallback mvar
    ...

------------------------------------------------------------------------

Cheers,
G.    
-- 
Gregory Collins <g...@gregorycollins.net>
_______________________________________________
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe

Reply via email to