{-# LANGUAGE DataKinds #-}
{-# LANGUAGE FlexibleContexts #-}
{-# LANGUAGE NamedFieldPuns #-}
{-# LANGUAGE PackageImports #-}
{-# LANGUAGE RankNTypes #-}
module Utxorpc.Client
(
UtxorpcInfo (..),
simpleUtxorpcClient,
utxorpcClient,
utxorpcClientWith,
UtxorpcClient (..),
BuildClient (..),
SubmitClient (..),
SyncClient (..),
WatchClient (..),
ServerStreamCall,
ServerStreamReply,
UnaryReply,
UtxorpcClientLogger (..),
RequestLogger,
ReplyLogger,
ServerStreamLogger,
ServerStreamEndLogger,
)
where
import qualified Data.ByteString.Char8 as BS
import Network.GRPC.Client (gzip, uncompressed)
import Network.GRPC.Client.Helpers
( GrpcClient (_grpcClientHeaders),
GrpcClientConfig,
UseTlsOrNot,
close,
grpcClientConfigSimple,
setupGrpcClient,
_grpcClientConfigCompression,
)
import Network.GRPC.HTTP2.ProtoLens (RPC (RPC))
import Proto.Utxorpc.V1alpha.Build.Build
import Proto.Utxorpc.V1alpha.Submit.Submit
import Proto.Utxorpc.V1alpha.Sync.Sync
import Proto.Utxorpc.V1alpha.Watch.Watch
import Utxorpc.Logged (ReplyLogger, RequestLogger, ServerStreamEndLogger, ServerStreamLogger, UtxorpcClientLogger (..), loggedSStream, loggedUnary)
import Utxorpc.Types
import "http2-client" Network.HTTP2.Client (ClientError, HostName, PortNumber, runClientIO)
data UtxorpcInfo m = UtxorpcInfo
{
forall (m :: * -> *). UtxorpcInfo m -> HostName
_hostName :: HostName,
forall (m :: * -> *). UtxorpcInfo m -> PortNumber
_portNumber :: PortNumber,
forall (m :: * -> *). UtxorpcInfo m -> UseTlsOrNot
_tlsEnabled :: UseTlsOrNot,
forall (m :: * -> *). UtxorpcInfo m -> UseTlsOrNot
_useGzip :: Bool,
:: [(BS.ByteString, BS.ByteString)],
forall (m :: * -> *).
UtxorpcInfo m -> Maybe (UtxorpcClientLogger m)
_logger :: Maybe (UtxorpcClientLogger m)
}
simpleUtxorpcClient ::
HostName ->
PortNumber ->
UseTlsOrNot ->
IO (Either ClientError UtxorpcClient)
simpleUtxorpcClient :: HostName
-> PortNumber
-> UseTlsOrNot
-> IO (Either ClientError UtxorpcClient)
simpleUtxorpcClient HostName
host PortNumber
port UseTlsOrNot
tlsEnabled =
UtxorpcInfo Any -> IO (Either ClientError UtxorpcClient)
forall (m :: * -> *).
UtxorpcInfo m -> IO (Either ClientError UtxorpcClient)
utxorpcClient (UtxorpcInfo Any -> IO (Either ClientError UtxorpcClient))
-> UtxorpcInfo Any -> IO (Either ClientError UtxorpcClient)
forall a b. (a -> b) -> a -> b
$
HostName
-> PortNumber
-> UseTlsOrNot
-> UseTlsOrNot
-> [(ByteString, ByteString)]
-> Maybe (UtxorpcClientLogger Any)
-> UtxorpcInfo Any
forall (m :: * -> *).
HostName
-> PortNumber
-> UseTlsOrNot
-> UseTlsOrNot
-> [(ByteString, ByteString)]
-> Maybe (UtxorpcClientLogger m)
-> UtxorpcInfo m
UtxorpcInfo HostName
host PortNumber
port UseTlsOrNot
tlsEnabled UseTlsOrNot
False [] Maybe (UtxorpcClientLogger Any)
forall a. Maybe a
Nothing
utxorpcClient :: UtxorpcInfo m -> IO (Either ClientError UtxorpcClient)
utxorpcClient :: forall (m :: * -> *).
UtxorpcInfo m -> IO (Either ClientError UtxorpcClient)
utxorpcClient
UtxorpcInfo {HostName
_hostName :: forall (m :: * -> *). UtxorpcInfo m -> HostName
_hostName :: HostName
_hostName, PortNumber
_portNumber :: forall (m :: * -> *). UtxorpcInfo m -> PortNumber
_portNumber :: PortNumber
_portNumber, UseTlsOrNot
_tlsEnabled :: forall (m :: * -> *). UtxorpcInfo m -> UseTlsOrNot
_tlsEnabled :: UseTlsOrNot
_tlsEnabled, UseTlsOrNot
_useGzip :: forall (m :: * -> *). UtxorpcInfo m -> UseTlsOrNot
_useGzip :: UseTlsOrNot
_useGzip, Maybe (UtxorpcClientLogger m)
_logger :: forall (m :: * -> *).
UtxorpcInfo m -> Maybe (UtxorpcClientLogger m)
_logger :: Maybe (UtxorpcClientLogger m)
_logger, [(ByteString, ByteString)]
_clientHeaders :: forall (m :: * -> *). UtxorpcInfo m -> [(ByteString, ByteString)]
_clientHeaders :: [(ByteString, ByteString)]
_clientHeaders} = do
Either ClientError GrpcClient
eClient <- HostName
-> PortNumber
-> UseTlsOrNot
-> UseTlsOrNot
-> IO (Either ClientError GrpcClient)
grpcClient HostName
_hostName PortNumber
_portNumber UseTlsOrNot
_tlsEnabled UseTlsOrNot
_useGzip
Either ClientError UtxorpcClient
-> IO (Either ClientError UtxorpcClient)
forall a. a -> IO a
forall (m :: * -> *) a. Monad m => a -> m a
return (Either ClientError UtxorpcClient
-> IO (Either ClientError UtxorpcClient))
-> Either ClientError UtxorpcClient
-> IO (Either ClientError UtxorpcClient)
forall a b. (a -> b) -> a -> b
$ Maybe (UtxorpcClientLogger m) -> GrpcClient -> UtxorpcClient
forall (m :: * -> *).
Maybe (UtxorpcClientLogger m) -> GrpcClient -> UtxorpcClient
fromGrpc Maybe (UtxorpcClientLogger m)
_logger (GrpcClient -> UtxorpcClient)
-> (GrpcClient -> GrpcClient) -> GrpcClient -> UtxorpcClient
forall b c a. (b -> c) -> (a -> b) -> a -> c
. [(ByteString, ByteString)] -> GrpcClient -> GrpcClient
withHeaders [(ByteString, ByteString)]
_clientHeaders (GrpcClient -> UtxorpcClient)
-> Either ClientError GrpcClient
-> Either ClientError UtxorpcClient
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> Either ClientError GrpcClient
eClient
where
withHeaders :: [(ByteString, ByteString)] -> GrpcClient -> GrpcClient
withHeaders [(ByteString, ByteString)]
hdrs GrpcClient
client =
let oldHdrs :: [(ByteString, ByteString)]
oldHdrs = GrpcClient -> [(ByteString, ByteString)]
_grpcClientHeaders GrpcClient
client
in GrpcClient
client {_grpcClientHeaders = oldHdrs ++ hdrs}
utxorpcClientWith ::
GrpcClientConfig ->
Maybe (UtxorpcClientLogger m) ->
IO (Either ClientError UtxorpcClient)
utxorpcClientWith :: forall (m :: * -> *).
GrpcClientConfig
-> Maybe (UtxorpcClientLogger m)
-> IO (Either ClientError UtxorpcClient)
utxorpcClientWith GrpcClientConfig
config Maybe (UtxorpcClientLogger m)
logger = do
Either ClientError GrpcClient
eClient <- ClientIO GrpcClient -> IO (Either ClientError GrpcClient)
forall a. ClientIO a -> IO (Either ClientError a)
runClientIO (ClientIO GrpcClient -> IO (Either ClientError GrpcClient))
-> ClientIO GrpcClient -> IO (Either ClientError GrpcClient)
forall a b. (a -> b) -> a -> b
$ GrpcClientConfig -> ClientIO GrpcClient
setupGrpcClient GrpcClientConfig
config
Either ClientError UtxorpcClient
-> IO (Either ClientError UtxorpcClient)
forall a. a -> IO a
forall (m :: * -> *) a. Monad m => a -> m a
return (Either ClientError UtxorpcClient
-> IO (Either ClientError UtxorpcClient))
-> Either ClientError UtxorpcClient
-> IO (Either ClientError UtxorpcClient)
forall a b. (a -> b) -> a -> b
$ Maybe (UtxorpcClientLogger m) -> GrpcClient -> UtxorpcClient
forall (m :: * -> *).
Maybe (UtxorpcClientLogger m) -> GrpcClient -> UtxorpcClient
fromGrpc Maybe (UtxorpcClientLogger m)
logger (GrpcClient -> UtxorpcClient)
-> Either ClientError GrpcClient
-> Either ClientError UtxorpcClient
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> Either ClientError GrpcClient
eClient
grpcClient ::
HostName ->
PortNumber ->
UseTlsOrNot ->
Bool ->
IO (Either ClientError GrpcClient)
grpcClient :: HostName
-> PortNumber
-> UseTlsOrNot
-> UseTlsOrNot
-> IO (Either ClientError GrpcClient)
grpcClient HostName
host PortNumber
port UseTlsOrNot
tlsEnabled UseTlsOrNot
doCompress = ClientIO GrpcClient -> IO (Either ClientError GrpcClient)
forall a. ClientIO a -> IO (Either ClientError a)
runClientIO (ClientIO GrpcClient -> IO (Either ClientError GrpcClient))
-> ClientIO GrpcClient -> IO (Either ClientError GrpcClient)
forall a b. (a -> b) -> a -> b
$ do
GrpcClientConfig -> ClientIO GrpcClient
setupGrpcClient
( (HostName -> PortNumber -> UseTlsOrNot -> GrpcClientConfig
grpcClientConfigSimple HostName
host PortNumber
port UseTlsOrNot
tlsEnabled)
{ _grpcClientConfigCompression = compression
}
)
where
compression :: Compression
compression = if UseTlsOrNot
doCompress then Compression
gzip else Compression
uncompressed
fromGrpc :: Maybe (UtxorpcClientLogger m) -> GrpcClient -> UtxorpcClient
fromGrpc :: forall (m :: * -> *).
Maybe (UtxorpcClientLogger m) -> GrpcClient -> UtxorpcClient
fromGrpc Maybe (UtxorpcClientLogger m)
logger GrpcClient
client =
BuildClient
-> SubmitClient
-> SyncClient
-> WatchClient
-> IO (Either ClientError ())
-> UtxorpcClient
UtxorpcClient
(Maybe (UtxorpcClientLogger m) -> GrpcClient -> BuildClient
forall (m :: * -> *).
Maybe (UtxorpcClientLogger m) -> GrpcClient -> BuildClient
mkBuildClient Maybe (UtxorpcClientLogger m)
logger GrpcClient
client)
(Maybe (UtxorpcClientLogger m) -> GrpcClient -> SubmitClient
forall (m :: * -> *).
Maybe (UtxorpcClientLogger m) -> GrpcClient -> SubmitClient
mkSubmitClient Maybe (UtxorpcClientLogger m)
logger GrpcClient
client)
(Maybe (UtxorpcClientLogger m) -> GrpcClient -> SyncClient
forall (m :: * -> *).
Maybe (UtxorpcClientLogger m) -> GrpcClient -> SyncClient
mkSyncClient Maybe (UtxorpcClientLogger m)
logger GrpcClient
client)
(Maybe (UtxorpcClientLogger m) -> GrpcClient -> WatchClient
forall (m :: * -> *).
Maybe (UtxorpcClientLogger m) -> GrpcClient -> WatchClient
mkWatchClient Maybe (UtxorpcClientLogger m)
logger GrpcClient
client)
(ClientIO () -> IO (Either ClientError ())
forall a. ClientIO a -> IO (Either ClientError a)
runClientIO (ClientIO () -> IO (Either ClientError ()))
-> ClientIO () -> IO (Either ClientError ())
forall a b. (a -> b) -> a -> b
$ GrpcClient -> ClientIO ()
Network.GRPC.Client.Helpers.close GrpcClient
client)
mkBuildClient :: Maybe (UtxorpcClientLogger m) -> GrpcClient -> BuildClient
mkBuildClient :: forall (m :: * -> *).
Maybe (UtxorpcClientLogger m) -> GrpcClient -> BuildClient
mkBuildClient Maybe (UtxorpcClientLogger m)
logger GrpcClient
client =
(GetChainTipRequest -> UnaryReply GetChainTipResponse)
-> (GetChainParamRequest -> UnaryReply GetChainParamResponse)
-> (GetUtxoByAddressRequest -> UnaryReply GetUtxoByAddressResponse)
-> (GetUtxoByRefRequest -> UnaryReply GetUtxoByRefResponse)
-> ServerStreamCall HoldUtxoRequest HoldUtxoResponse
-> BuildClient
BuildClient
(Maybe (UtxorpcClientLogger m)
-> RPC LedgerStateService "getChainTip"
-> GrpcClient
-> GetChainTipRequest
-> UnaryReply GetChainTipResponse
forall r i o (m :: * -> *).
(GRPCInput r i, GRPCOutput r o, Show i, Message i, Show o,
Message o) =>
Maybe (UtxorpcClientLogger m)
-> r -> GrpcClient -> i -> UnaryReply o
loggedUnary Maybe (UtxorpcClientLogger m)
logger RPC LedgerStateService "getChainTip"
getChainTipRPC GrpcClient
client)
(Maybe (UtxorpcClientLogger m)
-> RPC LedgerStateService "getChainParam"
-> GrpcClient
-> GetChainParamRequest
-> UnaryReply GetChainParamResponse
forall r i o (m :: * -> *).
(GRPCInput r i, GRPCOutput r o, Show i, Message i, Show o,
Message o) =>
Maybe (UtxorpcClientLogger m)
-> r -> GrpcClient -> i -> UnaryReply o
loggedUnary Maybe (UtxorpcClientLogger m)
logger RPC LedgerStateService "getChainParam"
getChainParamRPC GrpcClient
client)
(Maybe (UtxorpcClientLogger m)
-> RPC LedgerStateService "getUtxoByAddress"
-> GrpcClient
-> GetUtxoByAddressRequest
-> UnaryReply GetUtxoByAddressResponse
forall r i o (m :: * -> *).
(GRPCInput r i, GRPCOutput r o, Show i, Message i, Show o,
Message o) =>
Maybe (UtxorpcClientLogger m)
-> r -> GrpcClient -> i -> UnaryReply o
loggedUnary Maybe (UtxorpcClientLogger m)
logger RPC LedgerStateService "getUtxoByAddress"
getUtxoByAddressRPC GrpcClient
client)
(Maybe (UtxorpcClientLogger m)
-> RPC LedgerStateService "getUtxoByRef"
-> GrpcClient
-> GetUtxoByRefRequest
-> UnaryReply GetUtxoByRefResponse
forall r i o (m :: * -> *).
(GRPCInput r i, GRPCOutput r o, Show i, Message i, Show o,
Message o) =>
Maybe (UtxorpcClientLogger m)
-> r -> GrpcClient -> i -> UnaryReply o
loggedUnary Maybe (UtxorpcClientLogger m)
logger RPC LedgerStateService "getUtxoByRef"
getUtxoByRefRPC GrpcClient
client)
(Maybe (UtxorpcClientLogger m)
-> RPC LedgerStateService "holdUtxo"
-> GrpcClient
-> a
-> HoldUtxoRequest
-> (a -> [(ByteString, ByteString)] -> HoldUtxoResponse -> IO a)
-> ServerStreamReply a
forall r o i (m :: * -> *) a.
(GRPCOutput r o, GRPCInput r i, Show i, Message i, Show o,
Message o) =>
Maybe (UtxorpcClientLogger m)
-> r
-> GrpcClient
-> a
-> i
-> (a -> [(ByteString, ByteString)] -> o -> IO a)
-> ServerStreamReply a
loggedSStream Maybe (UtxorpcClientLogger m)
logger RPC LedgerStateService "holdUtxo"
holdUtxoRPC GrpcClient
client)
getChainTipRPC :: RPC LedgerStateService "getChainTip"
getChainTipRPC :: RPC LedgerStateService "getChainTip"
getChainTipRPC = RPC LedgerStateService "getChainTip"
forall s (m :: Symbol). RPC s m
RPC
getChainParamRPC :: RPC LedgerStateService "getChainParam"
getChainParamRPC :: RPC LedgerStateService "getChainParam"
getChainParamRPC = RPC LedgerStateService "getChainParam"
forall s (m :: Symbol). RPC s m
RPC
getUtxoByAddressRPC :: RPC LedgerStateService "getUtxoByAddress"
getUtxoByAddressRPC :: RPC LedgerStateService "getUtxoByAddress"
getUtxoByAddressRPC = RPC LedgerStateService "getUtxoByAddress"
forall s (m :: Symbol). RPC s m
RPC
getUtxoByRefRPC :: RPC LedgerStateService "getUtxoByRef"
getUtxoByRefRPC :: RPC LedgerStateService "getUtxoByRef"
getUtxoByRefRPC = RPC LedgerStateService "getUtxoByRef"
forall s (m :: Symbol). RPC s m
RPC
holdUtxoRPC :: RPC LedgerStateService "holdUtxo"
holdUtxoRPC :: RPC LedgerStateService "holdUtxo"
holdUtxoRPC = RPC LedgerStateService "holdUtxo"
forall s (m :: Symbol). RPC s m
RPC
mkSubmitClient :: Maybe (UtxorpcClientLogger m) -> GrpcClient -> SubmitClient
mkSubmitClient :: forall (m :: * -> *).
Maybe (UtxorpcClientLogger m) -> GrpcClient -> SubmitClient
mkSubmitClient Maybe (UtxorpcClientLogger m)
logger GrpcClient
client =
(SubmitTxRequest -> UnaryReply SubmitTxResponse)
-> (ReadMempoolRequest -> UnaryReply ReadMempoolResponse)
-> ServerStreamCall WaitForTxRequest WaitForTxResponse
-> ServerStreamCall WatchMempoolRequest WatchMempoolResponse
-> SubmitClient
SubmitClient
(Maybe (UtxorpcClientLogger m)
-> RPC SubmitService "submitTx"
-> GrpcClient
-> SubmitTxRequest
-> UnaryReply SubmitTxResponse
forall r i o (m :: * -> *).
(GRPCInput r i, GRPCOutput r o, Show i, Message i, Show o,
Message o) =>
Maybe (UtxorpcClientLogger m)
-> r -> GrpcClient -> i -> UnaryReply o
loggedUnary Maybe (UtxorpcClientLogger m)
logger RPC SubmitService "submitTx"
submitTxRPC GrpcClient
client)
(Maybe (UtxorpcClientLogger m)
-> RPC SubmitService "readMempool"
-> GrpcClient
-> ReadMempoolRequest
-> UnaryReply ReadMempoolResponse
forall r i o (m :: * -> *).
(GRPCInput r i, GRPCOutput r o, Show i, Message i, Show o,
Message o) =>
Maybe (UtxorpcClientLogger m)
-> r -> GrpcClient -> i -> UnaryReply o
loggedUnary Maybe (UtxorpcClientLogger m)
logger RPC SubmitService "readMempool"
readMempoolRPC GrpcClient
client)
(Maybe (UtxorpcClientLogger m)
-> RPC SubmitService "waitForTx"
-> GrpcClient
-> a
-> WaitForTxRequest
-> (a -> [(ByteString, ByteString)] -> WaitForTxResponse -> IO a)
-> ServerStreamReply a
forall r o i (m :: * -> *) a.
(GRPCOutput r o, GRPCInput r i, Show i, Message i, Show o,
Message o) =>
Maybe (UtxorpcClientLogger m)
-> r
-> GrpcClient
-> a
-> i
-> (a -> [(ByteString, ByteString)] -> o -> IO a)
-> ServerStreamReply a
loggedSStream Maybe (UtxorpcClientLogger m)
logger RPC SubmitService "waitForTx"
waitForTxRPC GrpcClient
client)
(Maybe (UtxorpcClientLogger m)
-> RPC SubmitService "watchMempool"
-> GrpcClient
-> a
-> WatchMempoolRequest
-> (a
-> [(ByteString, ByteString)] -> WatchMempoolResponse -> IO a)
-> ServerStreamReply a
forall r o i (m :: * -> *) a.
(GRPCOutput r o, GRPCInput r i, Show i, Message i, Show o,
Message o) =>
Maybe (UtxorpcClientLogger m)
-> r
-> GrpcClient
-> a
-> i
-> (a -> [(ByteString, ByteString)] -> o -> IO a)
-> ServerStreamReply a
loggedSStream Maybe (UtxorpcClientLogger m)
logger RPC SubmitService "watchMempool"
watchMempoolRPC GrpcClient
client)
submitTxRPC :: RPC SubmitService "submitTx"
submitTxRPC :: RPC SubmitService "submitTx"
submitTxRPC = RPC SubmitService "submitTx"
forall s (m :: Symbol). RPC s m
RPC
readMempoolRPC :: RPC SubmitService "readMempool"
readMempoolRPC :: RPC SubmitService "readMempool"
readMempoolRPC = RPC SubmitService "readMempool"
forall s (m :: Symbol). RPC s m
RPC
waitForTxRPC :: RPC SubmitService "waitForTx"
waitForTxRPC :: RPC SubmitService "waitForTx"
waitForTxRPC = RPC SubmitService "waitForTx"
forall s (m :: Symbol). RPC s m
RPC
watchMempoolRPC :: RPC SubmitService "watchMempool"
watchMempoolRPC :: RPC SubmitService "watchMempool"
watchMempoolRPC = RPC SubmitService "watchMempool"
forall s (m :: Symbol). RPC s m
RPC
mkSyncClient :: Maybe (UtxorpcClientLogger m) -> GrpcClient -> SyncClient
mkSyncClient :: forall (m :: * -> *).
Maybe (UtxorpcClientLogger m) -> GrpcClient -> SyncClient
mkSyncClient Maybe (UtxorpcClientLogger m)
logger GrpcClient
client =
(FetchBlockRequest -> UnaryReply FetchBlockResponse)
-> (DumpHistoryRequest -> UnaryReply DumpHistoryResponse)
-> ServerStreamCall FollowTipRequest FollowTipResponse
-> SyncClient
SyncClient
(Maybe (UtxorpcClientLogger m)
-> RPC ChainSyncService "fetchBlock"
-> GrpcClient
-> FetchBlockRequest
-> UnaryReply FetchBlockResponse
forall r i o (m :: * -> *).
(GRPCInput r i, GRPCOutput r o, Show i, Message i, Show o,
Message o) =>
Maybe (UtxorpcClientLogger m)
-> r -> GrpcClient -> i -> UnaryReply o
loggedUnary Maybe (UtxorpcClientLogger m)
logger RPC ChainSyncService "fetchBlock"
fetchBlockRPC GrpcClient
client)
(Maybe (UtxorpcClientLogger m)
-> RPC ChainSyncService "dumpHistory"
-> GrpcClient
-> DumpHistoryRequest
-> UnaryReply DumpHistoryResponse
forall r i o (m :: * -> *).
(GRPCInput r i, GRPCOutput r o, Show i, Message i, Show o,
Message o) =>
Maybe (UtxorpcClientLogger m)
-> r -> GrpcClient -> i -> UnaryReply o
loggedUnary Maybe (UtxorpcClientLogger m)
logger RPC ChainSyncService "dumpHistory"
dumpHistoryRPC GrpcClient
client)
(Maybe (UtxorpcClientLogger m)
-> RPC ChainSyncService "followTip"
-> GrpcClient
-> a
-> FollowTipRequest
-> (a -> [(ByteString, ByteString)] -> FollowTipResponse -> IO a)
-> ServerStreamReply a
forall r o i (m :: * -> *) a.
(GRPCOutput r o, GRPCInput r i, Show i, Message i, Show o,
Message o) =>
Maybe (UtxorpcClientLogger m)
-> r
-> GrpcClient
-> a
-> i
-> (a -> [(ByteString, ByteString)] -> o -> IO a)
-> ServerStreamReply a
loggedSStream Maybe (UtxorpcClientLogger m)
logger RPC ChainSyncService "followTip"
followTipRPC GrpcClient
client)
fetchBlockRPC :: RPC ChainSyncService "fetchBlock"
fetchBlockRPC :: RPC ChainSyncService "fetchBlock"
fetchBlockRPC = RPC ChainSyncService "fetchBlock"
forall s (m :: Symbol). RPC s m
RPC
dumpHistoryRPC :: RPC ChainSyncService "dumpHistory"
dumpHistoryRPC :: RPC ChainSyncService "dumpHistory"
dumpHistoryRPC = RPC ChainSyncService "dumpHistory"
forall s (m :: Symbol). RPC s m
RPC
followTipRPC :: RPC ChainSyncService "followTip"
followTipRPC :: RPC ChainSyncService "followTip"
followTipRPC = RPC ChainSyncService "followTip"
forall s (m :: Symbol). RPC s m
RPC
mkWatchClient :: Maybe (UtxorpcClientLogger m) -> GrpcClient -> WatchClient
mkWatchClient :: forall (m :: * -> *).
Maybe (UtxorpcClientLogger m) -> GrpcClient -> WatchClient
mkWatchClient Maybe (UtxorpcClientLogger m)
logger GrpcClient
client =
ServerStreamCall WatchTxRequest WatchTxResponse -> WatchClient
WatchClient (ServerStreamCall WatchTxRequest WatchTxResponse -> WatchClient)
-> ServerStreamCall WatchTxRequest WatchTxResponse -> WatchClient
forall a b. (a -> b) -> a -> b
$ Maybe (UtxorpcClientLogger m)
-> RPC WatchService "watchTx"
-> GrpcClient
-> a
-> WatchTxRequest
-> (a -> [(ByteString, ByteString)] -> WatchTxResponse -> IO a)
-> ServerStreamReply a
forall r o i (m :: * -> *) a.
(GRPCOutput r o, GRPCInput r i, Show i, Message i, Show o,
Message o) =>
Maybe (UtxorpcClientLogger m)
-> r
-> GrpcClient
-> a
-> i
-> (a -> [(ByteString, ByteString)] -> o -> IO a)
-> ServerStreamReply a
loggedSStream Maybe (UtxorpcClientLogger m)
logger RPC WatchService "watchTx"
watchTxRPC GrpcClient
client
watchTxRPC :: RPC WatchService "watchTx"
watchTxRPC :: RPC WatchService "watchTx"
watchTxRPC = RPC WatchService "watchTx"
forall s (m :: Symbol). RPC s m
RPC