gore-and-ash-sdl-2.1.1.0: Gore&Ash core module for integration with SDL library

Copyright(c) Anton Gushcha, 2015-2016
LicenseBSD3
Maintainerncrashed@gmail.com
Stabilityexperimental
PortabilityPOSIX
Safe HaskellNone
LanguageHaskell2010

Game.GoreAndAsh.SDL

Contents

Description

The core module contains API for SDL2 library integration. The module doesn't depends on others core modules and could be place in any place in game monad stack.

The module is NOT pure within first phase (see ModuleStack docs), therefore currently only IO end monad can handler the module.

Example of embedding:

-- | Application monad is monad stack build from given list of modules over base monad (IO)
type AppStack = ModuleStack [SDLT, ... other modules ... ] IO
newtype AppState = AppState (ModuleState AppStack)
  deriving (Generic)

instance NFData AppState 

-- | Wrapper around type family
newtype AppMonad a = AppMonad (AppStack a)
  deriving (Functor, Applicative, Monad, MonadFix, MonadIO, MonadThrow, MonadCatch, MonadSDL, ... other modules monads ... )
  
instance GameModule AppMonad AppState where 
  type ModuleState AppMonad = AppState
  runModule (AppMonad m) (AppState s) = do 
    (a, s') <- runModule m s 
    return (a, AppState s')
  newModuleState = AppState $ newModuleState
  withModule _ = withModule (Proxy :: Proxy AppStack)
  cleanupModule (AppState s) = cleanupModule s 

-- | Arrow that is build over the monad stack
type AppWire a b = GameWire AppMonad a b
-- | Action that makes indexed app wire
type AppActor i a b = GameActor AppMonad i a b

Synopsis

Low level API

data SDLState s Source #

Inner state of SDL module.

s
- State of next module, the states are chained via nesting.

Instances

Generic (SDLState s) Source # 

Associated Types

type Rep (SDLState s) :: * -> * #

Methods

from :: SDLState s -> Rep (SDLState s) x #

to :: Rep (SDLState s) x -> SDLState s #

NFData s => NFData (SDLState s) Source # 

Methods

rnf :: SDLState s -> () #

Monad m => MonadState (SDLState s) (SDLT s m) 

Methods

get :: SDLT s m (SDLState s)

put :: SDLState s -> SDLT s m ()

state :: (SDLState s -> (a, SDLState s)) -> SDLT s m a

type Rep (SDLState s) Source # 
type Rep (SDLState s) = D1 (MetaData "SDLState" "Game.GoreAndAsh.SDL.State" "gore-and-ash-sdl-2.1.1.0-KphxcxP57zE2taVj4mp3mt" False) (C1 (MetaCons "SDLState" PrefixI True) ((:*:) ((:*:) ((:*:) ((:*:) ((:*:) (S1 (MetaSel (Just Symbol "sdlNextState") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 s)) (S1 (MetaSel (Just Symbol "sdlWindows") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 (HashMap WindowName WindowInfo)))) ((:*:) (S1 (MetaSel (Just Symbol "sdlWindowShownEvents") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 (Seq WindowShownEventData))) (S1 (MetaSel (Just Symbol "sdlWindowHiddenEvents") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 (Seq WindowHiddenEventData))))) ((:*:) ((:*:) (S1 (MetaSel (Just Symbol "sdlWindowExposedEvents") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 (Seq WindowExposedEventData))) (S1 (MetaSel (Just Symbol "sdlWindowMovedEvents") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 (Seq WindowMovedEventData)))) ((:*:) (S1 (MetaSel (Just Symbol "sdlWindowResizedEvents") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 (Seq WindowResizedEventData))) ((:*:) (S1 (MetaSel (Just Symbol "sdlWindowSizeChangedEvents") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 (Seq WindowSizeChangedEventData))) (S1 (MetaSel (Just Symbol "sdlWindowMinimizedEvents") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 (Seq WindowMinimizedEventData))))))) ((:*:) ((:*:) ((:*:) (S1 (MetaSel (Just Symbol "sdlWindowMaximizedEvents") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 (Seq WindowMaximizedEventData))) (S1 (MetaSel (Just Symbol "sdlWindowRestoredEvents") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 (Seq WindowRestoredEventData)))) ((:*:) (S1 (MetaSel (Just Symbol "sdlWindowGainedMouseFocusEvents") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 (Seq WindowGainedMouseFocusEventData))) ((:*:) (S1 (MetaSel (Just Symbol "sdlWindowLostMouseFocusEvents") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 (Seq WindowLostMouseFocusEventData))) (S1 (MetaSel (Just Symbol "sdlWindowGainedKeyboardFocusEvents") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 (Seq WindowGainedKeyboardFocusEventData)))))) ((:*:) ((:*:) (S1 (MetaSel (Just Symbol "sdlWindowLostKeyboardFocusEvents") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 (Seq WindowLostKeyboardFocusEventData))) (S1 (MetaSel (Just Symbol "sdlWindowClosedEvents") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 (Seq WindowClosedEventData)))) ((:*:) (S1 (MetaSel (Just Symbol "sdlKeyboardEvents") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 (Seq KeyboardEventData))) ((:*:) (S1 (MetaSel (Just Symbol "sdlTextEditingEvents") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 (Seq TextEditingEventData))) (S1 (MetaSel (Just Symbol "sdlTextInputEvents") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 (Seq TextInputEventData)))))))) ((:*:) ((:*:) ((:*:) ((:*:) (S1 (MetaSel (Just Symbol "sdlMouseMotionEvents") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 (Seq MouseMotionEventData))) (S1 (MetaSel (Just Symbol "sdlMouseButtonEvents") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 (Seq MouseButtonEventData)))) ((:*:) (S1 (MetaSel (Just Symbol "sdlMouseWheelEvents") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 (Seq MouseWheelEventData))) (S1 (MetaSel (Just Symbol "sdlJoyAxisEvents") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 (Seq JoyAxisEventData))))) ((:*:) ((:*:) (S1 (MetaSel (Just Symbol "sdlJoyBallEvents") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 (Seq JoyBallEventData))) (S1 (MetaSel (Just Symbol "sdlJoyHatEvents") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 (Seq JoyHatEventData)))) ((:*:) (S1 (MetaSel (Just Symbol "sdlJoyButtonEvents") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 (Seq JoyButtonEventData))) ((:*:) (S1 (MetaSel (Just Symbol "sdlJoyDeviceEvents") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 (Seq JoyDeviceEventData))) (S1 (MetaSel (Just Symbol "sdlControllerAxisEvents") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 (Seq ControllerAxisEventData))))))) ((:*:) ((:*:) ((:*:) (S1 (MetaSel (Just Symbol "sdlControllerButtonEvents") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 (Seq ControllerButtonEventData))) (S1 (MetaSel (Just Symbol "sdlControllerDeviceEvents") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 (Seq ControllerDeviceEventData)))) ((:*:) (S1 (MetaSel (Just Symbol "sdlQuitEvent") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 Bool)) ((:*:) (S1 (MetaSel (Just Symbol "sdlUserEvents") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 (Seq UserEventData))) (S1 (MetaSel (Just Symbol "sdlSysWMEvents") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 (Seq SysWMEventData)))))) ((:*:) ((:*:) (S1 (MetaSel (Just Symbol "sdlTouchFingerEvents") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 (Seq TouchFingerEventData))) (S1 (MetaSel (Just Symbol "sdlMultiGestureEvents") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 (Seq MultiGestureEventData)))) ((:*:) (S1 (MetaSel (Just Symbol "sdlDollarGestureEvents") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 (Seq DollarGestureEventData))) ((:*:) (S1 (MetaSel (Just Symbol "sdlDropEvents") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 (Seq DropEventData))) (S1 (MetaSel (Just Symbol "sdlClipboardUpdateEvents") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 (Seq ClipboardUpdateEventData))))))))))

data SDLT s m a Source #

Monad transformer of SDL core module.

s
- State of next core module in modules chain;
m
- Next monad in modules monad stack;
a
- Type of result value;

How to embed module:

type AppStack = ModuleStack [SDLT, ... other modules ... ] IO

newtype AppMonad a = AppMonad (AppStack a)
  deriving (Functor, Applicative, Monad, MonadFix, MonadIO, MonadThrow, MonadCatch, MonadSDL)

The module is NOT pure within first phase (see ModuleStack docs), therefore currently only IO end monad can handler the module.

Instances

MonadBase IO m => MonadBase IO (SDLT s m) Source # 

Methods

liftBase :: IO α -> SDLT s m α

MonadError e m => MonadError e (SDLT s m) Source # 

Methods

throwError :: e -> SDLT s m a

catchError :: SDLT s m a -> (e -> SDLT s m a) -> SDLT s m a

MonadTrans (SDLT s) Source # 

Methods

lift :: Monad m => m a -> SDLT s m a #

Monad m => MonadState (SDLState s) (SDLT s m) Source # 

Methods

get :: SDLT s m (SDLState s)

put :: SDLState s -> SDLT s m ()

state :: (SDLState s -> (a, SDLState s)) -> SDLT s m a

Monad m => Monad (SDLT s m) Source # 

Methods

(>>=) :: SDLT s m a -> (a -> SDLT s m b) -> SDLT s m b #

(>>) :: SDLT s m a -> SDLT s m b -> SDLT s m b #

return :: a -> SDLT s m a #

fail :: String -> SDLT s m a #

Functor m => Functor (SDLT s m) Source # 

Methods

fmap :: (a -> b) -> SDLT s m a -> SDLT s m b #

(<$) :: a -> SDLT s m b -> SDLT s m a #

MonadFix m => MonadFix (SDLT s m) Source # 

Methods

mfix :: (a -> SDLT s m a) -> SDLT s m a #

Monad m => Applicative (SDLT s m) Source # 

Methods

pure :: a -> SDLT s m a #

(<*>) :: SDLT s m (a -> b) -> SDLT s m a -> SDLT s m b #

(*>) :: SDLT s m a -> SDLT s m b -> SDLT s m b #

(<*) :: SDLT s m a -> SDLT s m b -> SDLT s m a #

MonadIO m => MonadIO (SDLT s m) Source # 

Methods

liftIO :: IO a -> SDLT s m a #

MonadThrow m => MonadThrow (SDLT s m) Source # 

Methods

throwM :: Exception e => e -> SDLT s m a

MonadMask m => MonadMask (SDLT s m) Source # 

Methods

mask :: ((forall a. SDLT s m a -> SDLT s m a) -> SDLT s m b) -> SDLT s m b

uninterruptibleMask :: ((forall a. SDLT s m a -> SDLT s m a) -> SDLT s m b) -> SDLT s m b

MonadCatch m => MonadCatch (SDLT s m) Source # 

Methods

catch :: Exception e => SDLT s m a -> (e -> SDLT s m a) -> SDLT s m a

MonadResource m => MonadResource (SDLT s m) Source # 

Methods

liftResourceT :: ResourceT IO a -> SDLT s m a

(MonadIO m, MonadThrow m) => MonadSDL (SDLT s m) Source # 

Methods

sdlCreateWindowM :: WindowName -> Text -> WindowConfig -> RendererConfig -> SDLT s m (Window, Renderer) Source #

sdlGetWindowM :: WindowName -> SDLT s m (Maybe (Window, Renderer)) Source #

sdlDestroyWindowM :: WindowName -> SDLT s m () Source #

sdlSetBackColor :: WindowName -> Maybe (V4 Word8) -> SDLT s m () Source #

sdlCreateContext :: WindowName -> SDLT s m () Source #

sdlMakeCurrent :: WindowName -> SDLT s m () Source #

sdlWindowShownEventsM :: SDLT s m (Seq WindowShownEventData) Source #

sdlWindowHiddenEventsM :: SDLT s m (Seq WindowHiddenEventData) Source #

sdlWindowExposedEventsM :: SDLT s m (Seq WindowExposedEventData) Source #

sdlWindowMovedEventsM :: SDLT s m (Seq WindowMovedEventData) Source #

sdlWindowResizedEventsM :: SDLT s m (Seq WindowResizedEventData) Source #

sdlWindowSizeChangedEventsM :: SDLT s m (Seq WindowSizeChangedEventData) Source #

sdlWindowMinimizedEventsM :: SDLT s m (Seq WindowMinimizedEventData) Source #

sdlWindowMaximizedEventsM :: SDLT s m (Seq WindowMaximizedEventData) Source #

sdlWindowRestoredEventsM :: SDLT s m (Seq WindowRestoredEventData) Source #

sdlWindowGainedMouseFocusEventsM :: SDLT s m (Seq WindowGainedMouseFocusEventData) Source #

sdlWindowLostMouseFocusEventsM :: SDLT s m (Seq WindowLostMouseFocusEventData) Source #

sdlWindowGainedKeyboardFocusEventsM :: SDLT s m (Seq WindowGainedKeyboardFocusEventData) Source #

sdlWindowLostKeyboardFocusEventsM :: SDLT s m (Seq WindowLostKeyboardFocusEventData) Source #

sdlWindowClosedEventsM :: SDLT s m (Seq WindowClosedEventData) Source #

sdlKeyboardEventsM :: SDLT s m (Seq KeyboardEventData) Source #

sdlTextEditingEventsM :: SDLT s m (Seq TextEditingEventData) Source #

sdlTextInputEventsM :: SDLT s m (Seq TextInputEventData) Source #

sdlMouseMotionEventsM :: SDLT s m (Seq MouseMotionEventData) Source #

sdlMouseButtonEventsM :: SDLT s m (Seq MouseButtonEventData) Source #

sdlMouseWheelEventsM :: SDLT s m (Seq MouseWheelEventData) Source #

sdlJoyAxisEventsM :: SDLT s m (Seq JoyAxisEventData) Source #

sdlJoyBallEventsM :: SDLT s m (Seq JoyBallEventData) Source #

sdlJoyHatEventsM :: SDLT s m (Seq JoyHatEventData) Source #

sdlJoyButtonEventsM :: SDLT s m (Seq JoyButtonEventData) Source #

sdlJoyDeviceEventsM :: SDLT s m (Seq JoyDeviceEventData) Source #

sdlControllerAxisEventsM :: SDLT s m (Seq ControllerAxisEventData) Source #

sdlControllerButtonEventsM :: SDLT s m (Seq ControllerButtonEventData) Source #

sdlControllerDeviceEventsM :: SDLT s m (Seq ControllerDeviceEventData) Source #

sdlQuitEventM :: SDLT s m Bool Source #

sdlUserEventsM :: SDLT s m (Seq UserEventData) Source #

sdlSysWMEventsM :: SDLT s m (Seq SysWMEventData) Source #

sdlTouchFingerEventsM :: SDLT s m (Seq TouchFingerEventData) Source #

sdlMultiGestureEventsM :: SDLT s m (Seq MultiGestureEventData) Source #

sdlDollarGestureEventsM :: SDLT s m (Seq DollarGestureEventData) Source #

sdlDropEventsM :: SDLT s m (Seq DropEventData) Source #

sdlClipboardUpdateEventsM :: SDLT s m (Seq ClipboardUpdateEventData) Source #

type ModuleState (SDLT s m) Source # 
type ModuleState (SDLT s m) = SDLState s

class (MonadIO m, MonadThrow m) => MonadSDL m where Source #

Low level API for module

Methods

sdlCreateWindowM :: WindowName -> Text -> WindowConfig -> RendererConfig -> m (Window, Renderer) Source #

Creates window and stores in module context

Throws SDL'ConflictingWindows on name conflict

sdlGetWindowM :: WindowName -> m (Maybe (Window, Renderer)) Source #

Getting window and renderer by name

sdlDestroyWindowM :: WindowName -> m () Source #

Destroying window and renderer by name

sdlSetBackColor :: WindowName -> Maybe (V4 Word8) -> m () Source #

Setup background color for window

sdlCreateContext :: WindowName -> m () Source #

Creates context for given window

Note: destroys previous context if existed

sdlMakeCurrent :: WindowName -> m () Source #

Makes GL context of given window current

Does nothing if sdlCreateContext wasn't called.

sdlWindowShownEventsM :: m (Seq WindowShownEventData) Source #

Getting window shown events that occurs scince last frame

sdlWindowHiddenEventsM :: m (Seq WindowHiddenEventData) Source #

Getting window hidden events that occurs scince last frame

sdlWindowExposedEventsM :: m (Seq WindowExposedEventData) Source #

Getting window exposed events that occurs scince last frame

sdlWindowMovedEventsM :: m (Seq WindowMovedEventData) Source #

Getting window move events that occurs scince last frame

sdlWindowResizedEventsM :: m (Seq WindowResizedEventData) Source #

Getting window resize events that occurs scince last frame

This is event is always preceded by WindowSizeChangedEvent.

sdlWindowSizeChangedEventsM :: m (Seq WindowSizeChangedEventData) Source #

Getting window resize events that occurs scince last frame

The window size has changed, either as a result of an API call or through the system or user changing the window size; this event is followed by WindowResizedEvent if the size was changed by an external event, i.e. the user or the window manager.

sdlWindowMinimizedEventsM :: m (Seq WindowMinimizedEventData) Source #

Getting window minimization events that occurs scince last frame

sdlWindowMaximizedEventsM :: m (Seq WindowMaximizedEventData) Source #

Getting window maximization events that occurs scince last frame

sdlWindowRestoredEventsM :: m (Seq WindowRestoredEventData) Source #

Getting window restore events that occurs scince last frame

sdlWindowGainedMouseFocusEventsM :: m (Seq WindowGainedMouseFocusEventData) Source #

Getting window focus events that occurs scince last frame

sdlWindowLostMouseFocusEventsM :: m (Seq WindowLostMouseFocusEventData) Source #

Getting window focus events that occurs scince last frame

sdlWindowGainedKeyboardFocusEventsM :: m (Seq WindowGainedKeyboardFocusEventData) Source #

Getting window focus events that occurs scince last frame

sdlWindowLostKeyboardFocusEventsM :: m (Seq WindowLostKeyboardFocusEventData) Source #

Getting window focus events that occurs scince last frame

sdlWindowClosedEventsM :: m (Seq WindowClosedEventData) Source #

Getting window close events that occurs scince last frame

sdlKeyboardEventsM :: m (Seq KeyboardEventData) Source #

Getting keyboard events that occurs scince last frame

sdlTextEditingEventsM :: m (Seq TextEditingEventData) Source #

Getting input API events that occurs scince last frame

sdlTextInputEventsM :: m (Seq TextInputEventData) Source #

Getting input API events that occurs scince last frame

sdlMouseMotionEventsM :: m (Seq MouseMotionEventData) Source #

Getting mouse events that occurs scince last frame

sdlMouseButtonEventsM :: m (Seq MouseButtonEventData) Source #

Getting mouse events that occurs scince last frame

sdlMouseWheelEventsM :: m (Seq MouseWheelEventData) Source #

Getting mouse events that occurs scince last frame

sdlJoyAxisEventsM :: m (Seq JoyAxisEventData) Source #

Getting joystick events that occurs scince last frame

sdlJoyBallEventsM :: m (Seq JoyBallEventData) Source #

Getting joystick events that occurs scince last frame

sdlJoyHatEventsM :: m (Seq JoyHatEventData) Source #

Getting joystick events that occurs scince last frame

sdlJoyButtonEventsM :: m (Seq JoyButtonEventData) Source #

Getting joystick events that occurs scince last frame

sdlJoyDeviceEventsM :: m (Seq JoyDeviceEventData) Source #

Getting joystick events that occurs scince last frame

sdlControllerAxisEventsM :: m (Seq ControllerAxisEventData) Source #

Getting controller events that occurs scince last frame

sdlControllerButtonEventsM :: m (Seq ControllerButtonEventData) Source #

Getting controller events that occurs scince last frame

sdlControllerDeviceEventsM :: m (Seq ControllerDeviceEventData) Source #

Getting controller events that occurs scince last frame

sdlQuitEventM :: m Bool Source #

Getting quit request event

sdlUserEventsM :: m (Seq UserEventData) Source #

Getting user events that occurs scince last frame

sdlSysWMEventsM :: m (Seq SysWMEventData) Source #

Getting video driver specific events that occurs scince last frame

sdlTouchFingerEventsM :: m (Seq TouchFingerEventData) Source #

Getting touch events that occurs scince last frame

sdlMultiGestureEventsM :: m (Seq MultiGestureEventData) Source #

Getting touch events that occurs scince last frame

sdlDollarGestureEventsM :: m (Seq DollarGestureEventData) Source #

Getting touch events that occurs scince last frame

sdlDropEventsM :: m (Seq DropEventData) Source #

Getting file opened events that occurs scince last frame

sdlClipboardUpdateEventsM :: m (Seq ClipboardUpdateEventData) Source #

Getting clipboard changed events that occurs scince last frame

Instances

(MonadIO (mt m), MonadThrow (mt m), MonadSDL m, MonadTrans mt) => MonadSDL (mt m) Source # 

Methods

sdlCreateWindowM :: WindowName -> Text -> WindowConfig -> RendererConfig -> mt m (Window, Renderer) Source #

sdlGetWindowM :: WindowName -> mt m (Maybe (Window, Renderer)) Source #

sdlDestroyWindowM :: WindowName -> mt m () Source #

sdlSetBackColor :: WindowName -> Maybe (V4 Word8) -> mt m () Source #

sdlCreateContext :: WindowName -> mt m () Source #

sdlMakeCurrent :: WindowName -> mt m () Source #

sdlWindowShownEventsM :: mt m (Seq WindowShownEventData) Source #

sdlWindowHiddenEventsM :: mt m (Seq WindowHiddenEventData) Source #

sdlWindowExposedEventsM :: mt m (Seq WindowExposedEventData) Source #

sdlWindowMovedEventsM :: mt m (Seq WindowMovedEventData) Source #

sdlWindowResizedEventsM :: mt m (Seq WindowResizedEventData) Source #

sdlWindowSizeChangedEventsM :: mt m (Seq WindowSizeChangedEventData) Source #

sdlWindowMinimizedEventsM :: mt m (Seq WindowMinimizedEventData) Source #

sdlWindowMaximizedEventsM :: mt m (Seq WindowMaximizedEventData) Source #

sdlWindowRestoredEventsM :: mt m (Seq WindowRestoredEventData) Source #

sdlWindowGainedMouseFocusEventsM :: mt m (Seq WindowGainedMouseFocusEventData) Source #

sdlWindowLostMouseFocusEventsM :: mt m (Seq WindowLostMouseFocusEventData) Source #

sdlWindowGainedKeyboardFocusEventsM :: mt m (Seq WindowGainedKeyboardFocusEventData) Source #

sdlWindowLostKeyboardFocusEventsM :: mt m (Seq WindowLostKeyboardFocusEventData) Source #

sdlWindowClosedEventsM :: mt m (Seq WindowClosedEventData) Source #

sdlKeyboardEventsM :: mt m (Seq KeyboardEventData) Source #

sdlTextEditingEventsM :: mt m (Seq TextEditingEventData) Source #

sdlTextInputEventsM :: mt m (Seq TextInputEventData) Source #

sdlMouseMotionEventsM :: mt m (Seq MouseMotionEventData) Source #

sdlMouseButtonEventsM :: mt m (Seq MouseButtonEventData) Source #

sdlMouseWheelEventsM :: mt m (Seq MouseWheelEventData) Source #

sdlJoyAxisEventsM :: mt m (Seq JoyAxisEventData) Source #

sdlJoyBallEventsM :: mt m (Seq JoyBallEventData) Source #

sdlJoyHatEventsM :: mt m (Seq JoyHatEventData) Source #

sdlJoyButtonEventsM :: mt m (Seq JoyButtonEventData) Source #

sdlJoyDeviceEventsM :: mt m (Seq JoyDeviceEventData) Source #

sdlControllerAxisEventsM :: mt m (Seq ControllerAxisEventData) Source #

sdlControllerButtonEventsM :: mt m (Seq ControllerButtonEventData) Source #

sdlControllerDeviceEventsM :: mt m (Seq ControllerDeviceEventData) Source #

sdlQuitEventM :: mt m Bool Source #

sdlUserEventsM :: mt m (Seq UserEventData) Source #

sdlSysWMEventsM :: mt m (Seq SysWMEventData) Source #

sdlTouchFingerEventsM :: mt m (Seq TouchFingerEventData) Source #

sdlMultiGestureEventsM :: mt m (Seq MultiGestureEventData) Source #

sdlDollarGestureEventsM :: mt m (Seq DollarGestureEventData) Source #

sdlDropEventsM :: mt m (Seq DropEventData) Source #

sdlClipboardUpdateEventsM :: mt m (Seq ClipboardUpdateEventData) Source #

(MonadIO m, MonadThrow m) => MonadSDL (SDLT s m) Source # 

Methods

sdlCreateWindowM :: WindowName -> Text -> WindowConfig -> RendererConfig -> SDLT s m (Window, Renderer) Source #

sdlGetWindowM :: WindowName -> SDLT s m (Maybe (Window, Renderer)) Source #

sdlDestroyWindowM :: WindowName -> SDLT s m () Source #

sdlSetBackColor :: WindowName -> Maybe (V4 Word8) -> SDLT s m () Source #

sdlCreateContext :: WindowName -> SDLT s m () Source #

sdlMakeCurrent :: WindowName -> SDLT s m () Source #

sdlWindowShownEventsM :: SDLT s m (Seq WindowShownEventData) Source #

sdlWindowHiddenEventsM :: SDLT s m (Seq WindowHiddenEventData) Source #

sdlWindowExposedEventsM :: SDLT s m (Seq WindowExposedEventData) Source #

sdlWindowMovedEventsM :: SDLT s m (Seq WindowMovedEventData) Source #

sdlWindowResizedEventsM :: SDLT s m (Seq WindowResizedEventData) Source #

sdlWindowSizeChangedEventsM :: SDLT s m (Seq WindowSizeChangedEventData) Source #

sdlWindowMinimizedEventsM :: SDLT s m (Seq WindowMinimizedEventData) Source #

sdlWindowMaximizedEventsM :: SDLT s m (Seq WindowMaximizedEventData) Source #

sdlWindowRestoredEventsM :: SDLT s m (Seq WindowRestoredEventData) Source #

sdlWindowGainedMouseFocusEventsM :: SDLT s m (Seq WindowGainedMouseFocusEventData) Source #

sdlWindowLostMouseFocusEventsM :: SDLT s m (Seq WindowLostMouseFocusEventData) Source #

sdlWindowGainedKeyboardFocusEventsM :: SDLT s m (Seq WindowGainedKeyboardFocusEventData) Source #

sdlWindowLostKeyboardFocusEventsM :: SDLT s m (Seq WindowLostKeyboardFocusEventData) Source #

sdlWindowClosedEventsM :: SDLT s m (Seq WindowClosedEventData) Source #

sdlKeyboardEventsM :: SDLT s m (Seq KeyboardEventData) Source #

sdlTextEditingEventsM :: SDLT s m (Seq TextEditingEventData) Source #

sdlTextInputEventsM :: SDLT s m (Seq TextInputEventData) Source #

sdlMouseMotionEventsM :: SDLT s m (Seq MouseMotionEventData) Source #

sdlMouseButtonEventsM :: SDLT s m (Seq MouseButtonEventData) Source #

sdlMouseWheelEventsM :: SDLT s m (Seq MouseWheelEventData) Source #

sdlJoyAxisEventsM :: SDLT s m (Seq JoyAxisEventData) Source #

sdlJoyBallEventsM :: SDLT s m (Seq JoyBallEventData) Source #

sdlJoyHatEventsM :: SDLT s m (Seq JoyHatEventData) Source #

sdlJoyButtonEventsM :: SDLT s m (Seq JoyButtonEventData) Source #

sdlJoyDeviceEventsM :: SDLT s m (Seq JoyDeviceEventData) Source #

sdlControllerAxisEventsM :: SDLT s m (Seq ControllerAxisEventData) Source #

sdlControllerButtonEventsM :: SDLT s m (Seq ControllerButtonEventData) Source #

sdlControllerDeviceEventsM :: SDLT s m (Seq ControllerDeviceEventData) Source #

sdlQuitEventM :: SDLT s m Bool Source #

sdlUserEventsM :: SDLT s m (Seq UserEventData) Source #

sdlSysWMEventsM :: SDLT s m (Seq SysWMEventData) Source #

sdlTouchFingerEventsM :: SDLT s m (Seq TouchFingerEventData) Source #

sdlMultiGestureEventsM :: SDLT s m (Seq MultiGestureEventData) Source #

sdlDollarGestureEventsM :: SDLT s m (Seq DollarGestureEventData) Source #

sdlDropEventsM :: SDLT s m (Seq DropEventData) Source #

sdlClipboardUpdateEventsM :: SDLT s m (Seq ClipboardUpdateEventData) Source #

Arrow API

data WindowConfig :: * #

Constructors

WindowConfig 

Fields

Instances

Eq WindowConfig 
Ord WindowConfig 
Read WindowConfig 
Show WindowConfig 
Generic WindowConfig 

Associated Types

type Rep WindowConfig :: * -> * #

type Rep WindowConfig 

data RendererConfig :: * #

Instances

Eq RendererConfig 
Data RendererConfig 

Methods

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

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

toConstr :: RendererConfig -> Constr #

dataTypeOf :: RendererConfig -> DataType #

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

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

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

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

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

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

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

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

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

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

Ord RendererConfig 
Read RendererConfig 
Show RendererConfig 
Generic RendererConfig 

Associated Types

type Rep RendererConfig :: * -> * #

ToNumber RendererConfig Word32 
FromNumber RendererConfig Word32 
type Rep RendererConfig 
type Rep RendererConfig = D1 (MetaData "RendererConfig" "SDL.Video.Renderer" "sdl2-2.1.3-DowE7uPk79X5oshOMg5tVk" False) (C1 (MetaCons "RendererConfig" PrefixI True) ((:*:) (S1 (MetaSel (Just Symbol "rendererType") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 RendererType)) (S1 (MetaSel (Just Symbol "rendererTargetTexture") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 Bool))))

data RendererType :: * #

Instances

Bounded RendererType 
Enum RendererType 
Eq RendererType 
Data RendererType 

Methods

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

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

toConstr :: RendererType -> Constr #

dataTypeOf :: RendererType -> DataType #

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

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

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

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

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

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

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

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

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

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

Ord RendererType 
Read RendererType 
Show RendererType 
Generic RendererType 

Associated Types

type Rep RendererType :: * -> * #

type Rep RendererType 
type Rep RendererType = D1 (MetaData "RendererType" "SDL.Video.Renderer" "sdl2-2.1.3-DowE7uPk79X5oshOMg5tVk" False) ((:+:) ((:+:) (C1 (MetaCons "UnacceleratedRenderer" PrefixI False) U1) (C1 (MetaCons "AcceleratedRenderer" PrefixI False) U1)) ((:+:) (C1 (MetaCons "AcceleratedVSyncRenderer" PrefixI False) U1) (C1 (MetaCons "SoftwareRenderer" PrefixI False) U1)))

Keyboard arrow API

keyScancode :: MonadSDL m => Scancode -> InputMotion -> GameWire m a (Event (Seq KeyboardEventData)) Source #

Fires when specific scancode key is pressed/unpressed

keyPress :: MonadSDL m => Scancode -> GameWire m a (Event (Seq KeyboardEventData)) Source #

Fires when specific scancode key is pressed

keyRelease :: MonadSDL m => Scancode -> GameWire m a (Event (Seq KeyboardEventData)) Source #

Fires when specific scancode key is released

keyPressing :: MonadSDL m => Scancode -> GameWire m a (Event KeyboardEventData) Source #

Fires event from moment of press until release of given key

Mouse arrow API

mouseScroll :: MonadSDL m => GameWire m a (Event (V2 Int32)) Source #

Returns accumulated mouse scroll scince last frame

mouseScrollX :: MonadSDL m => GameWire m a (Event Int32) Source #

Returns accumulated mouse scroll scince last frame

mouseScrollY :: MonadSDL m => GameWire m a (Event Int32) Source #

Returns accumulated mouse scroll scince last frame

mouseClick :: MonadSDL m => MouseButton -> GameWire m a (Event (V2 Double)) Source #

Fires when user clicks within window. Click coordinates are in [-1 .. 1] range

Window arrow API

windowClosed :: MonadSDL m => Text -> GameWire m a (Event ()) Source #

Fires when window with specific name is closed