affection-0.0.0.7: A simple Game Engine using SDL

Safe HaskellNone
LanguageHaskell2010

Affection.Types

Synopsis

Documentation

data AffectionConfig us Source #

Configuration for the aplication. needed at startup.

Constructors

AffectionConfig 

Fields

data InitComponents Source #

Components to initialize in SDL.

Constructors

All 
Only [InitFlag] 

data AffectionData us Source #

Main type for defining the look, feel and action of the whole application.

Constructors

AffectionData 

Fields

  • quitEvent :: Bool

    Loop breaker.

  • userState :: us

    State data provided by user

  • drawWindow :: Window

    SDL window

  • glContext :: GLContext

    OpenGL rendering context

  • windowRenderer :: Renderer

    Internal renderer of window

  • drawTexture :: Texture

    SDL Texture to draw to , drawFormat :: B.BablFormatPtr -- ^ Target format

  • screenMode :: WindowMode

    current screen mode , drawStack :: [DrawRequest] -- ^ Stack of DrawRequests to be processed

  • drawDimensions :: (Int, Int)

    Dimensions of target surface

  • drawStride :: Int

    Stride of target buffer

  • drawCPP :: Int

    Number of components per pixel

  • elapsedTime :: Double

    Elapsed time in seconds

  • deltaTime :: Double

    Elapsed time in seconds since last tick

  • sysTime :: TimeSpec

    System time (NOT the time on the clock)

  • pausedTime :: Bool

    Should the update loop be executed? , messageChannel :: Channel msg -- ^ The main broadcast channel to duplicate all others from

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 # 

Methods

get :: AffectionState us m us #

put :: us -> AffectionState us m () #

state :: (us -> (a, us)) -> AffectionState us m a

Monad m => Monad (AffectionState us m) Source # 

Methods

(>>=) :: AffectionState us m a -> (a -> AffectionState us m b) -> AffectionState us m b

(>>) :: AffectionState us m a -> AffectionState us m b -> AffectionState us m b

return :: a -> AffectionState us m a

fail :: String -> AffectionState us m a

Functor m => Functor (AffectionState us m) Source # 

Methods

fmap :: (a -> b) -> AffectionState us m a -> AffectionState us m b

(<$) :: a -> AffectionState us m b -> AffectionState us m a

Monad m => Applicative (AffectionState us m) Source # 

Methods

pure :: a -> AffectionState us m a

(<*>) :: AffectionState us m (a -> b) -> AffectionState us m a -> AffectionState us m b

liftA2 :: (a -> b -> c) -> AffectionState us m a -> AffectionState us m b -> AffectionState us m c

(*>) :: AffectionState us m a -> AffectionState us m b -> AffectionState us m b

(<*) :: AffectionState us m a -> AffectionState us m b -> AffectionState us m a

MonadIO m => MonadIO (AffectionState us m) Source # 

Methods

liftIO :: IO a -> AffectionState us m a

MonadParallel m => MonadParallel (AffectionState us m) Source # 

Methods

bindM2 :: (a -> b -> AffectionState us m c) -> AffectionState us m a -> AffectionState us m b -> AffectionState us m c

data DrawType Source #

Type for defining the draw type of draw functions

Constructors

Fill

Fill the specified area completely with color

Line

only draw the outline of the area

Fields

type Angle = Double Source #