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)

Then you probably want a big labeled record,

data ProgramState =
  ProgramState { var1 :: IORef Int
               , var2 :: IORef Int
               , var3 :: IORef Int
               , objects :: IORef [Object]
               , etc ....}

with a big nasty init function that calls newIORef a bunch of times with the initial values. Then you just pass around your ProgramState value.

initProgramState :: IO ProgramState
initProgramState =
    do ref1 <- newIORef 0
       ref2 <- newIORef 12345
       ref3 <- newIORef 1111
       .....
       return ProgramState { var1 = ref1, var2 =  ref2, var3 =  ref3, ... }

main = ps <- initProgramState
       mainLoop ps

This has the nice property that you can add new fields to your record without having to change the signature of dozens of functions.

Of course, you can alternately just create a big labeled record of pure values, and stick the whole thing in an IORef, or use recursive argument passing trick and skip the IORefs altogether. I'm not sure I'm competent to give a breakdown of the advantages and disadvantages of each method, although I am personally inclined toward avoiding IORefs.

Some people may suggest that you to create top-level IORefs using unsafePerformIO, but I don't recommend that for this situation.

_______________________________________________
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe

Reply via email to