Safe Haskell | None |
---|---|
Language | Haskell2010 |
Synopsis
- type Affection us a = AffectionState (AffectionData us) IO a
- 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 AffectionData us = AffectionData {
- quitEvent :: Bool
- userState :: us
- drawWindow :: Window
- glContext :: GLContext
- screenMode :: WindowMode
- drawDimensions :: (Int, 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
- data InitComponents
- type Angle = Double
- data WindowConfig = WindowConfig {}
- data WindowMode
- data EventPayload
- = 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
- data InitFlag
- data Window
- data GLContext
Documentation
type Affection us a = AffectionState (AffectionData us) IO a Source #
data AffectionConfig us Source #
Configuration for the aplication. needed at startup.
AffectionConfig | |
|
data AffectionData us Source #
Main type for defining the look, feel and action of the whole application.
AffectionData | |
|
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
AffectionState | |
|
Instances
SDL reexports
data WindowConfig #
WindowConfig | |
|
Instances
data WindowMode #
Fullscreen | Real fullscreen with a video mode change |
FullscreenDesktop | Fake fullscreen that takes the size of the desktop |
Maximized | |
Minimized | |
Windowed |
Instances
data EventPayload #
An enumeration of all possible SDL event types. This data type pairs up event types with their payload, where possible.
Instances
Instances
Bounded InitFlag | |
Enum InitFlag | |
Eq InitFlag | |
Data InitFlag | |
Defined in SDL.Init 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 | |
Read InitFlag | |
Show InitFlag | |
Generic InitFlag | |
ToNumber InitFlag Word32 | |
type Rep InitFlag | |
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 :: * -> *)))) |
Instances
Eq Window | |
Data Window | |
Defined in SDL.Internal.Types 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 | |
Show Window | |
Generic Window | |
type Rep Window | |
Defined in SDL.Internal.Types |