module Network.GRPC.Common.Binary (
RawRpc
, encode
, decodeOrThrow
, DecodeException(..)
) where
import Control.Exception
import Control.Monad.IO.Class
import Data.Binary
import Data.Binary.Get qualified as Binary
import Data.ByteString.Lazy qualified as BS.Lazy
import Data.ByteString.Lazy qualified as Lazy (ByteString)
import Network.GRPC.Spec
decodeOrThrow :: (MonadIO m, Binary a) => Lazy.ByteString -> m a
decodeOrThrow :: forall (m :: * -> *) a. (MonadIO m, Binary a) => ByteString -> m a
decodeOrThrow ByteString
bs = IO a -> m a
forall a. IO a -> m a
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO a -> m a) -> IO a -> m a
forall a b. (a -> b) -> a -> b
$
case ByteString
-> Either
(ByteString, ByteOffset, String) (ByteString, ByteOffset, a)
forall a.
Binary a =>
ByteString
-> Either
(ByteString, ByteOffset, String) (ByteString, ByteOffset, a)
decodeOrFail ByteString
bs of
Left (ByteString
unconsumed, ByteOffset
consumed, String
errorMessage) ->
DecodeException -> IO a
forall e a. (HasCallStack, Exception e) => e -> IO a
throwIO (DecodeException -> IO a) -> DecodeException -> IO a
forall a b. (a -> b) -> a -> b
$ DecodeException{ByteString
unconsumed :: ByteString
unconsumed :: ByteString
unconsumed, ByteOffset
consumed :: ByteOffset
consumed :: ByteOffset
consumed, String
errorMessage :: String
errorMessage :: String
errorMessage}
Right (ByteString
unconsumed, ByteOffset
consumed, a
a) ->
if ByteString -> Bool
BS.Lazy.null ByteString
unconsumed then
a -> IO a
forall a. a -> IO a
forall (m :: * -> *) a. Monad m => a -> m a
return a
a
else do
let errorMessage :: String
errorMessage = String
"Not all bytes consumed"
DecodeException -> IO a
forall e a. (HasCallStack, Exception e) => e -> IO a
throwIO (DecodeException -> IO a) -> DecodeException -> IO a
forall a b. (a -> b) -> a -> b
$ DecodeException{ByteString
unconsumed :: ByteString
unconsumed :: ByteString
unconsumed, ByteOffset
consumed :: ByteOffset
consumed :: ByteOffset
consumed, String
errorMessage :: String
errorMessage :: String
errorMessage}
data DecodeException =
DecodeException {
DecodeException -> ByteString
unconsumed :: Lazy.ByteString
, DecodeException -> ByteOffset
consumed :: Binary.ByteOffset
, DecodeException -> String
errorMessage :: String
}
deriving stock (Int -> DecodeException -> ShowS
[DecodeException] -> ShowS
DecodeException -> String
(Int -> DecodeException -> ShowS)
-> (DecodeException -> String)
-> ([DecodeException] -> ShowS)
-> Show DecodeException
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
$cshowsPrec :: Int -> DecodeException -> ShowS
showsPrec :: Int -> DecodeException -> ShowS
$cshow :: DecodeException -> String
show :: DecodeException -> String
$cshowList :: [DecodeException] -> ShowS
showList :: [DecodeException] -> ShowS
Show)
deriving anyclass (Show DecodeException
Typeable DecodeException
(Typeable DecodeException, Show DecodeException) =>
(DecodeException -> SomeException)
-> (SomeException -> Maybe DecodeException)
-> (DecodeException -> String)
-> (DecodeException -> Bool)
-> Exception DecodeException
SomeException -> Maybe DecodeException
DecodeException -> Bool
DecodeException -> String
DecodeException -> SomeException
forall e.
(Typeable e, Show e) =>
(e -> SomeException)
-> (SomeException -> Maybe e)
-> (e -> String)
-> (e -> Bool)
-> Exception e
$ctoException :: DecodeException -> SomeException
toException :: DecodeException -> SomeException
$cfromException :: SomeException -> Maybe DecodeException
fromException :: SomeException -> Maybe DecodeException
$cdisplayException :: DecodeException -> String
displayException :: DecodeException -> String
$cbacktraceDesired :: DecodeException -> Bool
backtraceDesired :: DecodeException -> Bool
Exception)