Safe Haskell | Safe-Inferred |
---|---|
Language | Haskell2010 |
Synopsis
- getModState :: (Functor m, MonadIO m) => m KeyModifier
- data KeyModifier = KeyModifier {}
- getKeyboardState :: MonadIO m => m (Scancode -> Bool)
- startTextInput :: MonadIO m => Rect -> m ()
- stopTextInput :: MonadIO m => m ()
- hasScreenKeyboardSupport :: MonadIO m => m Bool
- isScreenKeyboardShown :: MonadIO m => Window -> m Bool
- getScancodeName :: MonadIO m => Scancode -> m String
- newtype Scancode = Scancode {}
- newtype Keycode = Keycode {}
- data Keysym = Keysym {}
- module SDL.Input.Keyboard.Codes
Keyboard Modifiers
getModState :: (Functor m, MonadIO m) => m KeyModifier Source #
Get the current key modifier state for the keyboard. The key modifier state is a mask special keys that are held down.
See SDL_GetModState
for C documentation.
data KeyModifier Source #
Information about which keys are currently held down. Use getModState
to generate this information.
Instances
getKeyboardState :: MonadIO m => m (Scancode -> Bool) Source #
Get a snapshot of the current state of the keyboard.
This computation generates a mapping from Scancode
to Bool
- evaluating the function at specific Scancode
s will inform you as to whether or not that key was held down when getKeyboardState
was called.
See SDL_GetKeyboardState
for C documentation.
Text Input
startTextInput :: MonadIO m => Rect -> m () Source #
Set the rectangle used to type text inputs and start accepting text input events.
See SDL_StartTextInput
for C documentation.
stopTextInput :: MonadIO m => m () Source #
Stop receiving any text input events.
See SDL_StopTextInput
for C documentation.
Screen Keyboard
hasScreenKeyboardSupport :: MonadIO m => m Bool Source #
Check whether the platform has screen keyboard support.
See SDL_HasScreenKeyboardSupport
for C documentation.
isScreenKeyboardShown :: MonadIO m => Window -> m Bool Source #
Check whether the screen keyboard is shown for the given window.
See SDL_IsScreenKeyboardShown
for C documentation.
Scancodes
getScancodeName :: MonadIO m => Scancode -> m String Source #
Get a human-readable name for a scancode. If the scancode doesn't have a name this function returns the empty string.
See SDL_GetScancodeName
for C documentation.
Instances
Keycodes
Instances
Data Keycode Source # | |
Defined in SDL.Input.Keyboard.Codes gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> Keycode -> c Keycode Source # gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c Keycode Source # toConstr :: Keycode -> Constr Source # dataTypeOf :: Keycode -> DataType Source # dataCast1 :: Typeable t => (forall d. Data d => c (t d)) -> Maybe (c Keycode) Source # dataCast2 :: Typeable t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c Keycode) Source # gmapT :: (forall b. Data b => b -> b) -> Keycode -> Keycode Source # gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> Keycode -> r Source # gmapQr :: forall r r'. (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> Keycode -> r Source # gmapQ :: (forall d. Data d => d -> u) -> Keycode -> [u] Source # gmapQi :: Int -> (forall d. Data d => d -> u) -> Keycode -> u Source # gmapM :: Monad m => (forall d. Data d => d -> m d) -> Keycode -> m Keycode Source # gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> Keycode -> m Keycode Source # gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> Keycode -> m Keycode Source # | |
Bounded Keycode Source # | |
Generic Keycode Source # | |
Read Keycode Source # | |
Show Keycode Source # | |
Eq Keycode Source # | |
Ord Keycode Source # | |
Defined in SDL.Input.Keyboard.Codes | |
FromNumber Keycode Int32 Source # | |
Defined in SDL.Input.Keyboard.Codes fromNumber :: Int32 -> Keycode Source # | |
ToNumber Keycode Int32 Source # | |
type Rep Keycode Source # | |
Defined in SDL.Input.Keyboard.Codes |
Keysym
Information about a key press or key release event.
Keysym | |
|
Instances
Data Keysym Source # | |
Defined in SDL.Input.Keyboard gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> Keysym -> c Keysym Source # gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c Keysym Source # toConstr :: Keysym -> Constr Source # dataTypeOf :: Keysym -> DataType Source # dataCast1 :: Typeable t => (forall d. Data d => c (t d)) -> Maybe (c Keysym) Source # dataCast2 :: Typeable t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c Keysym) Source # gmapT :: (forall b. Data b => b -> b) -> Keysym -> Keysym Source # gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> Keysym -> r Source # gmapQr :: forall r r'. (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> Keysym -> r Source # gmapQ :: (forall d. Data d => d -> u) -> Keysym -> [u] Source # gmapQi :: Int -> (forall d. Data d => d -> u) -> Keysym -> u Source # gmapM :: Monad m => (forall d. Data d => d -> m d) -> Keysym -> m Keysym Source # gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> Keysym -> m Keysym Source # gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> Keysym -> m Keysym Source # | |
Generic Keysym Source # | |
Read Keysym Source # | |
Show Keysym Source # | |
Eq Keysym Source # | |
Ord Keysym Source # | |
Defined in SDL.Input.Keyboard | |
type Rep Keysym Source # | |
Defined in SDL.Input.Keyboard type Rep Keysym = D1 ('MetaData "Keysym" "SDL.Input.Keyboard" "sdl2-2.5.5.0-inplace" 'False) (C1 ('MetaCons "Keysym" 'PrefixI 'True) (S1 ('MetaSel ('Just "keysymScancode") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 Scancode) :*: (S1 ('MetaSel ('Just "keysymKeycode") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 Keycode) :*: S1 ('MetaSel ('Just "keysymModifier") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 KeyModifier)))) |
Keycodes and Scancodes
module SDL.Input.Keyboard.Codes