| License | GPL-2 |
|---|---|
| Maintainer | yi-devel@googlegroups.com |
| Stability | experimental |
| Portability | portable |
| Safe Haskell | None |
| Language | Haskell2010 |
| Extensions |
|
Yi.Keymap.Vim.Common
Description
Common types used by the vim keymap.
Documentation
Constructors
| Normal | |
| NormalOperatorPending OperatorName | |
| Insert Char | char denotes how state got into insert mode ( |
| Replace | |
| ReplaceSingleChar | |
| InsertNormal | after C-o |
| InsertVisual | after C-o and one of v, V, C-v |
| Visual RegionStyle | |
| Ex | |
| Search | |
Fields | |
Instances
data VimBinding Source #
Constructors
| VimBindingY (EventString -> VimState -> MatchResult (YiM RepeatToken)) | |
| VimBindingE (EventString -> VimState -> MatchResult (EditorM RepeatToken)) |
data GotoCharCommand Source #
Constructors
| GotoCharCommand !Char !Direction !RegionStyle |
Instances
| Generic GotoCharCommand Source # | |
Defined in Yi.Keymap.Vim.Common Associated Types type Rep GotoCharCommand :: Type -> Type # Methods from :: GotoCharCommand -> Rep GotoCharCommand x # to :: Rep GotoCharCommand x -> GotoCharCommand # | |
| Binary GotoCharCommand Source # | |
Defined in Yi.Keymap.Vim.Common Methods put :: GotoCharCommand -> Put # get :: Get GotoCharCommand # putList :: [GotoCharCommand] -> Put # | |
| type Rep GotoCharCommand Source # | |
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)))) | |
Constructors
| VimState | |
Fields
| |
Constructors
| Register | |
Fields | |
Instances
| Show Register Source # | |
| Generic Register Source # | |
| Binary Register Source # | |
| type Rep Register Source # | |
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 #
Instances
| Show RepeatToken Source # | |
Defined in Yi.Keymap.Vim.Common Methods showsPrec :: Int -> RepeatToken -> ShowS # show :: RepeatToken -> String # showList :: [RepeatToken] -> ShowS # | |
data RepeatableAction Source #
Constructors
| RepeatableAction | |
Fields
| |
Instances
data MatchResult a Source #
Constructors
| NoMatch | |
| PartialMatch | |
| WholeMatch a |
Instances
| Functor MatchResult Source # | |
Defined in Yi.Keymap.Vim.MatchResult Methods fmap :: (a -> b) -> MatchResult a -> MatchResult b # (<$) :: a -> MatchResult b -> MatchResult a # | |
| Applicative MatchResult Source # | |
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 # | |
Defined in Yi.Keymap.Vim.MatchResult Methods empty :: MatchResult a # (<|>) :: MatchResult a -> MatchResult a -> MatchResult a # some :: MatchResult a -> MatchResult [a] # many :: MatchResult a -> MatchResult [a] # | |
| Show (MatchResult a) Source # | |
Defined in Yi.Keymap.Vim.MatchResult Methods showsPrec :: Int -> MatchResult a -> ShowS # show :: MatchResult a -> String # showList :: [MatchResult a] -> ShowS # | |
newtype EventString Source #
Instances
newtype OperatorName Source #
Instances
| Eq OperatorName Source # | |
Defined in Yi.Keymap.Vim.Common | |
| Show OperatorName Source # | |
Defined in Yi.Keymap.Vim.Common Methods showsPrec :: Int -> OperatorName -> ShowS # show :: OperatorName -> String # showList :: [OperatorName] -> ShowS # | |
| IsString OperatorName Source # | |
Defined in Yi.Keymap.Vim.Common Methods fromString :: String -> OperatorName # | |
| Semigroup OperatorName Source # | |
Defined in Yi.Keymap.Vim.Common Methods (<>) :: OperatorName -> OperatorName -> OperatorName # sconcat :: NonEmpty OperatorName -> OperatorName # stimes :: Integral b => b -> OperatorName -> OperatorName # | |
| Monoid OperatorName Source # | |
Defined in Yi.Keymap.Vim.Common Methods mempty :: OperatorName # mappend :: OperatorName -> OperatorName -> OperatorName # mconcat :: [OperatorName] -> OperatorName # | |
| Binary OperatorName Source # | |
Defined in Yi.Keymap.Vim.Common | |
type RegisterName = Char Source #
data Substitution Source #
Constructors
| Substitution | |
Fields
| |
Instances
| Generic Substitution Source # | |
Defined in Yi.Keymap.Vim.Common Associated Types type Rep Substitution :: Type -> Type # | |
| Binary Substitution Source # | |
Defined in Yi.Keymap.Vim.Common | |
| type Rep Substitution Source # | |
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
| Functor MatchResult Source # | |
Defined in Yi.Keymap.Vim.MatchResult Methods fmap :: (a -> b) -> MatchResult a -> MatchResult b # (<$) :: a -> MatchResult b -> MatchResult a # | |
| Applicative MatchResult Source # | |
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 # | |
Defined in Yi.Keymap.Vim.MatchResult Methods empty :: MatchResult a # (<|>) :: MatchResult a -> MatchResult a -> MatchResult a # some :: MatchResult a -> MatchResult [a] # many :: MatchResult a -> MatchResult [a] # | |
| Show (MatchResult a) Source # | |
Defined in Yi.Keymap.Vim.MatchResult Methods showsPrec :: Int -> MatchResult a -> ShowS # show :: MatchResult a -> String # showList :: [MatchResult a] -> ShowS # | |
lookupBestMatch :: EventString -> [(EventString, a)] -> MatchResult a Source #
matchesString :: EventString -> EventString -> MatchResult () Source #