affection-0.0.0.9: 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 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

newtype AffectionState us m a Source #

Affection's state monad

Constructors

AffectionState 

Fields

Instances
Monad m => MonadState us (AffectionState us m) Source # 
Instance details

Defined in Affection.Types

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 # 
Instance details

Defined in Affection.Types

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 # 
Instance details

Defined in Affection.Types

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 # 
Instance details

Defined in Affection.Types

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 # 
Instance details

Defined in Affection.Types

Methods

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

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

Defined in Affection.Types

Methods

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

data InitComponents Source #

Components to initialize in SDL.

Constructors

All 
Only [InitFlag] 

SDL reexports

data WindowConfig #

Constructors

WindowConfig 

Fields

Instances
Eq WindowConfig 
Instance details

Defined in SDL.Video

Ord WindowConfig 
Instance details

Defined in SDL.Video

Read WindowConfig 
Instance details

Defined in SDL.Video

Show WindowConfig 
Instance details

Defined in SDL.Video

Generic WindowConfig 
Instance details

Defined in SDL.Video

Associated Types

type Rep WindowConfig :: * -> * #

type Rep WindowConfig 
Instance details

Defined in SDL.Video

data WindowMode #

Constructors

Fullscreen

Real fullscreen with a video mode change

FullscreenDesktop

Fake fullscreen that takes the size of the desktop

Maximized 
Minimized 
Windowed 
Instances
Bounded WindowMode 
Instance details

Defined in SDL.Video

Enum WindowMode 
Instance details

Defined in SDL.Video

Eq WindowMode 
Instance details

Defined in SDL.Video

Data WindowMode 
Instance details

Defined in SDL.Video

Methods

gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> WindowMode -> c WindowMode #

gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c WindowMode #

toConstr :: WindowMode -> Constr #

dataTypeOf :: WindowMode -> DataType #

dataCast1 :: Typeable t => (forall d. Data d => c (t d)) -> Maybe (c WindowMode) #

dataCast2 :: Typeable t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c WindowMode) #

gmapT :: (forall b. Data b => b -> b) -> WindowMode -> WindowMode #

gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> WindowMode -> r #

gmapQr :: (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> WindowMode -> r #

gmapQ :: (forall d. Data d => d -> u) -> WindowMode -> [u] #

gmapQi :: Int -> (forall d. Data d => d -> u) -> WindowMode -> u #

gmapM :: Monad m => (forall d. Data d => d -> m d) -> WindowMode -> m WindowMode #

gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> WindowMode -> m WindowMode #

gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> WindowMode -> m WindowMode #

Ord WindowMode 
Instance details

Defined in SDL.Video

Read WindowMode 
Instance details

Defined in SDL.Video

Show WindowMode 
Instance details

Defined in SDL.Video

Generic WindowMode 
Instance details

Defined in SDL.Video

Associated Types

type Rep WindowMode :: * -> * #

FromNumber WindowMode Word32 
Instance details

Defined in SDL.Video

ToNumber WindowMode Word32 
Instance details

Defined in SDL.Video

type Rep WindowMode 
Instance details

Defined in SDL.Video

type Rep WindowMode = D1 (MetaData "WindowMode" "SDL.Video" "sdl2-2.4.1.0-JfGLkN9ODDEI4y1RAyJJ9B" False) ((C1 (MetaCons "Fullscreen" PrefixI False) (U1 :: * -> *) :+: C1 (MetaCons "FullscreenDesktop" PrefixI False) (U1 :: * -> *)) :+: (C1 (MetaCons "Maximized" PrefixI False) (U1 :: * -> *) :+: (C1 (MetaCons "Minimized" PrefixI False) (U1 :: * -> *) :+: C1 (MetaCons "Windowed" PrefixI False) (U1 :: * -> *))))

data EventPayload #

An enumeration of all possible SDL event types. This data type pairs up event types with their payload, where possible.

Constructors

WindowShownEvent !WindowShownEventData 
WindowHiddenEvent !WindowHiddenEventData 
WindowExposedEvent !WindowExposedEventData 
WindowMovedEvent !WindowMovedEventData 
WindowResizedEvent !WindowResizedEventData 
WindowSizeChangedEvent !WindowSizeChangedEventData 
WindowMinimizedEvent !WindowMinimizedEventData 
WindowMaximizedEvent !WindowMaximizedEventData 
WindowRestoredEvent !WindowRestoredEventData 
WindowGainedMouseFocusEvent !WindowGainedMouseFocusEventData 
WindowLostMouseFocusEvent !WindowLostMouseFocusEventData 
WindowGainedKeyboardFocusEvent !WindowGainedKeyboardFocusEventData 
WindowLostKeyboardFocusEvent !WindowLostKeyboardFocusEventData 
WindowClosedEvent !WindowClosedEventData 
KeyboardEvent !KeyboardEventData 
TextEditingEvent !TextEditingEventData 
TextInputEvent !TextInputEventData 
KeymapChangedEvent 
MouseMotionEvent !MouseMotionEventData 
MouseButtonEvent !MouseButtonEventData 
MouseWheelEvent !MouseWheelEventData 
JoyAxisEvent !JoyAxisEventData 
JoyBallEvent !JoyBallEventData 
JoyHatEvent !JoyHatEventData 
JoyButtonEvent !JoyButtonEventData 
JoyDeviceEvent !JoyDeviceEventData 
ControllerAxisEvent !ControllerAxisEventData 
ControllerButtonEvent !ControllerButtonEventData 
ControllerDeviceEvent !ControllerDeviceEventData 
AudioDeviceEvent !AudioDeviceEventData 
QuitEvent 
UserEvent !UserEventData 
SysWMEvent !SysWMEventData 
TouchFingerEvent !TouchFingerEventData 
TouchFingerMotionEvent !TouchFingerMotionEventData 
MultiGestureEvent !MultiGestureEventData 
DollarGestureEvent !DollarGestureEventData 
DropEvent !DropEventData 
ClipboardUpdateEvent 
UnknownEvent !UnknownEventData 
Instances
Eq EventPayload 
Instance details

Defined in SDL.Event

Ord EventPayload 
Instance details

Defined in SDL.Event

Show EventPayload 
Instance details

Defined in SDL.Event

Generic EventPayload 
Instance details

Defined in SDL.Event

Associated Types

type Rep EventPayload :: * -> * #

type Rep EventPayload 
Instance details

Defined in SDL.Event

type Rep EventPayload = D1 (MetaData "EventPayload" "SDL.Event" "sdl2-2.4.1.0-JfGLkN9ODDEI4y1RAyJJ9B" False) (((((C1 (MetaCons "WindowShownEvent" PrefixI False) (S1 (MetaSel (Nothing :: Maybe Symbol) NoSourceUnpackedness SourceStrict DecidedUnpack) (Rec0 WindowShownEventData)) :+: C1 (MetaCons "WindowHiddenEvent" PrefixI False) (S1 (MetaSel (Nothing :: Maybe Symbol) NoSourceUnpackedness SourceStrict DecidedUnpack) (Rec0 WindowHiddenEventData))) :+: (C1 (MetaCons "WindowExposedEvent" PrefixI False) (S1 (MetaSel (Nothing :: Maybe Symbol) NoSourceUnpackedness SourceStrict DecidedUnpack) (Rec0 WindowExposedEventData)) :+: (C1 (MetaCons "WindowMovedEvent" PrefixI False) (S1 (MetaSel (Nothing :: Maybe Symbol) NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 WindowMovedEventData)) :+: C1 (MetaCons "WindowResizedEvent" PrefixI False) (S1 (MetaSel (Nothing :: Maybe Symbol) NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 WindowResizedEventData))))) :+: ((C1 (MetaCons "WindowSizeChangedEvent" PrefixI False) (S1 (MetaSel (Nothing :: Maybe Symbol) NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 WindowSizeChangedEventData)) :+: C1 (MetaCons "WindowMinimizedEvent" PrefixI False) (S1 (MetaSel (Nothing :: Maybe Symbol) NoSourceUnpackedness SourceStrict DecidedUnpack) (Rec0 WindowMinimizedEventData))) :+: (C1 (MetaCons "WindowMaximizedEvent" PrefixI False) (S1 (MetaSel (Nothing :: Maybe Symbol) NoSourceUnpackedness SourceStrict DecidedUnpack) (Rec0 WindowMaximizedEventData)) :+: (C1 (MetaCons "WindowRestoredEvent" PrefixI False) (S1 (MetaSel (Nothing :: Maybe Symbol) NoSourceUnpackedness SourceStrict DecidedUnpack) (Rec0 WindowRestoredEventData)) :+: C1 (MetaCons "WindowGainedMouseFocusEvent" PrefixI False) (S1 (MetaSel (Nothing :: Maybe Symbol) NoSourceUnpackedness SourceStrict DecidedUnpack) (Rec0 WindowGainedMouseFocusEventData)))))) :+: (((C1 (MetaCons "WindowLostMouseFocusEvent" PrefixI False) (S1 (MetaSel (Nothing :: Maybe Symbol) NoSourceUnpackedness SourceStrict DecidedUnpack) (Rec0 WindowLostMouseFocusEventData)) :+: C1 (MetaCons "WindowGainedKeyboardFocusEvent" PrefixI False) (S1 (MetaSel (Nothing :: Maybe Symbol) NoSourceUnpackedness SourceStrict DecidedUnpack) (Rec0 WindowGainedKeyboardFocusEventData))) :+: (C1 (MetaCons "WindowLostKeyboardFocusEvent" PrefixI False) (S1 (MetaSel (Nothing :: Maybe Symbol) NoSourceUnpackedness SourceStrict DecidedUnpack) (Rec0 WindowLostKeyboardFocusEventData)) :+: (C1 (MetaCons "WindowClosedEvent" PrefixI False) (S1 (MetaSel (Nothing :: Maybe Symbol) NoSourceUnpackedness SourceStrict DecidedUnpack) (Rec0 WindowClosedEventData)) :+: C1 (MetaCons "KeyboardEvent" PrefixI False) (S1 (MetaSel (Nothing :: Maybe Symbol) NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 KeyboardEventData))))) :+: ((C1 (MetaCons "TextEditingEvent" PrefixI False) (S1 (MetaSel (Nothing :: Maybe Symbol) NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 TextEditingEventData)) :+: C1 (MetaCons "TextInputEvent" PrefixI False) (S1 (MetaSel (Nothing :: Maybe Symbol) NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 TextInputEventData))) :+: (C1 (MetaCons "KeymapChangedEvent" PrefixI False) (U1 :: * -> *) :+: (C1 (MetaCons "MouseMotionEvent" PrefixI False) (S1 (MetaSel (Nothing :: Maybe Symbol) NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 MouseMotionEventData)) :+: C1 (MetaCons "MouseButtonEvent" PrefixI False) (S1 (MetaSel (Nothing :: Maybe Symbol) NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 MouseButtonEventData))))))) :+: ((((C1 (MetaCons "MouseWheelEvent" PrefixI False) (S1 (MetaSel (Nothing :: Maybe Symbol) NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 MouseWheelEventData)) :+: C1 (MetaCons "JoyAxisEvent" PrefixI False) (S1 (MetaSel (Nothing :: Maybe Symbol) NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 JoyAxisEventData))) :+: (C1 (MetaCons "JoyBallEvent" PrefixI False) (S1 (MetaSel (Nothing :: Maybe Symbol) NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 JoyBallEventData)) :+: (C1 (MetaCons "JoyHatEvent" PrefixI False) (S1 (MetaSel (Nothing :: Maybe Symbol) NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 JoyHatEventData)) :+: C1 (MetaCons "JoyButtonEvent" PrefixI False) (S1 (MetaSel (Nothing :: Maybe Symbol) NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 JoyButtonEventData))))) :+: ((C1 (MetaCons "JoyDeviceEvent" PrefixI False) (S1 (MetaSel (Nothing :: Maybe Symbol) NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 JoyDeviceEventData)) :+: C1 (MetaCons "ControllerAxisEvent" PrefixI False) (S1 (MetaSel (Nothing :: Maybe Symbol) NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 ControllerAxisEventData))) :+: (C1 (MetaCons "ControllerButtonEvent" PrefixI False) (S1 (MetaSel (Nothing :: Maybe Symbol) NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 ControllerButtonEventData)) :+: (C1 (MetaCons "ControllerDeviceEvent" PrefixI False) (S1 (MetaSel (Nothing :: Maybe Symbol) NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 ControllerDeviceEventData)) :+: C1 (MetaCons "AudioDeviceEvent" PrefixI False) (S1 (MetaSel (Nothing :: Maybe Symbol) NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 AudioDeviceEventData)))))) :+: (((C1 (MetaCons "QuitEvent" PrefixI False) (U1 :: * -> *) :+: C1 (MetaCons "UserEvent" PrefixI False) (S1 (MetaSel (Nothing :: Maybe Symbol) NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 UserEventData))) :+: (C1 (MetaCons "SysWMEvent" PrefixI False) (S1 (MetaSel (Nothing :: Maybe Symbol) NoSourceUnpackedness SourceStrict DecidedUnpack) (Rec0 SysWMEventData)) :+: (C1 (MetaCons "TouchFingerEvent" PrefixI False) (S1 (MetaSel (Nothing :: Maybe Symbol) NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 TouchFingerEventData)) :+: C1 (MetaCons "TouchFingerMotionEvent" PrefixI False) (S1 (MetaSel (Nothing :: Maybe Symbol) NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 TouchFingerMotionEventData))))) :+: ((C1 (MetaCons "MultiGestureEvent" PrefixI False) (S1 (MetaSel (Nothing :: Maybe Symbol) NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 MultiGestureEventData)) :+: C1 (MetaCons "DollarGestureEvent" PrefixI False) (S1 (MetaSel (Nothing :: Maybe Symbol) NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 DollarGestureEventData))) :+: (C1 (MetaCons "DropEvent" PrefixI False) (S1 (MetaSel (Nothing :: Maybe Symbol) NoSourceUnpackedness SourceStrict DecidedUnpack) (Rec0 DropEventData)) :+: (C1 (MetaCons "ClipboardUpdateEvent" PrefixI False) (U1 :: * -> *) :+: C1 (MetaCons "UnknownEvent" PrefixI False) (S1 (MetaSel (Nothing :: Maybe Symbol) NoSourceUnpackedness SourceStrict DecidedUnpack) (Rec0 UnknownEventData))))))))

data InitFlag #

Instances
Bounded InitFlag 
Instance details

Defined in SDL.Init

Enum InitFlag 
Instance details

Defined in SDL.Init

Eq InitFlag 
Instance details

Defined in SDL.Init

Data InitFlag 
Instance details

Defined in SDL.Init

Methods

gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> InitFlag -> c InitFlag #

gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c InitFlag #

toConstr :: InitFlag -> Constr #

dataTypeOf :: InitFlag -> DataType #

dataCast1 :: Typeable t => (forall d. Data d => c (t d)) -> Maybe (c InitFlag) #

dataCast2 :: Typeable t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c InitFlag) #

gmapT :: (forall b. Data b => b -> b) -> InitFlag -> InitFlag #

gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> InitFlag -> r #

gmapQr :: (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> InitFlag -> r #

gmapQ :: (forall d. Data d => d -> u) -> InitFlag -> [u] #

gmapQi :: Int -> (forall d. Data d => d -> u) -> InitFlag -> u #

gmapM :: Monad m => (forall d. Data d => d -> m d) -> InitFlag -> m InitFlag #

gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> InitFlag -> m InitFlag #

gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> InitFlag -> m InitFlag #

Ord InitFlag 
Instance details

Defined in SDL.Init

Read InitFlag 
Instance details

Defined in SDL.Init

Show InitFlag 
Instance details

Defined in SDL.Init

Generic InitFlag 
Instance details

Defined in SDL.Init

Associated Types

type Rep InitFlag :: * -> * #

Methods

from :: InitFlag -> Rep InitFlag x #

to :: Rep InitFlag x -> InitFlag #

ToNumber InitFlag Word32 
Instance details

Defined in SDL.Init

Methods

toNumber :: InitFlag -> Word32 #

type Rep InitFlag 
Instance details

Defined in SDL.Init

type Rep InitFlag = D1 (MetaData "InitFlag" "SDL.Init" "sdl2-2.4.1.0-JfGLkN9ODDEI4y1RAyJJ9B" False) ((C1 (MetaCons "InitTimer" PrefixI False) (U1 :: * -> *) :+: (C1 (MetaCons "InitAudio" PrefixI False) (U1 :: * -> *) :+: C1 (MetaCons "InitVideo" PrefixI False) (U1 :: * -> *))) :+: ((C1 (MetaCons "InitJoystick" PrefixI False) (U1 :: * -> *) :+: C1 (MetaCons "InitHaptic" PrefixI False) (U1 :: * -> *)) :+: (C1 (MetaCons "InitGameController" PrefixI False) (U1 :: * -> *) :+: C1 (MetaCons "InitEvents" PrefixI False) (U1 :: * -> *))))

data Window #

Instances
Eq Window 
Instance details

Defined in SDL.Internal.Types

Methods

(==) :: Window -> Window -> Bool #

(/=) :: Window -> Window -> Bool #

Data Window 
Instance details

Defined in SDL.Internal.Types

Methods

gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> Window -> c Window #

gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c Window #

toConstr :: Window -> Constr #

dataTypeOf :: Window -> DataType #

dataCast1 :: Typeable t => (forall d. Data d => c (t d)) -> Maybe (c Window) #

dataCast2 :: Typeable t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c Window) #

gmapT :: (forall b. Data b => b -> b) -> Window -> Window #

gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> Window -> r #

gmapQr :: (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> Window -> r #

gmapQ :: (forall d. Data d => d -> u) -> Window -> [u] #

gmapQi :: Int -> (forall d. Data d => d -> u) -> Window -> u #

gmapM :: Monad m => (forall d. Data d => d -> m d) -> Window -> m Window #

gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> Window -> m Window #

gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> Window -> m Window #

Ord Window 
Instance details

Defined in SDL.Internal.Types

Show Window 
Instance details

Defined in SDL.Internal.Types

Generic Window 
Instance details

Defined in SDL.Internal.Types

Associated Types

type Rep Window :: * -> * #

Methods

from :: Window -> Rep Window x #

to :: Rep Window x -> Window #

type Rep Window 
Instance details

Defined in SDL.Internal.Types

type Rep Window = D1 (MetaData "Window" "SDL.Internal.Types" "sdl2-2.4.1.0-JfGLkN9ODDEI4y1RAyJJ9B" True) (C1 (MetaCons "Window" PrefixI False) (S1 (MetaSel (Nothing :: Maybe Symbol) NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 Window)))

data GLContext #

A created OpenGL context.

Instances
Eq GLContext 
Instance details

Defined in SDL.Video.OpenGL