22{-# LANGUAGE FlexibleContexts #-}
33{-# LANGUAGE LambdaCase #-}
44{-# LANGUAGE StandaloneDeriving #-}
5- {-# LANGUAGE TypeApplications #-}
65{-# LANGUAGE TypeFamilies #-}
76{-# LANGUAGE TypeOperators #-}
87{-# LANGUAGE UndecidableInstances #-}
@@ -21,7 +20,6 @@ module Ouroboros.Consensus.Peras.SelectView
2120 ) where
2221
2322import Data.Function (on )
24- import Data.Word (Word64 )
2523import Ouroboros.Consensus.Block
2624import Ouroboros.Consensus.Peras.Weight
2725import Ouroboros.Consensus.Protocol.Abstract
@@ -39,12 +37,8 @@ import qualified Ouroboros.Network.AnchoredFragment as AF
3937-- as the fragments might not intersect, and so some blocks after their
4038-- intersection (and hence their weight boost) are unknown.
4139data WeightedSelectView proto = WeightedSelectView
42- { wsvLength :: ! Word64
43- -- ^ The length of the fragment.
44- --
45- -- If we ignore EBBs, then it would be equivalent to use the tip 'BlockNo'
46- -- here. However, with EBBs, the 'BlockNo' can result in misleading
47- -- comparisons if only one fragment contains EBBs.
40+ { wsvBlockNo :: ! BlockNo
41+ -- ^ The 'BlockNo' at the tip of a fragment.
4842 , wsvWeightBoost :: ! PerasWeight
4943 -- ^ The weight boost of a fragment (w.r.t. a particular anchor).
5044 , wsvTiebreaker :: TiebreakerView proto
@@ -58,11 +52,11 @@ deriving stock instance Eq (TiebreakerView proto) => Eq (WeightedSelectView prot
5852-- 'WeightedSelectView's obtained from fragments with different anchors?
5953-- Something ST-trick like?
6054
61- -- | The total weight, ie the sum of 'wsvLength ' and 'wsvBoostedWeight'.
55+ -- | The total weight, ie the sum of 'wsvBlockNo ' and 'wsvBoostedWeight'.
6256wsvTotalWeight :: WeightedSelectView proto -> PerasWeight
6357-- could be cached, but then we need to be careful to maintain the invariant
6458wsvTotalWeight wsv =
65- PerasWeight (wsvLength wsv) <> wsvWeightBoost wsv
59+ PerasWeight (unBlockNo (wsvBlockNo wsv) ) <> wsvWeightBoost wsv
6660
6761instance Ord (TiebreakerView proto ) => Ord (WeightedSelectView proto ) where
6862 compare =
@@ -100,7 +94,7 @@ weightedSelectView bcfg weights = \case
10094 frag@ (_ AF. :> (getHeader1 -> hdr)) ->
10195 NonEmptyFragment
10296 WeightedSelectView
103- { wsvLength = fromIntegral @ Int @ Word64 $ AF. length frag
97+ { wsvBlockNo = blockNo hdr
10498 , wsvWeightBoost = weightBoostOfFragment weights frag
10599 , wsvTiebreaker = tiebreakerView bcfg hdr
106100 }
0 commit comments