module Control.FRPNow.Gloss(GEvent,Time,runNowGloss, runNowGlossPure, toMouseMoves, toMousePos, toKeysDown, filterMouseButtons) where
import Graphics.Gloss.Interface.IO.Game hiding (Event)
import Control.FRPNow
import Data.Sequence
import Control.Applicative
import qualified Data.Sequence as Seq
import Data.Maybe
import Data.IORef
import Debug.Trace
import GHC.Float
import qualified Data.Foldable as Fold
import Data.Set
import qualified Data.Set as Set
import qualified Graphics.Gloss.Interface.IO.Game as Gloss
import Debug.Trace
type GEvent = Gloss.Event
type Time = Float
runNowGloss ::
Display
-> Color
-> Int
-> (Behavior Time -> EvStream GEvent -> Now (Behavior Picture))
-> IO ()
runNowGloss disp bg fps m =
do scheduleRef <- newIORef Seq.empty
callbackRef <- newIORef undefined
pictureRef <- newIORef Blank
initNow (schedule scheduleRef) (initM callbackRef pictureRef)
(cbTime, cbgEv) <- readIORef callbackRef
playIO disp bg fps ()
(\_ -> readIORef pictureRef)
(\ev _ -> cbgEv ev)
(\deltaTime _ -> do cbTime deltaTime
rounds <- readIORef scheduleRef
writeIORef scheduleRef Seq.empty
mapM_ id (Fold.toList rounds)
return ()
)
where
initM callbackRef pictureRef =
do (timeEvs,cbtime) <- callbackStream
(gevEvs,cbgEv) <- callbackStream
sync $ writeIORef callbackRef (cbtime,cbgEv)
clock <- sample $ foldEs (+) 0 timeEvs
pict <- m clock gevEvs
curPict <- sample pict
sync $ writeIORef pictureRef curPict
callIOStream (writeIORef pictureRef) (toChanges pict)
return never
schedule ref m = atomicModifyIORef ref (\s -> (s |> m, ()))
runNowGlossPure ::
Display
-> Color
-> Int
-> (Behavior Time -> EvStream GEvent -> Behavior (Behavior Picture))
-> IO ()
runNowGlossPure disp bg fps b = runNowGloss disp bg fps (\t e -> sample $ b t e)
toMouseMoves :: EvStream GEvent -> EvStream (Float,Float)
toMouseMoves evs = filterMapEs getMouseMove evs
where getMouseMove (EventMotion p) = Just p
getMouseMove _ = Nothing
toMousePos :: EvStream GEvent -> Behavior (Behavior (Float, Float))
toMousePos evs = fromChanges (0,0) (toMouseMoves evs)
toKeysDown :: EvStream GEvent -> Behavior (Behavior (Set Key))
toKeysDown evs = foldEs updateSet Set.empty evs where
updateSet :: Set Key -> GEvent -> Set Key
updateSet s (EventKey k i _ _) = action i k s
where action Up = delete
action Down = insert
updateSet s _ = s
filterMouseButtons :: Behavior (Set Key) -> Behavior (Set MouseButton)
filterMouseButtons b =
let isMouseButton (MouseButton _) = True
isMouseButton _ = False
in Set.map (\(MouseButton x) -> x) . Set.filter isMouseButton <$> b