module Ribosome.Host.Data.RpcError where
import Data.MessagePack (Object)
import qualified Data.Text as Text
import Exon (exon)
import Log (Severity (Error))
import Ribosome.Host.Class.Msgpack.Decode (MsgpackDecode)
import Ribosome.Host.Class.Msgpack.Encode (MsgpackEncode)
import Ribosome.Host.Class.Msgpack.Error (DecodeError, renderError)
import Ribosome.Host.Data.Report (Report (Report), Reportable (toReport))
import Ribosome.Host.Data.Request (RpcMethod (RpcMethod))
data RpcError =
Unexpected Text
|
Api RpcMethod [Object] Text
|
Decode DecodeError
deriving stock (RpcError -> RpcError -> Bool
(RpcError -> RpcError -> Bool)
-> (RpcError -> RpcError -> Bool) -> Eq RpcError
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: RpcError -> RpcError -> Bool
$c/= :: RpcError -> RpcError -> Bool
== :: RpcError -> RpcError -> Bool
$c== :: RpcError -> RpcError -> Bool
Eq, Int -> RpcError -> ShowS
[RpcError] -> ShowS
RpcError -> String
(Int -> RpcError -> ShowS)
-> (RpcError -> String) -> ([RpcError] -> ShowS) -> Show RpcError
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [RpcError] -> ShowS
$cshowList :: [RpcError] -> ShowS
show :: RpcError -> String
$cshow :: RpcError -> String
showsPrec :: Int -> RpcError -> ShowS
$cshowsPrec :: Int -> RpcError -> ShowS
Show, (forall x. RpcError -> Rep RpcError x)
-> (forall x. Rep RpcError x -> RpcError) -> Generic RpcError
forall x. Rep RpcError x -> RpcError
forall x. RpcError -> Rep RpcError x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cto :: forall x. Rep RpcError x -> RpcError
$cfrom :: forall x. RpcError -> Rep RpcError x
Generic)
deriving anyclass (RpcError -> Object
(RpcError -> Object) -> MsgpackEncode RpcError
forall a. (a -> Object) -> MsgpackEncode a
toMsgpack :: RpcError -> Object
$ctoMsgpack :: RpcError -> Object
MsgpackEncode, Object -> Either DecodeError RpcError
(Object -> Either DecodeError RpcError) -> MsgpackDecode RpcError
forall a. (Object -> Either DecodeError a) -> MsgpackDecode a
fromMsgpack :: Object -> Either DecodeError RpcError
$cfromMsgpack :: Object -> Either DecodeError RpcError
MsgpackDecode)
instance IsString RpcError where
fromString :: String -> RpcError
fromString =
Text -> RpcError
Unexpected (Text -> RpcError) -> (String -> Text) -> String -> RpcError
forall b c a. (b -> c) -> (a -> b) -> a -> c
. String -> Text
forall a. ToText a => a -> Text
toText
instance Reportable RpcError where
toReport :: RpcError -> Report
toReport = \case
Unexpected Text
e ->
HasCallStack => Text -> [Text] -> Severity -> Report
Text -> [Text] -> Severity -> Report
Report Text
"Internal error" [Text
Item [Text]
e] Severity
Error
Api (RpcMethod Text
m) [Object]
args Text
e ->
HasCallStack => Text -> [Text] -> Severity -> Report
Text -> [Text] -> Severity -> Report
Report Text
"Nvim API failure" [Text
Item [Text]
m, [Object] -> Text
forall b a. (Show a, IsString b) => a -> b
show [Object]
args, Text
Item [Text]
e] Severity
Error
Decode DecodeError
e ->
DecodeError -> Report
forall e. Reportable e => e -> Report
toReport DecodeError
e
rpcError :: RpcError -> Text
rpcError :: RpcError -> Text
rpcError = \case
Unexpected Text
e -> Text
e
Api (RpcMethod Text
m) [Object]
args Text
e -> [exon|#{m}: #{e}(#{Text.intercalate ", " (show <$> args)})|]
Decode DecodeError
e -> DecodeError -> Text
renderError DecodeError
e