mu-grpc-client-0.4.0.1: gRPC clients from Mu definitions
Safe HaskellNone
LanguageHaskell2010

Mu.GRpc.Client.Record

Description

For further information over initialization of the connection, consult the http2-client-grpc docs.

Synopsis

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.

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 GRpcReply a Source #

Instances

Instances details
Functor GRpcReply Source # 
Instance details

Defined in Mu.GRpc.Client.Internal

Methods

fmap :: (a -> b) -> GRpcReply a -> GRpcReply b #

(<$) :: a -> GRpcReply b -> GRpcReply a #

Show a => Show (GRpcReply a) Source # 
Instance details

Defined in Mu.GRpc.Client.Internal

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.