bbrown wrote:
This is more an aesthetics question, I have a simple opengl application that has a singleton like object I need to pass around to the display loop and possibly to the keyboard action handler. (pseudo code)

data SimpleMech = SimpleMech {
      mechPos         :: !MVector,
      mechRot         :: !MVector
    } deriving (Read)

mainMech = initMech (0, 0, 0) (0, 0, 0)
mainMechRef <- newIORef(mainMech)

displayCallback $= displayGameLoop mainMechRef


rotateMech :: (Double, SimpleMech) -> SimpleMech
rotateMech (angle, mech) =
  -- Calculate a new rotation
  let (xrot,yrot,zrot) = (mechRot mech)
      newyrot = newyrot + angle

               ^^^
That should be
        newyrot = yrot + angle

  in SimpleMech { mechRot = (xrot, newyrot, zrot),
                  mechPos = (mechPos mech) }


displayGameLoop mechRef = do
mech <- get mechRef
mechRef $= (rotateMech (0.1, mech))

....
....
For some reason in that code above, the "mechRef" doesnt update the value I want to change. It is like I am getting an instance of the initial valyue back. Also, when I use writeIORef, eg writeIORef mechRef (rotateMech (0.1, mech)

I get stack overflow exceptions.

The bug above is probably responsible for both the stack overflows with writeIORef and for a $= that doesn't update (it wants to update, but the program is trapped in an infinite loop).


Btw, you don't need parenthesis about function applications, you can use record update syntax and functions with several arguments are usually written in curried form:

      -- Calculate a new rotation
  rotateMech :: Double -> SimpleMech -> SimpleMech
  rotateMech angle mech =
     mech { mechRot = (xrot, yrot + angle, zrot) }
     where
        (xrot,yrot,zrot) = mechRot mech

  mainMech = initMech (0, 0, 0) (0, 0, 0)

  main = do
     mainMechRef <- newIORef mainMech
     displayCallback $= displayGameLoop mainMechRef

  displayGameLoop mechRef = do
     mech <- get mechRef
     mechRef $= rotateMech 0.1 mech

The latter can also be written as

  displayGameLoop mechRef = do
     mechRef $~ rotateMech 0.1


Regards,
apfelmus

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

Reply via email to