module Affection.Util where import Affection.Types import Affection.Logging import qualified SDL import System.Clock import Control.Monad.State -- Prehandle SDL events in case any window events occur preHandleEvents :: [SDL.Event] -> Affection us [SDL.EventPayload] preHandleEvents evs = return $ map SDL.eventPayload evs -- | Return the userstate to the user getAffection :: Affection us us getAffection = do ad <- get return $ userState ad -- | Put altered user state back putAffection :: us -- User state -> Affection us () putAffection us = do ad <- get put $ ad { userState = us } -- | block a thread for a specified amount of time delaySec :: Int -- ^ Number of seconds -> IO () delaySec dur = SDL.delay (fromIntegral $ dur * 1000) -- | Get time since start but always the same in the current tick. getElapsedTime :: Affection us Double getElapsedTime = elapsedTime <$> get getDelta :: Affection us Double getDelta = deltaTime <$> get quit :: Affection us () quit = do ad <- get put $ ad { quitEvent = True } -- | Toggle the Screen mode between 'SDL.Windowed' and 'SDL.FullscreenDesktop'. -- Pauses the Engine in the process. toggleScreen :: Affection us () toggleScreen = do ad <- get newMode <- case screenMode ad of SDL.Windowed -> do SDL.setWindowMode (drawWindow ad) SDL.FullscreenDesktop return SDL.FullscreenDesktop SDL.FullscreenDesktop -> do SDL.setWindowMode (drawWindow ad) SDL.Windowed return SDL.Windowed x -> do liftIO $ logIO Warn ("Unknown Screen mode: " ++ show x) return x now <- liftIO $ getTime Monotonic put ad { sysTime = now , screenMode = newMode }