{-# OPTIONS_HADDOCK hide #-}
module Graphics.Gloss.Internals.Rendering.Common
        ( gf, gsizei
        , withModelview
        , withClearBuffer)
where
import Unsafe.Coerce
import Graphics.Gloss.Internals.Data.Color
import Graphics.Gloss.Internals.Rendering.Color
import Graphics.Rendering.OpenGL               (($=))
import qualified Graphics.Rendering.OpenGL.GL   as GL
gf :: Float -> GL.GLfloat
gf x = unsafeCoerce x
{-# INLINE gf #-}
gsizei :: Int -> GL.GLsizei
gsizei x = unsafeCoerce x
{-# INLINE gsizei #-}
withModelview
        :: (Int, Int)  
        -> IO ()       
        -> IO ()
withModelview (sizeX, sizeY) action
 = do
        GL.matrixMode   $= GL.Projection
        GL.preservingMatrix
         $ do
                
                GL.loadIdentity
                let (sx, sy)    = (fromIntegral sizeX / 2, fromIntegral sizeY / 2)
                GL.ortho (-sx) sx (-sy) sy 0 (-100)
                
                GL.matrixMode   $= GL.Modelview 0
                action
                GL.matrixMode   $= GL.Projection
        GL.matrixMode   $= GL.Modelview 0
withClearBuffer
        :: Color        
        -> IO ()        
        -> IO ()
withClearBuffer clearColor action
 = do
        
        
        GL.depthFunc    GL.$= Just GL.Always
        
        GL.clearColor   GL.$= glColor4OfColor clearColor
        
        GL.clear [GL.ColorBuffer, GL.DepthBuffer]
        GL.color $ GL.Color4 0 0 0 (1 :: GL.GLfloat)
        action