@@ -9,9 +9,9 @@ import Control.Monad.Catch
99import Control.Monad.Reader
1010import Control.Monad.State
1111import Data.Foldable
12- import Data.List (union )
1312import qualified Data.Map.Strict as Map
1413import Data.Maybe
14+ import qualified Data.Set as Set
1515import Lens.Micro.Platform
1616
1717import Concordium.Genesis.Data.BaseV1
@@ -511,44 +511,16 @@ processTimeout tm = do
511511 -- should either be the current epoch or the previous one.
512512 let maybeFinComm = getFinalizersForEpoch (cbEpoch highestCB)
513513 forM_ maybeFinComm $ \ finCommQC -> do
514- -- The baker IDs of the finalizers who have signed in the first epoch.
515- let firstBakerIds
516- | Just firstFinComm <- getFinalizersForEpoch tmFirstEpoch =
517- bakerIdsFor firstFinComm tmFirstEpochTimeouts
518- | otherwise = []
519- -- The baker IDs of the finalizers who have signed in the second epoch.
520- let secondBakerIds
521- | not (null tmSecondEpochTimeouts),
522- Just secondFinComm <- getFinalizersForEpoch (tmFirstEpoch + 1 ) =
523- bakerIdsFor secondFinComm tmSecondEpochTimeouts
524- | otherwise = []
525- -- Compute the accumulated voting power by folding over the finalization committee.
526- -- We are here making use of the fact that the finalization committee is ordered
527- -- by ascending baker ids and that the list of bakerids are also ordered by ascending baker id.
528- -- Moreover there MUST be no duplicates in either @firstBakerIds@ or @secondBakerIds@.
529- let voterPowerSum =
530- fst $
531- foldl'
532- ( \ (! accum, bids) finalizer ->
533- -- We are done accumulating.
534- if null bids
535- then (accum, [] )
536- else
537- if head bids == finalizerBakerId finalizer
538- then -- If we have a match we add the weight to the
539- -- accumulator and proceed to the next baker id
540- -- and finalizer.
541- (accum + finalizerWeight finalizer, tail bids)
542- else -- If we did not have a match we continue
543- -- checking with a new finalizer.
544- (accum, bids)
545- )
546- (0 , firstBakerIds `union` secondBakerIds)
547- (committeeFinalizers finCommQC)
548- let totalWeightRational = toRational $ committeeTotalWeight finCommQC
514+ -- Determine the fractional weight of the finalizers that have signed timeout messages.
515+ let voterPowerFrac =
516+ voterPowerFraction
517+ finCommQC
518+ (getFinalizersForEpoch tmFirstEpoch)
519+ (getFinalizersForEpoch (tmFirstEpoch + 1 ))
520+ (Map. keys tmFirstEpochTimeouts)
521+ (Map. keys tmSecondEpochTimeouts)
549522 genesisSigThreshold <- toRational . genesisSignatureThreshold . gmParameters <$> use genesisMetadata
550- let voterPowerSumRational = toRational voterPowerSum
551- when (voterPowerSumRational / totalWeightRational >= genesisSigThreshold) $ do
523+ when (voterPowerFrac >= genesisSigThreshold) $ do
552524 let currentRound = _rsCurrentRound currentRoundStatus
553525 let tc = makeTimeoutCertificate currentRound newTimeoutMessages
554526 advanceRoundWithTimeout
@@ -557,14 +529,49 @@ processTimeout tm = do
557529 rtTimeoutCertificate = tc
558530 }
559531 makeBlock
532+
533+ -- | Compute the fraction of the total weight of the finalizers that have signed timeout messages.
534+ -- This is used to determine whether a timeout certificate should be formed.
535+ -- The weight of a finalizer is considered to be its weight in the first finalization committee.
536+ -- The baker identities are determined by the finalization committees for the first and second
537+ -- epoch. If either of these is not provided, the corresponding set of baker identities is empty.
538+ -- (Generally, if the finalization committee is not provided, then the timeout messages for that
539+ -- epoch should also be empty.)
540+ voterPowerFraction ::
541+ -- | The finalization committee used for weighting the finalizers.
542+ FinalizationCommittee ->
543+ -- | The finalization committee for the first epoch.
544+ Maybe FinalizationCommittee ->
545+ -- | The finalization committee for the second epoch.
546+ Maybe FinalizationCommittee ->
547+ -- | The finalizer indexes that have signed in the first epoch.
548+ [FinalizerIndex ] ->
549+ -- | The finalizer indexes that have signed in the second epoch.
550+ [FinalizerIndex ] ->
551+ -- | The fraction of the total weight of the finalizers that have signed.
552+ Rational
553+ voterPowerFraction finCommQC mFirstFinComm mSecondFinComm firstEpochTimeouts secondEpochTimeouts =
554+ toRational voterPowerSum / toRational (committeeTotalWeight finCommQC)
560555 where
561- -- baker ids for the finalizers who have signed off the message.
562- -- Note that the finalization committee is sorted by ascending baker ids.
563- bakerIdsFor finComm timeouts =
556+ -- The sum of the voter power of the finalizers who have signed.
557+ voterPowerSum = sum $ voterPower <$> committeeFinalizers finCommQC
558+ -- The weight that a finalizer contributes to the timeout certificate.
559+ -- A finalizer only contributes if they have signed (in either epoch), otherwise
560+ -- it contributes weight 0.
561+ voterPower finalizer
562+ | finalizerBakerId finalizer `Set.member` allBakerIds = finalizerWeight finalizer
563+ | otherwise = 0
564+ allBakerIds = Set. fromList $ firstBakerIds ++ secondBakerIds
565+ -- The baker IDs of the finalizers who have signed in the first epoch.
566+ firstBakerIds = bakerIdsFor mFirstFinComm firstEpochTimeouts
567+ -- The baker IDs of the finalizers who have signed in the second epoch.
568+ secondBakerIds = bakerIdsFor mSecondFinComm secondEpochTimeouts
569+ -- The baker IDs of the finalizers who have signed in the given epoch.
570+ bakerIdsFor (Just finComm) timeouts =
564571 mapMaybe
565572 (fmap finalizerBakerId . finalizerByIndex finComm)
566- -- Note that @Map.keys@ returns the keys in ascending order.
567- ( Map. keys timeouts)
573+ timeouts
574+ bakerIdsFor Nothing _ = []
568575
569576-- | Make a 'TimeoutCertificate' from a 'TimeoutMessages'.
570577--
0 commit comments