sdl2-2.4.1.0: Both high- and low-level bindings to the SDL library (version 2.0.4+).

Safe HaskellNone
LanguageHaskell2010

SDL.Event

Contents

Description

SDL.Event exports an interface for working with the SDL event model. Event handling allows your application to receive input from the user. Internally, SDL stores all the events waiting to be handled in an event queue. Using functions like pollEvent and waitEvent you can observe and handle waiting input events.

The event queue itself is composed of a series of Event values, one for each waiting event. Event values are read from the queue with the pollEvent function and it is then up to the application to process the information stored with them.

Synopsis

Polling events

pollEvent :: MonadIO m => m (Maybe Event) Source #

Poll for currently pending events. You can only call this function in the thread that set the video mode.

pollEvents :: (Functor m, MonadIO m) => m [Event] Source #

Clear the event queue by polling for all pending events.

mapEvents :: MonadIO m => (Event -> m ()) -> m () Source #

Run a monadic computation, accumulating over all known Events.

This can be useful when used with a state monad, allowing you to fold all events together.

pumpEvents :: MonadIO m => m () Source #

Pump the event loop, gathering events from the input devices.

This function updates the event queue and internal input device state.

This should only be run in the thread that initialized the video subsystem, and for extra safety, you should consider only doing those things on the main thread in any case.

pumpEvents gathers all the pending input information from devices and places it in the event queue. Without calls to pumpEvents no events would ever be placed on the queue. Often the need for calls to pumpEvents is hidden from the user since pollEvent and waitEvent implicitly call pumpEvents. However, if you are not polling or waiting for events (e.g. you are filtering them), then you must call pumpEvents to force an event queue update.

See SDL_PumpEvents for C documentation.

waitEvent :: MonadIO m => m Event Source #

Wait indefinitely for the next available event.

waitEventTimeout Source #

Arguments

:: MonadIO m 
=> CInt

The maximum amount of time to wait, in milliseconds.

-> m (Maybe Event) 

Wait until the specified timeout for the next available amount.

Registering user events

data RegisteredEventType a Source #

A user defined event structure that has been registered with SDL.

Use registerEvent, below, to obtain an instance.

data RegisteredEventData Source #

A record used to convert between SDL Events and user-defined data structures.

Used for registerEvent, below.

Constructors

RegisteredEventData 

Fields

Instances

Eq RegisteredEventData Source # 
Ord RegisteredEventData Source # 
Show RegisteredEventData Source # 
Generic RegisteredEventData Source # 
type Rep RegisteredEventData Source # 
type Rep RegisteredEventData = D1 * (MetaData "RegisteredEventData" "SDL.Event" "sdl2-2.4.1.0-GJ23ELiCVd1AQAhvhiAzSX" False) (C1 * (MetaCons "RegisteredEventData" PrefixI True) ((:*:) * ((:*:) * (S1 * (MetaSel (Just Symbol "registeredEventWindow") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 * (Maybe Window))) (S1 * (MetaSel (Just Symbol "registeredEventCode") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 * Int32))) ((:*:) * (S1 * (MetaSel (Just Symbol "registeredEventData1") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 * (Ptr ()))) (S1 * (MetaSel (Just Symbol "registeredEventData2") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 * (Ptr ()))))))

data EventPushResult Source #

Possible results of an attempted push of an event to the queue.

Instances

Eq EventPushResult Source # 
Data EventPushResult Source # 

Methods

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

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

toConstr :: EventPushResult -> Constr #

dataTypeOf :: EventPushResult -> DataType #

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

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

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

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

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

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

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

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

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

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

Ord EventPushResult Source # 
Read EventPushResult Source # 
Show EventPushResult Source # 
Generic EventPushResult Source # 
type Rep EventPushResult Source # 
type Rep EventPushResult = D1 * (MetaData "EventPushResult" "SDL.Event" "sdl2-2.4.1.0-GJ23ELiCVd1AQAhvhiAzSX" False) ((:+:) * (C1 * (MetaCons "EventPushSuccess" PrefixI False) (U1 *)) ((:+:) * (C1 * (MetaCons "EventPushFiltered" PrefixI False) (U1 *)) (C1 * (MetaCons "EventPushFailure" PrefixI False) (S1 * (MetaSel (Nothing Symbol) NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 * Text)))))

emptyRegisteredEvent :: RegisteredEventData Source #

A registered event with no associated data.

This is a resonable baseline to modify for converting to RegisteredEventData.

registerEvent :: MonadIO m => (RegisteredEventData -> Timestamp -> IO (Maybe a)) -> (a -> IO RegisteredEventData) -> m (Maybe (RegisteredEventType a)) Source #

Register a new event type with SDL.

Provide functions that convert between UserEventData and your structure. You can then use pushRegisteredEvent to add a custom event of the registered type to the queue, and getRegisteredEvent to test for such events in the main loop.

Watching events

type EventWatchCallback = Event -> IO () Source #

An EventWatchCallback can process and respond to an event when it is added to the event queue.

addEventWatch :: MonadIO m => EventWatchCallback -> m EventWatch Source #

Trigger an EventWatchCallback when an event is added to the SDL event queue.

See https://wiki.libsdl.org/SDL_AddEventWatch for C documentation.

Event data

data Event Source #

A single SDL event. This event occured at eventTimestamp and carries data under eventPayload.

Constructors

Event 

Fields

Instances

Eq Event Source # 

Methods

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

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

Ord Event Source # 

Methods

compare :: Event -> Event -> Ordering #

(<) :: Event -> Event -> Bool #

(<=) :: Event -> Event -> Bool #

(>) :: Event -> Event -> Bool #

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

max :: Event -> Event -> Event #

min :: Event -> Event -> Event #

Show Event Source # 

Methods

showsPrec :: Int -> Event -> ShowS #

show :: Event -> String #

showList :: [Event] -> ShowS #

Generic Event Source # 

Associated Types

type Rep Event :: * -> * #

Methods

from :: Event -> Rep Event x #

to :: Rep Event x -> Event #

type Rep Event Source # 
type Rep Event = D1 * (MetaData "Event" "SDL.Event" "sdl2-2.4.1.0-GJ23ELiCVd1AQAhvhiAzSX" False) (C1 * (MetaCons "Event" PrefixI True) ((:*:) * (S1 * (MetaSel (Just Symbol "eventTimestamp") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 * Timestamp)) (S1 * (MetaSel (Just Symbol "eventPayload") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 * EventPayload))))

data EventPayload Source #

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 Source # 
Ord EventPayload Source # 
Show EventPayload Source # 
Generic EventPayload Source # 

Associated Types

type Rep EventPayload :: * -> * #

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

Window events

newtype WindowShownEventData Source #

A window has been shown.

Constructors

WindowShownEventData 

Fields

newtype WindowHiddenEventData Source #

A window has been hidden.

Constructors

WindowHiddenEventData 

Fields

newtype WindowExposedEventData Source #

A part of a window has been exposed - where exposure means to become visible (for example, an overlapping window no longer overlaps with the window).

Constructors

WindowExposedEventData 

Fields

Instances

data WindowMovedEventData Source #

A Window has been moved.

Constructors

WindowMovedEventData 

Fields

Instances

Eq WindowMovedEventData Source # 
Ord WindowMovedEventData Source # 
Show WindowMovedEventData Source # 
Generic WindowMovedEventData Source # 
type Rep WindowMovedEventData Source # 
type Rep WindowMovedEventData = D1 * (MetaData "WindowMovedEventData" "SDL.Event" "sdl2-2.4.1.0-GJ23ELiCVd1AQAhvhiAzSX" False) (C1 * (MetaCons "WindowMovedEventData" PrefixI True) ((:*:) * (S1 * (MetaSel (Just Symbol "windowMovedEventWindow") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 * Window)) (S1 * (MetaSel (Just Symbol "windowMovedEventPosition") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 * (Point V2 Int32)))))

data WindowResizedEventData Source #

Window has been resized. This is event is always preceded by WindowSizeChangedEvent.

Constructors

WindowResizedEventData 

Fields

Instances

Eq WindowResizedEventData Source # 
Ord WindowResizedEventData Source # 
Show WindowResizedEventData Source # 
Generic WindowResizedEventData Source # 
type Rep WindowResizedEventData Source # 
type Rep WindowResizedEventData = D1 * (MetaData "WindowResizedEventData" "SDL.Event" "sdl2-2.4.1.0-GJ23ELiCVd1AQAhvhiAzSX" False) (C1 * (MetaCons "WindowResizedEventData" PrefixI True) ((:*:) * (S1 * (MetaSel (Just Symbol "windowResizedEventWindow") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 * Window)) (S1 * (MetaSel (Just Symbol "windowResizedEventSize") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 * (V2 Int32)))))

data WindowSizeChangedEventData Source #

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.

Constructors

WindowSizeChangedEventData 

Fields

Instances

Eq WindowSizeChangedEventData Source # 
Ord WindowSizeChangedEventData Source # 
Show WindowSizeChangedEventData Source # 
Generic WindowSizeChangedEventData Source # 
type Rep WindowSizeChangedEventData Source # 
type Rep WindowSizeChangedEventData = D1 * (MetaData "WindowSizeChangedEventData" "SDL.Event" "sdl2-2.4.1.0-GJ23ELiCVd1AQAhvhiAzSX" False) (C1 * (MetaCons "WindowSizeChangedEventData" PrefixI True) ((:*:) * (S1 * (MetaSel (Just Symbol "windowSizeChangedEventWindow") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 * Window)) (S1 * (MetaSel (Just Symbol "windowSizeChangedEventSize") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 * (V2 Int32)))))

newtype WindowMinimizedEventData Source #

The window has been minimized.

Instances

Eq WindowMinimizedEventData Source # 
Ord WindowMinimizedEventData Source # 
Show WindowMinimizedEventData Source # 
Generic WindowMinimizedEventData Source # 
type Rep WindowMinimizedEventData Source # 
type Rep WindowMinimizedEventData = D1 * (MetaData "WindowMinimizedEventData" "SDL.Event" "sdl2-2.4.1.0-GJ23ELiCVd1AQAhvhiAzSX" True) (C1 * (MetaCons "WindowMinimizedEventData" PrefixI True) (S1 * (MetaSel (Just Symbol "windowMinimizedEventWindow") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 * Window)))

newtype WindowMaximizedEventData Source #

The window has been maximized.

Instances

Eq WindowMaximizedEventData Source # 
Ord WindowMaximizedEventData Source # 
Show WindowMaximizedEventData Source # 
Generic WindowMaximizedEventData Source # 
type Rep WindowMaximizedEventData Source # 
type Rep WindowMaximizedEventData = D1 * (MetaData "WindowMaximizedEventData" "SDL.Event" "sdl2-2.4.1.0-GJ23ELiCVd1AQAhvhiAzSX" True) (C1 * (MetaCons "WindowMaximizedEventData" PrefixI True) (S1 * (MetaSel (Just Symbol "windowMaximizedEventWindow") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 * Window)))

newtype WindowRestoredEventData Source #

The window has been restored to normal size and position.

Constructors

WindowRestoredEventData 

Fields

Instances

Eq WindowRestoredEventData Source # 
Ord WindowRestoredEventData Source # 
Show WindowRestoredEventData Source # 
Generic WindowRestoredEventData Source # 
type Rep WindowRestoredEventData Source # 
type Rep WindowRestoredEventData = D1 * (MetaData "WindowRestoredEventData" "SDL.Event" "sdl2-2.4.1.0-GJ23ELiCVd1AQAhvhiAzSX" True) (C1 * (MetaCons "WindowRestoredEventData" PrefixI True) (S1 * (MetaSel (Just Symbol "windowRestoredEventWindow") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 * Window)))

newtype WindowGainedMouseFocusEventData Source #

The window has gained mouse focus.

Instances

Eq WindowGainedMouseFocusEventData Source # 
Ord WindowGainedMouseFocusEventData Source # 
Show WindowGainedMouseFocusEventData Source # 
Generic WindowGainedMouseFocusEventData Source # 
type Rep WindowGainedMouseFocusEventData Source # 
type Rep WindowGainedMouseFocusEventData = D1 * (MetaData "WindowGainedMouseFocusEventData" "SDL.Event" "sdl2-2.4.1.0-GJ23ELiCVd1AQAhvhiAzSX" True) (C1 * (MetaCons "WindowGainedMouseFocusEventData" PrefixI True) (S1 * (MetaSel (Just Symbol "windowGainedMouseFocusEventWindow") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 * Window)))

newtype WindowLostMouseFocusEventData Source #

The window has lost mouse focus.

Instances

Eq WindowLostMouseFocusEventData Source # 
Ord WindowLostMouseFocusEventData Source # 
Show WindowLostMouseFocusEventData Source # 
Generic WindowLostMouseFocusEventData Source # 
type Rep WindowLostMouseFocusEventData Source # 
type Rep WindowLostMouseFocusEventData = D1 * (MetaData "WindowLostMouseFocusEventData" "SDL.Event" "sdl2-2.4.1.0-GJ23ELiCVd1AQAhvhiAzSX" True) (C1 * (MetaCons "WindowLostMouseFocusEventData" PrefixI True) (S1 * (MetaSel (Just Symbol "windowLostMouseFocusEventWindow") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 * Window)))

newtype WindowGainedKeyboardFocusEventData Source #

The window has gained keyboard focus.

Instances

Eq WindowGainedKeyboardFocusEventData Source # 
Ord WindowGainedKeyboardFocusEventData Source # 
Show WindowGainedKeyboardFocusEventData Source # 
Generic WindowGainedKeyboardFocusEventData Source # 
type Rep WindowGainedKeyboardFocusEventData Source # 
type Rep WindowGainedKeyboardFocusEventData = D1 * (MetaData "WindowGainedKeyboardFocusEventData" "SDL.Event" "sdl2-2.4.1.0-GJ23ELiCVd1AQAhvhiAzSX" True) (C1 * (MetaCons "WindowGainedKeyboardFocusEventData" PrefixI True) (S1 * (MetaSel (Just Symbol "windowGainedKeyboardFocusEventWindow") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 * Window)))

newtype WindowLostKeyboardFocusEventData Source #

The window has lost keyboard focus.

Instances

Eq WindowLostKeyboardFocusEventData Source # 
Ord WindowLostKeyboardFocusEventData Source # 
Show WindowLostKeyboardFocusEventData Source # 
Generic WindowLostKeyboardFocusEventData Source # 
type Rep WindowLostKeyboardFocusEventData Source # 
type Rep WindowLostKeyboardFocusEventData = D1 * (MetaData "WindowLostKeyboardFocusEventData" "SDL.Event" "sdl2-2.4.1.0-GJ23ELiCVd1AQAhvhiAzSX" True) (C1 * (MetaCons "WindowLostKeyboardFocusEventData" PrefixI True) (S1 * (MetaSel (Just Symbol "windowLostKeyboardFocusEventWindow") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 * Window)))

newtype WindowClosedEventData Source #

The window manager requests that the window be closed.

Constructors

WindowClosedEventData 

Fields

Keyboard events

data KeyboardEventData Source #

A keyboard key has been pressed or released.

Constructors

KeyboardEventData 

Fields

Instances

Eq KeyboardEventData Source # 
Ord KeyboardEventData Source # 
Show KeyboardEventData Source # 
Generic KeyboardEventData Source # 
type Rep KeyboardEventData Source # 
type Rep KeyboardEventData = D1 * (MetaData "KeyboardEventData" "SDL.Event" "sdl2-2.4.1.0-GJ23ELiCVd1AQAhvhiAzSX" False) (C1 * (MetaCons "KeyboardEventData" PrefixI True) ((:*:) * ((:*:) * (S1 * (MetaSel (Just Symbol "keyboardEventWindow") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 * (Maybe Window))) (S1 * (MetaSel (Just Symbol "keyboardEventKeyMotion") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 * InputMotion))) ((:*:) * (S1 * (MetaSel (Just Symbol "keyboardEventRepeat") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 * Bool)) (S1 * (MetaSel (Just Symbol "keyboardEventKeysym") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 * Keysym)))))

data TextEditingEventData Source #

Keyboard text editing event information.

Constructors

TextEditingEventData 

Fields

Instances

Eq TextEditingEventData Source # 
Ord TextEditingEventData Source # 
Show TextEditingEventData Source # 
Generic TextEditingEventData Source # 
type Rep TextEditingEventData Source # 
type Rep TextEditingEventData = D1 * (MetaData "TextEditingEventData" "SDL.Event" "sdl2-2.4.1.0-GJ23ELiCVd1AQAhvhiAzSX" False) (C1 * (MetaCons "TextEditingEventData" PrefixI True) ((:*:) * ((:*:) * (S1 * (MetaSel (Just Symbol "textEditingEventWindow") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 * (Maybe Window))) (S1 * (MetaSel (Just Symbol "textEditingEventText") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 * Text))) ((:*:) * (S1 * (MetaSel (Just Symbol "textEditingEventStart") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 * Int32)) (S1 * (MetaSel (Just Symbol "textEditingEventLength") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 * Int32)))))

data TextInputEventData Source #

Keyboard text input event information.

Constructors

TextInputEventData 

Fields

Mouse events

data MouseMotionEventData Source #

A mouse or pointer device was moved.

Constructors

MouseMotionEventData 

Fields

Instances

Eq MouseMotionEventData Source # 
Ord MouseMotionEventData Source # 
Show MouseMotionEventData Source # 
Generic MouseMotionEventData Source # 
type Rep MouseMotionEventData Source # 
type Rep MouseMotionEventData = D1 * (MetaData "MouseMotionEventData" "SDL.Event" "sdl2-2.4.1.0-GJ23ELiCVd1AQAhvhiAzSX" False) (C1 * (MetaCons "MouseMotionEventData" PrefixI True) ((:*:) * ((:*:) * (S1 * (MetaSel (Just Symbol "mouseMotionEventWindow") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 * (Maybe Window))) (S1 * (MetaSel (Just Symbol "mouseMotionEventWhich") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 * MouseDevice))) ((:*:) * (S1 * (MetaSel (Just Symbol "mouseMotionEventState") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 * [MouseButton])) ((:*:) * (S1 * (MetaSel (Just Symbol "mouseMotionEventPos") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 * (Point V2 Int32))) (S1 * (MetaSel (Just Symbol "mouseMotionEventRelMotion") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 * (V2 Int32)))))))

data MouseButtonEventData Source #

A mouse or pointer device button was pressed or released.

Constructors

MouseButtonEventData 

Fields

Instances

Eq MouseButtonEventData Source # 
Ord MouseButtonEventData Source # 
Show MouseButtonEventData Source # 
Generic MouseButtonEventData Source # 
type Rep MouseButtonEventData Source # 
type Rep MouseButtonEventData = D1 * (MetaData "MouseButtonEventData" "SDL.Event" "sdl2-2.4.1.0-GJ23ELiCVd1AQAhvhiAzSX" False) (C1 * (MetaCons "MouseButtonEventData" PrefixI True) ((:*:) * ((:*:) * (S1 * (MetaSel (Just Symbol "mouseButtonEventWindow") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 * (Maybe Window))) ((:*:) * (S1 * (MetaSel (Just Symbol "mouseButtonEventMotion") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 * InputMotion)) (S1 * (MetaSel (Just Symbol "mouseButtonEventWhich") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 * MouseDevice)))) ((:*:) * (S1 * (MetaSel (Just Symbol "mouseButtonEventButton") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 * MouseButton)) ((:*:) * (S1 * (MetaSel (Just Symbol "mouseButtonEventClicks") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 * Word8)) (S1 * (MetaSel (Just Symbol "mouseButtonEventPos") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 * (Point V2 Int32)))))))

data MouseWheelEventData Source #

Mouse wheel event information.

Constructors

MouseWheelEventData 

Fields

Instances

Eq MouseWheelEventData Source # 
Ord MouseWheelEventData Source # 
Show MouseWheelEventData Source # 
Generic MouseWheelEventData Source # 
type Rep MouseWheelEventData Source # 
type Rep MouseWheelEventData = D1 * (MetaData "MouseWheelEventData" "SDL.Event" "sdl2-2.4.1.0-GJ23ELiCVd1AQAhvhiAzSX" False) (C1 * (MetaCons "MouseWheelEventData" PrefixI True) ((:*:) * ((:*:) * (S1 * (MetaSel (Just Symbol "mouseWheelEventWindow") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 * (Maybe Window))) (S1 * (MetaSel (Just Symbol "mouseWheelEventWhich") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 * MouseDevice))) ((:*:) * (S1 * (MetaSel (Just Symbol "mouseWheelEventPos") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 * (V2 Int32))) (S1 * (MetaSel (Just Symbol "mouseWheelEventDirection") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 * MouseScrollDirection)))))

Joystick events

data JoyAxisEventData Source #

Joystick axis motion event information

Constructors

JoyAxisEventData 

Fields

Instances

Eq JoyAxisEventData Source # 
Ord JoyAxisEventData Source # 
Show JoyAxisEventData Source # 
Generic JoyAxisEventData Source # 
type Rep JoyAxisEventData Source # 
type Rep JoyAxisEventData = D1 * (MetaData "JoyAxisEventData" "SDL.Event" "sdl2-2.4.1.0-GJ23ELiCVd1AQAhvhiAzSX" False) (C1 * (MetaCons "JoyAxisEventData" PrefixI True) ((:*:) * (S1 * (MetaSel (Just Symbol "joyAxisEventWhich") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 * JoystickID)) ((:*:) * (S1 * (MetaSel (Just Symbol "joyAxisEventAxis") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 * Word8)) (S1 * (MetaSel (Just Symbol "joyAxisEventValue") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 * Int16)))))

data JoyBallEventData Source #

Joystick trackball motion event information.

Constructors

JoyBallEventData 

Fields

Instances

Eq JoyBallEventData Source # 
Ord JoyBallEventData Source # 
Show JoyBallEventData Source # 
Generic JoyBallEventData Source # 
type Rep JoyBallEventData Source # 
type Rep JoyBallEventData = D1 * (MetaData "JoyBallEventData" "SDL.Event" "sdl2-2.4.1.0-GJ23ELiCVd1AQAhvhiAzSX" False) (C1 * (MetaCons "JoyBallEventData" PrefixI True) ((:*:) * (S1 * (MetaSel (Just Symbol "joyBallEventWhich") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 * JoystickID)) ((:*:) * (S1 * (MetaSel (Just Symbol "joyBallEventBall") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 * Word8)) (S1 * (MetaSel (Just Symbol "joyBallEventRelMotion") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 * (V2 Int16))))))

data JoyHatEventData Source #

Joystick hat position change event information

Constructors

JoyHatEventData 

Fields

Instances

data JoyButtonEventData Source #

Joystick button event information.

Constructors

JoyButtonEventData 

Fields

Instances

Eq JoyButtonEventData Source # 
Ord JoyButtonEventData Source # 
Show JoyButtonEventData Source # 
Generic JoyButtonEventData Source # 
type Rep JoyButtonEventData Source # 
type Rep JoyButtonEventData = D1 * (MetaData "JoyButtonEventData" "SDL.Event" "sdl2-2.4.1.0-GJ23ELiCVd1AQAhvhiAzSX" False) (C1 * (MetaCons "JoyButtonEventData" PrefixI True) ((:*:) * (S1 * (MetaSel (Just Symbol "joyButtonEventWhich") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 * JoystickID)) ((:*:) * (S1 * (MetaSel (Just Symbol "joyButtonEventButton") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 * Word8)) (S1 * (MetaSel (Just Symbol "joyButtonEventState") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 * JoyButtonState)))))

data JoyDeviceEventData Source #

Joystick device event information.

Constructors

JoyDeviceEventData 

Fields

Controller events

data ControllerAxisEventData Source #

Game controller axis motion event information.

Constructors

ControllerAxisEventData 

Fields

Instances

Eq ControllerAxisEventData Source # 
Ord ControllerAxisEventData Source # 
Show ControllerAxisEventData Source # 
Generic ControllerAxisEventData Source # 
type Rep ControllerAxisEventData Source # 
type Rep ControllerAxisEventData = D1 * (MetaData "ControllerAxisEventData" "SDL.Event" "sdl2-2.4.1.0-GJ23ELiCVd1AQAhvhiAzSX" False) (C1 * (MetaCons "ControllerAxisEventData" PrefixI True) ((:*:) * (S1 * (MetaSel (Just Symbol "controllerAxisEventWhich") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 * JoystickID)) ((:*:) * (S1 * (MetaSel (Just Symbol "controllerAxisEventAxis") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 * Word8)) (S1 * (MetaSel (Just Symbol "controllerAxisEventValue") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 * Int16)))))

data ControllerButtonEventData Source #

Game controller button event information

Constructors

ControllerButtonEventData 

Fields

Instances

Eq ControllerButtonEventData Source # 
Ord ControllerButtonEventData Source # 
Show ControllerButtonEventData Source # 
Generic ControllerButtonEventData Source # 
type Rep ControllerButtonEventData Source # 
type Rep ControllerButtonEventData = D1 * (MetaData "ControllerButtonEventData" "SDL.Event" "sdl2-2.4.1.0-GJ23ELiCVd1AQAhvhiAzSX" False) (C1 * (MetaCons "ControllerButtonEventData" PrefixI True) ((:*:) * (S1 * (MetaSel (Just Symbol "controllerButtonEventWhich") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 * JoystickID)) ((:*:) * (S1 * (MetaSel (Just Symbol "controllerButtonEventButton") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 * ControllerButton)) (S1 * (MetaSel (Just Symbol "controllerButtonEventState") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 * ControllerButtonState)))))

data ControllerDeviceEventData Source #

Controller device event information

Constructors

ControllerDeviceEventData 

Fields

Instances

Eq ControllerDeviceEventData Source # 
Ord ControllerDeviceEventData Source # 
Show ControllerDeviceEventData Source # 
Generic ControllerDeviceEventData Source # 
type Rep ControllerDeviceEventData Source # 
type Rep ControllerDeviceEventData = D1 * (MetaData "ControllerDeviceEventData" "SDL.Event" "sdl2-2.4.1.0-GJ23ELiCVd1AQAhvhiAzSX" False) (C1 * (MetaCons "ControllerDeviceEventData" PrefixI True) ((:*:) * (S1 * (MetaSel (Just Symbol "controllerDeviceEventConnection") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 * ControllerDeviceConnection)) (S1 * (MetaSel (Just Symbol "controllerDeviceEventWhich") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 * Int32))))

Audio events

data AudioDeviceEventData Source #

Constructors

AudioDeviceEventData 

Fields

Instances

Eq AudioDeviceEventData Source # 
Ord AudioDeviceEventData Source # 
Show AudioDeviceEventData Source # 
Generic AudioDeviceEventData Source # 
type Rep AudioDeviceEventData Source # 
type Rep AudioDeviceEventData = D1 * (MetaData "AudioDeviceEventData" "SDL.Event" "sdl2-2.4.1.0-GJ23ELiCVd1AQAhvhiAzSX" False) (C1 * (MetaCons "AudioDeviceEventData" PrefixI True) ((:*:) * (S1 * (MetaSel (Just Symbol "audioDeviceEventIsAddition") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 * Bool)) ((:*:) * (S1 * (MetaSel (Just Symbol "audioDeviceEventWhich") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 * Word32)) (S1 * (MetaSel (Just Symbol "audioDeviceEventIsCapture") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 * Bool)))))

User events

data UserEventData Source #

Event data for application-defined events.

Constructors

UserEventData 

Fields

Instances

Eq UserEventData Source # 
Ord UserEventData Source # 
Show UserEventData Source # 
Generic UserEventData Source # 

Associated Types

type Rep UserEventData :: * -> * #

type Rep UserEventData Source # 
type Rep UserEventData = D1 * (MetaData "UserEventData" "SDL.Event" "sdl2-2.4.1.0-GJ23ELiCVd1AQAhvhiAzSX" False) (C1 * (MetaCons "UserEventData" PrefixI True) ((:*:) * ((:*:) * (S1 * (MetaSel (Just Symbol "userEventType") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 * Word32)) (S1 * (MetaSel (Just Symbol "userEventWindow") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 * (Maybe Window)))) ((:*:) * (S1 * (MetaSel (Just Symbol "userEventCode") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 * Int32)) ((:*:) * (S1 * (MetaSel (Just Symbol "userEventData1") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 * (Ptr ()))) (S1 * (MetaSel (Just Symbol "userEventData2") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 * (Ptr ())))))))

Touch events

data TouchFingerEventData Source #

Finger touch event information.

Constructors

TouchFingerEventData 

Fields

Instances

Eq TouchFingerEventData Source # 
Ord TouchFingerEventData Source # 
Show TouchFingerEventData Source # 
Generic TouchFingerEventData Source # 
type Rep TouchFingerEventData Source # 
type Rep TouchFingerEventData = D1 * (MetaData "TouchFingerEventData" "SDL.Event" "sdl2-2.4.1.0-GJ23ELiCVd1AQAhvhiAzSX" False) (C1 * (MetaCons "TouchFingerEventData" PrefixI True) ((:*:) * ((:*:) * (S1 * (MetaSel (Just Symbol "touchFingerEventTouchID") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 * TouchID)) (S1 * (MetaSel (Just Symbol "touchFingerEventFingerID") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 * FingerID))) ((:*:) * (S1 * (MetaSel (Just Symbol "touchFingerEventMotion") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 * InputMotion)) ((:*:) * (S1 * (MetaSel (Just Symbol "touchFingerEventPos") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 * (Point V2 CFloat))) (S1 * (MetaSel (Just Symbol "touchFingerEventPressure") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 * CFloat))))))

data TouchFingerMotionEventData Source #

Finger motion event information.

Constructors

TouchFingerMotionEventData 

Fields

Instances

Eq TouchFingerMotionEventData Source # 
Ord TouchFingerMotionEventData Source # 
Show TouchFingerMotionEventData Source # 
Generic TouchFingerMotionEventData Source # 
type Rep TouchFingerMotionEventData Source # 
type Rep TouchFingerMotionEventData = D1 * (MetaData "TouchFingerMotionEventData" "SDL.Event" "sdl2-2.4.1.0-GJ23ELiCVd1AQAhvhiAzSX" False) (C1 * (MetaCons "TouchFingerMotionEventData" PrefixI True) ((:*:) * ((:*:) * (S1 * (MetaSel (Just Symbol "touchFingerMotionEventTouchID") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 * TouchID)) (S1 * (MetaSel (Just Symbol "touchFingerMotionEventFingerID") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 * FingerID))) ((:*:) * (S1 * (MetaSel (Just Symbol "touchFingerMotionEventPos") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 * (Point V2 CFloat))) ((:*:) * (S1 * (MetaSel (Just Symbol "touchFingerMotionEventRelMotion") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 * (V2 CFloat))) (S1 * (MetaSel (Just Symbol "touchFingerMotionEventPressure") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 * CFloat))))))

Gesture events

data MultiGestureEventData Source #

Multiple finger gesture event information

Constructors

MultiGestureEventData 

Fields

Instances

Eq MultiGestureEventData Source # 
Ord MultiGestureEventData Source # 
Show MultiGestureEventData Source # 
Generic MultiGestureEventData Source # 
type Rep MultiGestureEventData Source # 
type Rep MultiGestureEventData = D1 * (MetaData "MultiGestureEventData" "SDL.Event" "sdl2-2.4.1.0-GJ23ELiCVd1AQAhvhiAzSX" False) (C1 * (MetaCons "MultiGestureEventData" PrefixI True) ((:*:) * ((:*:) * (S1 * (MetaSel (Just Symbol "multiGestureEventTouchID") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 * TouchID)) (S1 * (MetaSel (Just Symbol "multiGestureEventDTheta") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 * CFloat))) ((:*:) * (S1 * (MetaSel (Just Symbol "multiGestureEventDDist") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 * CFloat)) ((:*:) * (S1 * (MetaSel (Just Symbol "multiGestureEventPos") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 * (Point V2 CFloat))) (S1 * (MetaSel (Just Symbol "multiGestureEventNumFingers") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 * Word16))))))

data DollarGestureEventData Source #

Complex gesture event information.

Constructors

DollarGestureEventData 

Fields

Instances

Eq DollarGestureEventData Source # 
Ord DollarGestureEventData Source # 
Show DollarGestureEventData Source # 
Generic DollarGestureEventData Source # 
type Rep DollarGestureEventData Source # 
type Rep DollarGestureEventData = D1 * (MetaData "DollarGestureEventData" "SDL.Event" "sdl2-2.4.1.0-GJ23ELiCVd1AQAhvhiAzSX" False) (C1 * (MetaCons "DollarGestureEventData" PrefixI True) ((:*:) * ((:*:) * (S1 * (MetaSel (Just Symbol "dollarGestureEventTouchID") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 * TouchID)) (S1 * (MetaSel (Just Symbol "dollarGestureEventGestureID") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 * GestureID))) ((:*:) * (S1 * (MetaSel (Just Symbol "dollarGestureEventNumFingers") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 * Word32)) ((:*:) * (S1 * (MetaSel (Just Symbol "dollarGestureEventError") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 * CFloat)) (S1 * (MetaSel (Just Symbol "dollarGestureEventPos") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 * (Point V2 CFloat)))))))

Drag and drop events

Unknown events

Auxiliary event data

data InputMotion Source #

Constructors

Released 
Pressed 

Instances

Bounded InputMotion Source # 
Enum InputMotion Source # 
Eq InputMotion Source # 
Data InputMotion Source # 

Methods

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

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

toConstr :: InputMotion -> Constr #

dataTypeOf :: InputMotion -> DataType #

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

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

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

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

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

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

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

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

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

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

Ord InputMotion Source # 
Read InputMotion Source # 
Show InputMotion Source # 
Generic InputMotion Source # 

Associated Types

type Rep InputMotion :: * -> * #

type Rep InputMotion Source # 
type Rep InputMotion = D1 * (MetaData "InputMotion" "SDL.Event" "sdl2-2.4.1.0-GJ23ELiCVd1AQAhvhiAzSX" False) ((:+:) * (C1 * (MetaCons "Released" PrefixI False) (U1 *)) (C1 * (MetaCons "Pressed" PrefixI False) (U1 *)))

data MouseButton Source #

Constructors

ButtonLeft 
ButtonMiddle 
ButtonRight 
ButtonX1 
ButtonX2 
ButtonExtra !Int

An unknown mouse button.

Instances

Eq MouseButton Source # 
Data MouseButton Source # 

Methods

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

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

toConstr :: MouseButton -> Constr #

dataTypeOf :: MouseButton -> DataType #

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

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

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

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

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

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

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

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

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

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

Ord MouseButton Source # 
Read MouseButton Source # 
Show MouseButton Source # 
Generic MouseButton Source # 

Associated Types

type Rep MouseButton :: * -> * #

ToNumber MouseButton Word8 Source # 
FromNumber MouseButton Word8 Source # 
type Rep MouseButton Source # 
type Rep MouseButton = D1 * (MetaData "MouseButton" "SDL.Input.Mouse" "sdl2-2.4.1.0-GJ23ELiCVd1AQAhvhiAzSX" False) ((:+:) * ((:+:) * (C1 * (MetaCons "ButtonLeft" PrefixI False) (U1 *)) ((:+:) * (C1 * (MetaCons "ButtonMiddle" PrefixI False) (U1 *)) (C1 * (MetaCons "ButtonRight" PrefixI False) (U1 *)))) ((:+:) * (C1 * (MetaCons "ButtonX1" PrefixI False) (U1 *)) ((:+:) * (C1 * (MetaCons "ButtonX2" PrefixI False) (U1 *)) (C1 * (MetaCons "ButtonExtra" PrefixI False) (S1 * (MetaSel (Nothing Symbol) NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 * Int))))))