Skip to content

Commit b3aa800

Browse files
facundominguezamesgen
authored andcommitted
Update configuration after recovering BulkSync in ouroboros-network
1 parent c2763cb commit b3aa800

File tree

8 files changed

+110
-79
lines changed

8 files changed

+110
-79
lines changed

cabal.project

Lines changed: 2 additions & 2 deletions
Original file line numberDiff line numberDiff line change
@@ -51,8 +51,8 @@ constraints: Cabal < 3.13
5151
source-repository-package
5252
type: git
5353
location: https://github.com/IntersectMBO/ouroboros-network
54-
tag: fcb842fcd6f32b43a7cdf18a4301c1659a8bb879
55-
--sha256: kjwUrduwwxC+5QRQNJa4stEBzz7kqDJyyHOgGMfDw7s=
54+
tag: dcc2402326ea8c33a6578babbc7a1edb20ce7f5a
55+
--sha256: sha256-kEOkWueiv41E5A7aMu6gCckVC3Q/AOj+zWWQQgvnMtc=
5656
subdir:
5757
ouroboros-network
5858
ouroboros-network-api

ouroboros-consensus-diffusion/src/ouroboros-consensus-diffusion/Ouroboros/Consensus/Node.hs

Lines changed: 5 additions & 1 deletion
Original file line numberDiff line numberDiff line change
@@ -317,7 +317,8 @@ nonImmutableDbPath (MultipleDbPaths _ vol) = vol
317317
--
318318
-- See 'stdLowLevelRunNodeArgsIO'.
319319
data StdRunNodeArgs m blk (p2p :: Diffusion.P2P) = StdRunNodeArgs
320-
{ srnBfcMaxConcurrencyDeadline :: Maybe Word
320+
{ srnBfcMaxConcurrencyBulkSync :: Maybe Word
321+
, srnBfcMaxConcurrencyDeadline :: Maybe Word
321322
, srnChainDbValidateOverride :: Bool
322323
-- ^ If @True@, validate the ChainDB on init no matter what
323324
, srnDiskPolicyArgs :: DiskPolicyArgs
@@ -981,6 +982,9 @@ stdLowLevelRunNodeArgsIO RunNodeArgs{ rnProtocolInfo
981982
maybe id
982983
(\mc bfc -> bfc { bfcMaxConcurrencyDeadline = mc })
983984
srnBfcMaxConcurrencyDeadline
985+
. maybe id
986+
(\mc bfc -> bfc { bfcMaxConcurrencyBulkSync = mc })
987+
srnBfcMaxConcurrencyBulkSync
984988
modifyMempoolCapacityOverride =
985989
maybe id
986990
(\mc nka -> nka { mempoolCapacityOverride = mc })

ouroboros-consensus-diffusion/src/ouroboros-consensus-diffusion/Ouroboros/Consensus/Node/Genesis.hs

Lines changed: 27 additions & 27 deletions
Original file line numberDiff line numberDiff line change
@@ -63,26 +63,26 @@ data GenesisConfig = GenesisConfig
6363

6464
-- | Genesis configuration flags and low-level args, as parsed from config file or CLI
6565
data GenesisConfigFlags = GenesisConfigFlags
66-
{ gcfEnableCSJ :: Bool
67-
, gcfEnableLoEAndGDD :: Bool
68-
, gcfEnableLoP :: Bool
69-
, gcfBulkSyncGracePeriod :: Maybe Integer
70-
, gcfBucketCapacity :: Maybe Integer
71-
, gcfBucketRate :: Maybe Integer
72-
, gcfCSJJumpSize :: Maybe Integer
73-
, gcfGDDRateLimit :: Maybe DiffTime
66+
{ gcfEnableCSJ :: Bool
67+
, gcfEnableLoEAndGDD :: Bool
68+
, gcfEnableLoP :: Bool
69+
, gcfBlockFetchGracePeriod :: Maybe Integer
70+
, gcfBucketCapacity :: Maybe Integer
71+
, gcfBucketRate :: Maybe Integer
72+
, gcfCSJJumpSize :: Maybe Integer
73+
, gcfGDDRateLimit :: Maybe DiffTime
7474
} deriving stock (Eq, Generic, Show)
7575

7676
defaultGenesisConfigFlags :: GenesisConfigFlags
7777
defaultGenesisConfigFlags = GenesisConfigFlags
78-
{ gcfEnableCSJ = True
79-
, gcfEnableLoEAndGDD = True
80-
, gcfEnableLoP = True
81-
, gcfBulkSyncGracePeriod = Nothing
82-
, gcfBucketCapacity = Nothing
83-
, gcfBucketRate = Nothing
84-
, gcfCSJJumpSize = Nothing
85-
, gcfGDDRateLimit = Nothing
78+
{ gcfEnableCSJ = True
79+
, gcfEnableLoEAndGDD = True
80+
, gcfEnableLoP = True
81+
, gcfBlockFetchGracePeriod = Nothing
82+
, gcfBucketCapacity = Nothing
83+
, gcfBucketRate = Nothing
84+
, gcfCSJJumpSize = Nothing
85+
, gcfGDDRateLimit = Nothing
8686
}
8787

8888
enableGenesisConfigDefault :: GenesisConfig
@@ -96,7 +96,7 @@ mkGenesisConfig :: Maybe GenesisConfigFlags -> GenesisConfig
9696
mkGenesisConfig Nothing = -- disable Genesis
9797
GenesisConfig
9898
{ gcBlockFetchConfig = GenesisBlockFetchConfiguration
99-
{ gbfcBulkSyncGracePeriod = 0 -- no grace period when Genesis is disabled
99+
{ gbfcGracePeriod = 0 -- no grace period when Genesis is disabled
100100
}
101101
, gcChainSyncLoPBucketConfig = ChainSyncLoPBucketDisabled
102102
, gcCSJConfig = CSJDisabled
@@ -106,7 +106,7 @@ mkGenesisConfig Nothing = -- disable Genesis
106106
mkGenesisConfig (Just GenesisConfigFlags{..}) =
107107
GenesisConfig
108108
{ gcBlockFetchConfig = GenesisBlockFetchConfiguration
109-
{ gbfcBulkSyncGracePeriod
109+
{ gbfcGracePeriod
110110
}
111111
, gcChainSyncLoPBucketConfig = if gcfEnableLoP
112112
then ChainSyncLoPBucketEnabled ChainSyncLoPBucketEnabledConfig
@@ -129,18 +129,18 @@ mkGenesisConfig (Just GenesisConfigFlags{..}) =
129129
}
130130
where
131131
-- TODO justification/derivation from other parameters
132-
defaultBulkSyncGracePeriod = 10 -- seconds
133-
defaultCapacity = 100_000 -- number of tokens
134-
defaultRate = 500 -- tokens per second leaking, 1/2ms
132+
defaultBlockFetchGracePeriod = 10 -- seconds
133+
defaultCapacity = 100_000 -- number of tokens
134+
defaultRate = 500 -- tokens per second leaking, 1/2ms
135135
-- 3 * 2160 * 20 works in more recent ranges of slots, but causes syncing to
136136
-- block in byron.
137-
defaultCSJJumpSize = 2 * 2160
138-
defaultGDDRateLimit = 1.0 -- seconds
137+
defaultCSJJumpSize = 2 * 2160
138+
defaultGDDRateLimit = 1.0 -- seconds
139139

140-
gbfcBulkSyncGracePeriod = fromInteger $ fromMaybe defaultBulkSyncGracePeriod gcfBulkSyncGracePeriod
141-
csbcCapacity = fromInteger $ fromMaybe defaultCapacity gcfBucketCapacity
142-
csbcRate = fromInteger $ fromMaybe defaultRate gcfBucketRate
143-
csjcJumpSize = fromInteger $ fromMaybe defaultCSJJumpSize gcfCSJJumpSize
140+
gbfcGracePeriod = fromInteger $ fromMaybe defaultBlockFetchGracePeriod gcfBlockFetchGracePeriod
141+
csbcCapacity = fromInteger $ fromMaybe defaultCapacity gcfBucketCapacity
142+
csbcRate = fromInteger $ fromMaybe defaultRate gcfBucketRate
143+
csjcJumpSize = fromInteger $ fromMaybe defaultCSJJumpSize gcfCSJJumpSize
144144
lgpGDDRateLimit = fromMaybe defaultGDDRateLimit gcfGDDRateLimit
145145

146146
newtype LoEAndGDDParams = LoEAndGDDParams

ouroboros-consensus-diffusion/src/ouroboros-consensus-diffusion/Ouroboros/Consensus/NodeKernel.hs

Lines changed: 11 additions & 1 deletion
Original file line numberDiff line numberDiff line change
@@ -95,6 +95,9 @@ import Ouroboros.Network.AnchoredFragment (AnchoredFragment,
9595
import qualified Ouroboros.Network.AnchoredFragment as AF
9696
import Ouroboros.Network.Block (castTip, tipFromHeader)
9797
import Ouroboros.Network.BlockFetch
98+
import Ouroboros.Network.BlockFetch.ConsensusInterface
99+
(GenesisFetchMode)
100+
import Ouroboros.Network.ConsensusMode (ConsensusMode (..))
98101
import Ouroboros.Network.Diffusion (PublicPeerSelectionState)
99102
import Ouroboros.Network.NodeToNode (ConnectionId,
100103
MiniProtocolParameters (..))
@@ -136,7 +139,7 @@ data NodeKernel m addrNTN addrNTC blk = NodeKernel {
136139

137140
-- | The fetch mode, used by diffusion.
138141
--
139-
, getFetchMode :: STM m FetchMode
142+
, getFetchMode :: STM m GenesisFetchMode
140143

141144
-- | The GSM state, used by diffusion. A ledger judgement can be derived
142145
-- from it with 'GSM.gsmStateToLedgerJudgement'.
@@ -378,6 +381,7 @@ initInternalState NodeKernelArgs { tracers, chainDB, registry, cfg
378381
, mempoolCapacityOverride
379382
, gsmArgs, getUseBootstrapPeers
380383
, getDiffusionPipeliningSupport
384+
, genesisArgs
381385
} = do
382386
varGsmState <- do
383387
let GsmNodeKernelArgs {..} = gsmArgs
@@ -398,6 +402,7 @@ initInternalState NodeKernelArgs { tracers, chainDB, registry, cfg
398402

399403
slotForgeTimeOracle <- BlockFetchClientInterface.initSlotForgeTimeOracle cfg chainDB
400404
let readFetchMode = BlockFetchClientInterface.readFetchModeDefault
405+
(toConsensusMode $ gnkaLoEAndGDDArgs genesisArgs)
401406
btime
402407
(ChainDB.getCurrentChain chainDB)
403408
getUseBootstrapPeers
@@ -416,6 +421,11 @@ initInternalState NodeKernelArgs { tracers, chainDB, registry, cfg
416421
peerSharingRegistry <- newPeerSharingRegistry
417422

418423
return IS {..}
424+
where
425+
toConsensusMode :: forall a. LoEAndGDDConfig a -> ConsensusMode
426+
toConsensusMode = \case
427+
LoEAndGDDDisabled -> PraosMode
428+
LoEAndGDDEnabled _ -> GenesisMode
419429

420430
forkBlockForging ::
421431
forall m addrNTN addrNTC blk.

ouroboros-consensus-diffusion/src/unstable-diffusion-testlib/Test/ThreadNet/Network.hs

Lines changed: 4 additions & 3 deletions
Original file line numberDiff line numberDiff line change
@@ -1013,10 +1013,11 @@ runThreadNetwork systemTime ThreadNetworkArgs
10131013
txSubmissionMaxUnacked = 1000 -- TODO ?
10141014
}
10151015
, blockFetchConfiguration = BlockFetchConfiguration {
1016-
bfcMaxConcurrencyDeadline = 2
1016+
bfcMaxConcurrencyBulkSync = 1
1017+
, bfcMaxConcurrencyDeadline = 2
10171018
, bfcMaxRequestsInflight = 10
1018-
, bfcDecisionLoopIntervalBulkSync = 0.0 -- Mock testsuite can use sub-second slot
1019-
, bfcDecisionLoopIntervalDeadline = 0.0 -- interval which doesn't play nice with
1019+
, bfcDecisionLoopIntervalPraos = 0.0 -- Mock testsuite can use sub-second slot
1020+
, bfcDecisionLoopIntervalGenesis = 0.0 -- interval which doesn't play nice with
10201021
-- blockfetch descision interval.
10211022
, bfcSalt = 0
10221023
, bfcGenesisBFConfig = gcBlockFetchConfig enableGenesisConfigDefault

ouroboros-consensus-diffusion/test/consensus-test/Test/Consensus/PeerSimulator/BlockFetch.hs

Lines changed: 12 additions & 9 deletions
Original file line numberDiff line numberDiff line change
@@ -37,10 +37,12 @@ import Ouroboros.Consensus.Storage.ChainDB.API
3737
import Ouroboros.Consensus.Util (ShowProxy)
3838
import Ouroboros.Consensus.Util.IOLike
3939
import Ouroboros.Network.BlockFetch (BlockFetchConfiguration (..),
40-
FetchClientRegistry, FetchMode (..),
41-
GenesisBlockFetchConfiguration (..), blockFetchLogic,
42-
bracketFetchClient, bracketKeepAliveClient)
40+
FetchClientRegistry, GenesisBlockFetchConfiguration (..),
41+
blockFetchLogic, bracketFetchClient,
42+
bracketKeepAliveClient)
4343
import Ouroboros.Network.BlockFetch.Client (blockFetchClient)
44+
import Ouroboros.Network.BlockFetch.ConsensusInterface
45+
(GenesisFetchMode (..))
4446
import Ouroboros.Network.Channel (Channel)
4547
import Ouroboros.Network.ControlMessage (ControlMessageSTM)
4648
import Ouroboros.Network.Driver (runPeer)
@@ -93,13 +95,13 @@ startBlockFetchLogic enableChainSelStarvation registry tracer chainDb fetchClien
9395
-- do not serialize the blocks.
9496
(\_hdr -> 1000)
9597
slotForgeTime
96-
-- This is a syncing test, so we use 'FetchModeBulkSync'.
97-
(pure FetchModeBulkSync)
98+
-- This is a syncing test, so we use 'FetchModeGenesis'.
99+
(pure FetchModeGenesis)
98100
DiffusionPipeliningOn
99101

100102
bfcGenesisBFConfig = if enableChainSelStarvation
101103
then GenesisBlockFetchConfiguration
102-
{ gbfcBulkSyncGracePeriod =
104+
{ gbfcGracePeriod =
103105
if enableChainSelStarvation then
104106
10 -- default value for cardano-node at the time of writing
105107
else
@@ -110,10 +112,11 @@ startBlockFetchLogic enableChainSelStarvation registry tracer chainDb fetchClien
110112
-- Values taken from
111113
-- ouroboros-consensus-diffusion/src/unstable-diffusion-testlib/Test/ThreadNet/Network.hs
112114
blockFetchCfg = BlockFetchConfiguration
113-
{ bfcMaxConcurrencyDeadline = 50 -- unused because of @pure FetchModeBulkSync@ above
115+
{ bfcMaxConcurrencyBulkSync = 50
116+
, bfcMaxConcurrencyDeadline = 50 -- unused because of @pure FetchModeBulkSync@ above
114117
, bfcMaxRequestsInflight = 10
115-
, bfcDecisionLoopIntervalBulkSync = 0
116-
, bfcDecisionLoopIntervalDeadline = 0
118+
, bfcDecisionLoopIntervalPraos = 0
119+
, bfcDecisionLoopIntervalGenesis = 0
117120
, bfcSalt = 0
118121
, bfcGenesisBFConfig
119122
}

ouroboros-consensus/src/ouroboros-consensus/Ouroboros/Consensus/MiniProtocol/BlockFetch/ClientInterface.hs

Lines changed: 34 additions & 29 deletions
Original file line numberDiff line numberDiff line change
@@ -46,7 +46,8 @@ import Ouroboros.Network.Block (MaxSlotNo)
4646
import Ouroboros.Network.BlockFetch.ConsensusInterface
4747
(BlockFetchConsensusInterface (..),
4848
ChainSelStarvation (..), FetchMode (..),
49-
FromConsensus (..))
49+
FromConsensus (..), GenesisFetchMode (..), mkReadFetchMode)
50+
import Ouroboros.Network.ConsensusMode (ConsensusMode)
5051
import Ouroboros.Network.PeerSelection.Bootstrap (UseBootstrapPeers,
5152
requiresBootstrapPeers)
5253
import Ouroboros.Network.PeerSelection.LedgerPeers.Type
@@ -142,37 +143,41 @@ initSlotForgeTimeOracle cfg chainDB = do
142143

143144
readFetchModeDefault ::
144145
(MonadSTM m, HasHeader blk)
145-
=> BlockchainTime m
146+
=> ConsensusMode
147+
-> BlockchainTime m
146148
-> STM m (AnchoredFragment blk)
147149
-> STM m UseBootstrapPeers
148150
-> STM m LedgerStateJudgement
149-
-> STM m FetchMode
150-
readFetchModeDefault btime getCurrentChain
151-
getUseBootstrapPeers getLedgerStateJudgement = do
152-
mCurSlot <- getCurrentSlot btime
153-
usingBootstrapPeers <- requiresBootstrapPeers <$> getUseBootstrapPeers
154-
<*> getLedgerStateJudgement
151+
-> STM m GenesisFetchMode
152+
readFetchModeDefault consensusMode btime getCurrentChain
153+
getUseBootstrapPeers getLedgerStateJudgement =
154+
mkReadFetchMode consensusMode getLedgerStateJudgement praosFetchMode
155+
where
156+
praosFetchMode = do
157+
mCurSlot <- getCurrentSlot btime
158+
usingBootstrapPeers <- requiresBootstrapPeers <$> getUseBootstrapPeers
159+
<*> getLedgerStateJudgement
155160

156-
-- This logic means that when the node is using bootstrap peers and is in
157-
-- TooOld state it will always return BulkSync. Otherwise if the node
158-
-- isn't using bootstrap peers (i.e. has them disabled it will use the old
159-
-- logic of returning BulkSync if behind 1000 slots
160-
case (usingBootstrapPeers, mCurSlot) of
161-
(True, _) -> return FetchModeBulkSync
162-
(False, CurrentSlotUnknown) -> return FetchModeBulkSync
163-
(False, CurrentSlot curSlot) -> do
164-
curChainSlot <- AF.headSlot <$> getCurrentChain
165-
let slotsBehind = case curChainSlot of
166-
-- There's nothing in the chain. If the current slot is 0, then
167-
-- we're 1 slot behind.
168-
Origin -> unSlotNo curSlot + 1
169-
NotOrigin slot -> unSlotNo curSlot - unSlotNo slot
170-
maxSlotsBehind = 1000
171-
return $ if slotsBehind < maxSlotsBehind
172-
-- When the current chain is near to "now", use deadline mode,
173-
-- when it is far away, use bulk sync mode.
174-
then FetchModeDeadline
175-
else FetchModeBulkSync
161+
-- This logic means that when the node is using bootstrap peers and is in
162+
-- TooOld state it will always return BulkSync. Otherwise if the node
163+
-- isn't using bootstrap peers (i.e. has them disabled it will use the old
164+
-- logic of returning BulkSync if behind 1000 slots
165+
case (usingBootstrapPeers, mCurSlot) of
166+
(True, _) -> return FetchModeBulkSync
167+
(False, CurrentSlotUnknown) -> return FetchModeBulkSync
168+
(False, CurrentSlot curSlot) -> do
169+
curChainSlot <- AF.headSlot <$> getCurrentChain
170+
let slotsBehind = case curChainSlot of
171+
-- There's nothing in the chain. If the current slot is 0, then
172+
-- we're 1 slot behind.
173+
Origin -> unSlotNo curSlot + 1
174+
NotOrigin slot -> unSlotNo curSlot - unSlotNo slot
175+
maxSlotsBehind = 1000
176+
return $ if slotsBehind < maxSlotsBehind
177+
-- When the current chain is near to "now", use deadline mode,
178+
-- when it is far away, use bulk sync mode.
179+
then FetchModeDeadline
180+
else FetchModeBulkSync
176181

177182
mkBlockFetchConsensusInterface ::
178183
forall m peer blk.
@@ -188,7 +193,7 @@ mkBlockFetchConsensusInterface ::
188193
-> (Header blk -> SizeInBytes)
189194
-> SlotForgeTimeOracle m blk
190195
-- ^ Slot forge time, see 'headerForgeUTCTime' and 'blockForgeUTCTime'.
191-
-> STM m FetchMode
196+
-> STM m GenesisFetchMode
192197
-- ^ See 'readFetchMode'.
193198
-> DiffusionPipeliningSupport
194199
-> BlockFetchConsensusInterface peer (Header blk) blk m

ouroboros-consensus/test/consensus-test/Test/Consensus/MiniProtocol/BlockFetch/Client.hs

Lines changed: 15 additions & 7 deletions
Original file line numberDiff line numberDiff line change
@@ -57,6 +57,8 @@ import Ouroboros.Network.BlockFetch (BlockFetchConfiguration (..),
5757
bracketFetchClient, bracketKeepAliveClient,
5858
bracketSyncWithFetchClient, newFetchClientRegistry)
5959
import Ouroboros.Network.BlockFetch.Client (blockFetchClient)
60+
import Ouroboros.Network.BlockFetch.ConsensusInterface
61+
(GenesisFetchMode (..))
6062
import Ouroboros.Network.ControlMessage (ControlMessage (..))
6163
import Ouroboros.Network.Mock.Chain (Chain)
6264
import qualified Ouroboros.Network.Mock.Chain as Chain
@@ -97,8 +99,9 @@ prop_blockFetch bfcts@BlockFetchClientTestSetup{..} =
9799
[ Map.keysSet bfcoBlockFetchResults === Map.keysSet peerUpdates
98100
, counterexample ("Fetched blocks per peer: " <> condense bfcoFetchedBlocks) $
99101
property $ case blockFetchMode of
100-
FetchModeDeadline -> all (> 0) bfcoFetchedBlocks
101-
FetchModeBulkSync -> any (> 0) bfcoFetchedBlocks
102+
PraosFetchMode FetchModeDeadline -> all (> 0) bfcoFetchedBlocks
103+
PraosFetchMode FetchModeBulkSync -> all (> 0) bfcoFetchedBlocks
104+
FetchModeGenesis -> any (> 0) bfcoFetchedBlocks
102105
]
103106
where
104107
BlockFetchClientOutcome{..} = runSimOrThrow $ runBlockFetchTest bfcts
@@ -330,7 +333,7 @@ data BlockFetchClientTestSetup = BlockFetchClientTestSetup {
330333
-- the candidate fragments provided by the ChainSync client.
331334
peerUpdates :: Map PeerId (Schedule ChainUpdate)
332335
-- | BlockFetch 'FetchMode'
333-
, blockFetchMode :: FetchMode
336+
, blockFetchMode :: GenesisFetchMode
334337
, blockFetchCfg :: BlockFetchConfiguration
335338
, blockFetchPipelining :: DiffusionPipeliningSupport
336339
}
@@ -362,18 +365,23 @@ instance Arbitrary BlockFetchClientTestSetup where
362365
peerUpdates <-
363366
Map.fromList . zip peerIds
364367
<$> replicateM numPeers (genUpdateSchedule blockFetchPipelining)
365-
blockFetchMode <- elements [FetchModeBulkSync, FetchModeDeadline]
368+
blockFetchMode <- elements
369+
[ PraosFetchMode FetchModeBulkSync
370+
, PraosFetchMode FetchModeDeadline
371+
, FetchModeGenesis
372+
]
366373
blockFetchCfg <- do
367374
let -- ensure that we can download blocks from all peers
375+
bfcMaxConcurrencyBulkSync = fromIntegral numPeers
368376
bfcMaxConcurrencyDeadline = fromIntegral numPeers
369377
-- This is used to introduce a minimal delay between BlockFetch
370378
-- logic iterations in case the monitored state vars change too
371379
-- fast, which we don't have to worry about in this test.
372-
bfcDecisionLoopIntervalBulkSync = 0
373-
bfcDecisionLoopIntervalDeadline = 0
380+
bfcDecisionLoopIntervalGenesis = 0
381+
bfcDecisionLoopIntervalPraos = 0
374382
bfcMaxRequestsInflight <- chooseEnum (2, 10)
375383
bfcSalt <- arbitrary
376-
gbfcBulkSyncGracePeriod <- fromIntegral <$> chooseInteger (5, 60)
384+
gbfcGracePeriod <- fromIntegral <$> chooseInteger (5, 60)
377385
let bfcGenesisBFConfig = GenesisBlockFetchConfiguration {..}
378386
pure BlockFetchConfiguration {..}
379387
pure BlockFetchClientTestSetup {..}

0 commit comments

Comments
 (0)