grapesy
Safe HaskellNone
LanguageHaskell2010

Network.GRPC.Client.StreamType.IO

Description

Execute handlers for specific communication patterns

See also Network.GRPC.Common.StreamType as well as Network.GRPC.Client.StreamType.CanCallRPC.

Synopsis

Documentation

nonStreaming :: forall {k} (rpc :: k) m. Connection -> ClientHandler' 'NonStreaming (ReaderT Connection m) rpc -> Input rpc -> m (Output rpc) Source #

Make a non-streaming RPC

Example usage:

type GetFeature = Protobuf RouteGuide "getFeature"

getFeature :: Connection -> Point -> IO ()
getFeature conn point = do
    features <- nonStreaming conn (rpc @GetFeature) point
    print features

clientStreaming :: forall {k} (rpc :: k) m r. MonadIO m => Connection -> ClientHandler' 'ClientStreaming (ReaderT Connection m) rpc -> ((NextElem (Input rpc) -> m ()) -> m r) -> m (Output rpc, r) Source #

Generalization of clientStreaming_ with an additional result.

clientStreaming_ :: forall {k} (rpc :: k) m. MonadIO m => Connection -> ClientHandler' 'ClientStreaming (ReaderT Connection m) rpc -> ((NextElem (Input rpc) -> m ()) -> m ()) -> m (Output rpc) Source #

Make a client-side streaming RPC

Example usage:

type RecordRoute = Protobuf RouteGuide "recordRoute"

recordRoute :: Connection -> [Point] -> IO ()
recordRoute conn points = do
    summary <- clientStreaming_ conn (rpc @RecordRoute) $ \send ->
                 forM_ points send
    print summary

serverStreaming :: forall {k} (rpc :: k) m r. MonadIO m => Connection -> ClientHandler' 'ServerStreaming (ReaderT Connection m) rpc -> Input rpc -> (m (NextElem (Output rpc)) -> m r) -> m r Source #

Make a server-side streaming RPC

Example usage:

type ListFeatures = Protobuf RouteGuide "listFeatures"

listFeatures :: Connection -> Rectangle -> IO ()
listFeatures conn rect =
    serverStreaming conn (rpc @ListFeatures) rect $ \recv ->
      whileJust_ recv print

biDiStreaming :: forall {k} (rpc :: k) m r. MonadIO m => Connection -> ClientHandler' 'BiDiStreaming (ReaderT Connection m) rpc -> ((NextElem (Input rpc) -> m ()) -> m (NextElem (Output rpc)) -> m r) -> m r Source #

Make a bidirectional RPC

Example usage:

type RouteChat = Protobuf RouteGuide "routeChat"

routeChat :: Connection -> [RouteNote] -> IO ()
routeChat conn notes =
    biDiStreaming conn (rpc @RouteChat) $ \send recv ->
      forM_ notes $ \note -> do
        send note
        print =<< recv