Safe Haskell | None |
---|---|
Language | Haskell2010 |
Set of helpers helping with writing gRPC clients with not much exposure of the http2-client complexity.
The GrpcClient handles automatic background connection-level window updates to prevent the connection from starving and pings to force a connection alive.
There is no automatic reconnection, retry, or healthchecking. These features are not planned in this library and should be added at higher-levels.
Synopsis
- data GrpcClient = GrpcClient {}
- data BackgroundTasks = BackgroundTasks {
- backgroundWindowUpdate :: Async ()
- backgroundPing :: Async ()
- data GrpcClientConfig = GrpcClientConfig {
- _grpcClientConfigHost :: !HostName
- _grpcClientConfigPort :: !PortNumber
- _grpcClientConfigHeaders :: ![(ByteString, ByteString)]
- _grpcClientConfigTimeout :: !Timeout
- _grpcClientConfigCompression :: !Compression
- _grpcClientConfigTLS :: !(Maybe ClientParams)
- _grpcClientConfigGoAwayHandler :: GoAwayHandler
- _grpcClientConfigFallbackHandler :: FallBackFrameHandler
- _grpcClientConfigWindowUpdateDelay :: Int
- _grpcClientConfigPingDelay :: Int
- grpcClientConfigSimple :: HostName -> PortNumber -> UseTlsOrNot -> GrpcClientConfig
- type UseTlsOrNot = Bool
- tlsSettings :: UseTlsOrNot -> HostName -> PortNumber -> Maybe ClientParams
- setupGrpcClient :: GrpcClientConfig -> IO GrpcClient
- close :: GrpcClient -> IO ()
- rawUnary :: (Service s, HasMethod s m) => RPC s m -> GrpcClient -> MethodInput s m -> IO (Either TooMuchConcurrency (RawReply (MethodOutput s m)))
- unaryOutput :: (Applicative f, Field3 a1 b1 (Either c1 a2) (Either c1 b2)) => (a2 -> f b2) -> Either c2 (Either c3 a1) -> f (Either c2 (Either c3 b1))
- rawStreamServer :: (Service s, HasMethod s m, MethodStreamingType s m ~ ServerStreaming) => RPC s m -> GrpcClient -> a -> MethodInput s m -> (a -> HeaderList -> MethodOutput s m -> IO a) -> IO (Either TooMuchConcurrency (a, HeaderList, HeaderList))
- rawStreamClient :: (Service s, HasMethod s m, MethodStreamingType s m ~ ClientStreaming) => RPC s m -> GrpcClient -> a -> (a -> IO (a, Either StreamDone (CompressMode, MethodInput s m))) -> IO (Either TooMuchConcurrency (a, RawReply (MethodOutput s m)))
Documentation
data GrpcClient Source #
A simplified gRPC Client connected via an HTTP2Client to a given server. Each call from one client will share similar headers, timeout, compression.
GrpcClient | |
|
data BackgroundTasks Source #
BackgroundTasks | |
|
data GrpcClientConfig Source #
Configuration to setup a GrpcClient.
GrpcClientConfig | |
|
type UseTlsOrNot = Bool Source #
tlsSettings :: UseTlsOrNot -> HostName -> PortNumber -> Maybe ClientParams Source #
close :: GrpcClient -> IO () Source #
Cancels background tasks and closes the underlying HTTP2 client.
:: (Service s, HasMethod s m) | |
=> RPC s m | The RPC to call. |
-> GrpcClient | An initialized client. |
-> MethodInput s m | The input. |
-> IO (Either TooMuchConcurrency (RawReply (MethodOutput s m))) |
Run an unary query.
unaryOutput :: (Applicative f, Field3 a1 b1 (Either c1 a2) (Either c1 b2)) => (a2 -> f b2) -> Either c2 (Either c3 a1) -> f (Either c2 (Either c3 b1)) Source #
Prism helper to unpack an unary gRPC call output.
out <- rawUnary rpc grpc method print $ out ^? unaryOutput . somefield
:: (Service s, HasMethod s m, MethodStreamingType s m ~ ServerStreaming) | |
=> RPC s m | The RPC to call. |
-> GrpcClient | An initialized client. |
-> a | An initial state. |
-> MethodInput s m | The input of the stream request. |
-> (a -> HeaderList -> MethodOutput s m -> IO a) | A state-passing handler called for each server-sent output. Headers are repeated for convenience but are the same for every iteration. |
-> IO (Either TooMuchConcurrency (a, HeaderList, HeaderList)) |
Calls for a server stream of requests.
:: (Service s, HasMethod s m, MethodStreamingType s m ~ ClientStreaming) | |
=> RPC s m | The RPC to call. |
-> GrpcClient | An initialized client. |
-> a | An initial state. |
-> (a -> IO (a, Either StreamDone (CompressMode, MethodInput s m))) | A state-passing step function to decide the next message. |
-> IO (Either TooMuchConcurrency (a, RawReply (MethodOutput s m))) |
Sends a streams of requests to the server.
Messages are submitted to the HTTP2 underlying client and hence this function can block until the HTTP2 client has some network credit.