{-# LANGUAGE ForeignFunctionInterface #-} {-# INCLUDE "cal3d_c.h" #-} module Graphics.Animation.Cal3D.OpenGL ( getAmbientColor , getDiffuseColor , getSpecularColor ) where import Foreign import Graphics.Rendering.OpenGL import Graphics.Animation.Cal3D getAmbientColor :: Renderer -> IO (Color4 GLfloat) getAmbientColor = withAmbientColorPtr toColor getDiffuseColor :: Renderer -> IO (Color4 GLfloat) getDiffuseColor = withDiffuseColorPtr toColor getSpecularColor :: Renderer -> IO (Color4 GLfloat) getSpecularColor = withSpecularColorPtr toColor -- toColor takes a pointer to 4 bytes of 8-bit color component -- and returns a nice OpenGL Color4 GLfloat. toColor :: Ptr Word8 -> IO (Color4 GLfloat) toColor ptr = do { r <- peekElemOff ptr 0 ; g <- peekElemOff ptr 1 ; b <- peekElemOff ptr 2 ; a <- peekElemOff ptr 3 ; return $ Color4 (float r) (float g) (float b) (float a) } -- Helper function for calColor float :: Word8 -> GLfloat float w = (fromIntegral w) / 255.0