module Ribosome.Api.Function where import qualified Data.Text as Text (intercalate) import Ribosome.Control.Monad.Ribo (NvimE) import Ribosome.Nvim.Api.IO (vimCommand) defineFunction :: NvimE e m => Text -> [Text] -> [Text] -> m () defineFunction :: Text -> [Text] -> [Text] -> m () defineFunction Text name [Text] params [Text] body = Text -> m () forall (m :: * -> *) e. (Nvim m, MonadDeepError e RpcError m) => Text -> m () vimCommand (Text -> m ()) -> Text -> m () forall a b. (a -> b) -> a -> b $ [Text] -> Text forall t. IsText t "unlines" => [t] -> t unlines ([Text] -> Text) -> [Text] -> Text forall a b. (a -> b) -> a -> b $ Text sig Text -> [Text] -> [Text] forall a. a -> [a] -> [a] : [Text] body [Text] -> [Text] -> [Text] forall a. [a] -> [a] -> [a] ++ [Item [Text] "endfunction"] where sig :: Text sig = Text "function! " Text -> Text -> Text forall a. Semigroup a => a -> a -> a <> Text name Text -> Text -> Text forall a. Semigroup a => a -> a -> a <> Text "(" Text -> Text -> Text forall a. Semigroup a => a -> a -> a <> Text -> [Text] -> Text Text.intercalate Text ", " [Text] params Text -> Text -> Text forall a. Semigroup a => a -> a -> a <> Text ")"