module Ribosome.Host.Handler where
import qualified Data.Text as Text
import Ribosome.Host.Data.Execution (Execution (Sync))
import qualified Ribosome.Host.Data.RpcHandler as RpcHandler
import Ribosome.Host.Data.RpcHandler (Handler, RpcHandler (RpcHandler))
import Ribosome.Host.Data.RpcName (RpcName)
import qualified Ribosome.Host.Data.RpcType as RpcType
import Ribosome.Host.Data.RpcType (
AutocmdEvents,
AutocmdOptions,
CommandArgs (CommandArgs),
CommandCompletion (CompleteBuiltin, CompleteHandler),
CommandOptions (CommandOptions),
CompleteStyle (CompleteFiltered, CompleteUnfiltered),
completionName,
)
import Ribosome.Host.Handler.Codec (HandlerCodec (handlerCodec))
import Ribosome.Host.Handler.Command (CommandHandler (commandOptions), OptionStateZero)
rpcFunction ::
∀ r h .
HandlerCodec h r =>
RpcName ->
Execution ->
h ->
RpcHandler r
rpcFunction :: forall (r :: [(* -> *) -> * -> *]) h.
HandlerCodec h r =>
RpcName -> Execution -> h -> RpcHandler r
rpcFunction RpcName
name Execution
execution h
h =
RpcType -> RpcName -> Execution -> RpcHandlerFun r -> RpcHandler r
forall (r :: [(* -> *) -> * -> *]).
RpcType -> RpcName -> Execution -> RpcHandlerFun r -> RpcHandler r
RpcHandler RpcType
RpcType.Function RpcName
name Execution
execution (h -> RpcHandlerFun r
forall h (r :: [(* -> *) -> * -> *]).
HandlerCodec h r =>
h -> RpcHandlerFun r
handlerCodec h
h)
rpcCommand ::
∀ r h .
HandlerCodec h r =>
CommandHandler OptionStateZero h =>
RpcName ->
Execution ->
h ->
RpcHandler r
rpcCommand :: forall (r :: [(* -> *) -> * -> *]) h.
(HandlerCodec h r, CommandHandler OptionStateZero h) =>
RpcName -> Execution -> h -> RpcHandler r
rpcCommand RpcName
name Execution
execution h
h =
RpcType -> RpcName -> Execution -> RpcHandlerFun r -> RpcHandler r
forall (r :: [(* -> *) -> * -> *]).
RpcType -> RpcName -> Execution -> RpcHandlerFun r -> RpcHandler r
RpcHandler (CommandOptions -> CommandArgs -> RpcType
RpcType.Command (Map Text Object -> Maybe CommandCompletion -> CommandOptions
CommandOptions Map Text Object
opts Maybe CommandCompletion
forall a. Maybe a
Nothing) ([Text] -> CommandArgs
CommandArgs [Text]
args)) RpcName
name Execution
execution (h -> RpcHandlerFun r
forall h (r :: [(* -> *) -> * -> *]).
HandlerCodec h r =>
h -> RpcHandlerFun r
handlerCodec h
h)
where
(Map Text Object
opts, [Text]
args) =
forall (state :: OptionState) h.
CommandHandler state h =>
(Map Text Object, [Text])
commandOptions @OptionStateZero @h
complete ::
CommandCompletion ->
RpcHandler r ->
RpcHandler r
complete :: forall (r :: [(* -> *) -> * -> *]).
CommandCompletion -> RpcHandler r -> RpcHandler r
complete CommandCompletion
c = \case
RpcHandler (RpcType.Command (CommandOptions Map Text Object
opts Maybe CommandCompletion
_) CommandArgs
args) RpcName
n Execution
e RpcHandlerFun r
h ->
RpcType -> RpcName -> Execution -> RpcHandlerFun r -> RpcHandler r
forall (r :: [(* -> *) -> * -> *]).
RpcType -> RpcName -> Execution -> RpcHandlerFun r -> RpcHandler r
RpcHandler (CommandOptions -> CommandArgs -> RpcType
RpcType.Command (Map Text Object -> Maybe CommandCompletion -> CommandOptions
CommandOptions Map Text Object
opts (CommandCompletion -> Maybe CommandCompletion
forall a. a -> Maybe a
Just CommandCompletion
c)) CommandArgs
args) RpcName
n Execution
e RpcHandlerFun r
h
RpcHandler r
h ->
RpcHandler r
h
completeBuiltin ::
Text ->
RpcHandler r ->
RpcHandler r
completeBuiltin :: forall (r :: [(* -> *) -> * -> *]).
Text -> RpcHandler r -> RpcHandler r
completeBuiltin Text
f =
CommandCompletion -> RpcHandler r -> RpcHandler r
forall (r :: [(* -> *) -> * -> *]).
CommandCompletion -> RpcHandler r -> RpcHandler r
complete (Text -> CommandCompletion
CompleteBuiltin Text
f)
completeCustom ::
RpcName ->
(Text -> Text -> Int -> Handler r [Text]) ->
CompleteStyle ->
RpcHandler r
completeCustom :: forall (r :: [(* -> *) -> * -> *]).
RpcName
-> (Text -> Text -> Int -> Handler r [Text])
-> CompleteStyle
-> RpcHandler r
completeCustom RpcName
name Text -> Text -> Int -> Handler r [Text]
f = \case
CompleteStyle
CompleteFiltered ->
RpcName
-> Execution
-> (Text -> Text -> Int -> Handler r [Text])
-> RpcHandler r
forall (r :: [(* -> *) -> * -> *]) h.
HandlerCodec h r =>
RpcName -> Execution -> h -> RpcHandler r
rpcFunction RpcName
cn Execution
Sync Text -> Text -> Int -> Handler r [Text]
f
CompleteStyle
CompleteUnfiltered ->
RpcName
-> Execution
-> (Text -> Text -> Int -> Sem (Stop Report : r) Text)
-> RpcHandler r
forall (r :: [(* -> *) -> * -> *]) h.
HandlerCodec h r =>
RpcName -> Execution -> h -> RpcHandler r
rpcFunction RpcName
cn Execution
Sync \ Text
lead Text
line Int
pos -> [Text] -> Text
Text.unlines ([Text] -> Text) -> Handler r [Text] -> Sem (Stop Report : r) Text
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> Text -> Text -> Int -> Handler r [Text]
f Text
lead Text
line Int
pos
where
cn :: RpcName
cn =
RpcName -> RpcName
completionName RpcName
name
completeWith ::
CompleteStyle ->
(Text -> Text -> Int -> Handler r [Text]) ->
RpcHandler r ->
[RpcHandler r]
completeWith :: forall (r :: [(* -> *) -> * -> *]).
CompleteStyle
-> (Text -> Text -> Int -> Handler r [Text])
-> RpcHandler r
-> [RpcHandler r]
completeWith CompleteStyle
style Text -> Text -> Int -> Handler r [Text]
f main :: RpcHandler r
main@RpcHandler {RpcName
$sel:rpcName:RpcHandler :: forall (r :: [(* -> *) -> * -> *]). RpcHandler r -> RpcName
rpcName :: RpcName
rpcName} =
[
CommandCompletion -> RpcHandler r -> RpcHandler r
forall (r :: [(* -> *) -> * -> *]).
CommandCompletion -> RpcHandler r -> RpcHandler r
complete (CompleteStyle -> RpcName -> CommandCompletion
CompleteHandler CompleteStyle
style RpcName
rpcName) RpcHandler r
main,
RpcName
-> (Text -> Text -> Int -> Handler r [Text])
-> CompleteStyle
-> RpcHandler r
forall (r :: [(* -> *) -> * -> *]).
RpcName
-> (Text -> Text -> Int -> Handler r [Text])
-> CompleteStyle
-> RpcHandler r
completeCustom RpcName
rpcName Text -> Text -> Int -> Handler r [Text]
f CompleteStyle
style
]
rpcAutocmd ::
∀ r h .
HandlerCodec h r =>
RpcName ->
Execution ->
AutocmdEvents ->
AutocmdOptions ->
h ->
RpcHandler r
rpcAutocmd :: forall (r :: [(* -> *) -> * -> *]) h.
HandlerCodec h r =>
RpcName
-> Execution
-> AutocmdEvents
-> AutocmdOptions
-> h
-> RpcHandler r
rpcAutocmd RpcName
name Execution
execution AutocmdEvents
event AutocmdOptions
options h
h =
RpcType -> RpcName -> Execution -> RpcHandlerFun r -> RpcHandler r
forall (r :: [(* -> *) -> * -> *]).
RpcType -> RpcName -> Execution -> RpcHandlerFun r -> RpcHandler r
RpcHandler (AutocmdEvents -> AutocmdOptions -> RpcType
RpcType.Autocmd AutocmdEvents
event AutocmdOptions
options) RpcName
name Execution
execution (h -> RpcHandlerFun r
forall h (r :: [(* -> *) -> * -> *]).
HandlerCodec h r =>
h -> RpcHandlerFun r
handlerCodec h
h)
rpc ::
∀ r h .
HandlerCodec h r =>
CommandHandler OptionStateZero h =>
RpcName ->
Execution ->
h ->
[RpcHandler r]
rpc :: forall (r :: [(* -> *) -> * -> *]) h.
(HandlerCodec h r, CommandHandler OptionStateZero h) =>
RpcName -> Execution -> h -> [RpcHandler r]
rpc RpcName
name Execution
execution h
h =
[
RpcName -> Execution -> h -> RpcHandler r
forall (r :: [(* -> *) -> * -> *]) h.
HandlerCodec h r =>
RpcName -> Execution -> h -> RpcHandler r
rpcFunction RpcName
name Execution
execution h
h,
RpcName -> Execution -> h -> RpcHandler r
forall (r :: [(* -> *) -> * -> *]) h.
(HandlerCodec h r, CommandHandler OptionStateZero h) =>
RpcName -> Execution -> h -> RpcHandler r
rpcCommand RpcName
name Execution
execution h
h
]