affection-0.0.0.0: A simple Game Engine using SDL

Safe HaskellNone
LanguageHaskell2010

Affection.Types

Synopsis

Documentation

type Affection us a = AffectionState (AffectionData us) IO a #

data AffectionData us #

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

Constructors

AffectionData 

Fields

data AffectionConfig us #

Configuration for the aplication. needed at startup.

Constructors

AffectionConfig 

Fields

newtype AffectionState us m a #

Affection's state monad

Constructors

AffectionState 

Fields

Instances

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

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) # 

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) # 

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) # 

Methods

pure :: a -> AffectionState us m a

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

(*>) :: 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) # 

Methods

liftIO :: IO a -> AffectionState us m a #

type AffectionStateInner us m a = StateT us m a #

Inner StateT monad for the update state type AffectionStateInner us m a = StateT (AffectionData us) m a

data InitComponents #

Components to initialize in SDL.

Constructors

All 
Only [InitFlag] 

data RGBA #

Constructors

RGBA 

Fields

  • r :: Int
     
  • g :: Int
     
  • b :: Int
     
  • a :: Int
     

data DrawType #

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

data DrawRequest #

This datatype stores information about areas of a GeglBuffer to be updated

Constructors

DrawRequest 

Fields

data RequestPersist #

Constructors

Yes 
Kill (Maybe GeglNode) 

data Angle #

Type for defining angles

Constructors

Rad Double

Angle in radians

Deg Double

Angle in degrees

Instances

Eq Angle # 

Methods

(==) :: Angle -> Angle -> Bool

(/=) :: Angle -> Angle -> Bool

Show Angle # 

Methods

showsPrec :: Int -> Angle -> ShowS

show :: Angle -> String

showList :: [Angle] -> ShowS

ConvertAngle Angle # 

Methods

toRad :: Angle -> Angle #

toDeg :: Angle -> Angle #

class ConvertAngle a where #

Typeclass for converting Angles from Deg to Rad and vice versa.

Minimal complete definition

toRad, toDeg

Methods

toRad :: a -> a #

toDeg :: a -> a #

Instances

Particle system

data Particle #

A single particle

Constructors

Particle 

Fields

data ParticleSystem #

The particle system

data ParticleStorage #

The particle storage datatype

Constructors

ParticleStorage 

Fields

Convenience exports

liftIO :: MonadIO m => forall a. IO a -> m a #

data WindowConfig :: * #

Constructors

WindowConfig 

Fields

Instances

Eq WindowConfig 

Methods

(==) :: WindowConfig -> WindowConfig -> Bool

(/=) :: WindowConfig -> WindowConfig -> Bool

Ord WindowConfig 
Read WindowConfig 

Methods

readsPrec :: Int -> ReadS WindowConfig

readList :: ReadS [WindowConfig]

readPrec :: ReadPrec WindowConfig

readListPrec :: ReadPrec [WindowConfig]

Show WindowConfig 

Methods

showsPrec :: Int -> WindowConfig -> ShowS

show :: WindowConfig -> String

showList :: [WindowConfig] -> ShowS

Generic WindowConfig 

Associated Types

type Rep WindowConfig :: * -> *

type Rep WindowConfig 
type Rep WindowConfig = D1 (MetaData "WindowConfig" "SDL.Video" "sdl2-2.1.3-DowE7uPk79X5oshOMg5tVk" False) (C1 (MetaCons "WindowConfig" PrefixI True) ((:*:) ((:*:) ((:*:) (S1 (MetaSel (Just Symbol "windowBorder") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 Bool)) (S1 (MetaSel (Just Symbol "windowHighDPI") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 Bool))) ((:*:) (S1 (MetaSel (Just Symbol "windowInputGrabbed") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 Bool)) (S1 (MetaSel (Just Symbol "windowMode") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 WindowMode)))) ((:*:) ((:*:) (S1 (MetaSel (Just Symbol "windowOpenGL") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 (Maybe OpenGLConfig))) (S1 (MetaSel (Just Symbol "windowPosition") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 WindowPosition))) ((:*:) (S1 (MetaSel (Just Symbol "windowResizable") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 Bool)) (S1 (MetaSel (Just Symbol "windowInitialSize") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 (V2 CInt)))))))

GEGL reexports

data GeglRectangle :: * #

Constructors

GeglRectangle 

Fields

Instances

Show GeglRectangle 

Methods

showsPrec :: Int -> GeglRectangle -> ShowS

show :: GeglRectangle -> String

showList :: [GeglRectangle] -> ShowS

Storable GeglRectangle 

Methods

sizeOf :: GeglRectangle -> Int

alignment :: GeglRectangle -> Int

peekElemOff :: Ptr GeglRectangle -> Int -> IO GeglRectangle

pokeElemOff :: Ptr GeglRectangle -> Int -> GeglRectangle -> IO ()

peekByteOff :: Ptr b -> Int -> IO GeglRectangle

pokeByteOff :: Ptr b -> Int -> GeglRectangle -> IO ()

peek :: Ptr GeglRectangle -> IO GeglRectangle

poke :: Ptr GeglRectangle -> GeglRectangle -> IO ()

data GeglBuffer :: * #

Constructors

GeglBuffer GeglBufferDummy