sdl2-2.1.2.1: Both high- and low-level bindings to the SDL library (version 2.0.2).

Safe HaskellNone
LanguageHaskell2010

SDL.Input.Keyboard

Contents

Synopsis

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

Eq KeyModifier Source # 
Data KeyModifier Source # 

Methods

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

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

toConstr :: KeyModifier -> Constr #

dataTypeOf :: KeyModifier -> DataType #

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

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

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

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

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

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

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

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

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

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

Ord KeyModifier Source # 
Read KeyModifier Source # 
Show KeyModifier Source # 
Generic KeyModifier Source # 

Associated Types

type Rep KeyModifier :: * -> * #

type Rep KeyModifier Source # 
type Rep KeyModifier = D1 (MetaData "KeyModifier" "SDL.Input.Keyboard" "sdl2-2.1.2.1-K4kKAqflmYB2sRFMmKxiAm" False) (C1 (MetaCons "KeyModifier" PrefixI True) ((:*:) ((:*:) ((:*:) (S1 (MetaSel (Just Symbol "keyModifierLeftShift") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 Bool)) (S1 (MetaSel (Just Symbol "keyModifierRightShift") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 Bool))) ((:*:) (S1 (MetaSel (Just Symbol "keyModifierLeftCtrl") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 Bool)) ((:*:) (S1 (MetaSel (Just Symbol "keyModifierRightCtrl") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 Bool)) (S1 (MetaSel (Just Symbol "keyModifierLeftAlt") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 Bool))))) ((:*:) ((:*:) (S1 (MetaSel (Just Symbol "keyModifierRightAlt") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 Bool)) ((:*:) (S1 (MetaSel (Just Symbol "keyModifierLeftGUI") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 Bool)) (S1 (MetaSel (Just Symbol "keyModifierRightGUI") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 Bool)))) ((:*:) (S1 (MetaSel (Just Symbol "keyModifierNumLock") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 Bool)) ((:*:) (S1 (MetaSel (Just Symbol "keyModifierCapsLock") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 Bool)) (S1 (MetaSel (Just Symbol "keyModifierAltGr") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 Bool)))))))

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

newtype Scancode Source #

Constructors

Scancode 

Instances

Bounded Scancode Source # 
Eq Scancode Source # 
Data Scancode Source # 

Methods

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

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

toConstr :: Scancode -> Constr #

dataTypeOf :: Scancode -> DataType #

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

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

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

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

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

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

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

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

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

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

Ord Scancode Source # 
Read Scancode Source # 
Show Scancode Source # 
Generic Scancode Source # 

Associated Types

type Rep Scancode :: * -> * #

Methods

from :: Scancode -> Rep Scancode x #

to :: Rep Scancode x -> Scancode #

type Rep Scancode Source # 
type Rep Scancode = D1 (MetaData "Scancode" "SDL.Input.Keyboard.Codes" "sdl2-2.1.2.1-K4kKAqflmYB2sRFMmKxiAm" True) (C1 (MetaCons "Scancode" PrefixI True) (S1 (MetaSel (Just Symbol "unwrapScancode") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 Word32)))

Keycodes

newtype Keycode Source #

Constructors

Keycode 

Fields

Instances

Bounded Keycode Source # 
Eq Keycode Source # 

Methods

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

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

Data Keycode Source # 

Methods

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

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

toConstr :: Keycode -> Constr #

dataTypeOf :: Keycode -> DataType #

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

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

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

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

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

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

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

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

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

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

Ord Keycode Source # 
Read Keycode Source # 
Show Keycode Source # 
Generic Keycode Source # 

Associated Types

type Rep Keycode :: * -> * #

Methods

from :: Keycode -> Rep Keycode x #

to :: Rep Keycode x -> Keycode #

type Rep Keycode Source # 
type Rep Keycode = D1 (MetaData "Keycode" "SDL.Input.Keyboard.Codes" "sdl2-2.1.2.1-K4kKAqflmYB2sRFMmKxiAm" True) (C1 (MetaCons "Keycode" PrefixI True) (S1 (MetaSel (Just Symbol "unwrapKeycode") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 Int32)))

Keysym

data Keysym Source #

Information about a key press or key release event.

Constructors

Keysym 

Fields

Instances

Eq Keysym Source # 

Methods

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

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

Data Keysym Source # 

Methods

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

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

toConstr :: Keysym -> Constr #

dataTypeOf :: Keysym -> DataType #

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

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

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

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

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

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

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

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

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

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

Ord Keysym Source # 
Read Keysym Source # 
Show Keysym Source # 
Generic Keysym Source # 

Associated Types

type Rep Keysym :: * -> * #

Methods

from :: Keysym -> Rep Keysym x #

to :: Rep Keysym x -> Keysym #

type Rep Keysym Source # 
type Rep Keysym = D1 (MetaData "Keysym" "SDL.Input.Keyboard" "sdl2-2.1.2.1-K4kKAqflmYB2sRFMmKxiAm" False) (C1 (MetaCons "Keysym" PrefixI True) ((:*:) (S1 (MetaSel (Just Symbol "keysymScancode") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 Scancode)) ((:*:) (S1 (MetaSel (Just Symbol "keysymKeycode") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 Keycode)) (S1 (MetaSel (Just Symbol "keysymModifier") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 KeyModifier)))))

Keycodes and Scancodes