Skip to content

Commit 8617d14

Browse files
cootcrocodile-dentist
authored andcommitted
dmq: genesis file & KES EvolutionConfig
1 parent 6ddda46 commit 8617d14

File tree

6 files changed

+45
-12
lines changed

6 files changed

+45
-12
lines changed

dmq-node/app/Main.hs

Lines changed: 14 additions & 1 deletion
Original file line numberDiff line numberDiff line change
@@ -6,6 +6,7 @@
66

77
module Main where
88

9+
import Control.Exception (throwIO)
910
import Control.Monad (void, when)
1011
import Control.Tracer (Tracer (..), nullTracer, traceWith)
1112

@@ -22,6 +23,7 @@ import System.Exit (exitSuccess)
2223
import System.Random (newStdGen, split)
2324

2425
import Cardano.Git.Rev (gitRev)
26+
import Cardano.KESAgent.KES.Evolution qualified as KES
2527
import Cardano.KESAgent.Protocols.StandardCrypto (StandardCrypto)
2628

2729
import DMQ.Configuration
@@ -68,6 +70,7 @@ runDMQ commandLineConfig = do
6870
let dmqConfig@Configuration {
6971
dmqcPrettyLog = I prettyLog,
7072
dmqcTopologyFile = I topologyFile,
73+
dmqcShelleyGenesisFile = I genesisFile,
7174
dmqcHandshakeTracer = I handshakeTracer,
7275
dmqcLocalHandshakeTracer = I localHandshakeTracer,
7376
dmqcVersion = I version
@@ -95,14 +98,24 @@ runDMQ commandLineConfig = do
9598
]
9699
exitSuccess
97100

101+
res <- KES.evolutionConfigFromGenesisFile genesisFile
102+
evolutionConfig <- case res of
103+
Left err -> traceWith tracer (WithEventType "ShelleyGenesisFile" err)
104+
>> throwIO (userError $ err)
105+
Right ev -> return ev
106+
98107
traceWith tracer (WithEventType "Configuration" dmqConfig)
99108
nt <- readTopologyFileOrError topologyFile
100109
traceWith tracer (WithEventType "NetworkTopology" nt)
101110

102111
stdGen <- newStdGen
103112
let (psRng, policyRng) = split stdGen
104113

105-
withNodeKernel @StandardCrypto tracer dmqConfig psRng $ \nodeKernel -> do
114+
withNodeKernel @StandardCrypto
115+
tracer
116+
dmqConfig
117+
evolutionConfig
118+
psRng $ \nodeKernel -> do
106119
dmqDiffusionConfiguration <- mkDiffusionConfiguration dmqConfig nt
107120

108121
let dmqNtNApps =

dmq-node/src/DMQ/Configuration.hs

Lines changed: 8 additions & 0 deletions
Original file line numberDiff line numberDiff line change
@@ -90,6 +90,10 @@ data Configuration' f =
9090
dmqcPortNumber :: f PortNumber,
9191
dmqcConfigFile :: f FilePath,
9292
dmqcTopologyFile :: f FilePath,
93+
dmqcShelleyGenesisFile :: f FilePath,
94+
-- ^ shelley genesis file, e.g.
95+
-- `/configuration/cardano/mainnet-shelley-genesis.json` in `cardano-node`
96+
-- repo.
9397
dmqcAcceptedConnectionsLimit :: f AcceptedConnectionsLimit,
9498
dmqcDiffusionMode :: f DiffusionMode,
9599
dmqcTargetOfRootPeers :: f Int,
@@ -210,6 +214,7 @@ defaultConfiguration = Configuration {
210214
dmqcPortNumber = I 3_141,
211215
dmqcConfigFile = I "dmq.configuration.yaml",
212216
dmqcTopologyFile = I "dmq.topology.json",
217+
dmqcShelleyGenesisFile = I "mainnet-shelley-genesis.json",
213218
dmqcAcceptedConnectionsLimit = I defaultAcceptedConnectionsLimit,
214219
dmqcDiffusionMode = I InitiatorAndResponderDiffusionMode,
215220
dmqcTargetOfRootPeers = I targetNumberOfRootPeers,
@@ -300,6 +305,8 @@ instance FromJSON PartialConfig where
300305
dmqcDiffusionMode <- Last <$> v .:? "DiffusionMode"
301306
dmqcPeerSharing <- Last <$> v .:? "PeerSharing"
302307

308+
dmqcShelleyGenesisFile <- Last <$> v .:? "ShelleyGenesisFile"
309+
303310
dmqcTargetOfRootPeers <- Last <$> v .:? "TargetNumberOfRootPeers"
304311
dmqcTargetOfKnownPeers <- Last <$> v .:? "TargetNumberOfKnownPeers"
305312
dmqcTargetOfEstablishedPeers <- Last <$> v .:? "TargetNumberOfEstablishedPeers"
@@ -376,6 +383,7 @@ instance ToJSON Configuration where
376383
, "LocalAddress" .= unI dmqcLocalAddress
377384
, "ConfigFile" .= unI dmqcConfigFile
378385
, "TopologyFile" .= unI dmqcTopologyFile
386+
, "ShelleyGenesisFile" .= unI dmqcShelleyGenesisFile
379387
, "AcceptedConnectionsLimit" .= unI dmqcAcceptedConnectionsLimit
380388
, "DiffusionMode" .= unI dmqcDiffusionMode
381389
, "TargetOfRootPeers" .= unI dmqcTargetOfRootPeers

dmq-node/src/DMQ/Diffusion/NodeKernel.hs

Lines changed: 14 additions & 5 deletions
Original file line numberDiff line numberDiff line change
@@ -21,13 +21,16 @@ import Data.Functor.Contravariant ((>$<))
2121
import Data.Hashable
2222
import Data.Sequence (Seq)
2323
import Data.Sequence qualified as Seq
24+
import Data.Set (Set)
25+
import Data.Set qualified as Set
2426
import Data.Time.Clock.POSIX (POSIXTime)
2527
import Data.Time.Clock.POSIX qualified as Time
2628
import Data.Void (Void)
2729
import System.Random (StdGen)
2830
import System.Random qualified as Random
2931

3032
import Cardano.KESAgent.KES.Crypto (Crypto (..))
33+
import Cardano.KESAgent.KES.Evolution qualified as KES
3134

3235
import Ouroboros.Network.BlockFetch (FetchClientRegistry,
3336
newFetchClientRegistry)
@@ -38,11 +41,12 @@ import Ouroboros.Network.PeerSharing (PeerSharingAPI, PeerSharingRegistry,
3841
newPeerSharingAPI, newPeerSharingRegistry,
3942
ps_POLICY_PEER_SHARE_MAX_PEERS, ps_POLICY_PEER_SHARE_STICKY_TIME)
4043
import Ouroboros.Network.TxSubmission.Inbound.V2
41-
import Ouroboros.Network.TxSubmission.Mempool.Simple (Mempool (..), MempoolSeq (..))
44+
import Ouroboros.Network.TxSubmission.Mempool.Simple (Mempool (..),
45+
MempoolSeq (..))
4246
import Ouroboros.Network.TxSubmission.Mempool.Simple qualified as Mempool
4347

4448
import DMQ.Configuration
45-
import DMQ.Protocol.SigSubmission.Type (Sig (sigId, sigExpiresAt), SigId)
49+
import DMQ.Protocol.SigSubmission.Type (Sig (sigExpiresAt, sigId), SigId)
4650
import DMQ.Tracer
4751

4852

@@ -56,6 +60,7 @@ data NodeKernel crypto ntnAddr m =
5660
, peerSharingRegistry :: !(PeerSharingRegistry ntnAddr m)
5761
, peerSharingAPI :: !(PeerSharingAPI ntnAddr StdGen m)
5862
, mempool :: !(Mempool m SigId (Sig crypto))
63+
, evolutionConfig :: !(KES.EvolutionConfig)
5964
, sigChannelVar :: !(TxChannelsVar m ntnAddr SigId (Sig crypto))
6065
, sigMempoolSem :: !(TxMempoolSem m)
6166
, sigSharedTxStateVar :: !(SharedTxStateVar m ntnAddr SigId (Sig crypto))
@@ -65,9 +70,10 @@ newNodeKernel :: ( MonadLabelledSTM m
6570
, MonadMVar m
6671
, Ord ntnAddr
6772
)
68-
=> StdGen
73+
=> KES.EvolutionConfig
74+
-> StdGen
6975
-> m (NodeKernel crypto ntnAddr m)
70-
newNodeKernel rng = do
76+
newNodeKernel evolutionConfig rng = do
7177
publicPeerSelectionStateVar <- makePublicPeerSelectionStateVar
7278

7379
fetchClientRegistry <- newFetchClientRegistry
@@ -90,6 +96,7 @@ newNodeKernel rng = do
9096
, peerSharingRegistry
9197
, peerSharingAPI
9298
, mempool
99+
, evolutionConfig
93100
, sigChannelVar
94101
, sigMempoolSem
95102
, sigSharedTxStateVar
@@ -111,6 +118,7 @@ withNodeKernel :: forall crypto ntnAddr m a.
111118
)
112119
=> (forall ev. Aeson.ToJSON ev => Tracer m (WithEventType ev))
113120
-> Configuration
121+
-> KES.EvolutionConfig
114122
-> StdGen
115123
-> (NodeKernel crypto ntnAddr m -> m a)
116124
-- ^ as soon as the callback exits the `mempoolWorker` and all
@@ -120,12 +128,13 @@ withNodeKernel tracer
120128
Configuration {
121129
dmqcSigSubmissionLogicTracer = I sigSubmissionLogicTracer
122130
}
131+
evolutionConfig
123132
rng k = do
124133
nodeKernel@NodeKernel { mempool,
125134
sigChannelVar,
126135
sigSharedTxStateVar
127136
}
128-
<- newNodeKernel rng
137+
<- newNodeKernel evolutionConfig rng
129138
withAsync (mempoolWorker mempool)
130139
$ \mempoolThread ->
131140
withAsync (decisionLogicThreads

dmq-node/src/DMQ/NodeToNode.hs

Lines changed: 2 additions & 1 deletion
Original file line numberDiff line numberDiff line change
@@ -196,6 +196,7 @@ ntnApps
196196
, peerSharingRegistry
197197
, peerSharingAPI
198198
, mempool
199+
, evolutionConfig
199200
, sigChannelVar
200201
, sigMempoolSem
201202
, sigSharedTxStateVar
@@ -234,7 +235,7 @@ ntnApps
234235
-- mempool.
235236
mempoolWriter = Mempool.getWriter sigId
236237
(pure ()) -- TODO not needed
237-
(\_ -> validateSig)
238+
(\_ -> validateSig evolutionConfig)
238239
(\_ -> True)
239240
mempool
240241

dmq-node/src/DMQ/Protocol/SigSubmission/Type.hs

Lines changed: 5 additions & 2 deletions
Original file line numberDiff line numberDiff line change
@@ -47,6 +47,7 @@ import Cardano.Crypto.DSIGN.Class (ContextDSIGN, DSIGNAlgorithm, VerKeyDSIGN)
4747
import Cardano.Crypto.DSIGN.Class qualified as DSIGN
4848
import Cardano.Crypto.KES.Class (KESAlgorithm (..), Signable)
4949
import Cardano.KESAgent.KES.Crypto as KES
50+
import Cardano.KESAgent.KES.Evolution qualified as KES
5051
import Cardano.KESAgent.KES.OCert (KESPeriod (..), OCert (..), OCertSignable,
5152
validateOCert)
5253

@@ -290,9 +291,11 @@ validateSig :: forall crypto.
290291
, ContextKES (KES crypto) ~ ()
291292
, Signable (KES crypto) ByteString
292293
)
293-
=> Sig crypto
294+
=> KES.EvolutionConfig
295+
-> Sig crypto
294296
-> Either SigValidationError ()
295-
validateSig Sig { sigSignedBytes = signedBytes,
297+
validateSig _ec
298+
Sig { sigSignedBytes = signedBytes,
296299
sigKESPeriod,
297300
sigOpCertificate = SigOpCertificate ocert@OCert {
298301
ocertKESPeriod,

dmq-node/test/DMQ/Protocol/SigSubmission/Test.hs

Lines changed: 2 additions & 3 deletions
Original file line numberDiff line numberDiff line change
@@ -514,8 +514,7 @@ encodeSigRaw sigRaw@SigRaw { sigRawKESSignature, sigRawOpCertificate, sigRawCold
514514

515515
-- note: KES signature is updated by updateSigFn
516516
shrinkSigFn :: forall crypto.
517-
( Crypto crypto
518-
)
517+
Crypto crypto
519518
=> Sig crypto -> [Sig crypto]
520519
shrinkSigFn SigWithBytes {sigRawWithSignedBytes = SigRawWithSignedBytes { sigRaw, sigRawSignedBytes } } =
521520
mkSig . (\sigRaw' -> SigRawWithSignedBytes { sigRaw = sigRaw', sigRawSignedBytes }) <$> shrinkSigRawFn sigRaw
@@ -830,7 +829,7 @@ prop_validateSig
830829
-> Property
831830
prop_validateSig constr = ioProperty $ do
832831
sig <- runWithConstr constr
833-
return $ case validateSig sig of
832+
return $ case validateSig KES.defEvolutionConfig sig of
834833
Left err -> counterexample ("KES seed: " ++ show (ctx constr))
835834
. counterexample ("KES vk key: " ++ show (ocertVkHot . getSigOpCertificate . sigOpCertificate $ sig))
836835
. counterexample (show sig)

0 commit comments

Comments
 (0)