SDL-0.4.0: Binding to libSDLSource codeContentsIndex
Graphics.UI.SDL.Events
Portabilityportable
Stabilityprovisional
Maintainerlemmih@gmail.com
Description
Synopsis
data Event
= NoEvent
| GotFocus [Focus]
| LostFocus [Focus]
| KeyDown !Keysym
| KeyUp !Keysym
| MouseMotion !Word16 !Word16 !Word16 !Word16
| MouseButtonDown !Word16 !Word16 !MouseButton
| MouseButtonUp !Word16 !Word16 !MouseButton
| JoyAxisMotion !Word8 !Word8 !Int16
| JoyBallMotion !Word8 !Word8 !Int16 !Int16
| JoyHatMotion !Word8 !Word8 !Word8
| JoyButtonDown !Word8 !Word8
| JoyButtonUp !Word8 !Word8
| VideoResize !Int !Int
| VideoExpose
| Quit
| User !UserEventID !Int !(Ptr ()) !(Ptr ())
| Unknown
data SDLEvent
= SDLNoEvent
| SDLActiveEvent
| SDLKeyDown
| SDLKeyUp
| SDLMouseMotion
| SDLMouseButtonDown
| SDLMouseButtonUp
| SDLJoyAxisMotion
| SDLJoyBallMotion
| SDLJoyHatMotion
| SDLJoyButtonDown
| SDLJoyButtonUp
| SDLQuit
| SDLSysWMEvent
| SDLVideoResize
| SDLVideoExpose
| SDLUserEvent Word8
| SDLNumEvents
data UserEventID
= UID0
| UID1
| UID2
| UID3
| UID4
| UID5
| UID6
| UID7
data MouseButton
= ButtonLeft
| ButtonMiddle
| ButtonRight
| ButtonWheelUp
| ButtonWheelDown
data Focus
= MouseFocus
| InputFocus
| ApplicationFocus
toSafePtr :: Typeable a => a -> IO SafePtr
tryFromSafePtr :: Typeable a => SafePtr -> IO (Maybe a)
fromSafePtr :: Typeable a => SafePtr -> IO a
typeOfSafePtr :: SafePtr -> IO TypeRep
enableKeyRepeat :: Int -> Int -> IO Bool
enableUnicode :: Bool -> IO ()
queryUnicodeState :: IO Bool
getKeyName :: SDLKey -> String
getMouseState :: IO (Int, Int, [MouseButton])
getRelativeMouseState :: IO (Int, Int, [MouseButton])
getModState :: IO [Modifier]
setModState :: [Modifier] -> IO ()
tryPushEvent :: Event -> IO Bool
pushEvent :: Event -> IO ()
pollEvent :: IO Event
waitEvent :: IO Event
waitEventBlocking :: IO Event
pumpEvents :: IO ()
enableEvent :: SDLEvent -> Bool -> IO ()
queryEventState :: SDLEvent -> IO Bool
getAppState :: IO [Focus]
Documentation
data Event Source
High level event structure.
Constructors
NoEvent
GotFocus [Focus]
LostFocus [Focus]
KeyDown !Keysym
KeyUp !Keysym
MouseMotion !Word16 !Word16 !Word16 !Word16
MouseButtonDown !Word16 !Word16 !MouseButton
MouseButtonUp !Word16 !Word16 !MouseButton
JoyAxisMotion !Word8 !Word8 !Int16device index, axis index, axis value.
JoyBallMotion !Word8 !Word8 !Int16 !Int16device index, trackball index, relative motion.
JoyHatMotion !Word8 !Word8 !Word8device index, hat index, hat position.
JoyButtonDown !Word8 !Word8device index, button index.
JoyButtonUp !Word8 !Word8device index, button index.
VideoResize !Int !IntWhen Resizable is passed as a flag to setVideoMode the user is allowed to resize the applications window. When the window is resized an VideoResize is reported, with the new window width and height values. When an VideoResize is recieved the window should be resized to the new dimensions using setVideoMode.
VideoExposeA VideoExpose event is triggered when the screen has been modified outside of the application, usually by the window manager and needs to be redrawn.
Quit
User !UserEventID !Int !(Ptr ()) !(Ptr ())
Unknown
show/hide Instances
data SDLEvent Source
Low level event structure keeping a one-to-one relation with the C event structure.
Constructors
SDLNoEvent
SDLActiveEvent
SDLKeyDown
SDLKeyUp
SDLMouseMotion
SDLMouseButtonDown
SDLMouseButtonUp
SDLJoyAxisMotion
SDLJoyBallMotion
SDLJoyHatMotion
SDLJoyButtonDown
SDLJoyButtonUp
SDLQuit
SDLSysWMEvent
SDLVideoResize
SDLVideoExpose
SDLUserEvent Word8
SDLNumEvents
show/hide Instances
data UserEventID Source
Typed user events ranging from 0 to 7
Constructors
UID0
UID1
UID2
UID3
UID4
UID5
UID6
UID7
show/hide Instances
data MouseButton Source
Constructors
ButtonLeft
ButtonMiddle
ButtonRight
ButtonWheelUp
ButtonWheelDown
show/hide Instances
data Focus Source
Constructors
MouseFocus
InputFocus
ApplicationFocus
show/hide Instances
toSafePtr :: Typeable a => a -> IO SafePtrSource
Constructs a safe pointer from an arbitrary value.
tryFromSafePtr :: Typeable a => SafePtr -> IO (Maybe a)Source
Get object from a safe pointer. Nothing on type mismatch.
fromSafePtr :: Typeable a => SafePtr -> IO aSource
Get object from a safe pointer. Throws an exception on type mismatch.
typeOfSafePtr :: SafePtr -> IO TypeRepSource
Return the type of the object the safe pointer was created from.
enableKeyRepeatSource
:: IntInitial delay. 0 to disable.
-> IntInterval.
-> IO Bool
Sets keyboard repeat rate. Returns False on error.
enableUnicode :: Bool -> IO ()Source
Enables or disables unicode translation.
queryUnicodeState :: IO BoolSource
Returns the current state of unicode translation. See also enableUnicode.
getKeyName :: SDLKey -> StringSource
Gets the name of an SDL virtual keysym.
getMouseState :: IO (Int, Int, [MouseButton])Source
Retrieves the current state of the mouse. Returns (X position, Y position, pressed buttons).
getRelativeMouseState :: IO (Int, Int, [MouseButton])Source
Retrieve the current state of the mouse. Like getMouseState except that X and Y are set to the change since last call to getRelativeMouseState.
getModState :: IO [Modifier]Source
Gets the state of modifier keys.
setModState :: [Modifier] -> IO ()Source
Sets the internal state of modifier keys.
tryPushEvent :: Event -> IO BoolSource
Pushes an event onto the event queue. Returns False on error.
pushEvent :: Event -> IO ()Source
Pushes an event onto the event queue. Throws an exception on error.
pollEvent :: IO EventSource
Polls for currently pending events.
waitEvent :: IO EventSource
Waits indefinitely for the next available event.
waitEventBlocking :: IO EventSource
Waits indefinitely for the next available event. Blocks Haskell threads.
pumpEvents :: IO ()Source
Pumps the event loop, gathering events from the input devices.
enableEvent :: SDLEvent -> Bool -> IO ()Source
Enable or disable events from being processed.
queryEventState :: SDLEvent -> IO BoolSource
Checks current state of a event. See also enableEvent.
getAppState :: IO [Focus]Source
Gets the state of the application.
Produced by Haddock version 0.8