vty-5.15.1: A simple terminal UI library

Safe HaskellSafe
LanguageHaskell2010

Graphics.Vty.Input.Events

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

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 #

Read Key Source # 
Show Key Source # 

Methods

showsPrec :: Int -> Key -> ShowS #

show :: Key -> String #

showList :: [Key] -> ShowS #

Generic Key Source # 

Associated Types

type Rep Key :: * -> * #

Methods

from :: Key -> Rep Key x #

to :: Rep Key x -> Key #

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

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

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

Associated Types

type Rep Modifier :: * -> * #

Methods

from :: Modifier -> Rep Modifier x #

to :: Rep Modifier x -> Modifier #

type Rep Modifier Source # 
type Rep Modifier = D1 (MetaData "Modifier" "Graphics.Vty.Input.Events" "vty-5.15.1-DXxVH8hZfWcLVVBML8dvvP" False) ((:+:) ((:+:) (C1 (MetaCons "MShift" PrefixI False) U1) (C1 (MetaCons "MCtrl" PrefixI False) U1)) ((:+:) (C1 (MetaCons "MMeta" PrefixI False) U1) (C1 (MetaCons "MAlt" PrefixI False) U1)))

data Button Source #

Mouse buttons.

Constructors

BLeft 
BMiddle 
BRight 

Instances

Eq Button Source # 

Methods

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

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

Ord Button Source # 
Read Button Source # 
Show Button Source # 
Generic Button Source # 

Associated Types

type Rep Button :: * -> * #

Methods

from :: Button -> Rep Button x #

to :: Rep Button x -> Button #

type Rep Button Source # 
type Rep Button = D1 (MetaData "Button" "Graphics.Vty.Input.Events" "vty-5.15.1-DXxVH8hZfWcLVVBML8dvvP" False) ((:+:) (C1 (MetaCons "BLeft" PrefixI False) U1) ((:+:) (C1 (MetaCons "BMiddle" PrefixI False) U1) (C1 (MetaCons "BRight" PrefixI False) U1)))

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

If read from eventChannel this is the size at the time of the signal. If read from nextEvent this is the size at the time the event was processed by Vty. Typically these are the same, but if somebody is resizing the terminal quickly they can be different.

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.

Instances

Eq Event Source # 

Methods

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

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

Ord Event Source # 

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 #

Read Event Source # 
Show Event Source # 

Methods

showsPrec :: Int -> Event -> ShowS #

show :: Event -> String #

showList :: [Event] -> ShowS #

Generic Event Source # 

Associated Types

type Rep Event :: * -> * #

Methods

from :: Event -> Rep Event x #

to :: Rep Event x -> Event #

type Rep Event Source # 
type Rep Event = D1 (MetaData "Event" "Graphics.Vty.Input.Events" "vty-5.15.1-DXxVH8hZfWcLVVBML8dvvP" False) ((:+:) ((:+:) (C1 (MetaCons "EvKey" PrefixI False) ((:*:) (S1 (MetaSel (Nothing Symbol) NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 Key)) (S1 (MetaSel (Nothing Symbol) NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 [Modifier])))) (C1 (MetaCons "EvMouseDown" PrefixI False) ((:*:) ((:*:) (S1 (MetaSel (Nothing Symbol) NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 Int)) (S1 (MetaSel (Nothing Symbol) NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 Int))) ((:*:) (S1 (MetaSel (Nothing Symbol) NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 Button)) (S1 (MetaSel (Nothing Symbol) NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 [Modifier])))))) ((:+:) (C1 (MetaCons "EvMouseUp" PrefixI False) ((:*:) (S1 (MetaSel (Nothing Symbol) NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 Int)) ((:*:) (S1 (MetaSel (Nothing Symbol) NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 Int)) (S1 (MetaSel (Nothing Symbol) NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 (Maybe Button)))))) ((:+:) (C1 (MetaCons "EvResize" PrefixI False) ((:*:) (S1 (MetaSel (Nothing Symbol) NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 Int)) (S1 (MetaSel (Nothing Symbol) NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 Int)))) (C1 (MetaCons "EvPaste" PrefixI False) (S1 (MetaSel (Nothing Symbol) NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 ByteString))))))