Skip to content

Commit 6442d81

Browse files
amesgenNiols
andcommitted
ChainDB: allow to trigger chain selection synchronously
This is useful for tests. Co-authored-by: Nicolas “Niols” Jeannerod <[email protected]>
1 parent d16178f commit 6442d81

File tree

6 files changed

+66
-35
lines changed

6 files changed

+66
-35
lines changed
Lines changed: 3 additions & 0 deletions
Original file line numberDiff line numberDiff line change
@@ -0,0 +1,3 @@
1+
### Breaking
2+
3+
- ChainDB: allow to trigger chain selection synchronously

ouroboros-consensus/src/ouroboros-consensus/Ouroboros/Consensus/Genesis/Governor.hs

Lines changed: 2 additions & 2 deletions
Original file line numberDiff line numberDiff line change
@@ -32,7 +32,7 @@ module Ouroboros.Consensus.Genesis.Governor (
3232
, sharedCandidatePrefix
3333
) where
3434

35-
import Control.Monad (guard, when)
35+
import Control.Monad (guard, void, when)
3636
import Control.Tracer (Tracer, traceWith)
3737
import Data.Bifunctor (second)
3838
import Data.Containers.ListUtils (nubOrd)
@@ -142,7 +142,7 @@ gddWatcher cfg tracer chainDb getGsmState getHandles varLoEFrag =
142142
-- The chain selection only depends on the LoE tip, so there
143143
-- is no point in retriggering it if the LoE tip hasn't changed.
144144
when (AF.headHash oldLoEFrag /= AF.headHash loeFrag) $
145-
ChainDB.triggerChainSelectionAsync chainDb
145+
void $ ChainDB.triggerChainSelectionAsync chainDb
146146

147147
-- | Pure snapshot of the dynamic data the GDD operates on.
148148
data GDDStateView m blk peer = GDDStateView {

ouroboros-consensus/src/ouroboros-consensus/Ouroboros/Consensus/Storage/ChainDB/API.hs

Lines changed: 21 additions & 2 deletions
Original file line numberDiff line numberDiff line change
@@ -27,6 +27,9 @@ module Ouroboros.Consensus.Storage.ChainDB.API (
2727
, addBlock
2828
, addBlockWaitWrittenToDisk
2929
, addBlock_
30+
-- * Trigger chain selection
31+
, ChainSelectionPromise (..)
32+
, triggerChainSelection
3033
, triggerChainSelectionAsync
3134
-- * Serialised block/header with its point
3235
, WithPoint (..)
@@ -135,7 +138,7 @@ data ChainDB m blk = ChainDB {
135138
addBlockAsync :: InvalidBlockPunishment m -> blk -> m (AddBlockPromise m blk)
136139

137140
-- | Trigger reprocessing of blocks postponed by the LoE.
138-
, chainSelAsync :: m ()
141+
, chainSelAsync :: m (ChainSelectionPromise m)
139142

140143
-- | Get the current chain fragment
141144
--
@@ -462,9 +465,25 @@ addBlock_ = void ..: addBlock
462465

463466
-- | Alias for naming consistency.
464467
-- The short name was chosen to avoid a larger diff from alignment changes.
465-
triggerChainSelectionAsync :: ChainDB m blk -> m ()
468+
triggerChainSelectionAsync :: ChainDB m blk -> m (ChainSelectionPromise m)
466469
triggerChainSelectionAsync = chainSelAsync
467470

471+
-- | A promise that the chain selection will be performed. It is returned by
472+
-- 'triggerChainSelectionAsync' and contains a monadic action that waits until
473+
-- the corresponding run of Chain Selection is done.
474+
newtype ChainSelectionPromise m = ChainSelectionPromise {
475+
-- NOTE: We might want a mechanism similar to 'AddBlockPromise' and
476+
-- 'AddBlockResult', in case the background ChainDB thread dies; but we
477+
-- currently only use the synchronous variant in tests.
478+
waitChainSelectionPromise :: m ()
479+
}
480+
481+
-- | Trigger selection synchronously: wait until the chain selection has been
482+
-- performed. This is a partial function, only to support tests.
483+
triggerChainSelection :: IOLike m => ChainDB m blk -> m ()
484+
triggerChainSelection chainDB =
485+
waitChainSelectionPromise =<< chainSelAsync chainDB
486+
468487
{-------------------------------------------------------------------------------
469488
Serialised block/header with its point
470489
-------------------------------------------------------------------------------}

ouroboros-consensus/src/ouroboros-consensus/Ouroboros/Consensus/Storage/ChainDB/Impl/Background.hs

Lines changed: 3 additions & 2 deletions
Original file line numberDiff line numberDiff line change
@@ -525,7 +525,8 @@ addBlockRunner fuse cdb@CDB{..} = forever $ do
525525
(lift $ getChainSelMessage cdbChainSelQueue)
526526
(\message -> lift $ atomically $ do
527527
case message of
528-
ChainSelReprocessLoEBlocks -> pure ()
528+
ChainSelReprocessLoEBlocks varProcessed ->
529+
void $ tryPutTMVar varProcessed ()
529530
ChainSelAddBlock BlockToAdd{varBlockWrittenToDisk, varBlockProcessed} -> do
530531
_ <- tryPutTMVar varBlockWrittenToDisk
531532
False
@@ -535,7 +536,7 @@ addBlockRunner fuse cdb@CDB{..} = forever $ do
535536
closeChainSelQueue cdbChainSelQueue)
536537
(\message -> do
537538
lift $ case message of
538-
ChainSelReprocessLoEBlocks ->
539+
ChainSelReprocessLoEBlocks _ ->
539540
trace PoppedReprocessLoEBlocksFromQueue
540541
ChainSelAddBlock BlockToAdd{blockToAdd} ->
541542
trace $ PoppedBlockFromQueue $ FallingEdgeWith $

ouroboros-consensus/src/ouroboros-consensus/Ouroboros/Consensus/Storage/ChainDB/Impl/ChainSel.hs

Lines changed: 24 additions & 22 deletions
Original file line numberDiff line numberDiff line change
@@ -267,7 +267,7 @@ triggerChainSelectionAsync ::
267267
forall m blk.
268268
IOLike m =>
269269
ChainDbEnv m blk ->
270-
m ()
270+
m (ChainSelectionPromise m)
271271
triggerChainSelectionAsync CDB {cdbTracer, cdbChainSelQueue} =
272272
addReprocessLoEBlocks (TraceAddBlockEvent >$< cdbTracer) cdbChainSelQueue
273273

@@ -303,27 +303,29 @@ chainSelSync ::
303303
-- 'ChainSelReprocessLoEBlocks' whenever we receive a new header or lose a
304304
-- peer.
305305
-- If 'cdbLoE' is 'LoEDisabled', this task is skipped.
306-
chainSelSync cdb@CDB{..} ChainSelReprocessLoEBlocks = lift cdbLoE >>= \case
307-
LoEDisabled -> pure ()
308-
LoEEnabled _ -> do
309-
(succsOf, chain) <- lift $ atomically $ do
310-
invalid <- forgetFingerprint <$> readTVar cdbInvalid
311-
(,)
312-
<$> (ignoreInvalidSuc cdbVolatileDB invalid <$>
313-
VolatileDB.filterByPredecessor cdbVolatileDB)
314-
<*> Query.getCurrentChain cdb
315-
let
316-
succsOf' = Set.toList . succsOf . pointHash . castPoint
317-
loeHashes = succsOf' (AF.anchorPoint chain)
318-
firstHeader = either (const Nothing) Just $ AF.last chain
319-
-- We avoid the VolatileDB for the headers we already have in the chain
320-
getHeaderFromHash hash =
321-
case firstHeader of
322-
Just header | headerHash header == hash -> pure header
323-
_ -> VolatileDB.getKnownBlockComponent cdbVolatileDB GetHeader hash
324-
loeHeaders <- lift (mapM getHeaderFromHash loeHashes)
325-
for_ loeHeaders $ \hdr ->
326-
void (chainSelectionForBlock cdb BlockCache.empty hdr noPunishment)
306+
chainSelSync cdb@CDB{..} (ChainSelReprocessLoEBlocks varProcessed) = do
307+
lift cdbLoE >>= \case
308+
LoEDisabled -> pure ()
309+
LoEEnabled _ -> do
310+
(succsOf, chain) <- lift $ atomically $ do
311+
invalid <- forgetFingerprint <$> readTVar cdbInvalid
312+
(,)
313+
<$> (ignoreInvalidSuc cdbVolatileDB invalid <$>
314+
VolatileDB.filterByPredecessor cdbVolatileDB)
315+
<*> Query.getCurrentChain cdb
316+
let
317+
succsOf' = Set.toList . succsOf . pointHash . castPoint
318+
loeHashes = succsOf' (AF.anchorPoint chain)
319+
firstHeader = either (const Nothing) Just $ AF.last chain
320+
-- We avoid the VolatileDB for the headers we already have in the chain
321+
getHeaderFromHash hash =
322+
case firstHeader of
323+
Just header | headerHash header == hash -> pure header
324+
_ -> VolatileDB.getKnownBlockComponent cdbVolatileDB GetHeader hash
325+
loeHeaders <- lift (mapM getHeaderFromHash loeHashes)
326+
for_ loeHeaders $ \hdr ->
327+
void (chainSelectionForBlock cdb BlockCache.empty hdr noPunishment)
328+
lift $ atomically $ putTMVar varProcessed ()
327329

328330
chainSelSync cdb@CDB {..} (ChainSelAddBlock BlockToAdd { blockToAdd = b, .. }) = do
329331
(isMember, invalid, curChain) <- lift $ atomically $ (,,)

ouroboros-consensus/src/ouroboros-consensus/Ouroboros/Consensus/Storage/ChainDB/Impl/Types.hs

Lines changed: 13 additions & 7 deletions
Original file line numberDiff line numberDiff line change
@@ -19,6 +19,7 @@ module Ouroboros.Consensus.Storage.ChainDB.Impl.Types (
1919
ChainDbEnv (..)
2020
, ChainDbHandle (..)
2121
, ChainDbState (..)
22+
, ChainSelectionPromise (..)
2223
, SerialiseDiskConstraints
2324
, getEnv
2425
, getEnv1
@@ -83,9 +84,9 @@ import Ouroboros.Consensus.Ledger.Inspect
8384
import Ouroboros.Consensus.Ledger.SupportsProtocol
8485
import Ouroboros.Consensus.Protocol.Abstract
8586
import Ouroboros.Consensus.Storage.ChainDB.API (AddBlockPromise (..),
86-
AddBlockResult (..), ChainDbError (..), ChainType,
87-
InvalidBlockReason, LoE, StreamFrom, StreamTo,
88-
UnknownRange)
87+
AddBlockResult (..), ChainDbError (..),
88+
ChainSelectionPromise (..), ChainType, InvalidBlockReason,
89+
LoE, StreamFrom, StreamTo, UnknownRange)
8990
import Ouroboros.Consensus.Storage.ChainDB.API.Types.InvalidBlockPunishment
9091
(InvalidBlockPunishment)
9192
import Ouroboros.Consensus.Storage.ChainDB.Impl.LgrDB (LgrDB,
@@ -462,8 +463,10 @@ data BlockToAdd m blk = BlockToAdd
462463
data ChainSelMessage m blk
463464
-- | Add a new block
464465
= ChainSelAddBlock !(BlockToAdd m blk)
465-
-- | Reprocess blocks that have been postponed by the LoE
466+
-- | Reprocess blocks that have been postponed by the LoE.
466467
| ChainSelReprocessLoEBlocks
468+
!(StrictTMVar m ())
469+
-- ^ Used for 'ChainSelectionPromise'.
467470

468471
-- | Create a new 'ChainSelQueue' with the given size.
469472
newChainSelQueue :: IOLike m => Word -> m (ChainSelQueue m blk)
@@ -503,10 +506,13 @@ addReprocessLoEBlocks
503506
:: IOLike m
504507
=> Tracer m (TraceAddBlockEvent blk)
505508
-> ChainSelQueue m blk
506-
-> m ()
509+
-> m (ChainSelectionPromise m)
507510
addReprocessLoEBlocks tracer (ChainSelQueue queue) = do
511+
varProcessed <- newEmptyTMVarIO
512+
let waitUntilRan = atomically $ readTMVar varProcessed
508513
traceWith tracer $ AddedReprocessLoEBlocksToQueue
509-
atomically $ writeTBQueue queue ChainSelReprocessLoEBlocks
514+
atomically $ writeTBQueue queue $ ChainSelReprocessLoEBlocks varProcessed
515+
return $ ChainSelectionPromise waitUntilRan
510516

511517
-- | Get the oldest message from the 'ChainSelQueue' queue. Can block when the
512518
-- queue is empty.
@@ -524,7 +530,7 @@ closeChainSelQueue (ChainSelQueue queue) = do
524530
where
525531
blockAdd = \case
526532
ChainSelAddBlock ab -> Just ab
527-
ChainSelReprocessLoEBlocks -> Nothing
533+
ChainSelReprocessLoEBlocks _ -> Nothing
528534

529535

530536
{-------------------------------------------------------------------------------

0 commit comments

Comments
 (0)