vty-5.38: A simple terminal UI library
Safe HaskellSafe-Inferred
LanguageHaskell2010

Graphics.Vty.Input

Description

This module provides the input layer for Vty, including methods for initializing an Input structure and reading Events from the terminal.

Note that due to the evolution of terminal emulators, some keys and combinations will not reliably map to the expected events by any terminal program. There is no 1:1 mapping from key events to bytes read from the terminal input device. In very limited cases the terminal and vty's input process can be customized to resolve these issues; see Graphics.Vty.Config for how to configure vty's input processing.

VTY's Implementation

There are two input modes:

  1. 7-bit
  2. 8-bit

The 7-bit input mode is the default and the expected mode in most use cases. This is what Vty uses.

7-bit input encoding

Control key combinations are represented by masking the two high bits of the 7-bit input. Historically the control key actually grounded the two high bit wires: 6 and 7. This is why control key combos map to single character events: the input bytes are identical. The input byte is the bit encoding of the character with bits 6 and 7 masked. Bit 6 is set by shift. Bit 6 and 7 are masked by control. For example,

  • Control-I is i, `01101001`, and has bit 6 and 7 masked to become `00001001`, which is the ASCII and UTF-8 encoding of the Tab key.
  • Control+Shift-C is C, `01000011`, with bit 6 and 7 set to zero which is `0000011` and is the "End of Text" code.
  • Hypothesis: This is why capital-A, A, has value 65 in ASCII: this is the value 1 with bit 7 set and 6 unset.
  • Hypothesis: Bit 6 is unset by upper case letters because, initially, there were only upper case letters used and a 5 bit encoding.

8-bit encoding

The 8th bit was originally used for parity checking which is useless for terminal emulators. Some terminal emulators support an 8-bit input encoding. While this provides some advantages, the actual usage is low. Most systems use 7-bit mode but recognize 8-bit control characters when escaped. This is what Vty does.

Escaped Control Keys

Using 7-bit input encoding, the ESC byte can signal the start of an encoded control key. To differentiate a single ESC event from a control key, the timing of the input is used.

  1. ESC individually: ESC byte; no bytes following for a period of VMIN milliseconds.
  2. Control keys that contain ESC in their encoding: The @ESC byte is followed by more bytes read within VMIN milliseconds. All bytes up until the next valid input block are passed to the classifier.

If the current runtime is the threaded runtime then the terminal's VMIN and VTIME behavior reliably implement the above rules. If the current runtime does not support forkOS then there is currently no implementation.

Unicode Input and Escaped Control Key Sequences

The input encoding determines how UTF-8 encoded characters are recognized.

  • 7-bit mode: UTF-8 can be input unambiguously. UTF-8 input is a superset of ASCII. UTF-8 does not overlap escaped control key sequences. However, the escape key must be differentiated from escaped control key sequences by the timing of the input bytes.
  • 8-bit mode: UTF-8 cannot be input unambiguously. This does not require using the timing of input bytes to differentiate the escape key. Many terminals do not support 8-bit mode.

Terminfo

The terminfo system is used to determine how some keys are encoded. Terminfo is incomplete and in some cases terminfo is incorrect. Vty assumes terminfo is correct but provides a mechanism to override terminfo; see Graphics.Vty.Config, specifically inputOverrides.

Terminal Input is Broken

Clearly terminal input has fundamental issues. There is no easy way to reliably resolve these issues.

One resolution would be to ditch standard terminal interfaces entirely and just go directly to scancodes. This would be a reasonable option for Vty if everybody used the linux kernel console but for obvious reasons this is not possible.

The Graphics.Vty.Config module supports customizing the input-byte-to-event mapping and xterm supports customizing the scancode-to-input-byte mapping. With a lot of work a user's system can be set up to encode all the key combos in an almost-sane manner.

See also

Synopsis

Documentation

data Key Source #

Representations of non-modifier keys.

  • KFun is indexed from 0 to 63. Range of supported FKeys varies by terminal and keyboard.
  • KUpLeft, KUpRight, KDownLeft, KDownRight, KCenter support varies by terminal and keyboard.
  • Actually, support for most of these but KEsc, KChar, KBS, and KEnter vary by terminal and keyboard.

Instances

Instances details
Generic Key Source # 
Instance details

Defined in Graphics.Vty.Input.Events

Associated Types

type Rep Key :: Type -> Type #

Methods

from :: Key -> Rep Key x #

to :: Rep Key x -> Key #

Read Key Source # 
Instance details

Defined in Graphics.Vty.Input.Events

Show Key Source # 
Instance details

Defined in Graphics.Vty.Input.Events

Methods

showsPrec :: Int -> Key -> ShowS #

show :: Key -> String #

showList :: [Key] -> ShowS #

NFData Key Source # 
Instance details

Defined in Graphics.Vty.Input.Events

Methods

rnf :: Key -> () #

Eq Key Source # 
Instance details

Defined in Graphics.Vty.Input.Events

Methods

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

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

Ord Key Source # 
Instance details

Defined in Graphics.Vty.Input.Events

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 #

type Rep Key Source # 
Instance details

Defined in Graphics.Vty.Input.Events

type Rep Key = D1 ('MetaData "Key" "Graphics.Vty.Input.Events" "vty-5.38-A9ULz6eXn7w9dhVWw4fFjs" 'False) ((((C1 ('MetaCons "KEsc" 'PrefixI 'False) (U1 :: Type -> Type) :+: (C1 ('MetaCons "KChar" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'SourceUnpack 'NoSourceStrictness 'DecidedStrict) (Rec0 Char)) :+: C1 ('MetaCons "KBS" 'PrefixI 'False) (U1 :: Type -> Type))) :+: (C1 ('MetaCons "KEnter" 'PrefixI 'False) (U1 :: Type -> Type) :+: (C1 ('MetaCons "KLeft" 'PrefixI 'False) (U1 :: Type -> Type) :+: C1 ('MetaCons "KRight" 'PrefixI 'False) (U1 :: Type -> Type)))) :+: ((C1 ('MetaCons "KUp" 'PrefixI 'False) (U1 :: Type -> Type) :+: (C1 ('MetaCons "KDown" 'PrefixI 'False) (U1 :: Type -> Type) :+: C1 ('MetaCons "KUpLeft" 'PrefixI 'False) (U1 :: Type -> Type))) :+: (C1 ('MetaCons "KUpRight" 'PrefixI 'False) (U1 :: Type -> Type) :+: (C1 ('MetaCons "KDownLeft" 'PrefixI 'False) (U1 :: Type -> Type) :+: C1 ('MetaCons "KDownRight" 'PrefixI 'False) (U1 :: Type -> Type))))) :+: (((C1 ('MetaCons "KCenter" 'PrefixI 'False) (U1 :: Type -> Type) :+: (C1 ('MetaCons "KFun" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'SourceUnpack 'NoSourceStrictness 'DecidedStrict) (Rec0 Int)) :+: C1 ('MetaCons "KBackTab" 'PrefixI 'False) (U1 :: Type -> Type))) :+: (C1 ('MetaCons "KPrtScr" 'PrefixI 'False) (U1 :: Type -> Type) :+: (C1 ('MetaCons "KPause" 'PrefixI 'False) (U1 :: Type -> Type) :+: C1 ('MetaCons "KIns" 'PrefixI 'False) (U1 :: Type -> Type)))) :+: ((C1 ('MetaCons "KHome" 'PrefixI 'False) (U1 :: Type -> Type) :+: (C1 ('MetaCons "KPageUp" 'PrefixI 'False) (U1 :: Type -> Type) :+: C1 ('MetaCons "KDel" 'PrefixI 'False) (U1 :: Type -> Type))) :+: ((C1 ('MetaCons "KEnd" 'PrefixI 'False) (U1 :: Type -> Type) :+: C1 ('MetaCons "KPageDown" 'PrefixI 'False) (U1 :: Type -> Type)) :+: (C1 ('MetaCons "KBegin" 'PrefixI 'False) (U1 :: Type -> Type) :+: C1 ('MetaCons "KMenu" 'PrefixI 'False) (U1 :: Type -> Type))))))

data Modifier Source #

Modifier keys. Key codes are interpreted such that users are more likely to have Meta than Alt; for instance on the PC Linux console, MMeta will generally correspond to the physical Alt key.

Constructors

MShift 
MCtrl 
MMeta 
MAlt 

Instances

Instances details
Generic Modifier Source # 
Instance details

Defined in Graphics.Vty.Input.Events

Associated Types

type Rep Modifier :: Type -> Type #

Methods

from :: Modifier -> Rep Modifier x #

to :: Rep Modifier x -> Modifier #

Read Modifier Source # 
Instance details

Defined in Graphics.Vty.Input.Events

Show Modifier Source # 
Instance details

Defined in Graphics.Vty.Input.Events

NFData Modifier Source # 
Instance details

Defined in Graphics.Vty.Input.Events

Methods

rnf :: Modifier -> () #

Eq Modifier Source # 
Instance details

Defined in Graphics.Vty.Input.Events

Ord Modifier Source # 
Instance details

Defined in Graphics.Vty.Input.Events

type Rep Modifier Source # 
Instance details

Defined in Graphics.Vty.Input.Events

type Rep Modifier = D1 ('MetaData "Modifier" "Graphics.Vty.Input.Events" "vty-5.38-A9ULz6eXn7w9dhVWw4fFjs" 'False) ((C1 ('MetaCons "MShift" 'PrefixI 'False) (U1 :: Type -> Type) :+: C1 ('MetaCons "MCtrl" 'PrefixI 'False) (U1 :: Type -> Type)) :+: (C1 ('MetaCons "MMeta" 'PrefixI 'False) (U1 :: Type -> Type) :+: C1 ('MetaCons "MAlt" 'PrefixI 'False) (U1 :: Type -> Type)))

data Button Source #

Mouse buttons.

Instances

Instances details
Generic Button Source # 
Instance details

Defined in Graphics.Vty.Input.Events

Associated Types

type Rep Button :: Type -> Type #

Methods

from :: Button -> Rep Button x #

to :: Rep Button x -> Button #

Read Button Source # 
Instance details

Defined in Graphics.Vty.Input.Events

Show Button Source # 
Instance details

Defined in Graphics.Vty.Input.Events

NFData Button Source # 
Instance details

Defined in Graphics.Vty.Input.Events

Methods

rnf :: Button -> () #

Eq Button Source # 
Instance details

Defined in Graphics.Vty.Input.Events

Methods

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

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

Ord Button Source # 
Instance details

Defined in Graphics.Vty.Input.Events

type Rep Button Source # 
Instance details

Defined in Graphics.Vty.Input.Events

type Rep Button = D1 ('MetaData "Button" "Graphics.Vty.Input.Events" "vty-5.38-A9ULz6eXn7w9dhVWw4fFjs" 'False) ((C1 ('MetaCons "BLeft" 'PrefixI 'False) (U1 :: Type -> Type) :+: C1 ('MetaCons "BMiddle" 'PrefixI 'False) (U1 :: Type -> Type)) :+: (C1 ('MetaCons "BRight" 'PrefixI 'False) (U1 :: Type -> Type) :+: (C1 ('MetaCons "BScrollUp" 'PrefixI 'False) (U1 :: Type -> Type) :+: C1 ('MetaCons "BScrollDown" 'PrefixI 'False) (U1 :: Type -> Type))))

data Event Source #

Events.

Constructors

EvKey Key [Modifier]

A keyboard key was pressed with the specified modifiers.

EvMouseDown Int Int Button [Modifier]

A mouse button was pressed at the specified column and row. Any modifiers available in the event are also provided.

EvMouseUp Int Int (Maybe Button)

A mouse button was released at the specified column and row. Some terminals report only that a button was released without specifying which one; in that case, Nothing is provided. Otherwise Just the button released is included in the event.

EvResize Int Int 
EvPaste ByteString

A paste event occurs when a bracketed paste input sequence is received. For terminals that support bracketed paste mode, these events will be triggered on a paste event. Terminals that do not support bracketed pastes will send the paste contents as ordinary input (which is probably bad, so beware!) Note that the data is provided in raw form and you'll have to decode (e.g. as UTF-8) if that's what your application expects.

EvLostFocus

The terminal running the application lost input focus.

EvGainedFocus

The terminal running the application gained input focus.

Instances

Instances details
Generic Event Source # 
Instance details

Defined in Graphics.Vty.Input.Events

Associated Types

type Rep Event :: Type -> Type #

Methods

from :: Event -> Rep Event x #

to :: Rep Event x -> Event #

Read Event Source # 
Instance details

Defined in Graphics.Vty.Input.Events

Show Event Source # 
Instance details

Defined in Graphics.Vty.Input.Events

Methods

showsPrec :: Int -> Event -> ShowS #

show :: Event -> String #

showList :: [Event] -> ShowS #

NFData Event Source # 
Instance details

Defined in Graphics.Vty.Input.Events

Methods

rnf :: Event -> () #

Eq Event Source # 
Instance details

Defined in Graphics.Vty.Input.Events

Methods

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

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

Ord Event Source # 
Instance details

Defined in Graphics.Vty.Input.Events

Methods

compare :: Event -> Event -> Ordering #

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

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

(>) :: Event -> Event -> Bool #

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

max :: Event -> Event -> Event #

min :: Event -> Event -> Event #

type Rep Event Source # 
Instance details

Defined in Graphics.Vty.Input.Events

type Rep Event = D1 ('MetaData "Event" "Graphics.Vty.Input.Events" "vty-5.38-A9ULz6eXn7w9dhVWw4fFjs" 'False) ((C1 ('MetaCons "EvKey" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedStrict) (Rec0 Key) :*: S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedStrict) (Rec0 [Modifier])) :+: (C1 ('MetaCons "EvMouseDown" 'PrefixI 'False) ((S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedStrict) (Rec0 Int) :*: S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedStrict) (Rec0 Int)) :*: (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedStrict) (Rec0 Button) :*: S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedStrict) (Rec0 [Modifier]))) :+: C1 ('MetaCons "EvMouseUp" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedStrict) (Rec0 Int) :*: (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedStrict) (Rec0 Int) :*: S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedStrict) (Rec0 (Maybe Button)))))) :+: ((C1 ('MetaCons "EvResize" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedStrict) (Rec0 Int) :*: S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedStrict) (Rec0 Int)) :+: C1 ('MetaCons "EvPaste" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedStrict) (Rec0 ByteString))) :+: (C1 ('MetaCons "EvLostFocus" 'PrefixI 'False) (U1 :: Type -> Type) :+: C1 ('MetaCons "EvGainedFocus" 'PrefixI 'False) (U1 :: Type -> Type))))

data Input Source #

Constructors

Input 

Fields

inputForConfig :: Config -> IO Input Source #

Set up the terminal with file descriptor inputFd for input. Returns an Input.

The table used to determine the Events to produce for the input bytes comes from classifyMapForTerm which is then overridden by the the applicable entries from the configuration's inputMap.

The terminal device's mode flags are configured by the attributeControl function.

attributeControl :: Fd -> IO (IO (), IO ()) Source #

Construct two IO actions: one to configure the terminal for Vty and one to restore the terminal mode flags to the values they had at the time this function was called.

This function constructs a configuration action to clear the following terminal mode flags:

  • IXON disabled: disables software flow control on outgoing data. This stops the process from being suspended if the output terminal cannot keep up.
  • Raw mode is used for input.
  • ISIG (enables keyboard combinations that result in signals)
  • ECHO (input is not echoed to the output)
  • ICANON (canonical mode (line mode) input is not used)
  • IEXTEN (extended functions are disabled)

The configuration action also explicitly sets these flags:

  • ICRNL (input carriage returns are mapped to newlines)