vgrep-0.2.3.0: A pager for grep
Safe HaskellSafe-Inferred
LanguageHaskell2010

Vgrep.Key

Description

Basic definitions for Keys, Modifiers, and Chords of Keys and Modifiers. We can read key Chords from Graphics.Vty EvKey events using fromVty.

This module is intended for qualified import:

import qualified Vgrep.Key as Key

We define our own Key and Mod types rather than using Graphics.Vty's Key and Modifier, because it simplifies parsing (of keys like Space and Tab, which are represented as ' ' and 't' in Graphics.Vty), and because a Set of Mods is simpler to check for equality than a list of Modifiers.

Synopsis

Documentation

data Chord Source #

A chord of keys and modifiers pressed simultaneously.

Constructors

Chord (Set Mod) Key 

Instances

Instances details
Eq Chord Source # 
Instance details

Defined in Vgrep.Key

Methods

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

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

Ord Chord Source # 
Instance details

Defined in Vgrep.Key

Methods

compare :: Chord -> Chord -> Ordering #

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

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

(>) :: Chord -> Chord -> Bool #

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

max :: Chord -> Chord -> Chord #

min :: Chord -> Chord -> Chord #

Show Chord Source # 
Instance details

Defined in Vgrep.Key

Methods

showsPrec :: Int -> Chord -> ShowS #

show :: Chord -> String #

showList :: [Chord] -> ShowS #

Generic Chord Source # 
Instance details

Defined in Vgrep.Key

Associated Types

type Rep Chord :: Type -> Type #

Methods

from :: Chord -> Rep Chord x #

to :: Rep Chord x -> Chord #

type Rep Chord Source # 
Instance details

Defined in Vgrep.Key

type Rep Chord = D1 ('MetaData "Chord" "Vgrep.Key" "vgrep-0.2.3.0-79CAs1b54BVGsHizAm4Sjp" 'False) (C1 ('MetaCons "Chord" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (Set Mod)) :*: S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 Key)))

data Key Source #

Instances

Instances details
Eq Key Source # 
Instance details

Defined in Vgrep.Key

Methods

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

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

Ord Key Source # 
Instance details

Defined in Vgrep.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 #

Read Key Source # 
Instance details

Defined in Vgrep.Key

Show Key Source # 
Instance details

Defined in Vgrep.Key

Methods

showsPrec :: Int -> Key -> ShowS #

show :: Key -> String #

showList :: [Key] -> ShowS #

Generic Key Source # 
Instance details

Defined in Vgrep.Key

Associated Types

type Rep Key :: Type -> Type #

Methods

from :: Key -> Rep Key x #

to :: Rep Key x -> Key #

type Rep Key Source # 
Instance details

Defined in Vgrep.Key

type Rep Key = D1 ('MetaData "Key" "Vgrep.Key" "vgrep-0.2.3.0-79CAs1b54BVGsHizAm4Sjp" 'False) (((C1 ('MetaCons "Char" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 Char)) :+: (C1 ('MetaCons "Space" 'PrefixI 'False) (U1 :: Type -> Type) :+: C1 ('MetaCons "Esc" 'PrefixI 'False) (U1 :: Type -> Type))) :+: ((C1 ('MetaCons "Backspace" 'PrefixI 'False) (U1 :: Type -> Type) :+: C1 ('MetaCons "Enter" 'PrefixI 'False) (U1 :: Type -> Type)) :+: (C1 ('MetaCons "Del" 'PrefixI 'False) (U1 :: Type -> Type) :+: C1 ('MetaCons "Tab" '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 "Home" 'PrefixI 'False) (U1 :: Type -> Type) :+: C1 ('MetaCons "End" 'PrefixI 'False) (U1 :: Type -> Type)) :+: (C1 ('MetaCons "PageUp" 'PrefixI 'False) (U1 :: Type -> Type) :+: C1 ('MetaCons "PageDown" 'PrefixI 'False) (U1 :: Type -> Type)))))

data Mod Source #

Constructors

Ctrl 
Meta 
Shift 

Instances

Instances details
Eq Mod Source # 
Instance details

Defined in Vgrep.Key

Methods

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

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

Ord Mod Source # 
Instance details

Defined in Vgrep.Key

Methods

compare :: Mod -> Mod -> Ordering #

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

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

(>) :: Mod -> Mod -> Bool #

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

max :: Mod -> Mod -> Mod #

min :: Mod -> Mod -> Mod #

Show Mod Source # 
Instance details

Defined in Vgrep.Key

Methods

showsPrec :: Int -> Mod -> ShowS #

show :: Mod -> String #

showList :: [Mod] -> ShowS #

Generic Mod Source # 
Instance details

Defined in Vgrep.Key

Associated Types

type Rep Mod :: Type -> Type #

Methods

from :: Mod -> Rep Mod x #

to :: Rep Mod x -> Mod #

type Rep Mod Source # 
Instance details

Defined in Vgrep.Key

type Rep Mod = D1 ('MetaData "Mod" "Vgrep.Key" "vgrep-0.2.3.0-79CAs1b54BVGsHizAm4Sjp" 'False) (C1 ('MetaCons "Ctrl" 'PrefixI 'False) (U1 :: Type -> Type) :+: (C1 ('MetaCons "Meta" 'PrefixI 'False) (U1 :: Type -> Type) :+: C1 ('MetaCons "Shift" 'PrefixI 'False) (U1 :: Type -> Type)))

fromVty :: Event -> Maybe Chord Source #

Reads the key and modifiers from an Event. Non-key events and events with unknown keys are mapped to Nothing.

key :: Key -> Chord Source #

Build a Chord from a single Key

withModifier :: Chord -> Mod -> Chord Source #

Add a Modifier to a Chord