-- |API functions for Neovim options.
module Ribosome.Api.Option where

import Data.MessagePack (Object)
import Data.Text (splitOn)
import Exon (exon)

import Ribosome.Host.Api.Effect (vimGetOption, vimSetOption)
import Ribosome.Host.Class.Msgpack.Encode (MsgpackEncode)
import Ribosome.Host.Effect.Rpc (Rpc)

-- |Append a string to a comma-separated option.
optionCat ::
  Member Rpc r =>
  Text ->
  Text ->
  Sem r ()
optionCat :: forall (r :: EffectRow). Member Rpc r => Text -> Text -> Sem r ()
optionCat Text
name Text
extra = do
  Text
current <- Text -> Sem r Text
forall a (r :: EffectRow).
(Member Rpc r, MsgpackDecode a) =>
Text -> Sem r a
vimGetOption Text
name
  Text -> Text -> Sem r ()
forall p_1 (r :: EffectRow).
(Member Rpc r, MsgpackEncode p_1) =>
Text -> p_1 -> Sem r ()
vimSetOption Text
name [exon|#{current},#{extra}|]

-- |Append a string to the option @runtimepath@.
rtpCat ::
  Member Rpc r =>
  Text ->
  Sem r ()
rtpCat :: forall (r :: EffectRow). Member Rpc r => Text -> Sem r ()
rtpCat =
  Text -> Text -> Sem r ()
forall (r :: EffectRow). Member Rpc r => Text -> Text -> Sem r ()
optionCat Text
"runtimepath"

-- |Get a list of strings from a comma-separated option.
optionList ::
  Member Rpc r =>
  Text ->
  Sem r [Text]
optionList :: forall (r :: EffectRow). Member Rpc r => Text -> Sem r [Text]
optionList Text
name = do
  Text
s <- Text -> Sem r Text
forall a (r :: EffectRow).
(Member Rpc r, MsgpackDecode a) =>
Text -> Sem r a
vimGetOption Text
name
  pure (Text -> Text -> [Text]
splitOn Text
"," Text
s)

-- |Run an action with an option temporarily set to a value, then restore the old value.
withOption ::
   a r b .
  Members [Rpc, Resource] r =>
  MsgpackEncode a =>
  Text ->
  a ->
  Sem r b ->
  Sem r b
withOption :: forall a (r :: EffectRow) b.
(Members '[Rpc, Resource] r, MsgpackEncode a) =>
Text -> a -> Sem r b -> Sem r b
withOption Text
name a
value =
  Sem r Object
-> (Object -> Sem r ()) -> (Object -> Sem r b) -> Sem r b
forall (r :: EffectRow) a c b.
Member Resource r =>
Sem r a -> (a -> Sem r c) -> (a -> Sem r b) -> Sem r b
bracket Sem r Object
setOpt Object -> Sem r ()
reset ((Object -> Sem r b) -> Sem r b)
-> (Sem r b -> Object -> Sem r b) -> Sem r b -> Sem r b
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Sem r b -> Object -> Sem r b
forall a b. a -> b -> a
const
  where
    setOpt :: Sem r Object
setOpt =
      forall a (r :: EffectRow).
(Member Rpc r, MsgpackDecode a) =>
Text -> Sem r a
vimGetOption @Object Text
name Sem r Object -> Sem r () -> Sem r Object
forall (f :: * -> *) a b. Applicative f => f a -> f b -> f a
<* Text -> a -> Sem r ()
forall p_1 (r :: EffectRow).
(Member Rpc r, MsgpackEncode p_1) =>
Text -> p_1 -> Sem r ()
vimSetOption Text
name a
value
    reset :: Object -> Sem r ()
reset =
      Text -> Object -> Sem r ()
forall p_1 (r :: EffectRow).
(Member Rpc r, MsgpackEncode p_1) =>
Text -> p_1 -> Sem r ()
vimSetOption Text
name