{-# LANGUAGE PackageImports #-}
{-# LANGUAGE RankNTypes #-}
module Utxorpc.Types
( UtxorpcClient (..),
BuildClientImpl (..),
SubmitClientImpl (..),
SyncClientImpl (..),
WatchClientImpl (..),
ServerStreamCall,
ServerStreamReply,
UnaryReply,
)
where
import Network.GRPC.Client (HeaderList, RawReply)
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 "http2-client" Network.HTTP2.Client (ClientError, TooMuchConcurrency)
type ServerStreamCall i o =
forall a.
a ->
i ->
(a -> HeaderList -> o -> IO a) ->
ServerStreamReply a
type UnaryReply o =
IO
(Either ClientError (Either TooMuchConcurrency (RawReply o)))
type ServerStreamReply a =
IO
(Either ClientError (Either TooMuchConcurrency (a, HeaderList, HeaderList)))
data UtxorpcClient = UtxorpcClient
{
UtxorpcClient -> BuildClientImpl
buildClient :: BuildClientImpl,
UtxorpcClient -> SubmitClientImpl
submitClient :: SubmitClientImpl,
UtxorpcClient -> SyncClientImpl
syncClient :: SyncClientImpl,
UtxorpcClient -> WatchClientImpl
watchClient :: WatchClientImpl,
UtxorpcClient -> IO (Either ClientError ())
close :: IO (Either ClientError ())
}
data BuildClientImpl = BuildClientImpl
{ BuildClientImpl
-> GetChainTipRequest -> UnaryReply GetChainTipResponse
getChainTip :: GetChainTipRequest -> UnaryReply GetChainTipResponse,
BuildClientImpl
-> GetChainParamRequest -> UnaryReply GetChainParamResponse
getChainParam :: GetChainParamRequest -> UnaryReply GetChainParamResponse,
BuildClientImpl
-> GetUtxoByAddressRequest -> UnaryReply GetUtxoByAddressResponse
getUtxoByAddress :: GetUtxoByAddressRequest -> UnaryReply GetUtxoByAddressResponse,
BuildClientImpl
-> GetUtxoByRefRequest -> UnaryReply GetUtxoByRefResponse
getUtxoByRef :: GetUtxoByRefRequest -> UnaryReply GetUtxoByRefResponse,
BuildClientImpl
-> ServerStreamCall HoldUtxoRequest HoldUtxoResponse
holdUtxo :: ServerStreamCall HoldUtxoRequest HoldUtxoResponse
}
data SubmitClientImpl = SubmitClientImpl
{ SubmitClientImpl -> SubmitTxRequest -> UnaryReply SubmitTxResponse
submitTx :: SubmitTxRequest -> UnaryReply SubmitTxResponse,
SubmitClientImpl
-> ReadMempoolRequest -> UnaryReply ReadMempoolResponse
readMempool :: ReadMempoolRequest -> UnaryReply ReadMempoolResponse,
SubmitClientImpl
-> ServerStreamCall WaitForTxRequest WaitForTxResponse
waitForTx :: ServerStreamCall WaitForTxRequest WaitForTxResponse,
SubmitClientImpl
-> ServerStreamCall WatchMempoolRequest WatchMempoolResponse
watchMempool :: ServerStreamCall WatchMempoolRequest WatchMempoolResponse
}
data SyncClientImpl = SyncClientImpl
{ SyncClientImpl
-> FetchBlockRequest -> UnaryReply FetchBlockResponse
fetchBlock :: FetchBlockRequest -> UnaryReply FetchBlockResponse,
SyncClientImpl
-> DumpHistoryRequest -> UnaryReply DumpHistoryResponse
dumpHistory :: DumpHistoryRequest -> UnaryReply DumpHistoryResponse,
SyncClientImpl
-> ServerStreamCall FollowTipRequest FollowTipResponse
followTip :: ServerStreamCall FollowTipRequest FollowTipResponse
}
newtype WatchClientImpl = WatchClientImpl
{ WatchClientImpl -> ServerStreamCall WatchTxRequest WatchTxResponse
watchTx :: ServerStreamCall WatchTxRequest WatchTxResponse
}