module Ribosome.Host.Api.Autocmd where
import Data.MessagePack (Object)
import Prelude hiding (group)
import Ribosome.Host.Api.Data (nvimCreateAugroup, nvimCreateAutocmd)
import Ribosome.Host.Class.Msgpack.Encode (toMsgpack)
import Ribosome.Host.Class.Msgpack.Map (msgpackMap)
import Ribosome.Host.Data.RpcCall (RpcCall)
import Ribosome.Host.Data.RpcType (
AutocmdBuffer (AutocmdBuffer),
AutocmdEvents (AutocmdEvents),
AutocmdGroup (AutocmdGroup),
AutocmdId (AutocmdId),
AutocmdOptions (..),
AutocmdPatterns (AutocmdPatterns),
)
withAugroup :: Maybe AutocmdGroup -> (Map Text Object -> RpcCall a) -> RpcCall a
withAugroup :: forall a.
Maybe AutocmdGroup -> (Map Text Object -> RpcCall a) -> RpcCall a
withAugroup (Just (AutocmdGroup Text
g)) Map Text Object -> RpcCall a
f =
Text -> Map Text Object -> RpcCall Int
nvimCreateAugroup Text
g [(Text
"clear", Bool -> Object
forall a. MsgpackEncode a => a -> Object
toMsgpack Bool
False)] RpcCall Int -> RpcCall a -> RpcCall a
forall (f :: * -> *) a b. Applicative f => f a -> f b -> f b
*> Map Text Object -> RpcCall a
f [(Text
"group", Text -> Object
forall a. MsgpackEncode a => a -> Object
toMsgpack Text
g)]
withAugroup Maybe AutocmdGroup
Nothing Map Text Object -> RpcCall a
f =
Map Text Object -> RpcCall a
f Map Text Object
forall a. Monoid a => a
mempty
autocmd ::
AutocmdEvents ->
AutocmdOptions ->
Text ->
RpcCall AutocmdId
autocmd :: AutocmdEvents -> AutocmdOptions -> Text -> RpcCall AutocmdId
autocmd (AutocmdEvents [Text]
events) AutocmdOptions {Bool
Maybe AutocmdGroup
Either AutocmdBuffer AutocmdPatterns
$sel:group:AutocmdOptions :: AutocmdOptions -> Maybe AutocmdGroup
$sel:once:AutocmdOptions :: AutocmdOptions -> Bool
$sel:nested:AutocmdOptions :: AutocmdOptions -> Bool
$sel:target:AutocmdOptions :: AutocmdOptions -> Either AutocmdBuffer AutocmdPatterns
group :: Maybe AutocmdGroup
once :: Bool
nested :: Bool
target :: Either AutocmdBuffer AutocmdPatterns
..} Text
cmd =
Maybe AutocmdGroup
-> (Map Text Object -> RpcCall AutocmdId) -> RpcCall AutocmdId
forall a.
Maybe AutocmdGroup -> (Map Text Object -> RpcCall a) -> RpcCall a
withAugroup Maybe AutocmdGroup
group \ Map Text Object
grp -> Int -> AutocmdId
AutocmdId (Int -> AutocmdId) -> RpcCall Int -> RpcCall AutocmdId
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> [Text] -> Map Text Object -> RpcCall Int
forall p_0.
MsgpackEncode p_0 =>
p_0 -> Map Text Object -> RpcCall Int
nvimCreateAutocmd [Text]
events (Map Text Object
opts Map Text Object -> Map Text Object -> Map Text Object
forall a. Semigroup a => a -> a -> a
<> Map Text Object
bufPat Map Text Object -> Map Text Object -> Map Text Object
forall a. Semigroup a => a -> a -> a
<> Map Text Object
grp)
where
opts :: Map Text Object
opts =
(Text, Text) -> (Text, Bool) -> (Text, Bool) -> Map Text Object
forall a. MsgpackMap a => a
msgpackMap (Text
"command", Text
cmd) (Text
"once", Bool
once) (Text
"nested", Bool
nested)
bufPat :: Map Text Object
bufPat =
(AutocmdBuffer -> Map Text Object)
-> (AutocmdPatterns -> Map Text Object)
-> Either AutocmdBuffer AutocmdPatterns
-> Map Text Object
forall a c b. (a -> c) -> (b -> c) -> Either a b -> c
either AutocmdBuffer -> Map Text Object
forall {l} {a}.
(IsList l, IsString a, Item l ~ (a, Object)) =>
AutocmdBuffer -> l
bufOpt AutocmdPatterns -> Map Text Object
forall {l} {a}.
(IsList l, IsString a, Item l ~ (a, Object)) =>
AutocmdPatterns -> l
patternOpt Either AutocmdBuffer AutocmdPatterns
target
patternOpt :: AutocmdPatterns -> l
patternOpt (AutocmdPatterns [Text]
pat) =
[(a
"pattern", [Text] -> Object
forall a. MsgpackEncode a => a -> Object
toMsgpack [Text]
pat)]
bufOpt :: AutocmdBuffer -> l
bufOpt (AutocmdBuffer Int
buf) =
[(a
"buffer", Int -> Object
forall a. MsgpackEncode a => a -> Object
toMsgpack Int
buf)]