Safe Haskell | None |
---|---|
Language | Haskell2010 |
Network.GRPC.Spec
Description
Pure implementation of the gRPC spec
Most code will not need to use this module directly.
Intended for unqualified import.
Synopsis
- class (NFData (Input rpc), NFData (Output rpc), Show (Input rpc), Show (Output rpc), Show (RequestMetadata rpc), Show (ResponseInitialMetadata rpc), Show (ResponseTrailingMetadata rpc)) => IsRPC (rpc :: k) where
- rpcContentType :: Proxy rpc -> ByteString
- rpcServiceName :: Proxy rpc -> ByteString
- rpcMethodName :: Proxy rpc -> ByteString
- rpcMessageType :: Proxy rpc -> Maybe ByteString
- type family Input (rpc :: k)
- type family Output (rpc :: k)
- class (IsRPC rpc, BuildMetadata (RequestMetadata rpc), ParseMetadata (ResponseInitialMetadata rpc), ParseMetadata (ResponseTrailingMetadata rpc)) => SupportsClientRpc (rpc :: k) where
- rpcSerializeInput :: Proxy rpc -> Input rpc -> ByteString
- rpcDeserializeOutput :: Proxy rpc -> ByteString -> Either String (Output rpc)
- class (IsRPC rpc, ParseMetadata (RequestMetadata rpc), BuildMetadata (ResponseInitialMetadata rpc), StaticMetadata (ResponseTrailingMetadata rpc)) => SupportsServerRpc (rpc :: k) where
- rpcDeserializeInput :: Proxy rpc -> ByteString -> Either String (Input rpc)
- rpcSerializeOutput :: Proxy rpc -> Output rpc -> ByteString
- defaultRpcContentType :: ByteString -> ByteString
- data Protobuf serv (meth :: Symbol)
- newtype Proto msg = Proto msg
- getProto :: Proto msg -> msg
- data JsonRpc (serv :: Symbol) (meth :: Symbol)
- data JsonObject (a :: [(Symbol, Type)]) where
- JsonObject :: JsonObject ('[] :: [(Symbol, Type)])
- (:*) :: forall (f :: Symbol) x (fs :: [(Symbol, Type)]). x -> JsonObject fs -> JsonObject ('(f, x) ': fs)
- newtype Required a = Required {
- getRequired :: a
- newtype Optional a = Optional {
- getOptional :: Maybe a
- class DecodeFields (fs :: [(Symbol, Type)])
- class EncodeFields (fs :: [(Symbol, Type)])
- data RawRpc (serv :: Symbol) (meth :: Symbol)
- data StreamingType
- data SStreamingType (a :: StreamingType) where
- class ValidStreamingType (styp :: StreamingType) where
- validStreamingType :: Proxy styp -> SStreamingType styp
- class ValidStreamingType styp => SupportsStreamingType (rpc :: k) (styp :: StreamingType)
- class SupportsStreamingType rpc (RpcStreamingType rpc) => HasStreamingType (rpc :: k) where
- type RpcStreamingType (rpc :: k) :: StreamingType
- data NextElem a
- = NoNextElem
- | NextElem !a
- type Send a = NextElem a -> IO ()
- type Recv a = IO (NextElem a)
- type Positive (m :: k -> Type) a (b :: k) = a -> m b
- newtype Negative (m :: Type -> Type) a b = Negative {
- runNegative :: forall r. (a -> m r) -> m (b, r)
- data HandlerRole
- type family Handler (r :: HandlerRole) (s :: StreamingType) (m :: Type -> Type) (rpc :: k) where ...
- data ServerHandler' (styp :: StreamingType) (m :: Type -> Type) (rpc :: k) where
- ServerHandler :: forall {k} (rpc :: k) (styp :: StreamingType) (m :: Type -> Type). SupportsStreamingType rpc styp => Handler 'Server styp m rpc -> ServerHandler' styp m rpc
- type ServerHandler (m :: Type -> Type) (rpc :: k) = ServerHandler' (RpcStreamingType rpc) m rpc
- data ClientHandler' (s :: StreamingType) (m :: Type -> Type) (rpc :: k) where
- ClientHandler :: forall {k} (rpc :: k) (s :: StreamingType) (m :: Type -> Type). SupportsStreamingType rpc s => Handler 'Client s m rpc -> ClientHandler' s m rpc
- type ClientHandler (m :: Type -> Type) (rpc :: k) = ClientHandler' (RpcStreamingType rpc) m rpc
- hoistServerHandler :: forall {k} (styp :: StreamingType) m n (rpc :: k). ValidStreamingType styp => (forall a. m a -> n a) -> ServerHandler' styp m rpc -> ServerHandler' styp n rpc
- data CompressionId
- data Compression = Compression {}
- noCompression :: Compression
- gzip :: Compression
- allSupportedCompression :: NonEmpty Compression
- serializeCompressionId :: CompressionId -> ByteString
- deserializeCompressionId :: ByteString -> CompressionId
- data OutboundMeta = OutboundMeta {}
- data InboundMeta = InboundMeta {}
- data RequestHeaders_ (f :: Type -> Type) = RequestHeaders {
- requestTimeout :: HKD f (Maybe Timeout)
- requestCompression :: HKD f (Maybe CompressionId)
- requestAcceptCompression :: HKD f (Maybe (NonEmpty CompressionId))
- requestContentType :: HKD f (Maybe ContentType)
- requestMessageType :: HKD f (Maybe MessageType)
- requestUserAgent :: HKD f (Maybe ByteString)
- requestIncludeTE :: HKD f Bool
- requestTraceContext :: HKD f (Maybe TraceContext)
- requestPreviousRpcAttempts :: HKD f (Maybe Int)
- requestMetadata :: CustomMetadataMap
- requestUnrecognized :: HKD f ()
- type RequestHeaders = RequestHeaders_ Undecorated
- type RequestHeaders' e = RequestHeaders_ (Checked (InvalidHeaders e))
- data CallParams (rpc :: k)
- data PseudoHeaders = PseudoHeaders {}
- data ServerHeaders = ServerHeaders {}
- data ResourceHeaders = ResourceHeaders {}
- data Path = Path {}
- data Address = Address {}
- data Scheme
- data Method = Post
- rpcPath :: forall {k} (rpc :: k). IsRPC rpc => Proxy rpc -> Path
- data Timeout = Timeout TimeoutUnit TimeoutValue
- data TimeoutValue where
- pattern TimeoutValue :: Word -> TimeoutValue
- data TimeoutUnit
- = Hour
- | Minute
- | Second
- | Millisecond
- | Microsecond
- | Nanosecond
- timeoutToMicro :: Timeout -> Integer
- isValidTimeoutValue :: Word -> Bool
- data ResponseHeaders_ (f :: Type -> Type) = ResponseHeaders {}
- type ResponseHeaders = ResponseHeaders_ Undecorated
- type ResponseHeaders' e = ResponseHeaders_ (Checked (InvalidHeaders e))
- data ProperTrailers_ (f :: Type -> Type) = ProperTrailers {
- properTrailersGrpcStatus :: HKD f GrpcStatus
- properTrailersGrpcMessage :: HKD f (Maybe Text)
- properTrailersStatusDetails :: HKD f (Maybe ByteString)
- properTrailersPushback :: HKD f (Maybe Pushback)
- properTrailersOrcaLoadReport :: HKD f (Maybe OrcaLoadReport)
- properTrailersMetadata :: CustomMetadataMap
- properTrailersUnrecognized :: HKD f ()
- type ProperTrailers = ProperTrailers_ Undecorated
- type ProperTrailers' = ProperTrailers_ (Checked (InvalidHeaders GrpcException))
- data TrailersOnly_ (f :: Type -> Type) = TrailersOnly {}
- type TrailersOnly = TrailersOnly_ Undecorated
- type TrailersOnly' e = TrailersOnly_ (Checked (InvalidHeaders e))
- data Pushback
- simpleProperTrailers :: forall (f :: Type -> Type). ValidDecoration Applicative f => HKD f GrpcStatus -> HKD f (Maybe Text) -> HKD f (Maybe ByteString) -> CustomMetadataMap -> ProperTrailers_ f
- data GrpcNormalTermination = GrpcNormalTermination {}
- grpcExceptionToTrailers :: GrpcException -> ProperTrailers
- grpcClassifyTermination :: ProperTrailers' -> Either GrpcException GrpcNormalTermination
- properTrailersToTrailersOnly :: forall (f :: Type -> Type). (ProperTrailers_ f, HKD f (Maybe ContentType)) -> TrailersOnly_ f
- trailersOnlyToProperTrailers :: forall (f :: Type -> Type). TrailersOnly_ f -> (ProperTrailers_ f, HKD f (Maybe ContentType))
- data GrpcStatus
- data GrpcError
- fromGrpcStatus :: GrpcStatus -> Word
- fromGrpcError :: GrpcError -> Word
- toGrpcStatus :: Word -> Maybe GrpcStatus
- toGrpcError :: Word -> Maybe GrpcError
- data GrpcException = GrpcException {}
- throwGrpcError :: GrpcError -> IO a
- data Status
- data CustomMetadata where
- pattern CustomMetadata :: HasCallStack => HeaderName -> ByteString -> CustomMetadata
- customMetadataName :: CustomMetadata -> HeaderName
- customMetadataValue :: CustomMetadata -> ByteString
- safeCustomMetadata :: HeaderName -> ByteString -> Maybe CustomMetadata
- data HeaderName where
- pattern BinaryHeader :: HasCallStack => ByteString -> HeaderName
- pattern AsciiHeader :: HasCallStack => ByteString -> HeaderName
- safeHeaderName :: ByteString -> Maybe HeaderName
- isValidAsciiValue :: ByteString -> Bool
- data NoMetadata = NoMetadata
- data UnexpectedMetadata = UnexpectedMetadata [CustomMetadata]
- data CustomMetadataMap
- customMetadataMapFromList :: [CustomMetadata] -> CustomMetadataMap
- customMetadataMapToList :: CustomMetadataMap -> [CustomMetadata]
- customMetadataMapInsert :: CustomMetadata -> CustomMetadataMap -> CustomMetadataMap
- type family RequestMetadata (rpc :: k)
- type family ResponseInitialMetadata (rpc :: k)
- type family ResponseTrailingMetadata (rpc :: k)
- data ResponseMetadata (rpc :: k)
- class BuildMetadata a where
- buildMetadata :: a -> [CustomMetadata]
- class ParseMetadata a where
- parseMetadata :: MonadThrow m => [CustomMetadata] -> m a
- class BuildMetadata a => StaticMetadata a where
- metadataHeaderNames :: Proxy a -> [HeaderName]
- buildMetadataIO :: BuildMetadata a => a -> IO [CustomMetadata]
- newtype InvalidHeaders e = InvalidHeaders {
- getInvalidHeaders :: [InvalidHeader e]
- data InvalidHeader e
- invalidHeader :: Maybe Status -> Header -> String -> InvalidHeaders e
- missingHeader :: Maybe Status -> HeaderName -> InvalidHeaders e
- unexpectedHeader :: HeaderName -> InvalidHeaders e
- invalidHeaderSynthesize :: e -> InvalidHeader HandledSynthesized -> InvalidHeaders e
- throwInvalidHeader :: MonadError (InvalidHeaders e) m => Header -> Either String a -> m a
- data HandledSynthesized
- handledSynthesized :: HandledSynthesized -> a
- dropSynthesized :: InvalidHeaders e -> InvalidHeaders HandledSynthesized
- mapSynthesizedM :: Monad m => (e -> m e') -> InvalidHeaders e -> m (InvalidHeaders e')
- mapSynthesized :: (e -> e') -> InvalidHeaders e -> InvalidHeaders e'
- throwSynthesized :: (Traversable h, Monad m) => (forall a. GrpcException -> m a) -> h (Checked (InvalidHeaders GrpcException)) -> m (h (Checked (InvalidHeaders HandledSynthesized)))
- invalidHeaders :: InvalidHeaders e -> [Header]
- prettyInvalidHeaders :: InvalidHeaders HandledSynthesized -> Builder
- statusInvalidHeaders :: InvalidHeaders HandledSynthesized -> Status
- data ContentType
- chooseContentType :: forall {k} (rpc :: k). IsRPC rpc => Proxy rpc -> ContentType -> ByteString
- data MessageType
- chooseMessageType :: forall {k} (rpc :: k). IsRPC rpc => Proxy rpc -> MessageType -> Maybe ByteString
- data TraceContext = TraceContext {}
- newtype TraceId = TraceId {}
- newtype SpanId = SpanId {}
- data TraceOptions = TraceOptions {}
- data OrcaLoadReport
RPC
class (NFData (Input rpc), NFData (Output rpc), Show (Input rpc), Show (Output rpc), Show (RequestMetadata rpc), Show (ResponseInitialMetadata rpc), Show (ResponseTrailingMetadata rpc)) => IsRPC (rpc :: k) where Source #
Abstract definition of an RPC
Note on encoding: the gRPC specification does not say anything about text encoding issues for paths (service names and method names) or message types. The Protobuf compiler (by far the most common instantation of gRPC) does not allow for non-ASCII character at all ("interpreting non ascii codepoint"). We therefore punt on the encoding issue here, and use bytestrings. If applications want to use non-ASCII characters, they can choose their own encoding.
Methods
rpcContentType :: Proxy rpc -> ByteString Source #
Content-type
gRPC is agnostic to the message format; the spec defines the Content-Type
header as
Content-Type → "content-type" "application/grpc" [("+proto" / "+json" / {custom})]
defaultRpcContentType
can be used in the case that the format (such as
proto
) is known.
Note on terminology: throughout this codebase we avoid the terms "encoding" and "decoding", which can be ambiguous. Instead we use "serialize"/"deserialize" and "compress"/"decompress".
rpcServiceName :: Proxy rpc -> ByteString Source #
Service name
For Protobuf, this is the fully qualified service name.
rpcMethodName :: Proxy rpc -> ByteString Source #
Method name
For Protobuf, this is just the method name (no qualifier required).
rpcMessageType :: Proxy rpc -> Maybe ByteString Source #
Message type, if specified
This is used to set the (optional) grpc-message-type
header.
For Protobuf, this is the fully qualified message type.
Instances
type family Output (rpc :: k) Source #
Messages from the server to the client
class (IsRPC rpc, BuildMetadata (RequestMetadata rpc), ParseMetadata (ResponseInitialMetadata rpc), ParseMetadata (ResponseTrailingMetadata rpc)) => SupportsClientRpc (rpc :: k) where Source #
Client-side RPC
Methods
rpcSerializeInput :: Proxy rpc -> Input rpc -> ByteString Source #
Serialize RPC input
We don't ask for a builder here, but instead ask for the complete serialized form. gRPC insists that individual messages are length prefixed, so we must compute the full serialization in memory before we can send anything.
We use the terms "serialize" and "deserialize" here, and "compress"/"decompress" for compression, rather than "encode"/"decode", which could refer to either process.
rpcDeserializeOutput :: Proxy rpc -> ByteString -> Either String (Output rpc) Source #
Deserialize RPC output
Discussion of rpcDeserializeInput
applies here, also.
Instances
class (IsRPC rpc, ParseMetadata (RequestMetadata rpc), BuildMetadata (ResponseInitialMetadata rpc), StaticMetadata (ResponseTrailingMetadata rpc)) => SupportsServerRpc (rpc :: k) where Source #
Server-side RPC
Methods
rpcDeserializeInput :: Proxy rpc -> ByteString -> Either String (Input rpc) Source #
Deserialize RPC input
This function does not have to deal with compression or length prefixes, and can assume fully consume the given bytestring (if there are unconsumed bytes, this should be considered a parse failure).
rpcSerializeOutput :: Proxy rpc -> Output rpc -> ByteString Source #
Serialize RPC output
Instances
defaultRpcContentType :: ByteString -> ByteString Source #
Default content type string
This is equal to "application/grpc+format
for some format
such as
proto
or json
. See also rpcContentType
.
Instances
Protobuf
data Protobuf serv (meth :: Symbol) Source #
Protobuf RPC
This exists only as a type-level marker
Instances
Wrapper around Protobuf messages and Protobuf enums
Protobuf messages and enums behave differently to normal Haskell datatypes.
Fields in messages always have defaults, enums can have unknown values, etc.
We therefore mark them at the type-level with this Proto
wrapper. Most of
the time you can work with Proto
values as if the wrapper is not there,
because Proto msg
inherits Message
and Data.ProtoLens.Field
HasField
instances from msg
. For example, you can create a
'Proto Point' value as
p = defMessage & #latitude .~ .. & #longitude .~ ..
and access fields from such a value using
p ^. #latitude
as per usual.
One advantage of the Proto
wrapper is that we can give blanket instances
for all Protobuf messages; we use this to provide GHC.Records
HasField
and GHC.Records.Compat
HasField
instances.
This means that you can also use OverloadedRecordDot
to access fields
p.latitude
or even OverloadedRecordUpdate
to set fields
p{latitude = ..}
Constructors
Proto msg |
Instances
HasField (Proto rec) fldName fldType => HasField (fldName :: Symbol) (Proto rec) fldType Source # | |
Defined in Network.GRPC.Spec.RPC.Protobuf | |
HasField (Proto rec) fldName fldType => HasField (fldName :: Symbol) (Proto rec) fldType Source # | |
Defined in Network.GRPC.Spec.RPC.Protobuf | |
NFData msg => NFData (Proto msg) Source # | |
Defined in Network.GRPC.Spec.RPC.Protobuf | |
Bounded msg => Bounded (Proto msg) Source # | |
Enum msg => Enum (Proto msg) Source # | |
Defined in Network.GRPC.Spec.RPC.Protobuf Methods succ :: Proto msg -> Proto msg # pred :: Proto msg -> Proto msg # fromEnum :: Proto msg -> Int # enumFrom :: Proto msg -> [Proto msg] # enumFromThen :: Proto msg -> Proto msg -> [Proto msg] # enumFromTo :: Proto msg -> Proto msg -> [Proto msg] # enumFromThenTo :: Proto msg -> Proto msg -> Proto msg -> [Proto msg] # | |
Show msg => Show (Proto msg) Source # | |
Eq msg => Eq (Proto msg) Source # | |
Ord msg => Ord (Proto msg) Source # | |
FieldDefault msg => FieldDefault (Proto msg) Source # | |
Defined in Network.GRPC.Spec.RPC.Protobuf Methods fieldDefault :: Proto msg # | |
Message msg => Message (Proto msg) Source # | |
Defined in Network.GRPC.Spec.RPC.Protobuf Methods messageName :: Proxy (Proto msg) -> Text # packedMessageDescriptor :: Proxy (Proto msg) -> ByteString # packedFileDescriptor :: Proxy (Proto msg) -> ByteString # defMessage :: Proto msg # fieldsByTag :: Map Tag (FieldDescriptor (Proto msg)) # fieldsByTextFormatName :: Map String (FieldDescriptor (Proto msg)) # unknownFields :: Lens' (Proto msg) FieldSet # parseMessage :: Parser (Proto msg) # buildMessage :: Proto msg -> Builder # | |
MessageEnum msg => MessageEnum (Proto msg) Source # | |
(HasField rec fldName x, RewrapField (Describe x) x fldType) => HasField (Proto rec) fldName fldType Source # | |
JSON
data JsonRpc (serv :: Symbol) (meth :: Symbol) Source #
gRPC using JSON as the message encoding
"JSON over gRPC" is a bit of an ambiguous phrase. It can be a very general
term, simply meaning using an otherwise-unspecified JSON encoding, or it can
refer to "Protobuf over JSON" (see
https://protobuf.dev/programming-guides/proto3/#json). In this module we
deal with the former, and don't deal with anything Protobuf-specific at all,
nor do we rely on any of the infrastructure generated by the Protobuf
compiler (in other words, there is no need to use protoc
). See
https://grpc.io/blog/grpc-with-json/ for a Java example of using gRPC with
JSON without Protobuf.
In the absence of the infrastructure provided by protoc
, you will need to
manually provide Input
and Output
instances for each RPC you use.
For example:
type Create = JsonRpc KeyValueService "Create" type Delete = JsonRpc KeyValueService "Delete" .. type instance Input Create = .. type instance Output Create = .. type instance Input Retrieve = .. type instance Output Retrieve = .. ..
On the client, you will need ToJSON
instances for inputs and FromJSON
instances for outputs; on the server the situation is dual. You may find it
convenient to use JsonObject
(but this is certainly not required).
TODO: https://github.com/well-typed/grapesy/issues/166 We don't currently offer explicit support for "Protobuf JSON".
Instances
(KnownSymbol serv, KnownSymbol meth, NFData (Input (JsonRpc serv meth)), NFData (Output (JsonRpc serv meth)), Show (Input (JsonRpc serv meth)), Show (Output (JsonRpc serv meth)), Show (RequestMetadata (JsonRpc serv meth)), Show (ResponseInitialMetadata (JsonRpc serv meth)), Show (ResponseTrailingMetadata (JsonRpc serv meth))) => IsRPC (JsonRpc serv meth :: Type) Source # | |
Defined in Network.GRPC.Spec.RPC.JSON Methods rpcContentType :: Proxy (JsonRpc serv meth) -> ByteString Source # rpcServiceName :: Proxy (JsonRpc serv meth) -> ByteString Source # rpcMethodName :: Proxy (JsonRpc serv meth) -> ByteString Source # rpcMessageType :: Proxy (JsonRpc serv meth) -> Maybe ByteString Source # | |
(IsRPC (JsonRpc serv meth), ToJSON (Input (JsonRpc serv meth)), FromJSON (Output (JsonRpc serv meth)), BuildMetadata (RequestMetadata (JsonRpc serv meth)), ParseMetadata (ResponseInitialMetadata (JsonRpc serv meth)), ParseMetadata (ResponseTrailingMetadata (JsonRpc serv meth))) => SupportsClientRpc (JsonRpc serv meth :: Type) Source # | |
Defined in Network.GRPC.Spec.RPC.JSON Methods rpcSerializeInput :: Proxy (JsonRpc serv meth) -> Input (JsonRpc serv meth) -> ByteString Source # rpcDeserializeOutput :: Proxy (JsonRpc serv meth) -> ByteString -> Either String (Output (JsonRpc serv meth)) Source # | |
(IsRPC (JsonRpc serv meth), FromJSON (Input (JsonRpc serv meth)), ToJSON (Output (JsonRpc serv meth)), ParseMetadata (RequestMetadata (JsonRpc serv meth)), BuildMetadata (ResponseInitialMetadata (JsonRpc serv meth)), StaticMetadata (ResponseTrailingMetadata (JsonRpc serv meth))) => SupportsServerRpc (JsonRpc serv meth :: Type) Source # | |
Defined in Network.GRPC.Spec.RPC.JSON Methods rpcDeserializeInput :: Proxy (JsonRpc serv meth) -> ByteString -> Either String (Input (JsonRpc serv meth)) Source # rpcSerializeOutput :: Proxy (JsonRpc serv meth) -> Output (JsonRpc serv meth) -> ByteString Source # | |
ValidStreamingType styp => SupportsStreamingType (JsonRpc serv meth :: Type) styp Source # | For JSON protocol we do not check communication protocols |
Defined in Network.GRPC.Spec.RPC.JSON |
data JsonObject (a :: [(Symbol, Type)]) where Source #
Convenient way to construct JSON values
Example:
type instance Input Create = JsonObject '[ '("key" , Required Key) , '("value" , Required Value) ]
Constructors
JsonObject :: JsonObject ('[] :: [(Symbol, Type)]) | |
(:*) :: forall (f :: Symbol) x (fs :: [(Symbol, Type)]). x -> JsonObject fs -> JsonObject ('(f, x) ': fs) infixr 5 |
Instances
DecodeFields fs => FromJSON (JsonObject fs) Source # | |
Defined in Network.GRPC.Spec.RPC.JSON Methods parseJSON :: Value -> Parser (JsonObject fs) # parseJSONList :: Value -> Parser [JsonObject fs] # omittedField :: Maybe (JsonObject fs) # | |
EncodeFields fs => ToJSON (JsonObject fs) Source # | |
Defined in Network.GRPC.Spec.RPC.JSON Methods toJSON :: JsonObject fs -> Value # toEncoding :: JsonObject fs -> Encoding # toJSONList :: [JsonObject fs] -> Value # toEncodingList :: [JsonObject fs] -> Encoding # omitField :: JsonObject fs -> Bool # | |
(NFData x, NFData (JsonObject fs)) => NFData (JsonObject ('(f, x) ': fs)) Source # | |
Defined in Network.GRPC.Spec.RPC.JSON Methods rnf :: JsonObject ('(f, x) ': fs) -> () # | |
NFData (JsonObject ('[] :: [(Symbol, Type)])) Source # | |
Defined in Network.GRPC.Spec.RPC.JSON Methods rnf :: JsonObject ('[] :: [(Symbol, Type)]) -> () # | |
(Show x, Show (JsonObject fs)) => Show (JsonObject ('(f, x) ': fs)) Source # | |
Defined in Network.GRPC.Spec.RPC.JSON Methods showsPrec :: Int -> JsonObject ('(f, x) ': fs) -> ShowS # show :: JsonObject ('(f, x) ': fs) -> String # showList :: [JsonObject ('(f, x) ': fs)] -> ShowS # | |
Show (JsonObject ('[] :: [(Symbol, Type)])) Source # | |
Defined in Network.GRPC.Spec.RPC.JSON |
Required field
Constructors
Required | |
Fields
|
Instances
NFData a => NFData (Required a) Source # | |
Defined in Network.GRPC.Spec.RPC.JSON | |
Show a => Show (Required a) Source # | |
(KnownSymbol f, FromJSON x, DecodeFields fs) => DecodeFields ('(f, Required x) ': fs) Source # | |
Defined in Network.GRPC.Spec.RPC.JSON Methods decodeFields :: Object -> Parser (JsonObject ('(f, Required x) ': fs)) | |
(KnownSymbol f, ToJSON x, EncodeFields fs) => EncodeFields ('(f, Required x) ': fs) Source # | |
Defined in Network.GRPC.Spec.RPC.JSON Methods encodeFields :: JsonObject ('(f, Required x) ': fs) -> [Pair] |
Optional field
Maybe
will be represented by the absence of the field in the object.
Constructors
Optional | |
Fields
|
Instances
NFData a => NFData (Optional a) Source # | |
Defined in Network.GRPC.Spec.RPC.JSON | |
Show a => Show (Optional a) Source # | |
(KnownSymbol f, FromJSON x, DecodeFields fs) => DecodeFields ('(f, Optional x) ': fs) Source # | |
Defined in Network.GRPC.Spec.RPC.JSON Methods decodeFields :: Object -> Parser (JsonObject ('(f, Optional x) ': fs)) | |
(KnownSymbol f, ToJSON x, EncodeFields fs) => EncodeFields ('(f, Optional x) ': fs) Source # | |
Defined in Network.GRPC.Spec.RPC.JSON Methods encodeFields :: JsonObject ('(f, Optional x) ': fs) -> [Pair] |
class DecodeFields (fs :: [(Symbol, Type)]) Source #
Auxiliary class used for the FromJSON
instance for JsonObject
It is not possible (nor necessary) to define additional instances.
Instances
DecodeFields ('[] :: [(Symbol, Type)]) Source # | |
Defined in Network.GRPC.Spec.RPC.JSON Methods decodeFields :: Object -> Parser (JsonObject ('[] :: [(Symbol, Type)])) | |
(KnownSymbol f, FromJSON x, DecodeFields fs) => DecodeFields ('(f, Optional x) ': fs) Source # | |
Defined in Network.GRPC.Spec.RPC.JSON Methods decodeFields :: Object -> Parser (JsonObject ('(f, Optional x) ': fs)) | |
(KnownSymbol f, FromJSON x, DecodeFields fs) => DecodeFields ('(f, Required x) ': fs) Source # | |
Defined in Network.GRPC.Spec.RPC.JSON Methods decodeFields :: Object -> Parser (JsonObject ('(f, Required x) ': fs)) |
class EncodeFields (fs :: [(Symbol, Type)]) Source #
Auxiliary class used for the ToJSON
instance for JsonObject
It is not possible (nor necessary) to define additional instances.
Instances
EncodeFields ('[] :: [(Symbol, Type)]) Source # | |
Defined in Network.GRPC.Spec.RPC.JSON Methods encodeFields :: JsonObject ('[] :: [(Symbol, Type)]) -> [Pair] | |
(KnownSymbol f, ToJSON x, EncodeFields fs) => EncodeFields ('(f, Optional x) ': fs) Source # | |
Defined in Network.GRPC.Spec.RPC.JSON Methods encodeFields :: JsonObject ('(f, Optional x) ': fs) -> [Pair] | |
(KnownSymbol f, ToJSON x, EncodeFields fs) => EncodeFields ('(f, Required x) ': fs) Source # | |
Defined in Network.GRPC.Spec.RPC.JSON Methods encodeFields :: JsonObject ('(f, Required x) ': fs) -> [Pair] |
Raw
data RawRpc (serv :: Symbol) (meth :: Symbol) Source #
Custom gRPC format
Usually gRPC
runs over Protobuf, but it does not have to. RawRpc
provides
an alternative format, which does not use serialization/deserialization at
all, just using raw bytestrings for messages. This is a non-standard format
(which the gRPC specification explicitly permits).
Instances
(KnownSymbol serv, KnownSymbol meth, Show (RequestMetadata (RawRpc serv meth)), Show (ResponseInitialMetadata (RawRpc serv meth)), Show (ResponseTrailingMetadata (RawRpc serv meth))) => IsRPC (RawRpc serv meth :: Type) Source # | |
Defined in Network.GRPC.Spec.RPC.Raw Methods rpcContentType :: Proxy (RawRpc serv meth) -> ByteString Source # rpcServiceName :: Proxy (RawRpc serv meth) -> ByteString Source # rpcMethodName :: Proxy (RawRpc serv meth) -> ByteString Source # rpcMessageType :: Proxy (RawRpc serv meth) -> Maybe ByteString Source # | |
(IsRPC (RawRpc serv meth), BuildMetadata (RequestMetadata (RawRpc serv meth)), ParseMetadata (ResponseInitialMetadata (RawRpc serv meth)), ParseMetadata (ResponseTrailingMetadata (RawRpc serv meth))) => SupportsClientRpc (RawRpc serv meth :: Type) Source # | |
Defined in Network.GRPC.Spec.RPC.Raw Methods rpcSerializeInput :: Proxy (RawRpc serv meth) -> Input (RawRpc serv meth) -> ByteString Source # rpcDeserializeOutput :: Proxy (RawRpc serv meth) -> ByteString -> Either String (Output (RawRpc serv meth)) Source # | |
(IsRPC (RawRpc serv meth), ParseMetadata (RequestMetadata (RawRpc serv meth)), BuildMetadata (ResponseInitialMetadata (RawRpc serv meth)), StaticMetadata (ResponseTrailingMetadata (RawRpc serv meth))) => SupportsServerRpc (RawRpc serv meth :: Type) Source # | |
Defined in Network.GRPC.Spec.RPC.Raw Methods rpcDeserializeInput :: Proxy (RawRpc serv meth) -> ByteString -> Either String (Input (RawRpc serv meth)) Source # rpcSerializeOutput :: Proxy (RawRpc serv meth) -> Output (RawRpc serv meth) -> ByteString Source # | |
ValidStreamingType styp => SupportsStreamingType (RawRpc serv meth :: Type) styp Source # | For the raw protocol we do not check communication protocols |
Defined in Network.GRPC.Spec.RPC.Raw | |
type Input (RawRpc serv meth :: Type) Source # | |
Defined in Network.GRPC.Spec.RPC.Raw | |
type Output (RawRpc serv meth :: Type) Source # | |
Defined in Network.GRPC.Spec.RPC.Raw |
Streaming types
data StreamingType #
Data type to be used as a promoted type for MethodStreamingType
.
Constructors
NonStreaming | |
ClientStreaming | |
ServerStreaming | |
BiDiStreaming |
Instances
Bounded StreamingType | |
Defined in Data.ProtoLens.Service.Types | |
Enum StreamingType | |
Defined in Data.ProtoLens.Service.Types Methods succ :: StreamingType -> StreamingType # pred :: StreamingType -> StreamingType # toEnum :: Int -> StreamingType # fromEnum :: StreamingType -> Int # enumFrom :: StreamingType -> [StreamingType] # enumFromThen :: StreamingType -> StreamingType -> [StreamingType] # enumFromTo :: StreamingType -> StreamingType -> [StreamingType] # enumFromThenTo :: StreamingType -> StreamingType -> StreamingType -> [StreamingType] # | |
Read StreamingType | |
Defined in Data.ProtoLens.Service.Types Methods readsPrec :: Int -> ReadS StreamingType # readList :: ReadS [StreamingType] # | |
Show StreamingType | |
Defined in Data.ProtoLens.Service.Types Methods showsPrec :: Int -> StreamingType -> ShowS # show :: StreamingType -> String # showList :: [StreamingType] -> ShowS # | |
Eq StreamingType | |
Defined in Data.ProtoLens.Service.Types Methods (==) :: StreamingType -> StreamingType -> Bool # (/=) :: StreamingType -> StreamingType -> Bool # | |
Ord StreamingType | |
Defined in Data.ProtoLens.Service.Types Methods compare :: StreamingType -> StreamingType -> Ordering # (<) :: StreamingType -> StreamingType -> Bool # (<=) :: StreamingType -> StreamingType -> Bool # (>) :: StreamingType -> StreamingType -> Bool # (>=) :: StreamingType -> StreamingType -> Bool # max :: StreamingType -> StreamingType -> StreamingType # min :: StreamingType -> StreamingType -> StreamingType # |
data SStreamingType (a :: StreamingType) where Source #
Singleton for StreamingType
class ValidStreamingType (styp :: StreamingType) where Source #
Valid streaming types
Instances
ValidStreamingType 'BiDiStreaming Source # | |
Defined in Network.GRPC.Spec.RPC.StreamType Methods validStreamingType :: Proxy 'BiDiStreaming -> SStreamingType 'BiDiStreaming Source # | |
ValidStreamingType 'ClientStreaming Source # | |
Defined in Network.GRPC.Spec.RPC.StreamType Methods validStreamingType :: Proxy 'ClientStreaming -> SStreamingType 'ClientStreaming Source # | |
ValidStreamingType 'NonStreaming Source # | |
Defined in Network.GRPC.Spec.RPC.StreamType Methods validStreamingType :: Proxy 'NonStreaming -> SStreamingType 'NonStreaming Source # | |
ValidStreamingType 'ServerStreaming Source # | |
Defined in Network.GRPC.Spec.RPC.StreamType Methods validStreamingType :: Proxy 'ServerStreaming -> SStreamingType 'ServerStreaming Source # |
Link RPCs to streaming types
class ValidStreamingType styp => SupportsStreamingType (rpc :: k) (styp :: StreamingType) Source #
This RPC supports the given streaming type
This is a weaker condition than HasStreamingType
: some (non-Protobuf) RPCs
may support more than one streaming type.
Instances
ValidStreamingType styp => SupportsStreamingType (JsonRpc serv meth :: Type) styp Source # | For JSON protocol we do not check communication protocols |
Defined in Network.GRPC.Spec.RPC.JSON | |
(styp ~ MethodStreamingType serv meth, ValidStreamingType styp) => SupportsStreamingType (Protobuf serv meth :: Type) styp Source # | |
Defined in Network.GRPC.Spec.RPC.Protobuf | |
ValidStreamingType styp => SupportsStreamingType (RawRpc serv meth :: Type) styp Source # | For the raw protocol we do not check communication protocols |
Defined in Network.GRPC.Spec.RPC.Raw |
class SupportsStreamingType rpc (RpcStreamingType rpc) => HasStreamingType (rpc :: k) Source #
The streaming type supported by this RPC
Associated Types
type RpcStreamingType (rpc :: k) :: StreamingType Source #
The (single) streaming type supported by this RPC
Instances
ValidStreamingType (MethodStreamingType serv meth) => HasStreamingType (Protobuf serv meth :: Type) Source # | |||||
Defined in Network.GRPC.Spec.RPC.Protobuf Associated Types
|
Handler type definition
Is there a next element in a stream?
Constructors
NoNextElem | |
NextElem !a |
Instances
Functor NextElem Source # | |
Foldable NextElem Source # | |
Defined in Network.GRPC.Spec.RPC.StreamType Methods fold :: Monoid m => NextElem m -> m # foldMap :: Monoid m => (a -> m) -> NextElem a -> m # foldMap' :: Monoid m => (a -> m) -> NextElem a -> m # foldr :: (a -> b -> b) -> b -> NextElem a -> b # foldr' :: (a -> b -> b) -> b -> NextElem a -> b # foldl :: (b -> a -> b) -> b -> NextElem a -> b # foldl' :: (b -> a -> b) -> b -> NextElem a -> b # foldr1 :: (a -> a -> a) -> NextElem a -> a # foldl1 :: (a -> a -> a) -> NextElem a -> a # elem :: Eq a => a -> NextElem a -> Bool # maximum :: Ord a => NextElem a -> a # minimum :: Ord a => NextElem a -> a # | |
Traversable NextElem Source # | |
Defined in Network.GRPC.Spec.RPC.StreamType | |
Show a => Show (NextElem a) Source # | |
Eq a => Eq (NextElem a) Source # | |
newtype Negative (m :: Type -> Type) a b Source #
Negative use of a
Constructors
Negative | |
Fields
|
data HandlerRole Source #
Handler role
type family Handler (r :: HandlerRole) (s :: StreamingType) (m :: Type -> Type) (rpc :: k) where ... Source #
Type of a handler
Equations
Handler 'Server 'NonStreaming m (rpc :: k) = Input rpc -> m (Output rpc) | |
Handler 'Client 'NonStreaming m (rpc :: k) = Input rpc -> m (Output rpc) | |
Handler 'Server 'ClientStreaming m (rpc :: k) = Positive m (Recv (Input rpc)) (Output rpc) | |
Handler 'Client 'ClientStreaming m (rpc :: k) = Negative m (Send (Input rpc)) (Output rpc) | |
Handler 'Server 'ServerStreaming m (rpc :: k) = Input rpc -> Positive m (Send (Output rpc)) () | |
Handler 'Client 'ServerStreaming m (rpc :: k) = Input rpc -> Negative m (Recv (Output rpc)) () | |
Handler 'Server 'BiDiStreaming m (rpc :: k) = Positive m (Recv (Input rpc), Send (Output rpc)) () | |
Handler 'Client 'BiDiStreaming m (rpc :: k) = Negative m (Send (Input rpc), Recv (Output rpc)) () |
Handler newtype wrappers
data ServerHandler' (styp :: StreamingType) (m :: Type -> Type) (rpc :: k) where Source #
Wrapper around Handler Server
to avoid ambiguous types
Constructors
ServerHandler :: forall {k} (rpc :: k) (styp :: StreamingType) (m :: Type -> Type). SupportsStreamingType rpc styp => Handler 'Server styp m rpc -> ServerHandler' styp m rpc |
type ServerHandler (m :: Type -> Type) (rpc :: k) = ServerHandler' (RpcStreamingType rpc) m rpc Source #
Alias for ServerHandler'
with the streaming type determined by the rpc
data ClientHandler' (s :: StreamingType) (m :: Type -> Type) (rpc :: k) where Source #
Wrapper around Handler Client
to avoid ambiguous types
Constructors
ClientHandler :: forall {k} (rpc :: k) (s :: StreamingType) (m :: Type -> Type). SupportsStreamingType rpc s => Handler 'Client s m rpc -> ClientHandler' s m rpc |
type ClientHandler (m :: Type -> Type) (rpc :: k) = ClientHandler' (RpcStreamingType rpc) m rpc Source #
Alias for ClientHandler'
with the streaming type determined by the rpc
hoistServerHandler :: forall {k} (styp :: StreamingType) m n (rpc :: k). ValidStreamingType styp => (forall a. m a -> n a) -> ServerHandler' styp m rpc -> ServerHandler' styp n rpc Source #
Hoist server handler from one monad to another
Compression
data CompressionId Source #
Compression ID
The gRPC specification defines
Content-Coding → "identity" / "gzip" / "deflate" / "snappy" / {custom}
Instances
IsString CompressionId Source # | |||||
Defined in Network.GRPC.Spec.Compression Methods fromString :: String -> CompressionId # | |||||
Generic CompressionId Source # | |||||
Defined in Network.GRPC.Spec.Compression Associated Types
| |||||
Show CompressionId Source # | |||||
Defined in Network.GRPC.Spec.Compression Methods showsPrec :: Int -> CompressionId -> ShowS # show :: CompressionId -> String # showList :: [CompressionId] -> ShowS # | |||||
Eq CompressionId Source # | |||||
Defined in Network.GRPC.Spec.Compression Methods (==) :: CompressionId -> CompressionId -> Bool # (/=) :: CompressionId -> CompressionId -> Bool # | |||||
Ord CompressionId Source # | |||||
Defined in Network.GRPC.Spec.Compression Methods compare :: CompressionId -> CompressionId -> Ordering # (<) :: CompressionId -> CompressionId -> Bool # (<=) :: CompressionId -> CompressionId -> Bool # (>) :: CompressionId -> CompressionId -> Bool # (>=) :: CompressionId -> CompressionId -> Bool # max :: CompressionId -> CompressionId -> CompressionId # min :: CompressionId -> CompressionId -> CompressionId # | |||||
type Rep CompressionId Source # | |||||
Defined in Network.GRPC.Spec.Compression type Rep CompressionId = D1 ('MetaData "CompressionId" "Network.GRPC.Spec.Compression" "grpc-spec-1.0.0-inplace" 'False) ((C1 ('MetaCons "Identity" 'PrefixI 'False) (U1 :: Type -> Type) :+: C1 ('MetaCons "GZip" 'PrefixI 'False) (U1 :: Type -> Type)) :+: (C1 ('MetaCons "Deflate" 'PrefixI 'False) (U1 :: Type -> Type) :+: (C1 ('MetaCons "Snappy" 'PrefixI 'False) (U1 :: Type -> Type) :+: C1 ('MetaCons "Custom" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 String))))) |
data Compression Source #
Compression scheme
Constructors
Compression | |
Fields
|
Instances
Show Compression Source # | |
Defined in Network.GRPC.Spec.Compression Methods showsPrec :: Int -> Compression -> ShowS # show :: Compression -> String # showList :: [Compression] -> ShowS # |
noCompression :: Compression Source #
Disable compression (referred to as identity
in the gRPC spec)
gzip :: Compression Source #
gzip
allSupportedCompression :: NonEmpty Compression Source #
All supported compression algorithms supported
The order of this list is important: algorithms listed earlier are preferred over algorithms listed later.
serializeCompressionId :: CompressionId -> ByteString Source #
Serialize compression ID
deserializeCompressionId :: ByteString -> CompressionId Source #
Parse compression ID
Message metadata
data OutboundMeta Source #
Meta-information for outbound messages
Constructors
OutboundMeta | |
Fields
|
Instances
Default OutboundMeta Source # | |||||
Defined in Network.GRPC.Spec.MessageMeta Methods def :: OutboundMeta # | |||||
NFData OutboundMeta Source # | |||||
Defined in Network.GRPC.Spec.MessageMeta Methods rnf :: OutboundMeta -> () # | |||||
Generic OutboundMeta Source # | |||||
Defined in Network.GRPC.Spec.MessageMeta Associated Types
| |||||
Show OutboundMeta Source # | |||||
Defined in Network.GRPC.Spec.MessageMeta Methods showsPrec :: Int -> OutboundMeta -> ShowS # show :: OutboundMeta -> String # showList :: [OutboundMeta] -> ShowS # | |||||
type Rep OutboundMeta Source # | |||||
Defined in Network.GRPC.Spec.MessageMeta type Rep OutboundMeta = D1 ('MetaData "OutboundMeta" "Network.GRPC.Spec.MessageMeta" "grpc-spec-1.0.0-inplace" 'False) (C1 ('MetaCons "OutboundMeta" 'PrefixI 'True) (S1 ('MetaSel ('Just "outboundEnableCompression") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 Bool))) |
data InboundMeta Source #
Meta-information about inbound messages
Constructors
InboundMeta | |
Fields
|
Instances
Show InboundMeta Source # | |
Defined in Network.GRPC.Spec.MessageMeta Methods showsPrec :: Int -> InboundMeta -> ShowS # show :: InboundMeta -> String # showList :: [InboundMeta] -> ShowS # |
Requests
data RequestHeaders_ (f :: Type -> Type) Source #
Full set of call parameters required to construct the RPC call
This is constructed internally; it is not part of the public API.
Constructors
RequestHeaders | |
Fields
|
Instances
Generic RequestHeaders Source # | |||||
Defined in Network.GRPC.Spec.Headers.Request Associated Types
Methods from :: RequestHeaders -> Rep RequestHeaders x # to :: Rep RequestHeaders x -> RequestHeaders # | |||||
Show RequestHeaders Source # | |||||
Defined in Network.GRPC.Spec.Headers.Request Methods showsPrec :: Int -> RequestHeaders -> ShowS # show :: RequestHeaders -> String # showList :: [RequestHeaders] -> ShowS # | |||||
Eq RequestHeaders Source # | |||||
Defined in Network.GRPC.Spec.Headers.Request Methods (==) :: RequestHeaders -> RequestHeaders -> Bool # (/=) :: RequestHeaders -> RequestHeaders -> Bool # | |||||
Coerce RequestHeaders_ Source # | |||||
Defined in Network.GRPC.Spec.Headers.Request | |||||
Traversable RequestHeaders_ Source # | |||||
Defined in Network.GRPC.Spec.Headers.Request Methods traverse :: Applicative m => (forall a. f a -> m (g a)) -> RequestHeaders_ (DecoratedWith f) -> m (RequestHeaders_ (DecoratedWith g)) Source # | |||||
Show e => Show (RequestHeaders' e) Source # | |||||
Defined in Network.GRPC.Spec.Headers.Request Methods showsPrec :: Int -> RequestHeaders' e -> ShowS # show :: RequestHeaders' e -> String # showList :: [RequestHeaders' e] -> ShowS # | |||||
Eq e => Eq (RequestHeaders' e) Source # | |||||
Defined in Network.GRPC.Spec.Headers.Request Methods (==) :: RequestHeaders' e -> RequestHeaders' e -> Bool # (/=) :: RequestHeaders' e -> RequestHeaders' e -> Bool # | |||||
type Rep (RequestHeaders_ Undecorated) Source # | |||||
Defined in Network.GRPC.Spec.Headers.Request type Rep (RequestHeaders_ Undecorated) = D1 ('MetaData "RequestHeaders_" "Network.GRPC.Spec.Headers.Request" "grpc-spec-1.0.0-inplace" 'False) (C1 ('MetaCons "RequestHeaders" 'PrefixI 'True) (((S1 ('MetaSel ('Just "requestTimeout") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (HKD Undecorated (Maybe Timeout))) :*: S1 ('MetaSel ('Just "requestCompression") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (HKD Undecorated (Maybe CompressionId)))) :*: (S1 ('MetaSel ('Just "requestAcceptCompression") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (HKD Undecorated (Maybe (NonEmpty CompressionId)))) :*: (S1 ('MetaSel ('Just "requestContentType") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (HKD Undecorated (Maybe ContentType))) :*: S1 ('MetaSel ('Just "requestMessageType") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (HKD Undecorated (Maybe MessageType)))))) :*: ((S1 ('MetaSel ('Just "requestUserAgent") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (HKD Undecorated (Maybe ByteString))) :*: (S1 ('MetaSel ('Just "requestIncludeTE") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (HKD Undecorated Bool)) :*: S1 ('MetaSel ('Just "requestTraceContext") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (HKD Undecorated (Maybe TraceContext))))) :*: (S1 ('MetaSel ('Just "requestPreviousRpcAttempts") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (HKD Undecorated (Maybe Int))) :*: (S1 ('MetaSel ('Just "requestMetadata") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 CustomMetadataMap) :*: S1 ('MetaSel ('Just "requestUnrecognized") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (HKD Undecorated ()))))))) |
type RequestHeaders = RequestHeaders_ Undecorated Source #
Request headers (without allowing for invalid headers)
NOTE: The HKD type
RequestHeaders_ Undecorated
means that each field of type HKD f a
is simply of type a
(that is,
undecorated).
type RequestHeaders' e = RequestHeaders_ (Checked (InvalidHeaders e)) Source #
Request headers allowing for invalid headers
NOTE: The HKD type
RequestHeaders_ (Checked InvalidHeaders)
means that each field of type HKD f a
is of type
Either InvalidHeaders a
(i.e., either valid or invalid).
See InvalidHeaderSynthesize
for an explanation of the e
parameter.
Parameters
data CallParams (rpc :: k) Source #
RPC parameters that can be chosen on a per-call basis
Instances
Default (RequestMetadata rpc) => Default (CallParams rpc) Source # | Default |
Defined in Network.GRPC.Spec.Call Methods def :: CallParams rpc # | |
Show (RequestMetadata rpc) => Show (CallParams rpc) Source # | |
Defined in Network.GRPC.Spec.Call Methods showsPrec :: Int -> CallParams rpc -> ShowS # show :: CallParams rpc -> String # showList :: [CallParams rpc] -> ShowS # |
Pseudo-headers
data PseudoHeaders Source #
All pseudo-headers
Constructors
PseudoHeaders | |
Fields |
Instances
Show PseudoHeaders Source # | |
Defined in Network.GRPC.Spec.Headers.PseudoHeaders Methods showsPrec :: Int -> PseudoHeaders -> ShowS # show :: PseudoHeaders -> String # showList :: [PseudoHeaders] -> ShowS # |
data ServerHeaders Source #
Partial pseudo headers: identify the server, but not a specific resource
Constructors
ServerHeaders | |
Fields |
Instances
Show ServerHeaders Source # | |
Defined in Network.GRPC.Spec.Headers.PseudoHeaders Methods showsPrec :: Int -> ServerHeaders -> ShowS # show :: ServerHeaders -> String # showList :: [ServerHeaders] -> ShowS # |
data ResourceHeaders Source #
Request pseudo-methods
https://datatracker.ietf.org/doc/html/rfc7540#section-8.1.2.3
Constructors
ResourceHeaders | |
Fields
|
Instances
Show ResourceHeaders Source # | |
Defined in Network.GRPC.Spec.Headers.PseudoHeaders Methods showsPrec :: Int -> ResourceHeaders -> ShowS # show :: ResourceHeaders -> String # showList :: [ResourceHeaders] -> ShowS # |
Path
The gRPC spec specifies:
Path → ":path" "/" Service-Name "/" {method name} # But see note below.
Moreover, it says:
Path is case-sensitive. Some gRPC implementations may allow the Path format shown above to be overridden, but this functionality is strongly discouraged. gRPC does not go out of its way to break users that are using this kind of override, but we do not actively support it, and some functionality (e.g., service config support) will not work when the path is not of the form shown above.
We don't support these non-standard paths at all.
Constructors
Path | |
Fields |
Address
The address of a server to connect to. This is not standard gRPC nomenclature, but follows convention such as adopted by grpcurl and grpc-client-cli, which distinguish between the address of a server to connect to (hostname and port), and the (optional) HTTP authority, which is an (optional) string to be included as the HTTP2 :authority pseudo-header.
Constructors
Address | |
Fields
|
Method
The only method supported by gRPC is POST
.
See also https://datatracker.ietf.org/doc/html/rfc7231#section-4.
Constructors
Post |
Timeouts
Timeout
Constructors
Timeout TimeoutUnit TimeoutValue |
Instances
Generic Timeout Source # | |||||
Defined in Network.GRPC.Spec.Timeout Associated Types
| |||||
Show Timeout Source # | |||||
Eq Timeout Source # | |||||
type Rep Timeout Source # | |||||
Defined in Network.GRPC.Spec.Timeout type Rep Timeout = D1 ('MetaData "Timeout" "Network.GRPC.Spec.Timeout" "grpc-spec-1.0.0-inplace" 'False) (C1 ('MetaCons "Timeout" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 TimeoutUnit) :*: S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 TimeoutValue))) |
data TimeoutValue where Source #
Positive integer with ASCII representation of at most 8 digits
Bundled Patterns
pattern TimeoutValue :: Word -> TimeoutValue |
Instances
Generic TimeoutValue Source # | |||||
Defined in Network.GRPC.Spec.Timeout Associated Types
| |||||
Show TimeoutValue Source # |
| ||||
Defined in Network.GRPC.Spec.Timeout Methods showsPrec :: Int -> TimeoutValue -> ShowS # show :: TimeoutValue -> String # showList :: [TimeoutValue] -> ShowS # | |||||
Eq TimeoutValue Source # | |||||
Defined in Network.GRPC.Spec.Timeout | |||||
type Rep TimeoutValue Source # | |||||
Defined in Network.GRPC.Spec.Timeout type Rep TimeoutValue = D1 ('MetaData "TimeoutValue" "Network.GRPC.Spec.Timeout" "grpc-spec-1.0.0-inplace" 'True) (C1 ('MetaCons "UnsafeTimeoutValue" 'PrefixI 'True) (S1 ('MetaSel ('Just "getTimeoutValue") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 Word))) |
data TimeoutUnit Source #
Timeout unit
Constructors
Hour | Hours |
Minute | Minutes |
Second | Seconds |
Millisecond | Milliseconds |
Microsecond | Microseconds |
Nanosecond | Nanoseconds Although some servers may be able to interpret this in a meaningful way, we cannot, and round this up to the nearest microsecond. |
Instances
Generic TimeoutUnit Source # | |||||
Defined in Network.GRPC.Spec.Timeout Associated Types
| |||||
Show TimeoutUnit Source # | |||||
Defined in Network.GRPC.Spec.Timeout Methods showsPrec :: Int -> TimeoutUnit -> ShowS # show :: TimeoutUnit -> String # showList :: [TimeoutUnit] -> ShowS # | |||||
Eq TimeoutUnit Source # | |||||
Defined in Network.GRPC.Spec.Timeout | |||||
type Rep TimeoutUnit Source # | |||||
Defined in Network.GRPC.Spec.Timeout type Rep TimeoutUnit = D1 ('MetaData "TimeoutUnit" "Network.GRPC.Spec.Timeout" "grpc-spec-1.0.0-inplace" 'False) ((C1 ('MetaCons "Hour" 'PrefixI 'False) (U1 :: Type -> Type) :+: (C1 ('MetaCons "Minute" 'PrefixI 'False) (U1 :: Type -> Type) :+: C1 ('MetaCons "Second" 'PrefixI 'False) (U1 :: Type -> Type))) :+: (C1 ('MetaCons "Millisecond" 'PrefixI 'False) (U1 :: Type -> Type) :+: (C1 ('MetaCons "Microsecond" 'PrefixI 'False) (U1 :: Type -> Type) :+: C1 ('MetaCons "Nanosecond" 'PrefixI 'False) (U1 :: Type -> Type)))) |
timeoutToMicro :: Timeout -> Integer Source #
Translate Timeout
to microseconds
For Nanosecond
timeout we round up.
Note: the choice of Integer
for the result is important: timeouts can be
quite long, and might easily exceed the range of a 32-bit int: 2^31
microseconds is roughly 35 minutes (on 64-bit architectures this is much less
important; 2^63
microseconds is 292,277.2 years). We could use Int64
or
Word64
, but Integer
works nicely with the unbounded-delays
package.
isValidTimeoutValue :: Word -> Bool Source #
Valid timeout values
Timeout values cannot exceed 8 digits. If you need a longer timeout, consider
using a different TimeoutUnit
instead.
Responses
Headers
data ResponseHeaders_ (f :: Type -> Type) Source #
Response headers
Constructors
ResponseHeaders | |
Fields
|
Instances
Generic ResponseHeaders Source # | |||||
Defined in Network.GRPC.Spec.Headers.Response Associated Types
Methods from :: ResponseHeaders -> Rep ResponseHeaders x # to :: Rep ResponseHeaders x -> ResponseHeaders # | |||||
Show ResponseHeaders Source # | |||||
Defined in Network.GRPC.Spec.Headers.Response Methods showsPrec :: Int -> ResponseHeaders -> ShowS # show :: ResponseHeaders -> String # showList :: [ResponseHeaders] -> ShowS # | |||||
Eq ResponseHeaders Source # | |||||
Defined in Network.GRPC.Spec.Headers.Response Methods (==) :: ResponseHeaders -> ResponseHeaders -> Bool # (/=) :: ResponseHeaders -> ResponseHeaders -> Bool # | |||||
Coerce ResponseHeaders_ Source # | |||||
Defined in Network.GRPC.Spec.Headers.Response | |||||
Traversable ResponseHeaders_ Source # | |||||
Defined in Network.GRPC.Spec.Headers.Response Methods traverse :: Applicative m => (forall a. f a -> m (g a)) -> ResponseHeaders_ (DecoratedWith f) -> m (ResponseHeaders_ (DecoratedWith g)) Source # | |||||
Show e => Show (ResponseHeaders_ (Checked e)) Source # | |||||
Defined in Network.GRPC.Spec.Headers.Response | |||||
Eq e => Eq (ResponseHeaders_ (Checked e)) Source # | |||||
Defined in Network.GRPC.Spec.Headers.Response Methods (==) :: ResponseHeaders_ (Checked e) -> ResponseHeaders_ (Checked e) -> Bool # (/=) :: ResponseHeaders_ (Checked e) -> ResponseHeaders_ (Checked e) -> Bool # | |||||
type Rep (ResponseHeaders_ Undecorated) Source # | |||||
Defined in Network.GRPC.Spec.Headers.Response type Rep (ResponseHeaders_ Undecorated) = D1 ('MetaData "ResponseHeaders_" "Network.GRPC.Spec.Headers.Response" "grpc-spec-1.0.0-inplace" 'False) (C1 ('MetaCons "ResponseHeaders" 'PrefixI 'True) ((S1 ('MetaSel ('Just "responseCompression") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (HKD Undecorated (Maybe CompressionId))) :*: S1 ('MetaSel ('Just "responseAcceptCompression") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (HKD Undecorated (Maybe (NonEmpty CompressionId))))) :*: (S1 ('MetaSel ('Just "responseContentType") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (HKD Undecorated (Maybe ContentType))) :*: (S1 ('MetaSel ('Just "responseMetadata") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 CustomMetadataMap) :*: S1 ('MetaSel ('Just "responseUnrecognized") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (HKD Undecorated ())))))) |
type ResponseHeaders = ResponseHeaders_ Undecorated Source #
Response headers (without allowing for invalid headers)
See RequestHeaders
for an explanation of Undecorated
.
type ResponseHeaders' e = ResponseHeaders_ (Checked (InvalidHeaders e)) Source #
Response headers allowing for invalid headers
See RequestHeaders'
for an explanation of Checked
and
the purpose of e
.
Trailers
data ProperTrailers_ (f :: Type -> Type) Source #
Information sent by the peer after the final output
Response trailers are a HTTP2 concept: they are HTTP headers that are sent after the content body. For example, imagine the server is streaming a file that it's reading from disk; it could use trailers to give the client an MD5 checksum when streaming is complete.
Constructors
ProperTrailers | |
Fields
|
Instances
Generic ProperTrailers Source # | |||||
Defined in Network.GRPC.Spec.Headers.Response Associated Types
Methods from :: ProperTrailers -> Rep ProperTrailers x # to :: Rep ProperTrailers x -> ProperTrailers # | |||||
Show ProperTrailers Source # | |||||
Defined in Network.GRPC.Spec.Headers.Response Methods showsPrec :: Int -> ProperTrailers -> ShowS # show :: ProperTrailers -> String # showList :: [ProperTrailers] -> ShowS # | |||||
Eq ProperTrailers Source # | |||||
Defined in Network.GRPC.Spec.Headers.Response Methods (==) :: ProperTrailers -> ProperTrailers -> Bool # (/=) :: ProperTrailers -> ProperTrailers -> Bool # | |||||
Coerce ProperTrailers_ Source # | |||||
Defined in Network.GRPC.Spec.Headers.Response | |||||
Traversable ProperTrailers_ Source # | |||||
Defined in Network.GRPC.Spec.Headers.Response Methods traverse :: Applicative m => (forall a. f a -> m (g a)) -> ProperTrailers_ (DecoratedWith f) -> m (ProperTrailers_ (DecoratedWith g)) Source # | |||||
Show e => Show (ProperTrailers_ (Checked e)) Source # | |||||
Defined in Network.GRPC.Spec.Headers.Response | |||||
Eq e => Eq (ProperTrailers_ (Checked e)) Source # | |||||
Defined in Network.GRPC.Spec.Headers.Response Methods (==) :: ProperTrailers_ (Checked e) -> ProperTrailers_ (Checked e) -> Bool # (/=) :: ProperTrailers_ (Checked e) -> ProperTrailers_ (Checked e) -> Bool # | |||||
type Rep (ProperTrailers_ Undecorated) Source # | |||||
Defined in Network.GRPC.Spec.Headers.Response type Rep (ProperTrailers_ Undecorated) = D1 ('MetaData "ProperTrailers_" "Network.GRPC.Spec.Headers.Response" "grpc-spec-1.0.0-inplace" 'False) (C1 ('MetaCons "ProperTrailers" 'PrefixI 'True) ((S1 ('MetaSel ('Just "properTrailersGrpcStatus") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (HKD Undecorated GrpcStatus)) :*: (S1 ('MetaSel ('Just "properTrailersGrpcMessage") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (HKD Undecorated (Maybe Text))) :*: S1 ('MetaSel ('Just "properTrailersStatusDetails") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (HKD Undecorated (Maybe ByteString))))) :*: ((S1 ('MetaSel ('Just "properTrailersPushback") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (HKD Undecorated (Maybe Pushback))) :*: S1 ('MetaSel ('Just "properTrailersOrcaLoadReport") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (HKD Undecorated (Maybe OrcaLoadReport)))) :*: (S1 ('MetaSel ('Just "properTrailersMetadata") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 CustomMetadataMap) :*: S1 ('MetaSel ('Just "properTrailersUnrecognized") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (HKD Undecorated ())))))) |
type ProperTrailers = ProperTrailers_ Undecorated Source #
Trailers sent after the response (without allowing for invalid trailers)
type ProperTrailers' = ProperTrailers_ (Checked (InvalidHeaders GrpcException)) Source #
Trailers sent after the response, allowing for invalid trailers
We do not parameterize this over the type of synthesized errors: unlike response (or request) headers, we have no opportunity to check the trailers for synthesized errors ahead of time, so having a type to signal "trailers without synthesized errors" is not particularly useful.
data TrailersOnly_ (f :: Type -> Type) Source #
Trailers sent in the gRPC Trailers-Only case
We deal with the HTTP status elsewhere.
Constructors
TrailersOnly | |
Fields
|
Instances
Generic TrailersOnly Source # | |||||
Defined in Network.GRPC.Spec.Headers.Response Associated Types
| |||||
Show TrailersOnly Source # | |||||
Defined in Network.GRPC.Spec.Headers.Response Methods showsPrec :: Int -> TrailersOnly -> ShowS # show :: TrailersOnly -> String # showList :: [TrailersOnly] -> ShowS # | |||||
Eq TrailersOnly Source # | |||||
Defined in Network.GRPC.Spec.Headers.Response | |||||
Coerce TrailersOnly_ Source # | |||||
Defined in Network.GRPC.Spec.Headers.Response Methods undecorate :: TrailersOnly_ (DecoratedWith Identity) -> TrailersOnly_ Undecorated Source # decorate :: TrailersOnly_ Undecorated -> TrailersOnly_ (DecoratedWith Identity) Source # | |||||
Traversable TrailersOnly_ Source # | |||||
Defined in Network.GRPC.Spec.Headers.Response Methods traverse :: Applicative m => (forall a. f a -> m (g a)) -> TrailersOnly_ (DecoratedWith f) -> m (TrailersOnly_ (DecoratedWith g)) Source # | |||||
Show e => Show (TrailersOnly_ (Checked e)) Source # | |||||
Defined in Network.GRPC.Spec.Headers.Response | |||||
Eq e => Eq (TrailersOnly_ (Checked e)) Source # | |||||
Defined in Network.GRPC.Spec.Headers.Response Methods (==) :: TrailersOnly_ (Checked e) -> TrailersOnly_ (Checked e) -> Bool # (/=) :: TrailersOnly_ (Checked e) -> TrailersOnly_ (Checked e) -> Bool # | |||||
type Rep (TrailersOnly_ Undecorated) Source # | |||||
Defined in Network.GRPC.Spec.Headers.Response type Rep (TrailersOnly_ Undecorated) = D1 ('MetaData "TrailersOnly_" "Network.GRPC.Spec.Headers.Response" "grpc-spec-1.0.0-inplace" 'False) (C1 ('MetaCons "TrailersOnly" 'PrefixI 'True) (S1 ('MetaSel ('Just "trailersOnlyContentType") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (HKD Undecorated (Maybe ContentType))) :*: S1 ('MetaSel ('Just "trailersOnlyProper") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (ProperTrailers_ Undecorated)))) |
type TrailersOnly = TrailersOnly_ Undecorated Source #
Trailers for the Trailers-Only case (without allowing for invalid trailers)
type TrailersOnly' e = TrailersOnly_ (Checked (InvalidHeaders e)) Source #
Trailers for the Trailers-Only case, allowing for invalid headers
Pushback
The server adds this header to push back against client retries. We do not yet support automatic retries (https://github.com/well-typed/grapesy/issues/104), but do we parse this header so that if the server includes it, we do not throw a parser error.
See also https://github.com/grpc/proposal/blob/master/A6-client-retries.md
Constructors
RetryAfter Word | |
DoNotRetry |
Instances
Generic Pushback Source # | |||||
Defined in Network.GRPC.Spec.Headers.Response Associated Types
| |||||
Show Pushback Source # | |||||
Eq Pushback Source # | |||||
type Rep Pushback Source # | |||||
Defined in Network.GRPC.Spec.Headers.Response type Rep Pushback = D1 ('MetaData "Pushback" "Network.GRPC.Spec.Headers.Response" "grpc-spec-1.0.0-inplace" 'False) (C1 ('MetaCons "RetryAfter" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 Word)) :+: C1 ('MetaCons "DoNotRetry" 'PrefixI 'False) (U1 :: Type -> Type)) |
simpleProperTrailers :: forall (f :: Type -> Type). ValidDecoration Applicative f => HKD f GrpcStatus -> HKD f (Maybe Text) -> HKD f (Maybe ByteString) -> CustomMetadataMap -> ProperTrailers_ f Source #
Default constructor for ProperTrailers
Termination
data GrpcNormalTermination Source #
Server indicated normal termination
This is only an exception if the client tries to send any further messages.
Constructors
GrpcNormalTermination | |
Fields |
Instances
Exception GrpcNormalTermination Source # | |
Defined in Network.GRPC.Spec.Headers.Response | |
Show GrpcNormalTermination Source # | |
Defined in Network.GRPC.Spec.Headers.Response Methods showsPrec :: Int -> GrpcNormalTermination -> ShowS # show :: GrpcNormalTermination -> String # showList :: [GrpcNormalTermination] -> ShowS # |
grpcExceptionToTrailers :: GrpcException -> ProperTrailers Source #
Translate gRPC exception to response trailers
grpcClassifyTermination :: ProperTrailers' -> Either GrpcException GrpcNormalTermination Source #
Check if trailers correspond to an exceptional response
The gRPC spec states that
Trailers-Only is permitted for calls that produce an immediate error
However, in practice gRPC servers can also respond with Trailers-Only
in
non-error cases, simply indicating that the server considers the
conversation over. To distinguish, we look at properTrailersGrpcStatus
.
properTrailersToTrailersOnly :: forall (f :: Type -> Type). (ProperTrailers_ f, HKD f (Maybe ContentType)) -> TrailersOnly_ f Source #
ProperTrailers
is a subset of TrailersOnly
trailersOnlyToProperTrailers :: forall (f :: Type -> Type). TrailersOnly_ f -> (ProperTrailers_ f, HKD f (Maybe ContentType)) Source #
TrailersOnly
is a superset of ProperTrailers
Status
data GrpcStatus Source #
gRPC status
Defined in https://github.com/grpc/grpc/blob/master/doc/statuscodes.md.
Instances
Generic GrpcStatus Source # | |||||
Defined in Network.GRPC.Spec.Status Associated Types
| |||||
Show GrpcStatus Source # | |||||
Defined in Network.GRPC.Spec.Status Methods showsPrec :: Int -> GrpcStatus -> ShowS # show :: GrpcStatus -> String # showList :: [GrpcStatus] -> ShowS # | |||||
Eq GrpcStatus Source # | |||||
Defined in Network.GRPC.Spec.Status | |||||
type Rep GrpcStatus Source # | |||||
Defined in Network.GRPC.Spec.Status type Rep GrpcStatus = D1 ('MetaData "GrpcStatus" "Network.GRPC.Spec.Status" "grpc-spec-1.0.0-inplace" 'False) (C1 ('MetaCons "GrpcOk" 'PrefixI 'False) (U1 :: Type -> Type) :+: C1 ('MetaCons "GrpcError" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 GrpcError))) |
gRPC error code
This is a subset of the gRPC status codes. See GrpcStatus
.
Constructors
GrpcCancelled | Cancelled The operation was cancelled, typically by the caller. |
GrpcUnknown | Unknown error For example, this error may be returned when a |
GrpcInvalidArgument | Invalid argument The client specified an invalid argument. Note that this differs from
|
GrpcDeadlineExceeded | Deadline exceeded The deadline expired before the operation could complete. For operations that change the state of the system, this error may be returned even if the operation has completed successfully. For example, a successful response from a server could have been delayed long. |
GrpcNotFound | Not found Some requested entity (e.g., file or directory) was not found. Note to server developers: if a request is denied for an entire class of
users, such as gradual feature rollout or undocumented allowlist,
If a request is denied for some users within a class of users, such as
user-based access control, |
GrpcAlreadyExists | Already exists The entity that a client attempted to create (e.g., file or directory) already exists. |
GrpcPermissionDenied | Permission denied The caller does not have permission to execute the specified operation.
This error code does not imply the request is valid or the requested entity exists or satisfies other pre-conditions. |
GrpcResourceExhausted | Resource exhausted Some resource has been exhausted, perhaps a per-user quota, or perhaps the entire file system is out of space. |
GrpcFailedPrecondition | Failed precondition The operation was rejected because the system is not in a state required for the operation's execution. For example, the directory to be deleted is non-empty, an rmdir operation is applied to a non-directory, etc. Service implementors can use the following guidelines to decide between
(a) Use |
GrpcAborted | Aborted The operation was aborted, typically due to a concurrency issue such as a
sequencer check failure or transaction abort. See the guidelines above
for deciding between |
GrpcOutOfRange | Out of range The operation was attempted past the valid range. E.g., seeking or reading past end-of-file. Unlike There is a fair bit of overlap between |
GrpcUnimplemented | Unimplemented The operation is not implemented or is not supported/enabled in this service. |
GrpcInternal | Internal errors This means that some invariants expected by the underlying system have been broken. This error code is reserved for serious errors. |
GrpcUnavailable | Unavailable The service is currently unavailable. This is most likely a transient condition, which can be corrected by retrying with a backoff. Note that it is not always safe to retry non-idempotent operations. |
GrpcDataLoss | Data loss Unrecoverable data loss or corruption. |
GrpcUnauthenticated | Unauthenticated The request does not have valid authentication credentials for the operation. |
Instances
Exception GrpcError Source # | |||||
Defined in Network.GRPC.Spec.Status Methods toException :: GrpcError -> SomeException # fromException :: SomeException -> Maybe GrpcError # displayException :: GrpcError -> String # backtraceDesired :: GrpcError -> Bool # | |||||
Generic GrpcError Source # | |||||
Defined in Network.GRPC.Spec.Status Associated Types
| |||||
Show GrpcError Source # | |||||
Eq GrpcError Source # | |||||
Ord GrpcError Source # | |||||
type Rep GrpcError Source # | |||||
Defined in Network.GRPC.Spec.Status type Rep GrpcError = D1 ('MetaData "GrpcError" "Network.GRPC.Spec.Status" "grpc-spec-1.0.0-inplace" 'False) ((((C1 ('MetaCons "GrpcCancelled" 'PrefixI 'False) (U1 :: Type -> Type) :+: C1 ('MetaCons "GrpcUnknown" 'PrefixI 'False) (U1 :: Type -> Type)) :+: (C1 ('MetaCons "GrpcInvalidArgument" 'PrefixI 'False) (U1 :: Type -> Type) :+: C1 ('MetaCons "GrpcDeadlineExceeded" 'PrefixI 'False) (U1 :: Type -> Type))) :+: ((C1 ('MetaCons "GrpcNotFound" 'PrefixI 'False) (U1 :: Type -> Type) :+: C1 ('MetaCons "GrpcAlreadyExists" 'PrefixI 'False) (U1 :: Type -> Type)) :+: (C1 ('MetaCons "GrpcPermissionDenied" 'PrefixI 'False) (U1 :: Type -> Type) :+: C1 ('MetaCons "GrpcResourceExhausted" 'PrefixI 'False) (U1 :: Type -> Type)))) :+: (((C1 ('MetaCons "GrpcFailedPrecondition" 'PrefixI 'False) (U1 :: Type -> Type) :+: C1 ('MetaCons "GrpcAborted" 'PrefixI 'False) (U1 :: Type -> Type)) :+: (C1 ('MetaCons "GrpcOutOfRange" 'PrefixI 'False) (U1 :: Type -> Type) :+: C1 ('MetaCons "GrpcUnimplemented" 'PrefixI 'False) (U1 :: Type -> Type))) :+: ((C1 ('MetaCons "GrpcInternal" 'PrefixI 'False) (U1 :: Type -> Type) :+: C1 ('MetaCons "GrpcUnavailable" 'PrefixI 'False) (U1 :: Type -> Type)) :+: (C1 ('MetaCons "GrpcDataLoss" 'PrefixI 'False) (U1 :: Type -> Type) :+: C1 ('MetaCons "GrpcUnauthenticated" 'PrefixI 'False) (U1 :: Type -> Type))))) |
Numerical status codes
fromGrpcStatus :: GrpcStatus -> Word Source #
Translate GrpcStatus
to numerical status code
See https://grpc.github.io/grpc/core/md_doc_statuscodes.html
fromGrpcError :: GrpcError -> Word Source #
Translate GrpcError
to numerical status code
See also fromGrpcStatus
toGrpcStatus :: Word -> Maybe GrpcStatus Source #
Inverse to fromGrpcStatus
toGrpcError :: Word -> Maybe GrpcError Source #
Inverse to fromGrpcError
Exceptions
data GrpcException Source #
Server indicated a gRPC error
For the common case where you just want to set grpcError
, you can use
throwGrpcError
.
Constructors
GrpcException | |
Fields |
Instances
Exception GrpcException Source # | |
Defined in Network.GRPC.Spec.Status Methods toException :: GrpcException -> SomeException # fromException :: SomeException -> Maybe GrpcException # displayException :: GrpcException -> String # backtraceDesired :: GrpcException -> Bool # | |
Show GrpcException Source # | |
Defined in Network.GRPC.Spec.Status Methods showsPrec :: Int -> GrpcException -> ShowS # show :: GrpcException -> String # showList :: [GrpcException] -> ShowS # | |
Eq GrpcException Source # | |
Defined in Network.GRPC.Spec.Status Methods (==) :: GrpcException -> GrpcException -> Bool # (/=) :: GrpcException -> GrpcException -> Bool # |
throwGrpcError :: GrpcError -> IO a Source #
Convenience function to throw an GrpcException
with the specified error
Details
Fields :
code
:: Lens' Status Data.Int.Int32
message
:: Lens' Status Data.Text.Text
details
:: Lens' Status [Proto.Google.Protobuf.Any.Any]
vec'details
:: Lens' Status (Data.Vector.Vector Proto.Google.Protobuf.Any.Any)
Instances
NFData Status Source # | |
Defined in Proto.Status | |
Show Status Source # | |
Eq Status Source # | |
Ord Status Source # | |
Message Status Source # | |
Defined in Proto.Status Methods messageName :: Proxy Status -> Text # packedMessageDescriptor :: Proxy Status -> ByteString # packedFileDescriptor :: Proxy Status -> ByteString # defMessage :: Status # fieldsByTag :: Map Tag (FieldDescriptor Status) # fieldsByTextFormatName :: Map String (FieldDescriptor Status) # unknownFields :: Lens' Status FieldSet # parseMessage :: Parser Status # buildMessage :: Status -> Builder # | |
HasField Status "code" Int32 Source # | |
HasField Status "message" Text Source # | |
HasField Status "details" [Any] Source # | |
HasField Status "vec'details" (Vector Any) Source # | |
Metadata
data CustomMetadata where Source #
Custom metadata
This is an arbitrary set of key-value pairs defined by the application layer.
Custom metadata 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.
Bundled Patterns
pattern CustomMetadata :: HasCallStack => HeaderName -> ByteString -> CustomMetadata |
Instances
NFData CustomMetadata Source # | |||||
Defined in Network.GRPC.Spec.CustomMetadata.Raw Methods rnf :: CustomMetadata -> () # | |||||
Generic CustomMetadata Source # | |||||
Defined in Network.GRPC.Spec.CustomMetadata.Raw Associated Types
Methods from :: CustomMetadata -> Rep CustomMetadata x # to :: Rep CustomMetadata x -> CustomMetadata # | |||||
Show CustomMetadata Source # |
| ||||
Defined in Network.GRPC.Spec.CustomMetadata.Raw Methods showsPrec :: Int -> CustomMetadata -> ShowS # show :: CustomMetadata -> String # showList :: [CustomMetadata] -> ShowS # | |||||
Eq CustomMetadata Source # | |||||
Defined in Network.GRPC.Spec.CustomMetadata.Raw Methods (==) :: CustomMetadata -> CustomMetadata -> Bool # (/=) :: CustomMetadata -> CustomMetadata -> Bool # | |||||
type Rep CustomMetadata Source # | |||||
Defined in Network.GRPC.Spec.CustomMetadata.Raw type Rep CustomMetadata = D1 ('MetaData "CustomMetadata" "Network.GRPC.Spec.CustomMetadata.Raw" "grpc-spec-1.0.0-inplace" 'False) (C1 ('MetaCons "UnsafeCustomMetadata" 'PrefixI 'True) (S1 ('MetaSel ('Just "customMetadataName") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 HeaderName) :*: S1 ('MetaSel ('Just "customMetadataValue") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 ByteString))) |
customMetadataName :: CustomMetadata -> HeaderName Source #
Header name
The header name determines if this is an ASCII header or a binary
header; see the CustomMetadata
pattern synonym.
customMetadataValue :: CustomMetadata -> ByteString Source #
Header value
safeCustomMetadata :: HeaderName -> ByteString -> Maybe CustomMetadata Source #
Construct CustomMetadata
Returns Nothing
if the HeaderName
indicates an ASCII header but the
value is not valid ASCII (consider using a binary header instead).
data HeaderName where Source #
Header name
To construct a HeaderName
, you can either use the IsString
instance
"foo" :: HeaderName -- an ASCII header "bar-bin" :: HeaderName -- a binary header
or alternatively use the AsciiHeader
and BinaryHeader
patterns
AsciiHeader "foo" BinaryHeader "bar-bin"
The latter style is more explicit, and can catch more errors:
AsciiHeader "foo-bin" -- exception: unexpected -bin suffix BinaryHeader "bar" -- exception: expected -bin suffix
Header names cannot be empty, and must consist of digits (0-9
), lowercase
letters (a-z
), underscore (_
), hyphen (-
), or period (.
).
Reserved header names are disallowed.
See also safeHeaderName
.
Bundled Patterns
pattern BinaryHeader :: HasCallStack => ByteString -> HeaderName | |
pattern AsciiHeader :: HasCallStack => ByteString -> HeaderName |
Instances
NFData HeaderName Source # | |||||
Defined in Network.GRPC.Spec.CustomMetadata.Raw Methods rnf :: HeaderName -> () # | |||||
IsString HeaderName Source # | |||||
Defined in Network.GRPC.Spec.CustomMetadata.Raw Methods fromString :: String -> HeaderName # | |||||
Generic HeaderName Source # | |||||
Defined in Network.GRPC.Spec.CustomMetadata.Raw Associated Types
| |||||
Show HeaderName Source # | |||||
Defined in Network.GRPC.Spec.CustomMetadata.Raw Methods showsPrec :: Int -> HeaderName -> ShowS # show :: HeaderName -> String # showList :: [HeaderName] -> ShowS # | |||||
Eq HeaderName Source # | |||||
Defined in Network.GRPC.Spec.CustomMetadata.Raw | |||||
Ord HeaderName Source # | |||||
Defined in Network.GRPC.Spec.CustomMetadata.Raw Methods compare :: HeaderName -> HeaderName -> Ordering # (<) :: HeaderName -> HeaderName -> Bool # (<=) :: HeaderName -> HeaderName -> Bool # (>) :: HeaderName -> HeaderName -> Bool # (>=) :: HeaderName -> HeaderName -> Bool # max :: HeaderName -> HeaderName -> HeaderName # min :: HeaderName -> HeaderName -> HeaderName # | |||||
type Rep HeaderName Source # | |||||
Defined in Network.GRPC.Spec.CustomMetadata.Raw type Rep HeaderName = D1 ('MetaData "HeaderName" "Network.GRPC.Spec.CustomMetadata.Raw" "grpc-spec-1.0.0-inplace" 'False) (C1 ('MetaCons "UnsafeBinaryHeader" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 ByteString)) :+: C1 ('MetaCons "UnsafeAsciiHeader" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 ByteString))) |
safeHeaderName :: ByteString -> Maybe HeaderName Source #
Check for header name validity
We choose between BinaryHeader
and AsciiHeader
based on the presence or
absence of a @-bin suffix.
isValidAsciiValue :: ByteString -> Bool Source #
Check for valid ASCII header value
ASCII-Value → 1*( %x20-%x7E ) ; space and printable ASCII
NOTE: By rights this should verify that the header is non-empty. However, empty header values do occasionally show up, and so we permit them. The main reason for checking for validity at all is to ensure that we don't confuse binary headers and ASCII headers.
data NoMetadata Source #
Indicate the absence of custom metadata
NOTE: The ParseMetadata
instance for NoMetadata
throws an exception if
any metadata is present (that is, metadata is not silently ignored).
Constructors
NoMetadata |
Instances
Default NoMetadata Source # | |
Defined in Network.GRPC.Spec.CustomMetadata.NoMetadata Methods def :: NoMetadata # | |
Show NoMetadata Source # | |
Defined in Network.GRPC.Spec.CustomMetadata.NoMetadata Methods showsPrec :: Int -> NoMetadata -> ShowS # show :: NoMetadata -> String # showList :: [NoMetadata] -> ShowS # | |
Eq NoMetadata Source # | |
Defined in Network.GRPC.Spec.CustomMetadata.NoMetadata | |
BuildMetadata NoMetadata Source # | |
Defined in Network.GRPC.Spec.CustomMetadata.NoMetadata Methods buildMetadata :: NoMetadata -> [CustomMetadata] Source # | |
ParseMetadata NoMetadata Source # | |
Defined in Network.GRPC.Spec.CustomMetadata.NoMetadata Methods parseMetadata :: MonadThrow m => [CustomMetadata] -> m NoMetadata Source # | |
StaticMetadata NoMetadata Source # | |
Defined in Network.GRPC.Spec.CustomMetadata.NoMetadata Methods metadataHeaderNames :: Proxy NoMetadata -> [HeaderName] Source # |
data UnexpectedMetadata Source #
Unexpected metadata
This exception can be thrown in ParseMetadata
instances. See ParseMetadata
for discussion.
Constructors
UnexpectedMetadata [CustomMetadata] |
Instances
Exception UnexpectedMetadata Source # | |
Defined in Network.GRPC.Spec.CustomMetadata.Typed Methods toException :: UnexpectedMetadata -> SomeException # fromException :: SomeException -> Maybe UnexpectedMetadata # | |
Show UnexpectedMetadata Source # | |
Defined in Network.GRPC.Spec.CustomMetadata.Typed Methods showsPrec :: Int -> UnexpectedMetadata -> ShowS # show :: UnexpectedMetadata -> String # showList :: [UnexpectedMetadata] -> ShowS # |
Handling of duplicate metadata entries
data CustomMetadataMap Source #
Map from header names to values
The gRPC spec mandates
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.
Internally we don't allow for these duplicates, but instead join the headers as mandated by the spec.
Instances
Monoid CustomMetadataMap Source # | |||||
Defined in Network.GRPC.Spec.CustomMetadata.Map Methods mappend :: CustomMetadataMap -> CustomMetadataMap -> CustomMetadataMap # mconcat :: [CustomMetadataMap] -> CustomMetadataMap # | |||||
Semigroup CustomMetadataMap Source # | |||||
Defined in Network.GRPC.Spec.CustomMetadata.Map Methods (<>) :: CustomMetadataMap -> CustomMetadataMap -> CustomMetadataMap # sconcat :: NonEmpty CustomMetadataMap -> CustomMetadataMap # stimes :: Integral b => b -> CustomMetadataMap -> CustomMetadataMap # | |||||
Generic CustomMetadataMap Source # | |||||
Defined in Network.GRPC.Spec.CustomMetadata.Map Associated Types
Methods from :: CustomMetadataMap -> Rep CustomMetadataMap x # to :: Rep CustomMetadataMap x -> CustomMetadataMap # | |||||
Show CustomMetadataMap Source # | |||||
Defined in Network.GRPC.Spec.CustomMetadata.Map Methods showsPrec :: Int -> CustomMetadataMap -> ShowS # show :: CustomMetadataMap -> String # showList :: [CustomMetadataMap] -> ShowS # | |||||
Eq CustomMetadataMap Source # | |||||
Defined in Network.GRPC.Spec.CustomMetadata.Map Methods (==) :: CustomMetadataMap -> CustomMetadataMap -> Bool # (/=) :: CustomMetadataMap -> CustomMetadataMap -> Bool # | |||||
type Rep CustomMetadataMap Source # | |||||
Defined in Network.GRPC.Spec.CustomMetadata.Map type Rep CustomMetadataMap = D1 ('MetaData "CustomMetadataMap" "Network.GRPC.Spec.CustomMetadata.Map" "grpc-spec-1.0.0-inplace" 'True) (C1 ('MetaCons "CustomMetadataMap" 'PrefixI 'True) (S1 ('MetaSel ('Just "getCustomMetadataMap") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (Map HeaderName ByteString)))) |
customMetadataMapFromList :: [CustomMetadata] -> CustomMetadataMap Source #
Construct CustomMetadataMap
, joining duplicates
customMetadataMapToList :: CustomMetadataMap -> [CustomMetadata] Source #
Flatten CustomMetadataMap
to a list
Precondition: the map must be valid.
customMetadataMapInsert :: CustomMetadata -> CustomMetadataMap -> CustomMetadataMap Source #
Insert value into CustomMetadataMap
If a header with the same name already exists, the value is appended to (the end of) the existing value.
Typed
type family RequestMetadata (rpc :: k) Source #
Metadata included in the request
Often you can give a blanket metadata definition for all methods in a service. For example:
type instance RequestMetadata (Protobuf RouteGuide meth) = NoMetadata type instance ResponseInitialMetadata (Protobuf RouteGuide meth) = NoMetadata type instance ResponseTrailingMetadata (Protobuf RouteGuide meth) = NoMetadata
If you want to give specific types of metadata for specific methods but not for others, it can sometimes be useful to introduce an auxiliary closed type, so that you can give a catch-all case. For example:
type instance ResponseInitialMetadata (Protobuf Greeter meth) = GreeterResponseInitialMetadata meth type family GreeterResponseInitialMetadata (meth :: Symbol) where GreeterResponseInitialMetadata "sayHelloStreamReply" = SayHelloMetadata GreeterResponseInitialMetadata meth = NoMetadata
type family ResponseInitialMetadata (rpc :: k) Source #
Metadata included in the initial response
See RequestMetadata
for discussion.
type family ResponseTrailingMetadata (rpc :: k) Source #
Metadata included in the response trailers
See RequestMetadata
for discussion.
data ResponseMetadata (rpc :: k) Source #
Response metadata
It occassionally happens that we do not know if we should expect the initial
metadata from the server or the trailing metadata (when the server uses
Trailers-Only); for example, see
recvResponseInitialMetadata
.
Constructors
ResponseInitialMetadata (ResponseInitialMetadata rpc) | |
ResponseTrailingMetadata (ResponseTrailingMetadata rpc) |
Instances
(Show (ResponseInitialMetadata rpc), Show (ResponseTrailingMetadata rpc)) => Show (ResponseMetadata rpc) Source # | |
Defined in Network.GRPC.Spec.CustomMetadata.Typed Methods showsPrec :: Int -> ResponseMetadata rpc -> ShowS # show :: ResponseMetadata rpc -> String # showList :: [ResponseMetadata rpc] -> ShowS # | |
(Eq (ResponseInitialMetadata rpc), Eq (ResponseTrailingMetadata rpc)) => Eq (ResponseMetadata rpc) Source # | |
Defined in Network.GRPC.Spec.CustomMetadata.Typed Methods (==) :: ResponseMetadata rpc -> ResponseMetadata rpc -> Bool # (/=) :: ResponseMetadata rpc -> ResponseMetadata rpc -> Bool # |
Serialization
class BuildMetadata a where Source #
Serialize metadata to custom metadata headers
Methods
buildMetadata :: a -> [CustomMetadata] Source #
Instances
BuildMetadata NoMetadata Source # | |
Defined in Network.GRPC.Spec.CustomMetadata.NoMetadata Methods buildMetadata :: NoMetadata -> [CustomMetadata] Source # |
class ParseMetadata a where Source #
Parse metadata from custom metadata headers
Some guidelines for defining instances:
- You can assume that the list of headers will not contain duplicates. The
gRPC spec does allow for duplicate headers and specifies how to process
them, but this will be taken care of before
parseMetadata
is called. - However, you should assume no particular order.
- If there are unexpected headers present, you have a choice whether you want to consider this a error and throw an exception, or regard the additional headers as merely additional information and simply ignore them. There is no single right answer here: ignoring additional metadata runs the risk of not realizing that the peer is trying to tell you something important, but throwing an error runs the risk of unnecessarily aborting an RPC.
Methods
parseMetadata :: MonadThrow m => [CustomMetadata] -> m a Source #
Instances
ParseMetadata NoMetadata Source # | |
Defined in Network.GRPC.Spec.CustomMetadata.NoMetadata Methods parseMetadata :: MonadThrow m => [CustomMetadata] -> m NoMetadata Source # |
class BuildMetadata a => StaticMetadata a where Source #
Metadata with statically known fields
This is required for the response trailing metadata. When the server sends
the initial set of headers to the client, it must tell the client which
trailers to expect (by means of the HTTP Trailer
header; see
https://datatracker.ietf.org/doc/html/rfc7230#section-4.4).
Any headers constructed in buildMetadata
must be listed here; not doing
so is a bug. However, the converse is not true: it is acceptable for a header
to be listed in metadataHeaderNames
but not in buildMetadata
. Put another
way: the list of "trailers to expect" included in the initial request headers
is allowed to be an overapproximation, but not an underapproximation.
Methods
metadataHeaderNames :: Proxy a -> [HeaderName] Source #
Instances
StaticMetadata NoMetadata Source # | |
Defined in Network.GRPC.Spec.CustomMetadata.NoMetadata Methods metadataHeaderNames :: Proxy NoMetadata -> [HeaderName] Source # |
buildMetadataIO :: BuildMetadata a => a -> IO [CustomMetadata] Source #
Wrapper around buildMetadata
that catches any pure exceptions
These pure exceptions can arise when invalid headers are generated (for example, ASCII headers with non-ASCII values).
Invalid headers
newtype InvalidHeaders e Source #
Invalid headers
This is used for request headers, response headers, and response trailers.
Constructors
InvalidHeaders | |
Fields
|
Instances
Monoid (InvalidHeaders e) Source # | |
Defined in Network.GRPC.Spec.Headers.Invalid Methods mempty :: InvalidHeaders e # mappend :: InvalidHeaders e -> InvalidHeaders e -> InvalidHeaders e # mconcat :: [InvalidHeaders e] -> InvalidHeaders e # | |
Semigroup (InvalidHeaders e) Source # | |
Defined in Network.GRPC.Spec.Headers.Invalid Methods (<>) :: InvalidHeaders e -> InvalidHeaders e -> InvalidHeaders e # sconcat :: NonEmpty (InvalidHeaders e) -> InvalidHeaders e # stimes :: Integral b => b -> InvalidHeaders e -> InvalidHeaders e # | |
Show e => Show (InvalidHeaders e) Source # | |
Defined in Network.GRPC.Spec.Headers.Invalid Methods showsPrec :: Int -> InvalidHeaders e -> ShowS # show :: InvalidHeaders e -> String # showList :: [InvalidHeaders e] -> ShowS # | |
Show e => Show (RequestHeaders' e) Source # | |
Defined in Network.GRPC.Spec.Headers.Request Methods showsPrec :: Int -> RequestHeaders' e -> ShowS # show :: RequestHeaders' e -> String # showList :: [RequestHeaders' e] -> ShowS # | |
Eq e => Eq (InvalidHeaders e) Source # | |
Defined in Network.GRPC.Spec.Headers.Invalid Methods (==) :: InvalidHeaders e -> InvalidHeaders e -> Bool # (/=) :: InvalidHeaders e -> InvalidHeaders e -> Bool # | |
Eq e => Eq (RequestHeaders' e) Source # | |
Defined in Network.GRPC.Spec.Headers.Request Methods (==) :: RequestHeaders' e -> RequestHeaders' e -> Bool # (/=) :: RequestHeaders' e -> RequestHeaders' e -> Bool # |
data InvalidHeader e Source #
Invalid header
This corresponds to a single "raw" HTTP header. It is possible that a
particular field of, say, RequestHeaders
corresponds to multiple InvalidHeader
, when the value of that field is
determined by combining multiple HTTP headers. A special case of this is the
field for unrecognized headers (see
requestUnrecognized
,
responseUnrecognized
, etc.), which
collects all unrecognized headers in one field (and has value ()
if there
are none).
For some invalid headers the gRPC spec mandates a specific HTTP status; if this status is not specified, then we use 400 Bad Request.
Constructors
InvalidHeader (Maybe Status) Header String | We failed to parse this header We record the original header and the reason parsing failed. |
MissingHeader (Maybe Status) HeaderName | Missing header (header that should have been present but was not) |
UnexpectedHeader HeaderName | Unexpected header (header that should not have been present but was) |
InvalidHeaderSynthesize e (InvalidHeader HandledSynthesized) | Synthesize gRPC exception This will be instantiated to We record both the actual error and the synthesized error. |
Instances
Show e => Show (InvalidHeader e) Source # | |
Defined in Network.GRPC.Spec.Headers.Invalid Methods showsPrec :: Int -> InvalidHeader e -> ShowS # show :: InvalidHeader e -> String # showList :: [InvalidHeader e] -> ShowS # | |
Eq e => Eq (InvalidHeader e) Source # | |
Defined in Network.GRPC.Spec.Headers.Invalid Methods (==) :: InvalidHeader e -> InvalidHeader e -> Bool # (/=) :: InvalidHeader e -> InvalidHeader e -> Bool # |
Construction
invalidHeader :: Maybe Status -> Header -> String -> InvalidHeaders e Source #
Convenience constructor around InvalidHeader
missingHeader :: Maybe Status -> HeaderName -> InvalidHeaders e Source #
Convenience constructor around MissingHeader
unexpectedHeader :: HeaderName -> InvalidHeaders e Source #
Convenience constructor around UnexpectedHeader
invalidHeaderSynthesize :: e -> InvalidHeader HandledSynthesized -> InvalidHeaders e Source #
Convenience constructor around InvalidHeaderSynthesize
throwInvalidHeader :: MonadError (InvalidHeaders e) m => Header -> Either String a -> m a Source #
Convenience function for throwing an invalidHeader
exception.
Synthesized errors
data HandledSynthesized Source #
Indicate that all synthesized errors have been handled
For some headers the gRPC spec mandates a specific gRPC error that should
be synthesized when the header is invalid. We use HandledSynthesized
in types to indicate that all errors that should have been synthesized have
already been thrown.
For example, RequestHeaders'
HandledSynthesized
indicates that these request headers may still contain errors for some
headers, but no errors for which the spec mandates that we synthesize a
specific gRPC exception.
Instances
Show HandledSynthesized Source # | |
Defined in Network.GRPC.Spec.Headers.Invalid Methods showsPrec :: Int -> HandledSynthesized -> ShowS # show :: HandledSynthesized -> String # showList :: [HandledSynthesized] -> ShowS # | |
Eq HandledSynthesized Source # | |
Defined in Network.GRPC.Spec.Headers.Invalid Methods (==) :: HandledSynthesized -> HandledSynthesized -> Bool # (/=) :: HandledSynthesized -> HandledSynthesized -> Bool # |
handledSynthesized :: HandledSynthesized -> a Source #
Evidence that HandledSynthesized
is an empty type
dropSynthesized :: InvalidHeaders e -> InvalidHeaders HandledSynthesized Source #
Drop all synthesized errors, leaving just the original
mapSynthesizedM :: Monad m => (e -> m e') -> InvalidHeaders e -> m (InvalidHeaders e') Source #
Map over the errors
mapSynthesized :: (e -> e') -> InvalidHeaders e -> InvalidHeaders e' Source #
Pure version of mapSynthesizedM
throwSynthesized :: (Traversable h, Monad m) => (forall a. GrpcException -> m a) -> h (Checked (InvalidHeaders GrpcException)) -> m (h (Checked (InvalidHeaders HandledSynthesized))) Source #
Throw all synthesized errors
After this we are guaranteed that the synthesized errors have been handlded.
Use
invalidHeaders :: InvalidHeaders e -> [Header] Source #
Extract all invalid headers
statusInvalidHeaders :: InvalidHeaders HandledSynthesized -> Status Source #
HTTP status to report
If there are multiple headers, each of which with a mandated status, we just use the first; the spec is essentially ambiguous in this case.
Common infrastructure to all headers
data ContentType Source #
Content type
Constructors
ContentTypeDefault | The default content type for this RPC This is given by |
ContentTypeOverride ByteString | Override the content type Depending on the choice of override, this may or may not be conform spec. See https://datatracker.ietf.org/doc/html/rfc2045#section-5 for a spec of the Content-Type header; the gRPC spec however disallows most of what is technically allowed by this RPC. |
Instances
Default ContentType Source # | |||||
Defined in Network.GRPC.Spec.Headers.Common Methods def :: ContentType # | |||||
Generic ContentType Source # | |||||
Defined in Network.GRPC.Spec.Headers.Common Associated Types
| |||||
Show ContentType Source # | |||||
Defined in Network.GRPC.Spec.Headers.Common Methods showsPrec :: Int -> ContentType -> ShowS # show :: ContentType -> String # showList :: [ContentType] -> ShowS # | |||||
Eq ContentType Source # | |||||
Defined in Network.GRPC.Spec.Headers.Common | |||||
type Rep ContentType Source # | |||||
Defined in Network.GRPC.Spec.Headers.Common type Rep ContentType = D1 ('MetaData "ContentType" "Network.GRPC.Spec.Headers.Common" "grpc-spec-1.0.0-inplace" 'False) (C1 ('MetaCons "ContentTypeDefault" 'PrefixI 'False) (U1 :: Type -> Type) :+: C1 ('MetaCons "ContentTypeOverride" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 ByteString))) |
chooseContentType :: forall {k} (rpc :: k). IsRPC rpc => Proxy rpc -> ContentType -> ByteString Source #
Interpret ContentType
data MessageType Source #
Message type
Constructors
MessageTypeDefault | Default message type for this RPC This is given by |
MessageTypeOverride ByteString | Override the message type |
Instances
Default MessageType Source # | |||||
Defined in Network.GRPC.Spec.Headers.Common Methods def :: MessageType # | |||||
Generic MessageType Source # | |||||
Defined in Network.GRPC.Spec.Headers.Common Associated Types
| |||||
Show MessageType Source # | |||||
Defined in Network.GRPC.Spec.Headers.Common Methods showsPrec :: Int -> MessageType -> ShowS # show :: MessageType -> String # showList :: [MessageType] -> ShowS # | |||||
Eq MessageType Source # | |||||
Defined in Network.GRPC.Spec.Headers.Common | |||||
type Rep MessageType Source # | |||||
Defined in Network.GRPC.Spec.Headers.Common type Rep MessageType = D1 ('MetaData "MessageType" "Network.GRPC.Spec.Headers.Common" "grpc-spec-1.0.0-inplace" 'False) (C1 ('MetaCons "MessageTypeDefault" 'PrefixI 'False) (U1 :: Type -> Type) :+: C1 ('MetaCons "MessageTypeOverride" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 ByteString))) |
chooseMessageType :: forall {k} (rpc :: k). IsRPC rpc => Proxy rpc -> MessageType -> Maybe ByteString Source #
Interpret MessageType
OpenTelemetry
data TraceContext Source #
Trace context
Representation of the "trace context" in OpenTelemetry, corresponding
directly to the W3C traceparent
header.
References:
- https://www.w3.org/TR/trace-context/#traceparent-header W3C spec
- https://github.com/census-instrumentation/opencensus-specs/blob/master/encodings/BinaryEncoding.md
Binary format used for the
grpc-trace-bin
header - https://github.com/open-telemetry/opentelemetry-specification/issues/639 Current status of the binary encoding.
Relation to Haskell OpenTelemetry implementations:
- The Haskell
opentelemetry
package calls this aSpanContext
, but provides no binaryPropagationFormat
, and does not supportTraceOptions
.
https://hackage.haskell.org/package/opentelemetry
- The Haskell
hs-opentelemetry
ecosystem definesSpanContext
, which is the combination of the W3Ctraceparent
header (ourTraceContext
) and the W3Ctracestate
header (which we do not support). It too does not support thegrpc-trace-bin
binary format.
https://github.com/iand675/hs-opentelemetry https://hackage.haskell.org/package/hs-opentelemetry-propagator-w3c
Constructors
TraceContext | |
Instances
Binary TraceContext Source # | |||||
Defined in Network.GRPC.Spec.Serialization.TraceContext | |||||
Default TraceContext Source # | |||||
Defined in Network.GRPC.Spec.TraceContext Methods def :: TraceContext # | |||||
Generic TraceContext Source # | |||||
Defined in Network.GRPC.Spec.TraceContext Associated Types
| |||||
Show TraceContext Source # | |||||
Defined in Network.GRPC.Spec.TraceContext Methods showsPrec :: Int -> TraceContext -> ShowS # show :: TraceContext -> String # showList :: [TraceContext] -> ShowS # | |||||
Eq TraceContext Source # | |||||
Defined in Network.GRPC.Spec.TraceContext | |||||
type Rep TraceContext Source # | |||||
Defined in Network.GRPC.Spec.TraceContext type Rep TraceContext = D1 ('MetaData "TraceContext" "Network.GRPC.Spec.TraceContext" "grpc-spec-1.0.0-inplace" 'False) (C1 ('MetaCons "TraceContext" 'PrefixI 'True) (S1 ('MetaSel ('Just "traceContextTraceId") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (Maybe TraceId)) :*: (S1 ('MetaSel ('Just "traceContextSpanId") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (Maybe SpanId)) :*: S1 ('MetaSel ('Just "traceContextOptions") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (Maybe TraceOptions))))) |
Trace ID
The ID of the whole trace forest. Must be a 16-byte string.
Constructors
TraceId | |
Fields |
Instances
Binary TraceId Source # | |||||
IsString TraceId Source # | |||||
Defined in Network.GRPC.Spec.TraceContext Methods fromString :: String -> TraceId # | |||||
Generic TraceId Source # | |||||
Defined in Network.GRPC.Spec.TraceContext Associated Types
| |||||
Show TraceId Source # | |||||
Eq TraceId Source # | |||||
type Rep TraceId Source # | |||||
Defined in Network.GRPC.Spec.TraceContext type Rep TraceId = D1 ('MetaData "TraceId" "Network.GRPC.Spec.TraceContext" "grpc-spec-1.0.0-inplace" 'True) (C1 ('MetaCons "TraceId" 'PrefixI 'True) (S1 ('MetaSel ('Just "getTraceId") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 ByteString))) |
Span ID
ID of the caller span (parent). Must be an 8-byte string.
Constructors
SpanId | |
Fields |
Instances
Binary SpanId Source # | |||||
IsString SpanId Source # | |||||
Defined in Network.GRPC.Spec.TraceContext Methods fromString :: String -> SpanId # | |||||
Generic SpanId Source # | |||||
Defined in Network.GRPC.Spec.TraceContext Associated Types
| |||||
Show SpanId Source # | |||||
Eq SpanId Source # | |||||
type Rep SpanId Source # | |||||
Defined in Network.GRPC.Spec.TraceContext type Rep SpanId = D1 ('MetaData "SpanId" "Network.GRPC.Spec.TraceContext" "grpc-spec-1.0.0-inplace" 'True) (C1 ('MetaCons "SpanId" 'PrefixI 'True) (S1 ('MetaSel ('Just "getSpanId") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 ByteString))) |
data TraceOptions Source #
Tracing options
The flags are recommendations given by the caller rather than strict rules to follow for 3 reasons:
- Trust and abuse.
- Bug in caller
- Different load between caller service and callee service might force callee to down sample.
Constructors
TraceOptions | |
Fields
|
Instances
Binary TraceOptions Source # | |||||
Defined in Network.GRPC.Spec.Serialization.TraceContext | |||||
Generic TraceOptions Source # | |||||
Defined in Network.GRPC.Spec.TraceContext Associated Types
| |||||
Show TraceOptions Source # | |||||
Defined in Network.GRPC.Spec.TraceContext Methods showsPrec :: Int -> TraceOptions -> ShowS # show :: TraceOptions -> String # showList :: [TraceOptions] -> ShowS # | |||||
Eq TraceOptions Source # | |||||
Defined in Network.GRPC.Spec.TraceContext | |||||
type Rep TraceOptions Source # | |||||
Defined in Network.GRPC.Spec.TraceContext type Rep TraceOptions = D1 ('MetaData "TraceOptions" "Network.GRPC.Spec.TraceContext" "grpc-spec-1.0.0-inplace" 'False) (C1 ('MetaCons "TraceOptions" 'PrefixI 'True) (S1 ('MetaSel ('Just "traceOptionsSampled") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 Bool))) |
ORCA
data OrcaLoadReport Source #
Fields :
cpuUtilization
:: Lens' OrcaLoadReport Prelude.Double
memUtilization
:: Lens' OrcaLoadReport Prelude.Double
rps
:: Lens' OrcaLoadReport Data.Word.Word64
requestCost
:: Lens' OrcaLoadReport (Data.Map.Map Data.Text.Text Prelude.Double)
utilization
:: Lens' OrcaLoadReport (Data.Map.Map Data.Text.Text Prelude.Double)
rpsFractional
:: Lens' OrcaLoadReport Prelude.Double
eps
:: Lens' OrcaLoadReport Prelude.Double
namedMetrics
:: Lens' OrcaLoadReport (Data.Map.Map Data.Text.Text Prelude.Double)
applicationUtilization
:: Lens' OrcaLoadReport Prelude.Double
Instances
NFData OrcaLoadReport Source # | |
Defined in Proto.OrcaLoadReport Methods rnf :: OrcaLoadReport -> () # | |
Show OrcaLoadReport Source # | |
Defined in Proto.OrcaLoadReport Methods showsPrec :: Int -> OrcaLoadReport -> ShowS # show :: OrcaLoadReport -> String # showList :: [OrcaLoadReport] -> ShowS # | |
Eq OrcaLoadReport Source # | |
Defined in Proto.OrcaLoadReport Methods (==) :: OrcaLoadReport -> OrcaLoadReport -> Bool # (/=) :: OrcaLoadReport -> OrcaLoadReport -> Bool # | |
Ord OrcaLoadReport Source # | |
Defined in Proto.OrcaLoadReport Methods compare :: OrcaLoadReport -> OrcaLoadReport -> Ordering # (<) :: OrcaLoadReport -> OrcaLoadReport -> Bool # (<=) :: OrcaLoadReport -> OrcaLoadReport -> Bool # (>) :: OrcaLoadReport -> OrcaLoadReport -> Bool # (>=) :: OrcaLoadReport -> OrcaLoadReport -> Bool # max :: OrcaLoadReport -> OrcaLoadReport -> OrcaLoadReport # min :: OrcaLoadReport -> OrcaLoadReport -> OrcaLoadReport # | |
Message OrcaLoadReport Source # | |
Defined in Proto.OrcaLoadReport Methods messageName :: Proxy OrcaLoadReport -> Text # packedMessageDescriptor :: Proxy OrcaLoadReport -> ByteString # packedFileDescriptor :: Proxy OrcaLoadReport -> ByteString # defMessage :: OrcaLoadReport # fieldsByTag :: Map Tag (FieldDescriptor OrcaLoadReport) # fieldsByTextFormatName :: Map String (FieldDescriptor OrcaLoadReport) # unknownFields :: Lens' OrcaLoadReport FieldSet # parseMessage :: Parser OrcaLoadReport # buildMessage :: OrcaLoadReport -> Builder # | |
HasField OrcaLoadReport "applicationUtilization" Double Source # | |
Defined in Proto.OrcaLoadReport Methods fieldOf :: Functor f => Proxy# "applicationUtilization" -> (Double -> f Double) -> OrcaLoadReport -> f OrcaLoadReport # | |
HasField OrcaLoadReport "cpuUtilization" Double Source # | |
Defined in Proto.OrcaLoadReport Methods fieldOf :: Functor f => Proxy# "cpuUtilization" -> (Double -> f Double) -> OrcaLoadReport -> f OrcaLoadReport # | |
HasField OrcaLoadReport "eps" Double Source # | |
Defined in Proto.OrcaLoadReport Methods fieldOf :: Functor f => Proxy# "eps" -> (Double -> f Double) -> OrcaLoadReport -> f OrcaLoadReport # | |
HasField OrcaLoadReport "memUtilization" Double Source # | |
Defined in Proto.OrcaLoadReport Methods fieldOf :: Functor f => Proxy# "memUtilization" -> (Double -> f Double) -> OrcaLoadReport -> f OrcaLoadReport # | |
HasField OrcaLoadReport "rps" Word64 Source # | |
Defined in Proto.OrcaLoadReport Methods fieldOf :: Functor f => Proxy# "rps" -> (Word64 -> f Word64) -> OrcaLoadReport -> f OrcaLoadReport # | |
HasField OrcaLoadReport "rpsFractional" Double Source # | |
Defined in Proto.OrcaLoadReport Methods fieldOf :: Functor f => Proxy# "rpsFractional" -> (Double -> f Double) -> OrcaLoadReport -> f OrcaLoadReport # | |
HasField OrcaLoadReport "namedMetrics" (Map Text Double) Source # | |
Defined in Proto.OrcaLoadReport | |
HasField OrcaLoadReport "requestCost" (Map Text Double) Source # | |
Defined in Proto.OrcaLoadReport | |
HasField OrcaLoadReport "utilization" (Map Text Double) Source # | |
Defined in Proto.OrcaLoadReport |