{-# LANGUAGE GeneralizedNewtypeDeriving, DeriveFunctor #-}
module Affection.Types
( Affection
, AffectionConfig(..)
, AffectionData(..)
, AffectionStateInner
, AffectionState(..)
, InitComponents(..)
, Angle
, SDL.WindowConfig(..)
, SDL.WindowMode(..)
, SDL.EventPayload(..)
, SDL.InitFlag(..)
, SDL.Window
, SDL.GLContext
) where
import qualified SDL.Init as SDL
import qualified SDL.Video as SDL
import qualified SDL.Event as SDL
import qualified Data.Text as T
import Control.Monad.IO.Class
import Control.Monad.State.Strict
import qualified Control.Monad.Parallel as MP
import System.Clock (TimeSpec)
data AffectionConfig us = AffectionConfig
{ initComponents :: InitComponents
, windowTitle :: T.Text
, windowConfig :: SDL.WindowConfig
, canvasSize :: Maybe (Int, Int)
, initScreenMode :: SDL.WindowMode
, loadState :: IO us
, preLoop :: Affection us ()
, eventLoop :: [SDL.EventPayload] -> Affection us ()
, updateLoop :: Double -> Affection us ()
, drawLoop :: Affection us ()
, cleanUp :: us -> IO ()
}
data InitComponents
= All
| Only [SDL.InitFlag]
data AffectionData us = AffectionData
{ quitEvent :: Bool
, userState :: us
, drawWindow :: SDL.Window
, glContext :: SDL.GLContext
, screenMode :: SDL.WindowMode
, drawDimensions :: (Int, Int)
, elapsedTime :: Double
, deltaTime :: Double
, sysTime :: TimeSpec
, pausedTime :: Bool
}
type AffectionStateInner us a = StateT us a
newtype AffectionState us m a = AffectionState
{ runState :: AffectionStateInner us m a }
deriving (Functor, Applicative, Monad, MonadIO, MonadState us)
instance MP.MonadParallel m => MP.MonadParallel (AffectionState us m)
type Affection us a = AffectionState (AffectionData us) IO a
type Angle = Double