ribosome-host-0.9.9.9: Neovim plugin host for Polysemy
Safe HaskellSafe-Inferred
LanguageHaskell2010

Ribosome.Host.Data.RpcHandler

Synopsis

Documentation

type Handler r a = Sem (Stop Report ': r) a Source #

A request handler function is a Sem with arbitrary stack that has an error of type Report at its head.

These error messages are reported to the user by return value for synchronous requests and via echo for asynchronous ones, provided that the severity specified in the error is greater than the log level set in UserError.

If the plugin was started with --log-file, it is also written to the file log. Additionally, reports are stored in memory by the effect Reports.

For an explanation of Stop, see Errors.

type RpcHandlerFun r = [Object] -> Handler r Object Source #

This type is the canonical form of an RPC handler, taking a list of MessagePack Objects to a Sem with a Report at the head, returning an Object.

data RpcHandler r Source #

This type defines a request handler, using a Handler function, the request type, a name, and whether it should block Neovim while executing. It can be constructed from handler functions using rpcFunction, rpcCommand and rpcAutocmd.

A list of RpcHandlers can be used as a Neovim plugin by passing them to runNvimHandlersIO.

Constructors

RpcHandler 

Fields

  • rpcType :: RpcType

    Whether the trigger is a function, command, or autocmd, and the various options Neovim offers for them.

  • rpcName :: RpcName

    An identifier used to associate a request with a handler, which is also used as the name of the function or command.

  • rpcExecution :: Execution

    If this is Sync, the handler will block Neovim via rpcrequest. If it is Async, Neovim will use rpcnotify and forget about it.

  • rpcHandler :: RpcHandlerFun r

    The function operating on raw msgpack objects, derived from a Handler by the smart constructors.

Instances

Instances details
Generic (RpcHandler r) Source # 
Instance details

Defined in Ribosome.Host.Data.RpcHandler

Associated Types

type Rep (RpcHandler r) :: Type -> Type #

Methods

from :: RpcHandler r -> Rep (RpcHandler r) x #

to :: Rep (RpcHandler r) x -> RpcHandler r #

Show (RpcHandler m) Source # 
Instance details

Defined in Ribosome.Host.Data.RpcHandler

type Rep (RpcHandler r) Source # 
Instance details

Defined in Ribosome.Host.Data.RpcHandler

type Rep (RpcHandler r) = D1 ('MetaData "RpcHandler" "Ribosome.Host.Data.RpcHandler" "ribosome-host-0.9.9.9-4n86eC1033RAA2pmC2T1m9" 'False) (C1 ('MetaCons "RpcHandler" 'PrefixI 'True) ((S1 ('MetaSel ('Just "rpcType") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 RpcType) :*: S1 ('MetaSel ('Just "rpcName") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 RpcName)) :*: (S1 ('MetaSel ('Just "rpcExecution") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 Execution) :*: S1 ('MetaSel ('Just "rpcHandler") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (RpcHandlerFun r)))))

hoistRpcHandler :: (forall x. Sem (Stop Report ': r) x -> Sem (Stop Report ': r1) x) -> RpcHandler r -> RpcHandler r1 Source #

Apply a stack-manipulating transformation to the handler function.

hoistRpcHandlers :: (forall x. Sem (Stop Report ': r) x -> Sem (Stop Report ': r1) x) -> [RpcHandler r] -> [RpcHandler r1] Source #

Apply a stack-manipulating transformation to the handler functions.

rpcMethod :: RpcType -> RpcName -> RpcMethod Source #

Create an RpcMethod by joining an RpcType and an RpcName with a colon.

rpcHandlerMethod :: RpcHandler r -> RpcMethod Source #

Create an RpcMethod by joining an RpcType and an RpcName with a colon, extracted from an RpcHandler.

simpleHandler :: Member (Rpc !! RpcError) r => Sem (Rpc ': (Stop Report ': r)) a -> Handler r a Source #

Convert a handler using Rpc without handling errors to the canonical Handler type.