[Haskell-cafe] How to variables

yin yin at atom.sk
Mon Jul 18 16:39:24 EDT 2005


robert dockins wrote:

>
>
> yin wrote:
>
>> Hello all!
>>
>> I'm doing a 3D simulation. Now I need something like variables in
>> imperative languages. My mainLoop check for new events and renders
>> scene.
>
>
> Then you want IORef.
> http://www.haskell.org/ghc/docs/latest/html/libraries/base/Data.IORef.html
>
>
>
> Consider, however, that this kind of construct can be done without
> mutable variables. (warning, made-up code ahead)
>
>
> main = loop 0 0 0 -- initial values
>  where loop loop_num xpos ypos =
>             do e <- pollEvent
>                let xpos' = <calculate new xpos>
>                    ypos' = <calculate new ypos>
>                someActionInvolvingPosition xpos' ypos'
>                when breakCondition (return ())
>                loop (loop_num+1) xpos' ypos'
>
>
I saw it. The problem is, I need an amount of 100*X of mutable variables
to implement the system (camera position, rotation, aceleration, ...,
position and deformetion infomations for every object, ..., renderer
situations [like temprary fading and other efects], ... and more)

I tried something like this:

main = withInit [InitVideo] $
       do progname <- getProgName
          createAWindow progname
          mainLoop 0

mainLoop :: Int -> IO ()
mainLoop ll = do
        event <- pollEvent
        quit <- case event of
                VideoResize w h -> resizeGLScene w h >> return False
                KeyDown (Keysym SDLK_q _ _) -> return True
                Quit -> return True
                _ -> drawGLScreen ((fromIntegral ll) / 10) >> return False
        when (not quit) (mainLoop (ll + 1))

drawGLScreen :: Double -> IO ()
drawGLScreen = do
  clear [ColorBuffer,DepthBuffer]
  loadIdentity
  translate $ (\(x,y,z) -> Vector3 x y z) getCameraPos
  rotate blah, blah, ...
  renderPrimitive Polygon $ mapM_ (\(x,y,z) -> vertex$Vertex3 x y z)
polygonPoints
  glSwapBuffers

getCameraPos :: (GLfloat, GLfloat, GLfloat)
getCameraPos = readIORef refCameraPos

setCameraPos :: (GLfloat, GLfloat, GLfloat) -> IO ()
setCameraPos (a, b, c) = writeIORef refCameraPos (a, b, c)

And there si the problem - how to initialize refCameraPos with newIORef,
and then using it.

If I write "refCameraPos = newIORef (0, 0, 0)" it will initialize new
IORef every time. I need Just persistent, mutualy variable. I was
covered on this list , but I've deleted the messages.

Matej 'Yin' Gagyi



More information about the Haskell-Cafe mailing list