{-# LANGUAGE NamedFieldPuns #-}
{-# LANGUAGE RankNTypes #-}
module Utxorpc.Server
(
runUtxorpc,
ServiceConfig (..),
UtxorpcHandlers (..),
QueryHandlers (..),
SubmitHandlers (..),
SyncHandlers (..),
WatchHandlers (..),
UtxorpcServiceLogger (..),
RequestLogger,
ReplyLogger,
ServerStreamLogger,
ServerStreamEndLogger,
)
where
import Control.Monad.IO.Class (MonadIO)
import Network.GRPC.HTTP2.Encoding (Compression)
import Network.GRPC.Server
import Network.Wai.Handler.Warp (Settings)
import Network.Wai.Handler.WarpTLS (TLSSettings)
import Utxorpc.Query as Query (QueryHandlers (..), serviceHandlers)
import Utxorpc.Logged (ReplyLogger, RequestLogger, ServerStreamEndLogger, ServerStreamLogger, UtxorpcServiceLogger (..))
import Utxorpc.Submit as Submit (SubmitHandlers (..), serviceHandlers)
import Utxorpc.Sync as Sync (SyncHandlers (..), serviceHandlers)
import Utxorpc.Watch as Watch (WatchHandlers (..), serviceHandlers)
runUtxorpc ::
(MonadIO m) =>
ServiceConfig m a b c d e ->
IO ()
runUtxorpc :: forall (m :: * -> *) a b c d e.
MonadIO m =>
ServiceConfig m a b c d e -> IO ()
runUtxorpc
ServiceConfig
{ TLSSettings
tlsSettings :: TLSSettings
tlsSettings :: forall (m :: * -> *) a b c d e.
ServiceConfig m a b c d e -> TLSSettings
tlsSettings,
Settings
warpSettings :: Settings
warpSettings :: forall (m :: * -> *) a b c d e.
ServiceConfig m a b c d e -> Settings
warpSettings,
UtxorpcHandlers m a b c d e
handlers :: UtxorpcHandlers m a b c d e
handlers :: forall (m :: * -> *) a b c d e.
ServiceConfig m a b c d e -> UtxorpcHandlers m a b c d e
handlers,
Maybe (UtxorpcServiceLogger m)
logger :: Maybe (UtxorpcServiceLogger m)
logger :: forall (m :: * -> *) a b c d e.
ServiceConfig m a b c d e -> Maybe (UtxorpcServiceLogger m)
logger,
forall x. m x -> IO x
unlift :: forall x. m x -> IO x
unlift :: forall (m :: * -> *) a b c d e.
ServiceConfig m a b c d e -> forall x. m x -> IO x
unlift,
[Compression]
compression :: [Compression]
compression :: forall (m :: * -> *) a b c d e.
ServiceConfig m a b c d e -> [Compression]
compression
} =
TLSSettings
-> Settings -> [ServiceHandler] -> [Compression] -> IO ()
runGrpc
TLSSettings
tlsSettings
Settings
warpSettings
(Maybe (UtxorpcServiceLogger m)
-> (forall x. m x -> IO x)
-> UtxorpcHandlers m a b c d e
-> [ServiceHandler]
forall (m :: * -> *) a b c d e.
MonadIO m =>
Maybe (UtxorpcServiceLogger m)
-> (forall x. m x -> IO x)
-> UtxorpcHandlers m a b c d e
-> [ServiceHandler]
Utxorpc.Server.serviceHandlers Maybe (UtxorpcServiceLogger m)
logger m x -> IO x
forall x. m x -> IO x
unlift UtxorpcHandlers m a b c d e
handlers)
[Compression]
compression
data ServiceConfig m a b c d e = ServiceConfig
{
forall (m :: * -> *) a b c d e.
ServiceConfig m a b c d e -> TLSSettings
tlsSettings :: TLSSettings,
forall (m :: * -> *) a b c d e.
ServiceConfig m a b c d e -> Settings
warpSettings :: Settings,
forall (m :: * -> *) a b c d e.
ServiceConfig m a b c d e -> UtxorpcHandlers m a b c d e
handlers :: UtxorpcHandlers m a b c d e,
forall (m :: * -> *) a b c d e.
ServiceConfig m a b c d e -> Maybe (UtxorpcServiceLogger m)
logger :: Maybe (UtxorpcServiceLogger m),
forall (m :: * -> *) a b c d e.
ServiceConfig m a b c d e -> forall x. m x -> IO x
unlift :: forall x. m x -> IO x,
forall (m :: * -> *) a b c d e.
ServiceConfig m a b c d e -> [Compression]
compression :: [Compression]
}
data
UtxorpcHandlers
m
a
b
c
d
e
= UtxorpcHandlers
{
forall (m :: * -> *) a b c d e.
UtxorpcHandlers m a b c d e -> Maybe (QueryHandlers m a)
queryHandlers :: Maybe (QueryHandlers m a),
forall (m :: * -> *) a b c d e.
UtxorpcHandlers m a b c d e -> Maybe (SubmitHandlers m b c)
submitHandlers :: Maybe (SubmitHandlers m b c),
forall (m :: * -> *) a b c d e.
UtxorpcHandlers m a b c d e -> Maybe (SyncHandlers m d)
syncHandlers :: Maybe (SyncHandlers m d),
forall (m :: * -> *) a b c d e.
UtxorpcHandlers m a b c d e -> Maybe (WatchHandlers m e)
watchHandlers :: Maybe (WatchHandlers m e)
}
serviceHandlers ::
(MonadIO m) =>
Maybe (UtxorpcServiceLogger m) ->
(forall x. m x -> IO x) ->
UtxorpcHandlers m a b c d e ->
[ServiceHandler]
serviceHandlers :: forall (m :: * -> *) a b c d e.
MonadIO m =>
Maybe (UtxorpcServiceLogger m)
-> (forall x. m x -> IO x)
-> UtxorpcHandlers m a b c d e
-> [ServiceHandler]
serviceHandlers
Maybe (UtxorpcServiceLogger m)
logger
forall x. m x -> IO x
unlift
UtxorpcHandlers {Maybe (QueryHandlers m a)
queryHandlers :: forall (m :: * -> *) a b c d e.
UtxorpcHandlers m a b c d e -> Maybe (QueryHandlers m a)
queryHandlers :: Maybe (QueryHandlers m a)
queryHandlers, Maybe (SubmitHandlers m b c)
submitHandlers :: forall (m :: * -> *) a b c d e.
UtxorpcHandlers m a b c d e -> Maybe (SubmitHandlers m b c)
submitHandlers :: Maybe (SubmitHandlers m b c)
submitHandlers, Maybe (SyncHandlers m d)
syncHandlers :: forall (m :: * -> *) a b c d e.
UtxorpcHandlers m a b c d e -> Maybe (SyncHandlers m d)
syncHandlers :: Maybe (SyncHandlers m d)
syncHandlers, Maybe (WatchHandlers m e)
watchHandlers :: forall (m :: * -> *) a b c d e.
UtxorpcHandlers m a b c d e -> Maybe (WatchHandlers m e)
watchHandlers :: Maybe (WatchHandlers m e)
watchHandlers} =
[ServiceHandler]
-> (QueryHandlers m a -> [ServiceHandler])
-> Maybe (QueryHandlers m a)
-> [ServiceHandler]
forall b a. b -> (a -> b) -> Maybe a -> b
maybe [] (Maybe (UtxorpcServiceLogger m)
-> (forall x. m x -> IO x) -> QueryHandlers m a -> [ServiceHandler]
forall (m :: * -> *) b.
MonadIO m =>
Maybe (UtxorpcServiceLogger m)
-> (forall x. m x -> IO x) -> QueryHandlers m b -> [ServiceHandler]
Query.serviceHandlers Maybe (UtxorpcServiceLogger m)
logger m x -> IO x
forall x. m x -> IO x
unlift) Maybe (QueryHandlers m a)
queryHandlers
[ServiceHandler] -> [ServiceHandler] -> [ServiceHandler]
forall a. Semigroup a => a -> a -> a
<> [ServiceHandler]
-> (SubmitHandlers m b c -> [ServiceHandler])
-> Maybe (SubmitHandlers m b c)
-> [ServiceHandler]
forall b a. b -> (a -> b) -> Maybe a -> b
maybe [] (Maybe (UtxorpcServiceLogger m)
-> (forall x. m x -> IO x)
-> SubmitHandlers m b c
-> [ServiceHandler]
forall (m :: * -> *) b c.
MonadIO m =>
Maybe (UtxorpcServiceLogger m)
-> (forall x. m x -> IO x)
-> SubmitHandlers m b c
-> [ServiceHandler]
Submit.serviceHandlers Maybe (UtxorpcServiceLogger m)
logger m x -> IO x
forall x. m x -> IO x
unlift) Maybe (SubmitHandlers m b c)
submitHandlers
[ServiceHandler] -> [ServiceHandler] -> [ServiceHandler]
forall a. Semigroup a => a -> a -> a
<> [ServiceHandler]
-> (SyncHandlers m d -> [ServiceHandler])
-> Maybe (SyncHandlers m d)
-> [ServiceHandler]
forall b a. b -> (a -> b) -> Maybe a -> b
maybe [] (Maybe (UtxorpcServiceLogger m)
-> (forall x. m x -> IO x) -> SyncHandlers m d -> [ServiceHandler]
forall (m :: * -> *) b.
MonadIO m =>
Maybe (UtxorpcServiceLogger m)
-> (forall x. m x -> IO x) -> SyncHandlers m b -> [ServiceHandler]
Sync.serviceHandlers Maybe (UtxorpcServiceLogger m)
logger m x -> IO x
forall x. m x -> IO x
unlift) Maybe (SyncHandlers m d)
syncHandlers
[ServiceHandler] -> [ServiceHandler] -> [ServiceHandler]
forall a. Semigroup a => a -> a -> a
<> [ServiceHandler]
-> (WatchHandlers m e -> [ServiceHandler])
-> Maybe (WatchHandlers m e)
-> [ServiceHandler]
forall b a. b -> (a -> b) -> Maybe a -> b
maybe [] (Maybe (UtxorpcServiceLogger m)
-> (forall x. m x -> IO x) -> WatchHandlers m e -> [ServiceHandler]
forall (m :: * -> *) b.
MonadIO m =>
Maybe (UtxorpcServiceLogger m)
-> (forall x. m x -> IO x) -> WatchHandlers m b -> [ServiceHandler]
Watch.serviceHandlers Maybe (UtxorpcServiceLogger m)
logger m x -> IO x
forall x. m x -> IO x
unlift) Maybe (WatchHandlers m e)
watchHandlers