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

Ribosome.Host

Synopsis

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

newtype HostConfig Source #

The configuration for a host, which consists only of a LogConfig.

Constructors

HostConfig 

Fields

Instances

Instances details
Generic HostConfig Source # 
Instance details

Defined in Ribosome.Host.Data.HostConfig

Associated Types

type Rep HostConfig :: Type -> Type #

Show HostConfig Source # 
Instance details

Defined in Ribosome.Host.Data.HostConfig

Default HostConfig Source # 
Instance details

Defined in Ribosome.Host.Data.HostConfig

Methods

def :: HostConfig #

Eq HostConfig Source # 
Instance details

Defined in Ribosome.Host.Data.HostConfig

type Rep HostConfig Source # 
Instance details

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

data LogConfig Source #

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.

Instances

Instances details
Generic LogConfig Source # 
Instance details

Defined in Ribosome.Host.Data.HostConfig

Associated Types

type Rep LogConfig :: Type -> Type #

Show LogConfig Source # 
Instance details

Defined in Ribosome.Host.Data.HostConfig

Default LogConfig Source # 
Instance details

Defined in Ribosome.Host.Data.HostConfig

Methods

def :: LogConfig #

Eq LogConfig Source # 
Instance details

Defined in Ribosome.Host.Data.HostConfig

type Rep LogConfig Source # 
Instance details

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 RpcHandlers can be used as a Neovim plugin by passing them to runNvimHandlersIO.

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

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.

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.

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

Constructors

CompleteFiltered

Completion returns matching items.

CompleteUnfiltered

Completion returns all items.

Instances

Instances details
Show CompleteStyle Source # 
Instance details

Defined in Ribosome.Host.Data.RpcType

Eq CompleteStyle Source # 
Instance details

Defined in Ribosome.Host.Data.RpcType

data RpcError Source #

The basic error type for the plugin host, used by the listener, Rpc and several other components.

Instances

Instances details
IsString RpcError Source # 
Instance details

Defined in Ribosome.Host.Data.RpcError

Generic RpcError Source # 
Instance details

Defined in Ribosome.Host.Data.RpcError

Associated Types

type Rep RpcError :: Type -> Type #

Methods

from :: RpcError -> Rep RpcError x #

to :: Rep RpcError x -> RpcError #

Show RpcError Source # 
Instance details

Defined in Ribosome.Host.Data.RpcError

Eq RpcError Source # 
Instance details

Defined in Ribosome.Host.Data.RpcError

MsgpackDecode RpcError Source # 
Instance details

Defined in Ribosome.Host.Data.RpcError

MsgpackEncode RpcError Source # 
Instance details

Defined in Ribosome.Host.Data.RpcError

Reportable RpcError Source # 
Instance details

Defined in Ribosome.Host.Data.RpcError

type Rep RpcError Source # 
Instance details

Defined in Ribosome.Host.Data.RpcError

rpcError :: RpcError -> Text Source #

Extract an error message from an RpcError.

rpcFunction Source #

Arguments

:: 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 Handler r a for the return type of the handler instead of using 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

rpcCommand Source #

Arguments

:: 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 Handler r a for the return type of the handler instead of using 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.

rpcAutocmd Source #

Arguments

:: 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 VimLeave.

-> AutocmdEvents

The Neovim event identifier, like BufWritePre or User.

-> 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 Handler r a for the return type of the handler instead of using 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.

data Execution Source #

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.

Constructors

Sync

RPC Request

Async

RPC Notification

data Bang Source #

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.

Constructors

Bang

Bang was used.

NoBang

Bang was not used.

Instances

Instances details
Show Bang Source # 
Instance details

Defined in Ribosome.Host.Data.Bang

Methods

showsPrec :: Int -> Bang -> ShowS #

show :: Bang -> String #

showList :: [Bang] -> ShowS #

Eq Bang Source # 
Instance details

Defined in Ribosome.Host.Data.Bang

Methods

(==) :: Bang -> Bang -> Bool #

(/=) :: Bang -> Bang -> Bool #

MsgpackDecode Bang Source # 
Instance details

Defined in Ribosome.Host.Data.Bang

Member (Stop Report) r => HandlerArg Bang r Source # 
Instance details

Defined in Ribosome.Host.Handler.Codec

Methods

handlerArg :: [Object] -> Sem r ([Object], Bang) Source #

BeforeRegular al Bang => SpecialParam ('OptionState al c ac) Bang Source # 
Instance details

Defined in Ribosome.Host.Handler.Command

Associated Types

type TransSpecial ('OptionState al c ac) Bang :: OptionState Source #

type TransSpecial ('OptionState al c ac) Bang Source # 
Instance details

Defined in Ribosome.Host.Handler.Command

type TransSpecial ('OptionState al c ac) Bang = 'OptionState al c ac

data Bar Source #

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.

Constructors

Bar 

Instances

Instances details
Show Bar Source # 
Instance details

Defined in Ribosome.Host.Data.Bar

Methods

showsPrec :: Int -> Bar -> ShowS #

show :: Bar -> String #

showList :: [Bar] -> ShowS #

Eq Bar Source # 
Instance details

Defined in Ribosome.Host.Data.Bar

Methods

(==) :: Bar -> Bar -> Bool #

(/=) :: Bar -> Bar -> Bool #

MsgpackDecode Bar Source # 
Instance details

Defined in Ribosome.Host.Data.Bar

HandlerArg Bar r Source # 
Instance details

Defined in Ribosome.Host.Handler.Codec

Methods

handlerArg :: [Object] -> Sem r ([Object], Bar) Source #

BeforeRegular al Bar => SpecialParam ('OptionState al c ac) Bar Source # 
Instance details

Defined in Ribosome.Host.Handler.Command

Associated Types

type TransSpecial ('OptionState al c ac) Bar :: OptionState Source #

type TransSpecial ('OptionState al c ac) Bar Source # 
Instance details

Defined in Ribosome.Host.Handler.Command

type TransSpecial ('OptionState al c ac) Bar = 'OptionState al c ac

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.

Constructors

CommandMods Text 

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.

Constructors

CommandRegister Text 

Instances

Instances details
IsString CommandRegister Source # 
Instance details

Defined in Ribosome.Host.Data.CommandRegister

Show CommandRegister Source # 
Instance details

Defined in Ribosome.Host.Data.CommandRegister

Eq CommandRegister Source # 
Instance details

Defined in Ribosome.Host.Data.CommandRegister

Ord CommandRegister Source # 
Instance details

Defined in Ribosome.Host.Data.CommandRegister

MsgpackDecode CommandRegister Source # 
Instance details

Defined in Ribosome.Host.Data.CommandRegister

BeforeRegular al CommandRegister => SpecialParam ('OptionState al c ac) CommandRegister Source # 
Instance details

Defined in Ribosome.Host.Handler.Command

Associated Types

type TransSpecial ('OptionState al c ac) CommandRegister :: OptionState Source #

type TransSpecial ('OptionState al c ac) CommandRegister Source # 
Instance details

Defined in Ribosome.Host.Handler.Command

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

Constructors

Range Int64 (Maybe Int64) 

Instances

Instances details
Show (Range style) Source # 
Instance details

Defined in Ribosome.Host.Data.Range

Methods

showsPrec :: Int -> Range style -> ShowS #

show :: Range style -> String #

showList :: [Range style] -> ShowS #

Eq (Range style) Source # 
Instance details

Defined in Ribosome.Host.Data.Range

Methods

(==) :: Range style -> Range style -> Bool #

(/=) :: Range style -> Range style -> Bool #

Typeable style => MsgpackDecode (Range style) Source # 
Instance details

Defined in Ribosome.Host.Data.Range

(BeforeRegular al (Range rs), RangeStyleOpt rs) => SpecialParam ('OptionState al c ac) (Range rs) Source # 
Instance details

Defined in Ribosome.Host.Handler.Command

Associated Types

type TransSpecial ('OptionState al c ac) (Range rs) :: OptionState Source #

type TransSpecial ('OptionState al c ac) (Range rs) Source # 
Instance details

Defined in Ribosome.Host.Handler.Command

type TransSpecial ('OptionState al c ac) (Range rs) = 'OptionState al c ac

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.

Constructors

RangeFile

Prefix line range, defaulting to the entire file (-range=%).

RangeLine (Maybe Nat)

Nothing: Prefix line range defaulting to the current line (-range). |Just N: Prefix count defaulting to N (-range=N).

RangeCount (Maybe Nat)

Just N: Prefix or postfix count defaulting to N (-count=N). |Nothing: Same as Just 0 (-count).

Effects

type ScopedMState s = PScoped s () (MState s) Source #

A PScoped alias for MState that allows running it on a local region without having to involve IO in the stack.

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.

mmodify :: Member (MState s) r => (s -> s) -> Sem r () Source #

Apply a pure function to the state.

mread :: Member (MState s) r => Sem r s Source #

Obtain the current state.

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 #

Interpret State in terms of MState.

withMState :: Member (ScopedMState s) r => s -> InterpreterFor (MState s) r Source #

Run a PScoped MState on a local region without having to involve IO in the stack.

data Reports :: Effect Source #

This internal effect stores all errors in memory that have been created through the Report system.

data Responses k v :: Effect Source #

data Rpc :: Effect Source #

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 RpcCalls 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 RpcCalls, 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 RpcHandlers 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.

runHost :: Members (HostDeps er) r => Sem 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 #

Interpret MState as State.

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 #

Neovim API

data Window Source #

Instances

Instances details
Show Window Source # 
Instance details

Defined in Ribosome.Host.Api.Data

Eq Window Source # 
Instance details

Defined in Ribosome.Host.Api.Data

Methods

(==) :: Window -> Window -> Bool #

(/=) :: Window -> Window -> Bool #

MsgpackDecode Window Source # 
Instance details

Defined in Ribosome.Host.Api.Data

MsgpackEncode Window Source # 
Instance details

Defined in Ribosome.Host.Api.Data

data Tabpage Source #

Instances

Instances details
Show Tabpage Source # 
Instance details

Defined in Ribosome.Host.Api.Data

Eq Tabpage Source # 
Instance details

Defined in Ribosome.Host.Api.Data

Methods

(==) :: Tabpage -> Tabpage -> Bool #

(/=) :: Tabpage -> Tabpage -> Bool #

MsgpackDecode Tabpage Source # 
Instance details

Defined in Ribosome.Host.Api.Data

MsgpackEncode Tabpage Source # 
Instance details

Defined in Ribosome.Host.Api.Data

data Buffer Source #

Instances

Instances details
Show Buffer Source # 
Instance details

Defined in Ribosome.Host.Api.Data

Eq Buffer Source # 
Instance details

Defined in Ribosome.Host.Api.Data

Methods

(==) :: Buffer -> Buffer -> Bool #

(/=) :: Buffer -> Buffer -> Bool #

MsgpackDecode Buffer Source # 
Instance details

Defined in Ribosome.Host.Api.Data

MsgpackEncode Buffer Source # 
Instance details

Defined in Ribosome.Host.Api.Data

Messagepack

class MsgpackDecode a where Source #

Class of values that can be decoded from MessagePack Objects.

Minimal complete definition

Nothing

Methods

fromMsgpack :: Object -> Either DecodeError a Source #

Decode a value from a MessagePack Object.

The default implementation uses generic derivation.

Instances

Instances details
MsgpackDecode Int64 Source # 
Instance details

Defined in Ribosome.Host.Class.Msgpack.Decode

MsgpackDecode ByteString Source # 
Instance details

Defined in Ribosome.Host.Class.Msgpack.Decode

MsgpackDecode Object Source # 
Instance details

Defined in Ribosome.Host.Class.Msgpack.Decode

MsgpackDecode MicroSeconds Source # 
Instance details

Defined in Ribosome.Host.Class.Msgpack.Decode

MsgpackDecode MilliSeconds Source # 
Instance details

Defined in Ribosome.Host.Class.Msgpack.Decode

MsgpackDecode NanoSeconds Source # 
Instance details

Defined in Ribosome.Host.Class.Msgpack.Decode

MsgpackDecode Seconds Source # 
Instance details

Defined in Ribosome.Host.Class.Msgpack.Decode

MsgpackDecode Buffer Source # 
Instance details

Defined in Ribosome.Host.Api.Data

MsgpackDecode Tabpage Source # 
Instance details

Defined in Ribosome.Host.Api.Data

MsgpackDecode Window Source # 
Instance details

Defined in Ribosome.Host.Api.Data

MsgpackDecode DecodeError Source # 
Instance details

Defined in Ribosome.Host.Class.Msgpack.Decode

MsgpackDecode FieldError Source # 
Instance details

Defined in Ribosome.Host.Class.Msgpack.Decode

MsgpackDecode ValidUtf8 Source # 
Instance details

Defined in Ribosome.Host.Class.Msgpack.Decode

MsgpackDecode ValidUtf8String Source # 
Instance details

Defined in Ribosome.Host.Class.Msgpack.Decode

MsgpackDecode ApiInfo Source # 
Instance details

Defined in Ribosome.Host.Data.ApiInfo

MsgpackDecode ExtType Source # 
Instance details

Defined in Ribosome.Host.Data.ApiInfo

MsgpackDecode ExtTypeMeta Source # 
Instance details

Defined in Ribosome.Host.Data.ApiInfo

MsgpackDecode RpcDecl Source # 
Instance details

Defined in Ribosome.Host.Data.ApiInfo

MsgpackDecode ApiType Source # 
Instance details

Defined in Ribosome.Host.Data.ApiType

MsgpackDecode Bang Source # 
Instance details

Defined in Ribosome.Host.Data.Bang

MsgpackDecode Bar Source # 
Instance details

Defined in Ribosome.Host.Data.Bar

MsgpackDecode ChannelId Source # 
Instance details

Defined in Ribosome.Host.Data.ChannelId

MsgpackDecode CommandMods Source # 
Instance details

Defined in Ribosome.Host.Data.CommandMods

MsgpackDecode CommandRegister Source # 
Instance details

Defined in Ribosome.Host.Data.CommandRegister

MsgpackDecode EventName Source # 
Instance details

Defined in Ribosome.Host.Data.Event

MsgpackDecode Execution Source # 
Instance details

Defined in Ribosome.Host.Data.Execution

MsgpackDecode LuaRef Source # 
Instance details

Defined in Ribosome.Host.Data.LuaRef

MsgpackDecode RequestId Source # 
Instance details

Defined in Ribosome.Host.Data.Request

MsgpackDecode RpcMethod Source # 
Instance details

Defined in Ribosome.Host.Data.Request

MsgpackDecode RpcError Source # 
Instance details

Defined in Ribosome.Host.Data.RpcError

MsgpackDecode RpcMessage Source # 
Instance details

Defined in Ribosome.Host.Data.RpcMessage

MsgpackDecode AutocmdBuffer Source # 
Instance details

Defined in Ribosome.Host.Data.RpcType

MsgpackDecode AutocmdEvents Source # 
Instance details

Defined in Ribosome.Host.Data.RpcType

MsgpackDecode AutocmdGroup Source # 
Instance details

Defined in Ribosome.Host.Data.RpcType

MsgpackDecode AutocmdId Source # 
Instance details

Defined in Ribosome.Host.Data.RpcType

MsgpackDecode AutocmdPatterns Source # 
Instance details

Defined in Ribosome.Host.Data.RpcType

MsgpackDecode Text Source # 
Instance details

Defined in Ribosome.Host.Class.Msgpack.Decode

MsgpackDecode String Source # 
Instance details

Defined in Ribosome.Host.Class.Msgpack.Decode

MsgpackDecode Integer Source # 
Instance details

Defined in Ribosome.Host.Class.Msgpack.Decode

MsgpackDecode () Source # 
Instance details

Defined in Ribosome.Host.Class.Msgpack.Decode

MsgpackDecode Bool Source # 
Instance details

Defined in Ribosome.Host.Class.Msgpack.Decode

MsgpackDecode Char Source # 
Instance details

Defined in Ribosome.Host.Class.Msgpack.Decode

MsgpackDecode Double Source # 
Instance details

Defined in Ribosome.Host.Class.Msgpack.Decode

MsgpackDecode Float Source # 
Instance details

Defined in Ribosome.Host.Class.Msgpack.Decode

MsgpackDecode Int Source # 
Instance details

Defined in Ribosome.Host.Class.Msgpack.Decode

Typeable style => MsgpackDecode (Range style) Source # 
Instance details

Defined in Ribosome.Host.Data.Range

MsgpackDecode a => MsgpackDecode (Maybe a) Source # 
Instance details

Defined in Ribosome.Host.Class.Msgpack.Decode

(Typeable a, MsgpackDecode a) => MsgpackDecode [a] Source # 
Instance details

Defined in Ribosome.Host.Class.Msgpack.Decode

(MsgpackDecode a, MsgpackDecode b) => MsgpackDecode (Either a b) Source # 
Instance details

Defined in Ribosome.Host.Class.Msgpack.Decode

(Ord k, Typeable k, Typeable v, MsgpackDecode k, MsgpackDecode v) => MsgpackDecode (Map k v) Source # 
Instance details

Defined in Ribosome.Host.Class.Msgpack.Decode

(Typeable b, Typeable t, DecodePath b t) => MsgpackDecode (Path b t) Source # 
Instance details

Defined in Ribosome.Host.Class.Msgpack.Decode

(Typeable a, Typeable b, MsgpackDecode a, MsgpackDecode b) => MsgpackDecode (a, b) Source # 
Instance details

Defined in Ribosome.Host.Class.Msgpack.Decode

(Typeable a, Typeable b, Typeable c, MsgpackDecode a, MsgpackDecode b, MsgpackDecode c) => MsgpackDecode (a, b, c) Source # 
Instance details

Defined in Ribosome.Host.Class.Msgpack.Decode

Methods

fromMsgpack :: Object -> Either DecodeError (a, b, c) Source #

(Typeable a, Typeable b, Typeable c, Typeable d, MsgpackDecode a, MsgpackDecode b, MsgpackDecode c, MsgpackDecode d) => MsgpackDecode (a, b, c, d) Source # 
Instance details

Defined in Ribosome.Host.Class.Msgpack.Decode

Methods

fromMsgpack :: Object -> Either DecodeError (a, b, c, d) Source #

(Typeable a, Typeable b, Typeable c, Typeable d, Typeable e, MsgpackDecode a, MsgpackDecode b, MsgpackDecode c, MsgpackDecode d, MsgpackDecode e) => MsgpackDecode (a, b, c, d, e) Source # 
Instance details

Defined in Ribosome.Host.Class.Msgpack.Decode

Methods

fromMsgpack :: Object -> Either DecodeError (a, b, c, d, e) Source #

(Typeable a, Typeable b, Typeable c, Typeable d, Typeable e, Typeable f, MsgpackDecode a, MsgpackDecode b, MsgpackDecode c, MsgpackDecode d, MsgpackDecode e, MsgpackDecode f) => MsgpackDecode (a, b, c, d, e, f) Source # 
Instance details

Defined in Ribosome.Host.Class.Msgpack.Decode

Methods

fromMsgpack :: Object -> Either DecodeError (a, b, c, d, e, f) Source #

(Typeable a, Typeable b, Typeable c, Typeable d, Typeable e, Typeable f, Typeable g, MsgpackDecode a, MsgpackDecode b, MsgpackDecode c, MsgpackDecode d, MsgpackDecode e, MsgpackDecode f, MsgpackDecode g) => MsgpackDecode (a, b, c, d, e, f, g) Source # 
Instance details

Defined in Ribosome.Host.Class.Msgpack.Decode

Methods

fromMsgpack :: Object -> Either DecodeError (a, b, c, d, e, f, g) Source #

class MsgpackEncode a where Source #

Class of values that can be encoded to MessagePack Objects.

Minimal complete definition

Nothing

Methods

toMsgpack :: a -> Object Source #

Encode a value to MessagePack.

The default implementation uses generic derivation.

Instances

Instances details
MsgpackEncode Int64 Source # 
Instance details

Defined in Ribosome.Host.Class.Msgpack.Encode

MsgpackEncode ByteString Source # 
Instance details

Defined in Ribosome.Host.Class.Msgpack.Encode

MsgpackEncode Object Source # 
Instance details

Defined in Ribosome.Host.Class.Msgpack.Encode

MsgpackEncode MicroSeconds Source # 
Instance details

Defined in Ribosome.Host.Class.Msgpack.Encode

MsgpackEncode MilliSeconds Source # 
Instance details

Defined in Ribosome.Host.Class.Msgpack.Encode

MsgpackEncode NanoSeconds Source # 
Instance details

Defined in Ribosome.Host.Class.Msgpack.Encode

MsgpackEncode Seconds Source # 
Instance details

Defined in Ribosome.Host.Class.Msgpack.Encode

MsgpackEncode Buffer Source # 
Instance details

Defined in Ribosome.Host.Api.Data

MsgpackEncode Tabpage Source # 
Instance details

Defined in Ribosome.Host.Api.Data

MsgpackEncode Window Source # 
Instance details

Defined in Ribosome.Host.Api.Data

MsgpackEncode DecodeError Source # 
Instance details

Defined in Ribosome.Host.Class.Msgpack.Encode

MsgpackEncode FieldError Source # 
Instance details

Defined in Ribosome.Host.Class.Msgpack.Encode

MsgpackEncode ValidUtf8 Source # 
Instance details

Defined in Ribosome.Host.Class.Msgpack.Encode

MsgpackEncode EventName Source # 
Instance details

Defined in Ribosome.Host.Data.Event

MsgpackEncode Execution Source # 
Instance details

Defined in Ribosome.Host.Data.Execution

MsgpackEncode LuaRef Source # 
Instance details

Defined in Ribosome.Host.Data.LuaRef

MsgpackEncode Request Source # 
Instance details

Defined in Ribosome.Host.Data.Request

MsgpackEncode RequestId Source # 
Instance details

Defined in Ribosome.Host.Data.Request

MsgpackEncode RpcMethod Source # 
Instance details

Defined in Ribosome.Host.Data.Request

MsgpackEncode RpcError Source # 
Instance details

Defined in Ribosome.Host.Data.RpcError

MsgpackEncode RpcMessage Source # 
Instance details

Defined in Ribosome.Host.Data.RpcMessage

MsgpackEncode AutocmdBuffer Source # 
Instance details

Defined in Ribosome.Host.Data.RpcType

MsgpackEncode AutocmdEvents Source # 
Instance details

Defined in Ribosome.Host.Data.RpcType

MsgpackEncode AutocmdGroup Source # 
Instance details

Defined in Ribosome.Host.Data.RpcType

MsgpackEncode AutocmdId Source # 
Instance details

Defined in Ribosome.Host.Data.RpcType

MsgpackEncode AutocmdPatterns Source # 
Instance details

Defined in Ribosome.Host.Data.RpcType

MsgpackEncode Text Source # 
Instance details

Defined in Ribosome.Host.Class.Msgpack.Encode

MsgpackEncode String Source # 
Instance details

Defined in Ribosome.Host.Class.Msgpack.Encode

MsgpackEncode Integer Source # 
Instance details

Defined in Ribosome.Host.Class.Msgpack.Encode

MsgpackEncode () Source # 
Instance details

Defined in Ribosome.Host.Class.Msgpack.Encode

Methods

toMsgpack :: () -> Object Source #

MsgpackEncode Bool Source # 
Instance details

Defined in Ribosome.Host.Class.Msgpack.Encode

MsgpackEncode Double Source # 
Instance details

Defined in Ribosome.Host.Class.Msgpack.Encode

MsgpackEncode Float Source # 
Instance details

Defined in Ribosome.Host.Class.Msgpack.Encode

MsgpackEncode Int Source # 
Instance details

Defined in Ribosome.Host.Class.Msgpack.Encode

Methods

toMsgpack :: Int -> Object Source #

MsgpackEncode a => MsgpackEncode (NonEmpty a) Source # 
Instance details

Defined in Ribosome.Host.Class.Msgpack.Encode

MsgpackEncode a => MsgpackEncode (Seq a) Source # 
Instance details

Defined in Ribosome.Host.Class.Msgpack.Encode

Methods

toMsgpack :: Seq a -> Object Source #

MsgpackEncode a => MsgpackEncode (Maybe a) Source # 
Instance details

Defined in Ribosome.Host.Class.Msgpack.Encode

Methods

toMsgpack :: Maybe a -> Object Source #

MsgpackEncode a => MsgpackEncode [a] Source # 
Instance details

Defined in Ribosome.Host.Class.Msgpack.Encode

Methods

toMsgpack :: [a] -> Object Source #

(MsgpackEncode k, MsgpackEncode v) => MsgpackEncode (Map k v) Source # 
Instance details

Defined in Ribosome.Host.Class.Msgpack.Encode

Methods

toMsgpack :: Map k v -> Object Source #

MsgpackEncode (Path b t) Source # 
Instance details

Defined in Ribosome.Host.Class.Msgpack.Encode

Methods

toMsgpack :: Path b t -> Object Source #

(MsgpackEncode a, MsgpackEncode b) => MsgpackEncode (a, b) Source # 
Instance details

Defined in Ribosome.Host.Class.Msgpack.Encode

Methods

toMsgpack :: (a, b) -> Object Source #

(MsgpackEncode a, MsgpackEncode b, MsgpackEncode c) => MsgpackEncode (a, b, c) Source # 
Instance details

Defined in Ribosome.Host.Class.Msgpack.Encode

Methods

toMsgpack :: (a, b, c) -> Object Source #

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 Reports. 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 Reportable NumbersError to convert the call to stop.

Methods

toReport :: e -> Report Source #

Instances

Instances details
Reportable Void Source # 
Instance details

Defined in Ribosome.Host.Data.Report

Methods

toReport :: Void -> Report Source #

Reportable DecodeError Source # 
Instance details

Defined in Ribosome.Host.Class.Msgpack.Error

Reportable Report Source # 
Instance details

Defined in Ribosome.Host.Data.Report

Reportable RpcError Source # 
Instance details

Defined in Ribosome.Host.Data.RpcError

data LogReport Source #

The type used by request handlers and expected by the RPC dispatcher.

Instances

Instances details
IsString LogReport Source # 
Instance details

Defined in Ribosome.Host.Data.Report

Generic LogReport Source # 
Instance details

Defined in Ribosome.Host.Data.Report

Associated Types

type Rep LogReport :: Type -> Type #

Show LogReport Source # 
Instance details

Defined in Ribosome.Host.Data.Report

type Rep LogReport Source # 
Instance details

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

data Report where Source #

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.

Constructors

Report :: HasCallStack => !Text -> ![Text] -> !Severity -> Report 

Instances

Instances details
IsString Report Source # 
Instance details

Defined in Ribosome.Host.Data.Report

Methods

fromString :: String -> Report #

Show Report Source # 
Instance details

Defined in Ribosome.Host.Data.Report

Reportable Report Source # 
Instance details

Defined in Ribosome.Host.Data.Report

MsgpackEncode a => HandlerCodec (Handler r a) r Source # 
Instance details

Defined in Ribosome.Host.Handler.Codec

newtype ReportContext Source #

The provenance of a report, for use in logs.

Constructors

ReportContext 

Fields

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 Stop err to Stop Report if 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 Resumable err eff and Stop Report if 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.

ignoreRpcError :: Member (Rpc !! RpcError) r => Sem (Rpc ': r) a -> Sem r () Source #

Run a Sem that uses Rpc and discard RpcErrors, interpreting Rpc to Rpc !! RpcError.

newtype BootError Source #

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.

Constructors

BootError Text 

data StoredReport Source #

Data type that attaches a time stamp to a Report.

Constructors

StoredReport !Report !Time 

Instances

Instances details
Show StoredReport Source # 
Instance details

Defined in Ribosome.Host.Data.StoredReport