{-# OPTIONS_HADDOCK hide #-}
module Graphics.UI.Fungen.Display (
display
) where
import Graphics.UI.Fungen.Game
import Graphics.UI.Fungen.Util (when)
import Graphics.Rendering.OpenGL
import Graphics.UI.GLUT
display :: Game t s u v -> IOGame t s u v () -> DisplayCallback
display :: Game t s u v -> IOGame t s u v () -> DisplayCallback
display Game t s u v
g IOGame t s u v ()
gameCycle = do
[ClearBuffer] -> DisplayCallback
clear [ClearBuffer
ColorBuffer]
IOGame t s u v () -> Game t s u v -> IO (Game t s u v, ())
forall t s u v a.
IOGame t s u v a -> Game t s u v -> IO (Game t s u v, a)
runIOGame (IOGame t s u v () -> IOGame t s u v ()
forall t s u v. IOGame t s u v () -> IOGame t s u v ()
displayIOGame IOGame t s u v ()
gameCycle) Game t s u v
g
DisplayCallback
forall (m :: * -> *). MonadIO m => m ()
swapBuffers
DisplayCallback
flush
displayIOGame :: IOGame t s u v () -> IOGame t s u v ()
displayIOGame :: IOGame t s u v () -> IOGame t s u v ()
displayIOGame IOGame t s u v ()
gameCycle = do
(Bool
_,Bool
_,Bool
objectsMoving) <- IOGame t s u v (Bool, Bool, Bool)
forall t s u v. IOGame t s u v (Bool, Bool, Bool)
getGameFlags
Bool -> IOGame t s u v () -> IOGame t s u v ()
forall (m :: * -> *). Monad m => Bool -> m () -> m ()
when Bool
objectsMoving IOGame t s u v ()
forall t s u v. IOGame t s u v ()
moveAllObjects
IOGame t s u v ()
gameCycle
(Bool
mapDrawing,Bool
objectsDrawing,Bool
_) <- IOGame t s u v (Bool, Bool, Bool)
forall t s u v. IOGame t s u v (Bool, Bool, Bool)
getGameFlags
Bool -> IOGame t s u v () -> IOGame t s u v ()
forall (m :: * -> *). Monad m => Bool -> m () -> m ()
when Bool
mapDrawing IOGame t s u v ()
forall t s u v. IOGame t s u v ()
drawMap
Bool -> IOGame t s u v () -> IOGame t s u v ()
forall (m :: * -> *). Monad m => Bool -> m () -> m ()
when Bool
objectsDrawing IOGame t s u v ()
forall t s u v. IOGame t s u v ()
drawAllObjects
IOGame t s u v ()
forall t s u v. IOGame t s u v ()
printText