{-# LANGUAGE DataKinds #-} {-# LANGUAGE NamedFieldPuns #-} {-# LANGUAGE RankNTypes #-} module Utxorpc.Sync (SyncHandlers (..), serviceHandlers) where import Control.Monad.IO.Class (MonadIO) import Network.GRPC.HTTP2.ProtoLens (RPC (RPC)) import Network.GRPC.Server (ServerStreamHandler, ServiceHandler, UnaryHandler) import Proto.Utxorpc.V1alpha.Sync.Sync import Utxorpc.Logged (UtxorpcServiceLogger, loggedSStream, loggedUnary) data SyncHandlers m a = SyncHandlers { forall (m :: * -> *) a. SyncHandlers m a -> UnaryHandler m FetchBlockRequest FetchBlockResponse fetchBlock :: UnaryHandler m FetchBlockRequest FetchBlockResponse, forall (m :: * -> *) a. SyncHandlers m a -> UnaryHandler m DumpHistoryRequest DumpHistoryResponse dumpHistory :: UnaryHandler m DumpHistoryRequest DumpHistoryResponse, forall (m :: * -> *) a. SyncHandlers m a -> ServerStreamHandler m FollowTipRequest FollowTipResponse a followTip :: ServerStreamHandler m FollowTipRequest FollowTipResponse a } serviceHandlers :: (MonadIO m) => Maybe (UtxorpcServiceLogger m) -> (forall x. m x -> IO x) -> SyncHandlers m b -> [ServiceHandler] serviceHandlers :: forall (m :: * -> *) b. MonadIO m => Maybe (UtxorpcServiceLogger m) -> (forall x. m x -> IO x) -> SyncHandlers m b -> [ServiceHandler] serviceHandlers Maybe (UtxorpcServiceLogger m) logger forall x. m x -> IO x f SyncHandlers {UnaryHandler m FetchBlockRequest FetchBlockResponse fetchBlock :: forall (m :: * -> *) a. SyncHandlers m a -> UnaryHandler m FetchBlockRequest FetchBlockResponse fetchBlock :: UnaryHandler m FetchBlockRequest FetchBlockResponse fetchBlock, UnaryHandler m DumpHistoryRequest DumpHistoryResponse dumpHistory :: forall (m :: * -> *) a. SyncHandlers m a -> UnaryHandler m DumpHistoryRequest DumpHistoryResponse dumpHistory :: UnaryHandler m DumpHistoryRequest DumpHistoryResponse dumpHistory, ServerStreamHandler m FollowTipRequest FollowTipResponse b followTip :: forall (m :: * -> *) a. SyncHandlers m a -> ServerStreamHandler m FollowTipRequest FollowTipResponse a followTip :: ServerStreamHandler m FollowTipRequest FollowTipResponse b followTip} = [ServiceHandler fetchBlockSH, ServiceHandler dumpHistorySH, ServiceHandler followTipSH] where fetchBlockSH :: ServiceHandler fetchBlockSH = (forall x. m x -> IO x) -> RPC ChainSyncService "fetchBlock" -> UnaryHandler m FetchBlockRequest FetchBlockResponse -> Maybe (UtxorpcServiceLogger m) -> ServiceHandler forall (m :: * -> *) r i o. (MonadIO m, GRPCInput r i, GRPCOutput r o, Show i, Show o) => (forall x. m x -> IO x) -> r -> UnaryHandler m i o -> Maybe (UtxorpcServiceLogger m) -> ServiceHandler loggedUnary m x -> IO x forall x. m x -> IO x f (RPC ChainSyncService "fetchBlock" forall s (m :: Symbol). RPC s m RPC :: RPC ChainSyncService "fetchBlock") UnaryHandler m FetchBlockRequest FetchBlockResponse fetchBlock Maybe (UtxorpcServiceLogger m) logger dumpHistorySH :: ServiceHandler dumpHistorySH = (forall x. m x -> IO x) -> RPC ChainSyncService "dumpHistory" -> UnaryHandler m DumpHistoryRequest DumpHistoryResponse -> Maybe (UtxorpcServiceLogger m) -> ServiceHandler forall (m :: * -> *) r i o. (MonadIO m, GRPCInput r i, GRPCOutput r o, Show i, Show o) => (forall x. m x -> IO x) -> r -> UnaryHandler m i o -> Maybe (UtxorpcServiceLogger m) -> ServiceHandler loggedUnary m x -> IO x forall x. m x -> IO x f (RPC ChainSyncService "dumpHistory" forall s (m :: Symbol). RPC s m RPC :: RPC ChainSyncService "dumpHistory") UnaryHandler m DumpHistoryRequest DumpHistoryResponse dumpHistory Maybe (UtxorpcServiceLogger m) logger followTipSH :: ServiceHandler followTipSH = (forall x. m x -> IO x) -> RPC ChainSyncService "followTip" -> ServerStreamHandler m FollowTipRequest FollowTipResponse b -> Maybe (UtxorpcServiceLogger m) -> ServiceHandler forall (m :: * -> *) r i o a. (MonadIO m, GRPCInput r i, GRPCOutput r o, Show i, Show o) => (forall x. m x -> IO x) -> r -> ServerStreamHandler m i o a -> Maybe (UtxorpcServiceLogger m) -> ServiceHandler loggedSStream m x -> IO x forall x. m x -> IO x f (RPC ChainSyncService "followTip" forall s (m :: Symbol). RPC s m RPC :: RPC ChainSyncService "followTip") ServerStreamHandler m FollowTipRequest FollowTipResponse b followTip Maybe (UtxorpcServiceLogger m) logger