{-# LANGUAGE DataKinds #-}
{-# LANGUAGE FlexibleContexts #-}
{-# LANGUAGE NamedFieldPuns #-}
{-# LANGUAGE PackageImports #-}
{-# LANGUAGE RankNTypes #-}

-- |
-- Module        : Utxorpc.Client
-- Description   : Create a connected UTxO RPC client.
-- Create a UTxO RPC client connected to a UTxO RPC service.
-- Provide a UtxorpcClientLogger to perform automated logging.
module Utxorpc.Client
  ( -- * How to use this library
    -- $use

    -- ** Building Messages
    -- $messages

    -- ** Server Stream Methods
    -- $streaming

    -- ** Logging
    -- $logging

    -- ** Examples
    -- $examples

    -- * Creating a @'UtxorpcClient'@
    UtxorpcInfo (..),
    simpleUtxorpcClient,
    utxorpcClient,
    utxorpcClientWith,

    -- * The @'UtxorpcClient'@
    UtxorpcClient (..),
    QueryClient (..),
    SubmitClient (..),
    SyncClient (..),
    WatchClient (..),

    -- ** RPC call function types
    ServerStreamCall,
    ServerStreamReply,
    UnaryReply,

    -- * Logging
    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.Query.Query
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)

-- | Configuration info for a UTxO RPC Client.
-- For more fine-grained control, use @'GrpcClientConfig'@ and @'utxorpcClientWith'@
data UtxorpcInfo m = UtxorpcInfo
  { -- | Host name of the service.
    forall (m :: * -> *). UtxorpcInfo m -> HostName
_hostName :: HostName,
    -- | Port number of the service.
    forall (m :: * -> *). UtxorpcInfo m -> PortNumber
_portNumber :: PortNumber,
    -- | Whether or not to use TLS.
    forall (m :: * -> *). UtxorpcInfo m -> UseTlsOrNot
_tlsEnabled :: UseTlsOrNot,
    -- | Whether or not to use gzip compression.
    forall (m :: * -> *). UtxorpcInfo m -> UseTlsOrNot
_useGzip :: Bool,
    -- | Headers to include in each request (e.g., API key/authorization).
    forall (m :: * -> *). UtxorpcInfo m -> [(ByteString, ByteString)]
_clientHeaders :: [(BS.ByteString, BS.ByteString)],
    -- | Log all RPC events.
    forall (m :: * -> *).
UtxorpcInfo m -> Maybe (UtxorpcClientLogger m)
_logger :: Maybe (UtxorpcClientLogger m)
  }

-- | Make a connection to a UTxO RPC service with the minimum required information.
-- No compression is used, no headers are added, and no logging is performed.
-- For more configurability, use @'utxorpcClient'@ or @'utxorpcClientWith'@.
simpleUtxorpcClient ::
  -- | Host name of the service.
  HostName ->
  -- | Port number of the service.
  PortNumber ->
  -- | Whether or not to use TLS.
  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

-- | Connect to a UTxO RPC service from a @'UtxorpcInfo'@.
-- Provides more configurability than @'simpleUtxorpcClient'@ but less than @'utxorpcClientWith'@.
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
    let sanitizedHost :: HostName
sanitizedHost = if HostName
_hostName HostName -> HostName -> UseTlsOrNot
forall a. Eq a => a -> a -> UseTlsOrNot
== HostName
"localhost" then HostName
"127.0.0.1" else HostName
_hostName
    Either ClientError GrpcClient
eClient <- HostName
-> PortNumber
-> UseTlsOrNot
-> UseTlsOrNot
-> IO (Either ClientError GrpcClient)
grpcClient HostName
sanitizedHost 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}

-- | Connect to a UTxO RPC from a @'GrpcClientConfig'@.
-- For a simpler interface with less configurability, use @'utxorpcClient'@ or @'simpleUtxorpcClient'@.
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 =
  QueryClient
-> SubmitClient
-> SyncClient
-> WatchClient
-> IO (Either ClientError ())
-> UtxorpcClient
UtxorpcClient
    (Maybe (UtxorpcClientLogger m) -> GrpcClient -> QueryClient
forall (m :: * -> *).
Maybe (UtxorpcClientLogger m) -> GrpcClient -> QueryClient
mkQueryClient 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)

{--------------------------------------
  QUERY
--------------------------------------}

mkQueryClient :: Maybe (UtxorpcClientLogger m) -> GrpcClient -> QueryClient
mkQueryClient :: forall (m :: * -> *).
Maybe (UtxorpcClientLogger m) -> GrpcClient -> QueryClient
mkQueryClient Maybe (UtxorpcClientLogger m)
logger GrpcClient
client =
  (ReadParamsRequest -> UnaryReply ReadParamsResponse)
-> (ReadUtxosRequest -> UnaryReply ReadUtxosResponse)
-> (SearchUtxosRequest -> UnaryReply SearchUtxosResponse)
-> ServerStreamCall ReadUtxosRequest ReadUtxosResponse
-> QueryClient
QueryClient
    (Maybe (UtxorpcClientLogger m)
-> RPC QueryService "readParams"
-> GrpcClient
-> ReadParamsRequest
-> UnaryReply ReadParamsResponse
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 QueryService "readParams"
readParamsRPC GrpcClient
client)
    (Maybe (UtxorpcClientLogger m)
-> RPC QueryService "readUtxos"
-> GrpcClient
-> ReadUtxosRequest
-> UnaryReply ReadUtxosResponse
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 QueryService "readUtxos"
readUtxosRPC GrpcClient
client)
    (Maybe (UtxorpcClientLogger m)
-> RPC QueryService "searchUtxos"
-> GrpcClient
-> SearchUtxosRequest
-> UnaryReply SearchUtxosResponse
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 QueryService "searchUtxos"
searchUtxosRPC GrpcClient
client)
    (Maybe (UtxorpcClientLogger m)
-> RPC QueryService "streamUtxos"
-> GrpcClient
-> a
-> ReadUtxosRequest
-> (a -> [(ByteString, ByteString)] -> ReadUtxosResponse -> 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 QueryService "streamUtxos"
streamUtxosRPC GrpcClient
client)

readParamsRPC :: RPC QueryService "readParams"
readParamsRPC :: RPC QueryService "readParams"
readParamsRPC = RPC QueryService "readParams"
forall s (m :: Symbol). RPC s m
RPC

readUtxosRPC :: RPC QueryService "readUtxos"
readUtxosRPC :: RPC QueryService "readUtxos"
readUtxosRPC = RPC QueryService "readUtxos"
forall s (m :: Symbol). RPC s m
RPC

searchUtxosRPC :: RPC QueryService "searchUtxos"
searchUtxosRPC :: RPC QueryService "searchUtxos"
searchUtxosRPC = RPC QueryService "searchUtxos"
forall s (m :: Symbol). RPC s m
RPC

streamUtxosRPC :: RPC QueryService "streamUtxos"
streamUtxosRPC :: RPC QueryService "streamUtxos"
streamUtxosRPC = RPC QueryService "streamUtxos"
forall s (m :: Symbol). RPC s m
RPC

{--------------------------------------
  SUBMIT
--------------------------------------}

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

{--------------------------------------
  SYNC
--------------------------------------}

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

{--------------------------------------
  WATCH
--------------------------------------}

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

-- $use
-- Call any method of a UTxO RPC service through the functions contained in a @'UtxorpcClient'@.
-- Obtain a client by calling one of the client-creating functions:
--
--    1. 'simpleUtxorpcClient' ➤ connect to a service using the bare minimum required information.
--
--        1. See @[quick-start](https://github.com/utxorpc/haskell-sdk/tree/main/client/quick-start)@.
--
--    2. @'utxorpcClient'@ ➤ connect to a service using a @'UtxorpcInfo'@ record.
--
--        1. See @[example](https://github.com/utxorpc/haskell-sdk/tree/main/client/example)@.
--
--    3. @'utxorpcClientWith'@ ➤ provide a @'GrpcClientConfig'@ for fine grained configuration.
--
-- Access the functions of a @'UtxorpcClient'@ through record access:
--
-- > fetchBlock (syncClient client)
--
-- Close the connection throught client's close function:
--
-- > close client

-- $messages
-- To call a UTxO RPC method, you will need a record of the relevant @'Message'@ instance.
-- Build a @'Message'@ with @'defMessage'@ and set its fields with lens operators.
--
-- @
-- import Control.Lens.Operators ((&), (.~))
-- import Data.ProtoLens.Message (Message (defMessage))
-- import qualified Data.Text.Encoding as T
-- import Proto.Utxorpc.V1.Sync.Sync (FetchBlockRequest)
-- import Proto.Utxorpc.V1.Sync.Sync_Fields (hash, index)
--
-- fetchBlockRequest :: FetchBlockRequest
-- fetchBlockRequest =
-- defMessage
--     & ref .~
--     [ defMessage
--         & index .~ 116541970
--         & hash .~ T.encodeUtf8 "9d5abce5b1a7d94b141a597fd621a1ff9dcd46579ff1939664364311cd1be338"
--     ]
-- @

-- $streaming
-- Note that calling a server-stream method requires an input-stream function and initial input-stream state.
-- The input-stream function is of type @(a -> 'HeaderList' -> o -> IO a)@, where @a@ is the initial input-stream
-- state and @o@ is the type of message streamed by the server. The input-stream function folds over its state
-- until the stream is closed.

-- $logging
-- This SDK supports automated logging through the @'UtxorpcClientLogger'@ type.
-- It is a record of one user-defined logging function for each of the following events:
--
--     1. Request sent.
--
--     2. Reply received.
--
--     3. Server stream data received.
--
--     4. Server stream ended.
--
-- For more information, see @'UtxorpcClientLogger'@ and the examples.

-- $examples
-- There are two examples included in the [project](https://github.com/utxorpc/haskell-sdk).
-- There are two provided examples:
--
--     1. `/quick-start` shows the bare minimum required to make a single unary request.
--
--         > stack run client-quick-start -- -p 443
--     2. `/example` shows a more involved example that uses one of the following two logger implementations:
--
--         1. `/example/SimpleLogger.hs` is a simple logger implementation that prints human-readable output.
--
--             > stack run client-example
--             > Usage: [--katip] <hostName> <port> <tlsEnabled> <useGzip> [<headerKey>:<headerValue> [...]]
--             > stack run client-example -- "localhost" 443 True False
--
--         2. `/example/KatipLogger.hs` is a more involved logger that demonstrates how to use logging functions
--         that run in a transformer stack. Run the example with `--katip` to use this logger.
--
--             > stack run client-example -- --katip "localhost" 443 True False