pituicat/src/Affection/Types.hs

97 lines
3.0 KiB
Haskell

{-# LANGUAGE GeneralizedNewtypeDeriving, DeriveFunctor #-}
module Affection.Types
( AffectionData(..)
, AffectionConfig(..)
, AffectionState(..)
-- , AffectionDraw(..)
-- , Draw(..)
, AffectionStateInner(..)
-- , AffectionDrawInner(..)
, InitComponents(..)
-- , Loop(..)
, RGBA(..)
, SDL.WindowConfig(..)
, SDL.defaultWindow
) where
import qualified SDL.Init as SDL
import qualified SDL.Video as SDL
import qualified Data.Text as T
import Control.Monad.IO.Class
import Control.Monad.State
import Control.Monad.Reader
import Control.Concurrent.MVar
-- | Configuration for the aplication. needed at startup.
data AffectionConfig us = AffectionConfig
{ initComponents :: InitComponents
-- ^ SDL components to initialize at startup
, windowTitle :: T.Text
-- ^ Window title
, windowConfig :: SDL.WindowConfig
-- ^ Window configuration
, drawLoop :: AffectionState (AffectionData us) IO ()
-- ^ Function for updating graphics.
, updateLoop :: Double -> AffectionState (AffectionData us) IO ()
-- ^ Main update function. Takes fractions of a second as input.
, loadState :: SDL.Surface -> IO us
-- ^ Provide your own load function to create this data.
}
-- | Main type for defining the look, feel and action of the whole application.
data AffectionData us = AffectionData
-- { affectionConfig :: AffectionConfig us -- ^ Application configuration.
{ quitEvent :: Bool -- ^ Loop breaker.
, userState :: us -- ^ State data provided by user
, drawWindow :: SDL.Window -- ^ SDL window
, drawSurface :: SDL.Surface -- ^ SDL surface
}
-- -- | Data and surfaces for drawing.
-- data AffectionDraw dd = AffectionDraw
-- }
-- | Components to initialize in SDL.
data InitComponents
= All
| Only [SDL.InitFlag]
-- | Inner 'StateT' monad for the update state
-- type AffectionStateInner us m a = StateT (AffectionData us) m a
type AffectionStateInner us m a = StateT us m a
-- | Affection's state monad
newtype AffectionState us m a = AffectionState
{ runState :: AffectionStateInner us m a }
deriving (Functor, Applicative, Monad, MonadIO, MonadState us)
-- -- | Inner 'StateT' monad of Affection
-- type AffectionInner us od a = StateT (AffectionState us od) IO a
--
-- -- | Affection state monad
-- newtype Affection us od a = Affection
-- { runAffection :: AffectionInner us od a }
-- deriving (Functor, Applicative, Monad, MonadState (AffectionState us od))
--
-- -- | Inner drawing monad of Affection.
-- type AffectionDrawInner ds a = ReaderT (Draw ds) a
--
-- -- | Affectiondrawinf reader monad.
-- newtype AffectionDraw ds a = AffectionDraw
-- { runDraw :: (ds -> a) }
-- deriving (Functor, Applicative, Monad, MonadReader ds)
--
-- -- | Loop state monad to hold elapsed time per frame
-- newtype Loop f a = Loop
-- { runLoop :: f -> (a, f) }
-- deriving (Functor, Applicative, Monad, MonadState (Loop f))
data RGBA = RGBA
{ r :: Int
, g :: Int
, b :: Int
, a :: Int
}