ribosome-test-0.9.9.9: Test tools for Ribosome
Safe HaskellSafe-Inferred
LanguageHaskell2010

Ribosome.Handler

Synopsis

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).

Constructors

CompleteFiltered

Completion returns matching items.

CompleteUnfiltered

Completion returns all items.

Instances

Instances details
Show CompleteStyle 
Instance details

Defined in Ribosome.Host.Data.RpcType

Eq CompleteStyle 
Instance details

Defined in Ribosome.Host.Data.RpcType

newtype AutocmdEvents #

A set of autocmd event specifiers, like BufEnter, used to create and trigger autocmds.

Constructors

AutocmdEvents 

Fields

Instances

Instances details
IsString AutocmdEvents 
Instance details

Defined in Ribosome.Host.Data.RpcType

Generic AutocmdEvents 
Instance details

Defined in Ribosome.Host.Data.RpcType

Associated Types

type Rep AutocmdEvents :: Type -> Type #

Show AutocmdEvents 
Instance details

Defined in Ribosome.Host.Data.RpcType

Eq AutocmdEvents 
Instance details

Defined in Ribosome.Host.Data.RpcType

MsgpackDecode AutocmdEvents 
Instance details

Defined in Ribosome.Host.Data.RpcType

MsgpackEncode AutocmdEvents 
Instance details

Defined in Ribosome.Host.Data.RpcType

type Rep AutocmdEvents 
Instance details

Defined in Ribosome.Host.Data.RpcType

type Rep AutocmdEvents = D1 ('MetaData "AutocmdEvents" "Ribosome.Host.Data.RpcType" "ribosome-host-0.9.9.9-4n86eC1033RAA2pmC2T1m9" 'True) (C1 ('MetaCons "AutocmdEvents" 'PrefixI 'True) (S1 ('MetaSel ('Just "unAutocmdEvent") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 [Text])))

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.

Constructors

AutocmdPatterns 

Fields

data AutocmdOptions #

The options with which an autocmd may be defined.

See :help :autocmd.

Instances

Instances details
IsString AutocmdOptions 
Instance details

Defined in Ribosome.Host.Data.RpcType

Generic AutocmdOptions 
Instance details

Defined in Ribosome.Host.Data.RpcType

Associated Types

type Rep AutocmdOptions :: Type -> Type #

Show AutocmdOptions 
Instance details

Defined in Ribosome.Host.Data.RpcType

Default AutocmdOptions 
Instance details

Defined in Ribosome.Host.Data.RpcType

Methods

def :: AutocmdOptions #

Eq AutocmdOptions 
Instance details

Defined in Ribosome.Host.Data.RpcType

type Rep AutocmdOptions 
Instance details

Defined in Ribosome.Host.Data.RpcType

type Rep AutocmdOptions = D1 ('MetaData "AutocmdOptions" "Ribosome.Host.Data.RpcType" "ribosome-host-0.9.9.9-4n86eC1033RAA2pmC2T1m9" 'False) (C1 ('MetaCons "AutocmdOptions" 'PrefixI 'True) ((S1 ('MetaSel ('Just "target") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (Either AutocmdBuffer AutocmdPatterns)) :*: S1 ('MetaSel ('Just "nested") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 Bool)) :*: (S1 ('MetaSel ('Just "once") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 Bool) :*: S1 ('MetaSel ('Just "group") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (Maybe AutocmdGroup)))))

data CommandCompletion #

The completion to use for a command.

Constructors

CompleteBuiltin Text

Complete with one of the builtin completions, see :help :command-completion.

CompleteHandler CompleteStyle RpcName

Complete with an RPC handler defined by a plugin.

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

Instances details
Show CommandOptions 
Instance details

Defined in Ribosome.Host.Data.RpcType

data RpcType #

The type of RPC handler and its options.

Instances

Instances details
Generic RpcType 
Instance details

Defined in Ribosome.Host.Data.RpcType

Associated Types

type Rep RpcType :: Type -> Type #

Methods

from :: RpcType -> Rep RpcType x #

to :: Rep RpcType x -> RpcType #

Show RpcType 
Instance details

Defined in Ribosome.Host.Data.RpcType

type Rep RpcType 
Instance details

Defined in Ribosome.Host.Data.RpcType

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 #

Create a completion handler that can be used by another handler by wrapping it with complete, using the same RpcName.

complete :: forall (r :: [(Type -> Type) -> Type -> Type]). CommandCompletion -> RpcHandler r -> RpcHandler r #

Add the given completion to an RpcHandler.