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.API

Description

The module contains monadic and arrow API of the core module.

Synopsis

Documentation

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 #

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