module Ribosome.Test.Exists where import Data.MessagePack (Object(ObjectInt)) import Neovim (Neovim, toObject) import Neovim.API.Text (vim_call_function) import UnliftIO.Exception (tryAny) import Ribosome.Data.Text (capitalize) import Ribosome.System.Time (epochSeconds, sleep) retry :: MonadIO m => MonadFail m => Double -> Int -> m a -> (a -> m (Either Text b)) -> m b retry :: Double -> Int -> m a -> (a -> m (Either Text b)) -> m b retry Double interval Int timeout m a thunk a -> m (Either Text b) check = do Int start <- m Int forall (m :: * -> *). MonadIO m => m Int epochSeconds Int -> m b step Int start where step :: Int -> m b step Int start = do a result <- m a thunk Either Text b checked <- a -> m (Either Text b) check a result Int -> Either Text b -> m b recurse Int start Either Text b checked recurse :: Int -> Either Text b -> m b recurse Int _ (Right b b) = b -> m b forall (m :: * -> *) a. Monad m => a -> m a return b b recurse Int start (Left Text e) = do Int current <- m Int forall (m :: * -> *). MonadIO m => m Int epochSeconds if (Int current Int -> Int -> Int forall a. Num a => a -> a -> a - Int start) Int -> Int -> Bool forall a. Ord a => a -> a -> Bool < Int timeout then do Double -> m () forall (m :: * -> *). MonadIO m => Double -> m () sleep Double interval Int -> m b step Int start else String -> m b forall (m :: * -> *) a. MonadFail m => String -> m a fail (Text -> String forall a. ToString a => a -> String toString Text e) waitForPlugin :: Text -> Double -> Int -> Neovim env () waitForPlugin :: Text -> Double -> Int -> Neovim env () waitForPlugin Text name Double interval Int timeout = Double -> Int -> Neovim env (Either SomeException Object) -> (Either SomeException Object -> Neovim env (Either Text ())) -> Neovim env () forall (m :: * -> *) a b. (MonadIO m, MonadFail m) => Double -> Int -> m a -> (a -> m (Either Text b)) -> m b retry Double interval Int timeout Neovim env (Either SomeException Object) thunk Either SomeException Object -> Neovim env (Either Text ()) check where thunk :: Neovim env (Either SomeException Object) thunk = Neovim env Object -> Neovim env (Either SomeException Object) forall (m :: * -> *) a. MonadUnliftIO m => m a -> m (Either SomeException a) tryAny (Neovim env Object -> Neovim env (Either SomeException Object)) -> Neovim env Object -> Neovim env (Either SomeException Object) forall a b. (a -> b) -> a -> b $ Text -> Vector Object -> forall env. Neovim env Object vim_call_function Text "exists" (Vector Object -> forall env. Neovim env Object) -> Vector Object -> forall env. Neovim env Object forall a b. (a -> b) -> a -> b $ [Item (Vector Object)] -> Vector Object forall l. IsList l => [Item l] -> l fromList [Text -> Object forall o. NvimObject o => o -> Object toObject (Text -> Object) -> Text -> Object forall a b. (a -> b) -> a -> b $ Text "*" Text -> Text -> Text forall a. Semigroup a => a -> a -> a <> Text -> Text capitalize Text name Text -> Text -> Text forall a. Semigroup a => a -> a -> a <> Text "Poll"] check :: Either SomeException Object -> Neovim env (Either Text ()) check (Right (ObjectInt Int64 1)) = Either Text () -> Neovim env (Either Text ()) forall (m :: * -> *) a. Monad m => a -> m a return (Either Text () -> Neovim env (Either Text ())) -> Either Text () -> Neovim env (Either Text ()) forall a b. (a -> b) -> a -> b $ () -> Either Text () forall a b. b -> Either a b Right () check (Right Object a) = Either Text () -> Neovim env (Either Text ()) forall (m :: * -> *) a. Monad m => a -> m a return (Either Text () -> Neovim env (Either Text ())) -> Either Text () -> Neovim env (Either Text ()) forall a b. (a -> b) -> a -> b $ Text -> Either Text () forall a b. a -> Either a b Left (Text -> Either Text ()) -> Text -> Either Text () forall a b. (a -> b) -> a -> b $ Text errormsg Text -> Text -> Text forall a. Semigroup a => a -> a -> a <> Text "weird return type " Text -> Text -> Text forall a. Semigroup a => a -> a -> a <> Object -> Text forall b a. (Show a, IsString b) => a -> b show Object a check (Left SomeException e) = Either Text () -> Neovim env (Either Text ()) forall (m :: * -> *) a. Monad m => a -> m a return (Either Text () -> Neovim env (Either Text ())) -> Either Text () -> Neovim env (Either Text ()) forall a b. (a -> b) -> a -> b $ Text -> Either Text () forall a b. a -> Either a b Left (Text -> Either Text ()) -> Text -> Either Text () forall a b. (a -> b) -> a -> b $ Text errormsg Text -> Text -> Text forall a. Semigroup a => a -> a -> a <> SomeException -> Text forall b a. (Show a, IsString b) => a -> b show SomeException e errormsg :: Text errormsg = Text "plugin didn't start within " Text -> Text -> Text forall a. Semigroup a => a -> a -> a <> Int -> Text forall b a. (Show a, IsString b) => a -> b show Int timeout Text -> Text -> Text forall a. Semigroup a => a -> a -> a <> Text " seconds: "