11{-# LANGUAGE BangPatterns #-}
2+ {-# LANGUAGE BlockArguments #-}
23{-# LANGUAGE DataKinds #-}
34{-# LANGUAGE DeriveAnyClass #-}
45{-# LANGUAGE DeriveGeneric #-}
@@ -42,12 +43,15 @@ module Ouroboros.Consensus.Storage.ChainDB.Impl.Types (
4243 -- * Blocks to add
4344 , BlockToAdd (.. )
4445 , ChainSelMessage (.. )
45- , ChainSelQueue
46+ , ChainSelQueue -- opaque
4647 , addBlockToAdd
4748 , addReprocessLoEBlocks
4849 , closeChainSelQueue
4950 , getChainSelMessage
51+ , getMaxSlotNoChainSelQueue
52+ , memberChainSelQueue
5053 , newChainSelQueue
54+ , processedChainSelMessage
5155 -- * Trace types
5256 , SelectionChangedInfo (.. )
5357 , TraceAddBlockEvent (.. )
@@ -63,14 +67,15 @@ module Ouroboros.Consensus.Storage.ChainDB.Impl.Types (
6367 , TraceValidationEvent (.. )
6468 ) where
6569
66- import Cardano.Prelude (whenM )
6770import Control.Monad (when )
6871import Control.ResourceRegistry
6972import Control.Tracer
7073import Data.Foldable (traverse_ )
7174import Data.Map.Strict (Map )
7275import Data.Maybe (mapMaybe )
7376import Data.Maybe.Strict (StrictMaybe (.. ))
77+ import Data.MultiSet (MultiSet )
78+ import qualified Data.MultiSet as MultiSet
7479import Data.Set (Set )
7580import Data.Typeable
7681import Data.Void (Void )
@@ -107,7 +112,7 @@ import Ouroboros.Consensus.Util.Enclose (Enclosing, Enclosing' (..))
107112import Ouroboros.Consensus.Util.IOLike
108113import Ouroboros.Consensus.Util.STM (WithFingerprint )
109114import Ouroboros.Network.AnchoredFragment (AnchoredFragment )
110- import Ouroboros.Network.Block (MaxSlotNo )
115+ import Ouroboros.Network.Block (MaxSlotNo ( .. ) )
111116import Ouroboros.Network.BlockFetch.ConsensusInterface
112117 (ChainSelStarvation (.. ))
113118
@@ -419,7 +424,19 @@ data InvalidBlockInfo blk = InvalidBlockInfo
419424-- | FIFO queue used to add blocks asynchronously to the ChainDB. Blocks are
420425-- read from this queue by a background thread, which processes the blocks
421426-- synchronously.
422- newtype ChainSelQueue m blk = ChainSelQueue (TBQueue m (ChainSelMessage m blk ))
427+ --
428+ -- We also maintain a multiset of the points of all of the blocks in the queue,
429+ -- plus potentially the one block for which chain selection is currently in
430+ -- progress. It is used to account for queued blocks in eg 'getIsFetched' and
431+ -- 'getMaxSlotNo'.
432+ --
433+ -- INVARIANT: Counted with multiplicity, @varChainSelPoints@ contains exactly
434+ -- the same hashes or at most one additional hash compared to the hashes of
435+ -- blocks in @varChainSelQueue@.
436+ data ChainSelQueue m blk = ChainSelQueue {
437+ varChainSelQueue :: TBQueue m (ChainSelMessage m blk )
438+ , varChainSelPoints :: StrictTVar m (MultiSet (RealPoint blk ))
439+ }
423440 deriving NoThunks via OnlyCheckWhnfNamed " ChainSelQueue" (ChainSelQueue m blk )
424441
425442-- | Entry in the 'ChainSelQueue' queue: a block together with the 'TMVar's used
@@ -445,9 +462,14 @@ data ChainSelMessage m blk
445462 -- ^ Used for 'ChainSelectionPromise'.
446463
447464-- | Create a new 'ChainSelQueue' with the given size.
448- newChainSelQueue :: IOLike m => Word -> m (ChainSelQueue m blk )
449- newChainSelQueue queueSize = ChainSelQueue <$>
450- atomically (newTBQueue (fromIntegral queueSize))
465+ newChainSelQueue :: (IOLike m , StandardHash blk , Typeable blk ) => Word -> m (ChainSelQueue m blk )
466+ newChainSelQueue chainSelQueueCapacity = do
467+ varChainSelQueue <- newTBQueueIO (fromIntegral chainSelQueueCapacity)
468+ varChainSelPoints <- newTVarIO MultiSet. empty
469+ pure ChainSelQueue {
470+ varChainSelQueue
471+ , varChainSelPoints
472+ }
451473
452474-- | Add a block to the 'ChainSelQueue' queue. Can block when the queue is full.
453475addBlockToAdd ::
@@ -457,7 +479,7 @@ addBlockToAdd ::
457479 -> InvalidBlockPunishment m
458480 -> blk
459481 -> m (AddBlockPromise m blk )
460- addBlockToAdd tracer (ChainSelQueue queue ) punish blk = do
482+ addBlockToAdd tracer (ChainSelQueue {varChainSelQueue, varChainSelPoints} ) punish blk = do
461483 varBlockWrittenToDisk <- newEmptyTMVarIO
462484 varBlockProcessed <- newEmptyTMVarIO
463485 let ! toAdd = BlockToAdd
@@ -466,10 +488,12 @@ addBlockToAdd tracer (ChainSelQueue queue) punish blk = do
466488 , varBlockWrittenToDisk
467489 , varBlockProcessed
468490 }
469- traceWith tracer $ AddedBlockToQueue (blockRealPoint blk) RisingEdge
491+ pt = blockRealPoint blk
492+ traceWith tracer $ AddedBlockToQueue pt RisingEdge
470493 queueSize <- atomically $ do
471- writeTBQueue queue (ChainSelAddBlock toAdd)
472- lengthTBQueue queue
494+ writeTBQueue varChainSelQueue (ChainSelAddBlock toAdd)
495+ modifyTVar varChainSelPoints $ MultiSet. insert pt
496+ lengthTBQueue varChainSelQueue
473497 traceWith tracer $
474498 AddedBlockToQueue (blockRealPoint blk) (FallingEdgeWith (fromIntegral queueSize))
475499 return AddBlockPromise
@@ -483,11 +507,12 @@ addReprocessLoEBlocks
483507 => Tracer m (TraceAddBlockEvent blk )
484508 -> ChainSelQueue m blk
485509 -> m (ChainSelectionPromise m )
486- addReprocessLoEBlocks tracer ( ChainSelQueue queue) = do
510+ addReprocessLoEBlocks tracer ChainSelQueue {varChainSelQueue} = do
487511 varProcessed <- newEmptyTMVarIO
488512 let waitUntilRan = atomically $ readTMVar varProcessed
489513 traceWith tracer $ AddedReprocessLoEBlocksToQueue
490- atomically $ writeTBQueue queue $ ChainSelReprocessLoEBlocks varProcessed
514+ atomically $ writeTBQueue varChainSelQueue $
515+ ChainSelReprocessLoEBlocks varProcessed
491516 return $ ChainSelectionPromise waitUntilRan
492517
493518-- | Get the oldest message from the 'ChainSelQueue' queue. Can block when the
@@ -499,7 +524,7 @@ getChainSelMessage
499524 -> StrictTVar m ChainSelStarvation
500525 -> ChainSelQueue m blk
501526 -> m (ChainSelMessage m blk )
502- getChainSelMessage starvationTracer starvationVar ( ChainSelQueue queue) =
527+ getChainSelMessage starvationTracer starvationVar chainSelQueue =
503528 atomically (tryReadTBQueue' queue) >>= \ case
504529 Just msg -> pure msg
505530 Nothing -> do
@@ -508,6 +533,10 @@ getChainSelMessage starvationTracer starvationVar (ChainSelQueue queue) =
508533 terminateStarvationMeasure msg
509534 pure msg
510535 where
536+ ChainSelQueue {
537+ varChainSelQueue = queue
538+ } = chainSelQueue
539+
511540 startStarvationMeasure :: m ()
512541 startStarvationMeasure = do
513542 prevStarvation <- atomically $ swapTVar starvationVar ChainSelStarvationOngoing
@@ -531,7 +560,7 @@ tryReadTBQueue' q = (Just <$> readTBQueue q) `orElse` pure Nothing
531560-- | Flush the 'ChainSelQueue' queue and notify the waiting threads.
532561--
533562closeChainSelQueue :: IOLike m => ChainSelQueue m blk -> STM m ()
534- closeChainSelQueue ( ChainSelQueue queue) = do
563+ closeChainSelQueue ChainSelQueue {varChainSelQueue = queue} = do
535564 as <- mapMaybe blockAdd <$> flushTBQueue queue
536565 traverse_ (\ a -> tryPutTMVar (varBlockProcessed a)
537566 (FailedToAddBlock " Queue flushed" ))
@@ -541,6 +570,41 @@ closeChainSelQueue (ChainSelQueue queue) = do
541570 ChainSelAddBlock ab -> Just ab
542571 ChainSelReprocessLoEBlocks _ -> Nothing
543572
573+ -- | To invoke when the given 'ChainSelMessage' has been processed by ChainSel.
574+ -- This is used to remove the respective point from the multiset of points in
575+ -- the 'ChainSelQueue' (as the block has now been written to disk by ChainSel).
576+ processedChainSelMessage ::
577+ (IOLike m , HasHeader blk )
578+ => ChainSelQueue m blk
579+ -> ChainSelMessage m blk
580+ -> STM m ()
581+ processedChainSelMessage ChainSelQueue {varChainSelPoints} = \ case
582+ ChainSelAddBlock BlockToAdd {blockToAdd = blk} ->
583+ modifyTVar varChainSelPoints $ MultiSet. delete (blockRealPoint blk)
584+ ChainSelReprocessLoEBlocks {} ->
585+ pure ()
586+
587+ -- | Return a function to test the membership
588+ memberChainSelQueue ::
589+ (IOLike m , HasHeader blk )
590+ => ChainSelQueue m blk
591+ -> STM m (RealPoint blk -> Bool )
592+ memberChainSelQueue ChainSelQueue {varChainSelPoints} =
593+ flip MultiSet. member <$> readTVar varChainSelPoints
594+
595+ getMaxSlotNoChainSelQueue ::
596+ IOLike m
597+ => ChainSelQueue m blk
598+ -> STM m MaxSlotNo
599+ getMaxSlotNoChainSelQueue ChainSelQueue {varChainSelPoints} =
600+ aux <$> readTVar varChainSelPoints
601+ where
602+ -- | The 'Ord' instance of 'RealPoint' orders by 'SlotNo' first, so the
603+ -- maximal key of the map has the greatest 'SlotNo'.
604+ aux :: MultiSet (RealPoint blk ) -> MaxSlotNo
605+ aux pts = case MultiSet. maxView pts of
606+ Nothing -> NoMaxSlotNo
607+ Just (RealPoint s _, _) -> MaxSlotNo s
544608
545609{- ------------------------------------------------------------------------------
546610 Trace types
0 commit comments