{-# LANGUAGE PackageImports #-}
{-# LANGUAGE RankNTypes #-}
module Utxorpc.Types
( UtxorpcClient (..),
QueryClient (..),
SubmitClient (..),
SyncClient (..),
WatchClient (..),
ServerStreamCall,
ServerStreamReply,
UnaryReply,
)
where
import Network.GRPC.Client (HeaderList, RawReply)
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 "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 -> QueryClient
queryClient :: QueryClient,
UtxorpcClient -> SubmitClient
submitClient :: SubmitClient,
UtxorpcClient -> SyncClient
syncClient :: SyncClient,
UtxorpcClient -> WatchClient
watchClient :: WatchClient,
UtxorpcClient -> IO (Either ClientError ())
close :: IO (Either ClientError ())
}
data QueryClient = QueryClient
{ QueryClient -> ReadParamsRequest -> UnaryReply ReadParamsResponse
readParams :: ReadParamsRequest -> UnaryReply ReadParamsResponse,
QueryClient -> ReadUtxosRequest -> UnaryReply ReadUtxosResponse
readUtxos :: ReadUtxosRequest -> UnaryReply ReadUtxosResponse,
QueryClient -> SearchUtxosRequest -> UnaryReply SearchUtxosResponse
searchUtxos :: SearchUtxosRequest -> UnaryReply SearchUtxosResponse,
QueryClient -> ServerStreamCall ReadUtxosRequest ReadUtxosResponse
streamUtxos :: ServerStreamCall ReadUtxosRequest ReadUtxosResponse
}
data SubmitClient = SubmitClient
{ SubmitClient -> SubmitTxRequest -> UnaryReply SubmitTxResponse
submitTx :: SubmitTxRequest -> UnaryReply SubmitTxResponse,
SubmitClient
-> ReadMempoolRequest -> UnaryReply ReadMempoolResponse
readMempool :: ReadMempoolRequest -> UnaryReply ReadMempoolResponse,
SubmitClient -> ServerStreamCall WaitForTxRequest WaitForTxResponse
waitForTx :: ServerStreamCall WaitForTxRequest WaitForTxResponse,
SubmitClient
-> ServerStreamCall WatchMempoolRequest WatchMempoolResponse
watchMempool :: ServerStreamCall WatchMempoolRequest WatchMempoolResponse
}
data SyncClient = SyncClient
{ SyncClient -> FetchBlockRequest -> UnaryReply FetchBlockResponse
fetchBlock :: FetchBlockRequest -> UnaryReply FetchBlockResponse,
SyncClient -> DumpHistoryRequest -> UnaryReply DumpHistoryResponse
dumpHistory :: DumpHistoryRequest -> UnaryReply DumpHistoryResponse,
SyncClient -> ServerStreamCall FollowTipRequest FollowTipResponse
followTip :: ServerStreamCall FollowTipRequest FollowTipResponse
}
newtype WatchClient = WatchClient
{ WatchClient -> ServerStreamCall WatchTxRequest WatchTxResponse
watchTx :: ServerStreamCall WatchTxRequest WatchTxResponse
}