{-# LANGUAGE RecordWildCards #-} module Affection ( withAffection , withWindow , withDefaultWindow , delaySec , module Affection.Render , module Affection.Types ) where import qualified SDL import qualified GEGL as G import qualified Data.Text as T import Data.Maybe import System.TimeIt (timeItT) import Control.Monad.Loops import Control.Monad.State import Control.Monad.Reader import Control.Concurrent.MVar import Affection.Render import Affection.Types as Types withAffection :: AffectionConfig us -> IO () withAffection conf@AffectionConfig{..} = do case initComponents of All -> SDL.initializeAll Only is -> SDL.initialize is execTime <- newMVar 0 window <- SDL.createWindow windowTitle windowConfig surface <- SDL.getWindowSurface window let initContainer = AffectionData conf False userData window surface state <- newMVar initContainer (res, nState) <- runStateT ( whileM_ (do current <- get return $ Types.quitEvent current ) $ do lastTime <- liftIO $ fromMaybe 0 <$> tryReadMVar execTime (dTime, _) <- liftIO $ timeItT <$> drawLoop (uTime, _) <- liftIO $ timeItT <$> updateLoop lastTime liftIO $ putMVar execTime $ lastTime + dTime + uTime ) initContainer SDL.quit withWindow :: Monad m => T.Text -> WindowConfig -> SDL.RendererConfig -> RenderT m a -> IO () withWindow title wconf rconf ops = do window <- SDL.createWindow title wconf -- I don't need a renderer here, i need a surface renderer <- SDL.createRenderer window (-1) rconf surface <- SDL.getWindowSurface window G.gegl_init -- I think I need some AffectionT or someting similar here and not a RenderT -- from SDL. inRender renderer $ ops G.gegl_exit SDL.destroyWindow window withDefaultWindow :: Monad m => T.Text -> (RenderT m a) -> IO () withDefaultWindow title ops = withWindow title defaultWindow SDL.defaultRenderer ops delaySec :: Int -> IO () delaySec dur = SDL.delay (fromIntegral $ dur * 1000)