{-# LANGUAGE OverloadedStrings #-}
module Network.GRPC.HTTP2.Encoding (
decoder
, fromDecoder
, decodeInput
, decodeOutput
, encode
, fromBuilder
, encodeInput
, encodeOutput
, Compression(..)
, Encoding(..)
, Decoding(..)
, grpcCompressionHV
, uncompressed
, gzip
) where
import qualified Codec.Compression.GZip as GZip
import Data.Binary.Builder (Builder, toLazyByteString, fromByteString, singleton, putWord32be)
import Data.Binary.Get (getByteString, getInt8, getWord32be, runGetIncremental, Decoder(..), Get)
import Data.ByteString.Char8 (ByteString)
import qualified Data.ByteString.Char8 as ByteString
import Data.ByteString.Lazy (fromStrict, toStrict)
import Data.ProtoLens.Encoding (encodeMessage, decodeMessage)
import Data.ProtoLens.Message (Message)
import Data.ProtoLens.Service.Types (Service(..), HasMethod, HasMethodImpl(..))
import Network.GRPC.HTTP2.Types
decoder :: Message a => Compression -> Decoder (Either String a)
decoder compression = runGetIncremental $ do
isCompressed <- getInt8
let decompress = if isCompressed == 0 then pure else (_decompressionFunction compression)
n <- getWord32be
decodeMessage <$> (decompress =<< getByteString (fromIntegral n))
fromDecoder :: Decoder (Either String a) -> Either String a
fromDecoder (Fail _ _ msg) = Left msg
fromDecoder (Partial _) = Left "got only a subet of the message"
fromDecoder (Done _ _ val) = val
decodeOutput
:: (Service s, HasMethod s m)
=> RPC s m
-> Compression
-> Decoder (Either String (MethodOutput s m))
decodeOutput _ = decoder
decodeInput
:: (Service s, HasMethod s m)
=> RPC s m
-> Compression
-> Decoder (Either String (MethodInput s m))
decodeInput _ = decoder
encode :: Message m => Compression -> m -> Builder
encode compression plain =
mconcat [ singleton (if _compressionByteSet compression then 1 else 0)
, putWord32be (fromIntegral $ ByteString.length bin)
, fromByteString bin
]
where
bin = _compressionFunction compression $ encodeMessage plain
fromBuilder :: Builder -> ByteString
fromBuilder = toStrict . toLazyByteString
encodeInput
:: (Service s, HasMethod s m)
=> RPC s m
-> Compression
-> MethodInput s m
-> Builder
encodeInput _ = encode
encodeOutput
:: (Service s, HasMethod s m)
=> RPC s m
-> Compression
-> MethodOutput s m
-> Builder
encodeOutput _ = encode
data Compression = Compression {
_compressionName :: ByteString
, _compressionByteSet :: Bool
, _compressionFunction :: (ByteString -> ByteString)
, _decompressionFunction :: (ByteString -> Get ByteString)
}
newtype Encoding = Encoding { _getEncodingCompression :: Compression }
newtype Decoding = Decoding { _getDecodingCompression :: Compression }
grpcCompressionHV :: Compression -> HeaderValue
grpcCompressionHV = _compressionName
uncompressed :: Compression
uncompressed = Compression "identity" False id (\_ -> fail "decoder uninstalled")
gzip :: Compression
gzip = Compression "gzip" True
(toStrict . GZip.compress . fromStrict)
(pure . toStrict . GZip.decompress . fromStrict)