Safe Haskell | Safe-Inferred |
---|---|
Language | Haskell2010 |
Run UTxO RPC service from a set of method handlers.
Provide a
to perform automated logging.UtxorpcServiceLogger
Synopsis
- runUtxorpc :: MonadIO m => ServiceConfig m a b c d e -> IO ()
- data ServiceConfig m a b c d e = ServiceConfig {
- tlsSettings :: TLSSettings
- warpSettings :: Settings
- handlers :: UtxorpcHandlers m a b c d e
- logger :: Maybe (UtxorpcServiceLogger m)
- unlift :: forall x. m x -> IO x
- compression :: [Compression]
- data UtxorpcHandlers m a b c d e = UtxorpcHandlers {
- buildHandlers :: BuildHandlers m a
- submitHandlers :: SubmitHandlers m b c
- syncHandlers :: SyncHandlers m d
- watchHandlers :: WatchHandlers m e
- data BuildHandlers m a = BuildHandlers {
- getChainTip :: UnaryHandler m GetChainTipRequest GetChainTipResponse
- getChainParam :: UnaryHandler m GetChainParamRequest GetChainParamResponse
- getUtxoByAddress :: UnaryHandler m GetUtxoByAddressRequest GetUtxoByAddressResponse
- getUtxoByRef :: UnaryHandler m GetUtxoByRefRequest GetUtxoByRefResponse
- holdUtxo :: ServerStreamHandler m HoldUtxoRequest HoldUtxoResponse a
- data SubmitHandlers m a b = SubmitHandlers {}
- data SyncHandlers m a = SyncHandlers {}
- newtype WatchHandlers m a = WatchHandlers {}
- data UtxorpcServiceLogger m = UtxorpcServiceLogger {}
- type RequestLogger m = forall i. Show i => ByteString -> Request -> UUID -> i -> m ()
- type ReplyLogger m = forall o. Show o => ByteString -> Request -> UUID -> o -> m ()
- type ServerStreamLogger m = forall o. Show o => ByteString -> Request -> (UUID, Int) -> o -> m ()
- type ServerStreamEndLogger m = ByteString -> Request -> (UUID, Int) -> m ()
How to use this library
To run a UTxO RPC service:
- Create a
UtxorpcHandlers
record, containing a handler for each method in the specification. - Create a
ServiceConfig
record, containing server settings (e.g., TLS settings), the handlers, and (optionally), a logger. - Call
runUtxorpc
with theServiceConfig
.
Server Stream Methods
To implement a server stream method, provide a
.
Given request metadata and a record of the relevant Message instance,
a ServerStreamHandler
produces an initial stream state and a streaming function,
which folds over the stream state.
The stream is closed when the streaming function produces a ServerStreamHanlder
.Nothing
Logging
Automated logging is supported through the
type.
It is a record of one user-defined logging function for each of the following events:UtxorpcServiceLogger
- Request received.
- Unary reply sent.
- Server stream data sent.
- Server stream ended.
For more information, see
, ServiceConfig
,
and the UtxorpcServiceLogger
example
.
Running a service
:: MonadIO m | |
=> ServiceConfig m a b c d e | Configuration info and method handlers. |
-> IO () |
Run a UTxO RPC service from a
.ServiceConfig
data ServiceConfig m a b c d e Source #
Configuration info and method handlers.
Note that the handlers and logger run in the same monad.
The monadic actions of the logger and handlers for a single call are combined,
and
runs the combined action in IO. This means that changes to the
monadic state made by the request logger (e.g., adding a namespace) are seen by
the handlers and other logging functions for that specific call.unlift
ServiceConfig | |
|
data UtxorpcHandlers m a b c d e Source #
A handler for each method in the UTxO RPC specification.
s require a type variable representing the "stream state" (a value that the stream processes/folds over).
The type variables here (other than ServerStreamHandler
) are the type variables of each stream handler in the record.m
UtxorpcHandlers | |
|
data BuildHandlers m a Source #
data SubmitHandlers m a b Source #
data SyncHandlers m a Source #
newtype WatchHandlers m a Source #
Logging
data UtxorpcServiceLogger m Source #
A record of logging functions that runs in the same monad as
the request handlers. Monadic state is passed along throughout the
lifecycle of responding to a request. This means that changes to the
monadic state in the request logger is seen by the stream logger, stream
handler and logger, and reply logger. An unlift
function to run the monad
in IO is provided to
.runUtxorpc
type RequestLogger m Source #
= forall i. Show i | |
=> ByteString | The RPC path |
-> Request | Request metadata |
-> UUID | A UUID generated for this request and passed to stream and reply loggers. |
-> i | The request message |
-> m () |
Log incoming requests.
type ReplyLogger m Source #
= forall o. Show o | |
=> ByteString | The RPC path |
-> Request | Request metadata |
-> UUID | |
-> o | The reply message |
-> m () |
Log outgoing replies.
type ServerStreamLogger m Source #
= forall o. Show o | |
=> ByteString | The RPC path |
-> Request | Request metadata |
-> (UUID, Int) | The UUID generated for the request that generated this stream, and the 0-based index of the message in the stream. |
-> o | The stream message |
-> m () |
Log outgoing server stream messages.
type ServerStreamEndLogger m Source #
= ByteString | The RPC path |
-> Request | Request metadata |
-> (UUID, Int) | The UUID generated for the request that generated this stream, and the 0-based index of the message in the stream. |
-> m () |
Log the end of a server stream.