@@ -31,18 +31,15 @@ import Control.Monad.State.Strict (State, gets, modify', runState,
3131 state )
3232import Control.Tracer (Tracer (Tracer ), debugTracer , traceWith )
3333import Data.Bifunctor (first )
34- import Data.Bool (bool )
3534import Data.Foldable as Foldable (foldl' , foldr' )
3635import Data.List (intersperse , mapAccumL , sort , transpose )
3736import Data.List.NonEmpty (NonEmpty ((:|) ), nonEmpty , (<|) )
3837import qualified Data.List.NonEmpty as NonEmpty
3938import Data.Map (Map )
40- import qualified Data.Map as M
4139import Data.Map.Strict ((!?) )
4240import qualified Data.Map.Strict as Map
4341import Data.Maybe (fromMaybe , mapMaybe )
44- import Data.Monoid (Any (.. ), Sum (.. ))
45- import qualified Data.Set as S
42+ import Data.Monoid (First (.. ))
4643import Data.String (IsString (fromString ))
4744import Data.Vector (Vector )
4845import qualified Data.Vector as Vector
@@ -61,7 +58,7 @@ import Ouroboros.Network.AnchoredFragment (anchor, anchorToSlotNo)
6158import qualified Ouroboros.Network.AnchoredFragment as AF
6259import Ouroboros.Network.Block (HeaderHash )
6360import Test.Consensus.BlockTree (BlockTree (btBranches , btTrunk ),
64- BlockTreeBranch (btbPrefix , btbSuffix ), deforestBlockTree ,
61+ BlockTreeBranch (btbSuffix ), deforestBlockTree ,
6562 prettyBlockTree )
6663import Test.Consensus.PointSchedule.NodeState (NodeState (.. ),
6764 genesisNodeState )
@@ -359,41 +356,42 @@ initSlots lastSlot (Range l u) blocks =
359356 mkSlot num capacity =
360357 Slot {num = At num, capacity, aspects = [] }
361358
359+ -- | Get the fork number of the 'BlockTreeBranch' a block is on. /Some/ fork
360+ -- numbers are generated during the creation of the test 'BlockTree' in
361+ -- 'Test.Consensus.Genesis.Setup.GenChains.genChainsWithExtraHonestPeers'.
362+ -- There, for 'TestBlock's, these fork numbers are stored in the 'TestHash'
363+ -- by the 'IssueTestBlock' operations.
364+ -- Here, new fork numbers are created so that the pretty printing machinery
365+ -- works independently of the block type; this poses no problem because the
366+ -- exact fork numbers stored in 'TestBlock's are irrelevant as long as they
367+ -- uniquely determine each 'BlockTreeBranch'.
368+ --
369+ -- POSTCONDITION: All blocks on the same branch suffix share fork number.
370+ -- POSTCONDITION: Each 'BlockTreeBranch' has a distinct fork number.
362371hashForkNo :: AF. HasHeader blk => BlockTree blk -> HeaderHash blk -> Word64
363372hashForkNo bt hash =
364- let forkPoints =
365- -- The set of forking nodes. We can count how many of these are in our
366- -- ancestry to determine where we might have forked.
367- S. fromList $ do
368- btb <- btBranches bt
369- pure $ AF. headHash $ btbPrefix btb
370- forkFirstBlocks =
371- -- The set of forked nodes. If any of these is in our ancestry, we are
372- -- not on the trunk.
373- S. fromList $ do
374- btb <- btBranches bt
375- pure $ either AF. anchorToHash (BlockHash . blockHash) . AF. last $ btbSuffix btb
373+ let forkFirstBlocks =
374+ -- A map assigning numbers to forked nodes. If any of these is in our
375+ -- ancestry, we are on a branch and have a fork number.
376+ Map. fromList $ do
377+ -- `btBranches` are not sorted in a meaningful way, so the fork
378+ -- numbers assigned here are meant only to distinguish them.
379+ (btb, ix) <- zip (btBranches bt) [1 .. ]
380+ -- The first block in a branch is the /last/ (i.e. leftmost or oldest) one.
381+ -- See the documentation of `Test.Util.TestBlock.TestHash`
382+ -- in relation to this order.
383+ let firstBlockHash = either AF. anchorToHash (BlockHash . blockHash) . AF. last $ btbSuffix btb
384+ pure $ (firstBlockHash, ix)
385+ blockAncestry = foldMap AF. toNewestFirst $ Map. lookup hash $ deforestBlockTree bt
376386 in
377- case
378- -- Fold over each block in the ancestry. Add up how many of them are in
379- -- forkPoints, and determine whether any are in forkFirstBlocks.
380- flip foldMap (
381- maybe mempty AF. toOldestFirst $
382- M. lookup hash $ deforestBlockTree bt
383- )
384- $ \ blk ->
385- let h = BlockHash $ blockHash blk
386- in ( Any $ S. member h forkFirstBlocks
387- , Sum $ bool 0 1 $ S. member h forkPoints
388- )
389-
390- of
391- (Any True , Sum x) -> x
392- (Any False , _) -> 0
387+ -- Get the fork number of the most recent forked node in the ancestry.
388+ fromMaybe 0 $ getFirst $ flip foldMap blockAncestry $
389+ \ blk -> First $ let h = BlockHash $ blockHash blk
390+ in Map. lookup h forkFirstBlocks
393391
394392blockForkNo :: AF. HasHeader blk => BlockTree blk -> ChainHash blk -> Word64
395- blockForkNo pxy = \ case
396- BlockHash h -> hashForkNo pxy h
393+ blockForkNo bt = \ case
394+ BlockHash h -> hashForkNo bt h
397395 _ -> 0
398396
399397initBranch :: forall blk . (GetHeader blk , AF. HasHeader blk ) => BlockTree blk -> Int -> Range -> AF. AnchoredFragment blk -> BranchSlots blk
0 commit comments