{-# language DataKinds #-}
{-# language TypeApplications #-}
{-# language TypeFamilies #-}
module Mu.GRpc.Client.Examples where
import Data.Conduit
import Data.Conduit.Combinators as C
import Data.Conduit.List (consume)
import qualified Data.Text as T
import Network.HTTP2.Client (HostName, PortNumber)
import Mu.Adapter.ProtoBuf
import Mu.GRpc.Client.TyApps
import Mu.Rpc.Examples
import Mu.Schema
type instance AnnotatedSchema ProtoBufAnnotation QuickstartSchema
= '[ 'AnnField "HelloRequest" "name" ('ProtoBufId 1 '[])
, 'AnnField "HelloResponse" "message" ('ProtoBufId 1 '[])
, 'AnnField "HiRequest" "number" ('ProtoBufId 1 '[]) ]
sayHello' :: HostName -> PortNumber -> T.Text -> IO (GRpcReply T.Text)
sayHello' :: HostName -> PortNumber -> Text -> IO (GRpcReply Text)
sayHello' HostName
host PortNumber
port Text
req
= do Right GrpcClient
c <- GrpcClientConfig -> IO (Either ClientError GrpcClient)
forall (m :: * -> *).
MonadIO m =>
GrpcClientConfig -> m (Either ClientError GrpcClient)
setupGrpcClient' (HostName -> PortNumber -> UseTlsOrNot -> GrpcClientConfig
grpcClientConfigSimple HostName
host PortNumber
port UseTlsOrNot
False)
(HelloResponse -> Text)
-> GRpcReply HelloResponse -> GRpcReply Text
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
fmap (\(HelloResponse Text
r) -> Text
r) (GRpcReply HelloResponse -> GRpcReply Text)
-> IO (GRpcReply HelloResponse) -> IO (GRpcReply Text)
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> GrpcClient -> HelloRequest -> IO (GRpcReply HelloResponse)
sayHello GrpcClient
c (Text -> HelloRequest
HelloRequest Text
req)
sayHello :: GrpcClient -> HelloRequest -> IO (GRpcReply HelloResponse)
sayHello :: GrpcClient -> HelloRequest -> IO (GRpcReply HelloResponse)
sayHello = forall h (pkgName :: Symbol)
(services :: [Service Symbol Symbol Symbol (TypeRef Symbol)])
(methods :: [Method Symbol Symbol Symbol (TypeRef Symbol)]).
(QuickStartService ~ 'Package ('Just pkgName) services,
LookupService services "Greeter" ~ 'Service "Greeter" methods,
GRpcServiceMethodCall
'MsgProtoBuf
pkgName
"Greeter"
(LookupMethod methods "SayHello")
h) =>
GrpcClient -> h
forall (pro :: GRpcMessageProtocol) (pkg :: Package')
(srvName :: Symbol) (methodName :: Symbol) h (pkgName :: Symbol)
(services :: [Service Symbol Symbol Symbol (TypeRef Symbol)])
(methods :: [Method Symbol Symbol Symbol (TypeRef Symbol)]).
(pkg ~ 'Package ('Just pkgName) services,
LookupService services srvName ~ 'Service srvName methods,
GRpcServiceMethodCall
pro pkgName srvName (LookupMethod methods methodName) h) =>
GrpcClient -> h
gRpcCall @'MsgProtoBuf @QuickStartService @"Greeter" @"SayHello"
sayHi' :: HostName -> PortNumber -> Int -> IO [GRpcReply T.Text]
sayHi' :: HostName -> PortNumber -> Int -> IO [GRpcReply Text]
sayHi' HostName
host PortNumber
port Int
n
= do Right GrpcClient
c <- GrpcClientConfig -> IO (Either ClientError GrpcClient)
forall (m :: * -> *).
MonadIO m =>
GrpcClientConfig -> m (Either ClientError GrpcClient)
setupGrpcClient' (HostName -> PortNumber -> UseTlsOrNot -> GrpcClientConfig
grpcClientConfigSimple HostName
host PortNumber
port UseTlsOrNot
False)
ConduitT () (GRpcReply HelloResponse) IO ()
cndt <- GrpcClient
-> HiRequest -> IO (ConduitT () (GRpcReply HelloResponse) IO ())
sayHi GrpcClient
c (Int -> HiRequest
HiRequest Int
n)
ConduitT () Void IO [GRpcReply Text] -> IO [GRpcReply Text]
forall (m :: * -> *) r. Monad m => ConduitT () Void m r -> m r
runConduit (ConduitT () Void IO [GRpcReply Text] -> IO [GRpcReply Text])
-> ConduitT () Void IO [GRpcReply Text] -> IO [GRpcReply Text]
forall a b. (a -> b) -> a -> b
$ ConduitT () (GRpcReply HelloResponse) IO ()
cndt ConduitT () (GRpcReply HelloResponse) IO ()
-> ConduitM (GRpcReply HelloResponse) Void IO [GRpcReply Text]
-> ConduitT () Void IO [GRpcReply Text]
forall (m :: * -> *) a b c r.
Monad m =>
ConduitM a b m () -> ConduitM b c m r -> ConduitM a c m r
.| (GRpcReply HelloResponse -> GRpcReply Text)
-> ConduitT (GRpcReply HelloResponse) (GRpcReply Text) IO ()
forall (m :: * -> *) a b. Monad m => (a -> b) -> ConduitT a b m ()
C.map ((HelloResponse -> Text)
-> GRpcReply HelloResponse -> GRpcReply Text
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
fmap (\(HelloResponse Text
r) -> Text
r)) ConduitT (GRpcReply HelloResponse) (GRpcReply Text) IO ()
-> ConduitM (GRpcReply Text) Void IO [GRpcReply Text]
-> ConduitM (GRpcReply HelloResponse) Void IO [GRpcReply Text]
forall (m :: * -> *) a b c r.
Monad m =>
ConduitM a b m () -> ConduitM b c m r -> ConduitM a c m r
.| ConduitM (GRpcReply Text) Void IO [GRpcReply Text]
forall (m :: * -> *) a o. Monad m => ConduitT a o m [a]
consume
sayHi :: GrpcClient -> HiRequest -> IO (ConduitT () (GRpcReply HelloResponse) IO ())
sayHi :: GrpcClient
-> HiRequest -> IO (ConduitT () (GRpcReply HelloResponse) IO ())
sayHi = forall h (pkgName :: Symbol)
(services :: [Service Symbol Symbol Symbol (TypeRef Symbol)])
(methods :: [Method Symbol Symbol Symbol (TypeRef Symbol)]).
(QuickStartService ~ 'Package ('Just pkgName) services,
LookupService services "Greeter" ~ 'Service "Greeter" methods,
GRpcServiceMethodCall
'MsgProtoBuf pkgName "Greeter" (LookupMethod methods "SayHi") h) =>
GrpcClient -> h
forall (pro :: GRpcMessageProtocol) (pkg :: Package')
(srvName :: Symbol) (methodName :: Symbol) h (pkgName :: Symbol)
(services :: [Service Symbol Symbol Symbol (TypeRef Symbol)])
(methods :: [Method Symbol Symbol Symbol (TypeRef Symbol)]).
(pkg ~ 'Package ('Just pkgName) services,
LookupService services srvName ~ 'Service srvName methods,
GRpcServiceMethodCall
pro pkgName srvName (LookupMethod methods methodName) h) =>
GrpcClient -> h
gRpcCall @'MsgProtoBuf @QuickStartService @"Greeter" @"SayHi"