module Ribosome.Host.Data.ApiInfo where import Data.MessagePack (Object) import qualified Data.Serialize as Serialize import System.Process.Typed (proc, readProcessStdout_) import Ribosome.Host.Class.Msgpack.Decode (MsgpackDecode, nestedDecode) import Ribosome.Host.Class.Msgpack.Error (DecodeError, FieldError, toDecodeError) import Ribosome.Host.Data.ApiType (ApiType) data RpcDecl = RpcDecl { RpcDecl -> [Char] name :: String, RpcDecl -> [(ApiType, [Char])] parameters :: [(ApiType, String)], RpcDecl -> Maybe Int64 since :: Maybe Int64, RpcDecl -> Maybe Int64 deprecated_since :: Maybe Int64, RpcDecl -> Bool method :: Bool, RpcDecl -> ApiType return_type :: ApiType } deriving stock (RpcDecl -> RpcDecl -> Bool (RpcDecl -> RpcDecl -> Bool) -> (RpcDecl -> RpcDecl -> Bool) -> Eq RpcDecl forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a /= :: RpcDecl -> RpcDecl -> Bool $c/= :: RpcDecl -> RpcDecl -> Bool == :: RpcDecl -> RpcDecl -> Bool $c== :: RpcDecl -> RpcDecl -> Bool Eq, Int -> RpcDecl -> ShowS [RpcDecl] -> ShowS RpcDecl -> [Char] (Int -> RpcDecl -> ShowS) -> (RpcDecl -> [Char]) -> ([RpcDecl] -> ShowS) -> Show RpcDecl forall a. (Int -> a -> ShowS) -> (a -> [Char]) -> ([a] -> ShowS) -> Show a showList :: [RpcDecl] -> ShowS $cshowList :: [RpcDecl] -> ShowS show :: RpcDecl -> [Char] $cshow :: RpcDecl -> [Char] showsPrec :: Int -> RpcDecl -> ShowS $cshowsPrec :: Int -> RpcDecl -> ShowS Show, (forall x. RpcDecl -> Rep RpcDecl x) -> (forall x. Rep RpcDecl x -> RpcDecl) -> Generic RpcDecl forall x. Rep RpcDecl x -> RpcDecl forall x. RpcDecl -> Rep RpcDecl x forall a. (forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a $cto :: forall x. Rep RpcDecl x -> RpcDecl $cfrom :: forall x. RpcDecl -> Rep RpcDecl x Generic) deriving anyclass (Object -> Either DecodeError RpcDecl (Object -> Either DecodeError RpcDecl) -> MsgpackDecode RpcDecl forall a. (Object -> Either DecodeError a) -> MsgpackDecode a fromMsgpack :: Object -> Either DecodeError RpcDecl $cfromMsgpack :: Object -> Either DecodeError RpcDecl MsgpackDecode) newtype ExtType = ExtType { ExtType -> [Char] unExtType :: String } deriving stock (ExtType -> ExtType -> Bool (ExtType -> ExtType -> Bool) -> (ExtType -> ExtType -> Bool) -> Eq ExtType forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a /= :: ExtType -> ExtType -> Bool $c/= :: ExtType -> ExtType -> Bool == :: ExtType -> ExtType -> Bool $c== :: ExtType -> ExtType -> Bool Eq, Int -> ExtType -> ShowS [ExtType] -> ShowS ExtType -> [Char] (Int -> ExtType -> ShowS) -> (ExtType -> [Char]) -> ([ExtType] -> ShowS) -> Show ExtType forall a. (Int -> a -> ShowS) -> (a -> [Char]) -> ([a] -> ShowS) -> Show a showList :: [ExtType] -> ShowS $cshowList :: [ExtType] -> ShowS show :: ExtType -> [Char] $cshow :: ExtType -> [Char] showsPrec :: Int -> ExtType -> ShowS $cshowsPrec :: Int -> ExtType -> ShowS Show) deriving newtype ([Char] -> ExtType ([Char] -> ExtType) -> IsString ExtType forall a. ([Char] -> a) -> IsString a fromString :: [Char] -> ExtType $cfromString :: [Char] -> ExtType IsString, Eq ExtType Eq ExtType -> (ExtType -> ExtType -> Ordering) -> (ExtType -> ExtType -> Bool) -> (ExtType -> ExtType -> Bool) -> (ExtType -> ExtType -> Bool) -> (ExtType -> ExtType -> Bool) -> (ExtType -> ExtType -> ExtType) -> (ExtType -> ExtType -> ExtType) -> Ord ExtType ExtType -> ExtType -> Bool ExtType -> ExtType -> Ordering ExtType -> ExtType -> ExtType forall a. Eq a -> (a -> a -> Ordering) -> (a -> a -> Bool) -> (a -> a -> Bool) -> (a -> a -> Bool) -> (a -> a -> Bool) -> (a -> a -> a) -> (a -> a -> a) -> Ord a min :: ExtType -> ExtType -> ExtType $cmin :: ExtType -> ExtType -> ExtType max :: ExtType -> ExtType -> ExtType $cmax :: ExtType -> ExtType -> ExtType >= :: ExtType -> ExtType -> Bool $c>= :: ExtType -> ExtType -> Bool > :: ExtType -> ExtType -> Bool $c> :: ExtType -> ExtType -> Bool <= :: ExtType -> ExtType -> Bool $c<= :: ExtType -> ExtType -> Bool < :: ExtType -> ExtType -> Bool $c< :: ExtType -> ExtType -> Bool compare :: ExtType -> ExtType -> Ordering $ccompare :: ExtType -> ExtType -> Ordering Ord, Object -> Either DecodeError ExtType (Object -> Either DecodeError ExtType) -> MsgpackDecode ExtType forall a. (Object -> Either DecodeError a) -> MsgpackDecode a fromMsgpack :: Object -> Either DecodeError ExtType $cfromMsgpack :: Object -> Either DecodeError ExtType MsgpackDecode) data ExtTypeMeta = ExtTypeMeta { ExtTypeMeta -> Int64 id :: Int64, ExtTypeMeta -> [Char] prefix :: String } deriving stock (ExtTypeMeta -> ExtTypeMeta -> Bool (ExtTypeMeta -> ExtTypeMeta -> Bool) -> (ExtTypeMeta -> ExtTypeMeta -> Bool) -> Eq ExtTypeMeta forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a /= :: ExtTypeMeta -> ExtTypeMeta -> Bool $c/= :: ExtTypeMeta -> ExtTypeMeta -> Bool == :: ExtTypeMeta -> ExtTypeMeta -> Bool $c== :: ExtTypeMeta -> ExtTypeMeta -> Bool Eq, Int -> ExtTypeMeta -> ShowS [ExtTypeMeta] -> ShowS ExtTypeMeta -> [Char] (Int -> ExtTypeMeta -> ShowS) -> (ExtTypeMeta -> [Char]) -> ([ExtTypeMeta] -> ShowS) -> Show ExtTypeMeta forall a. (Int -> a -> ShowS) -> (a -> [Char]) -> ([a] -> ShowS) -> Show a showList :: [ExtTypeMeta] -> ShowS $cshowList :: [ExtTypeMeta] -> ShowS show :: ExtTypeMeta -> [Char] $cshow :: ExtTypeMeta -> [Char] showsPrec :: Int -> ExtTypeMeta -> ShowS $cshowsPrec :: Int -> ExtTypeMeta -> ShowS Show, (forall x. ExtTypeMeta -> Rep ExtTypeMeta x) -> (forall x. Rep ExtTypeMeta x -> ExtTypeMeta) -> Generic ExtTypeMeta forall x. Rep ExtTypeMeta x -> ExtTypeMeta forall x. ExtTypeMeta -> Rep ExtTypeMeta x forall a. (forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a $cto :: forall x. Rep ExtTypeMeta x -> ExtTypeMeta $cfrom :: forall x. ExtTypeMeta -> Rep ExtTypeMeta x Generic) deriving anyclass (Object -> Either DecodeError ExtTypeMeta (Object -> Either DecodeError ExtTypeMeta) -> MsgpackDecode ExtTypeMeta forall a. (Object -> Either DecodeError a) -> MsgpackDecode a fromMsgpack :: Object -> Either DecodeError ExtTypeMeta $cfromMsgpack :: Object -> Either DecodeError ExtTypeMeta MsgpackDecode) data ApiInfo = ApiInfo { ApiInfo -> Map ExtType ExtTypeMeta types :: Map ExtType ExtTypeMeta, ApiInfo -> [RpcDecl] functions :: [RpcDecl] } deriving stock (ApiInfo -> ApiInfo -> Bool (ApiInfo -> ApiInfo -> Bool) -> (ApiInfo -> ApiInfo -> Bool) -> Eq ApiInfo forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a /= :: ApiInfo -> ApiInfo -> Bool $c/= :: ApiInfo -> ApiInfo -> Bool == :: ApiInfo -> ApiInfo -> Bool $c== :: ApiInfo -> ApiInfo -> Bool Eq, Int -> ApiInfo -> ShowS [ApiInfo] -> ShowS ApiInfo -> [Char] (Int -> ApiInfo -> ShowS) -> (ApiInfo -> [Char]) -> ([ApiInfo] -> ShowS) -> Show ApiInfo forall a. (Int -> a -> ShowS) -> (a -> [Char]) -> ([a] -> ShowS) -> Show a showList :: [ApiInfo] -> ShowS $cshowList :: [ApiInfo] -> ShowS show :: ApiInfo -> [Char] $cshow :: ApiInfo -> [Char] showsPrec :: Int -> ApiInfo -> ShowS $cshowsPrec :: Int -> ApiInfo -> ShowS Show, (forall x. ApiInfo -> Rep ApiInfo x) -> (forall x. Rep ApiInfo x -> ApiInfo) -> Generic ApiInfo forall x. Rep ApiInfo x -> ApiInfo forall x. ApiInfo -> Rep ApiInfo x forall a. (forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a $cto :: forall x. Rep ApiInfo x -> ApiInfo $cfrom :: forall x. ApiInfo -> Rep ApiInfo x Generic) deriving anyclass (Object -> Either DecodeError ApiInfo (Object -> Either DecodeError ApiInfo) -> MsgpackDecode ApiInfo forall a. (Object -> Either DecodeError a) -> MsgpackDecode a fromMsgpack :: Object -> Either DecodeError ApiInfo $cfromMsgpack :: Object -> Either DecodeError ApiInfo MsgpackDecode) msgpack :: IO (Either FieldError Object) msgpack :: IO (Either FieldError Object) msgpack = ([Char] -> FieldError) -> Either [Char] Object -> Either FieldError Object forall (p :: * -> * -> *) a b c. Bifunctor p => (a -> b) -> p a c -> p b c first [Char] -> FieldError forall a. IsString a => [Char] -> a fromString (Either [Char] Object -> Either FieldError Object) -> (ByteString -> Either [Char] Object) -> ByteString -> Either FieldError Object forall b c a. (b -> c) -> (a -> b) -> a -> c . ByteString -> Either [Char] Object forall a. Serialize a => ByteString -> Either [Char] a Serialize.decode (ByteString -> Either [Char] Object) -> (ByteString -> ByteString) -> ByteString -> Either [Char] Object forall b c a. (b -> c) -> (a -> b) -> a -> c . ByteString -> ByteString forall l s. LazyStrict l s => l -> s toStrict (ByteString -> Either FieldError Object) -> IO ByteString -> IO (Either FieldError Object) forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b <$> ProcessConfig () () () -> IO ByteString forall (m :: * -> *) stdin stdoutIgnored stderr. MonadIO m => ProcessConfig stdin stdoutIgnored stderr -> m ByteString readProcessStdout_ ([Char] -> [[Char]] -> ProcessConfig () () () proc [Char] "nvim" [Item [[Char]] "--api-info"]) apiInfo :: IO (Either DecodeError ApiInfo) apiInfo :: IO (Either DecodeError ApiInfo) apiInfo = Either FieldError ApiInfo -> Either DecodeError ApiInfo forall a. Typeable a => Either FieldError a -> Either DecodeError a toDecodeError (Either FieldError ApiInfo -> Either DecodeError ApiInfo) -> (Either FieldError Object -> Either FieldError ApiInfo) -> Either FieldError Object -> Either DecodeError ApiInfo forall b c a. (b -> c) -> (a -> b) -> a -> c . (Object -> Either FieldError ApiInfo forall a. MsgpackDecode a => Object -> Either FieldError a nestedDecode (Object -> Either FieldError ApiInfo) -> Either FieldError Object -> Either FieldError ApiInfo forall (m :: * -> *) a b. Monad m => (a -> m b) -> m a -> m b =<<) (Either FieldError Object -> Either DecodeError ApiInfo) -> IO (Either FieldError Object) -> IO (Either DecodeError ApiInfo) forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b <$> IO (Either FieldError Object) msgpack