Safe Haskell | None |
---|---|
Language | Haskell2010 |
Module for GRPC <> HTTP2 mapping.
Synopsis
- type HeaderKey = ByteString
- type HeaderValue = ByteString
- grpcTimeoutH :: HeaderKey
- grpcEncodingH :: HeaderKey
- grpcAcceptEncodingH :: HeaderKey
- grpcAcceptEncodingHVdefault :: HeaderValue
- grpcStatusH :: HeaderKey
- grpcMessageH :: HeaderKey
- grpcContentTypeHV :: HeaderValue
- grpcStatusHV :: HeaderValue
- grpcMessageHV :: HeaderValue
- data GRPCStatusCode
- trailerForStatusCode :: GRPCStatusCode -> ByteString
- type GRPCStatusMessage = ByteString
- data GRPCStatus = GRPCStatus !GRPCStatusCode !GRPCStatusMessage
- trailers :: GRPCStatus -> [(ByteString, ByteString)]
- data RPC (s :: *) (m :: Symbol) = RPC
- path :: (Service s, HasMethod s m) => RPC s m -> ByteString
- newtype Timeout = Timeout Int
- showTimeout :: Timeout -> ByteString
- type Authority = ByteString
Documentation
type HeaderKey = ByteString Source #
HTTP2 Header Key.
type HeaderValue = ByteString Source #
HTTP2 Header Value.
data GRPCStatusCode Source #
Instances
Eq GRPCStatusCode Source # | |
Defined in Network.GRPC.HTTP2.Types (==) :: GRPCStatusCode -> GRPCStatusCode -> Bool # (/=) :: GRPCStatusCode -> GRPCStatusCode -> Bool # | |
Ord GRPCStatusCode Source # | |
Defined in Network.GRPC.HTTP2.Types 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 showsPrec :: Int -> GRPCStatusCode -> ShowS # show :: GRPCStatusCode -> String # showList :: [GRPCStatusCode] -> ShowS # |
type GRPCStatusMessage = ByteString Source #
data GRPCStatus Source #
Instances
Eq GRPCStatus Source # | |
Defined in Network.GRPC.HTTP2.Types (==) :: GRPCStatus -> GRPCStatus -> Bool # (/=) :: GRPCStatus -> GRPCStatus -> Bool # | |
Ord GRPCStatus Source # | |
Defined in Network.GRPC.HTTP2.Types 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 showsPrec :: Int -> GRPCStatus -> ShowS # show :: GRPCStatus -> String # showList :: [GRPCStatus] -> ShowS # | |
Exception GRPCStatus Source # | |
Defined in Network.GRPC.HTTP2.Types toException :: GRPCStatus -> SomeException # fromException :: SomeException -> Maybe GRPCStatus # displayException :: GRPCStatus -> String # |
trailers :: GRPCStatus -> [(ByteString, ByteString)] Source #
path :: (Service s, HasMethod s m) => RPC s m -> ByteString Source #
Returns the HTTP2 :path for a given RPC.
showTimeout :: Timeout -> ByteString Source #
type Authority = ByteString Source #
The HTTP2-Authority portion of an URL (e.g., "dicioccio.fr:7777").