Safe Haskell | None |
---|---|
Language | Haskell2010 |
Network.GRPC.HTTP2.Types
Description
Module for GRPC <> HTTP2 mapping.
Synopsis
- type HeaderKey = CI ByteString
- type HeaderValue = ByteString
- grpcTimeoutH :: HeaderKey
- grpcEncodingH :: HeaderKey
- grpcAcceptEncodingH :: HeaderKey
- grpcAcceptEncodingHVdefault :: HeaderValue
- grpcStatusH :: HeaderKey
- grpcMessageH :: HeaderKey
- grpcContentTypeHV :: HeaderValue
- data GRPCStatusCode
- trailerForStatusCode :: GRPCStatusCode -> HeaderValue
- type GRPCStatusMessage = HeaderValue
- data GRPCStatus = GRPCStatus !GRPCStatusCode !GRPCStatusMessage
- statusCodeForTrailer :: HeaderValue -> Maybe GRPCStatusCode
- trailers :: GRPCStatus -> [(HeaderKey, HeaderValue)]
- data InvalidGRPCStatus = InvalidGRPCStatus [(HeaderKey, HeaderValue)]
- readTrailers :: [(HeaderKey, HeaderValue)] -> Either InvalidGRPCStatus GRPCStatus
- data RPC (s :: *) (m :: Symbol) = RPC
- path :: (Service s, HasMethod s m) => RPC s m -> HeaderValue
- newtype Timeout = Timeout Int
- showTimeout :: Timeout -> HeaderValue
- type Authority = HeaderValue
Documentation
type HeaderKey = CI ByteString Source #
HTTP2 Header Key.
type HeaderValue = ByteString Source #
HTTP2 Header Value.
data GRPCStatusCode Source #
Constructors
Instances
Eq GRPCStatusCode Source # | |
Defined in Network.GRPC.HTTP2.Types Methods (==) :: GRPCStatusCode -> GRPCStatusCode -> Bool # (/=) :: GRPCStatusCode -> GRPCStatusCode -> Bool # | |
Ord GRPCStatusCode Source # | |
Defined in Network.GRPC.HTTP2.Types Methods compare :: GRPCStatusCode -> GRPCStatusCode -> Ordering # (<) :: GRPCStatusCode -> GRPCStatusCode -> Bool # (<=) :: GRPCStatusCode -> GRPCStatusCode -> Bool # (>) :: GRPCStatusCode -> GRPCStatusCode -> Bool # (>=) :: GRPCStatusCode -> GRPCStatusCode -> Bool # max :: GRPCStatusCode -> GRPCStatusCode -> GRPCStatusCode # min :: GRPCStatusCode -> GRPCStatusCode -> GRPCStatusCode # | |
Show GRPCStatusCode Source # | |
Defined in Network.GRPC.HTTP2.Types Methods showsPrec :: Int -> GRPCStatusCode -> ShowS # show :: GRPCStatusCode -> String # showList :: [GRPCStatusCode] -> ShowS # |
type GRPCStatusMessage = HeaderValue Source #
data GRPCStatus Source #
Constructors
GRPCStatus !GRPCStatusCode !GRPCStatusMessage |
Instances
Eq GRPCStatus Source # | |
Defined in Network.GRPC.HTTP2.Types | |
Ord GRPCStatus Source # | |
Defined in Network.GRPC.HTTP2.Types Methods compare :: GRPCStatus -> GRPCStatus -> Ordering # (<) :: GRPCStatus -> GRPCStatus -> Bool # (<=) :: GRPCStatus -> GRPCStatus -> Bool # (>) :: GRPCStatus -> GRPCStatus -> Bool # (>=) :: GRPCStatus -> GRPCStatus -> Bool # max :: GRPCStatus -> GRPCStatus -> GRPCStatus # min :: GRPCStatus -> GRPCStatus -> GRPCStatus # | |
Show GRPCStatus Source # | |
Defined in Network.GRPC.HTTP2.Types Methods showsPrec :: Int -> GRPCStatus -> ShowS # show :: GRPCStatus -> String # showList :: [GRPCStatus] -> ShowS # | |
Exception GRPCStatus Source # | |
Defined in Network.GRPC.HTTP2.Types Methods toException :: GRPCStatus -> SomeException # fromException :: SomeException -> Maybe GRPCStatus # displayException :: GRPCStatus -> String # |
trailers :: GRPCStatus -> [(HeaderKey, HeaderValue)] Source #
Trailers for a GRPCStatus.
data InvalidGRPCStatus Source #
In case a server replies with a gRPC status/message pair un-understood by this library.
Constructors
InvalidGRPCStatus [(HeaderKey, HeaderValue)] |
Instances
readTrailers :: [(HeaderKey, HeaderValue)] -> Either InvalidGRPCStatus GRPCStatus Source #
Read a GRPCStatus
from HTTP2 trailers.
data RPC (s :: *) (m :: Symbol) Source #
A proxy type for giving static information about RPCs.
Constructors
RPC |
path :: (Service s, HasMethod s m) => RPC s m -> HeaderValue Source #
Returns the HTTP2 :path for a given RPC.
showTimeout :: Timeout -> HeaderValue Source #
type Authority = HeaderValue Source #
The HTTP2-Authority portion of an URL (e.g., "dicioccio.fr:7777").