LambdaHack-0.6.1.0: A game engine library for roguelike dungeon crawlers

Safe HaskellNone
LanguageHaskell2010

Game.LambdaHack.Client.UI.Key

Description

Frontend-independent keyboard input operations.

Synopsis

Documentation

data Key Source #

Frontend-independent datatype to represent keys.

Constructors

Esc 
Return 
Space 
Tab 
BackTab 
BackSpace 
PgUp 
PgDn 
Left 
Right 
Up 
Down 
End 
Begin 
Insert 
Delete 
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

Eq Key Source # 

Methods

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

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

Ord Key Source # 

Methods

compare :: Key -> Key -> Ordering #

(<) :: Key -> Key -> Bool #

(<=) :: Key -> Key -> Bool #

(>) :: Key -> Key -> Bool #

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

max :: Key -> Key -> Key #

min :: Key -> Key -> Key #

Generic Key Source # 

Associated Types

type Rep Key :: * -> * #

Methods

from :: Key -> Rep Key x #

to :: Rep Key x -> Key #

Binary Key Source # 

Methods

put :: Key -> Put #

get :: Get Key #

putList :: [Key] -> Put #

NFData Key Source # 

Methods

rnf :: Key -> () #

type Rep Key Source # 
type Rep Key = D1 * (MetaData "Key" "Game.LambdaHack.Client.UI.Key" "LambdaHack-0.6.1.0-HURqEs4cFyW7LJywblRLqn" False) ((:+:) * ((:+:) * ((:+:) * ((:+:) * (C1 * (MetaCons "Esc" PrefixI False) (U1 *)) ((:+:) * (C1 * (MetaCons "Return" PrefixI False) (U1 *)) (C1 * (MetaCons "Space" PrefixI False) (U1 *)))) ((:+:) * ((:+:) * (C1 * (MetaCons "Tab" PrefixI False) (U1 *)) (C1 * (MetaCons "BackTab" PrefixI False) (U1 *))) ((:+:) * (C1 * (MetaCons "BackSpace" PrefixI False) (U1 *)) (C1 * (MetaCons "PgUp" PrefixI False) (U1 *))))) ((:+:) * ((:+:) * ((:+:) * (C1 * (MetaCons "PgDn" PrefixI False) (U1 *)) (C1 * (MetaCons "Left" PrefixI False) (U1 *))) ((:+:) * (C1 * (MetaCons "Right" PrefixI False) (U1 *)) (C1 * (MetaCons "Up" PrefixI False) (U1 *)))) ((:+:) * ((:+:) * (C1 * (MetaCons "Down" PrefixI False) (U1 *)) (C1 * (MetaCons "End" PrefixI False) (U1 *))) ((:+:) * (C1 * (MetaCons "Begin" PrefixI False) (U1 *)) (C1 * (MetaCons "Insert" PrefixI False) (U1 *)))))) ((:+:) * ((:+:) * ((:+:) * (C1 * (MetaCons "Delete" PrefixI False) (U1 *)) ((:+:) * (C1 * (MetaCons "Home" PrefixI False) (U1 *)) (C1 * (MetaCons "KP" PrefixI False) (S1 * (MetaSel (Nothing Symbol) NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 * Char))))) ((:+:) * ((:+:) * (C1 * (MetaCons "Char" PrefixI False) (S1 * (MetaSel (Nothing Symbol) NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 * Char))) (C1 * (MetaCons "Fun" PrefixI False) (S1 * (MetaSel (Nothing Symbol) NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 * Int)))) ((:+:) * (C1 * (MetaCons "LeftButtonPress" PrefixI False) (U1 *)) (C1 * (MetaCons "MiddleButtonPress" PrefixI False) (U1 *))))) ((:+:) * ((:+:) * ((:+:) * (C1 * (MetaCons "RightButtonPress" PrefixI False) (U1 *)) (C1 * (MetaCons "LeftButtonRelease" PrefixI False) (U1 *))) ((:+:) * (C1 * (MetaCons "MiddleButtonRelease" PrefixI False) (U1 *)) (C1 * (MetaCons "RightButtonRelease" PrefixI False) (U1 *)))) ((:+:) * ((:+:) * (C1 * (MetaCons "WheelNorth" PrefixI False) (U1 *)) (C1 * (MetaCons "WheelSouth" PrefixI False) (U1 *))) ((:+:) * (C1 * (MetaCons "Unknown" PrefixI False) (S1 * (MetaSel (Nothing Symbol) NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 * String))) (C1 * (MetaCons "DeadKey" PrefixI False) (U1 *)))))))

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.

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.orgen-USdocsWebAPIKeyboardEvent/key#Key_values) to our internal key type. To be used in web frontends. The argument says whether Shift is pressed.

data Modifier Source #

Our own encoding of modifiers.

Constructors

NoModifier 
Shift 
Control 
Alt 

Instances

Eq Modifier Source # 
Ord Modifier Source # 
Show Modifier Source # 
Generic Modifier Source # 

Associated Types

type Rep Modifier :: * -> * #

Methods

from :: Modifier -> Rep Modifier x #

to :: Rep Modifier x -> Modifier #

Binary Modifier Source # 

Methods

put :: Modifier -> Put #

get :: Get Modifier #

putList :: [Modifier] -> Put #

NFData Modifier Source # 

Methods

rnf :: Modifier -> () #

type Rep Modifier Source # 
type Rep Modifier = D1 * (MetaData "Modifier" "Game.LambdaHack.Client.UI.Key" "LambdaHack-0.6.1.0-HURqEs4cFyW7LJywblRLqn" 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 *))))

data KM Source #

Constructors

KM 

Fields

Instances

Eq KM Source # 

Methods

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

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

Ord KM Source # 

Methods

compare :: KM -> KM -> Ordering #

(<) :: KM -> KM -> Bool #

(<=) :: KM -> KM -> Bool #

(>) :: KM -> KM -> Bool #

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

max :: KM -> KM -> KM #

min :: KM -> KM -> KM #

Show KM Source # 

Methods

showsPrec :: Int -> KM -> ShowS #

show :: KM -> String #

showList :: [KM] -> ShowS #

Generic KM Source # 

Associated Types

type Rep KM :: * -> * #

Methods

from :: KM -> Rep KM x #

to :: Rep KM x -> KM #

Binary KM Source # 

Methods

put :: KM -> Put #

get :: Get KM #

putList :: [KM] -> Put #

NFData KM Source # 

Methods

rnf :: KM -> () #

type Rep KM Source # 
type Rep KM = D1 * (MetaData "KM" "Game.LambdaHack.Client.UI.Key" "LambdaHack-0.6.1.0-HURqEs4cFyW7LJywblRLqn" False) (C1 * (MetaCons "KM" PrefixI True) ((:*:) * (S1 * (MetaSel (Just Symbol "modifier") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 * Modifier)) (S1 * (MetaSel (Just Symbol "key") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 * Key))))

showKM :: KM -> String Source #

Show a key with a modifier, if any.