Safe Haskell | Safe-Inferred |
---|---|
Language | Haskell2010 |
Synopsis
- newtype AutocmdEvents = AutocmdEvents {
- unAutocmdEvent :: [Text]
- newtype AutocmdPatterns = AutocmdPatterns {
- unAutocmdPattern :: [Text]
- newtype AutocmdBuffer = AutocmdBuffer {}
- newtype AutocmdGroup = AutocmdGroup {}
- data AutocmdOptions = AutocmdOptions {}
- newtype AutocmdId = AutocmdId {
- unAutocmdId :: Int
- data CompleteStyle
- data CommandCompletion
- completionName :: RpcName -> RpcName
- completionValue :: CommandCompletion -> Text
- completionOption :: CommandCompletion -> Text
- data CommandOptions = CommandOptions {}
- newtype CommandArgs = CommandArgs {
- unCommandArgs :: [Text]
- data RpcType
- methodPrefix :: RpcType -> Text
Documentation
newtype AutocmdEvents Source #
A set of autocmd event specifiers, like BufEnter
, used to create and trigger autocmds.
Instances
newtype AutocmdPatterns Source #
A file pattern like *.hs
that defines the files in which an autocmd should be triggered.
If the AutocmdEvents
contain User
, this denotes the custom event name.
Instances
IsString AutocmdPatterns Source # | |
Defined in Ribosome.Host.Data.RpcType fromString :: String -> AutocmdPatterns # | |
Show AutocmdPatterns Source # | |
Defined in Ribosome.Host.Data.RpcType showsPrec :: Int -> AutocmdPatterns -> ShowS # show :: AutocmdPatterns -> String # showList :: [AutocmdPatterns] -> ShowS # | |
Default AutocmdPatterns Source # | |
Defined in Ribosome.Host.Data.RpcType def :: AutocmdPatterns # | |
Eq AutocmdPatterns Source # | |
Defined in Ribosome.Host.Data.RpcType (==) :: AutocmdPatterns -> AutocmdPatterns -> Bool # (/=) :: AutocmdPatterns -> AutocmdPatterns -> Bool # | |
MsgpackDecode AutocmdPatterns Source # | |
Defined in Ribosome.Host.Data.RpcType | |
MsgpackEncode AutocmdPatterns Source # | |
Defined in Ribosome.Host.Data.RpcType toMsgpack :: AutocmdPatterns -> Object Source # |
newtype AutocmdBuffer Source #
The buffer number in which a buffer autocmd is supposed to be created.
Instances
newtype AutocmdGroup Source #
An autocmd group.
Instances
data AutocmdOptions Source #
The options with which an autocmd may be defined.
See :help :autocmd
.
AutocmdOptions | |
|
Instances
Neovim assigns ID numbers to autocmds.
Instances
Enum AutocmdId Source # | |
Defined in Ribosome.Host.Data.RpcType succ :: AutocmdId -> AutocmdId # pred :: AutocmdId -> AutocmdId # fromEnum :: AutocmdId -> Int # enumFrom :: AutocmdId -> [AutocmdId] # enumFromThen :: AutocmdId -> AutocmdId -> [AutocmdId] # enumFromTo :: AutocmdId -> AutocmdId -> [AutocmdId] # enumFromThenTo :: AutocmdId -> AutocmdId -> AutocmdId -> [AutocmdId] # | |
Num AutocmdId Source # | |
Defined in Ribosome.Host.Data.RpcType | |
Integral AutocmdId Source # | |
Defined in Ribosome.Host.Data.RpcType | |
Real AutocmdId Source # | |
Defined in Ribosome.Host.Data.RpcType toRational :: AutocmdId -> Rational # | |
Show AutocmdId Source # | |
Eq AutocmdId Source # | |
Ord AutocmdId Source # | |
Defined in Ribosome.Host.Data.RpcType | |
MsgpackDecode AutocmdId Source # | |
Defined in Ribosome.Host.Data.RpcType | |
MsgpackEncode AutocmdId Source # | |
data CompleteStyle Source #
Neovim command completion can be designated as returning all items that may be completed regardless of the current
word (CompleteUnfiltered
) or only those that match the current word (CompleteFiltered
).
CompleteFiltered | Completion returns matching items. |
CompleteUnfiltered | Completion returns all items. |
Instances
Show CompleteStyle Source # | |
Defined in Ribosome.Host.Data.RpcType showsPrec :: Int -> CompleteStyle -> ShowS # show :: CompleteStyle -> String # showList :: [CompleteStyle] -> ShowS # | |
Eq CompleteStyle Source # | |
Defined in Ribosome.Host.Data.RpcType (==) :: CompleteStyle -> CompleteStyle -> Bool # (/=) :: CompleteStyle -> CompleteStyle -> Bool # |
data CommandCompletion Source #
The completion to use for a command.
CompleteBuiltin Text | Complete with one of the builtin completions, see |
CompleteHandler CompleteStyle RpcName | Complete with an RPC handler defined by a plugin. |
Instances
Show CommandCompletion Source # | |
Defined in Ribosome.Host.Data.RpcType showsPrec :: Int -> CommandCompletion -> ShowS # show :: CommandCompletion -> String # showList :: [CommandCompletion] -> ShowS # | |
Eq CommandCompletion Source # | |
Defined in Ribosome.Host.Data.RpcType (==) :: CommandCompletion -> CommandCompletion -> Bool # (/=) :: CommandCompletion -> CommandCompletion -> Bool # |
completionName :: RpcName -> RpcName Source #
Generate a name for the completion handler of a handler by prefixing its name with Complete_
.
completionValue :: CommandCompletion -> Text Source #
Render a CommandCompletion
as the value to the -complete=
option for a command definition.
completionOption :: CommandCompletion -> Text Source #
Render a CommandCompletion
as the -complete=
option for a command definition.
data CommandOptions Source #
Options for an RPC command on the Neovim side, consisting of the options described at :help :command-attributes
and an optional completion handler.
Instances
Show CommandOptions Source # | |
Defined in Ribosome.Host.Data.RpcType showsPrec :: Int -> CommandOptions -> ShowS # show :: CommandOptions -> String # showList :: [CommandOptions] -> ShowS # |
newtype CommandArgs Source #
The special arguments passed to an RPC call on the Neovim side that correspond to the declared CommandOptions
.
CommandArgs | |
|
Instances
Show CommandArgs Source # | |
Defined in Ribosome.Host.Data.RpcType showsPrec :: Int -> CommandArgs -> ShowS # show :: CommandArgs -> String # showList :: [CommandArgs] -> ShowS # | |
Eq CommandArgs Source # | |
Defined in Ribosome.Host.Data.RpcType (==) :: CommandArgs -> CommandArgs -> Bool # (/=) :: CommandArgs -> CommandArgs -> Bool # |
The type of RPC handler and its options.
Instances
Generic RpcType Source # | |
Show RpcType Source # | |
type Rep RpcType Source # | |
Defined in Ribosome.Host.Data.RpcType type Rep RpcType = D1 ('MetaData "RpcType" "Ribosome.Host.Data.RpcType" "ribosome-host-0.9.9.9-4n86eC1033RAA2pmC2T1m9" 'False) (C1 ('MetaCons "Function" 'PrefixI 'False) (U1 :: Type -> Type) :+: (C1 ('MetaCons "Command" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 CommandOptions) :*: S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 CommandArgs)) :+: C1 ('MetaCons "Autocmd" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 AutocmdEvents) :*: S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 AutocmdOptions)))) |
methodPrefix :: RpcType -> Text Source #
The prefix for the method name used to identify an RPC handler.