LambdaHack-0.9.4.1: A game engine library for tactical squad ASCII roguelike dungeon crawlers

Safe HaskellNone
LanguageHaskell2010

Game.LambdaHack.Client.UI.Key

Contents

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 
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
Eq Key Source # 
Instance details

Defined in Game.LambdaHack.Client.UI.Key

Methods

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

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

Ord Key Source # 
Instance details

Defined in Game.LambdaHack.Client.UI.Key

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 # 
Instance details

Defined in Game.LambdaHack.Client.UI.Key

Associated Types

type Rep Key :: Type -> Type #

Methods

from :: Key -> Rep Key x #

to :: Rep Key x -> Key #

Binary Key Source # 
Instance details

Defined in Game.LambdaHack.Client.UI.Key

Methods

put :: Key -> Put #

get :: Get Key #

putList :: [Key] -> Put #

NFData Key Source # 
Instance details

Defined in Game.LambdaHack.Client.UI.Key

Methods

rnf :: Key -> () #

type Rep Key Source # 
Instance details

Defined in Game.LambdaHack.Client.UI.Key

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

data Modifier Source #

Our own encoding of modifiers.

Constructors

NoModifier 
Shift 
Control 
Alt 
Instances
Eq Modifier Source # 
Instance details

Defined in Game.LambdaHack.Client.UI.Key

Ord Modifier Source # 
Instance details

Defined in Game.LambdaHack.Client.UI.Key

Show Modifier Source # 
Instance details

Defined in Game.LambdaHack.Client.UI.Key

Generic Modifier Source # 
Instance details

Defined in Game.LambdaHack.Client.UI.Key

Associated Types

type Rep Modifier :: Type -> Type #

Methods

from :: Modifier -> Rep Modifier x #

to :: Rep Modifier x -> Modifier #

Binary Modifier Source # 
Instance details

Defined in Game.LambdaHack.Client.UI.Key

Methods

put :: Modifier -> Put #

get :: Get Modifier #

putList :: [Modifier] -> Put #

NFData Modifier Source # 
Instance details

Defined in Game.LambdaHack.Client.UI.Key

Methods

rnf :: Modifier -> () #

type Rep Modifier Source # 
Instance details

Defined in Game.LambdaHack.Client.UI.Key

type Rep Modifier = D1 (MetaData "Modifier" "Game.LambdaHack.Client.UI.Key" "LambdaHack-0.9.4.1-inplace" False) ((C1 (MetaCons "NoModifier" PrefixI False) (U1 :: Type -> Type) :+: C1 (MetaCons "Shift" PrefixI False) (U1 :: Type -> Type)) :+: (C1 (MetaCons "Control" PrefixI False) (U1 :: Type -> Type) :+: C1 (MetaCons "Alt" PrefixI False) (U1 :: Type -> Type)))

data KM Source #

Key and modifier.

Constructors

KM 

Fields

Instances
Eq KM Source # 
Instance details

Defined in Game.LambdaHack.Client.UI.Key

Methods

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

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

Ord KM Source # 
Instance details

Defined in Game.LambdaHack.Client.UI.Key

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 # 
Instance details

Defined in Game.LambdaHack.Client.UI.Key

Methods

showsPrec :: Int -> KM -> ShowS #

show :: KM -> String #

showList :: [KM] -> ShowS #

Generic KM Source # 
Instance details

Defined in Game.LambdaHack.Client.UI.Key

Associated Types

type Rep KM :: Type -> Type #

Methods

from :: KM -> Rep KM x #

to :: Rep KM x -> KM #

Binary KM Source # 
Instance details

Defined in Game.LambdaHack.Client.UI.Key

Methods

put :: KM -> Put #

get :: Get KM #

putList :: [KM] -> Put #

NFData KM Source # 
Instance details

Defined in Game.LambdaHack.Client.UI.Key

Methods

rnf :: KM -> () #

type Rep KM Source # 
Instance details

Defined in Game.LambdaHack.Client.UI.Key

type Rep KM = D1 (MetaData "KM" "Game.LambdaHack.Client.UI.Key" "LambdaHack-0.9.4.1-inplace" False) (C1 (MetaCons "KM" PrefixI True) (S1 (MetaSel (Just "modifier") NoSourceUnpackedness NoSourceStrictness DecidedStrict) (Rec0 Modifier) :*: S1 (MetaSel (Just "key") NoSourceUnpackedness NoSourceStrictness DecidedStrict) (Rec0 Key)))

data KMP Source #

Key, modifier and position of mouse pointer.

Constructors

KMP 

Fields

showKey :: Key -> String Source #

Common and terse names for keys.

showKM :: KM -> String Source #

Show a key with a modifier, if any.

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/keynames.txt

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