{-# LANGUAGE RankNTypes #-}
module Graphics.Gloss.Internals.Interface.Game
( playWithBackendIO
, Event(..) )
where
import Graphics.Gloss.Data.Color
import Graphics.Gloss.Data.Picture
import Graphics.Gloss.Data.ViewPort
import Graphics.Gloss.Rendering
import Graphics.Gloss.Internals.Interface.Event
import Graphics.Gloss.Internals.Interface.Backend
import Graphics.Gloss.Internals.Interface.Window
import Graphics.Gloss.Internals.Interface.Common.Exit
import Graphics.Gloss.Internals.Interface.ViewState.Reshape
import Graphics.Gloss.Internals.Interface.Animate.Timing
import Graphics.Gloss.Internals.Interface.Simulate.Idle
import qualified Graphics.Gloss.Internals.Interface.Callback as Callback
import qualified Graphics.Gloss.Internals.Interface.Simulate.State as SM
import qualified Graphics.Gloss.Internals.Interface.Animate.State as AN
import Data.IORef
import System.Mem
playWithBackendIO
:: forall world a
. Backend a
=> a
-> Display
-> Color
-> Int
-> world
-> (world -> IO Picture)
-> (Event -> world -> IO world)
-> (Float -> world -> IO world)
-> Bool
-> IO ()
playWithBackendIO
backend
display
backgroundColor
simResolution
worldStart
worldToPicture
worldHandleEvent
worldAdvance
withCallbackExit
= do
let singleStepTime = 1
stateSR <- newIORef $ SM.stateInit simResolution
worldSR <- newIORef worldStart
viewSR <- newIORef viewPortInit
animateSR <- newIORef AN.stateInit
renderS_ <- initState
renderSR <- newIORef renderS_
let displayFun backendRef
= do
world <- readIORef worldSR
picture <- worldToPicture world
renderS <- readIORef renderSR
viewPort <- readIORef viewSR
windowSize <- getWindowDimensions backendRef
displayPicture
windowSize
backgroundColor
renderS
(viewPortScale viewPort)
(applyViewPortToPicture viewPort picture)
performGC
let callbacks
= [ Callback.Display (animateBegin animateSR)
, Callback.Display displayFun
, Callback.Display (animateEnd animateSR)
, Callback.Idle (callback_simulate_idle
stateSR animateSR (readIORef viewSR)
worldSR (\_ -> worldAdvance)
singleStepTime)
, callback_keyMouse worldSR viewSR worldHandleEvent
, callback_motion worldSR worldHandleEvent
, callback_reshape worldSR worldHandleEvent]
let exitCallback
= if withCallbackExit then [callback_exit ()] else []
createWindow
backend
display
backgroundColor
(callbacks ++ exitCallback)
(\_ -> return ())
callback_keyMouse
:: IORef world
-> IORef ViewPort
-> (Event -> world -> IO world)
-> Callback
callback_keyMouse worldRef viewRef eventFn
= KeyMouse (handle_keyMouse worldRef viewRef eventFn)
handle_keyMouse
:: IORef a
-> t
-> (Event -> a -> IO a)
-> KeyboardMouseCallback
handle_keyMouse worldRef _ eventFn backendRef key keyState keyMods pos
= do ev <- keyMouseEvent backendRef key keyState keyMods pos
world <- readIORef worldRef
world' <- eventFn ev world
writeIORef worldRef world'
callback_motion
:: IORef world
-> (Event -> world -> IO world)
-> Callback
callback_motion worldRef eventFn
= Motion (handle_motion worldRef eventFn)
handle_motion
:: IORef a
-> (Event -> a -> IO a)
-> MotionCallback
handle_motion worldRef eventFn backendRef pos
= do ev <- motionEvent backendRef pos
world <- readIORef worldRef
world' <- eventFn ev world
writeIORef worldRef world'
callback_reshape
:: IORef world
-> (Event -> world -> IO world)
-> Callback
callback_reshape worldRef eventFN
= Reshape (handle_reshape worldRef eventFN)
handle_reshape
:: IORef world
-> (Event -> world -> IO world)
-> ReshapeCallback
handle_reshape worldRef eventFn stateRef (width,height)
= do world <- readIORef worldRef
world' <- eventFn (EventResize (width, height)) world
writeIORef worldRef world'
viewState_reshape stateRef (width, height)