-- |Combinators for creating and manipulating RPC handlers.
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)

-- |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 'Ribosome.MsgpackDecode' (or more
-- specifically, 'Ribosome.Host.Handler.Codec.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' 'Ribosome.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
rpcFunction ::
   r h .
  HandlerCodec h r =>
  -- |Name of the Neovim function that will be created.
  RpcName ->
  -- |Execute sync or async.
  Execution ->
  -- |The handler function.
  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)

-- |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 'Ribosome.MsgpackDecode' (or more
-- specifically, 'Ribosome.Host.Handler.Codec.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
-- 'Ribosome.Range' for the line range specified to the command.
-- See [command params]("Ribosome#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@.
rpcCommand ::
   r h .
  HandlerCodec h r =>
  CommandHandler OptionStateZero h =>
  -- |Name of the Neovim function that will be created.
  RpcName ->
  -- |Execute sync or async.
  Execution ->
  -- |The handler function.
  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

-- |Add the given completion to an 'RpcHandler'.
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

-- |Configure the given 'RpcHandler' to use the specified builtin completion.
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)

-- |Create a completion handler that can be used by another handler by wrapping it with 'complete', using the same
-- 'RpcName'.
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

-- |Add command line completion to another 'RpcHandler' by creating a new handler that calls the given function to
-- obtain possible completions.
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
  ]

-- |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@.
rpcAutocmd ::
   r h .
  HandlerCodec h r =>
  RpcName ->
  -- |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@.
  Execution ->
  -- |The Neovim event identifier, like @BufWritePre@ or @User@.
  AutocmdEvents ->
  -- |Various Neovim options like the file pattern.
  AutocmdOptions ->
  -- |The handler function.
  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)

-- |Convenience function for creating a handler that is triggered by both a function and a command of the same name.
-- See 'rpcFunction' and 'rpcCommand'.
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
  ]