sdl2-2.5.3.0: Both high- and low-level bindings to the SDL library (version 2.0.6+).
Safe HaskellNone
LanguageHaskell2010

SDL.Event

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 OS thread that set the video mode.

pollEvents :: MonadIO m => m [Event] Source #

Clear the event queue by polling for all pending events.

Like pollEvent this function should only be called in the OS thread which set the video mode.

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 OS 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

Instances details
Eq RegisteredEventData Source # 
Instance details

Defined in SDL.Event

Ord RegisteredEventData Source # 
Instance details

Defined in SDL.Event

Show RegisteredEventData Source # 
Instance details

Defined in SDL.Event

Generic RegisteredEventData Source # 
Instance details

Defined in SDL.Event

Associated Types

type Rep RegisteredEventData :: Type -> Type #

type Rep RegisteredEventData Source # 
Instance details

Defined in SDL.Event

type Rep RegisteredEventData = D1 ('MetaData "RegisteredEventData" "SDL.Event" "sdl2-2.5.3.0-FYgxNXfOgR1EIBtbDjNyzg" 'False) (C1 ('MetaCons "RegisteredEventData" 'PrefixI 'True) ((S1 ('MetaSel ('Just "registeredEventWindow") 'NoSourceUnpackedness 'SourceStrict 'DecidedStrict) (Rec0 (Maybe Window)) :*: S1 ('MetaSel ('Just "registeredEventCode") 'NoSourceUnpackedness 'SourceStrict 'DecidedStrict) (Rec0 Int32)) :*: (S1 ('MetaSel ('Just "registeredEventData1") 'NoSourceUnpackedness 'SourceStrict 'DecidedStrict) (Rec0 (Ptr ())) :*: S1 ('MetaSel ('Just "registeredEventData2") 'NoSourceUnpackedness 'SourceStrict 'DecidedStrict) (Rec0 (Ptr ())))))

data EventPushResult Source #

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

Instances

Instances details
Eq EventPushResult Source # 
Instance details

Defined in SDL.Event

Data EventPushResult Source # 
Instance details

Defined in SDL.Event

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 :: forall r r'. (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 # 
Instance details

Defined in SDL.Event

Read EventPushResult Source # 
Instance details

Defined in SDL.Event

Show EventPushResult Source # 
Instance details

Defined in SDL.Event

Generic EventPushResult Source # 
Instance details

Defined in SDL.Event

Associated Types

type Rep EventPushResult :: Type -> Type #

type Rep EventPushResult Source # 
Instance details

Defined in SDL.Event

type Rep EventPushResult = D1 ('MetaData "EventPushResult" "SDL.Event" "sdl2-2.5.3.0-FYgxNXfOgR1EIBtbDjNyzg" 'False) (C1 ('MetaCons "EventPushSuccess" 'PrefixI 'False) (U1 :: Type -> Type) :+: (C1 ('MetaCons "EventPushFiltered" 'PrefixI 'False) (U1 :: Type -> Type) :+: C1 ('MetaCons "EventPushFailure" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe 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

Instances details
Eq Event Source # 
Instance details

Defined in SDL.Event

Methods

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

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

Ord Event Source # 
Instance details

Defined in SDL.Event

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

Defined in SDL.Event

Methods

showsPrec :: Int -> Event -> ShowS #

show :: Event -> String #

showList :: [Event] -> ShowS #

Generic Event Source # 
Instance details

Defined in SDL.Event

Associated Types

type Rep Event :: Type -> Type #

Methods

from :: Event -> Rep Event x #

to :: Rep Event x -> Event #

type Rep Event Source # 
Instance details

Defined in SDL.Event

type Rep Event = D1 ('MetaData "Event" "SDL.Event" "sdl2-2.5.3.0-FYgxNXfOgR1EIBtbDjNyzg" 'False) (C1 ('MetaCons "Event" 'PrefixI 'True) (S1 ('MetaSel ('Just "eventTimestamp") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 Timestamp) :*: S1 ('MetaSel ('Just "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

Instances details
Eq EventPayload Source # 
Instance details

Defined in SDL.Event

Ord EventPayload Source # 
Instance details

Defined in SDL.Event

Show EventPayload Source # 
Instance details

Defined in SDL.Event

Generic EventPayload Source # 
Instance details

Defined in SDL.Event

Associated Types

type Rep EventPayload :: Type -> Type #

type Rep EventPayload Source # 
Instance details

Defined in SDL.Event

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

Window events

newtype WindowShownEventData Source #

A window has been shown.

Constructors

WindowShownEventData 

Fields

Instances

Instances details
Eq WindowShownEventData Source # 
Instance details

Defined in SDL.Event

Ord WindowShownEventData Source # 
Instance details

Defined in SDL.Event

Show WindowShownEventData Source # 
Instance details

Defined in SDL.Event

Generic WindowShownEventData Source # 
Instance details

Defined in SDL.Event

Associated Types

type Rep WindowShownEventData :: Type -> Type #

type Rep WindowShownEventData Source # 
Instance details

Defined in SDL.Event

type Rep WindowShownEventData = D1 ('MetaData "WindowShownEventData" "SDL.Event" "sdl2-2.5.3.0-FYgxNXfOgR1EIBtbDjNyzg" 'True) (C1 ('MetaCons "WindowShownEventData" 'PrefixI 'True) (S1 ('MetaSel ('Just "windowShownEventWindow") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 Window)))

newtype WindowHiddenEventData Source #

A window has been hidden.

Constructors

WindowHiddenEventData 

Fields

Instances

Instances details
Eq WindowHiddenEventData Source # 
Instance details

Defined in SDL.Event

Ord WindowHiddenEventData Source # 
Instance details

Defined in SDL.Event

Show WindowHiddenEventData Source # 
Instance details

Defined in SDL.Event

Generic WindowHiddenEventData Source # 
Instance details

Defined in SDL.Event

Associated Types

type Rep WindowHiddenEventData :: Type -> Type #

type Rep WindowHiddenEventData Source # 
Instance details

Defined in SDL.Event

type Rep WindowHiddenEventData = D1 ('MetaData "WindowHiddenEventData" "SDL.Event" "sdl2-2.5.3.0-FYgxNXfOgR1EIBtbDjNyzg" 'True) (C1 ('MetaCons "WindowHiddenEventData" 'PrefixI 'True) (S1 ('MetaSel ('Just "windowHiddenEventWindow") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 Window)))

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

Instances details
Eq WindowExposedEventData Source # 
Instance details

Defined in SDL.Event

Ord WindowExposedEventData Source # 
Instance details

Defined in SDL.Event

Show WindowExposedEventData Source # 
Instance details

Defined in SDL.Event

Generic WindowExposedEventData Source # 
Instance details

Defined in SDL.Event

Associated Types

type Rep WindowExposedEventData :: Type -> Type #

type Rep WindowExposedEventData Source # 
Instance details

Defined in SDL.Event

type Rep WindowExposedEventData = D1 ('MetaData "WindowExposedEventData" "SDL.Event" "sdl2-2.5.3.0-FYgxNXfOgR1EIBtbDjNyzg" 'True) (C1 ('MetaCons "WindowExposedEventData" 'PrefixI 'True) (S1 ('MetaSel ('Just "windowExposedEventWindow") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 Window)))

data WindowMovedEventData Source #

A Window has been moved.

Constructors

WindowMovedEventData 

Fields

Instances

Instances details
Eq WindowMovedEventData Source # 
Instance details

Defined in SDL.Event

Ord WindowMovedEventData Source # 
Instance details

Defined in SDL.Event

Show WindowMovedEventData Source # 
Instance details

Defined in SDL.Event

Generic WindowMovedEventData Source # 
Instance details

Defined in SDL.Event

Associated Types

type Rep WindowMovedEventData :: Type -> Type #

type Rep WindowMovedEventData Source # 
Instance details

Defined in SDL.Event

type Rep WindowMovedEventData = D1 ('MetaData "WindowMovedEventData" "SDL.Event" "sdl2-2.5.3.0-FYgxNXfOgR1EIBtbDjNyzg" 'False) (C1 ('MetaCons "WindowMovedEventData" 'PrefixI 'True) (S1 ('MetaSel ('Just "windowMovedEventWindow") 'NoSourceUnpackedness 'SourceStrict 'DecidedStrict) (Rec0 Window) :*: S1 ('MetaSel ('Just "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

Instances details
Eq WindowResizedEventData Source # 
Instance details

Defined in SDL.Event

Ord WindowResizedEventData Source # 
Instance details

Defined in SDL.Event

Show WindowResizedEventData Source # 
Instance details

Defined in SDL.Event

Generic WindowResizedEventData Source # 
Instance details

Defined in SDL.Event

Associated Types

type Rep WindowResizedEventData :: Type -> Type #

type Rep WindowResizedEventData Source # 
Instance details

Defined in SDL.Event

type Rep WindowResizedEventData = D1 ('MetaData "WindowResizedEventData" "SDL.Event" "sdl2-2.5.3.0-FYgxNXfOgR1EIBtbDjNyzg" 'False) (C1 ('MetaCons "WindowResizedEventData" 'PrefixI 'True) (S1 ('MetaSel ('Just "windowResizedEventWindow") 'NoSourceUnpackedness 'SourceStrict 'DecidedStrict) (Rec0 Window) :*: S1 ('MetaSel ('Just "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

Instances details
Eq WindowSizeChangedEventData Source # 
Instance details

Defined in SDL.Event

Ord WindowSizeChangedEventData Source # 
Instance details

Defined in SDL.Event

Show WindowSizeChangedEventData Source # 
Instance details

Defined in SDL.Event

Generic WindowSizeChangedEventData Source # 
Instance details

Defined in SDL.Event

Associated Types

type Rep WindowSizeChangedEventData :: Type -> Type #

type Rep WindowSizeChangedEventData Source # 
Instance details

Defined in SDL.Event

type Rep WindowSizeChangedEventData = D1 ('MetaData "WindowSizeChangedEventData" "SDL.Event" "sdl2-2.5.3.0-FYgxNXfOgR1EIBtbDjNyzg" 'False) (C1 ('MetaCons "WindowSizeChangedEventData" 'PrefixI 'True) (S1 ('MetaSel ('Just "windowSizeChangedEventWindow") 'NoSourceUnpackedness 'SourceStrict 'DecidedStrict) (Rec0 Window) :*: S1 ('MetaSel ('Just "windowSizeChangedEventSize") 'NoSourceUnpackedness 'SourceStrict 'DecidedStrict) (Rec0 (V2 Int32))))

newtype WindowMinimizedEventData Source #

The window has been minimized.

Instances

Instances details
Eq WindowMinimizedEventData Source # 
Instance details

Defined in SDL.Event

Ord WindowMinimizedEventData Source # 
Instance details

Defined in SDL.Event

Show WindowMinimizedEventData Source # 
Instance details

Defined in SDL.Event

Generic WindowMinimizedEventData Source # 
Instance details

Defined in SDL.Event

Associated Types

type Rep WindowMinimizedEventData :: Type -> Type #

type Rep WindowMinimizedEventData Source # 
Instance details

Defined in SDL.Event

type Rep WindowMinimizedEventData = D1 ('MetaData "WindowMinimizedEventData" "SDL.Event" "sdl2-2.5.3.0-FYgxNXfOgR1EIBtbDjNyzg" 'True) (C1 ('MetaCons "WindowMinimizedEventData" 'PrefixI 'True) (S1 ('MetaSel ('Just "windowMinimizedEventWindow") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 Window)))

newtype WindowMaximizedEventData Source #

The window has been maximized.

Instances

Instances details
Eq WindowMaximizedEventData Source # 
Instance details

Defined in SDL.Event

Ord WindowMaximizedEventData Source # 
Instance details

Defined in SDL.Event

Show WindowMaximizedEventData Source # 
Instance details

Defined in SDL.Event

Generic WindowMaximizedEventData Source # 
Instance details

Defined in SDL.Event

Associated Types

type Rep WindowMaximizedEventData :: Type -> Type #

type Rep WindowMaximizedEventData Source # 
Instance details

Defined in SDL.Event

type Rep WindowMaximizedEventData = D1 ('MetaData "WindowMaximizedEventData" "SDL.Event" "sdl2-2.5.3.0-FYgxNXfOgR1EIBtbDjNyzg" 'True) (C1 ('MetaCons "WindowMaximizedEventData" 'PrefixI 'True) (S1 ('MetaSel ('Just "windowMaximizedEventWindow") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 Window)))

newtype WindowRestoredEventData Source #

The window has been restored to normal size and position.

Constructors

WindowRestoredEventData 

Fields

Instances

Instances details
Eq WindowRestoredEventData Source # 
Instance details

Defined in SDL.Event

Ord WindowRestoredEventData Source # 
Instance details

Defined in SDL.Event

Show WindowRestoredEventData Source # 
Instance details

Defined in SDL.Event

Generic WindowRestoredEventData Source # 
Instance details

Defined in SDL.Event

Associated Types

type Rep WindowRestoredEventData :: Type -> Type #

type Rep WindowRestoredEventData Source # 
Instance details

Defined in SDL.Event

type Rep WindowRestoredEventData = D1 ('MetaData "WindowRestoredEventData" "SDL.Event" "sdl2-2.5.3.0-FYgxNXfOgR1EIBtbDjNyzg" 'True) (C1 ('MetaCons "WindowRestoredEventData" 'PrefixI 'True) (S1 ('MetaSel ('Just "windowRestoredEventWindow") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 Window)))

newtype WindowGainedMouseFocusEventData Source #

The window has gained mouse focus.

Instances

Instances details
Eq WindowGainedMouseFocusEventData Source # 
Instance details

Defined in SDL.Event

Ord WindowGainedMouseFocusEventData Source # 
Instance details

Defined in SDL.Event

Show WindowGainedMouseFocusEventData Source # 
Instance details

Defined in SDL.Event

Generic WindowGainedMouseFocusEventData Source # 
Instance details

Defined in SDL.Event

Associated Types

type Rep WindowGainedMouseFocusEventData :: Type -> Type #

type Rep WindowGainedMouseFocusEventData Source # 
Instance details

Defined in SDL.Event

type Rep WindowGainedMouseFocusEventData = D1 ('MetaData "WindowGainedMouseFocusEventData" "SDL.Event" "sdl2-2.5.3.0-FYgxNXfOgR1EIBtbDjNyzg" 'True) (C1 ('MetaCons "WindowGainedMouseFocusEventData" 'PrefixI 'True) (S1 ('MetaSel ('Just "windowGainedMouseFocusEventWindow") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 Window)))

newtype WindowLostMouseFocusEventData Source #

The window has lost mouse focus.

Instances

Instances details
Eq WindowLostMouseFocusEventData Source # 
Instance details

Defined in SDL.Event

Ord WindowLostMouseFocusEventData Source # 
Instance details

Defined in SDL.Event

Show WindowLostMouseFocusEventData Source # 
Instance details

Defined in SDL.Event

Generic WindowLostMouseFocusEventData Source # 
Instance details

Defined in SDL.Event

Associated Types

type Rep WindowLostMouseFocusEventData :: Type -> Type #

type Rep WindowLostMouseFocusEventData Source # 
Instance details

Defined in SDL.Event

type Rep WindowLostMouseFocusEventData = D1 ('MetaData "WindowLostMouseFocusEventData" "SDL.Event" "sdl2-2.5.3.0-FYgxNXfOgR1EIBtbDjNyzg" 'True) (C1 ('MetaCons "WindowLostMouseFocusEventData" 'PrefixI 'True) (S1 ('MetaSel ('Just "windowLostMouseFocusEventWindow") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 Window)))

newtype WindowGainedKeyboardFocusEventData Source #

The window has gained keyboard focus.

Instances

Instances details
Eq WindowGainedKeyboardFocusEventData Source # 
Instance details

Defined in SDL.Event

Ord WindowGainedKeyboardFocusEventData Source # 
Instance details

Defined in SDL.Event

Show WindowGainedKeyboardFocusEventData Source # 
Instance details

Defined in SDL.Event

Generic WindowGainedKeyboardFocusEventData Source # 
Instance details

Defined in SDL.Event

Associated Types

type Rep WindowGainedKeyboardFocusEventData :: Type -> Type #

type Rep WindowGainedKeyboardFocusEventData Source # 
Instance details

Defined in SDL.Event

type Rep WindowGainedKeyboardFocusEventData = D1 ('MetaData "WindowGainedKeyboardFocusEventData" "SDL.Event" "sdl2-2.5.3.0-FYgxNXfOgR1EIBtbDjNyzg" 'True) (C1 ('MetaCons "WindowGainedKeyboardFocusEventData" 'PrefixI 'True) (S1 ('MetaSel ('Just "windowGainedKeyboardFocusEventWindow") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 Window)))

newtype WindowLostKeyboardFocusEventData Source #

The window has lost keyboard focus.

Instances

Instances details
Eq WindowLostKeyboardFocusEventData Source # 
Instance details

Defined in SDL.Event

Ord WindowLostKeyboardFocusEventData Source # 
Instance details

Defined in SDL.Event

Show WindowLostKeyboardFocusEventData Source # 
Instance details

Defined in SDL.Event

Generic WindowLostKeyboardFocusEventData Source # 
Instance details

Defined in SDL.Event

Associated Types

type Rep WindowLostKeyboardFocusEventData :: Type -> Type #

type Rep WindowLostKeyboardFocusEventData Source # 
Instance details

Defined in SDL.Event

type Rep WindowLostKeyboardFocusEventData = D1 ('MetaData "WindowLostKeyboardFocusEventData" "SDL.Event" "sdl2-2.5.3.0-FYgxNXfOgR1EIBtbDjNyzg" 'True) (C1 ('MetaCons "WindowLostKeyboardFocusEventData" 'PrefixI 'True) (S1 ('MetaSel ('Just "windowLostKeyboardFocusEventWindow") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 Window)))

newtype WindowClosedEventData Source #

The window manager requests that the window be closed.

Constructors

WindowClosedEventData 

Fields

Instances

Instances details
Eq WindowClosedEventData Source # 
Instance details

Defined in SDL.Event

Ord WindowClosedEventData Source # 
Instance details

Defined in SDL.Event

Show WindowClosedEventData Source # 
Instance details

Defined in SDL.Event

Generic WindowClosedEventData Source # 
Instance details

Defined in SDL.Event

Associated Types

type Rep WindowClosedEventData :: Type -> Type #

type Rep WindowClosedEventData Source # 
Instance details

Defined in SDL.Event

type Rep WindowClosedEventData = D1 ('MetaData "WindowClosedEventData" "SDL.Event" "sdl2-2.5.3.0-FYgxNXfOgR1EIBtbDjNyzg" 'True) (C1 ('MetaCons "WindowClosedEventData" 'PrefixI 'True) (S1 ('MetaSel ('Just "windowClosedEventWindow") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 Window)))

newtype SysWMEventData Source #

A video driver dependent system event

Constructors

SysWMEventData 

Instances

Instances details
Eq SysWMEventData Source # 
Instance details

Defined in SDL.Event

Ord SysWMEventData Source # 
Instance details

Defined in SDL.Event

Show SysWMEventData Source # 
Instance details

Defined in SDL.Event

Generic SysWMEventData Source # 
Instance details

Defined in SDL.Event

Associated Types

type Rep SysWMEventData :: Type -> Type #

type Rep SysWMEventData Source # 
Instance details

Defined in SDL.Event

type Rep SysWMEventData = D1 ('MetaData "SysWMEventData" "SDL.Event" "sdl2-2.5.3.0-FYgxNXfOgR1EIBtbDjNyzg" 'True) (C1 ('MetaCons "SysWMEventData" 'PrefixI 'True) (S1 ('MetaSel ('Just "sysWMEventMsg") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 SysWMmsg)))

Keyboard events

data KeyboardEventData Source #

A keyboard key has been pressed or released.

Constructors

KeyboardEventData 

Fields

Instances

Instances details
Eq KeyboardEventData Source # 
Instance details

Defined in SDL.Event

Ord KeyboardEventData Source # 
Instance details

Defined in SDL.Event

Show KeyboardEventData Source # 
Instance details

Defined in SDL.Event

Generic KeyboardEventData Source # 
Instance details

Defined in SDL.Event

Associated Types

type Rep KeyboardEventData :: Type -> Type #

type Rep KeyboardEventData Source # 
Instance details

Defined in SDL.Event

type Rep KeyboardEventData = D1 ('MetaData "KeyboardEventData" "SDL.Event" "sdl2-2.5.3.0-FYgxNXfOgR1EIBtbDjNyzg" 'False) (C1 ('MetaCons "KeyboardEventData" 'PrefixI 'True) ((S1 ('MetaSel ('Just "keyboardEventWindow") 'NoSourceUnpackedness 'SourceStrict 'DecidedStrict) (Rec0 (Maybe Window)) :*: S1 ('MetaSel ('Just "keyboardEventKeyMotion") 'NoSourceUnpackedness 'SourceStrict 'DecidedStrict) (Rec0 InputMotion)) :*: (S1 ('MetaSel ('Just "keyboardEventRepeat") 'NoSourceUnpackedness 'SourceStrict 'DecidedStrict) (Rec0 Bool) :*: S1 ('MetaSel ('Just "keyboardEventKeysym") 'NoSourceUnpackedness 'SourceStrict 'DecidedStrict) (Rec0 Keysym))))

data TextEditingEventData Source #

Keyboard text editing event information.

Constructors

TextEditingEventData 

Fields

Instances

Instances details
Eq TextEditingEventData Source # 
Instance details

Defined in SDL.Event

Ord TextEditingEventData Source # 
Instance details

Defined in SDL.Event

Show TextEditingEventData Source # 
Instance details

Defined in SDL.Event

Generic TextEditingEventData Source # 
Instance details

Defined in SDL.Event

Associated Types

type Rep TextEditingEventData :: Type -> Type #

type Rep TextEditingEventData Source # 
Instance details

Defined in SDL.Event

type Rep TextEditingEventData = D1 ('MetaData "TextEditingEventData" "SDL.Event" "sdl2-2.5.3.0-FYgxNXfOgR1EIBtbDjNyzg" 'False) (C1 ('MetaCons "TextEditingEventData" 'PrefixI 'True) ((S1 ('MetaSel ('Just "textEditingEventWindow") 'NoSourceUnpackedness 'SourceStrict 'DecidedStrict) (Rec0 (Maybe Window)) :*: S1 ('MetaSel ('Just "textEditingEventText") 'NoSourceUnpackedness 'SourceStrict 'DecidedStrict) (Rec0 Text)) :*: (S1 ('MetaSel ('Just "textEditingEventStart") 'NoSourceUnpackedness 'SourceStrict 'DecidedStrict) (Rec0 Int32) :*: S1 ('MetaSel ('Just "textEditingEventLength") 'NoSourceUnpackedness 'SourceStrict 'DecidedStrict) (Rec0 Int32))))

data TextInputEventData Source #

Keyboard text input event information.

Constructors

TextInputEventData 

Fields

Instances

Instances details
Eq TextInputEventData Source # 
Instance details

Defined in SDL.Event

Ord TextInputEventData Source # 
Instance details

Defined in SDL.Event

Show TextInputEventData Source # 
Instance details

Defined in SDL.Event

Generic TextInputEventData Source # 
Instance details

Defined in SDL.Event

Associated Types

type Rep TextInputEventData :: Type -> Type #

type Rep TextInputEventData Source # 
Instance details

Defined in SDL.Event

type Rep TextInputEventData = D1 ('MetaData "TextInputEventData" "SDL.Event" "sdl2-2.5.3.0-FYgxNXfOgR1EIBtbDjNyzg" 'False) (C1 ('MetaCons "TextInputEventData" 'PrefixI 'True) (S1 ('MetaSel ('Just "textInputEventWindow") 'NoSourceUnpackedness 'SourceStrict 'DecidedStrict) (Rec0 (Maybe Window)) :*: S1 ('MetaSel ('Just "textInputEventText") 'NoSourceUnpackedness 'SourceStrict 'DecidedStrict) (Rec0 Text)))

Mouse events

data MouseMotionEventData Source #

A mouse or pointer device was moved.

Constructors

MouseMotionEventData 

Fields

Instances

Instances details
Eq MouseMotionEventData Source # 
Instance details

Defined in SDL.Event

Ord MouseMotionEventData Source # 
Instance details

Defined in SDL.Event

Show MouseMotionEventData Source # 
Instance details

Defined in SDL.Event

Generic MouseMotionEventData Source # 
Instance details

Defined in SDL.Event

Associated Types

type Rep MouseMotionEventData :: Type -> Type #

type Rep MouseMotionEventData Source # 
Instance details

Defined in SDL.Event

type Rep MouseMotionEventData = D1 ('MetaData "MouseMotionEventData" "SDL.Event" "sdl2-2.5.3.0-FYgxNXfOgR1EIBtbDjNyzg" 'False) (C1 ('MetaCons "MouseMotionEventData" 'PrefixI 'True) ((S1 ('MetaSel ('Just "mouseMotionEventWindow") 'NoSourceUnpackedness 'SourceStrict 'DecidedStrict) (Rec0 (Maybe Window)) :*: S1 ('MetaSel ('Just "mouseMotionEventWhich") 'NoSourceUnpackedness 'SourceStrict 'DecidedStrict) (Rec0 MouseDevice)) :*: (S1 ('MetaSel ('Just "mouseMotionEventState") 'NoSourceUnpackedness 'SourceStrict 'DecidedStrict) (Rec0 [MouseButton]) :*: (S1 ('MetaSel ('Just "mouseMotionEventPos") 'NoSourceUnpackedness 'SourceStrict 'DecidedStrict) (Rec0 (Point V2 Int32)) :*: S1 ('MetaSel ('Just "mouseMotionEventRelMotion") 'NoSourceUnpackedness 'SourceStrict 'DecidedStrict) (Rec0 (V2 Int32))))))

data MouseButtonEventData Source #

A mouse or pointer device button was pressed or released.

Constructors

MouseButtonEventData 

Fields

Instances

Instances details
Eq MouseButtonEventData Source # 
Instance details

Defined in SDL.Event

Ord MouseButtonEventData Source # 
Instance details

Defined in SDL.Event

Show MouseButtonEventData Source # 
Instance details

Defined in SDL.Event

Generic MouseButtonEventData Source # 
Instance details

Defined in SDL.Event

Associated Types

type Rep MouseButtonEventData :: Type -> Type #

type Rep MouseButtonEventData Source # 
Instance details

Defined in SDL.Event

type Rep MouseButtonEventData = D1 ('MetaData "MouseButtonEventData" "SDL.Event" "sdl2-2.5.3.0-FYgxNXfOgR1EIBtbDjNyzg" 'False) (C1 ('MetaCons "MouseButtonEventData" 'PrefixI 'True) ((S1 ('MetaSel ('Just "mouseButtonEventWindow") 'NoSourceUnpackedness 'SourceStrict 'DecidedStrict) (Rec0 (Maybe Window)) :*: (S1 ('MetaSel ('Just "mouseButtonEventMotion") 'NoSourceUnpackedness 'SourceStrict 'DecidedStrict) (Rec0 InputMotion) :*: S1 ('MetaSel ('Just "mouseButtonEventWhich") 'NoSourceUnpackedness 'SourceStrict 'DecidedStrict) (Rec0 MouseDevice))) :*: (S1 ('MetaSel ('Just "mouseButtonEventButton") 'NoSourceUnpackedness 'SourceStrict 'DecidedStrict) (Rec0 MouseButton) :*: (S1 ('MetaSel ('Just "mouseButtonEventClicks") 'NoSourceUnpackedness 'SourceStrict 'DecidedStrict) (Rec0 Word8) :*: S1 ('MetaSel ('Just "mouseButtonEventPos") 'NoSourceUnpackedness 'SourceStrict 'DecidedStrict) (Rec0 (Point V2 Int32))))))

data MouseWheelEventData Source #

Mouse wheel event information.

Constructors

MouseWheelEventData 

Fields

Instances

Instances details
Eq MouseWheelEventData Source # 
Instance details

Defined in SDL.Event

Ord MouseWheelEventData Source # 
Instance details

Defined in SDL.Event

Show MouseWheelEventData Source # 
Instance details

Defined in SDL.Event

Generic MouseWheelEventData Source # 
Instance details

Defined in SDL.Event

Associated Types

type Rep MouseWheelEventData :: Type -> Type #

type Rep MouseWheelEventData Source # 
Instance details

Defined in SDL.Event

type Rep MouseWheelEventData = D1 ('MetaData "MouseWheelEventData" "SDL.Event" "sdl2-2.5.3.0-FYgxNXfOgR1EIBtbDjNyzg" 'False) (C1 ('MetaCons "MouseWheelEventData" 'PrefixI 'True) ((S1 ('MetaSel ('Just "mouseWheelEventWindow") 'NoSourceUnpackedness 'SourceStrict 'DecidedStrict) (Rec0 (Maybe Window)) :*: S1 ('MetaSel ('Just "mouseWheelEventWhich") 'NoSourceUnpackedness 'SourceStrict 'DecidedStrict) (Rec0 MouseDevice)) :*: (S1 ('MetaSel ('Just "mouseWheelEventPos") 'NoSourceUnpackedness 'SourceStrict 'DecidedStrict) (Rec0 (V2 Int32)) :*: S1 ('MetaSel ('Just "mouseWheelEventDirection") 'NoSourceUnpackedness 'SourceStrict 'DecidedStrict) (Rec0 MouseScrollDirection))))

Joystick events

data JoyAxisEventData Source #

Joystick axis motion event information

Constructors

JoyAxisEventData 

Fields

Instances

Instances details
Eq JoyAxisEventData Source # 
Instance details

Defined in SDL.Event

Ord JoyAxisEventData Source # 
Instance details

Defined in SDL.Event

Show JoyAxisEventData Source # 
Instance details

Defined in SDL.Event

Generic JoyAxisEventData Source # 
Instance details

Defined in SDL.Event

Associated Types

type Rep JoyAxisEventData :: Type -> Type #

type Rep JoyAxisEventData Source # 
Instance details

Defined in SDL.Event

type Rep JoyAxisEventData = D1 ('MetaData "JoyAxisEventData" "SDL.Event" "sdl2-2.5.3.0-FYgxNXfOgR1EIBtbDjNyzg" 'False) (C1 ('MetaCons "JoyAxisEventData" 'PrefixI 'True) (S1 ('MetaSel ('Just "joyAxisEventWhich") 'NoSourceUnpackedness 'SourceStrict 'DecidedStrict) (Rec0 JoystickID) :*: (S1 ('MetaSel ('Just "joyAxisEventAxis") 'NoSourceUnpackedness 'SourceStrict 'DecidedStrict) (Rec0 Word8) :*: S1 ('MetaSel ('Just "joyAxisEventValue") 'NoSourceUnpackedness 'SourceStrict 'DecidedStrict) (Rec0 Int16))))

data JoyBallEventData Source #

Joystick trackball motion event information.

Constructors

JoyBallEventData 

Fields

Instances

Instances details
Eq JoyBallEventData Source # 
Instance details

Defined in SDL.Event

Ord JoyBallEventData Source # 
Instance details

Defined in SDL.Event

Show JoyBallEventData Source # 
Instance details

Defined in SDL.Event

Generic JoyBallEventData Source # 
Instance details

Defined in SDL.Event

Associated Types

type Rep JoyBallEventData :: Type -> Type #

type Rep JoyBallEventData Source # 
Instance details

Defined in SDL.Event

type Rep JoyBallEventData = D1 ('MetaData "JoyBallEventData" "SDL.Event" "sdl2-2.5.3.0-FYgxNXfOgR1EIBtbDjNyzg" 'False) (C1 ('MetaCons "JoyBallEventData" 'PrefixI 'True) (S1 ('MetaSel ('Just "joyBallEventWhich") 'NoSourceUnpackedness 'SourceStrict 'DecidedStrict) (Rec0 JoystickID) :*: (S1 ('MetaSel ('Just "joyBallEventBall") 'NoSourceUnpackedness 'SourceStrict 'DecidedStrict) (Rec0 Word8) :*: S1 ('MetaSel ('Just "joyBallEventRelMotion") 'NoSourceUnpackedness 'SourceStrict 'DecidedStrict) (Rec0 (V2 Int16)))))

data JoyHatEventData Source #

Joystick hat position change event information

Constructors

JoyHatEventData 

Fields

Instances

Instances details
Eq JoyHatEventData Source # 
Instance details

Defined in SDL.Event

Ord JoyHatEventData Source # 
Instance details

Defined in SDL.Event

Show JoyHatEventData Source # 
Instance details

Defined in SDL.Event

Generic JoyHatEventData Source # 
Instance details

Defined in SDL.Event

Associated Types

type Rep JoyHatEventData :: Type -> Type #

type Rep JoyHatEventData Source # 
Instance details

Defined in SDL.Event

type Rep JoyHatEventData = D1 ('MetaData "JoyHatEventData" "SDL.Event" "sdl2-2.5.3.0-FYgxNXfOgR1EIBtbDjNyzg" 'False) (C1 ('MetaCons "JoyHatEventData" 'PrefixI 'True) (S1 ('MetaSel ('Just "joyHatEventWhich") 'NoSourceUnpackedness 'SourceStrict 'DecidedStrict) (Rec0 JoystickID) :*: (S1 ('MetaSel ('Just "joyHatEventHat") 'NoSourceUnpackedness 'SourceStrict 'DecidedStrict) (Rec0 Word8) :*: S1 ('MetaSel ('Just "joyHatEventValue") 'NoSourceUnpackedness 'SourceStrict 'DecidedStrict) (Rec0 JoyHatPosition))))

data JoyButtonEventData Source #

Joystick button event information.

Constructors

JoyButtonEventData 

Fields

Instances

Instances details
Eq JoyButtonEventData Source # 
Instance details

Defined in SDL.Event

Ord JoyButtonEventData Source # 
Instance details

Defined in SDL.Event

Show JoyButtonEventData Source # 
Instance details

Defined in SDL.Event

Generic JoyButtonEventData Source # 
Instance details

Defined in SDL.Event

Associated Types

type Rep JoyButtonEventData :: Type -> Type #

type Rep JoyButtonEventData Source # 
Instance details

Defined in SDL.Event

type Rep JoyButtonEventData = D1 ('MetaData "JoyButtonEventData" "SDL.Event" "sdl2-2.5.3.0-FYgxNXfOgR1EIBtbDjNyzg" 'False) (C1 ('MetaCons "JoyButtonEventData" 'PrefixI 'True) (S1 ('MetaSel ('Just "joyButtonEventWhich") 'NoSourceUnpackedness 'SourceStrict 'DecidedStrict) (Rec0 JoystickID) :*: (S1 ('MetaSel ('Just "joyButtonEventButton") 'NoSourceUnpackedness 'SourceStrict 'DecidedStrict) (Rec0 Word8) :*: S1 ('MetaSel ('Just "joyButtonEventState") 'NoSourceUnpackedness 'SourceStrict 'DecidedStrict) (Rec0 JoyButtonState))))

data JoyDeviceEventData Source #

Joystick device event information.

Constructors

JoyDeviceEventData 

Fields

Instances

Instances details
Eq JoyDeviceEventData Source # 
Instance details

Defined in SDL.Event

Ord JoyDeviceEventData Source # 
Instance details

Defined in SDL.Event

Show JoyDeviceEventData Source # 
Instance details

Defined in SDL.Event

Generic JoyDeviceEventData Source # 
Instance details

Defined in SDL.Event

Associated Types

type Rep JoyDeviceEventData :: Type -> Type #

type Rep JoyDeviceEventData Source # 
Instance details

Defined in SDL.Event

type Rep JoyDeviceEventData = D1 ('MetaData "JoyDeviceEventData" "SDL.Event" "sdl2-2.5.3.0-FYgxNXfOgR1EIBtbDjNyzg" 'False) (C1 ('MetaCons "JoyDeviceEventData" 'PrefixI 'True) (S1 ('MetaSel ('Just "joyDeviceEventConnection") 'NoSourceUnpackedness 'SourceStrict 'DecidedStrict) (Rec0 JoyDeviceConnection) :*: S1 ('MetaSel ('Just "joyDeviceEventWhich") 'NoSourceUnpackedness 'SourceStrict 'DecidedStrict) (Rec0 Int32)))

Controller events

data ControllerAxisEventData Source #

Game controller axis motion event information.

Constructors

ControllerAxisEventData 

Fields

Instances

Instances details
Eq ControllerAxisEventData Source # 
Instance details

Defined in SDL.Event

Ord ControllerAxisEventData Source # 
Instance details

Defined in SDL.Event

Show ControllerAxisEventData Source # 
Instance details

Defined in SDL.Event

Generic ControllerAxisEventData Source # 
Instance details

Defined in SDL.Event

Associated Types

type Rep ControllerAxisEventData :: Type -> Type #

type Rep ControllerAxisEventData Source # 
Instance details

Defined in SDL.Event

type Rep ControllerAxisEventData = D1 ('MetaData "ControllerAxisEventData" "SDL.Event" "sdl2-2.5.3.0-FYgxNXfOgR1EIBtbDjNyzg" 'False) (C1 ('MetaCons "ControllerAxisEventData" 'PrefixI 'True) (S1 ('MetaSel ('Just "controllerAxisEventWhich") 'NoSourceUnpackedness 'SourceStrict 'DecidedStrict) (Rec0 JoystickID) :*: (S1 ('MetaSel ('Just "controllerAxisEventAxis") 'NoSourceUnpackedness 'SourceStrict 'DecidedStrict) (Rec0 Word8) :*: S1 ('MetaSel ('Just "controllerAxisEventValue") 'NoSourceUnpackedness 'SourceStrict 'DecidedStrict) (Rec0 Int16))))

data ControllerButtonEventData Source #

Game controller button event information

Constructors

ControllerButtonEventData 

Fields

Instances

Instances details
Eq ControllerButtonEventData Source # 
Instance details

Defined in SDL.Event

Ord ControllerButtonEventData Source # 
Instance details

Defined in SDL.Event

Show ControllerButtonEventData Source # 
Instance details

Defined in SDL.Event

Generic ControllerButtonEventData Source # 
Instance details

Defined in SDL.Event

Associated Types

type Rep ControllerButtonEventData :: Type -> Type #

type Rep ControllerButtonEventData Source # 
Instance details

Defined in SDL.Event

type Rep ControllerButtonEventData = D1 ('MetaData "ControllerButtonEventData" "SDL.Event" "sdl2-2.5.3.0-FYgxNXfOgR1EIBtbDjNyzg" 'False) (C1 ('MetaCons "ControllerButtonEventData" 'PrefixI 'True) (S1 ('MetaSel ('Just "controllerButtonEventWhich") 'NoSourceUnpackedness 'SourceStrict 'DecidedStrict) (Rec0 JoystickID) :*: (S1 ('MetaSel ('Just "controllerButtonEventButton") 'NoSourceUnpackedness 'SourceStrict 'DecidedStrict) (Rec0 ControllerButton) :*: S1 ('MetaSel ('Just "controllerButtonEventState") 'NoSourceUnpackedness 'SourceStrict 'DecidedStrict) (Rec0 ControllerButtonState))))

data ControllerDeviceEventData Source #

Controller device event information

Constructors

ControllerDeviceEventData 

Fields

Instances

Instances details
Eq ControllerDeviceEventData Source # 
Instance details

Defined in SDL.Event

Ord ControllerDeviceEventData Source # 
Instance details

Defined in SDL.Event

Show ControllerDeviceEventData Source # 
Instance details

Defined in SDL.Event

Generic ControllerDeviceEventData Source # 
Instance details

Defined in SDL.Event

Associated Types

type Rep ControllerDeviceEventData :: Type -> Type #

type Rep ControllerDeviceEventData Source # 
Instance details

Defined in SDL.Event

type Rep ControllerDeviceEventData = D1 ('MetaData "ControllerDeviceEventData" "SDL.Event" "sdl2-2.5.3.0-FYgxNXfOgR1EIBtbDjNyzg" 'False) (C1 ('MetaCons "ControllerDeviceEventData" 'PrefixI 'True) (S1 ('MetaSel ('Just "controllerDeviceEventConnection") 'NoSourceUnpackedness 'SourceStrict 'DecidedStrict) (Rec0 ControllerDeviceConnection) :*: S1 ('MetaSel ('Just "controllerDeviceEventWhich") 'NoSourceUnpackedness 'SourceStrict 'DecidedStrict) (Rec0 Int32)))

Audio events

data AudioDeviceEventData Source #

Constructors

AudioDeviceEventData 

Fields

Instances

Instances details
Eq AudioDeviceEventData Source # 
Instance details

Defined in SDL.Event

Ord AudioDeviceEventData Source # 
Instance details

Defined in SDL.Event

Show AudioDeviceEventData Source # 
Instance details

Defined in SDL.Event

Generic AudioDeviceEventData Source # 
Instance details

Defined in SDL.Event

Associated Types

type Rep AudioDeviceEventData :: Type -> Type #

type Rep AudioDeviceEventData Source # 
Instance details

Defined in SDL.Event

type Rep AudioDeviceEventData = D1 ('MetaData "AudioDeviceEventData" "SDL.Event" "sdl2-2.5.3.0-FYgxNXfOgR1EIBtbDjNyzg" 'False) (C1 ('MetaCons "AudioDeviceEventData" 'PrefixI 'True) (S1 ('MetaSel ('Just "audioDeviceEventIsAddition") 'NoSourceUnpackedness 'SourceStrict 'DecidedStrict) (Rec0 Bool) :*: (S1 ('MetaSel ('Just "audioDeviceEventWhich") 'NoSourceUnpackedness 'SourceStrict 'DecidedStrict) (Rec0 Word32) :*: S1 ('MetaSel ('Just "audioDeviceEventIsCapture") 'NoSourceUnpackedness 'SourceStrict 'DecidedStrict) (Rec0 Bool))))

User events

data UserEventData Source #

Event data for application-defined events.

Constructors

UserEventData 

Fields

Instances

Instances details
Eq UserEventData Source # 
Instance details

Defined in SDL.Event

Ord UserEventData Source # 
Instance details

Defined in SDL.Event

Show UserEventData Source # 
Instance details

Defined in SDL.Event

Generic UserEventData Source # 
Instance details

Defined in SDL.Event

Associated Types

type Rep UserEventData :: Type -> Type #

type Rep UserEventData Source # 
Instance details

Defined in SDL.Event

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

Touch events

data TouchFingerEventData Source #

Finger touch event information.

Constructors

TouchFingerEventData 

Fields

Instances

Instances details
Eq TouchFingerEventData Source # 
Instance details

Defined in SDL.Event

Ord TouchFingerEventData Source # 
Instance details

Defined in SDL.Event

Show TouchFingerEventData Source # 
Instance details

Defined in SDL.Event

Generic TouchFingerEventData Source # 
Instance details

Defined in SDL.Event

Associated Types

type Rep TouchFingerEventData :: Type -> Type #

type Rep TouchFingerEventData Source # 
Instance details

Defined in SDL.Event

type Rep TouchFingerEventData = D1 ('MetaData "TouchFingerEventData" "SDL.Event" "sdl2-2.5.3.0-FYgxNXfOgR1EIBtbDjNyzg" 'False) (C1 ('MetaCons "TouchFingerEventData" 'PrefixI 'True) ((S1 ('MetaSel ('Just "touchFingerEventTouchID") 'NoSourceUnpackedness 'SourceStrict 'DecidedStrict) (Rec0 TouchID) :*: S1 ('MetaSel ('Just "touchFingerEventFingerID") 'NoSourceUnpackedness 'SourceStrict 'DecidedStrict) (Rec0 FingerID)) :*: (S1 ('MetaSel ('Just "touchFingerEventMotion") 'NoSourceUnpackedness 'SourceStrict 'DecidedStrict) (Rec0 InputMotion) :*: (S1 ('MetaSel ('Just "touchFingerEventPos") 'NoSourceUnpackedness 'SourceStrict 'DecidedStrict) (Rec0 (Point V2 CFloat)) :*: S1 ('MetaSel ('Just "touchFingerEventPressure") 'NoSourceUnpackedness 'SourceStrict 'DecidedStrict) (Rec0 CFloat)))))

data TouchFingerMotionEventData Source #

Finger motion event information.

Constructors

TouchFingerMotionEventData 

Fields

Instances

Instances details
Eq TouchFingerMotionEventData Source # 
Instance details

Defined in SDL.Event

Ord TouchFingerMotionEventData Source # 
Instance details

Defined in SDL.Event

Show TouchFingerMotionEventData Source # 
Instance details

Defined in SDL.Event

Generic TouchFingerMotionEventData Source # 
Instance details

Defined in SDL.Event

Associated Types

type Rep TouchFingerMotionEventData :: Type -> Type #

type Rep TouchFingerMotionEventData Source # 
Instance details

Defined in SDL.Event

type Rep TouchFingerMotionEventData = D1 ('MetaData "TouchFingerMotionEventData" "SDL.Event" "sdl2-2.5.3.0-FYgxNXfOgR1EIBtbDjNyzg" 'False) (C1 ('MetaCons "TouchFingerMotionEventData" 'PrefixI 'True) ((S1 ('MetaSel ('Just "touchFingerMotionEventTouchID") 'NoSourceUnpackedness 'SourceStrict 'DecidedStrict) (Rec0 TouchID) :*: S1 ('MetaSel ('Just "touchFingerMotionEventFingerID") 'NoSourceUnpackedness 'SourceStrict 'DecidedStrict) (Rec0 FingerID)) :*: (S1 ('MetaSel ('Just "touchFingerMotionEventPos") 'NoSourceUnpackedness 'SourceStrict 'DecidedStrict) (Rec0 (Point V2 CFloat)) :*: (S1 ('MetaSel ('Just "touchFingerMotionEventRelMotion") 'NoSourceUnpackedness 'SourceStrict 'DecidedStrict) (Rec0 (V2 CFloat)) :*: S1 ('MetaSel ('Just "touchFingerMotionEventPressure") 'NoSourceUnpackedness 'SourceStrict 'DecidedStrict) (Rec0 CFloat)))))

Gesture events

data MultiGestureEventData Source #

Multiple finger gesture event information

Constructors

MultiGestureEventData 

Fields

Instances

Instances details
Eq MultiGestureEventData Source # 
Instance details

Defined in SDL.Event

Ord MultiGestureEventData Source # 
Instance details

Defined in SDL.Event

Show MultiGestureEventData Source # 
Instance details

Defined in SDL.Event

Generic MultiGestureEventData Source # 
Instance details

Defined in SDL.Event

Associated Types

type Rep MultiGestureEventData :: Type -> Type #

type Rep MultiGestureEventData Source # 
Instance details

Defined in SDL.Event

type Rep MultiGestureEventData = D1 ('MetaData "MultiGestureEventData" "SDL.Event" "sdl2-2.5.3.0-FYgxNXfOgR1EIBtbDjNyzg" 'False) (C1 ('MetaCons "MultiGestureEventData" 'PrefixI 'True) ((S1 ('MetaSel ('Just "multiGestureEventTouchID") 'NoSourceUnpackedness 'SourceStrict 'DecidedStrict) (Rec0 TouchID) :*: S1 ('MetaSel ('Just "multiGestureEventDTheta") 'NoSourceUnpackedness 'SourceStrict 'DecidedStrict) (Rec0 CFloat)) :*: (S1 ('MetaSel ('Just "multiGestureEventDDist") 'NoSourceUnpackedness 'SourceStrict 'DecidedStrict) (Rec0 CFloat) :*: (S1 ('MetaSel ('Just "multiGestureEventPos") 'NoSourceUnpackedness 'SourceStrict 'DecidedStrict) (Rec0 (Point V2 CFloat)) :*: S1 ('MetaSel ('Just "multiGestureEventNumFingers") 'NoSourceUnpackedness 'SourceStrict 'DecidedStrict) (Rec0 Word16)))))

data DollarGestureEventData Source #

Complex gesture event information.

Constructors

DollarGestureEventData 

Fields

Instances

Instances details
Eq DollarGestureEventData Source # 
Instance details

Defined in SDL.Event

Ord DollarGestureEventData Source # 
Instance details

Defined in SDL.Event

Show DollarGestureEventData Source # 
Instance details

Defined in SDL.Event

Generic DollarGestureEventData Source # 
Instance details

Defined in SDL.Event

Associated Types

type Rep DollarGestureEventData :: Type -> Type #

type Rep DollarGestureEventData Source # 
Instance details

Defined in SDL.Event

type Rep DollarGestureEventData = D1 ('MetaData "DollarGestureEventData" "SDL.Event" "sdl2-2.5.3.0-FYgxNXfOgR1EIBtbDjNyzg" 'False) (C1 ('MetaCons "DollarGestureEventData" 'PrefixI 'True) ((S1 ('MetaSel ('Just "dollarGestureEventTouchID") 'NoSourceUnpackedness 'SourceStrict 'DecidedStrict) (Rec0 TouchID) :*: S1 ('MetaSel ('Just "dollarGestureEventGestureID") 'NoSourceUnpackedness 'SourceStrict 'DecidedStrict) (Rec0 GestureID)) :*: (S1 ('MetaSel ('Just "dollarGestureEventNumFingers") 'NoSourceUnpackedness 'SourceStrict 'DecidedStrict) (Rec0 Word32) :*: (S1 ('MetaSel ('Just "dollarGestureEventError") 'NoSourceUnpackedness 'SourceStrict 'DecidedStrict) (Rec0 CFloat) :*: S1 ('MetaSel ('Just "dollarGestureEventPos") 'NoSourceUnpackedness 'SourceStrict 'DecidedStrict) (Rec0 (Point V2 CFloat))))))

Drag and drop events

newtype DropEventData Source #

An event used to request a file open by the system

Constructors

DropEventData 

Fields

Instances

Instances details
Eq DropEventData Source # 
Instance details

Defined in SDL.Event

Ord DropEventData Source # 
Instance details

Defined in SDL.Event

Show DropEventData Source # 
Instance details

Defined in SDL.Event

Generic DropEventData Source # 
Instance details

Defined in SDL.Event

Associated Types

type Rep DropEventData :: Type -> Type #

type Rep DropEventData Source # 
Instance details

Defined in SDL.Event

type Rep DropEventData = D1 ('MetaData "DropEventData" "SDL.Event" "sdl2-2.5.3.0-FYgxNXfOgR1EIBtbDjNyzg" 'True) (C1 ('MetaCons "DropEventData" 'PrefixI 'True) (S1 ('MetaSel ('Just "dropEventFile") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 CString)))

Unknown events

newtype UnknownEventData Source #

SDL reported an unknown event type.

Constructors

UnknownEventData 

Fields

Auxiliary event data

data InputMotion Source #

Constructors

Released 
Pressed 

Instances

Instances details
Bounded InputMotion Source # 
Instance details

Defined in SDL.Event

Enum InputMotion Source # 
Instance details

Defined in SDL.Event

Eq InputMotion Source # 
Instance details

Defined in SDL.Event

Data InputMotion Source # 
Instance details

Defined in SDL.Event

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 :: forall r r'. (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 # 
Instance details

Defined in SDL.Event

Read InputMotion Source # 
Instance details

Defined in SDL.Event

Show InputMotion Source # 
Instance details

Defined in SDL.Event

Generic InputMotion Source # 
Instance details

Defined in SDL.Event

Associated Types

type Rep InputMotion :: Type -> Type #

type Rep InputMotion Source # 
Instance details

Defined in SDL.Event

type Rep InputMotion = D1 ('MetaData "InputMotion" "SDL.Event" "sdl2-2.5.3.0-FYgxNXfOgR1EIBtbDjNyzg" 'False) (C1 ('MetaCons "Released" 'PrefixI 'False) (U1 :: Type -> Type) :+: C1 ('MetaCons "Pressed" 'PrefixI 'False) (U1 :: Type -> Type))

data MouseButton Source #

Constructors

ButtonLeft 
ButtonMiddle 
ButtonRight 
ButtonX1 
ButtonX2 
ButtonExtra !Int

An unknown mouse button.

Instances

Instances details
Eq MouseButton Source # 
Instance details

Defined in SDL.Input.Mouse

Data MouseButton Source # 
Instance details

Defined in SDL.Input.Mouse

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 :: forall r r'. (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 # 
Instance details

Defined in SDL.Input.Mouse

Read MouseButton Source # 
Instance details

Defined in SDL.Input.Mouse

Show MouseButton Source # 
Instance details

Defined in SDL.Input.Mouse

Generic MouseButton Source # 
Instance details

Defined in SDL.Input.Mouse

Associated Types

type Rep MouseButton :: Type -> Type #

ToNumber MouseButton Word8 Source # 
Instance details

Defined in SDL.Input.Mouse

FromNumber MouseButton Word8 Source # 
Instance details

Defined in SDL.Input.Mouse

type Rep MouseButton Source # 
Instance details

Defined in SDL.Input.Mouse

type Rep MouseButton = D1 ('MetaData "MouseButton" "SDL.Input.Mouse" "sdl2-2.5.3.0-FYgxNXfOgR1EIBtbDjNyzg" 'False) ((C1 ('MetaCons "ButtonLeft" 'PrefixI 'False) (U1 :: Type -> Type) :+: (C1 ('MetaCons "ButtonMiddle" 'PrefixI 'False) (U1 :: Type -> Type) :+: C1 ('MetaCons "ButtonRight" 'PrefixI 'False) (U1 :: Type -> Type))) :+: (C1 ('MetaCons "ButtonX1" 'PrefixI 'False) (U1 :: Type -> Type) :+: (C1 ('MetaCons "ButtonX2" 'PrefixI 'False) (U1 :: Type -> Type) :+: C1 ('MetaCons "ButtonExtra" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'SourceStrict 'DecidedStrict) (Rec0 Int)))))