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

Ribosome

Synopsis

Introduction

This library is a framework for building Neovim plugins with Polysemy.

A plugin consists of a set of request handlers that can be executed by Neovim functions, commands, autocmds, or events, and may communicate with Neovim by calling its RPC API.

Here is an example for a simple plugin with a single request handler.

import Ribosome
import Ribosome.Api

count ::
  Members NvimPlugin r =>
  Int ->
  Handler r Int
count n = do
  s <- 0 <! nvimGetVar "sum"
  let s' = s + n
  ignoreRpcError (nvimSetVar "sum" s')
  pure s'

main :: IO ()
main =
  runNvimPluginIO_ "counter" [rpcFunction "Count" Sync count]

This module can be used as a Neovim plugin by running it with jobstart from Neovim:

:call jobstart(['/path/to/plugin.exe'], { 'rpc': 1 })

The handler will add up all numbers that are passed to the Neovim function Count and store the sum in the variable g:sum:

:echo Count(5)
5
:echo Count(13)
18
:echo g:sum
18

Creating a project

The most reliable way to set up a repository for a plugin is to use Nix, for which Ribosome provides an app that generates a ready-to-use plugin project that includes Neovim glue that fetches static binaries from Github, as well as config files for Github Actions that release those binaries for every commit and tag:

$ nix run 'github:tek/ribosome#new' my-plugin

The created plugin can be added to Neovim like any other. For example, linking its directory to ~/.local/share/nvim/site/pack/foo/opt/my-plugin will allow you to run:

:packadd my-plugin

Using start instead of opt in the pack path will run the plugin at startup.

Or simply use one of the many plugin managers.

On the first start, the plugin will either be built with Nix, if it is available, or a static binary will be fetched from Github. Once that is done, the template project's dummy handler can be executed:

:echo MyPluginPing()
0
:echo MyPluginPing()
1

The second time the plugin ist started, the executable will be run directly, without checking for updates, unless the result has been garbage collected by Nix (i.e. the result link in the repo is broken). In order to force a rebuild after pulling, run the command:

$ nix build

Handlers

A list of RpcHandlers can be created by passing a handler function to one the smart constructors:

echoHello :: Member (Rpc !! RpcError) => Sem r ()
echoHello = ignoreRpcError (echo "Hello")

handlers = [
  rpcFunction "Hello" Async echoHello,
  rpcCommand "Hello" Async echoHello,
  rpcAutocmd "HelloHaskellFile" Async "BufEnter" "*.hs" echoHello
]

Passing these handlers to runNvimPluginIO_ starts a plugin that calls echoHello when running :call Hello(), :Hello, or when entering a Haskell buffer.

When the plugin's main loop starts, withHandlers registers the triggers in Neovim by running vim code like this:

function! Hello(...) range
  return call('rpcnotify', [1, 'function:Hello'] + a:000)
endfunction
command! -nargs=0 Hello call call('rpcnotify', [1, 'command:Hello'])
autocmd BufEnter *.hs call call('rpcnotify', [1, 'autocmd:HelloHaskellFile'])

Handler definition

data RpcHandler (r :: [(Type -> Type) -> Type -> Type]) #

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

Defined in Ribosome.Host.Data.RpcHandler

type Rep (RpcHandler r) 
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 :: [(Type -> Type) -> Type -> Type]) a = Sem (Stop Report ': r) a #

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.

newtype RpcName #

This name is used for the function or command registered in Neovim as well as to internally identify a handler.

Constructors

RpcName 

Fields

Instances

Instances details
IsString RpcName 
Instance details

Defined in Ribosome.Host.Data.RpcName

Methods

fromString :: String -> RpcName #

Show RpcName 
Instance details

Defined in Ribosome.Host.Data.RpcName

Eq RpcName 
Instance details

Defined in Ribosome.Host.Data.RpcName

Methods

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

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

Ord RpcName 
Instance details

Defined in Ribosome.Host.Data.RpcName

Constructing handlers

rpcFunction #

Arguments

:: forall (r :: [(Type -> Type) -> Type -> Type]) 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 #

Arguments

:: forall (r :: [(Type -> Type) -> Type -> Type]) 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.

rpcAutocmd #

Arguments

:: forall (r :: [(Type -> Type) -> Type -> Type]) 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 :: [(Type -> Type) -> Type -> Type]) h. (HandlerCodec h r, CommandHandler OptionStateZero h) => RpcName -> Execution -> h -> [RpcHandler r] #

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 #

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

Remote plugin execution

There are many ways of running a plugin for different purposes, like as a remote plugin from Neovim (the usual production mode), directly in a test using an embedded Neovim process, or over a socket when testing a plugin in tmux.

runNvimPluginIO :: forall r. HigherOrder r (RemoteStack ()) => PluginConfig () -> InterpretersFor r (RemoteStack ()) -> [RpcHandler (r ++ RemoteStack ())] -> IO () Source #

Run a Neovim plugin using a set of handlers and configuration, with an arbitrary stack of custom effects placed between the handlers and the Ribosome stack. This is important, because the custom effects may want to use the Neovim API, while the handlers want to use both Neovim and the custom effects.

Example:

data Numbers :: Effect where
  Number :: Int -> Sem r Int

makeSem ''Numbers

runNumbers :: Member (Rpc !! RpcError) r => InterpreterFor Numbers r
runNumbers = \case
  Number i -> (-1) <! nvimGetVar ("number_" <> show i)

type CustomStack = [AtomicState Int, Numbers]

currentNumber :: Handler r Int
currentNumber = number =<< atomicGet

setNumber :: Int -> Handler r ()
setNumber = atomicPut

runCustomStack :: InterpretersFor CustomStack r
runCustomStack = interpretAtomic . runNumbers

main :: IO ()
main = runNvimPluginIO @CustomStack "numbers" runCustomStack [
  rpcFunction "CurrentNumber" Sync currentNumber,
  rpcFunction "SetNumber" Async setNumber
  ]

Note:

  • PluginConfig is being constructed via OverloadedStrings
  • CustomStack has to be specified as a type application, because GHC cannot figure it out on its own.
  • For an explanation of Rpc !! RpcError, see Errors

This runs the entire stack to completion, so it can be used in the app's main function.

For more flexibility and less type inference noise, this can be inlined as:

runRemoteStack conf $ runCustomStack $ withHandlers handlers remotePlugin

runNvimPluginIO_ :: PluginConfig () -> [RpcHandler (RemoteStack ())] -> IO () Source #

Run a Neovim plugin using a set of handlers and configuration.

This function does not allow additional effects to be used. See runNvimPluginIO for that purpose.

This runs the entire stack to completion, so it can be used in the app's main function.

runNvimPluginCli :: HigherOrder r (RemoteStack c) => PluginConfig c -> InterpretersFor r (RemoteStack c) -> [RpcHandler (r ++ RemoteStack c)] -> IO () Source #

Run a Neovim plugin using a set of handlers and configuration, with an arbitrary stack of custom effects placed between the handlers and the Ribosome stack.

Like runNvimPluginIO, but allows the PluginConfig to contain a CLI parser for an arbitrary type c that is then provided in a Reader c to the plugin.

This is separate from runNvimPluginIO because it requires a type hint when using OverloadedStrings or def to construct the config without an option parser.

withHandlers :: forall (r :: EffectRow) a. Members '[Handlers !! Report, Rpc !! RpcError, Log, Error BootError :: (Type -> Type) -> Type -> Type] r => [RpcHandler r] -> Sem r a -> Sem r a #

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.

remotePlugin :: forall c r. Members HandlerStack r => Members (BasicPluginStack c) r => Sem r () Source #

Run the main loop for a remote plugin.

type RemoteStack c = HandlerStack ++ BasicPluginStack c Source #

The complete stack of a Neovim plugin.

runRemoteStack :: PluginConfig () -> Sem (RemoteStack ()) () -> IO () Source #

Run plugin internals and IO effects for a remote plugin, reading options from the CLI.

runRemoteStackCli :: PluginConfig c -> Sem (RemoteStack c) () -> IO () Source #

Run plugin internals and IO effects for a remote plugin, reading options from the CLI.

Like runRemoteStack, but allows the CLI option parser to be specified.

interpretPluginRemote :: Members (BasicPluginStack c) r => InterpretersFor HandlerStack r Source #

Run plugin internals without IO effects.

type BasicPluginStack c = Reader PluginName ': (Reader (CustomConfig c) ': BasicStack) Source #

The effects that are shared by all variants (like embedded, remote, socket) of main functions.

Contains logging effects, IO related stuff and the plugin's name in a Reader.

runBasicPluginStack :: PluginName -> HostConfig -> c -> Sem (BasicPluginStack c) () -> IO () Source #

Execute the basic plugin stack all the way to an IO, given the plugin name and logging settings.

runCli :: PluginConfig c -> Sem (BasicPluginStack c) () -> IO () Source #

Execute the basic plugin stack all the way to an IO like runBasicPluginStack, reading config overrides from command line options.

type NvimPlugin = [Scratch !! RpcError, Settings !! SettingError, Rpc !! RpcError, Reader PluginName] Source #

The set of core effects that handlers and API functions commonly use.

Interacting with Neovim

  • The effect Rpc governs access to Neovim's remote API.
  • The module Ribosome.Api.Data contains declarative representations of all API calls that are listed at :help api.
  • The module Ribosome.Api.Effect, reexported from Ribosome.Api, contains the same set of API functions, but as callable Sem functions that use the data declarations with sync. Ribosome.Api additionally contains many composite functions using the Neovim API.

The API also defines the data types Buffer, Window and Tabpage, which are abstract types carrying an internal identifier generated by Neovim.

data Rpc (a :: Type -> Type) b #

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.

data Request #

The payload of an RPC request.

Constructors

Request RpcMethod [Object] 

Instances

Instances details
Generic Request 
Instance details

Defined in Ribosome.Host.Data.Request

Associated Types

type Rep Request :: Type -> Type #

Methods

from :: Request -> Rep Request x #

to :: Rep Request x -> Request #

Show Request 
Instance details

Defined in Ribosome.Host.Data.Request

Eq Request 
Instance details

Defined in Ribosome.Host.Data.Request

Methods

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

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

MsgpackEncode Request 
Instance details

Defined in Ribosome.Host.Data.Request

Methods

toMsgpack :: Request -> Object #

type Rep Request 
Instance details

Defined in Ribosome.Host.Data.Request

type Rep Request = D1 ('MetaData "Request" "Ribosome.Host.Data.Request" "ribosome-host-0.9.9.9-4n86eC1033RAA2pmC2T1m9" 'False) (C1 ('MetaCons "Request" 'PrefixI 'True) (S1 ('MetaSel ('Just "method") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 RpcMethod) :*: S1 ('MetaSel ('Just "arguments") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 [Object])))

data RpcCall a #

A wrapper for Request that allows applicative sequencing of calls for batch processing, used for a declarative representation of the Neovim API.

Neovim has an API function named nvim_call_atomic that makes it possible to send multiple RPC requests at once, reducing the communcation overhead. Applicative sequences of RpcCalls are automatically batched into a single call by Rpc.

This can be combined neatly with ApplicativeDo:

import Ribosome
import qualified Ribosome.Api.Data as Api

sync do
  a :: Int <- Api.nvimGetVar "number1"
  b :: Int <- Api.nvimGetVar "number2"
  pure (a + b)

Instances

Instances details
Applicative RpcCall 
Instance details

Defined in Ribosome.Host.Data.RpcCall

Methods

pure :: a -> RpcCall a #

(<*>) :: RpcCall (a -> b) -> RpcCall a -> RpcCall b #

liftA2 :: (a -> b -> c) -> RpcCall a -> RpcCall b -> RpcCall c #

(*>) :: RpcCall a -> RpcCall b -> RpcCall b #

(<*) :: RpcCall a -> RpcCall b -> RpcCall a #

Functor RpcCall 
Instance details

Defined in Ribosome.Host.Data.RpcCall

Methods

fmap :: (a -> b) -> RpcCall a -> RpcCall b #

(<$) :: a -> RpcCall b -> RpcCall a #

Monoid a => Monoid (RpcCall a) 
Instance details

Defined in Ribosome.Host.Data.RpcCall

Methods

mempty :: RpcCall a #

mappend :: RpcCall a -> RpcCall a -> RpcCall a #

mconcat :: [RpcCall a] -> RpcCall a #

Semigroup a => Semigroup (RpcCall a) 
Instance details

Defined in Ribosome.Host.Data.RpcCall

Methods

(<>) :: RpcCall a -> RpcCall a -> RpcCall a #

sconcat :: NonEmpty (RpcCall a) -> RpcCall a #

stimes :: Integral b => b -> RpcCall a -> RpcCall a #

sync :: forall (r :: EffectRow) a. Member Rpc r => RpcCall a -> Sem r a #

Block the current thread while sending an RPC request.

async :: forall a (r :: EffectRow). Member Rpc r => RpcCall a -> (Either RpcError a -> Sem r ()) -> Sem r () #

Send an RPC request and pass the result to the continuation on a new thread.

notify :: forall a (r :: EffectRow). Member Rpc r => RpcCall a -> Sem r () #

Send an RPC notification and return immediately.

channelId :: forall (r :: EffectRow). Member Rpc r => Sem r ChannelId #

The Neovim RPC channel ID

data Buffer #

Instances

Instances details
Show Buffer 
Instance details

Defined in Ribosome.Host.Api.Data

Eq Buffer 
Instance details

Defined in Ribosome.Host.Api.Data

Methods

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

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

MsgpackDecode Buffer 
Instance details

Defined in Ribosome.Host.Api.Data

MsgpackEncode Buffer 
Instance details

Defined in Ribosome.Host.Api.Data

Methods

toMsgpack :: Buffer -> Object #

data Window #

Instances

Instances details
Show Window 
Instance details

Defined in Ribosome.Host.Api.Data

Eq Window 
Instance details

Defined in Ribosome.Host.Api.Data

Methods

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

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

MsgpackDecode Window 
Instance details

Defined in Ribosome.Host.Api.Data

MsgpackEncode Window 
Instance details

Defined in Ribosome.Host.Api.Data

Methods

toMsgpack :: Window -> Object #

data Tabpage #

Instances

Instances details
Show Tabpage 
Instance details

Defined in Ribosome.Host.Api.Data

Eq Tabpage 
Instance details

Defined in Ribosome.Host.Api.Data

Methods

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

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

MsgpackDecode Tabpage 
Instance details

Defined in Ribosome.Host.Api.Data

MsgpackEncode Tabpage 
Instance details

Defined in Ribosome.Host.Api.Data

Methods

toMsgpack :: Tabpage -> Object #

data Event #

An event is an RPC notification sent by Neovim that is not intended to be dispatched to a named handler, but consumed in a broadcasting fashion.

Since they aren't marked as such, the host treats any notification with an unknown method name as an event.

Events can be consumed with Consume and subscribe.

Constructors

Event EventName [Object] 

Instances

Instances details
Show Event 
Instance details

Defined in Ribosome.Host.Data.Event

Methods

showsPrec :: Int -> Event -> ShowS #

show :: Event -> String #

showList :: [Event] -> ShowS #

Eq Event 
Instance details

Defined in Ribosome.Host.Data.Event

Methods

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

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

newtype EventName #

The name of an event, which corresponds to the RPC method in the payload.

Constructors

EventName Text 

Watching variables

Watched variable handlers are called whenever a certain Neovim variable's value has changed:

changed ::
  Members NvimPlugin r =>
  Object ->
  Handler r ()
changed value =
  ignoreRpcError (echo ("Update value to: " <> show value))

main :: IO ()
main = runRemoteStack "watch-plugin" (watchVariables [("trigger", changed)] remotePlugin)

This registers the variable named trigger to be watched for changes. When a change is detected, the handler changed whill be executed with the new value as its argument.

Note that the combinators in the main function are simply what's run by runNvimPluginIO, with watchVariables being used as the custom effect stack and an empty list of handlers.

watchVariables :: Members [VariableWatcher !! Report, Rpc !! RpcError, Resource, Mask mres, Race, Embed IO] r => Map WatchedVariable (Object -> Handler r ()) -> Sem r a -> Sem r a Source #

This is a reactive system that is triggered by several frequently sent autocommands to inspect a user-defined set of Neovim variables for changes. When a variable's value has been observed to have changed from the previously recorded state, the associated handler is executed.

This handler has to be passed to runNvimPluginIO or similar as part of the custom effect stack, like:

runNvimPluginIO "my-plugin" (watchVariables [("variable_name", handler)]) mempty

This does not remove VariableWatcher from the stack, but intercepts and resends it, to make it simpler to use with the plugin runners.

Embedded Neovim execution

While remote plugins are executed from within Neovim, Ribosome can also run Neovim from a Haskell process and attach to the subprocess' stdio.

The primary purpose of embedding Neovim is testing a plugin, but it could also be used to build a GUI application around Neovim.

The library Ribosome.Test provides more comprehensive functionality for the testing use case.

When embedding Neovim, the main loop is forked and the test is run synchronously:

import qualified Data.Text.IO as Text
import Ribosome
import Ribosome.Api

ping :: Handler r Text
ping = pure "Ping"

main :: IO ()
main =
  runEmbedPluginIO_ "ping-plugin" [rpcFunction "Ping" Sync ping] do
    ignoreRpcError do
      embed . Text.putStrLn =<< nvimCallFunction "Ping" []

runEmbedPluginIO :: HigherOrder r (EmbedStack ()) => PluginConfig () -> InterpretersFor r (EmbedStack ()) -> [RpcHandler (r ++ EmbedStack ())] -> Sem (r ++ EmbedStack ()) () -> IO () Source #

Run a Sem in an embedded plugin context by starting a Neovim subprocess, forking the Ribosome main loop and registering the supplied handlers, using the supplied custom effect stack.

This is a basic version of what ribosome-test provides, which uses polysemy-test and hedgehog for a comprehensive testing framework.

The parameters have the same meaning as for remote plugins.

runEmbedPluginIO_ :: PluginConfig () -> [RpcHandler (EmbedStack ())] -> Sem (EmbedStack ()) () -> IO () Source #

Run a Sem in an embedded plugin context by starting a Neovim subprocess, forking the Ribosome main loop and registering the supplied handlers.

Like runEmbedPluginIO, but without extra effects.

runEmbedPluginCli :: HigherOrder r (EmbedStack c) => PluginConfig c -> InterpretersFor r (EmbedStack c) -> [RpcHandler (r ++ EmbedStack c)] -> Sem (r ++ EmbedStack c) () -> IO () Source #

Run a Sem in an embedded plugin context by starting a Neovim subprocess, forking the Ribosome main loop and registering the supplied handlers, using the supplied custom effect stack.

Like runEmbedPluginIO, but allows the PluginConfig to contain a CLI parser for an arbitrary type c that is then provided in a Reader c to the plugin.

This is separate from runEmbedPluginIO because it requires a type hint when using OverloadedStrings or def to construct the config without an option parser.

embedPlugin :: Members (HostDeps er) r => Members BuiltinHandlersDeps r => Sem r a -> Sem r a Source #

Fork the main loop for a plugin connected to an embedded Neovim.

runEmbedStack :: PluginConfig () -> Sem (EmbedStack ()) () -> IO () Source #

Run an embedded Neovim, plugin internals and IO effects, reading options from the CLI.

runEmbedStackCli :: PluginConfig c -> Sem (EmbedStack c) () -> IO () Source #

Run an embedded Neovim, plugin internals and IO effects, reading options from the CLI.

Like runEmbedStack, but allows the CLI option parser to be specified.

interpretPluginEmbed :: Members [Log, Reader LogConfig, Reader PluginName] r => Members IOStack r => InterpretersFor HandlerEffects r Source #

Run the internal stack for an embedded Neovim test, without IO effects.

MessagePack codec

Neovim's RPC communication uses the MessagePack protocol. All API functions convert their arguments and return values using the classes MsgpackEncode and MsgpackDecode. There are several Haskell libraries for this purpose. Ribosome uses messagepack, simply for the reason that it allows easy incremental parsing via cereal.

All API functions that are declared as taking or returning an Object by Neovim are kept polymorphic, allowing the user to interface with them using arbitrary types. Codec classes for record types can be derived generically:

data Cat =
  Cat { name :: Text, age :: Int }
  deriving stock (Generic)
  deriving anyclass (MsgpackEncode, MsgpackDecode)

nvimSetVar "cat" (Cat "Dr. Boots" 4)

The module Ribosome.Msgpack contains tools for writing MessagePack instances for custom types.

class MsgpackDecode a where #

Class of values that can be decoded from MessagePack Objects.

Minimal complete definition

Nothing

Methods

fromMsgpack :: Object -> Either DecodeError a #

Decode a value from a MessagePack Object.

The default implementation uses generic derivation.

Instances

Instances details
MsgpackDecode Int64 
Instance details

Defined in Ribosome.Host.Class.Msgpack.Decode

MsgpackDecode ByteString 
Instance details

Defined in Ribosome.Host.Class.Msgpack.Decode

MsgpackDecode Object 
Instance details

Defined in Ribosome.Host.Class.Msgpack.Decode

MsgpackDecode MicroSeconds 
Instance details

Defined in Ribosome.Host.Class.Msgpack.Decode

MsgpackDecode MilliSeconds 
Instance details

Defined in Ribosome.Host.Class.Msgpack.Decode

MsgpackDecode NanoSeconds 
Instance details

Defined in Ribosome.Host.Class.Msgpack.Decode

MsgpackDecode Seconds 
Instance details

Defined in Ribosome.Host.Class.Msgpack.Decode

MsgpackDecode SimpleMode Source # 
Instance details

Defined in Ribosome.Api.Mode

MsgpackDecode MappingId Source # 
Instance details

Defined in Ribosome.Data.Mapping

MsgpackDecode NvimMode Source # 
Instance details

Defined in Ribosome.Data.Mode

MsgpackDecode Register Source # 
Instance details

Defined in Ribosome.Data.Register

MsgpackDecode RegisterType Source # 
Instance details

Defined in Ribosome.Data.RegisterType

MsgpackDecode ScratchId Source # 
Instance details

Defined in Ribosome.Data.ScratchId

MsgpackDecode WindowConfig Source # 
Instance details

Defined in Ribosome.Data.WindowConfig

MsgpackDecode PartialWindowView Source # 
Instance details

Defined in Ribosome.Data.WindowView

MsgpackDecode WindowView Source # 
Instance details

Defined in Ribosome.Data.WindowView

MsgpackDecode Buffer 
Instance details

Defined in Ribosome.Host.Api.Data

MsgpackDecode Tabpage 
Instance details

Defined in Ribosome.Host.Api.Data

MsgpackDecode Window 
Instance details

Defined in Ribosome.Host.Api.Data

MsgpackDecode DecodeError 
Instance details

Defined in Ribosome.Host.Class.Msgpack.Decode

MsgpackDecode FieldError 
Instance details

Defined in Ribosome.Host.Class.Msgpack.Decode

MsgpackDecode ValidUtf8 
Instance details

Defined in Ribosome.Host.Class.Msgpack.Decode

MsgpackDecode ValidUtf8String 
Instance details

Defined in Ribosome.Host.Class.Msgpack.Decode

MsgpackDecode ApiInfo 
Instance details

Defined in Ribosome.Host.Data.ApiInfo

MsgpackDecode ExtType 
Instance details

Defined in Ribosome.Host.Data.ApiInfo

MsgpackDecode ExtTypeMeta 
Instance details

Defined in Ribosome.Host.Data.ApiInfo

MsgpackDecode RpcDecl 
Instance details

Defined in Ribosome.Host.Data.ApiInfo

MsgpackDecode ApiType 
Instance details

Defined in Ribosome.Host.Data.ApiType

MsgpackDecode Bang 
Instance details

Defined in Ribosome.Host.Data.Bang

MsgpackDecode Bar 
Instance details

Defined in Ribosome.Host.Data.Bar

MsgpackDecode ChannelId 
Instance details

Defined in Ribosome.Host.Data.ChannelId

MsgpackDecode CommandMods 
Instance details

Defined in Ribosome.Host.Data.CommandMods

MsgpackDecode CommandRegister 
Instance details

Defined in Ribosome.Host.Data.CommandRegister

MsgpackDecode EventName 
Instance details

Defined in Ribosome.Host.Data.Event

MsgpackDecode Execution 
Instance details

Defined in Ribosome.Host.Data.Execution

MsgpackDecode LuaRef 
Instance details

Defined in Ribosome.Host.Data.LuaRef

MsgpackDecode RequestId 
Instance details

Defined in Ribosome.Host.Data.Request

MsgpackDecode RpcMethod 
Instance details

Defined in Ribosome.Host.Data.Request

MsgpackDecode RpcError 
Instance details

Defined in Ribosome.Host.Data.RpcError

MsgpackDecode RpcMessage 
Instance details

Defined in Ribosome.Host.Data.RpcMessage

MsgpackDecode AutocmdBuffer 
Instance details

Defined in Ribosome.Host.Data.RpcType

MsgpackDecode AutocmdEvents 
Instance details

Defined in Ribosome.Host.Data.RpcType

MsgpackDecode AutocmdGroup 
Instance details

Defined in Ribosome.Host.Data.RpcType

MsgpackDecode AutocmdId 
Instance details

Defined in Ribosome.Host.Data.RpcType

MsgpackDecode AutocmdPatterns 
Instance details

Defined in Ribosome.Host.Data.RpcType

MsgpackDecode Text 
Instance details

Defined in Ribosome.Host.Class.Msgpack.Decode

MsgpackDecode String 
Instance details

Defined in Ribosome.Host.Class.Msgpack.Decode

MsgpackDecode Integer 
Instance details

Defined in Ribosome.Host.Class.Msgpack.Decode

MsgpackDecode () 
Instance details

Defined in Ribosome.Host.Class.Msgpack.Decode

MsgpackDecode Bool 
Instance details

Defined in Ribosome.Host.Class.Msgpack.Decode

MsgpackDecode Char 
Instance details

Defined in Ribosome.Host.Class.Msgpack.Decode

MsgpackDecode Double 
Instance details

Defined in Ribosome.Host.Class.Msgpack.Decode

MsgpackDecode Float 
Instance details

Defined in Ribosome.Host.Class.Msgpack.Decode

MsgpackDecode Int 
Instance details

Defined in Ribosome.Host.Class.Msgpack.Decode

Typeable style => MsgpackDecode (Range style) 
Instance details

Defined in Ribosome.Host.Data.Range

MsgpackDecode a => MsgpackDecode (Maybe a) 
Instance details

Defined in Ribosome.Host.Class.Msgpack.Decode

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

Defined in Ribosome.Host.Class.Msgpack.Decode

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

Defined in Ribosome.Host.Class.Msgpack.Decode

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

Defined in Ribosome.Host.Class.Msgpack.Decode

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

Defined in Ribosome.Host.Class.Msgpack.Decode

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

Defined in Ribosome.Host.Class.Msgpack.Decode

Methods

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

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

Defined in Ribosome.Host.Class.Msgpack.Decode

Methods

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

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

Defined in Ribosome.Host.Class.Msgpack.Decode

Methods

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

(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) 
Instance details

Defined in Ribosome.Host.Class.Msgpack.Decode

Methods

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

(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) 
Instance details

Defined in Ribosome.Host.Class.Msgpack.Decode

Methods

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

(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) 
Instance details

Defined in Ribosome.Host.Class.Msgpack.Decode

Methods

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

class MsgpackEncode a where #

Class of values that can be encoded to MessagePack Objects.

Minimal complete definition

Nothing

Methods

toMsgpack :: a -> Object #

Encode a value to MessagePack.

The default implementation uses generic derivation.

Instances

Instances details
MsgpackEncode Int64 
Instance details

Defined in Ribosome.Host.Class.Msgpack.Encode

Methods

toMsgpack :: Int64 -> Object #

MsgpackEncode ByteString 
Instance details

Defined in Ribosome.Host.Class.Msgpack.Encode

MsgpackEncode Object 
Instance details

Defined in Ribosome.Host.Class.Msgpack.Encode

Methods

toMsgpack :: Object -> Object #

MsgpackEncode MicroSeconds 
Instance details

Defined in Ribosome.Host.Class.Msgpack.Encode

MsgpackEncode MilliSeconds 
Instance details

Defined in Ribosome.Host.Class.Msgpack.Encode

MsgpackEncode NanoSeconds 
Instance details

Defined in Ribosome.Host.Class.Msgpack.Encode

MsgpackEncode Seconds 
Instance details

Defined in Ribosome.Host.Class.Msgpack.Encode

Methods

toMsgpack :: Seconds -> Object #

MsgpackEncode FloatAnchor Source # 
Instance details

Defined in Ribosome.Data.FloatOptions

MsgpackEncode FloatBorder Source # 
Instance details

Defined in Ribosome.Data.FloatOptions

MsgpackEncode FloatOptions Source # 
Instance details

Defined in Ribosome.Data.FloatOptions

MsgpackEncode FloatRelative Source # 
Instance details

Defined in Ribosome.Data.FloatOptions

MsgpackEncode FloatStyle Source # 
Instance details

Defined in Ribosome.Data.FloatOptions

MsgpackEncode FloatZindex Source # 
Instance details

Defined in Ribosome.Data.FloatOptions

MsgpackEncode MappingId Source # 
Instance details

Defined in Ribosome.Data.Mapping

MsgpackEncode NvimMode Source # 
Instance details

Defined in Ribosome.Data.Mode

Methods

toMsgpack :: NvimMode -> Object #

MsgpackEncode Register Source # 
Instance details

Defined in Ribosome.Data.Register

Methods

toMsgpack :: Register -> Object #

MsgpackEncode RegisterType Source # 
Instance details

Defined in Ribosome.Data.RegisterType

MsgpackEncode ScratchId Source # 
Instance details

Defined in Ribosome.Data.ScratchId

MsgpackEncode WindowConfig Source # 
Instance details

Defined in Ribosome.Data.WindowConfig

MsgpackEncode PartialWindowView Source # 
Instance details

Defined in Ribosome.Data.WindowView

MsgpackEncode WindowView Source # 
Instance details

Defined in Ribosome.Data.WindowView

MsgpackEncode Buffer 
Instance details

Defined in Ribosome.Host.Api.Data

Methods

toMsgpack :: Buffer -> Object #

MsgpackEncode Tabpage 
Instance details

Defined in Ribosome.Host.Api.Data

Methods

toMsgpack :: Tabpage -> Object #

MsgpackEncode Window 
Instance details

Defined in Ribosome.Host.Api.Data

Methods

toMsgpack :: Window -> Object #

MsgpackEncode DecodeError 
Instance details

Defined in Ribosome.Host.Class.Msgpack.Encode

MsgpackEncode FieldError 
Instance details

Defined in Ribosome.Host.Class.Msgpack.Encode

MsgpackEncode ValidUtf8 
Instance details

Defined in Ribosome.Host.Class.Msgpack.Encode

MsgpackEncode EventName 
Instance details

Defined in Ribosome.Host.Data.Event

MsgpackEncode Execution 
Instance details

Defined in Ribosome.Host.Data.Execution

MsgpackEncode LuaRef 
Instance details

Defined in Ribosome.Host.Data.LuaRef

Methods

toMsgpack :: LuaRef -> Object #

MsgpackEncode Request 
Instance details

Defined in Ribosome.Host.Data.Request

Methods

toMsgpack :: Request -> Object #

MsgpackEncode RequestId 
Instance details

Defined in Ribosome.Host.Data.Request

MsgpackEncode RpcMethod 
Instance details

Defined in Ribosome.Host.Data.Request

MsgpackEncode RpcError 
Instance details

Defined in Ribosome.Host.Data.RpcError

Methods

toMsgpack :: RpcError -> Object #

MsgpackEncode RpcMessage 
Instance details

Defined in Ribosome.Host.Data.RpcMessage

MsgpackEncode AutocmdBuffer 
Instance details

Defined in Ribosome.Host.Data.RpcType

MsgpackEncode AutocmdEvents 
Instance details

Defined in Ribosome.Host.Data.RpcType

MsgpackEncode AutocmdGroup 
Instance details

Defined in Ribosome.Host.Data.RpcType

MsgpackEncode AutocmdId 
Instance details

Defined in Ribosome.Host.Data.RpcType

MsgpackEncode AutocmdPatterns 
Instance details

Defined in Ribosome.Host.Data.RpcType

MsgpackEncode Text 
Instance details

Defined in Ribosome.Host.Class.Msgpack.Encode

Methods

toMsgpack :: Text -> Object #

MsgpackEncode String 
Instance details

Defined in Ribosome.Host.Class.Msgpack.Encode

Methods

toMsgpack :: String -> Object #

MsgpackEncode Integer 
Instance details

Defined in Ribosome.Host.Class.Msgpack.Encode

Methods

toMsgpack :: Integer -> Object #

MsgpackEncode () 
Instance details

Defined in Ribosome.Host.Class.Msgpack.Encode

Methods

toMsgpack :: () -> Object #

MsgpackEncode Bool 
Instance details

Defined in Ribosome.Host.Class.Msgpack.Encode

Methods

toMsgpack :: Bool -> Object #

MsgpackEncode Double 
Instance details

Defined in Ribosome.Host.Class.Msgpack.Encode

Methods

toMsgpack :: Double -> Object #

MsgpackEncode Float 
Instance details

Defined in Ribosome.Host.Class.Msgpack.Encode

Methods

toMsgpack :: Float -> Object #

MsgpackEncode Int 
Instance details

Defined in Ribosome.Host.Class.Msgpack.Encode

Methods

toMsgpack :: Int -> Object #

MsgpackEncode a => MsgpackEncode (NonEmpty a) 
Instance details

Defined in Ribosome.Host.Class.Msgpack.Encode

Methods

toMsgpack :: NonEmpty a -> Object #

MsgpackEncode a => MsgpackEncode (Seq a) 
Instance details

Defined in Ribosome.Host.Class.Msgpack.Encode

Methods

toMsgpack :: Seq a -> Object #

MsgpackEncode a => MsgpackEncode (Maybe a) 
Instance details

Defined in Ribosome.Host.Class.Msgpack.Encode

Methods

toMsgpack :: Maybe a -> Object #

MsgpackEncode a => MsgpackEncode [a] 
Instance details

Defined in Ribosome.Host.Class.Msgpack.Encode

Methods

toMsgpack :: [a] -> Object #

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

Defined in Ribosome.Host.Class.Msgpack.Encode

Methods

toMsgpack :: Map k v -> Object #

MsgpackEncode (Path b t) 
Instance details

Defined in Ribosome.Host.Class.Msgpack.Encode

Methods

toMsgpack :: Path b t -> Object #

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

Defined in Ribosome.Host.Class.Msgpack.Encode

Methods

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

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

Defined in Ribosome.Host.Class.Msgpack.Encode

Methods

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

pattern Msgpack :: MsgpackDecode a => a -> Object #

Pattern synonym for decoding an Object.

msgpackArray :: MsgpackArray a => a #

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 #

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.

Utility effects

TODO

Settings

data Settings :: Effect Source #

This effects abstracts Neovim variables with associated defaults.

data Setting a Source #

This type is used by the effect Settings, representing a Neovim variable associated with a plugin.

It has a name, can optionally prefixed by the plugin's name and may define a default value that is used when the variable is undefined.

The type parameter determines how the Neovim value is decoded.

Constructors

Setting Text Bool (Maybe a) 

data SettingError Source #

The errors emitted by the effect Settings.

Instances

Instances details
Show SettingError Source # 
Instance details

Defined in Ribosome.Data.SettingError

Eq SettingError Source # 
Instance details

Defined in Ribosome.Data.SettingError

Reportable SettingError Source # 
Instance details

Defined in Ribosome.Data.SettingError

Scratch buffers

A scratch buffer is what Neovim calls text not associated with a file, used for informational or interactive content. Ribosome provides an interface for maintaining those, by associating a view configuration with an ID and allowing to update the text displayed in it. Its full API is exposed by Ribosome.Scratch.

data Scratch :: Effect Source #

This effect manages scratch buffers, that is, transient buffers displaying text not associated with a file. See ScratchOptions for configuration.

data ScratchOptions Source #

Configure the visual properties of a scratch buffer. If the option float is specified, the buffer will be opened in a floating window.

Instances

Instances details
Generic ScratchOptions Source # 
Instance details

Defined in Ribosome.Data.ScratchOptions

Associated Types

type Rep ScratchOptions :: Type -> Type #

Show ScratchOptions Source # 
Instance details

Defined in Ribosome.Data.ScratchOptions

Default ScratchOptions Source # 
Instance details

Defined in Ribosome.Data.ScratchOptions

Methods

def :: ScratchOptions #

Eq ScratchOptions Source # 
Instance details

Defined in Ribosome.Data.ScratchOptions

type Rep ScratchOptions Source # 
Instance details

Defined in Ribosome.Data.ScratchOptions

type Rep ScratchOptions = D1 ('MetaData "ScratchOptions" "Ribosome.Data.ScratchOptions" "ribosome-0.9.9.9-9qviHqnn5IlBIAvGWfH18d" 'False) (C1 ('MetaCons "ScratchOptions" 'PrefixI 'True) (((S1 ('MetaSel ('Just "tab") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 Bool) :*: (S1 ('MetaSel ('Just "vertical") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 Bool) :*: S1 ('MetaSel ('Just "wrap") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 Bool))) :*: ((S1 ('MetaSel ('Just "focus") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 Bool) :*: S1 ('MetaSel ('Just "resize") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 Bool)) :*: (S1 ('MetaSel ('Just "bottom") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 Bool) :*: S1 ('MetaSel ('Just "modify") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 Bool)))) :*: ((S1 ('MetaSel ('Just "float") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (Maybe FloatOptions)) :*: (S1 ('MetaSel ('Just "size") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (Maybe Int)) :*: S1 ('MetaSel ('Just "maxSize") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (Maybe Int)))) :*: ((S1 ('MetaSel ('Just "syntax") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 [Syntax]) :*: S1 ('MetaSel ('Just "mappings") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 [Mapping])) :*: (S1 ('MetaSel ('Just "filetype") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (Maybe Text)) :*: S1 ('MetaSel ('Just "name") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 ScratchId))))))

scratch :: ScratchId -> ScratchOptions Source #

The default configuration, setting all flags to False except for $sel:resize:ScratchOptions and $sel:bottom:ScratchOptions, and everything else to mempty.

data FloatOptions Source #

The set of options accepted by the float key of the argument to nvim_open_win, configuring the appearance and geometry of a floating window.

Instances

Instances details
Generic FloatOptions Source # 
Instance details

Defined in Ribosome.Data.FloatOptions

Associated Types

type Rep FloatOptions :: Type -> Type #

Show FloatOptions Source # 
Instance details

Defined in Ribosome.Data.FloatOptions

Default FloatOptions Source # 
Instance details

Defined in Ribosome.Data.FloatOptions

Methods

def :: FloatOptions #

Eq FloatOptions Source # 
Instance details

Defined in Ribosome.Data.FloatOptions

MsgpackEncode FloatOptions Source # 
Instance details

Defined in Ribosome.Data.FloatOptions

type Rep FloatOptions Source # 
Instance details

Defined in Ribosome.Data.FloatOptions

type Rep FloatOptions = D1 ('MetaData "FloatOptions" "Ribosome.Data.FloatOptions" "ribosome-0.9.9.9-9qviHqnn5IlBIAvGWfH18d" 'False) (C1 ('MetaCons "FloatOptions" 'PrefixI 'True) (((S1 ('MetaSel ('Just "relative") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 FloatRelative) :*: (S1 ('MetaSel ('Just "width") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 Int) :*: S1 ('MetaSel ('Just "height") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 Int))) :*: (S1 ('MetaSel ('Just "row") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 Int) :*: (S1 ('MetaSel ('Just "col") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 Int) :*: S1 ('MetaSel ('Just "focusable") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 Bool)))) :*: ((S1 ('MetaSel ('Just "anchor") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 FloatAnchor) :*: (S1 ('MetaSel ('Just "bufpos") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (Maybe (Int, Int))) :*: S1 ('MetaSel ('Just "border") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 FloatBorder))) :*: ((S1 ('MetaSel ('Just "noautocmd") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 Bool) :*: S1 ('MetaSel ('Just "enter") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 Bool)) :*: (S1 ('MetaSel ('Just "style") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (Maybe FloatStyle)) :*: S1 ('MetaSel ('Just "zindex") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (Maybe FloatZindex)))))))

newtype ScratchId Source #

The ID type used to store active scratch buffers.

Constructors

ScratchId Text 

data ScratchState Source #

The configuration and Neovim resources that define a scratch buffer and describe its previously recorded UI state.

Instances

Instances details
Generic ScratchState Source # 
Instance details

Defined in Ribosome.Data.ScratchState

Associated Types

type Rep ScratchState :: Type -> Type #

Show ScratchState Source # 
Instance details

Defined in Ribosome.Data.ScratchState

Eq ScratchState Source # 
Instance details

Defined in Ribosome.Data.ScratchState

type Rep ScratchState Source # 
Instance details

Defined in Ribosome.Data.ScratchState

Mappings

The function activateBufferMapping can be used to dynamically create buffer-local Neovim key mappings that trigger handlers of a Ribosome plugin.

A slightly reliable way of constructing a Mapping is to use mappingFor, which takes an RpcHandler to ensure that the name it calls was at least associated with a handler at some point.

One use case for mappings is in a Scratch buffer, which automatically registers a set of them after initializing the buffer.

data Mapping Source #

This type associates a sequence of keys and a mode for a Neovim mapping with an RPC handler or event. It is intended to be used with mappingFor or eventMapping and activateBufferMapping.

Instances

Instances details
Generic Mapping Source # 
Instance details

Defined in Ribosome.Data.Mapping

Associated Types

type Rep Mapping :: Type -> Type #

Methods

from :: Mapping -> Rep Mapping x #

to :: Rep Mapping x -> Mapping #

Show Mapping Source # 
Instance details

Defined in Ribosome.Data.Mapping

Eq Mapping Source # 
Instance details

Defined in Ribosome.Data.Mapping

Methods

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

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

type Rep Mapping Source # 
Instance details

Defined in Ribosome.Data.Mapping

data MappingAction Source #

The action that should be performed when a mapping is triggered.

Constructors

MappingCall RpcName

The name of the RpcHandler that should be called when the mapping is triggered.

MappingEvent EventName

The event to publish when the mapping is triggered.

Instances

Instances details
Show MappingAction Source # 
Instance details

Defined in Ribosome.Data.Mapping

Eq MappingAction Source # 
Instance details

Defined in Ribosome.Data.Mapping

newtype MappingId Source #

This ID type is intended to carry information about what buffer or other component triggered a mapping, if needed.

Constructors

MappingId Text 

newtype MappingLhs Source #

The sequence of keys that triggers a mapping.

Constructors

MappingLhs Text 

data MapMode Source #

All possible variants of Neovim's map commands, causing mappings to be registered for different modes.

Constructors

MapDefault

:map – normal, visual, select and operator-pending

MapNormal

:nmap – normal

MapInsertCmdline

:map! – insert and cmdline

MapInsert

:imap – insert

MapCmdline

:cmap – cmdline

MapLangArg

:lmap – insert, cmdline, lang-arg

MapVisual

:xmap – visual

MapSelect

:smap – select

MapVisualSelect

:vmap – visual and select

MapOperator

:omap – operator-pending

Instances

Instances details
Enum MapMode Source # 
Instance details

Defined in Ribosome.Data.Mapping

Show MapMode Source # 
Instance details

Defined in Ribosome.Data.Mapping

Default MapMode Source # 
Instance details

Defined in Ribosome.Data.Mapping

Methods

def :: MapMode #

Eq MapMode Source # 
Instance details

Defined in Ribosome.Data.Mapping

Methods

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

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

Ord MapMode Source # 
Instance details

Defined in Ribosome.Data.Mapping

data MappingSpec Source #

The configuration for a mapping that is specific to Neovim.

Instances

Instances details
IsString MappingSpec Source # 
Instance details

Defined in Ribosome.Data.Mapping

Generic MappingSpec Source # 
Instance details

Defined in Ribosome.Data.Mapping

Associated Types

type Rep MappingSpec :: Type -> Type #

Show MappingSpec Source # 
Instance details

Defined in Ribosome.Data.Mapping

Eq MappingSpec Source # 
Instance details

Defined in Ribosome.Data.Mapping

Ord MappingSpec Source # 
Instance details

Defined in Ribosome.Data.Mapping

type Rep MappingSpec Source # 
Instance details

Defined in Ribosome.Data.Mapping

type Rep MappingSpec = D1 ('MetaData "MappingSpec" "Ribosome.Data.Mapping" "ribosome-0.9.9.9-9qviHqnn5IlBIAvGWfH18d" 'False) (C1 ('MetaCons "MappingSpec" 'PrefixI 'True) (S1 ('MetaSel ('Just "lhs") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 MappingLhs) :*: S1 ('MetaSel ('Just "mode") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (NonEmpty MapMode))))

mappingFor :: RpcHandler r -> MappingLhs -> NonEmpty MapMode -> Maybe MappingId -> Map Text Object -> Mapping Source #

Construct a Mapping using the name from the supplied RpcHandler.

activateBufferMapping :: Member Rpc r => Buffer -> Mapping -> Sem r () Source #

Register a mapping in the supplied buffer.

activateMapping :: Member Rpc r => Mapping -> Sem r () Source #

Register a mapping globally.

Persisting data across vim sessions

data Persist a :: Effect Source #

This effect abstracts storing data of type a in the file system to allow loading it when a plugin starts.

Each distinct type corresponds to a separate copy of this effect. When the same type should be stored in separate files for different components of the plugin, use Tagged. The subdirectory or file name used for a type is specified to the interpreter. If the constructor store is called with Just a file name, each value is stored in a separate file, otherwise the same file is overwritten on every call to store.

The default interpreter delegates file path resolution to the effect PersistPath and uses JSON to codec the data.

interpretPersist :: ToJSON a => FromJSON a => Members [PersistPath !! PersistPathError, Error BootError, Log, Embed IO] r => Text -> InterpreterFor (Persist a !! PersistError) r Source #

Interpret Persist by writing to the file system.

Paths are determined as follows:

  • PersistPath defines the root directory for all Persist effects, which might be specific to a plugin, or additionally to entities like the currently edited project (e.g. by directory).
  • The value in the name argument is appended to the root depending on the arguments to the effect constructors.
  • When store or load are invoked with Nothing for the subpath argument, a file named name.json is used.
  • When invoked with Just a subpath, a file named name/subpath.json is used.

This uses Resumable, see Errors.

interpretPersistNull :: forall a err r. InterpreterFor (Persist a !! err) r Source #

Interpret Persist by storing nothing.

data PersistPath :: Effect Source #

This is a utility effect for Persist, determining the root directory for persistence files.

persistPath :: forall r. Member PersistPath r => Maybe (Path Rel Dir) -> Sem r (Path Abs Dir) Source #

Return the root if Nothing is given, or the subdir of the root if Just is given.

interpretPersistPath :: Members [Settings !! SettingError, Reader PluginName, Error BootError, Embed IO] r => Bool -> InterpreterFor (PersistPath !! PersistPathError) r Source #

Interpret PersistPath by reading the global setting for the root directory, or using the XDG cache directory if the variable is unset.

The plugin name is used as a subdir of the root.

This uses Resumable, see Errors.

interpretPersistPathSetting :: Members [Settings !! SettingError, Embed IO] r => Bool -> Maybe (Path Abs Dir) -> Path Rel Dir -> InterpreterFor (PersistPath !! PersistPathError) r Source #

Interpret PersistPath by reading the global setting for the root directory, or using the given directory if the variable is unset.

The given name is appended to the root, which usually identifies the plugin.

interpretPersistPathAt :: Member (Embed IO) r => Bool -> Path Abs Dir -> InterpreterFor (PersistPath !! PersistPathError) r Source #

Interpret PersistPath by using the specified root directory.

data PersistError Source #

The errors emitted by the effect PersistPath.

Instances

Instances details
Show PersistError Source # 
Instance details

Defined in Ribosome.Data.PersistError

Eq PersistError Source # 
Instance details

Defined in Ribosome.Data.PersistError

Reportable PersistError Source # 
Instance details

Defined in Ribosome.Data.PersistError

The plugin's name

newtype PluginName Source #

Represents the name of the plugin, to be used via Reader by all its components.

The name is usually provided by main function combinators like runNvimPluginIO via Reader PluginConfig.

Constructors

PluginName Text 

interpretPluginName :: Member (Reader (PluginConfig c)) r => InterpreterFor (Reader PluginName) r Source #

Interpret Reader PluginName by extracting the name from the plugin config provided by another Reader PluginConfig.

This interpreter is used by the main function machinery.

More functionality for handlers

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

completeBuiltin :: forall (r :: [(Type -> Type) -> Type -> Type]). Text -> RpcHandler r -> RpcHandler r #

Configure the given RpcHandler to use the specified builtin completion.

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

Special command parameter types

class HandlerArg a (r :: EffectRow) where #

This class is used by HandlerCodec to decode handler function parameters. Each parameter may consume zero or arbitrarily many of the RPC message's arguments.

Users may create instances for their types to implement custom decoding, especially for commands, since those don't have structured arguments.

See also CommandHandler.

Methods

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

Instances

Instances details
Member (Stop Report) r => HandlerArg ArgList r 
Instance details

Defined in Ribosome.Host.Handler.Codec

Methods

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

Member (Stop Report) r => HandlerArg Args r 
Instance details

Defined in Ribosome.Host.Handler.Codec

Methods

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

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

Defined in Ribosome.Host.Handler.Codec

Methods

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

HandlerArg Bar r 
Instance details

Defined in Ribosome.Host.Handler.Codec

Methods

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

(Member (Stop Report) r, MsgpackDecode a) => HandlerArg a r 
Instance details

Defined in Ribosome.Host.Handler.Codec

Methods

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

(Member (Stop Report) r, FromJSON a) => HandlerArg (JsonArgs a) r 
Instance details

Defined in Ribosome.Host.Handler.Codec

Methods

handlerArg :: [Object] -> Sem r ([Object], JsonArgs a) #

(Member (Stop Report) r, OptionParser a) => HandlerArg (Options a) r 
Instance details

Defined in Ribosome.Host.Handler.Codec

Methods

handlerArg :: [Object] -> Sem r ([Object], Options a) #

HandlerArg a r => HandlerArg (Maybe a) r 
Instance details

Defined in Ribosome.Host.Handler.Codec

Methods

handlerArg :: [Object] -> Sem r ([Object], Maybe a) #

class CommandHandler (state :: OptionState) h where #

Derive the command options and arguments that should be used when registering the Neovim command, from the parameters of the handler function.

See Command params for the list of supported special types.

The parameter state is a type level value that determines which parameter types may be used after another and counts the number of command arguments that are required or allowed. It is transitioned by families in the classes CommandParam, SpecialParam and RegularParam.

Methods

commandOptions :: (Map Text Object, [Text]) #

Return the list of command options and special arguments determined by the handler function's parameters.

Instances

Instances details
(special ~ CommandSpecial a, next ~ TransState special state a, CommandParam special state a, CommandHandler next b) => CommandHandler state (a -> b) 
Instance details

Defined in Ribosome.Host.Handler.Command

CommandHandler ('OptionState _a 'MinOne c) (Sem r a) 
Instance details

Defined in Ribosome.Host.Handler.Command

CommandHandler ('OptionState _a 'MinZero c) (Sem r a) 
Instance details

Defined in Ribosome.Host.Handler.Command

CommandHandler ('OptionState _a 'Zero c) (Sem r a) 
Instance details

Defined in Ribosome.Host.Handler.Command

newtype Args #

When this type is used as the (last) parameter of a command handler function, all remaining tokens passed to the command will be consumed and stored in this type.

The command will be declared with the -nargs=* or -nargs=+ option.

See CommandHandler.

Constructors

Args 

Fields

Instances

Instances details
IsString Args 
Instance details

Defined in Ribosome.Host.Data.Args

Methods

fromString :: String -> Args #

Show Args 
Instance details

Defined in Ribosome.Host.Data.Args

Methods

showsPrec :: Int -> Args -> ShowS #

show :: Args -> String #

showList :: [Args] -> ShowS #

Eq Args 
Instance details

Defined in Ribosome.Host.Data.Args

Methods

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

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

Ord Args 
Instance details

Defined in Ribosome.Host.Data.Args

Methods

compare :: Args -> Args -> Ordering #

(<) :: Args -> Args -> Bool #

(<=) :: Args -> Args -> Bool #

(>) :: Args -> Args -> Bool #

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

max :: Args -> Args -> Args #

min :: Args -> Args -> Args #

Member (Stop Report) r => HandlerArg Args r 
Instance details

Defined in Ribosome.Host.Handler.Codec

Methods

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

SpecialParam ('OptionState al count ('Nothing :: Maybe Type)) Args 
Instance details

Defined in Ribosome.Host.Handler.Command

Associated Types

type TransSpecial ('OptionState al count 'Nothing) Args :: OptionState #

type TransSpecial ('OptionState al count ('Nothing :: Maybe Type)) Args 
Instance details

Defined in Ribosome.Host.Handler.Command

newtype ArgList #

When this type is used as the (last) parameter of a command handler function, all remaining tokens passed to the command will be consumed and stored in this type, as a list of whitespace separated tokens.

The command will be declared with the -nargs=* or -nargs=+ option.

See CommandHandler.

Constructors

ArgList 

Fields

Instances

Instances details
Show ArgList 
Instance details

Defined in Ribosome.Host.Data.Args

Eq ArgList 
Instance details

Defined in Ribosome.Host.Data.Args

Methods

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

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

Member (Stop Report) r => HandlerArg ArgList r 
Instance details

Defined in Ribosome.Host.Handler.Codec

Methods

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

SpecialParam ('OptionState al count ac) ArgList 
Instance details

Defined in Ribosome.Host.Handler.Command

Associated Types

type TransSpecial ('OptionState al count ac) ArgList :: OptionState #

type TransSpecial ('OptionState al count ac) ArgList 
Instance details

Defined in Ribosome.Host.Handler.Command

type TransSpecial ('OptionState al count ac) ArgList = 'OptionState 'True (Max count 'MinZero) ('Just ArgList)

newtype JsonArgs a #

When this type is used as the (last) parameter of a command handler function, all remaining tokens passed to the command will be consumed, decoded as JSON and stored in this type.

The command will be declared with the -nargs=* or -nargs=+ option.

See CommandHandler.

Constructors

JsonArgs 

Fields

Instances

Instances details
Show a => Show (JsonArgs a) 
Instance details

Defined in Ribosome.Host.Data.Args

Methods

showsPrec :: Int -> JsonArgs a -> ShowS #

show :: JsonArgs a -> String #

showList :: [JsonArgs a] -> ShowS #

Eq a => Eq (JsonArgs a) 
Instance details

Defined in Ribosome.Host.Data.Args

Methods

(==) :: JsonArgs a -> JsonArgs a -> Bool #

(/=) :: JsonArgs a -> JsonArgs a -> Bool #

(Member (Stop Report) r, FromJSON a) => HandlerArg (JsonArgs a) r 
Instance details

Defined in Ribosome.Host.Handler.Codec

Methods

handlerArg :: [Object] -> Sem r ([Object], JsonArgs a) #

SpecialParam ('OptionState al count ac) (JsonArgs a) 
Instance details

Defined in Ribosome.Host.Handler.Command

Associated Types

type TransSpecial ('OptionState al count ac) (JsonArgs a) :: OptionState #

type TransSpecial ('OptionState al count ac) (JsonArgs a) 
Instance details

Defined in Ribosome.Host.Handler.Command

type TransSpecial ('OptionState al count ac) (JsonArgs a) = 'OptionState 'True (Max count 'MinZero) ('Just (JsonArgs a))

newtype Options a #

When this type is used as the (last) parameter of a command handler function, all remaining tokens passed to the command will be consumed, parsed via optparse-applicative and stored in this type.

The parser associated with a must be defined as an instance of OptionParser a.

The command will be declared with the -nargs=* or -nargs=+ option.

See CommandHandler.

Constructors

Options a 

Instances

Instances details
Show a => Show (Options a) 
Instance details

Defined in Ribosome.Host.Data.Args

Methods

showsPrec :: Int -> Options a -> ShowS #

show :: Options a -> String #

showList :: [Options a] -> ShowS #

Eq a => Eq (Options a) 
Instance details

Defined in Ribosome.Host.Data.Args

Methods

(==) :: Options a -> Options a -> Bool #

(/=) :: Options a -> Options a -> Bool #

(Member (Stop Report) r, OptionParser a) => HandlerArg (Options a) r 
Instance details

Defined in Ribosome.Host.Handler.Codec

Methods

handlerArg :: [Object] -> Sem r ([Object], Options a) #

SpecialParam ('OptionState al count ('Nothing :: Maybe Type)) (Options a) 
Instance details

Defined in Ribosome.Host.Handler.Command

Associated Types

type TransSpecial ('OptionState al count 'Nothing) (Options a) :: OptionState #

type TransSpecial ('OptionState al count ('Nothing :: Maybe Type)) (Options a) 
Instance details

Defined in Ribosome.Host.Handler.Command

type TransSpecial ('OptionState al count ('Nothing :: Maybe Type)) (Options a) = 'OptionState 'True (Max count 'MinZero) ('Just (Options a))

class OptionParser a where #

The parser used when declaring command handlers with the special parameter Options a.

Methods

optionParser :: Parser a #

data Bang #

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 
Instance details

Defined in Ribosome.Host.Data.Bang

Methods

showsPrec :: Int -> Bang -> ShowS #

show :: Bang -> String #

showList :: [Bang] -> ShowS #

Eq Bang 
Instance details

Defined in Ribosome.Host.Data.Bang

Methods

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

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

MsgpackDecode Bang 
Instance details

Defined in Ribosome.Host.Data.Bang

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

Defined in Ribosome.Host.Handler.Codec

Methods

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

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

Defined in Ribosome.Host.Handler.Command

Associated Types

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

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

Defined in Ribosome.Host.Handler.Command

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

data Bar #

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 
Instance details

Defined in Ribosome.Host.Data.Bar

Methods

showsPrec :: Int -> Bar -> ShowS #

show :: Bar -> String #

showList :: [Bar] -> ShowS #

Eq Bar 
Instance details

Defined in Ribosome.Host.Data.Bar

Methods

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

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

MsgpackDecode Bar 
Instance details

Defined in Ribosome.Host.Data.Bar

HandlerArg Bar r 
Instance details

Defined in Ribosome.Host.Handler.Codec

Methods

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

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

Defined in Ribosome.Host.Handler.Command

Associated Types

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

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

Defined in Ribosome.Host.Handler.Command

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

data Range (style :: RangeStyle) #

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

Defined in Ribosome.Host.Data.Range

Methods

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

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

Typeable style => MsgpackDecode (Range style) 
Instance details

Defined in Ribosome.Host.Data.Range

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

Defined in Ribosome.Host.Handler.Command

Associated Types

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

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

Defined in Ribosome.Host.Handler.Command

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

data RangeStyle #

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

newtype CommandMods #

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 #

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 
Instance details

Defined in Ribosome.Host.Data.CommandRegister

Show CommandRegister 
Instance details

Defined in Ribosome.Host.Data.CommandRegister

Eq CommandRegister 
Instance details

Defined in Ribosome.Host.Data.CommandRegister

Ord CommandRegister 
Instance details

Defined in Ribosome.Host.Data.CommandRegister

MsgpackDecode CommandRegister 
Instance details

Defined in Ribosome.Host.Data.CommandRegister

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

Defined in Ribosome.Host.Handler.Command

Associated Types

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

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

Defined in Ribosome.Host.Handler.Command

class HandlerCodec h (r :: [(Type -> Type) -> Type -> Type]) | h -> r where #

The class of functions that can be converted to canonical RPC handlers of type RpcHandlerFun.

Methods

handlerCodec :: h -> RpcHandlerFun r #

Convert a type containing a Sem to a canonicalized RpcHandlerFun by transforming each function parameter with HandlerArg.

Instances

Instances details
MsgpackEncode a => HandlerCodec (Handler r a) r 
Instance details

Defined in Ribosome.Host.Handler.Codec

Methods

handlerCodec :: Handler r a -> RpcHandlerFun r #

(HandlerArg a (Stop Report ': r), HandlerCodec b r) => HandlerCodec (a -> b) r 
Instance details

Defined in Ribosome.Host.Handler.Codec

Methods

handlerCodec :: (a -> b) -> RpcHandlerFun r #

Command Modifiers

modifyCmd :: forall (r :: EffectRow) a. Member Rpc r => Text -> Sem r a -> Sem r a #

Prefix all nvim_commands called in an action with the given string.

bufdo :: forall (r :: EffectRow) a. Member Rpc r => Buffer -> Sem r a -> Sem r a #

Prefix all nvim_commands called in an action with bufdo N where N is the number of the given buffer.

windo :: forall (r :: EffectRow) a. Member Rpc r => Window -> Sem r a -> Sem r a #

Prefix all nvim_commands called in an action with windo N where N is the number of the given window.

noautocmd :: forall (r :: EffectRow) a. Member Rpc r => Sem r a -> Sem r a #

Prefix all nvim_commands called in an action with noautocmd.

silent :: forall (r :: EffectRow) a. Member Rpc r => Sem r a -> Sem r a #

Prefix all nvim_commands called in an action with silent.

silentBang :: forall (r :: EffectRow) a. Member Rpc r => Sem r a -> Sem r a #

Prefix all nvim_commands called in an action with silent!.

Configuring the host

newtype HostConfig #

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

Constructors

HostConfig 

Fields

Instances

Instances details
Generic HostConfig 
Instance details

Defined in Ribosome.Host.Data.HostConfig

Associated Types

type Rep HostConfig :: Type -> Type #

Show HostConfig 
Instance details

Defined in Ribosome.Host.Data.HostConfig

Default HostConfig 
Instance details

Defined in Ribosome.Host.Data.HostConfig

Methods

def :: HostConfig #

Eq HostConfig 
Instance details

Defined in Ribosome.Host.Data.HostConfig

type Rep HostConfig 
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 #

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 
Instance details

Defined in Ribosome.Host.Data.HostConfig

Associated Types

type Rep LogConfig :: Type -> Type #

Show LogConfig 
Instance details

Defined in Ribosome.Host.Data.HostConfig

Default LogConfig 
Instance details

Defined in Ribosome.Host.Data.HostConfig

Methods

def :: LogConfig #

Eq LogConfig 
Instance details

Defined in Ribosome.Host.Data.HostConfig

type Rep LogConfig 
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 #

Set the stderr level on a HostConfig.

data PluginConfig c Source #

The full configuration for a Ribosome plugin, consisting of the HostConfig, the plugin's name, and an arbitrary type for additional config defined by individual plugins.

Instances

Instances details
IsString (PluginConfig ()) Source # 
Instance details

Defined in Ribosome.Data.PluginConfig

Generic (PluginConfig c) Source # 
Instance details

Defined in Ribosome.Data.PluginConfig

Associated Types

type Rep (PluginConfig c) :: Type -> Type #

Methods

from :: PluginConfig c -> Rep (PluginConfig c) x #

to :: Rep (PluginConfig c) x -> PluginConfig c #

Show (PluginConfig c) Source # 
Instance details

Defined in Ribosome.Data.PluginConfig

Eq (PluginConfig c) Source # 
Instance details

Defined in Ribosome.Data.PluginConfig

type Rep (PluginConfig c) Source # 
Instance details

Defined in Ribosome.Data.PluginConfig

type Rep (PluginConfig c) = D1 ('MetaData "PluginConfig" "Ribosome.Data.PluginConfig" "ribosome-0.9.9.9-9qviHqnn5IlBIAvGWfH18d" 'False) (C1 ('MetaCons "PluginConfig" 'PrefixI 'True) (S1 ('MetaSel ('Just "name") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 PluginName) :*: (S1 ('MetaSel ('Just "host") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 HostConfig) :*: S1 ('MetaSel ('Just "custom") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (Parser c)))))

pluginNamed :: PluginName -> PluginConfig () Source #

Construct a simple PluginConfig with the default config for the host, given the plugin's name.

Reports

Ribosome uses polysemy-resume extensively, which is a concept for tracking errors across interpreters by attaching them to a wrapper effect.

In short, when an interpreter is written for the effect Rpc !! RpcError (which is a symbolic alias for Resumable RpcError Rpc), every use of the bare effect Rpc must be converted at some point, with the possiblity of exposing the error on another interpreter that uses the effect.

Take the effect Scratch for example, whose interpreter is for the effect Scratch !! RpcError. In there is the expression:

restop @RpcError @Rpc (setScratchContent s text)

The function setScratchContent has a dependency on the bare effect Rpc. The function restop converts this dependency into Rpc !! RpcError and Stop RpcError, meaning that this expression acknowledges that Rpc might fail with RpcError, and rethrows the error, which is then turned into Scratch !! RpcError by the special interpreter combinator interpretResumable.

Instead of rethrowing, the error can also be caught, by using a combinator like resume or the operator <! that is similar to <$.

The concept is similar to Error, with the difference that a Resumable interpreter can communicate that it throws this type of error, while with plain Error, this would have to be tracked manually by the developer.

Since handler functions yield the control flow to Ribosome's internal machinery when returning, all Stop effects have to be converted to Report (which is expected by the request dispatcher and part of the Handler stack), and all bare effects like Rpc have to be resumed or restopped since their interpreters only operate on the Resumable variants.

To make this chore a little less verbose, the class Reportable can be leveraged to convert errors to Report, which consists of an Report and ReportContext, which optionally identifies the plugin component that threw the error.

Since RpcError is an instance of Reportable, the combinators resumeReport and mapReport can be used to reinterpret to Stop Report.

resumeReport :: forall (eff :: (Type -> Type) -> Type -> Type) e (r :: EffectRow) a. (Reportable e, Members '[eff !! e, Stop Report] r) => Sem (eff ': r) a -> Sem r a #

Convert the effect eff to Resumable err eff and Stop Report if err is an instance of Reportable.

mapReport :: forall e (r :: EffectRow) a. (Reportable e, Member (Stop Report) r) => Sem (Stop e ': r) a -> Sem r a #

Reinterpret Stop err to Stop Report if err is an instance of Reportable.

resumeReports :: ResumeReports effs errs r => InterpretersFor effs r #

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 #

Map multiple errors to Report. This needs the errors specified as type applications.

mapReports @[RpcError, SettingError]

data LogReport #

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

Instances

Instances details
IsString LogReport 
Instance details

Defined in Ribosome.Host.Data.Report

Generic LogReport 
Instance details

Defined in Ribosome.Host.Data.Report

Associated Types

type Rep LogReport :: Type -> Type #

Show LogReport 
Instance details

Defined in Ribosome.Host.Data.Report

type Rep LogReport 
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 #

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 
Instance details

Defined in Ribosome.Host.Data.Report

Methods

fromString :: String -> Report #

Show Report 
Instance details

Defined in Ribosome.Host.Data.Report

Reportable Report 
Instance details

Defined in Ribosome.Host.Data.Report

Methods

toReport :: Report -> Report #

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

Defined in Ribosome.Host.Handler.Codec

Methods

handlerCodec :: Handler r a -> RpcHandlerFun r #

class Reportable e where #

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 #

Instances

Instances details
Reportable Void 
Instance details

Defined in Ribosome.Host.Data.Report

Methods

toReport :: Void -> Report #

Reportable PersistError Source # 
Instance details

Defined in Ribosome.Data.PersistError

Reportable PersistPathError Source # 
Instance details

Defined in Ribosome.Data.PersistPathError

Reportable SettingError Source # 
Instance details

Defined in Ribosome.Data.SettingError

Reportable DecodeError 
Instance details

Defined in Ribosome.Host.Class.Msgpack.Error

Reportable Report 
Instance details

Defined in Ribosome.Host.Data.Report

Methods

toReport :: Report -> Report #

Reportable RpcError 
Instance details

Defined in Ribosome.Host.Data.RpcError

Methods

toReport :: RpcError -> Report #

newtype ReportContext #

The provenance of a report, for use in logs.

Constructors

ReportContext 

Fields

reportContext :: ReportContext -> Text #

Render a ReportContext by interspersing it with dots, using global if it is empty.

prefixReportContext :: ReportContext -> Text #

Render a ReportContext by interspersing it with dots, followed by a colon, using global if it is empty.

reportContext' :: ReportContext -> Maybe Text #

Render a ReportContext by interspersing it with dots, returning Nothing if it is empty.

prefixReportContext' :: ReportContext -> Maybe Text #

Render a ReportContext by interspersing it with dots, followed by a colon, returning Nothing if it is empty.

basicReport :: forall (r :: EffectRow) a. (Member (Stop Report) r, HasCallStack) => Text -> [Text] -> Sem r a #

Stop with a LogReport.

userReport :: Reportable e => e -> Text #

Extract the user message from an instance of Reportable.

reportMessages :: Report -> Text #

Extract both user and log messages from an Report, for use in tests.

resumeHoistUserMessage :: forall err (eff :: (Type -> Type) -> Type -> Type) err' (r :: EffectRow). (Reportable err, Members '[eff !! err, Stop err'] r) => (Text -> err') -> InterpreterFor eff r #

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 :: EffectRow). (Reportable err, Member (Stop err') r) => (Text -> err') -> InterpreterFor (Stop err) r #

Map an error that's an instance of Reportable by passing its user message to a function.

logReport :: Reportable e => Member (DataLog LogReport) r => e -> Sem r () Source #

Convert a value to Report via Reportable and send it to the log.

data RpcError #

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

Instances

Instances details
IsString RpcError 
Instance details

Defined in Ribosome.Host.Data.RpcError

Generic RpcError 
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 
Instance details

Defined in Ribosome.Host.Data.RpcError

Eq RpcError 
Instance details

Defined in Ribosome.Host.Data.RpcError

MsgpackDecode RpcError 
Instance details

Defined in Ribosome.Host.Data.RpcError

MsgpackEncode RpcError 
Instance details

Defined in Ribosome.Host.Data.RpcError

Methods

toMsgpack :: RpcError -> Object #

Reportable RpcError 
Instance details

Defined in Ribosome.Host.Data.RpcError

Methods

toReport :: RpcError -> Report #

type Rep RpcError 
Instance details

Defined in Ribosome.Host.Data.RpcError

rpcError :: RpcError -> Text #

Extract an error message from an RpcError.

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

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

onRpcError :: forall (r :: EffectRow) a. Member (Rpc !! RpcError) r => (RpcError -> Sem r a) -> Sem (Rpc ': r) a -> Sem r a #

Run a Sem that uses Rpc and catch RpcErrors with the supplied function, interpreting Rpc to Rpc !! RpcError.

newtype BootError #

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 

Fields

data StoredReport #

Data type that attaches a time stamp to a Report.

Constructors

StoredReport !Report !Time 

Instances

Instances details
Show StoredReport 
Instance details

Defined in Ribosome.Host.Data.StoredReport

data Reports (a :: Type -> Type) b #

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

storedReports :: forall (r :: EffectRow). Member Reports r => Sem r (Map ReportContext [StoredReport]) #

Get all reports.

reportStop :: forall err r. Reportable err => Member (DataLog LogReport) r => Sem (Stop err ': r) () -> Sem r () Source #

Eliminate Stop err by converting err to a Report and logging it, continuing execution for a unit action.

resumeLogReport :: forall eff e r. Reportable e => Members [eff !! e, DataLog LogReport] r => Sem (eff ': r) () -> Sem r () Source #

Resume an effect by converting the error to a Report and logging it, continuing execution for a unit action.

data UserError (a :: Type -> Type) b #

The effect UserError decides which messages to display in Neovim.

Additionally, the text may be manipulated, which is done by the interpreter in Ribosome, which prefixes the message with the plugin name.

interpretUserErrorPrefixed :: Member (Reader PluginName) r => InterpreterFor UserError r Source #

Interpret UserError by prefixing messages with the plugin name.

Mutex State

data MState s (a :: Type -> Type) b #

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.

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

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

mmodify :: forall s (r :: EffectRow). Member (MState s) r => (s -> s) -> Sem r () #

Apply a pure function to the state.

mread :: forall s (r :: EffectRow). Member (MState s) r => Sem r s #

Obtain the current state.

mreads :: forall s (r :: EffectRow) a. Member (MState s) r => (s -> a) -> Sem r a #

Obtain the current state, transformed by a pure function.

mstate :: forall s (r :: EffectRow) a. Member (MState s) r => (s -> (s, a)) -> Sem r a #

Apply a pure function to the state that additionally returns a value.

mtrans :: forall s (r :: EffectRow). Member (MState s) r => (s -> Sem r s) -> Sem r () #

Run a monadic action on the state in a mutually exclusive fashion.

muse :: forall s (r :: EffectRow) a. Member (MState s) r => (s -> Sem r (s, a)) -> Sem r a #

Run a monadic action on the state in a mutually exclusive fashion that additionally returns a value.

stateToMState :: forall s (r :: EffectRow). Member (MState s) r => InterpreterFor (State s :: (Type -> Type) -> Type -> Type) r #

Interpret State in terms of MState.

withMState :: forall s (r :: EffectRow). Member (ScopedMState s) r => s -> InterpreterFor (MState s) r #

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

evalMState :: forall s (r :: [Effect]). s -> InterpreterFor (MState s) r #

Interpret MState as State.

interpretMState :: forall mres (r :: EffectRow) s. Members '[Resource, Race, Mask mres, Embed IO] r => s -> InterpreterFor (MState s) r #

Interpret MState using AtomicState and Lock.

interpretMStates :: forall s mres (r :: EffectRow). Members '[Mask mres, Resource, Race, Embed IO] r => InterpreterFor (ScopedMState s) r #

Interpret MState as a scoped effect.

Misc

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

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

noHandlers :: forall (r :: [Effect]). InterpreterFor (Handlers !! Report) r #

Interpret Handlers by performing no actions.

interpretHandlers :: forall (r :: EffectRow). Members '[Rpc !! RpcError, Log, Error BootError :: (Type -> Type) -> Type -> Type] r => [RpcHandler r] -> InterpreterFor (Handlers !! Report) r #

Interpret Handlers with a set of RpcHandlers.

data Register Source #

A Neovim register.

Instances

Instances details
IsString Register Source # 
Instance details

Defined in Ribosome.Data.Register

Generic Register Source # 
Instance details

Defined in Ribosome.Data.Register

Associated Types

type Rep Register :: Type -> Type #

Methods

from :: Register -> Rep Register x #

to :: Rep Register x -> Register #

Show Register Source # 
Instance details

Defined in Ribosome.Data.Register

Eq Register Source # 
Instance details

Defined in Ribosome.Data.Register

Pretty Register Source # 
Instance details

Defined in Ribosome.Data.Register

Methods

pretty :: Register -> Doc ann #

prettyList :: [Register] -> Doc ann #

MsgpackDecode Register Source # 
Instance details

Defined in Ribosome.Data.Register

MsgpackEncode Register Source # 
Instance details

Defined in Ribosome.Data.Register

Methods

toMsgpack :: Register -> Object #

type Rep Register Source # 
Instance details

Defined in Ribosome.Data.Register

type Rep Register = D1 ('MetaData "Register" "Ribosome.Data.Register" "ribosome-0.9.9.9-9qviHqnn5IlBIAvGWfH18d" 'False) ((C1 ('MetaCons "Named" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 Text)) :+: C1 ('MetaCons "Numbered" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 Text))) :+: (C1 ('MetaCons "Special" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 Text)) :+: C1 ('MetaCons "Empty" 'PrefixI 'False) (U1 :: Type -> Type)))

data RegisterType Source #

The type of a Neovim register, corresponding to concepts like line- or character-wise visual mode.

registerRepr :: Register -> Text Source #

Render a register name as is usual for Neovim.

pathText :: Path b t -> Text #

Render a Path as Text.

newtype CustomConfig c Source #

Disambiguation type used for the custom CLI configuration that is polymorphic in the stack.

Constructors

CustomConfig c 

Instances

Instances details
Show c => Show (CustomConfig c) Source # 
Instance details

Defined in Ribosome.Data.CustomConfig

Eq c => Eq (CustomConfig c) Source # 
Instance details

Defined in Ribosome.Data.CustomConfig

Reexports

type (!!) (eff :: (Type -> Type) -> Type -> Type) err = Resumable err eff #

Infix alias for Resumable.

Member (Stopper !! Boom) r =>

(<!) :: forall err (eff :: (Type -> Type) -> Type -> Type) (r :: EffectRow) a. Member (Resumable err eff) r => a -> Sem (eff ': r) a -> Sem r a #

Operator version of resumeAs.

Since: polysemy-resume-0.2.0.0

data Stop e (a :: Type -> Type) b #

An effect similar to Error without the ability to be caught. Used to signal that an error is supposed to be expected by dependent programs.

interpretStopper ::
  Member (Stop Boom) r =>
  InterpreterFor Stopper r
interpretStopper =
  interpret \case
    StopBang -> stop (Bang 13)
    StopBoom -> stop (Boom "ouch")

Instances

Instances details
MsgpackEncode a => HandlerCodec (Handler r a) r 
Instance details

Defined in Ribosome.Host.Handler.Codec

Methods

handlerCodec :: Handler r a -> RpcHandlerFun r #