| Safe Haskell | None |
|---|---|
| Language | Haskell2010 |
Affection.Types
- data AffectionConfig us = AffectionConfig {
- initComponents :: InitComponents
- windowTitle :: Text
- windowConfig :: WindowConfig
- canvasSize :: Maybe (Int, Int)
- initScreenMode :: WindowMode
- loadState :: IO us
- preLoop :: Affection us ()
- eventLoop :: [EventPayload] -> Affection us ()
- updateLoop :: Double -> Affection us ()
- drawLoop :: Affection us ()
- cleanUp :: us -> IO ()
- data InitComponents
- data AffectionData us = AffectionData {
- quitEvent :: Bool
- userState :: us
- drawWindow :: Window
- glContext :: GLContext
- windowRenderer :: Renderer
- drawTexture :: Texture
- screenMode :: WindowMode
- drawDimensions :: (Int, Int)
- drawStride :: Int
- drawCPP :: 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
- type Affection us a = AffectionState (AffectionData us) IO a
- data DrawType
- type Angle = Double
Documentation
data AffectionConfig us Source #
Configuration for the aplication. needed at startup.
Constructors
| AffectionConfig | |
Fields
| |
data AffectionData us Source #
Main type for defining the look, feel and action of the whole application.
Constructors
| AffectionData | |
Fields
| |
type AffectionStateInner us a = StateT us a Source #
Inner StateT monad for the update state
type AffectionStateInner us m a = StateT (AffectionData us) m a
newtype AffectionState us m a Source #
Affection's state monad
Constructors
| AffectionState | |
Fields
| |
Instances
| Monad m => MonadState us (AffectionState us m) Source # | |
| Monad m => Monad (AffectionState us m) Source # | |
| Functor m => Functor (AffectionState us m) Source # | |
| Monad m => Applicative (AffectionState us m) Source # | |
| MonadIO m => MonadIO (AffectionState us m) Source # | |
| MonadParallel m => MonadParallel (AffectionState us m) Source # | |
type Affection us a = AffectionState (AffectionData us) IO a Source #
Type for defining the draw type of draw functions