Skip to content

Commit 1c5581f

Browse files
app: integration
1 parent ba655da commit 1c5581f

File tree

4 files changed

+56
-43
lines changed

4 files changed

+56
-43
lines changed

dmq-node/app/Main.hs

Lines changed: 35 additions & 16 deletions
Original file line numberDiff line numberDiff line change
@@ -15,7 +15,9 @@ import Data.Void (Void)
1515
import Options.Applicative
1616
import System.Random (newStdGen, split)
1717

18+
import Cardano.Crypto.DSIGN.Class qualified as DSIGN
1819
import Cardano.KESAgent.Protocols.StandardCrypto (StandardCrypto)
20+
import Cardano.Ledger.Hashes
1921

2022
import DMQ.Configuration
2123
import DMQ.Configuration.CLIOptions (parseCLIOptions)
@@ -31,9 +33,11 @@ import DMQ.Tracer
3133

3234
import DMQ.Diffusion.PeerSelection (policy)
3335
import DMQ.NodeToClient.LocalStateQueryClient
36+
import DMQ.Protocol.SigSubmission.Validate
3437
import Ouroboros.Network.Diffusion qualified as Diffusion
3538
import Ouroboros.Network.PeerSelection.PeerSharing.Codec (decodeRemoteAddress,
3639
encodeRemoteAddress)
40+
import Ouroboros.Network.SizeInBytes
3741
import Ouroboros.Network.Snocket
3842
import Ouroboros.Network.TxSubmission.Mempool.Simple qualified as Mempool
3943

@@ -87,23 +91,38 @@ runDMQ commandLineConfig = do
8791

8892
withAsync stakePoolMonitor \aid -> do
8993
link aid
90-
let dmqNtNApps =
91-
ntnApps tracer
92-
dmqConfig
93-
nodeKernel
94-
(dmqCodecs
95-
-- TODO: `maxBound :: Cardano.Network.NodeToNode.NodeToNodeVersion`
96-
-- is unsafe here!
97-
(encodeRemoteAddress maxBound)
98-
(decodeRemoteAddress maxBound))
99-
dmqLimitsAndTimeouts
100-
defaultSigDecisionPolicy
94+
let sigSize :: Sig StandardCrypto -> SizeInBytes
95+
sigSize _ = 0 -- TODO
96+
mempoolReader = Mempool.getReader sigId sigSize (mempool nodeKernel)
97+
dmqNtNApps =
98+
let ntnMempoolWriter = Mempool.writerAdapter $
99+
Mempool.getWriter sigId
100+
(poolValidationCtx $ stakePools nodeKernel)
101+
(validateSig FailDefault (KeyHash . DSIGN.hashVerKeyDSIGN))
102+
SigDuplicate
103+
(mempool nodeKernel)
104+
in ntnApps tracer
105+
dmqConfig
106+
mempoolReader
107+
ntnMempoolWriter
108+
sigSize
109+
nodeKernel
110+
(dmqCodecs
111+
-- TODO: `maxBound :: Cardano.Network.NodeToNode.NodeToNodeVersion`
112+
-- is unsafe here!
113+
(encodeRemoteAddress maxBound)
114+
(decodeRemoteAddress maxBound))
115+
dmqLimitsAndTimeouts
116+
defaultSigDecisionPolicy
101117
dmqNtCApps =
102-
let sigSize _ = 0 -- TODO
103-
maxMsgs = 1000 -- TODO: make this negotiated in the handshake?
104-
mempoolReader = Mempool.getReader sigId sigSize (mempool nodeKernel)
105-
mempoolWriter = Mempool.getWriter sigId (const ()) (\_ _ -> pure True) (mempool nodeKernel)
106-
in NtC.ntcApps mempoolReader mempoolWriter maxMsgs
118+
let maxMsgs = 1000 -- TODO: make this negotiated in the handshake?
119+
ntcMempoolWriter =
120+
Mempool.getWriter sigId
121+
(poolValidationCtx $ stakePools nodeKernel)
122+
(validateSig FailSoft (KeyHash . DSIGN.hashVerKeyDSIGN))
123+
SigDuplicate
124+
(mempool nodeKernel)
125+
in NtC.ntcApps mempoolReader ntcMempoolWriter maxMsgs
107126
(NtC.dmqCodecs encodeReject decodeReject)
108127
dmqDiffusionArguments =
109128
diffusionArguments (if handshakeTracer

dmq-node/dmq-node.cabal

Lines changed: 2 additions & 0 deletions
Original file line numberDiff line numberDiff line change
@@ -135,6 +135,8 @@ executable dmq-node
135135
acts,
136136
aeson,
137137
base,
138+
cardano-crypto-class,
139+
cardano-ledger-core,
138140
contra-tracer >=0.1 && <0.3,
139141
dmq-node,
140142
io-classes,

dmq-node/src/DMQ/NodeToClient.hs

Lines changed: 6 additions & 6 deletions
Original file line numberDiff line numberDiff line change
@@ -43,6 +43,7 @@ import DMQ.Protocol.LocalMsgSubmission.Codec
4343
import DMQ.Protocol.LocalMsgSubmission.Server
4444
import DMQ.Protocol.LocalMsgSubmission.Type
4545
import DMQ.Protocol.SigSubmission.Type (Sig)
46+
import DMQ.Protocol.SigSubmission.Validate
4647

4748
import Ouroboros.Network.Context
4849
import Ouroboros.Network.Driver.Simple
@@ -52,9 +53,8 @@ import Ouroboros.Network.Mux
5253
import Ouroboros.Network.Protocol.Handshake (Handshake, HandshakeArguments (..))
5354
import Ouroboros.Network.Protocol.Handshake.Codec (cborTermVersionDataCodec,
5455
codecHandshake, noTimeLimitsHandshake)
55-
import Ouroboros.Network.TxSubmission.Inbound.V2.Types
56-
(TxSubmissionMempoolWriter)
5756
import Ouroboros.Network.TxSubmission.Mempool.Reader
57+
import Ouroboros.Network.TxSubmission.Mempool.Simple
5858
import Ouroboros.Network.Util.ShowProxy
5959

6060

@@ -95,8 +95,8 @@ data Codecs m sig =
9595
dmqCodecs :: ( MonadST m
9696
, Crypto crypto
9797
)
98-
=> (SigMempoolFail -> CBOR.Encoding)
99-
-> (forall s. CBOR.Decoder s SigMempoolFail)
98+
=> (MempoolAddFail (Sig crypto) -> CBOR.Encoding)
99+
-> (forall s. CBOR.Decoder s (MempoolAddFail (Sig crypto)))
100100
-> Codecs m (Sig crypto)
101101
dmqCodecs encodeReject' decodeReject' =
102102
Codecs {
@@ -127,9 +127,9 @@ data Apps ntcAddr m a =
127127
-- | Construct applications for the node-to-client protocols
128128
--
129129
ntcApps
130-
:: (MonadThrow m, MonadThread m, MonadSTM m, ShowProxy SigMempoolFail, ShowProxy sig)
130+
:: (MonadThrow m, MonadThread m, MonadSTM m, ShowProxy (MempoolAddFail sig), ShowProxy sig)
131131
=> TxSubmissionMempoolReader msgid sig idx m
132-
-> TxSubmissionMempoolWriter msgid sig idx m
132+
-> MempoolWriter msgid sig failure idx m
133133
-> Word16
134134
-> Codecs m sig
135135
-> Apps ntcAddr m ()

dmq-node/src/DMQ/NodeToNode.hs

Lines changed: 13 additions & 21 deletions
Original file line numberDiff line numberDiff line change
@@ -90,7 +90,7 @@ import Ouroboros.Network.PeerSharing (bracketPeerSharingClient,
9090
peerSharingClient, peerSharingServer)
9191
import Ouroboros.Network.Snocket (RemoteAddress)
9292
import Ouroboros.Network.TxSubmission.Inbound.V2 as SigSubmission
93-
import Ouroboros.Network.TxSubmission.Mempool.Simple qualified as Mempool
93+
import Ouroboros.Network.TxSubmission.Mempool.Reader
9494
import Ouroboros.Network.TxSubmission.Outbound
9595

9696
import Ouroboros.Network.OrphanInstances ()
@@ -150,12 +150,12 @@ data Apps addr m a b =
150150
}
151151

152152
ntnApps
153-
:: forall crypto m addr .
153+
:: forall crypto m addr idx.
154154
( Crypto crypto
155-
, DSIGN.ContextDSIGN (DSIGN crypto) ~ ()
156-
, DSIGN.Signable (DSIGN crypto) (OCertSignable crypto)
157-
, KES.ContextKES (KES crypto) ~ ()
158-
, KES.Signable (KES crypto) BS.ByteString
155+
-- , DSIGN.ContextDSIGN (DSIGN crypto) ~ ()
156+
-- , DSIGN.Signable (DSIGN crypto) (OCertSignable crypto)
157+
-- , KES.ContextKES (KES crypto) ~ ()
158+
-- , KES.Signable (KES crypto) BS.ByteString
159159
, Typeable crypto
160160
, Alternative (STM m)
161161
, MonadAsync m
@@ -166,12 +166,16 @@ ntnApps
166166
, MonadThrow (STM m)
167167
, MonadTimer m
168168
, Ord addr
169+
, Ord idx
169170
, Show addr
170171
, Hashable addr
171172
, Aeson.ToJSON addr
172173
)
173174
=> (forall ev. Aeson.ToJSON ev => Tracer m (WithEventType ev))
174175
-> Configuration
176+
-> TxSubmissionMempoolReader SigId (Sig crypto) idx m
177+
-> TxSubmissionMempoolWriter SigId (Sig crypto) idx m
178+
-> (Sig crypto -> SizeInBytes)
175179
-> NodeKernel crypto addr m
176180
-> Codecs crypto addr m
177181
-> LimitsAndTimeouts crypto addr
@@ -187,11 +191,13 @@ ntnApps
187191
, dmqcPeerSharingClientTracer = I peerSharingClientTracer
188192
, dmqcPeerSharingServerTracer = I peerSharingServerTracer
189193
}
194+
mempoolReader
195+
mempoolWriter
196+
sigSize
190197
NodeKernel {
191198
fetchClientRegistry
192199
, peerSharingRegistry
193200
, peerSharingAPI
194-
, mempool
195201
, sigChannelVar
196202
, sigMempoolSem
197203
, sigSharedTxStateVar
@@ -220,20 +226,6 @@ ntnApps
220226
, aPeerSharingServer
221227
}
222228
where
223-
sigSize :: Sig crypto -> SizeInBytes
224-
sigSize _ = 0 -- TODO
225-
226-
mempoolReader = Mempool.getReader sigId sigSize mempool
227-
-- TODO: invalid signatures are just omitted from the mempool. For DMQ
228-
-- we need to validate signatures when we received them, and shutdown
229-
-- connection if we receive one, rather than validate them in the
230-
-- mempool.
231-
mempoolWriter = Mempool.getWriter sigId
232-
(pure ()) -- TODO not needed
233-
(\_ -> validateSig)
234-
(\_ -> True)
235-
mempool
236-
237229
aSigSubmissionClient
238230
:: NodeToNodeVersion
239231
-> ExpandedInitiatorContext addr m

0 commit comments

Comments
 (0)