module Ribosome.Remote where
import Ribosome.Data.PluginConfig (PluginConfig)
import Ribosome.Host.Data.RpcHandler (RpcHandler)
import Ribosome.Host.Interpret (HigherOrder)
import Ribosome.Host.Interpreter.Handlers (interpretHandlersNull, withHandlers)
import Ribosome.Host.Interpreter.Host (runHost)
import Ribosome.Host.Interpreter.Process.Stdio (interpretProcessCerealStdio)
import Ribosome.Host.Run (RpcDeps, RpcStack, interpretRpcStack)
import Ribosome.IOStack (BasicPluginStack, runCli)
import Ribosome.Interpreter.Scratch (interpretScratch)
import Ribosome.Interpreter.Settings (interpretSettingsRpc)
import Ribosome.Interpreter.UserError (interpretUserErrorPrefixed)
import Ribosome.Interpreter.VariableWatcher (interpretVariableWatcherNull)
import Ribosome.Plugin.Builtin (interceptHandlersBuiltin)
import Ribosome.Run (PluginEffects)
type HandlerStack =
PluginEffects ++ RpcStack ++ RpcDeps
type RemoteStack c =
HandlerStack ++ BasicPluginStack c
interpretPluginRemote ::
Members (BasicPluginStack c) r =>
InterpretersFor HandlerStack r
interpretPluginRemote :: forall c (r :: [(* -> *) -> * -> *]).
Members (BasicPluginStack c) r =>
InterpretersFor HandlerStack r
interpretPluginRemote =
Sem (UserError : r) a -> Sem r a
forall (r :: [(* -> *) -> * -> *]).
Member (Reader PluginName) r =>
InterpreterFor UserError r
interpretUserErrorPrefixed (Sem (UserError : r) a -> Sem r a)
-> (Sem
(Resumable RpcError Scratch
: Resumable SettingError Settings
: Resumable Report VariableWatcher : (Handlers !! Report) : Log
: DataLog LogReport : (Rpc !! RpcError)
: Resumable RpcError (Responses RequestId Response)
: Events (OutChan Event) Event
: PScoped () (EventChan Event) (Consume Event) : Reports
: Process RpcMessage (Either Text RpcMessage) : UserError : r)
a
-> Sem (UserError : r) a)
-> Sem
(Resumable RpcError Scratch
: Resumable SettingError Settings
: Resumable Report VariableWatcher : (Handlers !! Report) : Log
: DataLog LogReport : (Rpc !! RpcError)
: Resumable RpcError (Responses RequestId Response)
: Events (OutChan Event) Event
: PScoped () (EventChan Event) (Consume Event) : Reports
: Process RpcMessage (Either Text RpcMessage) : UserError : r)
a
-> Sem r a
forall b c a. (b -> c) -> (a -> b) -> a -> c
.
Sem (Process RpcMessage (Either Text RpcMessage) : UserError : r) a
-> Sem (UserError : r) a
forall a (r :: [(* -> *) -> * -> *]).
(Serialize a, Members IOStack r) =>
InterpreterFor (Process a (Either Text a)) r
interpretProcessCerealStdio (Sem
(Process RpcMessage (Either Text RpcMessage) : UserError : r) a
-> Sem (UserError : r) a)
-> (Sem
(Resumable RpcError Scratch
: Resumable SettingError Settings
: Resumable Report VariableWatcher : (Handlers !! Report) : Log
: DataLog LogReport : (Rpc !! RpcError)
: Resumable RpcError (Responses RequestId Response)
: Events (OutChan Event) Event
: PScoped () (EventChan Event) (Consume Event) : Reports
: Process RpcMessage (Either Text RpcMessage) : UserError : r)
a
-> Sem
(Process RpcMessage (Either Text RpcMessage) : UserError : r) a)
-> Sem
(Resumable RpcError Scratch
: Resumable SettingError Settings
: Resumable Report VariableWatcher : (Handlers !! Report) : Log
: DataLog LogReport : (Rpc !! RpcError)
: Resumable RpcError (Responses RequestId Response)
: Events (OutChan Event) Event
: PScoped () (EventChan Event) (Consume Event) : Reports
: Process RpcMessage (Either Text RpcMessage) : UserError : r)
a
-> Sem (UserError : r) a
forall b c a. (b -> c) -> (a -> b) -> a -> c
.
Sem
(Log
: DataLog LogReport : (Rpc !! RpcError)
: Resumable RpcError (Responses RequestId Response)
: Events (OutChan Event) Event
: PScoped () (EventChan Event) (Consume Event) : Reports
: Process RpcMessage (Either Text RpcMessage) : UserError : r)
a
-> Sem
(Process RpcMessage (Either Text RpcMessage) : UserError : r) a
forall (r :: [(* -> *) -> * -> *]).
(Members IOStack r, Members RpcDeps r,
Members '[Log, Reader LogConfig] r) =>
InterpretersFor RpcStack r
interpretRpcStack (Sem
(Log
: DataLog LogReport : (Rpc !! RpcError)
: Resumable RpcError (Responses RequestId Response)
: Events (OutChan Event) Event
: PScoped () (EventChan Event) (Consume Event) : Reports
: Process RpcMessage (Either Text RpcMessage) : UserError : r)
a
-> Sem
(Process RpcMessage (Either Text RpcMessage) : UserError : r) a)
-> (Sem
(Resumable RpcError Scratch
: Resumable SettingError Settings
: Resumable Report VariableWatcher : (Handlers !! Report) : Log
: DataLog LogReport : (Rpc !! RpcError)
: Resumable RpcError (Responses RequestId Response)
: Events (OutChan Event) Event
: PScoped () (EventChan Event) (Consume Event) : Reports
: Process RpcMessage (Either Text RpcMessage) : UserError : r)
a
-> Sem
(Log
: DataLog LogReport : (Rpc !! RpcError)
: Resumable RpcError (Responses RequestId Response)
: Events (OutChan Event) Event
: PScoped () (EventChan Event) (Consume Event) : Reports
: Process RpcMessage (Either Text RpcMessage) : UserError : r)
a)
-> Sem
(Resumable RpcError Scratch
: Resumable SettingError Settings
: Resumable Report VariableWatcher : (Handlers !! Report) : Log
: DataLog LogReport : (Rpc !! RpcError)
: Resumable RpcError (Responses RequestId Response)
: Events (OutChan Event) Event
: PScoped () (EventChan Event) (Consume Event) : Reports
: Process RpcMessage (Either Text RpcMessage) : UserError : r)
a
-> Sem
(Process RpcMessage (Either Text RpcMessage) : UserError : r) a
forall b c a. (b -> c) -> (a -> b) -> a -> c
.
Sem
((Handlers !! Report)
: Log : DataLog LogReport : (Rpc !! RpcError)
: Resumable RpcError (Responses RequestId Response)
: Events (OutChan Event) Event
: PScoped () (EventChan Event) (Consume Event) : Reports
: Process RpcMessage (Either Text RpcMessage) : UserError : r)
a
-> Sem
(Log
: DataLog LogReport : (Rpc !! RpcError)
: Resumable RpcError (Responses RequestId Response)
: Events (OutChan Event) Event
: PScoped () (EventChan Event) (Consume Event) : Reports
: Process RpcMessage (Either Text RpcMessage) : UserError : r)
a
forall (r :: [(* -> *) -> * -> *]).
InterpreterFor (Handlers !! Report) r
interpretHandlersNull (Sem
((Handlers !! Report)
: Log : DataLog LogReport : (Rpc !! RpcError)
: Resumable RpcError (Responses RequestId Response)
: Events (OutChan Event) Event
: PScoped () (EventChan Event) (Consume Event) : Reports
: Process RpcMessage (Either Text RpcMessage) : UserError : r)
a
-> Sem
(Log
: DataLog LogReport : (Rpc !! RpcError)
: Resumable RpcError (Responses RequestId Response)
: Events (OutChan Event) Event
: PScoped () (EventChan Event) (Consume Event) : Reports
: Process RpcMessage (Either Text RpcMessage) : UserError : r)
a)
-> (Sem
(Resumable RpcError Scratch
: Resumable SettingError Settings
: Resumable Report VariableWatcher : (Handlers !! Report) : Log
: DataLog LogReport : (Rpc !! RpcError)
: Resumable RpcError (Responses RequestId Response)
: Events (OutChan Event) Event
: PScoped () (EventChan Event) (Consume Event) : Reports
: Process RpcMessage (Either Text RpcMessage) : UserError : r)
a
-> Sem
((Handlers !! Report)
: Log : DataLog LogReport : (Rpc !! RpcError)
: Resumable RpcError (Responses RequestId Response)
: Events (OutChan Event) Event
: PScoped () (EventChan Event) (Consume Event) : Reports
: Process RpcMessage (Either Text RpcMessage) : UserError : r)
a)
-> Sem
(Resumable RpcError Scratch
: Resumable SettingError Settings
: Resumable Report VariableWatcher : (Handlers !! Report) : Log
: DataLog LogReport : (Rpc !! RpcError)
: Resumable RpcError (Responses RequestId Response)
: Events (OutChan Event) Event
: PScoped () (EventChan Event) (Consume Event) : Reports
: Process RpcMessage (Either Text RpcMessage) : UserError : r)
a
-> Sem
(Log
: DataLog LogReport : (Rpc !! RpcError)
: Resumable RpcError (Responses RequestId Response)
: Events (OutChan Event) Event
: PScoped () (EventChan Event) (Consume Event) : Reports
: Process RpcMessage (Either Text RpcMessage) : UserError : r)
a
forall b c a. (b -> c) -> (a -> b) -> a -> c
.
Sem
(Resumable Report VariableWatcher
: (Handlers !! Report) : Log : DataLog LogReport
: (Rpc !! RpcError)
: Resumable RpcError (Responses RequestId Response)
: Events (OutChan Event) Event
: PScoped () (EventChan Event) (Consume Event) : Reports
: Process RpcMessage (Either Text RpcMessage) : UserError : r)
a
-> Sem
((Handlers !! Report)
: Log : DataLog LogReport : (Rpc !! RpcError)
: Resumable RpcError (Responses RequestId Response)
: Events (OutChan Event) Event
: PScoped () (EventChan Event) (Consume Event) : Reports
: Process RpcMessage (Either Text RpcMessage) : UserError : r)
a
forall (r :: [(* -> *) -> * -> *]).
InterpreterFor (Resumable Report VariableWatcher) r
interpretVariableWatcherNull (Sem
(Resumable Report VariableWatcher
: (Handlers !! Report) : Log : DataLog LogReport
: (Rpc !! RpcError)
: Resumable RpcError (Responses RequestId Response)
: Events (OutChan Event) Event
: PScoped () (EventChan Event) (Consume Event) : Reports
: Process RpcMessage (Either Text RpcMessage) : UserError : r)
a
-> Sem
((Handlers !! Report)
: Log : DataLog LogReport : (Rpc !! RpcError)
: Resumable RpcError (Responses RequestId Response)
: Events (OutChan Event) Event
: PScoped () (EventChan Event) (Consume Event) : Reports
: Process RpcMessage (Either Text RpcMessage) : UserError : r)
a)
-> (Sem
(Resumable RpcError Scratch
: Resumable SettingError Settings
: Resumable Report VariableWatcher : (Handlers !! Report) : Log
: DataLog LogReport : (Rpc !! RpcError)
: Resumable RpcError (Responses RequestId Response)
: Events (OutChan Event) Event
: PScoped () (EventChan Event) (Consume Event) : Reports
: Process RpcMessage (Either Text RpcMessage) : UserError : r)
a
-> Sem
(Resumable Report VariableWatcher
: (Handlers !! Report) : Log : DataLog LogReport
: (Rpc !! RpcError)
: Resumable RpcError (Responses RequestId Response)
: Events (OutChan Event) Event
: PScoped () (EventChan Event) (Consume Event) : Reports
: Process RpcMessage (Either Text RpcMessage) : UserError : r)
a)
-> Sem
(Resumable RpcError Scratch
: Resumable SettingError Settings
: Resumable Report VariableWatcher : (Handlers !! Report) : Log
: DataLog LogReport : (Rpc !! RpcError)
: Resumable RpcError (Responses RequestId Response)
: Events (OutChan Event) Event
: PScoped () (EventChan Event) (Consume Event) : Reports
: Process RpcMessage (Either Text RpcMessage) : UserError : r)
a
-> Sem
((Handlers !! Report)
: Log : DataLog LogReport : (Rpc !! RpcError)
: Resumable RpcError (Responses RequestId Response)
: Events (OutChan Event) Event
: PScoped () (EventChan Event) (Consume Event) : Reports
: Process RpcMessage (Either Text RpcMessage) : UserError : r)
a
forall b c a. (b -> c) -> (a -> b) -> a -> c
.
Sem
(Resumable SettingError Settings
: Resumable Report VariableWatcher : (Handlers !! Report) : Log
: DataLog LogReport : (Rpc !! RpcError)
: Resumable RpcError (Responses RequestId Response)
: Events (OutChan Event) Event
: PScoped () (EventChan Event) (Consume Event) : Reports
: Process RpcMessage (Either Text RpcMessage) : UserError : r)
a
-> Sem
(Resumable Report VariableWatcher
: (Handlers !! Report) : Log : DataLog LogReport
: (Rpc !! RpcError)
: Resumable RpcError (Responses RequestId Response)
: Events (OutChan Event) Event
: PScoped () (EventChan Event) (Consume Event) : Reports
: Process RpcMessage (Either Text RpcMessage) : UserError : r)
a
forall (r :: [(* -> *) -> * -> *]).
Members '[Rpc !! RpcError, Reader PluginName] r =>
InterpreterFor (Resumable SettingError Settings) r
interpretSettingsRpc (Sem
(Resumable SettingError Settings
: Resumable Report VariableWatcher : (Handlers !! Report) : Log
: DataLog LogReport : (Rpc !! RpcError)
: Resumable RpcError (Responses RequestId Response)
: Events (OutChan Event) Event
: PScoped () (EventChan Event) (Consume Event) : Reports
: Process RpcMessage (Either Text RpcMessage) : UserError : r)
a
-> Sem
(Resumable Report VariableWatcher
: (Handlers !! Report) : Log : DataLog LogReport
: (Rpc !! RpcError)
: Resumable RpcError (Responses RequestId Response)
: Events (OutChan Event) Event
: PScoped () (EventChan Event) (Consume Event) : Reports
: Process RpcMessage (Either Text RpcMessage) : UserError : r)
a)
-> (Sem
(Resumable RpcError Scratch
: Resumable SettingError Settings
: Resumable Report VariableWatcher : (Handlers !! Report) : Log
: DataLog LogReport : (Rpc !! RpcError)
: Resumable RpcError (Responses RequestId Response)
: Events (OutChan Event) Event
: PScoped () (EventChan Event) (Consume Event) : Reports
: Process RpcMessage (Either Text RpcMessage) : UserError : r)
a
-> Sem
(Resumable SettingError Settings
: Resumable Report VariableWatcher : (Handlers !! Report) : Log
: DataLog LogReport : (Rpc !! RpcError)
: Resumable RpcError (Responses RequestId Response)
: Events (OutChan Event) Event
: PScoped () (EventChan Event) (Consume Event) : Reports
: Process RpcMessage (Either Text RpcMessage) : UserError : r)
a)
-> Sem
(Resumable RpcError Scratch
: Resumable SettingError Settings
: Resumable Report VariableWatcher : (Handlers !! Report) : Log
: DataLog LogReport : (Rpc !! RpcError)
: Resumable RpcError (Responses RequestId Response)
: Events (OutChan Event) Event
: PScoped () (EventChan Event) (Consume Event) : Reports
: Process RpcMessage (Either Text RpcMessage) : UserError : r)
a
-> Sem
(Resumable Report VariableWatcher
: (Handlers !! Report) : Log : DataLog LogReport
: (Rpc !! RpcError)
: Resumable RpcError (Responses RequestId Response)
: Events (OutChan Event) Event
: PScoped () (EventChan Event) (Consume Event) : Reports
: Process RpcMessage (Either Text RpcMessage) : UserError : r)
a
forall b c a. (b -> c) -> (a -> b) -> a -> c
.
Sem
(Resumable RpcError Scratch
: Resumable SettingError Settings
: Resumable Report VariableWatcher : (Handlers !! Report) : Log
: DataLog LogReport : (Rpc !! RpcError)
: Resumable RpcError (Responses RequestId Response)
: Events (OutChan Event) Event
: PScoped () (EventChan Event) (Consume Event) : Reports
: Process RpcMessage (Either Text RpcMessage) : UserError : r)
a
-> Sem
(Resumable SettingError Settings
: Resumable Report VariableWatcher : (Handlers !! Report) : Log
: DataLog LogReport : (Rpc !! RpcError)
: Resumable RpcError (Responses RequestId Response)
: Events (OutChan Event) Event
: PScoped () (EventChan Event) (Consume Event) : Reports
: Process RpcMessage (Either Text RpcMessage) : UserError : r)
a
forall (r :: [(* -> *) -> * -> *]).
Members
'[Rpc !! RpcError, Reader PluginName, Log, Resource, Embed IO] r =>
InterpreterFor (Resumable RpcError Scratch) r
interpretScratch
remotePlugin ::
∀ c r .
Members HandlerStack r =>
Members (BasicPluginStack c) r =>
Sem r ()
remotePlugin :: forall c (r :: [(* -> *) -> * -> *]).
(Members HandlerStack r, Members (BasicPluginStack c) r) =>
Sem r ()
remotePlugin =
Sem r () -> Sem r ()
forall (r :: [(* -> *) -> * -> *]) a.
Members BuiltinHandlersDeps r =>
Sem r a -> Sem r a
interceptHandlersBuiltin Sem r ()
forall er (r :: [(* -> *) -> * -> *]).
Members (HostDeps er) r =>
Sem r ()
runHost
runRemoteStackCli ::
PluginConfig c ->
Sem (RemoteStack c) () ->
IO ()
runRemoteStackCli :: forall c. PluginConfig c -> Sem (RemoteStack c) () -> IO ()
runRemoteStackCli PluginConfig c
conf =
PluginConfig c -> Sem (BasicPluginStack c) () -> IO ()
forall c. PluginConfig c -> Sem (BasicPluginStack c) () -> IO ()
runCli PluginConfig c
conf (Sem
'[Reader PluginName, Reader (CustomConfig c), Log,
Tagged "stderr" Log, Tagged "file" Log, Reader LogConfig,
Reader HostConfig, Time Time Date, Error BootError,
UninterruptibleMaskIO, UninterruptibleMaskIO, GatesIO, Race, Async,
Resource, Embed IO, Final IO]
()
-> IO ())
-> (Sem
'[Resumable RpcError Scratch, Resumable SettingError Settings,
Resumable Report VariableWatcher, Handlers !! Report, Log,
DataLog LogReport, Rpc !! RpcError,
Resumable RpcError (Responses RequestId Response),
Events (OutChan Event) Event,
PScoped () (EventChan Event) (Consume Event), Reports,
Process RpcMessage (Either Text RpcMessage), UserError,
Reader PluginName, Reader (CustomConfig c), Log,
Tagged "stderr" Log, Tagged "file" Log, Reader LogConfig,
Reader HostConfig, Time Time Date, Error BootError,
UninterruptibleMaskIO, UninterruptibleMaskIO, GatesIO, Race, Async,
Resource, Embed IO, Final IO]
()
-> Sem
'[Reader PluginName, Reader (CustomConfig c), Log,
Tagged "stderr" Log, Tagged "file" Log, Reader LogConfig,
Reader HostConfig, Time Time Date, Error BootError,
UninterruptibleMaskIO, UninterruptibleMaskIO, GatesIO, Race, Async,
Resource, Embed IO, Final IO]
())
-> Sem
'[Resumable RpcError Scratch, Resumable SettingError Settings,
Resumable Report VariableWatcher, Handlers !! Report, Log,
DataLog LogReport, Rpc !! RpcError,
Resumable RpcError (Responses RequestId Response),
Events (OutChan Event) Event,
PScoped () (EventChan Event) (Consume Event), Reports,
Process RpcMessage (Either Text RpcMessage), UserError,
Reader PluginName, Reader (CustomConfig c), Log,
Tagged "stderr" Log, Tagged "file" Log, Reader LogConfig,
Reader HostConfig, Time Time Date, Error BootError,
UninterruptibleMaskIO, UninterruptibleMaskIO, GatesIO, Race, Async,
Resource, Embed IO, Final IO]
()
-> IO ()
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Sem
'[Resumable RpcError Scratch, Resumable SettingError Settings,
Resumable Report VariableWatcher, Handlers !! Report, Log,
DataLog LogReport, Rpc !! RpcError,
Resumable RpcError (Responses RequestId Response),
Events (OutChan Event) Event,
PScoped () (EventChan Event) (Consume Event), Reports,
Process RpcMessage (Either Text RpcMessage), UserError,
Reader PluginName, Reader (CustomConfig c), Log,
Tagged "stderr" Log, Tagged "file" Log, Reader LogConfig,
Reader HostConfig, Time Time Date, Error BootError,
UninterruptibleMaskIO, UninterruptibleMaskIO, GatesIO, Race, Async,
Resource, Embed IO, Final IO]
()
-> Sem
'[Reader PluginName, Reader (CustomConfig c), Log,
Tagged "stderr" Log, Tagged "file" Log, Reader LogConfig,
Reader HostConfig, Time Time Date, Error BootError,
UninterruptibleMaskIO, UninterruptibleMaskIO, GatesIO, Race, Async,
Resource, Embed IO, Final IO]
()
forall c (r :: [(* -> *) -> * -> *]).
Members (BasicPluginStack c) r =>
InterpretersFor HandlerStack r
interpretPluginRemote
runRemoteStack ::
PluginConfig () ->
Sem (RemoteStack ()) () ->
IO ()
runRemoteStack :: PluginConfig () -> Sem (RemoteStack ()) () -> IO ()
runRemoteStack PluginConfig ()
conf =
PluginConfig () -> Sem (BasicPluginStack ()) () -> IO ()
forall c. PluginConfig c -> Sem (BasicPluginStack c) () -> IO ()
runCli PluginConfig ()
conf (Sem
'[Reader PluginName, Reader (CustomConfig ()), Log,
Tagged "stderr" Log, Tagged "file" Log, Reader LogConfig,
Reader HostConfig, Time Time Date, Error BootError,
UninterruptibleMaskIO, UninterruptibleMaskIO, GatesIO, Race, Async,
Resource, Embed IO, Final IO]
()
-> IO ())
-> (Sem
'[Resumable RpcError Scratch, Resumable SettingError Settings,
Resumable Report VariableWatcher, Handlers !! Report, Log,
DataLog LogReport, Rpc !! RpcError,
Resumable RpcError (Responses RequestId Response),
Events (OutChan Event) Event,
PScoped () (EventChan Event) (Consume Event), Reports,
Process RpcMessage (Either Text RpcMessage), UserError,
Reader PluginName, Reader (CustomConfig ()), Log,
Tagged "stderr" Log, Tagged "file" Log, Reader LogConfig,
Reader HostConfig, Time Time Date, Error BootError,
UninterruptibleMaskIO, UninterruptibleMaskIO, GatesIO, Race, Async,
Resource, Embed IO, Final IO]
()
-> Sem
'[Reader PluginName, Reader (CustomConfig ()), Log,
Tagged "stderr" Log, Tagged "file" Log, Reader LogConfig,
Reader HostConfig, Time Time Date, Error BootError,
UninterruptibleMaskIO, UninterruptibleMaskIO, GatesIO, Race, Async,
Resource, Embed IO, Final IO]
())
-> Sem
'[Resumable RpcError Scratch, Resumable SettingError Settings,
Resumable Report VariableWatcher, Handlers !! Report, Log,
DataLog LogReport, Rpc !! RpcError,
Resumable RpcError (Responses RequestId Response),
Events (OutChan Event) Event,
PScoped () (EventChan Event) (Consume Event), Reports,
Process RpcMessage (Either Text RpcMessage), UserError,
Reader PluginName, Reader (CustomConfig ()), Log,
Tagged "stderr" Log, Tagged "file" Log, Reader LogConfig,
Reader HostConfig, Time Time Date, Error BootError,
UninterruptibleMaskIO, UninterruptibleMaskIO, GatesIO, Race, Async,
Resource, Embed IO, Final IO]
()
-> IO ()
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Sem
'[Resumable RpcError Scratch, Resumable SettingError Settings,
Resumable Report VariableWatcher, Handlers !! Report, Log,
DataLog LogReport, Rpc !! RpcError,
Resumable RpcError (Responses RequestId Response),
Events (OutChan Event) Event,
PScoped () (EventChan Event) (Consume Event), Reports,
Process RpcMessage (Either Text RpcMessage), UserError,
Reader PluginName, Reader (CustomConfig ()), Log,
Tagged "stderr" Log, Tagged "file" Log, Reader LogConfig,
Reader HostConfig, Time Time Date, Error BootError,
UninterruptibleMaskIO, UninterruptibleMaskIO, GatesIO, Race, Async,
Resource, Embed IO, Final IO]
()
-> Sem
'[Reader PluginName, Reader (CustomConfig ()), Log,
Tagged "stderr" Log, Tagged "file" Log, Reader LogConfig,
Reader HostConfig, Time Time Date, Error BootError,
UninterruptibleMaskIO, UninterruptibleMaskIO, GatesIO, Race, Async,
Resource, Embed IO, Final IO]
()
forall c (r :: [(* -> *) -> * -> *]).
Members (BasicPluginStack c) r =>
InterpretersFor HandlerStack r
interpretPluginRemote
runNvimPluginCli ::
HigherOrder r (RemoteStack c) =>
PluginConfig c ->
InterpretersFor r (RemoteStack c) ->
[RpcHandler (r ++ RemoteStack c)] ->
IO ()
runNvimPluginCli :: forall (r :: [(* -> *) -> * -> *]) c.
HigherOrder r (RemoteStack c) =>
PluginConfig c
-> InterpretersFor r (RemoteStack c)
-> [RpcHandler (r ++ RemoteStack c)]
-> IO ()
runNvimPluginCli PluginConfig c
conf InterpretersFor r (RemoteStack c)
effs [RpcHandler (r ++ RemoteStack c)]
handlers =
PluginConfig c -> Sem (RemoteStack c) () -> IO ()
forall c. PluginConfig c -> Sem (RemoteStack c) () -> IO ()
runRemoteStackCli PluginConfig c
conf (Sem (r ++ RemoteStack c) () -> Sem (RemoteStack c) ()
InterpretersFor r (RemoteStack c)
effs ([RpcHandler
(Append
r
'[Resumable RpcError Scratch, Resumable SettingError Settings,
Resumable Report VariableWatcher, Handlers !! Report, Log,
DataLog LogReport, Rpc !! RpcError,
Resumable RpcError (Responses RequestId Response),
Events (OutChan Event) Event,
PScoped () (EventChan Event) (Consume Event), Reports,
Process RpcMessage (Either Text RpcMessage), UserError,
Reader PluginName, Reader (CustomConfig c), Log,
Tagged "stderr" Log, Tagged "file" Log, Reader LogConfig,
Reader HostConfig, Time Time Date, Error BootError,
UninterruptibleMaskIO, UninterruptibleMaskIO, GatesIO, Race, Async,
Resource, Embed IO, Final IO])]
-> Sem
(Append
r
'[Resumable RpcError Scratch, Resumable SettingError Settings,
Resumable Report VariableWatcher, Handlers !! Report, Log,
DataLog LogReport, Rpc !! RpcError,
Resumable RpcError (Responses RequestId Response),
Events (OutChan Event) Event,
PScoped () (EventChan Event) (Consume Event), Reports,
Process RpcMessage (Either Text RpcMessage), UserError,
Reader PluginName, Reader (CustomConfig c), Log,
Tagged "stderr" Log, Tagged "file" Log, Reader LogConfig,
Reader HostConfig, Time Time Date, Error BootError,
UninterruptibleMaskIO, UninterruptibleMaskIO, GatesIO, Race, Async,
Resource, Embed IO, Final IO])
()
-> Sem
(Append
r
'[Resumable RpcError Scratch, Resumable SettingError Settings,
Resumable Report VariableWatcher, Handlers !! Report, Log,
DataLog LogReport, Rpc !! RpcError,
Resumable RpcError (Responses RequestId Response),
Events (OutChan Event) Event,
PScoped () (EventChan Event) (Consume Event), Reports,
Process RpcMessage (Either Text RpcMessage), UserError,
Reader PluginName, Reader (CustomConfig c), Log,
Tagged "stderr" Log, Tagged "file" Log, Reader LogConfig,
Reader HostConfig, Time Time Date, Error BootError,
UninterruptibleMaskIO, UninterruptibleMaskIO, GatesIO, Race, Async,
Resource, Embed IO, Final IO])
()
forall (r :: [(* -> *) -> * -> *]) a.
Members
'[Handlers !! Report, Rpc !! RpcError, Log, Error BootError] r =>
[RpcHandler r] -> Sem r a -> Sem r a
withHandlers [RpcHandler
(Append
r
'[Resumable RpcError Scratch, Resumable SettingError Settings,
Resumable Report VariableWatcher, Handlers !! Report, Log,
DataLog LogReport, Rpc !! RpcError,
Resumable RpcError (Responses RequestId Response),
Events (OutChan Event) Event,
PScoped () (EventChan Event) (Consume Event), Reports,
Process RpcMessage (Either Text RpcMessage), UserError,
Reader PluginName, Reader (CustomConfig c), Log,
Tagged "stderr" Log, Tagged "file" Log, Reader LogConfig,
Reader HostConfig, Time Time Date, Error BootError,
UninterruptibleMaskIO, UninterruptibleMaskIO, GatesIO, Race, Async,
Resource, Embed IO, Final IO])]
[RpcHandler (r ++ RemoteStack c)]
handlers Sem
(Append
r
'[Resumable RpcError Scratch, Resumable SettingError Settings,
Resumable Report VariableWatcher, Handlers !! Report, Log,
DataLog LogReport, Rpc !! RpcError,
Resumable RpcError (Responses RequestId Response),
Events (OutChan Event) Event,
PScoped () (EventChan Event) (Consume Event), Reports,
Process RpcMessage (Either Text RpcMessage), UserError,
Reader PluginName, Reader (CustomConfig c), Log,
Tagged "stderr" Log, Tagged "file" Log, Reader LogConfig,
Reader HostConfig, Time Time Date, Error BootError,
UninterruptibleMaskIO, UninterruptibleMaskIO, GatesIO, Race, Async,
Resource, Embed IO, Final IO])
()
forall c (r :: [(* -> *) -> * -> *]).
(Members HandlerStack r, Members (BasicPluginStack c) r) =>
Sem r ()
remotePlugin))
runNvimPluginIO ::
∀ r .
HigherOrder r (RemoteStack ()) =>
PluginConfig () ->
InterpretersFor r (RemoteStack ()) ->
[RpcHandler (r ++ RemoteStack ())] ->
IO ()
runNvimPluginIO :: forall (r :: [(* -> *) -> * -> *]).
HigherOrder r (RemoteStack ()) =>
PluginConfig ()
-> InterpretersFor r (RemoteStack ())
-> [RpcHandler (r ++ RemoteStack ())]
-> IO ()
runNvimPluginIO PluginConfig ()
conf InterpretersFor r (RemoteStack ())
effs [RpcHandler (r ++ RemoteStack ())]
handlers =
PluginConfig () -> Sem (RemoteStack ()) () -> IO ()
runRemoteStack PluginConfig ()
conf (Sem (r ++ RemoteStack ()) () -> Sem (RemoteStack ()) ()
InterpretersFor r (RemoteStack ())
effs ([RpcHandler
(Append
r
'[Resumable RpcError Scratch, Resumable SettingError Settings,
Resumable Report VariableWatcher, Handlers !! Report, Log,
DataLog LogReport, Rpc !! RpcError,
Resumable RpcError (Responses RequestId Response),
Events (OutChan Event) Event,
PScoped () (EventChan Event) (Consume Event), Reports,
Process RpcMessage (Either Text RpcMessage), UserError,
Reader PluginName, Reader (CustomConfig ()), Log,
Tagged "stderr" Log, Tagged "file" Log, Reader LogConfig,
Reader HostConfig, Time Time Date, Error BootError,
UninterruptibleMaskIO, UninterruptibleMaskIO, GatesIO, Race, Async,
Resource, Embed IO, Final IO])]
-> Sem
(Append
r
'[Resumable RpcError Scratch, Resumable SettingError Settings,
Resumable Report VariableWatcher, Handlers !! Report, Log,
DataLog LogReport, Rpc !! RpcError,
Resumable RpcError (Responses RequestId Response),
Events (OutChan Event) Event,
PScoped () (EventChan Event) (Consume Event), Reports,
Process RpcMessage (Either Text RpcMessage), UserError,
Reader PluginName, Reader (CustomConfig ()), Log,
Tagged "stderr" Log, Tagged "file" Log, Reader LogConfig,
Reader HostConfig, Time Time Date, Error BootError,
UninterruptibleMaskIO, UninterruptibleMaskIO, GatesIO, Race, Async,
Resource, Embed IO, Final IO])
()
-> Sem
(Append
r
'[Resumable RpcError Scratch, Resumable SettingError Settings,
Resumable Report VariableWatcher, Handlers !! Report, Log,
DataLog LogReport, Rpc !! RpcError,
Resumable RpcError (Responses RequestId Response),
Events (OutChan Event) Event,
PScoped () (EventChan Event) (Consume Event), Reports,
Process RpcMessage (Either Text RpcMessage), UserError,
Reader PluginName, Reader (CustomConfig ()), Log,
Tagged "stderr" Log, Tagged "file" Log, Reader LogConfig,
Reader HostConfig, Time Time Date, Error BootError,
UninterruptibleMaskIO, UninterruptibleMaskIO, GatesIO, Race, Async,
Resource, Embed IO, Final IO])
()
forall (r :: [(* -> *) -> * -> *]) a.
Members
'[Handlers !! Report, Rpc !! RpcError, Log, Error BootError] r =>
[RpcHandler r] -> Sem r a -> Sem r a
withHandlers [RpcHandler
(Append
r
'[Resumable RpcError Scratch, Resumable SettingError Settings,
Resumable Report VariableWatcher, Handlers !! Report, Log,
DataLog LogReport, Rpc !! RpcError,
Resumable RpcError (Responses RequestId Response),
Events (OutChan Event) Event,
PScoped () (EventChan Event) (Consume Event), Reports,
Process RpcMessage (Either Text RpcMessage), UserError,
Reader PluginName, Reader (CustomConfig ()), Log,
Tagged "stderr" Log, Tagged "file" Log, Reader LogConfig,
Reader HostConfig, Time Time Date, Error BootError,
UninterruptibleMaskIO, UninterruptibleMaskIO, GatesIO, Race, Async,
Resource, Embed IO, Final IO])]
[RpcHandler (r ++ RemoteStack ())]
handlers Sem
(Append
r
'[Resumable RpcError Scratch, Resumable SettingError Settings,
Resumable Report VariableWatcher, Handlers !! Report, Log,
DataLog LogReport, Rpc !! RpcError,
Resumable RpcError (Responses RequestId Response),
Events (OutChan Event) Event,
PScoped () (EventChan Event) (Consume Event), Reports,
Process RpcMessage (Either Text RpcMessage), UserError,
Reader PluginName, Reader (CustomConfig ()), Log,
Tagged "stderr" Log, Tagged "file" Log, Reader LogConfig,
Reader HostConfig, Time Time Date, Error BootError,
UninterruptibleMaskIO, UninterruptibleMaskIO, GatesIO, Race, Async,
Resource, Embed IO, Final IO])
()
forall c (r :: [(* -> *) -> * -> *]).
(Members HandlerStack r, Members (BasicPluginStack c) r) =>
Sem r ()
remotePlugin))
runNvimPluginIO_ ::
PluginConfig () ->
[RpcHandler (RemoteStack ())] ->
IO ()
runNvimPluginIO_ :: PluginConfig () -> [RpcHandler (RemoteStack ())] -> IO ()
runNvimPluginIO_ PluginConfig ()
conf [RpcHandler (RemoteStack ())]
handlers =
PluginConfig () -> Sem (RemoteStack ()) () -> IO ()
runRemoteStack PluginConfig ()
conf ([RpcHandler
'[Resumable RpcError Scratch, Resumable SettingError Settings,
Resumable Report VariableWatcher, Handlers !! Report, Log,
DataLog LogReport, Rpc !! RpcError,
Resumable RpcError (Responses RequestId Response),
Events (OutChan Event) Event,
PScoped () (EventChan Event) (Consume Event), Reports,
Process RpcMessage (Either Text RpcMessage), UserError,
Reader PluginName, Reader (CustomConfig ()), Log,
Tagged "stderr" Log, Tagged "file" Log, Reader LogConfig,
Reader HostConfig, Time Time Date, Error BootError,
UninterruptibleMaskIO, UninterruptibleMaskIO, GatesIO, Race, Async,
Resource, Embed IO, Final IO]]
-> Sem
'[Resumable RpcError Scratch, Resumable SettingError Settings,
Resumable Report VariableWatcher, Handlers !! Report, Log,
DataLog LogReport, Rpc !! RpcError,
Resumable RpcError (Responses RequestId Response),
Events (OutChan Event) Event,
PScoped () (EventChan Event) (Consume Event), Reports,
Process RpcMessage (Either Text RpcMessage), UserError,
Reader PluginName, Reader (CustomConfig ()), Log,
Tagged "stderr" Log, Tagged "file" Log, Reader LogConfig,
Reader HostConfig, Time Time Date, Error BootError,
UninterruptibleMaskIO, UninterruptibleMaskIO, GatesIO, Race, Async,
Resource, Embed IO, Final IO]
()
-> Sem
'[Resumable RpcError Scratch, Resumable SettingError Settings,
Resumable Report VariableWatcher, Handlers !! Report, Log,
DataLog LogReport, Rpc !! RpcError,
Resumable RpcError (Responses RequestId Response),
Events (OutChan Event) Event,
PScoped () (EventChan Event) (Consume Event), Reports,
Process RpcMessage (Either Text RpcMessage), UserError,
Reader PluginName, Reader (CustomConfig ()), Log,
Tagged "stderr" Log, Tagged "file" Log, Reader LogConfig,
Reader HostConfig, Time Time Date, Error BootError,
UninterruptibleMaskIO, UninterruptibleMaskIO, GatesIO, Race, Async,
Resource, Embed IO, Final IO]
()
forall (r :: [(* -> *) -> * -> *]) a.
Members
'[Handlers !! Report, Rpc !! RpcError, Log, Error BootError] r =>
[RpcHandler r] -> Sem r a -> Sem r a
withHandlers [RpcHandler
'[Resumable RpcError Scratch, Resumable SettingError Settings,
Resumable Report VariableWatcher, Handlers !! Report, Log,
DataLog LogReport, Rpc !! RpcError,
Resumable RpcError (Responses RequestId Response),
Events (OutChan Event) Event,
PScoped () (EventChan Event) (Consume Event), Reports,
Process RpcMessage (Either Text RpcMessage), UserError,
Reader PluginName, Reader (CustomConfig ()), Log,
Tagged "stderr" Log, Tagged "file" Log, Reader LogConfig,
Reader HostConfig, Time Time Date, Error BootError,
UninterruptibleMaskIO, UninterruptibleMaskIO, GatesIO, Race, Async,
Resource, Embed IO, Final IO]]
[RpcHandler (RemoteStack ())]
handlers Sem
'[Resumable RpcError Scratch, Resumable SettingError Settings,
Resumable Report VariableWatcher, Handlers !! Report, Log,
DataLog LogReport, Rpc !! RpcError,
Resumable RpcError (Responses RequestId Response),
Events (OutChan Event) Event,
PScoped () (EventChan Event) (Consume Event), Reports,
Process RpcMessage (Either Text RpcMessage), UserError,
Reader PluginName, Reader (CustomConfig ()), Log,
Tagged "stderr" Log, Tagged "file" Log, Reader LogConfig,
Reader HostConfig, Time Time Date, Error BootError,
UninterruptibleMaskIO, UninterruptibleMaskIO, GatesIO, Race, Async,
Resource, Embed IO, Final IO]
()
forall c (r :: [(* -> *) -> * -> *]).
(Members HandlerStack r, Members (BasicPluginStack c) r) =>
Sem r ()
remotePlugin)