Safe Haskell | None |
---|---|
Language | Haskell2010 |
Network.GRPC.Spec.Serialization
Description
Serialization functions
We collect these functions in a separate module, rather than exporting them
from Network.GRPC.Spec, because while the functions in Network.GRPC.Spec
may be needed in some user code (albeit rarely), the serialization
functions from this module really should only be needed in gRPC
implementations such as grapesy
.
Synopsis
- buildInput :: forall {k} (rpc :: k). SupportsClientRpc rpc => Proxy rpc -> Compression -> (OutboundMeta, Input rpc) -> Builder
- parseInput :: forall {k} (rpc :: k). SupportsServerRpc rpc => Proxy rpc -> Compression -> Parser String (InboundMeta, Input rpc)
- buildOutput :: forall {k} (rpc :: k). SupportsServerRpc rpc => Proxy rpc -> Compression -> (OutboundMeta, Output rpc) -> Builder
- parseOutput :: forall {k} (rpc :: k). SupportsClientRpc rpc => Proxy rpc -> Compression -> Parser String (InboundMeta, Output rpc)
- data RawResourceHeaders = RawResourceHeaders {}
- data InvalidResourceHeaders
- buildResourceHeaders :: ResourceHeaders -> RawResourceHeaders
- parseResourceHeaders :: RawResourceHeaders -> Either InvalidResourceHeaders ResourceHeaders
- buildRequestHeaders :: forall {k} (rpc :: k). IsRPC rpc => Proxy rpc -> RequestHeaders -> [Header]
- parseRequestHeaders :: forall {k} (rpc :: k) m. (IsRPC rpc, MonadError (InvalidHeaders GrpcException) m) => Proxy rpc -> [Header] -> m RequestHeaders
- parseRequestHeaders' :: forall {k} (rpc :: k). IsRPC rpc => Proxy rpc -> [Header] -> RequestHeaders' GrpcException
- buildTimeout :: Timeout -> ByteString
- parseTimeout :: MonadError String m => ByteString -> m Timeout
- buildTraceContext :: TraceContext -> ByteString
- parseTraceContext :: MonadError String m => ByteString -> m TraceContext
- buildResponseHeaders :: forall {k} (rpc :: k). SupportsServerRpc rpc => Proxy rpc -> ResponseHeaders -> [Header]
- parseResponseHeaders :: forall {k} (rpc :: k) m. (IsRPC rpc, MonadError (InvalidHeaders GrpcException) m) => Proxy rpc -> [Header] -> m ResponseHeaders
- parseResponseHeaders' :: forall {k} (rpc :: k). IsRPC rpc => Proxy rpc -> [Header] -> ResponseHeaders' GrpcException
- buildPushback :: Pushback -> ByteString
- parsePushback :: Monad m => ByteString -> m Pushback
- buildProperTrailers :: ProperTrailers -> [Header]
- parseProperTrailers :: forall {k} (rpc :: k) m. (IsRPC rpc, MonadError (InvalidHeaders GrpcException) m) => Proxy rpc -> [Header] -> m ProperTrailers
- parseProperTrailers' :: forall {k} (rpc :: k). IsRPC rpc => Proxy rpc -> [Header] -> ProperTrailers'
- buildTrailersOnly :: (ContentType -> Maybe ByteString) -> TrailersOnly -> [Header]
- parseTrailersOnly :: forall {k} m (rpc :: k). (IsRPC rpc, MonadError (InvalidHeaders GrpcException) m) => Proxy rpc -> [Header] -> m TrailersOnly
- parseTrailersOnly' :: forall {k} (rpc :: k). IsRPC rpc => Proxy rpc -> [Header] -> TrailersOnly' GrpcException
- classifyServerResponse :: forall {k} (rpc :: k). IsRPC rpc => Proxy rpc -> Status -> [Header] -> Maybe ByteString -> Either (TrailersOnly' GrpcException) (ResponseHeaders' GrpcException)
- parseCustomMetadata :: MonadError (InvalidHeaders GrpcException) m => Header -> m CustomMetadata
- buildCustomMetadata :: CustomMetadata -> Header
- buildBinaryValue :: ByteString -> ByteString
- parseBinaryValue :: MonadError String m => ByteString -> m ByteString
- buildStatus :: Proto Status -> ByteString
- parseStatus :: ByteString -> Either String (Proto Status)
Messages
Inputs
buildInput :: forall {k} (rpc :: k). SupportsClientRpc rpc => Proxy rpc -> Compression -> (OutboundMeta, Input rpc) -> Builder Source #
Serialize RPC input
Length-Prefixed-Message → Compressed-Flag Message-Length Message Compressed-Flag → 0 / 1 # encoded as 1 byte unsigned integer Message-Length → {length of Message} # encoded as 4 byte unsigned integer (big endian) Message → *{binary octet}
parseInput :: forall {k} (rpc :: k). SupportsServerRpc rpc => Proxy rpc -> Compression -> Parser String (InboundMeta, Input rpc) Source #
Parse input
Outputs
buildOutput :: forall {k} (rpc :: k). SupportsServerRpc rpc => Proxy rpc -> Compression -> (OutboundMeta, Output rpc) -> Builder Source #
Serialize RPC output
parseOutput :: forall {k} (rpc :: k). SupportsClientRpc rpc => Proxy rpc -> Compression -> Parser String (InboundMeta, Output rpc) Source #
Parse output
Headers
Pseudoheaders
data RawResourceHeaders Source #
Raw (serialized) form of ResourceHeaders
Constructors
RawResourceHeaders | |
Fields
|
Instances
Show RawResourceHeaders Source # | |
Defined in Network.GRPC.Spec.Serialization.Headers.PseudoHeaders Methods showsPrec :: Int -> RawResourceHeaders -> ShowS # show :: RawResourceHeaders -> String # showList :: [RawResourceHeaders] -> ShowS # |
data InvalidResourceHeaders Source #
Invalid resource headers
Constructors
InvalidMethod ByteString | |
InvalidPath ByteString |
Instances
Show InvalidResourceHeaders Source # | |
Defined in Network.GRPC.Spec.Serialization.Headers.PseudoHeaders Methods showsPrec :: Int -> InvalidResourceHeaders -> ShowS # show :: InvalidResourceHeaders -> String # showList :: [InvalidResourceHeaders] -> ShowS # |
buildResourceHeaders :: ResourceHeaders -> RawResourceHeaders Source #
Serialize ResourceHeaders
(pseudo headers)
parseResourceHeaders :: RawResourceHeaders -> Either InvalidResourceHeaders ResourceHeaders Source #
Parse ResourceHeaders
(pseudo headers)
RequestHeaders
buildRequestHeaders :: forall {k} (rpc :: k). IsRPC rpc => Proxy rpc -> RequestHeaders -> [Header] Source #
Request headers
Request-Headers → Call-Definition *Custom-Metadata
parseRequestHeaders :: forall {k} (rpc :: k) m. (IsRPC rpc, MonadError (InvalidHeaders GrpcException) m) => Proxy rpc -> [Header] -> m RequestHeaders Source #
Parse RequestHeaders
Throws an error if any headers fail to parse; if this is not desired, see
parseRequestHeaders'
instead.
parseRequestHeaders' :: forall {k} (rpc :: k). IsRPC rpc => Proxy rpc -> [Header] -> RequestHeaders' GrpcException Source #
Parse request headers
This can report invalid headers on a per-header basis; see also
parseRequestHeaders
.
Timeouts
buildTimeout :: Timeout -> ByteString Source #
Serialize Timeout
parseTimeout :: MonadError String m => ByteString -> m Timeout Source #
Parse Timeout
OpenTelemetry
buildTraceContext :: TraceContext -> ByteString Source #
Serialize TraceContext
parseTraceContext :: MonadError String m => ByteString -> m TraceContext Source #
Parse TraceContext
ResponseHeaders
buildResponseHeaders :: forall {k} (rpc :: k). SupportsServerRpc rpc => Proxy rpc -> ResponseHeaders -> [Header] Source #
Build response headers
parseResponseHeaders :: forall {k} (rpc :: k) m. (IsRPC rpc, MonadError (InvalidHeaders GrpcException) m) => Proxy rpc -> [Header] -> m ResponseHeaders Source #
Parse response headers
parseResponseHeaders' :: forall {k} (rpc :: k). IsRPC rpc => Proxy rpc -> [Header] -> ResponseHeaders' GrpcException Source #
Generalization of parseResponseHeaders
that does not throw errors
See also parseRequestHeaders
versus
'parseRequestHeaders'
for a similar pair of functions.
Pushback
buildPushback :: Pushback -> ByteString Source #
Serialize Pushback
parsePushback :: Monad m => ByteString -> m Pushback Source #
Parse Pushback
Parsing a pushback cannot fail; the spec mandates:
If the value for pushback is negative or unparseble, then it will be seen as the server asking the client not to retry at all.
We therefore only require Monad m
, not MonadError m
(having the Monad
constraint at all keeps the type signature consistent with other parsing
functions).
ProperTrailers
buildProperTrailers :: ProperTrailers -> [Header] Source #
Build trailers (see buildTrailersOnly
for the Trailers-Only case)
parseProperTrailers :: forall {k} (rpc :: k) m. (IsRPC rpc, MonadError (InvalidHeaders GrpcException) m) => Proxy rpc -> [Header] -> m ProperTrailers Source #
Parse response trailers
The gRPC spec defines:
Trailers → .. Trailers-Only → HTTP-Status Content-Type Trailers
This means that Trailers-Only is a superset of the Trailers; we make use of
this here, and error out if we get an unexpected Content-Type
override.
parseProperTrailers' :: forall {k} (rpc :: k). IsRPC rpc => Proxy rpc -> [Header] -> ProperTrailers' Source #
Generalization of parseProperTrailers
that does not throw errors.
See also parseRequestHeaders
versus
'parseRequestHeaders'
for a similar pair of functions.
See ProperTrailers'
for a discussion of why ProperTrailers'
is not
parameterized (unlike ResponseHeaders'
and
RequestHeaders'
).
TrailersOnly
Arguments
:: (ContentType -> Maybe ByteString) | Interpret Under normal circumstances this should be To resolve this catch-22, this function is allowed to return |
-> TrailersOnly | |
-> [Header] |
Build trailers for the Trailers-Only case
parseTrailersOnly :: forall {k} m (rpc :: k). (IsRPC rpc, MonadError (InvalidHeaders GrpcException) m) => Proxy rpc -> [Header] -> m TrailersOnly Source #
Parse TrailersOnly
parseTrailersOnly' :: forall {k} (rpc :: k). IsRPC rpc => Proxy rpc -> [Header] -> TrailersOnly' GrpcException Source #
Generalization of parseTrailersOnly
does that not throw errors.
See also parseRequestHeaders
versus
'parseRequestHeaders'
for a similar pair of functions.
Classify server response
classifyServerResponse Source #
Arguments
:: forall {k} (rpc :: k). IsRPC rpc | |
=> Proxy rpc | |
-> Status | HTTP status |
-> [Header] | Headers |
-> Maybe ByteString | Response body, if known (used for errors only) |
-> Either (TrailersOnly' GrpcException) (ResponseHeaders' GrpcException) |
Classify server response
gRPC servers are supposed to respond with HTTP status 200 OK
no matter
whether the call was successful or not; if not successful, the information
about the failure should be reported using grpc-status
and related headers
(grpc-message
, grpc-status-details-bin
).
The gRPC spec mandates that if we get a non-200 status from a broken deployment, we synthesize a gRPC exception with an appropriate status and status message. The spec itself does not provide any guidance on what such an appropriate status would look like, but the official gRPC repo does provide a partial mapping between HTTP status codes and gRPC status codes at https://github.com/grpc/grpc/blob/master/doc/http-grpc-status-mapping.md. This is the mapping we implement here.
Custom metadata
parseCustomMetadata :: MonadError (InvalidHeaders GrpcException) m => Header -> m CustomMetadata Source #
Parse CustomMetadata
buildCustomMetadata :: CustomMetadata -> Header Source #
Serialize CustomMetadata
Binary values
buildBinaryValue :: ByteString -> ByteString Source #
Serialize binary value (base-64 encoding)
parseBinaryValue :: MonadError String m => ByteString -> m ByteString Source #
Parse binary value
The presence of duplicate headers makes this a bit subtle. Let's consider an example. Suppose we have two duplicate headers
foo-bin: YWJj -- encoding of "abc" foo-bin: ZGVm -- encoding of "def"
The spec says
Custom-Metadata header order is not guaranteed to be preserved except for values with duplicate header names. Duplicate header names may have their values joined with "," as the delimiter and be considered semantically equivalent.
We will do the decoding of both headers prior to joining duplicate headers,
and so the value we will reconstruct for foo-bin
is "abc,def".
However, suppose we deal with a (non-compliant) peer which is unaware of binary headers and has applied the joining rule without decoding:
foo-bin: YWJj,ZGVm
The spec is a bit vague about this case, saying only:
Implementations must split Binary-Headers on "," before decoding the Base64-encoded values.
Here we assume that this case must be treated the same way as if the headers had been decoded prior to joining. Therefore, we split the input on commas, decode each result separately, and join the results with commas again.
Status (Protobuf specific)
buildStatus :: Proto Status -> ByteString Source #
parseStatus :: ByteString -> Either String (Proto Status) Source #