module Ribosome.Api.Option where import Control.Exception.Lifted (bracket) import Data.Text (splitOn) import Ribosome.Control.Monad.Ribo (NvimE) import Ribosome.Msgpack.Encode (MsgpackEncode(toMsgpack)) import Ribosome.Nvim.Api.IO (vimGetOption, vimSetOption) optionCat :: NvimE e m => Text -> Text -> m () optionCat :: Text -> Text -> m () optionCat Text name Text extra = do Text current <- Text -> m Text forall (m :: * -> *) e a. (Nvim m, MonadDeepError e RpcError m, MsgpackDecode a) => Text -> m a vimGetOption Text name Text -> Object -> m () forall (m :: * -> *) e. (Nvim m, MonadDeepError e RpcError m) => Text -> Object -> m () vimSetOption Text name (Object -> m ()) -> Object -> m () forall a b. (a -> b) -> a -> b $ Text -> Object forall a. MsgpackEncode a => a -> Object toMsgpack (Text -> Object) -> Text -> Object forall a b. (a -> b) -> a -> b $ Text current Text -> Text -> Text forall a. Semigroup a => a -> a -> a <> Text "," Text -> Text -> Text forall a. Semigroup a => a -> a -> a <> Text extra rtpCat :: NvimE e m => Text -> m () rtpCat :: Text -> m () rtpCat = Text -> Text -> m () forall e (m :: * -> *). NvimE e m => Text -> Text -> m () optionCat Text "runtimepath" optionString :: NvimE e m => Text -> m Text optionString :: Text -> m Text optionString = Text -> m Text forall (m :: * -> *) e a. (Nvim m, MonadDeepError e RpcError m, MsgpackDecode a) => Text -> m a vimGetOption optionList :: NvimE e m => Text -> m [Text] optionList :: Text -> m [Text] optionList Text name = do Text s <- Text -> m Text forall (m :: * -> *) e a. (Nvim m, MonadDeepError e RpcError m, MsgpackDecode a) => Text -> m a vimGetOption Text name return $ Text -> Text -> [Text] splitOn Text "," Text s withOption :: NvimE e m => MsgpackEncode a => MonadBaseControl IO m => Text -> a -> m b -> m b withOption :: Text -> a -> m b -> m b withOption Text name a value = m Object -> (Object -> m ()) -> (Object -> m b) -> m b forall (m :: * -> *) a b c. MonadBaseControl IO m => m a -> (a -> m b) -> (a -> m c) -> m c bracket m Object set Object -> m () reset ((Object -> m b) -> m b) -> (m b -> Object -> m b) -> m b -> m b forall b c a. (b -> c) -> (a -> b) -> a -> c . m b -> Object -> m b forall a b. a -> b -> a const where set :: m Object set = Text -> m Object forall (m :: * -> *) e a. (Nvim m, MonadDeepError e RpcError m, MsgpackDecode a) => Text -> m a vimGetOption Text name m Object -> m () -> m Object forall (f :: * -> *) a b. Applicative f => f a -> f b -> f a <* Text -> Object -> m () forall (m :: * -> *) e. (Nvim m, MonadDeepError e RpcError m) => Text -> Object -> m () vimSetOption Text name (a -> Object forall a. MsgpackEncode a => a -> Object toMsgpack a value) reset :: Object -> m () reset = Text -> Object -> m () forall (m :: * -> *) e. (Nvim m, MonadDeepError e RpcError m) => Text -> Object -> m () vimSetOption Text name