| Safe Haskell | Safe-Inferred |
|---|---|
| Language | Haskell2010 |
Ribosome.Remote
Description
Main function combinators for remote plugins.
Synopsis
- type HandlerStack = PluginEffects ++ (RpcStack ++ RpcDeps)
- type RemoteStack c = HandlerStack ++ BasicPluginStack c
- interpretPluginRemote :: Members (BasicPluginStack c) r => InterpretersFor HandlerStack r
- remotePlugin :: forall c r. Members HandlerStack r => Members (BasicPluginStack c) r => Sem r ()
- runRemoteStackCli :: PluginConfig c -> Sem (RemoteStack c) () -> IO ()
- runRemoteStack :: PluginConfig () -> Sem (RemoteStack ()) () -> IO ()
- runNvimPluginCli :: HigherOrder r (RemoteStack c) => PluginConfig c -> InterpretersFor r (RemoteStack c) -> [RpcHandler (r ++ RemoteStack c)] -> IO ()
- runNvimPluginIO :: forall r. HigherOrder r (RemoteStack ()) => PluginConfig () -> InterpretersFor r (RemoteStack ()) -> [RpcHandler (r ++ RemoteStack ())] -> IO ()
- runNvimPluginIO_ :: PluginConfig () -> [RpcHandler (RemoteStack ())] -> IO ()
Documentation
type HandlerStack = PluginEffects ++ (RpcStack ++ RpcDeps) Source #
The stack of plugin internals.
type RemoteStack c = HandlerStack ++ BasicPluginStack c Source #
The complete stack of a Neovim plugin.
interpretPluginRemote :: Members (BasicPluginStack c) r => InterpretersFor HandlerStack r Source #
Run plugin internals without IO effects.
remotePlugin :: forall c r. Members HandlerStack r => Members (BasicPluginStack c) r => Sem r () Source #
Run the main loop for a remote plugin.
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.
runRemoteStack :: PluginConfig () -> Sem (RemoteStack ()) () -> IO () Source #
Run plugin internals and IO effects for a remote plugin, reading options from the CLI.
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 to the plugin.Reader c
This is separate from runNvimPluginIO because it requires a type hint when using OverloadedStrings or def to
construct the config without an option parser.
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:
PluginConfigis being constructed viaOverloadedStringsCustomStackhas 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.