Safe Haskell | Safe-Inferred |
---|---|
Language | Haskell2010 |
Synopsis
- data CompleteStyle
- newtype AutocmdEvents = AutocmdEvents {
- unAutocmdEvent :: [Text]
- newtype AutocmdPatterns = AutocmdPatterns {
- unAutocmdPattern :: [Text]
- newtype AutocmdGroup = AutocmdGroup {}
- data AutocmdOptions = AutocmdOptions {}
- data CommandCompletion
- data CommandOptions = CommandOptions {}
- data RpcType
- completeBuiltin :: forall (r :: [(Type -> Type) -> Type -> Type]). Text -> RpcHandler r -> RpcHandler r
- completeWith :: forall (r :: [(Type -> Type) -> Type -> Type]). CompleteStyle -> (Text -> Text -> Int -> Handler r [Text]) -> RpcHandler r -> [RpcHandler r]
- completeCustom :: forall (r :: [(Type -> Type) -> Type -> Type]). RpcName -> (Text -> Text -> Int -> Handler r [Text]) -> CompleteStyle -> RpcHandler r
- complete :: forall (r :: [(Type -> Type) -> Type -> Type]). CommandCompletion -> RpcHandler r -> RpcHandler r
Documentation
data CompleteStyle #
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 | |
Defined in Ribosome.Host.Data.RpcType showsPrec :: Int -> CompleteStyle -> ShowS # show :: CompleteStyle -> String # showList :: [CompleteStyle] -> ShowS # | |
Eq CompleteStyle | |
Defined in Ribosome.Host.Data.RpcType (==) :: CompleteStyle -> CompleteStyle -> Bool # (/=) :: CompleteStyle -> CompleteStyle -> Bool # |
newtype AutocmdEvents #
A set of autocmd event specifiers, like BufEnter
, used to create and trigger autocmds.
Instances
newtype AutocmdPatterns #
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 | |
Defined in Ribosome.Host.Data.RpcType fromString :: String -> AutocmdPatterns # | |
Show AutocmdPatterns | |
Defined in Ribosome.Host.Data.RpcType showsPrec :: Int -> AutocmdPatterns -> ShowS # show :: AutocmdPatterns -> String # showList :: [AutocmdPatterns] -> ShowS # | |
Default AutocmdPatterns | |
Defined in Ribosome.Host.Data.RpcType def :: AutocmdPatterns # | |
Eq AutocmdPatterns | |
Defined in Ribosome.Host.Data.RpcType (==) :: AutocmdPatterns -> AutocmdPatterns -> Bool # (/=) :: AutocmdPatterns -> AutocmdPatterns -> Bool # | |
MsgpackDecode AutocmdPatterns | |
Defined in Ribosome.Host.Data.RpcType fromMsgpack :: Object -> Either Text AutocmdPatterns # missingKey :: String -> Object -> Either Text AutocmdPatterns # | |
MsgpackEncode AutocmdPatterns | |
Defined in Ribosome.Host.Data.RpcType toMsgpack :: AutocmdPatterns -> Object # |
newtype AutocmdGroup #
An autocmd group.
Instances
data AutocmdOptions #
The options with which an autocmd may be defined.
See :help :autocmd
.
AutocmdOptions | |
|
Instances
data CommandCompletion #
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 | |
Defined in Ribosome.Host.Data.RpcType showsPrec :: Int -> CommandCompletion -> ShowS # show :: CommandCompletion -> String # showList :: [CommandCompletion] -> ShowS # | |
Eq CommandCompletion | |
Defined in Ribosome.Host.Data.RpcType (==) :: CommandCompletion -> CommandCompletion -> Bool # (/=) :: CommandCompletion -> CommandCompletion -> Bool # |
data CommandOptions #
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 | |
Defined in Ribosome.Host.Data.RpcType showsPrec :: Int -> CommandOptions -> ShowS # show :: CommandOptions -> String # showList :: [CommandOptions] -> ShowS # |
The type of RPC handler and its options.
Instances
Generic RpcType | |
Show RpcType | |
type Rep RpcType | |
Defined in Ribosome.Host.Data.RpcType type Rep RpcType = D1 ('MetaData "RpcType" "Ribosome.Host.Data.RpcType" "ribosome-host-0.9.9.9-5mVeOZw909e7nfaEBEbC5r" '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)))) |
completeBuiltin :: forall (r :: [(Type -> Type) -> Type -> Type]). Text -> RpcHandler r -> RpcHandler r #
Configure the given RpcHandler
to use the specified builtin completion.
completeWith :: forall (r :: [(Type -> Type) -> Type -> Type]). CompleteStyle -> (Text -> Text -> Int -> Handler r [Text]) -> RpcHandler r -> [RpcHandler r] #
Add command line completion to another RpcHandler
by creating a new handler that calls the given function to
obtain possible completions.
completeCustom :: forall (r :: [(Type -> Type) -> Type -> Type]). RpcName -> (Text -> Text -> Int -> Handler r [Text]) -> CompleteStyle -> RpcHandler r #
complete :: forall (r :: [(Type -> Type) -> Type -> Type]). CommandCompletion -> RpcHandler r -> RpcHandler r #
Add the given completion to an RpcHandler
.