Safe Haskell | None |
---|---|
Language | Haskell2010 |
For further information over initialization of the connection, consult the http2-client-grpc docs.
Synopsis
- data GrpcClient
- data GrpcClientConfig
- grpcClientConfigSimple :: HostName -> PortNumber -> UseTlsOrNot -> GrpcClientConfig
- setupGrpcClient' :: MonadIO m => GrpcClientConfig -> m (Either ClientError GrpcClient)
- setupGrpcClientZipkin :: (MonadIO m, MonadTrace m) => GrpcClientConfig -> Text -> m (Either ClientError GrpcClient)
- buildService :: forall (pro :: GRpcMessageProtocol) (pkg :: Package') (s :: Symbol) (p :: Symbol) t (pkgName :: Symbol) (ss :: [Service']) (ms :: [Method']). (pkg ~ 'Package ('Just pkgName) ss, LookupService ss s ~ 'Service s ms, Generic t, BuildService pro pkgName s p ms (Rep t)) => GrpcClient -> t
- data GRpcMessageProtocol
- data CompressMode
- data GRpcReply a
- generateRecordFromService :: String -> String -> Namer -> Name -> Q [Dec]
Initialization of the gRPC client
data GrpcClient #
A simplified gRPC Client connected via an HTTP2Client to a given server. Each call from one client will share similar headers, timeout, compression.
data GrpcClientConfig #
Configuration to setup a GrpcClient.
grpcClientConfigSimple :: HostName -> PortNumber -> UseTlsOrNot -> GrpcClientConfig #
setupGrpcClient' :: MonadIO m => GrpcClientConfig -> m (Either ClientError GrpcClient) Source #
Initialize a connection to a gRPC server.
setupGrpcClientZipkin :: (MonadIO m, MonadTrace m) => GrpcClientConfig -> Text -> m (Either ClientError GrpcClient) Source #
Initialize a connection to a gRPC server and pass information about distributed tracing.
Fill and generate the Haskell record of functions
buildService :: forall (pro :: GRpcMessageProtocol) (pkg :: Package') (s :: Symbol) (p :: Symbol) t (pkgName :: Symbol) (ss :: [Service']) (ms :: [Method']). (pkg ~ 'Package ('Just pkgName) ss, LookupService ss s ~ 'Service s ms, Generic t, BuildService pro pkgName s p ms (Rep t)) => GrpcClient -> t Source #
Fills in a Haskell record of functions with the corresponding
calls to gRPC services from a Mu Service
declaration.
data GRpcMessageProtocol #
Serialization formats supported with gRPC.
MsgProtoBuf | Protocol Buffers. |
MsgAvro | Avro. |
Instances
Eq GRpcMessageProtocol | |
Defined in Mu.GRpc.Bridge (==) :: GRpcMessageProtocol -> GRpcMessageProtocol -> Bool # (/=) :: GRpcMessageProtocol -> GRpcMessageProtocol -> Bool # | |
Show GRpcMessageProtocol | |
Defined in Mu.GRpc.Bridge showsPrec :: Int -> GRpcMessageProtocol -> ShowS # show :: GRpcMessageProtocol -> String # showList :: [GRpcMessageProtocol] -> ShowS # |
GRpcTooMuchConcurrency TooMuchConcurrency | |
GRpcErrorCode ErrorCode | |
GRpcErrorString String | |
GRpcClientError ClientError | |
GRpcOk a |
generateRecordFromService :: String -> String -> Namer -> Name -> Q [Dec] Source #
Generate the plain Haskell record corresponding to
a Mu Service
definition, and a concrete implementation
of buildService
for that record.