yi-keymap-vim-0.19.0: Vim keymap for Yi editor
LicenseGPL-2
Maintaineryi-devel@googlegroups.com
Stabilityexperimental
Portabilityportable
Safe HaskellNone
LanguageHaskell2010
Extensions
  • Cpp
  • TemplateHaskell
  • TemplateHaskellQuotes
  • DeriveDataTypeable
  • DeriveGeneric
  • GeneralizedNewtypeDeriving

Yi.Keymap.Vim.Common

Description

Common types used by the vim keymap.

Documentation

data VimMode Source #

Constructors

Normal 
NormalOperatorPending OperatorName 
Insert Char

char denotes how state got into insert mode (i, a, etc.)

Replace 
ReplaceSingleChar 
InsertNormal

after C-o

InsertVisual

after C-o and one of v, V, C-v

Visual RegionStyle 
Ex 
Search 

Instances

Instances details
Eq VimMode Source # 
Instance details

Defined in Yi.Keymap.Vim.Common

Methods

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

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

Show VimMode Source # 
Instance details

Defined in Yi.Keymap.Vim.Common

Generic VimMode Source # 
Instance details

Defined in Yi.Keymap.Vim.Common

Associated Types

type Rep VimMode :: Type -> Type #

Methods

from :: VimMode -> Rep VimMode x #

to :: Rep VimMode x -> VimMode #

Binary VimMode Source # 
Instance details

Defined in Yi.Keymap.Vim.Common

Methods

put :: VimMode -> Put #

get :: Get VimMode #

putList :: [VimMode] -> Put #

Default VimMode Source # 
Instance details

Defined in Yi.Keymap.Vim.Common

Methods

def :: VimMode #

type Rep VimMode Source # 
Instance details

Defined in Yi.Keymap.Vim.Common

type Rep VimMode = D1 ('MetaData "VimMode" "Yi.Keymap.Vim.Common" "yi-keymap-vim-0.19.0-DGElYUoNdNVDATo1msUqQB" 'False) (((C1 ('MetaCons "Normal" 'PrefixI 'False) (U1 :: Type -> Type) :+: C1 ('MetaCons "NormalOperatorPending" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 OperatorName))) :+: (C1 ('MetaCons "Insert" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 Char)) :+: (C1 ('MetaCons "Replace" 'PrefixI 'False) (U1 :: Type -> Type) :+: C1 ('MetaCons "ReplaceSingleChar" 'PrefixI 'False) (U1 :: Type -> Type)))) :+: ((C1 ('MetaCons "InsertNormal" 'PrefixI 'False) (U1 :: Type -> Type) :+: C1 ('MetaCons "InsertVisual" 'PrefixI 'False) (U1 :: Type -> Type)) :+: (C1 ('MetaCons "Visual" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 RegionStyle)) :+: (C1 ('MetaCons "Ex" 'PrefixI 'False) (U1 :: Type -> Type) :+: C1 ('MetaCons "Search" 'PrefixI 'True) (S1 ('MetaSel ('Just "previousMode") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 VimMode) :*: S1 ('MetaSel ('Just "direction") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 Direction))))))

data GotoCharCommand Source #

Instances

Instances details
Generic GotoCharCommand Source # 
Instance details

Defined in Yi.Keymap.Vim.Common

Associated Types

type Rep GotoCharCommand :: Type -> Type #

Binary GotoCharCommand Source # 
Instance details

Defined in Yi.Keymap.Vim.Common

type Rep GotoCharCommand Source # 
Instance details

Defined in Yi.Keymap.Vim.Common

type Rep GotoCharCommand = D1 ('MetaData "GotoCharCommand" "Yi.Keymap.Vim.Common" "yi-keymap-vim-0.19.0-DGElYUoNdNVDATo1msUqQB" 'False) (C1 ('MetaCons "GotoCharCommand" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'SourceStrict 'DecidedStrict) (Rec0 Char) :*: (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'SourceStrict 'DecidedStrict) (Rec0 Direction) :*: S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'SourceStrict 'DecidedStrict) (Rec0 RegionStyle))))

data VimState Source #

Instances

Instances details
Generic VimState Source # 
Instance details

Defined in Yi.Keymap.Vim.Common

Associated Types

type Rep VimState :: Type -> Type #

Methods

from :: VimState -> Rep VimState x #

to :: Rep VimState x -> VimState #

Binary VimState Source # 
Instance details

Defined in Yi.Keymap.Vim.Common

Methods

put :: VimState -> Put #

get :: Get VimState #

putList :: [VimState] -> Put #

Default VimState Source # 
Instance details

Defined in Yi.Keymap.Vim.Common

Methods

def :: VimState #

YiVariable VimState Source # 
Instance details

Defined in Yi.Keymap.Vim.Common

type Rep VimState Source # 
Instance details

Defined in Yi.Keymap.Vim.Common

data Register Source #

Instances

Instances details
Show Register Source # 
Instance details

Defined in Yi.Keymap.Vim.Common

Generic Register Source # 
Instance details

Defined in Yi.Keymap.Vim.Common

Associated Types

type Rep Register :: Type -> Type #

Methods

from :: Register -> Rep Register x #

to :: Rep Register x -> Register #

Binary Register Source # 
Instance details

Defined in Yi.Keymap.Vim.Common

Methods

put :: Register -> Put #

get :: Get Register #

putList :: [Register] -> Put #

type Rep Register Source # 
Instance details

Defined in Yi.Keymap.Vim.Common

type Rep Register = D1 ('MetaData "Register" "Yi.Keymap.Vim.Common" "yi-keymap-vim-0.19.0-DGElYUoNdNVDATo1msUqQB" 'False) (C1 ('MetaCons "Register" 'PrefixI 'True) (S1 ('MetaSel ('Just "regRegionStyle") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 RegionStyle) :*: S1 ('MetaSel ('Just "regContent") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 YiString)))

data RepeatToken Source #

Constructors

Finish 
Drop 
Continue 

Instances

Instances details
Show RepeatToken Source # 
Instance details

Defined in Yi.Keymap.Vim.Common

data RepeatableAction Source #

Instances

Instances details
Eq RepeatableAction Source # 
Instance details

Defined in Yi.Keymap.Vim.Common

Show RepeatableAction Source # 
Instance details

Defined in Yi.Keymap.Vim.Common

Generic RepeatableAction Source # 
Instance details

Defined in Yi.Keymap.Vim.Common

Associated Types

type Rep RepeatableAction :: Type -> Type #

Binary RepeatableAction Source # 
Instance details

Defined in Yi.Keymap.Vim.Common

type Rep RepeatableAction Source # 
Instance details

Defined in Yi.Keymap.Vim.Common

type Rep RepeatableAction = D1 ('MetaData "RepeatableAction" "Yi.Keymap.Vim.Common" "yi-keymap-vim-0.19.0-DGElYUoNdNVDATo1msUqQB" 'False) (C1 ('MetaCons "RepeatableAction" 'PrefixI 'True) (S1 ('MetaSel ('Just "raPreviousCount") 'NoSourceUnpackedness 'SourceStrict 'DecidedStrict) (Rec0 Int) :*: S1 ('MetaSel ('Just "raActionString") 'NoSourceUnpackedness 'SourceStrict 'DecidedStrict) (Rec0 EventString)))

data MatchResult a Source #

Constructors

NoMatch 
PartialMatch 
WholeMatch a 

Instances

Instances details
Functor MatchResult Source # 
Instance details

Defined in Yi.Keymap.Vim.MatchResult

Methods

fmap :: (a -> b) -> MatchResult a -> MatchResult b #

(<$) :: a -> MatchResult b -> MatchResult a #

Applicative MatchResult Source # 
Instance details

Defined in Yi.Keymap.Vim.MatchResult

Methods

pure :: a -> MatchResult a #

(<*>) :: MatchResult (a -> b) -> MatchResult a -> MatchResult b #

liftA2 :: (a -> b -> c) -> MatchResult a -> MatchResult b -> MatchResult c #

(*>) :: MatchResult a -> MatchResult b -> MatchResult b #

(<*) :: MatchResult a -> MatchResult b -> MatchResult a #

Alternative MatchResult Source # 
Instance details

Defined in Yi.Keymap.Vim.MatchResult

Show (MatchResult a) Source # 
Instance details

Defined in Yi.Keymap.Vim.MatchResult

newtype EventString Source #

Constructors

Ev 

Fields

Instances

Instances details
Eq EventString Source # 
Instance details

Defined in Yi.Keymap.Vim.Common

Ord EventString Source # 
Instance details

Defined in Yi.Keymap.Vim.Common

Show EventString Source # 
Instance details

Defined in Yi.Keymap.Vim.Common

IsString EventString Source # 
Instance details

Defined in Yi.Keymap.Vim.Common

Semigroup EventString Source # 
Instance details

Defined in Yi.Keymap.Vim.Common

Monoid EventString Source # 
Instance details

Defined in Yi.Keymap.Vim.Common

Binary EventString Source # 
Instance details

Defined in Yi.Keymap.Vim.Common

data Substitution Source #

Instances

Instances details
Generic Substitution Source # 
Instance details

Defined in Yi.Keymap.Vim.Common

Associated Types

type Rep Substitution :: Type -> Type #

Binary Substitution Source # 
Instance details

Defined in Yi.Keymap.Vim.Common

type Rep Substitution Source # 
Instance details

Defined in Yi.Keymap.Vim.Common

type Rep Substitution = D1 ('MetaData "Substitution" "Yi.Keymap.Vim.Common" "yi-keymap-vim-0.19.0-DGElYUoNdNVDATo1msUqQB" 'False) (C1 ('MetaCons "Substitution" 'PrefixI 'True) ((S1 ('MetaSel ('Just "subsFrom") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 YiString) :*: S1 ('MetaSel ('Just "subsTo") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 YiString)) :*: (S1 ('MetaSel ('Just "subsFlagGlobal") 'NoSourceUnpackedness 'SourceStrict 'DecidedStrict) (Rec0 Bool) :*: (S1 ('MetaSel ('Just "subsFlagCaseInsensitive") 'NoSourceUnpackedness 'SourceStrict 'DecidedStrict) (Rec0 Bool) :*: S1 ('MetaSel ('Just "subsFlagConfirm") 'NoSourceUnpackedness 'SourceStrict 'DecidedStrict) (Rec0 Bool)))))

data MatchResult a Source #

Constructors

NoMatch 
PartialMatch 
WholeMatch a 

Instances

Instances details
Functor MatchResult Source # 
Instance details

Defined in Yi.Keymap.Vim.MatchResult

Methods

fmap :: (a -> b) -> MatchResult a -> MatchResult b #

(<$) :: a -> MatchResult b -> MatchResult a #

Applicative MatchResult Source # 
Instance details

Defined in Yi.Keymap.Vim.MatchResult

Methods

pure :: a -> MatchResult a #

(<*>) :: MatchResult (a -> b) -> MatchResult a -> MatchResult b #

liftA2 :: (a -> b -> c) -> MatchResult a -> MatchResult b -> MatchResult c #

(*>) :: MatchResult a -> MatchResult b -> MatchResult b #

(<*) :: MatchResult a -> MatchResult b -> MatchResult a #

Alternative MatchResult Source # 
Instance details

Defined in Yi.Keymap.Vim.MatchResult

Show (MatchResult a) Source # 
Instance details

Defined in Yi.Keymap.Vim.MatchResult