Safe Haskell | Safe-Inferred |
---|---|
Language | Haskell2010 |
Create a UTxO RPC client connected to a UTxO RPC service. Provide a UtxorpcClientLogger to perform automated logging.
Synopsis
- data UtxorpcInfo m = UtxorpcInfo {
- _hostName :: HostName
- _portNumber :: PortNumber
- _tlsEnabled :: UseTlsOrNot
- _useGzip :: Bool
- _clientHeaders :: [(ByteString, ByteString)]
- _logger :: Maybe (UtxorpcClientLogger m)
- simpleUtxorpcClient :: HostName -> PortNumber -> UseTlsOrNot -> IO (Either ClientError UtxorpcClient)
- utxorpcClient :: UtxorpcInfo m -> IO (Either ClientError UtxorpcClient)
- utxorpcClientWith :: GrpcClientConfig -> Maybe (UtxorpcClientLogger m) -> IO (Either ClientError UtxorpcClient)
- data UtxorpcClient = UtxorpcClient {}
- data BuildClient = BuildClient {
- getChainTip :: GetChainTipRequest -> UnaryReply GetChainTipResponse
- getChainParam :: GetChainParamRequest -> UnaryReply GetChainParamResponse
- getUtxoByAddress :: GetUtxoByAddressRequest -> UnaryReply GetUtxoByAddressResponse
- getUtxoByRef :: GetUtxoByRefRequest -> UnaryReply GetUtxoByRefResponse
- holdUtxo :: ServerStreamCall HoldUtxoRequest HoldUtxoResponse
- data SubmitClient = SubmitClient {}
- data SyncClient = SyncClient {}
- newtype WatchClient = WatchClient {}
- type ServerStreamCall i o = forall a. a -> i -> (a -> HeaderList -> o -> IO a) -> ServerStreamReply a
- type ServerStreamReply a = IO (Either ClientError (Either TooMuchConcurrency (a, HeaderList, HeaderList)))
- type UnaryReply o = IO (Either ClientError (Either TooMuchConcurrency (RawReply o)))
- data UtxorpcClientLogger m = UtxorpcClientLogger {
- requestLogger :: RequestLogger m
- replyLogger :: ReplyLogger m
- serverStreamLogger :: ServerStreamLogger m
- serverStreamEndLogger :: ServerStreamEndLogger m
- unlift :: forall x. m x -> IO x
- type RequestLogger m = forall i. (Show i, Message i) => ByteString -> GrpcClient -> UUID -> i -> m ()
- type ReplyLogger m = forall o. (Show o, Message o) => ByteString -> GrpcClient -> UUID -> Either ClientError (Either TooMuchConcurrency (RawReply o)) -> m ()
- type ServerStreamLogger m = forall o. (Show o, Message o) => ByteString -> GrpcClient -> (UUID, Int) -> o -> m ()
- type ServerStreamEndLogger m = ByteString -> GrpcClient -> (UUID, Int) -> (HeaderList, HeaderList) -> m ()
How to use this library
Call any method of a UTxO RPC service through the functions contained in a
.
Obtain a client by calling one of the client-creating functions:UtxorpcClient
simpleUtxorpcClient
➤ connect to a service using the bare minimum required information.- See
quick-start
.
- See
➤ connect to a service using autxorpcClient
record.UtxorpcInfo
- See
example
.
- See
➤ provide autxorpcClientWith
for fine grained configuration.GrpcClientConfig
Access the functions of a
through record access:UtxorpcClient
fetchBlock (syncClient client)
Close the connection throught client's close function:
close client
Building Messages
To call a UTxO RPC method, you will need a record of the relevant
instance.
Build a Message
with Message
and set its fields with lens operators.defMessage
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" ]
Server Stream Methods
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 ->
, where HeaderList
-> o -> IO a)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
type.
It is a record of one user-defined logging function for each of the following events:UtxorpcClientLogger
- Request sent.
- Reply received.
- Server stream data received.
- Server stream ended.
For more information, see
and the examples.Logged
Examples
There are two examples included in the project. There are two provided examples:
- `/quick-start` shows the bare minimum required to make a single unary request.
stack run client-quick-start -- -p 443
`/example` shows a more involved example that uses one of the following two logger implementations:
`exampleSimpleLogger.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
`exampleKatipLogger.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
Creating a UtxorpcClient
UtxorpcClient
data UtxorpcInfo m Source #
Configuration info for a UTxO RPC Client.
For more fine-grained control, use
and GrpcClientConfig
utxorpcClientWith
UtxorpcInfo | |
|
:: HostName | Host name of the service. |
-> PortNumber | Port number of the service. |
-> UseTlsOrNot | Whether or not to use TLS. |
-> IO (Either ClientError UtxorpcClient) |
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
or utxorpcClient
.utxorpcClientWith
utxorpcClient :: UtxorpcInfo m -> IO (Either ClientError UtxorpcClient) Source #
Connect to a UTxO RPC service from a
.
Provides more configurability than UtxorpcInfo
but less than simpleUtxorpcClient
.utxorpcClientWith
utxorpcClientWith :: GrpcClientConfig -> Maybe (UtxorpcClientLogger m) -> IO (Either ClientError UtxorpcClient) Source #
Connect to a UTxO RPC from a
.
For a simpler interface with less configurability, use GrpcClientConfig
or utxorpcClient
.simpleUtxorpcClient
The UtxorpcClient
UtxorpcClient
data UtxorpcClient Source #
Methods for each module in UTxO RPC.
>>>
fetchBlock (buildClient client) defMessage
UtxorpcClient | |
|
data BuildClient Source #
Methods of the Build module
data SubmitClient Source #
Methods of the Submit module
data SyncClient Source #
Methods of the Sync module
newtype WatchClient Source #
Methods of the watch module
RPC call function types
type ServerStreamCall i o Source #
= forall a. a | The initial state for the stream processing function. |
-> i | The request message to send to the service. |
-> (a -> HeaderList -> o -> IO a) | The stream processing function. It is a fold over some state a with stream messages o. |
-> ServerStreamReply a | The final state of the stream processing function, or an error. |
Type definition for functions that make calls to server stream methods. Note that the stream state, a, can be different for each call.
type ServerStreamReply a = IO (Either ClientError (Either TooMuchConcurrency (a, HeaderList, HeaderList))) Source #
The type returned by calls to server stream methods. a is the final state of the stream processing function.
type UnaryReply o = IO (Either ClientError (Either TooMuchConcurrency (RawReply o))) Source #
The type returned by calls to unary service methods.
Logging
data UtxorpcClientLogger m Source #
Logging functions to log requests, replies, server stream messages, and server stream endings. A UUID is generated for each request and passed downstream to the other logging functions.
UtxorpcClientLogger | |
|
type RequestLogger m Source #
= forall i. (Show i, Message i) | |
=> ByteString | The RPC path |
-> GrpcClient | Included because it contains useful information such as the server address. |
-> UUID | Generated for this request, and passed to other logging functions for other RPC events generated by this request. E.g., A unary request and its reply both have the same UUID. |
-> i | The request message being sent. |
-> m () |
Log outgoing requests of all types (i.e., unary requests and server stream requests).
type ReplyLogger m Source #
= forall o. (Show o, Message o) | |
=> ByteString | The RPC path |
-> GrpcClient | Included because it contains useful information such as the server address. |
-> UUID | Generated for the request that this reply is associated with. |
-> Either ClientError (Either TooMuchConcurrency (RawReply o)) | Message received from the service (with headers) or an error. |
-> m () |
Log unary replies.
type ServerStreamLogger m Source #
= forall o. (Show o, Message o) | |
=> ByteString | The RPC path |
-> GrpcClient | Included because it contains useful information such as the server address. |
-> (UUID, Int) | The UUID was generated for the request that caused this reply, the Int is the index of this message in the stream. |
-> o | Message received from the service. |
-> m () |
Log server stream messages.
type ServerStreamEndLogger m Source #
= ByteString | The RPC path |
-> GrpcClient | Included because it contains useful information such as the server address. |
-> (UUID, Int) | The UUID was generated for the request that caused this reply, the Int is the total number of messages received in the stream. |
-> (HeaderList, HeaderList) | Headers and Trailers. |
-> m () |