|
| 1 | +{-# LANGUAGE DataKinds #-} |
1 | 2 | {-# LANGUAGE DeriveAnyClass #-} |
2 | 3 | {-# LANGUAGE DeriveGeneric #-} |
3 | 4 | {-# LANGUAGE LambdaCase #-} |
|
6 | 7 | module DMQ.NodeToClient where |
7 | 8 |
|
8 | 9 | import Codec.CBOR.Term qualified as CBOR |
| 10 | +import Codec.Serialise (Serialise (decode, encode)) |
9 | 11 | import Control.DeepSeq (NFData) |
10 | 12 | import Control.Monad ((>=>)) |
11 | 13 | import Data.Bits (Bits (..)) |
| 14 | +import Data.ByteString.Lazy (ByteString) |
12 | 15 | import Data.Text (Text) |
13 | 16 | import Data.Text qualified as T |
| 17 | +import Data.Void |
14 | 18 | import GHC.Generics (Generic) |
15 | 19 |
|
| 20 | +import Control.Concurrent.Class.MonadSTM |
| 21 | +import Control.Monad.Class.MonadFork |
16 | 22 | import Control.Monad.Class.MonadST (MonadST) |
| 23 | +import Control.Monad.Class.MonadThrow |
17 | 24 | import Control.Tracer (Tracer, nullTracer) |
18 | 25 |
|
19 | 26 | import Network.Mux qualified as Mx |
| 27 | +import Network.TypedProtocol.Codec hiding (encode, decode) |
| 28 | +import Network.TypedProtocol.Codec.CBOR qualified as CBOR |
| 29 | + |
| 30 | +import DMQ.Diffusion.NodeKernel |
| 31 | +import DMQ.NtC_Applications.LocalMsgSubmission |
| 32 | +import DMQ.NtC_Applications.LocalMsgNotification |
| 33 | +import DMQ.Protocol.LocalMsgNotification.Codec |
| 34 | +import DMQ.Protocol.LocalMsgNotification.Server |
| 35 | +import DMQ.Protocol.LocalMsgNotification.Type |
| 36 | +import DMQ.Protocol.LocalMsgSubmission.Codec |
| 37 | +import DMQ.Protocol.LocalMsgSubmission.Server |
| 38 | +import DMQ.Protocol.LocalMsgSubmission.Type |
| 39 | +import DMQ.Protocol.SigSubmission.Codec |
| 40 | +import DMQ.Protocol.SigSubmission.Type |
20 | 41 |
|
21 | 42 | import Ouroboros.Network.CodecCBORTerm (CodecCBORTerm (..)) |
22 | | -import Ouroboros.Network.ConnectionId (ConnectionId) |
23 | | -import Ouroboros.Network.Driver.Simple (TraceSendRecv) |
| 43 | +import Ouroboros.Network.Context |
| 44 | +import Ouroboros.Network.Driver.Simple |
24 | 45 | import Ouroboros.Network.Handshake.Acceptable (Acceptable (..)) |
25 | 46 | import Ouroboros.Network.Handshake.Queryable (Queryable (..)) |
26 | 47 | import Ouroboros.Network.Magic (NetworkMagic (..)) |
| 48 | +import Ouroboros.Network.Mux |
27 | 49 | import Ouroboros.Network.Protocol.Handshake (Accept (..), Handshake, |
28 | 50 | HandshakeArguments (..)) |
29 | 51 | import Ouroboros.Network.Protocol.Handshake.Codec (cborTermVersionDataCodec, |
30 | 52 | codecHandshake, noTimeLimitsHandshake) |
| 53 | +import Ouroboros.Network.TxSubmission.Mempool.Simple qualified as Mempool |
| 54 | + |
31 | 55 |
|
32 | 56 | data NodeToClientVersion = |
33 | 57 | NodeToClientV_1 |
@@ -106,9 +130,6 @@ nodeToClientCodecCBORTerm _v = CodecCBORTerm {encodeTerm, decodeTerm} |
106 | 130 | decoder x query | x >= 0 && x <= 0xffffffff = Right (NodeToClientVersionData (NetworkMagic $ fromIntegral x) query) |
107 | 131 | | otherwise = Left $ T.pack $ "networkMagic out of bound: " <> show x |
108 | 132 |
|
109 | | -data Protocols = |
110 | | - Protocols { |
111 | | - } |
112 | 133 |
|
113 | 134 | type HandshakeTr ntcAddr = Mx.WithBearer (ConnectionId ntcAddr) (TraceSendRecv (Handshake NodeToClientVersion CBOR.Term)) |
114 | 135 |
|
@@ -139,3 +160,158 @@ stdVersionDataNTC networkMagic = |
139 | 160 | { networkMagic |
140 | 161 | , query = False |
141 | 162 | } |
| 163 | + |
| 164 | + |
| 165 | +-- TODO: delete these aliases |
| 166 | +type LocalMsgSubmission' = LocalMsgSubmission Sig Int |
| 167 | +type LocalMsgNotification' = LocalMsgNotification Sig |
| 168 | + |
| 169 | +data Codecs m = |
| 170 | + Codecs { |
| 171 | + msgSubmissionCodec |
| 172 | + :: !(Codec LocalMsgSubmission' |
| 173 | + CBOR.DeserialiseFailure m ByteString) |
| 174 | + , msgNotificationCodec |
| 175 | + :: !(Codec LocalMsgNotification' |
| 176 | + CBOR.DeserialiseFailure m ByteString) |
| 177 | + } |
| 178 | + |
| 179 | +dmqCodecs :: MonadST m |
| 180 | + => Codecs m |
| 181 | +dmqCodecs = |
| 182 | + Codecs { |
| 183 | + msgSubmissionCodec = codecLocalMsgSubmission encodeSig decodeSig encode decode |
| 184 | + , msgNotificationCodec = codecLocalMsgNotification encodeSig decodeSig |
| 185 | + } |
| 186 | + |
| 187 | + |
| 188 | +-- | A node-to-client application |
| 189 | +-- |
| 190 | +type App ntcAddr m a = |
| 191 | + NodeToClientVersion |
| 192 | + -> ResponderContext ntcAddr |
| 193 | + -> Mx.Channel m ByteString |
| 194 | + -> m (a, Maybe ByteString) |
| 195 | + |
| 196 | + |
| 197 | +data Apps ntcAddr m a = |
| 198 | + Apps { |
| 199 | + -- | Start a sig-submission client |
| 200 | + aLocalMsgSubmission :: !(App ntcAddr m a) |
| 201 | + |
| 202 | + -- | Start a sig-submission server |
| 203 | + , aLocalMsgNotification :: !(App ntcAddr m a) |
| 204 | + } |
| 205 | + |
| 206 | + |
| 207 | +-- | Construct applications for the node-to-client protocols |
| 208 | +-- |
| 209 | +ntcApps |
| 210 | + :: (MonadThrow m, MonadThread m, MonadSTM m) |
| 211 | + => NodeKernel ntnAddr m |
| 212 | + -> Codecs m |
| 213 | + -> Apps ntcAddr m () |
| 214 | +ntcApps NodeKernel { mempool } |
| 215 | + Codecs { msgSubmissionCodec, msgNotificationCodec } = |
| 216 | + Apps { |
| 217 | + aLocalMsgSubmission |
| 218 | + , aLocalMsgNotification |
| 219 | + } |
| 220 | + where |
| 221 | + sigSize :: Sig -> SizeInBytes |
| 222 | + sigSize _ = 0 -- TODO |
| 223 | + |
| 224 | + mempoolReader = Mempool.getReader sigId sigSize mempool |
| 225 | + mempoolWriter = Mempool.getWriter sigId (const True) mempool |
| 226 | + |
| 227 | + aLocalMsgSubmission _version _ctx channel = do |
| 228 | + labelThisThread "LocalMsgSubmissionServer" |
| 229 | + runPeer |
| 230 | + nullTracer |
| 231 | + msgSubmissionCodec |
| 232 | + channel |
| 233 | + (localMsgSubmissionServerPeer $ |
| 234 | + localMsgSubmissionServer undefined mempoolWriter) |
| 235 | + |
| 236 | + aLocalMsgNotification _version _ctx channel = do |
| 237 | + labelThisThread "LocalMsgNotificationServer" |
| 238 | + runPeer |
| 239 | + nullTracer |
| 240 | + msgNotificationCodec |
| 241 | + channel |
| 242 | + (localMsgNotificationServerPeer $ |
| 243 | + localMsgNotificationServer undefined nullTracer undefined mempoolReader) |
| 244 | + |
| 245 | + |
| 246 | +data Protocols appType ntcAddr bytes m a b = |
| 247 | + Protocols { |
| 248 | + msgSubmissionProtocol :: !(RunMiniProtocolWithMinimalCtx appType ntcAddr bytes m a b) |
| 249 | + , msgNotificationProtocol :: !(RunMiniProtocolWithMinimalCtx appType ntcAddr bytes m a b) |
| 250 | + } |
| 251 | + |
| 252 | +responders |
| 253 | + :: Apps ntcAddr m a |
| 254 | + -> NodeToClientVersion |
| 255 | + -> NodeToClientVersionData |
| 256 | + -> OuroborosApplicationWithMinimalCtx Mx.ResponderMode ntcAddr ByteString m Void a |
| 257 | +responders Apps { |
| 258 | + aLocalMsgSubmission |
| 259 | + , aLocalMsgNotification |
| 260 | + } |
| 261 | + version = |
| 262 | + nodeToClientProtocols |
| 263 | + Protocols { |
| 264 | + msgSubmissionProtocol = |
| 265 | + ResponderProtocolOnly $ |
| 266 | + MiniProtocolCb $ aLocalMsgSubmission version |
| 267 | + , msgNotificationProtocol = |
| 268 | + ResponderProtocolOnly $ |
| 269 | + MiniProtocolCb $ aLocalMsgNotification version |
| 270 | + } |
| 271 | + version |
| 272 | + |
| 273 | + |
| 274 | +-- | Make an 'OuroborosApplication' for the bundle of mini-protocols that |
| 275 | +-- make up the overall node-to-client protocol. |
| 276 | +-- |
| 277 | +-- This function specifies the wire format protocol numbers as well as the |
| 278 | +-- protocols that run for each 'NodeToClientVersion'. |
| 279 | +-- |
| 280 | +-- They are chosen to not overlap with the node to node protocol numbers. |
| 281 | +-- This is not essential for correctness, but is helpful to allow a single |
| 282 | +-- shared implementation of tools that can analyse both protocols, e.g. |
| 283 | +-- wireshark plugins. |
| 284 | +-- |
| 285 | +nodeToClientProtocols |
| 286 | + :: Protocols appType ntcAddr bytes m a b |
| 287 | + -> NodeToClientVersion |
| 288 | + -> NodeToClientVersionData |
| 289 | + -> OuroborosApplicationWithMinimalCtx appType ntcAddr bytes m a b |
| 290 | +nodeToClientProtocols protocols _version _versionData = |
| 291 | + OuroborosApplication $ |
| 292 | + case protocols of |
| 293 | + Protocols { |
| 294 | + msgSubmissionProtocol |
| 295 | + , msgNotificationProtocol |
| 296 | + } -> |
| 297 | + [ localMsgSubmission msgSubmissionProtocol |
| 298 | + , localMsgNotification msgNotificationProtocol |
| 299 | + ] |
| 300 | + where |
| 301 | + -- TODO: verify protocol numbers |
| 302 | + localMsgSubmission protocol = MiniProtocol { |
| 303 | + miniProtocolNum = MiniProtocolNum 10, |
| 304 | + miniProtocolStart = StartOnDemand, |
| 305 | + miniProtocolLimits = maximumMiniProtocolLimits, |
| 306 | + miniProtocolRun = protocol |
| 307 | + } |
| 308 | + localMsgNotification protocol = MiniProtocol { |
| 309 | + miniProtocolNum = MiniProtocolNum 11, |
| 310 | + miniProtocolStart = StartOnDemand, |
| 311 | + miniProtocolLimits = maximumMiniProtocolLimits, |
| 312 | + miniProtocolRun = protocol |
| 313 | + } |
| 314 | + maximumMiniProtocolLimits = |
| 315 | + MiniProtocolLimits { |
| 316 | + maximumIngressQueue = 0xffffffff |
| 317 | + } |
0 commit comments