Safe Haskell | Safe-Inferred |
---|---|
Language | Haskell2010 |
Synopsis
- interpretHostEmbed :: Members BasicStack r => InterpretersFor HostEmbedStack r
- withHostEmbed :: Members BasicStack r => InterpreterFor (Handlers !! Report) (HostEmbedStack ++ r) -> InterpretersFor HostEmbedStack r
- testHostEmbed :: Members BasicStack r => InterpreterFor (Handlers !! Report) (HostEmbedStack ++ r) -> InterpretersFor (Rpc ': HostEmbedStack) r
- embedNvim :: Members BasicStack r => [RpcHandler (HostEmbedStack ++ r)] -> InterpretersFor (Rpc ': HostEmbedStack) r
- embedNvim_ :: Members BasicStack r => InterpretersFor (Rpc ': HostEmbedStack) r
- interpretHostRemote :: Members BasicStack r => InterpretersFor HostRemoteStack r
- runHostRemote :: Members BasicStack r => InterpreterFor (Handlers !! Report) (HostRemoteStack ++ r) -> Sem r ()
- runHostRemoteIO :: HostConfig -> [RpcHandler HostRemoteIOStack] -> IO ()
- newtype HostConfig = HostConfig {}
- data LogConfig = LogConfig {
- logFile :: Maybe (Path Abs File)
- logLevelEcho :: Severity
- logLevelStderr :: Severity
- logLevelFile :: Severity
- dataLogConc :: Bool
- setStderr :: Severity -> HostConfig -> HostConfig
- data RpcHandler r = RpcHandler RpcType RpcName Execution (RpcHandlerFun r)
- type Handler r a = Sem (Stop Report ': r) a
- simpleHandler :: Member (Rpc !! RpcError) r => Sem (Rpc ': (Stop Report ': r)) a -> Handler r a
- data CompleteStyle
- data RpcError
- rpcError :: RpcError -> Text
- rpcFunction :: forall r h. HandlerCodec h r => RpcName -> Execution -> h -> RpcHandler r
- rpcCommand :: forall r h. HandlerCodec h r => CommandHandler OptionStateZero h => RpcName -> Execution -> h -> RpcHandler r
- completeBuiltin :: Text -> RpcHandler r -> RpcHandler r
- completeWith :: CompleteStyle -> (Text -> Text -> Int -> Handler r [Text]) -> RpcHandler r -> [RpcHandler r]
- rpcAutocmd :: forall r h. HandlerCodec h r => RpcName -> Execution -> AutocmdEvents -> AutocmdOptions -> h -> RpcHandler r
- rpc :: forall r h. HandlerCodec h r => CommandHandler OptionStateZero h => RpcName -> Execution -> h -> [RpcHandler r]
- data Execution
- module Ribosome.Host.Data.Args
- data Bang
- data Bar = Bar
- newtype CommandMods = CommandMods Text
- newtype CommandRegister = CommandRegister Text
- data Range (style :: RangeStyle) = Range Int64 (Maybe Int64)
- data RangeStyle
- data Handlers :: Effect
- data Host :: Effect
- type ScopedMState s = PScoped s () (MState s)
- data MState s :: Effect
- muse :: Member (MState s) r => (s -> Sem r (s, a)) -> Sem r a
- mtrans :: Member (MState s) r => (s -> Sem r s) -> Sem r ()
- mstate :: Member (MState s) r => (s -> (s, a)) -> Sem r a
- mmodify :: Member (MState s) r => (s -> s) -> Sem r ()
- mread :: Member (MState s) r => Sem r s
- mreads :: Member (MState s) r => (s -> a) -> Sem r a
- stateToMState :: Member (MState s) r => InterpreterFor (State s) r
- withMState :: Member (ScopedMState s) r => s -> InterpreterFor (MState s) r
- data Reports :: Effect
- data Responses k v :: Effect
- data Rpc :: Effect
- sync :: forall r a. Member Rpc r => RpcCall a -> Sem r a
- async :: forall a r. Member Rpc r => RpcCall a -> (Either RpcError a -> Sem r ()) -> Sem r ()
- notify :: forall a r. Member Rpc r => RpcCall a -> Sem r ()
- module Ribosome.Host.Effect.UserError
- noHandlers :: InterpreterFor (Handlers !! Report) r
- withHandlers :: Members [Handlers !! Report, Rpc !! RpcError, Log, Error BootError] r => [RpcHandler r] -> Sem r a -> Sem r a
- interpretHandlers :: Members [Rpc !! RpcError, Log, Error BootError] r => [RpcHandler r] -> InterpreterFor (Handlers !! Report) r
- type HostDeps er = [Handlers !! Report, Process RpcMessage (Either Text RpcMessage), Rpc !! RpcError, DataLog LogReport, Events er Event, Responses RequestId Response !! RpcError, Log, Error BootError, Resource, Mask Restoration, Race, Async, Embed IO, Final IO]
- interpretHost :: Members [Handlers !! Report, Rpc !! RpcError, DataLog LogReport, Events er Event, Log, Final IO] r => InterpreterFor Host r
- withHost :: Members (HostDeps er) r => InterpreterFor Host r
- testHost :: Members (HostDeps er) r => InterpretersFor [Rpc, Host] r
- runHost :: Members (HostDeps er) r => Sem r ()
- interpretLogs :: Members [Reader LogConfig, Resource, ChronosTime, Race, Async, Embed IO] r => InterpretersFor [StderrLog, FileLog] r
- interpretMState :: Members [Resource, Race, Mask mres, Embed IO] r => s -> InterpreterFor (MState s) r
- evalMState :: s -> InterpreterFor (MState s) r
- interpretMStates :: forall s mres r. Members [Mask mres, Resource, Race, Embed IO] r => InterpreterFor (ScopedMState s) r
- interpretReports :: Members [ChronosTime, Embed IO] r => InterpreterFor Reports r
- interpretResponses :: forall k v r. Ord k => Num k => Show k => Member (Embed IO) r => InterpreterFor (Responses k v !! RpcError) r
- interpretRpc :: forall o r. Member (AtomicState (Maybe ChannelId)) r => Members [Responses RequestId Response !! RpcError, Process RpcMessage o, Log, Async] r => InterpreterFor (Rpc !! RpcError) r
- interpretUserErrorInfo :: InterpreterFor UserError r
- data Window
- data Tabpage
- data Buffer
- class MsgpackDecode a where
- fromMsgpack :: Object -> Either DecodeError a
- class MsgpackEncode a where
- msgpackArray :: MsgpackArray a => a
- msgpackMap :: MsgpackMap a => a
- resumeReports :: ResumeReports effs errs r => InterpretersFor effs r
- mapReports :: MapReports errs r => InterpretersFor (Stops errs) r
- class Reportable e where
- data LogReport = LogReport Report Bool Bool ReportContext
- data Report where
- newtype ReportContext = ReportContext {
- unReportContext :: [Text]
- basicReport :: Member (Stop Report) r => HasCallStack => Text -> [Text] -> Sem r a
- mapReport :: forall e r a. Reportable e => Member (Stop Report) r => Sem (Stop e ': r) a -> Sem r a
- resumeReport :: forall eff e r a. Reportable e => Members [eff !! e, Stop Report] r => Sem (eff ': r) a -> Sem r a
- userReport :: forall e. Reportable e => e -> Text
- resumeHoistUserMessage :: forall err eff err' r. Reportable err => Members [eff !! err, Stop err'] r => (Text -> err') -> InterpreterFor eff r
- mapUserMessage :: forall err err' r. Reportable err => Member (Stop err') r => (Text -> err') -> InterpreterFor (Stop err) r
- ignoreRpcError :: Member (Rpc !! RpcError) r => Sem (Rpc ': r) a -> Sem r ()
- newtype BootError = BootError Text
- data StoredReport = StoredReport !Report !Time
Introduction
This library is a framework for building Neovim plugins with Polysemy.
This package is the low-level core of the Neovim plugin host and is not intended for authors who want to build full plugins. Please consult the documentation for the main package instead.
Execution
withHostEmbed :: Members BasicStack r => InterpreterFor (Handlers !! Report) (HostEmbedStack ++ r) -> InterpretersFor HostEmbedStack r Source #
testHostEmbed :: Members BasicStack r => InterpreterFor (Handlers !! Report) (HostEmbedStack ++ r) -> InterpretersFor (Rpc ': HostEmbedStack) r Source #
embedNvim :: Members BasicStack r => [RpcHandler (HostEmbedStack ++ r)] -> InterpretersFor (Rpc ': HostEmbedStack) r Source #
embedNvim_ :: Members BasicStack r => InterpretersFor (Rpc ': HostEmbedStack) r Source #
runHostRemote :: Members BasicStack r => InterpreterFor (Handlers !! Report) (HostRemoteStack ++ r) -> Sem r () Source #
runHostRemoteIO :: HostConfig -> [RpcHandler HostRemoteIOStack] -> IO () Source #
newtype HostConfig Source #
The configuration for a host, which consists only of a LogConfig
.
Instances
Generic HostConfig Source # | |
Defined in Ribosome.Host.Data.HostConfig type Rep HostConfig :: Type -> Type # from :: HostConfig -> Rep HostConfig x # to :: Rep HostConfig x -> HostConfig # | |
Show HostConfig Source # | |
Defined in Ribosome.Host.Data.HostConfig showsPrec :: Int -> HostConfig -> ShowS # show :: HostConfig -> String # showList :: [HostConfig] -> ShowS # | |
Default HostConfig Source # | |
Defined in Ribosome.Host.Data.HostConfig def :: HostConfig # | |
Eq HostConfig Source # | |
Defined in Ribosome.Host.Data.HostConfig (==) :: HostConfig -> HostConfig -> Bool # (/=) :: HostConfig -> HostConfig -> Bool # | |
type Rep HostConfig Source # | |
Defined in Ribosome.Host.Data.HostConfig type Rep HostConfig = D1 ('MetaData "HostConfig" "Ribosome.Host.Data.HostConfig" "ribosome-host-0.9.9.9-4n86eC1033RAA2pmC2T1m9" 'True) (C1 ('MetaCons "HostConfig" 'PrefixI 'True) (S1 ('MetaSel ('Just "hostLog") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 LogConfig))) |
Logging config for a host, with different levels for Neovim echoing, stderr and file logs.
Note that stderr logging will be sent to Neovim when the plugin is running in remote mode, which will be ignored unless the plugin is started with a stderr handler.
LogConfig | |
|
Instances
Generic LogConfig Source # | |
Show LogConfig Source # | |
Default LogConfig Source # | |
Defined in Ribosome.Host.Data.HostConfig | |
Eq LogConfig Source # | |
type Rep LogConfig Source # | |
Defined in Ribosome.Host.Data.HostConfig type Rep LogConfig = D1 ('MetaData "LogConfig" "Ribosome.Host.Data.HostConfig" "ribosome-host-0.9.9.9-4n86eC1033RAA2pmC2T1m9" 'False) (C1 ('MetaCons "LogConfig" 'PrefixI 'True) ((S1 ('MetaSel ('Just "logFile") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (Maybe (Path Abs File))) :*: S1 ('MetaSel ('Just "logLevelEcho") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 Severity)) :*: (S1 ('MetaSel ('Just "logLevelStderr") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 Severity) :*: (S1 ('MetaSel ('Just "logLevelFile") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 Severity) :*: S1 ('MetaSel ('Just "dataLogConc") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 Bool))))) |
setStderr :: Severity -> HostConfig -> HostConfig Source #
Set the stderr level on a HostConfig
.
Handlers
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 RpcHandler
s can be used as a Neovim plugin by passing them to runNvimHandlersIO
.
Instances
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
.
simpleHandler :: Member (Rpc !! RpcError) r => Sem (Rpc ': (Stop Report ': r)) a -> Handler r a 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 # |
The basic error type for the plugin host, used by the listener, Rpc
and several other components.
Instances
:: forall r h. HandlerCodec h r | |
=> RpcName | Name of the Neovim function that will be created. |
-> Execution | Execute sync or async. |
-> h | The handler function. |
-> RpcHandler r |
Create an RpcHandler
that is triggered by a Neovim function of the specified name.
The handler can take arbitrary parameters, as long as they are instances of MsgpackDecode
(or more
specifically, HandlerArg
), just like the return type.
When invoking the function from Neovim, a value must be passed for each of the handler function's parameters, except
for some special cases, like a number of successive Maybe
parameters at the tail of the parameter list.
The function is converted to use messagepack types by the class HandlerCodec
.
For easier type inference, it is advisable to use
for the return type of the handler instead of using
Handler
r a
.Member
(Stop
LogReport
) r
Example:
import Ribosome ping :: Int -> Handler r Int ping 0 = basicLogReport "Invalid ping number!" ["This is written to the log"] ping i = pure i rpcFunction "Ping" Sync ping
:: forall r h. HandlerCodec h r | |
=> CommandHandler OptionStateZero h | |
=> RpcName | Name of the Neovim function that will be created. |
-> Execution | Execute sync or async. |
-> h | The handler function. |
-> RpcHandler r |
Create an RpcHandler
that is triggered by a Neovim command of the specified name.
The handler can take arbitrary parameters, as long as they are instances of MsgpackDecode
(or more
specifically, HandlerArg
), just like the return type.
The function is converted to use messagepack types by the class HandlerCodec
.
Commands have an (open) family of special parameter types that will be translated into command options, like
Range
for the line range specified to the command.
See command params.
For easier type inference, it is advisable to use
for the return type of the handler instead of using
Handler
r a
.Member
(Stop
Report
) r
completeBuiltin :: Text -> RpcHandler r -> RpcHandler r Source #
Configure the given RpcHandler
to use the specified builtin completion.
completeWith :: CompleteStyle -> (Text -> Text -> Int -> Handler r [Text]) -> RpcHandler r -> [RpcHandler r] Source #
Add command line completion to another RpcHandler
by creating a new handler that calls the given function to
obtain possible completions.
:: forall r h. HandlerCodec h r | |
=> RpcName | |
-> Execution | Execute sync or async. While autocommands can not interact with return values, this is still useful to keep Neovim
from continuing execution while the handler is active, which is particularly important for |
-> AutocmdEvents | The Neovim event identifier, like |
-> AutocmdOptions | Various Neovim options like the file pattern. |
-> h | The handler function. |
-> RpcHandler r |
Create an RpcHandler
that is triggered by a Neovim autocommand for the specified event.
For a user autocommand, specify User
for the event and the event name for the file pattern in AutocmdOptions
.
For easier type inference, it is advisable to use
for the return type of the handler instead of using
Handler
r a
.Member
(Stop
Report
) r
rpc :: forall r h. HandlerCodec h r => CommandHandler OptionStateZero h => RpcName -> Execution -> h -> [RpcHandler r] Source #
Convenience function for creating a handler that is triggered by both a function and a command of the same name.
See rpcFunction
and rpcCommand
.
This type indicates the execution style that Neovim should be instructed to use for RPC messages – synchronous requests that block Neovim until a result is returned and asynchronous notifications.
Instances
Bounded Execution Source # | |
Enum Execution Source # | |
Defined in Ribosome.Host.Data.Execution succ :: Execution -> Execution # pred :: Execution -> Execution # fromEnum :: Execution -> Int # enumFrom :: Execution -> [Execution] # enumFromThen :: Execution -> Execution -> [Execution] # enumFromTo :: Execution -> Execution -> [Execution] # enumFromThenTo :: Execution -> Execution -> Execution -> [Execution] # | |
Show Execution Source # | |
Eq Execution Source # | |
MsgpackDecode Execution Source # | |
Defined in Ribosome.Host.Data.Execution | |
MsgpackEncode Execution Source # | |
module Ribosome.Host.Data.Args
When this type is used as a parameter of a command handler function, the command is declared with the -bang
option, and when invoked, the argument passed to the handler is Bang
if the user specified the !
and NoBang
otherwise.
Instances
Show Bang Source # | |
Eq Bang Source # | |
MsgpackDecode Bang Source # | |
Defined in Ribosome.Host.Data.Bang fromMsgpack :: Object -> Either DecodeError Bang Source # | |
Member (Stop Report) r => HandlerArg Bang r Source # | |
Defined in Ribosome.Host.Handler.Codec | |
BeforeRegular al Bang => SpecialParam ('OptionState al c ac) Bang Source # | |
Defined in Ribosome.Host.Handler.Command type TransSpecial ('OptionState al c ac) Bang :: OptionState Source # | |
type TransSpecial ('OptionState al c ac) Bang Source # | |
Defined in Ribosome.Host.Handler.Command |
When this type is used as a parameter of a command handler function, the command is declared with the -bar
option,
allowing other commands to be chained after it with |
.
This has no effect on the execution.
Instances
Show Bar Source # | |
Eq Bar Source # | |
MsgpackDecode Bar Source # | |
Defined in Ribosome.Host.Data.Bar fromMsgpack :: Object -> Either DecodeError Bar Source # | |
HandlerArg Bar r Source # | |
Defined in Ribosome.Host.Handler.Codec | |
BeforeRegular al Bar => SpecialParam ('OptionState al c ac) Bar Source # | |
Defined in Ribosome.Host.Handler.Command type TransSpecial ('OptionState al c ac) Bar :: OptionState Source # | |
type TransSpecial ('OptionState al c ac) Bar Source # | |
Defined in Ribosome.Host.Handler.Command |
newtype CommandMods Source #
When this type is used as a parameter of a command handler function, the RPC trigger uses the special token
q-mods
in the call.
This type then contains the list of pre-command modifiers specified by the user, like :belowright
.
Instances
Show CommandMods Source # | |
Defined in Ribosome.Host.Data.CommandMods showsPrec :: Int -> CommandMods -> ShowS # show :: CommandMods -> String # showList :: [CommandMods] -> ShowS # | |
Eq CommandMods Source # | |
Defined in Ribosome.Host.Data.CommandMods (==) :: CommandMods -> CommandMods -> Bool # (/=) :: CommandMods -> CommandMods -> Bool # | |
MsgpackDecode CommandMods Source # | |
Defined in Ribosome.Host.Data.CommandMods | |
BeforeRegular al CommandMods => SpecialParam ('OptionState al c ac) CommandMods Source # | |
Defined in Ribosome.Host.Handler.Command type TransSpecial ('OptionState al c ac) CommandMods :: OptionState Source # | |
type TransSpecial ('OptionState al c ac) CommandMods Source # | |
Defined in Ribosome.Host.Handler.Command |
newtype CommandRegister Source #
When this type is used as a parameter of a command handler function, the RPC trigger uses the special token
reg
in the call.
This type then contains the name of the register specified by the user.
Instances
data Range (style :: RangeStyle) Source #
When this type is used as a parameter of a command handler function, the command is declared with the -range
option, and when invoked, the argument passed to the handler contains the line range specified by the user, as in:
:5Reverse :5,20Reverse
In the first case, the field $sel:high:Range
is Nothing
.
The type has a phantom parameter of kind RangeStyle
that configures the semantics of the range, as defined by
Neovim (see :help :command-range
).
Instances
Show (Range style) Source # | |
Eq (Range style) Source # | |
Typeable style => MsgpackDecode (Range style) Source # | |
Defined in Ribosome.Host.Data.Range fromMsgpack :: Object -> Either DecodeError (Range style) Source # | |
(BeforeRegular al (Range rs), RangeStyleOpt rs) => SpecialParam ('OptionState al c ac) (Range rs) Source # | |
Defined in Ribosome.Host.Handler.Command type TransSpecial ('OptionState al c ac) (Range rs) :: OptionState Source # | |
type TransSpecial ('OptionState al c ac) (Range rs) Source # | |
Defined in Ribosome.Host.Handler.Command |
data RangeStyle Source #
Neovim offers different semantics for the command range (see :help :command-range
).
This type determines the position (prefix line number/postfix count) and default values.
RangeFile | Prefix line range, defaulting to the entire file ( |
RangeLine (Maybe Nat) |
|
RangeCount (Maybe Nat) |
|
Effects
type ScopedMState s = PScoped s () (MState s) Source #
data MState s :: Effect Source #
A state effect that allows atomic updates with monadic actions.
The constructor muse
is analogous to the usual state
combinator, in that it transforms the state monadically
alongside a return value, but unlike State
and AtomicState
, the callback may be a Sem
.
This is accomplished by locking every call with an MVar
.
For read-only access to the state that doesn't care about currently running updates, the constructor mread
directly
returns the state without consulting the lock.
muse :: Member (MState s) r => (s -> Sem r (s, a)) -> Sem r a Source #
Run a monadic action on the state in a mutually exclusive fashion that additionally returns a value.
mtrans :: Member (MState s) r => (s -> Sem r s) -> Sem r () Source #
Run a monadic action on the state in a mutually exclusive fashion.
mstate :: Member (MState s) r => (s -> (s, a)) -> Sem r a Source #
Apply a pure function to the state that additionally returns a value.
mreads :: Member (MState s) r => (s -> a) -> Sem r a Source #
Obtain the current state, transformed by a pure function.
stateToMState :: Member (MState s) r => InterpreterFor (State s) r Source #
withMState :: Member (ScopedMState s) r => s -> InterpreterFor (MState s) r Source #
data Reports :: Effect Source #
This internal effect stores all errors in memory that have been created through the Report
system.
This effect abstracts interaction with the Neovim RPC API. An RPC call can either be a request or a notification, where the former expects a response to be sent while the latter returns immediately.
For requests, the constructor sync
blocks the current thread while async
takes a callback that is called from a
new thread.
The constructor notify
sends a notification.
The module Ribosome.Api.Data contains RpcCall
s for the entire Neovim API, generated by
calling neovim --api-info
during compilation from Template Haskell.
The module Ribosome.Api contains functions that call sync
with those RpcCall
s, converting the input and return
values to and from msgpack.
These functions have signatures like:
nvimGetVar :: ∀ a r . Member Rpc r => MsgpackDecode a => Text -> Sem r a
A manual call would be constructed like this:
Ribosome.sync (RpcCallRequest (Request "nvim_get_option" [toMsgpack "textwidth"]))
RPC calls may be batched and sent via nvim_call_atomic
, see RpcCall
.
This effect's default interpreter uses Resumable
for error tracking. See Errors.
sync :: forall r a. Member Rpc r => RpcCall a -> Sem r a Source #
Block the current thread while sending an RPC request.
async :: forall a r. Member Rpc r => RpcCall a -> (Either RpcError a -> Sem r ()) -> Sem r () Source #
Send an RPC request and pass the result to the continuation on a new thread.
notify :: forall a r. Member Rpc r => RpcCall a -> Sem r () Source #
Send an RPC notification and return immediately.
Interpreters
noHandlers :: InterpreterFor (Handlers !! Report) r Source #
Interpret Handlers
by performing no actions.
withHandlers :: Members [Handlers !! Report, Rpc !! RpcError, Log, Error BootError] r => [RpcHandler r] -> Sem r a -> Sem r a Source #
Add a set of RpcHandler
s to the plugin.
This can be used multiple times and has to be terminated by interpretHandlersNull
, which is done automatically when
using the plugin main functions.
interpretHandlers :: Members [Rpc !! RpcError, Log, Error BootError] r => [RpcHandler r] -> InterpreterFor (Handlers !! Report) r Source #
Interpret Handlers
with a set of RpcHandlers
.
type HostDeps er = [Handlers !! Report, Process RpcMessage (Either Text RpcMessage), Rpc !! RpcError, DataLog LogReport, Events er Event, Responses RequestId Response !! RpcError, Log, Error BootError, Resource, Mask Restoration, Race, Async, Embed IO, Final IO] Source #
interpretHost :: Members [Handlers !! Report, Rpc !! RpcError, DataLog LogReport, Events er Event, Log, Final IO] r => InterpreterFor Host r Source #
interpretLogs :: Members [Reader LogConfig, Resource, ChronosTime, Race, Async, Embed IO] r => InterpretersFor [StderrLog, FileLog] r Source #
interpretMState :: Members [Resource, Race, Mask mres, Embed IO] r => s -> InterpreterFor (MState s) r Source #
Interpret MState
using AtomicState
and Lock
.
evalMState :: s -> InterpreterFor (MState s) r Source #
interpretMStates :: forall s mres r. Members [Mask mres, Resource, Race, Embed IO] r => InterpreterFor (ScopedMState s) r Source #
Interpret MState
as a scoped effect.
interpretReports :: Members [ChronosTime, Embed IO] r => InterpreterFor Reports r Source #
Interpret Reports
by storing reports in AtomicState
and interpret the state effect.
interpretResponses :: forall k v r. Ord k => Num k => Show k => Member (Embed IO) r => InterpreterFor (Responses k v !! RpcError) r Source #
interpretRpc :: forall o r. Member (AtomicState (Maybe ChannelId)) r => Members [Responses RequestId Response !! RpcError, Process RpcMessage o, Log, Async] r => InterpreterFor (Rpc !! RpcError) r Source #
Neovim API
Instances
Show Window Source # | |
Eq Window Source # | |
MsgpackDecode Window Source # | |
Defined in Ribosome.Host.Api.Data fromMsgpack :: Object -> Either DecodeError Window Source # | |
MsgpackEncode Window Source # | |
Instances
Show Tabpage Source # | |
Eq Tabpage Source # | |
MsgpackDecode Tabpage Source # | |
Defined in Ribosome.Host.Api.Data fromMsgpack :: Object -> Either DecodeError Tabpage Source # | |
MsgpackEncode Tabpage Source # | |
Instances
Show Buffer Source # | |
Eq Buffer Source # | |
MsgpackDecode Buffer Source # | |
Defined in Ribosome.Host.Api.Data fromMsgpack :: Object -> Either DecodeError Buffer Source # | |
MsgpackEncode Buffer Source # | |
Messagepack
class MsgpackDecode a where Source #
Class of values that can be decoded from MessagePack Object
s.
Nothing
fromMsgpack :: Object -> Either DecodeError a Source #
Decode a value from a MessagePack Object
.
The default implementation uses generic derivation.
default fromMsgpack :: Typeable a => ReifySOP a ass => GMsgpackDecode (GDatatypeInfoOf a) (GCode a) => Object -> Either DecodeError a Source #
Instances
class MsgpackEncode a where Source #
Class of values that can be encoded to MessagePack Object
s.
Nothing
toMsgpack :: a -> Object Source #
Encode a value to MessagePack.
The default implementation uses generic derivation.
default toMsgpack :: ConstructSOP a ass => GMsgpackEncode (GDatatypeInfoOf a) (GCode a) => a -> Object Source #
Instances
msgpackArray :: MsgpackArray a => a Source #
Encode an arbitrary number of heterogeneously typed values to a single MessagePack array. This function is variadic, meaning that it takes an arbitrary number of arguments:
>>>
msgpackArray (5 :: Int) ("error" :: Text) (3.14 :: Double) :: Object
ObjectArray [ObjectInt 5, ObjectString "error", ObjectFloat 3.14]
This avoids the need to call toMsgpack
once for each element and then once more for the array.
msgpackMap :: MsgpackMap a => a Source #
Encode an arbitrary number of heterogeneously typed values to a single MessagePack map. This function is variadic, meaning that it takes an arbitrary number of arguments:
>>>
msgpackMap ("number", 5 :: Int) ("status", "error" :: Text) ("intensity", 3.14 :: Double) :: Object
ObjectMap (Map.fromList [(ObjectString "number", ObjectInt 5), (ObjectString "status", ObjectString "error"), (ObjectString "intensity", ObjectFloat 3.14)])
This avoids the need to call toMsgpack
once for each element and then once more for the map.
Errors
resumeReports :: ResumeReports effs errs r => InterpretersFor effs r Source #
Resume multiple effects as Report
s.
This needs both effects and errors specified as type applications (though only the shape for the errors).
resumeReports @[Rpc, Settings] @[_, _]
mapReports :: MapReports errs r => InterpretersFor (Stops errs) r Source #
Map multiple errors to Report
.
This needs the errors specified as type applications.
mapReports @[RpcError, SettingError]
class Reportable e where Source #
The class of types that are convertible to a Report
.
This is used to create a uniform format for handlers, since control flow is passed on to the internal machinery when
they return.
If an error would be thrown that is not caught by the request dispatcher, the entire plugin would stop, so all Stop
and Resumable
effects need to be converted to Report
before returning (see Errors).
The combinators associated with this class make this task a little less arduous:
data NumbersError = InvalidNumber instance Reportable NumbersError where toReport InvalidNumber = Report "Invalid number!" ["The user entered an invalid number"] Warn count :: Int -> Sem r Int count i = resumeReport @Rpc $ mapReport @NumbersError do when (i == 0) (stop InvalidNumber) nvimGetVar ("number_" <> show i)
Here resumeReport
converts a potential RpcError
from nvimGetVar
to Report
(e.g. if the variable
is not set), while mapReport
uses the instance
to convert the call to Reportable
NumbersError
stop
.
Instances
The type used by request handlers and expected by the RPC dispatcher.
Instances
IsString LogReport Source # | |
Defined in Ribosome.Host.Data.Report fromString :: String -> LogReport # | |
Generic LogReport Source # | |
Show LogReport Source # | |
type Rep LogReport Source # | |
Defined in Ribosome.Host.Data.Report type Rep LogReport = D1 ('MetaData "LogReport" "Ribosome.Host.Data.Report" "ribosome-host-0.9.9.9-4n86eC1033RAA2pmC2T1m9" 'False) (C1 ('MetaCons "LogReport" 'PrefixI 'True) ((S1 ('MetaSel ('Just "report") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 Report) :*: S1 ('MetaSel ('Just "echo") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 Bool)) :*: (S1 ('MetaSel ('Just "store") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 Bool) :*: S1 ('MetaSel ('Just "context") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 ReportContext)))) |
An report with different messages intended to be sent to Neovim and the log, respectively.
Used by request handlers and expected by the RPC dispatcher.
Also contains the Severity
of the report, or minimum log level, which determines whether the report should be
logged and echoed in Neovim, and what kind of highlighting should be used in Neovim (red for errors, orange for
warnings, none for infomrational errors).
The log message may span multiple lines.
Instances
IsString Report Source # | |
Defined in Ribosome.Host.Data.Report fromString :: String -> Report # | |
Show Report Source # | |
Reportable Report Source # | |
MsgpackEncode a => HandlerCodec (Handler r a) r Source # | |
Defined in Ribosome.Host.Handler.Codec handlerCodec :: Handler r a -> RpcHandlerFun r Source # |
newtype ReportContext Source #
The provenance of a report, for use in logs.
Instances
basicReport :: Member (Stop Report) r => HasCallStack => Text -> [Text] -> Sem r a Source #
Stop with a LogReport
.
mapReport :: forall e r a. Reportable e => Member (Stop Report) r => Sem (Stop e ': r) a -> Sem r a Source #
Reinterpret
to Stop
err
if Stop
Report
err
is an instance of Reportable
.
resumeReport :: forall eff e r a. Reportable e => Members [eff !! e, Stop Report] r => Sem (eff ': r) a -> Sem r a Source #
Convert the effect eff
to
and Resumable
err eff
if Stop
Report
err
is an instance of Reportable
.
userReport :: forall e. Reportable e => e -> Text Source #
Extract the user message from an instance of Reportable
.
resumeHoistUserMessage :: forall err eff err' r. Reportable err => Members [eff !! err, Stop err'] r => (Text -> err') -> InterpreterFor eff r Source #
Resume an effect with an error that's an instance of Reportable
by passing its user message to a function.
mapUserMessage :: forall err err' r. Reportable err => Member (Stop err') r => (Text -> err') -> InterpreterFor (Stop err) r Source #
Map an error that's an instance of Reportable
by passing its user message to a function.
This type represents the singular fatal error used by Ribosome.
Contrary to all other errors, this one is used with Error
instead of Stop
.
It is only thrown from intialization code of interpreters when operation of the plugin is impossible due to the error
condition.
data StoredReport Source #
Data type that attaches a time stamp to a Report
.
Instances
Show StoredReport Source # | |
Defined in Ribosome.Host.Data.StoredReport showsPrec :: Int -> StoredReport -> ShowS # show :: StoredReport -> String # showList :: [StoredReport] -> ShowS # |