Safe Haskell | None |
---|---|
Language | Haskell2010 |
Frontend-independent keyboard input operations.
Synopsis
- data Key
- = Esc
- | Return
- | Space
- | Tab
- | BackTab
- | BackSpace
- | PgUp
- | PgDn
- | Left
- | Right
- | Up
- | Down
- | End
- | Begin
- | Insert
- | Delete
- | PrintScreen
- | Home
- | KP Char
- | Char Char
- | Fun Int
- | LeftButtonPress
- | MiddleButtonPress
- | RightButtonPress
- | LeftButtonRelease
- | MiddleButtonRelease
- | RightButtonRelease
- | WheelNorth
- | WheelSouth
- | Unknown String
- | DeadKey
- data Modifier
- = NoModifier
- | Shift
- | Control
- | Alt
- data KM = KM {}
- data KMP = KMP {
- kmpKeyMod :: KM
- kmpPointer :: Point
- showKey :: Key -> String
- showKM :: KM -> String
- escKM :: KM
- spaceKM :: KM
- safeSpaceKM :: KM
- returnKM :: KM
- pgupKM :: KM
- pgdnKM :: KM
- wheelNorthKM :: KM
- wheelSouthKM :: KM
- upKM :: KM
- downKM :: KM
- leftKM :: KM
- rightKM :: KM
- homeKM :: KM
- endKM :: KM
- backspaceKM :: KM
- leftButtonReleaseKM :: KM
- rightButtonReleaseKM :: KM
- dirAllKey :: Bool -> Bool -> [Key]
- handleDir :: Bool -> Bool -> KM -> Maybe Vector
- moveBinding :: Bool -> Bool -> (Vector -> a) -> (Vector -> a) -> [(KM, a)]
- mkKM :: String -> KM
- mkChar :: Char -> KM
- mkKP :: Char -> KM
- keyTranslate :: String -> Key
- keyTranslateWeb :: String -> Bool -> Key
- dirKeypadKey :: [Key]
- dirKeypadShiftChar :: [Char]
- dirKeypadShiftKey :: [Key]
- dirLaptopKey :: [Key]
- dirLaptopShiftKey :: [Key]
- dirViChar :: [Char]
- dirViKey :: [Key]
- dirViShiftKey :: [Key]
- dirMoveNoModifier :: Bool -> Bool -> [Key]
- dirRunNoModifier :: Bool -> Bool -> [Key]
- dirRunControl :: [Key]
- dirRunShift :: [Key]
Documentation
Frontend-independent datatype to represent keys.
Esc | |
Return | |
Space | |
Tab | |
BackTab | |
BackSpace | |
PgUp | |
PgDn | |
Left | |
Right | |
Up | |
Down | |
End | |
Begin | |
Insert | |
Delete | |
PrintScreen | |
Home | |
KP Char | a keypad key for a character (digits and operators) |
Char Char | a single printable character |
Fun Int | function key |
LeftButtonPress | left mouse button pressed |
MiddleButtonPress | middle mouse button pressed |
RightButtonPress | right mouse button pressed |
LeftButtonRelease | left mouse button released |
MiddleButtonRelease | middle mouse button released |
RightButtonRelease | right mouse button released |
WheelNorth | mouse wheel rotated north |
WheelSouth | mouse wheel rotated south |
Unknown String | an unknown key, registered to warn the user |
DeadKey |
Instances
Our own encoding of modifiers.
Instances
Eq Modifier Source # | |
Ord Modifier Source # | |
Defined in Game.LambdaHack.Client.UI.Key | |
Show Modifier Source # | |
Generic Modifier Source # | |
Binary Modifier Source # | |
NFData Modifier Source # | |
Defined in Game.LambdaHack.Client.UI.Key | |
type Rep Modifier Source # | |
Defined in Game.LambdaHack.Client.UI.Key type Rep Modifier = D1 (MetaData "Modifier" "Game.LambdaHack.Client.UI.Key" "LambdaHack-0.8.1.0-1OhyQzgxgToLUwg19o2btM" False) ((C1 (MetaCons "NoModifier" PrefixI False) (U1 :: * -> *) :+: C1 (MetaCons "Shift" PrefixI False) (U1 :: * -> *)) :+: (C1 (MetaCons "Control" PrefixI False) (U1 :: * -> *) :+: C1 (MetaCons "Alt" PrefixI False) (U1 :: * -> *))) |
Key and modifier.
Instances
Eq KM Source # | |
Ord KM Source # | |
Show KM Source # | |
Generic KM Source # | |
Binary KM Source # | |
NFData KM Source # | |
Defined in Game.LambdaHack.Client.UI.Key | |
type Rep KM Source # | |
Defined in Game.LambdaHack.Client.UI.Key type Rep KM = D1 (MetaData "KM" "Game.LambdaHack.Client.UI.Key" "LambdaHack-0.8.1.0-1OhyQzgxgToLUwg19o2btM" False) (C1 (MetaCons "KM" PrefixI True) (S1 (MetaSel (Just "modifier") NoSourceUnpackedness NoSourceStrictness DecidedStrict) (Rec0 Modifier) :*: S1 (MetaSel (Just "key") NoSourceUnpackedness NoSourceStrictness DecidedStrict) (Rec0 Key))) |
Key, modifier and position of mouse pointer.
KMP | |
|
safeSpaceKM :: KM Source #
wheelNorthKM :: KM Source #
wheelSouthKM :: KM Source #
backspaceKM :: KM Source #
handleDir :: Bool -> Bool -> KM -> Maybe Vector Source #
Configurable event handler for the direction keys. Used for directed commands such as close door.
moveBinding :: Bool -> Bool -> (Vector -> a) -> (Vector -> a) -> [(KM, a)] Source #
Binding of both sets of movement keys, vi and laptop.
keyTranslate :: String -> Key Source #
Translate key from a GTK string description to our internal key type. To be used, in particular, for the command bindings and macros in the config file.
See https://github.com/twobob/gtk-/blob/master/gdk/keyname-table.h
keyTranslateWeb :: String -> Bool -> Key Source #
Translate key from a Web API string description (https://developer.mozilla.org/en-US/docs/Web/API/KeyboardEvent/key#Key_values) to our internal key type. To be used in web frontends. The argument says whether Shift is pressed.
Internal operations
dirKeypadKey :: [Key] Source #
dirKeypadShiftChar :: [Char] Source #
dirKeypadShiftKey :: [Key] Source #
dirLaptopKey :: [Key] Source #
dirLaptopShiftKey :: [Key] Source #
dirViShiftKey :: [Key] Source #
dirRunControl :: [Key] Source #
dirRunShift :: [Key] Source #