Skip to content

Commit

Permalink
Byron: move tip block number into ByronTransition
Browse files Browse the repository at this point in the history
Initial motivation for this is the need (in a later commit) to implement the
translation of the last *ticked* Byron ledger state to the first Shelley state,
which becomes possible as `ByronTransition` is part of the ticked Byron ledger
state.

Apart from the translation to Shelley, this tip block number is only used to
check whether an update proposal became stable, so it makes sense to make it
part of `ByronTransition` in any case.
  • Loading branch information
amesgen committed Sep 19, 2023
1 parent 76bc694 commit 2f88679
Show file tree
Hide file tree
Showing 4 changed files with 58 additions and 47 deletions.
Original file line number Diff line number Diff line change
Expand Up @@ -89,27 +89,30 @@ import Ouroboros.Consensus.Util (ShowProxy (..), (..:))
-------------------------------------------------------------------------------}

data instance LedgerState ByronBlock = ByronLedgerState {
byronLedgerTipBlockNo :: !(WithOrigin BlockNo)
, byronLedgerState :: !CC.ChainValidationState
byronLedgerState :: !CC.ChainValidationState
, byronLedgerTransition :: !ByronTransition
}
deriving (Eq, Show, Generic, NoThunks)

-- | Information required to determine the transition from Byron to Shelley
data ByronTransition =
-- | Per candidate proposal, the 'BlockNo' in which it became a candidate
--
-- The HFC needs to know when a candidate proposal becomes stable. We cannot
-- reliably do this using 'SlotNo': doing so would mean that if we were to
-- switch to a denser fork, something that was previously deemed stable is
-- suddenly not deemed stable anymore (although in actuality it still is).
-- We therefore must do this based on 'BlockNo' instead, but unfortunately
-- the Byron ledger does not record this information. Therefore, we record
-- it here instead.
--
-- Invariant: the domain of this map should equal the set of candidate
-- proposals.
ByronTransitionInfo !(Map Update.ProtocolVersion BlockNo)
data ByronTransition = ByronTransitionInfo {
-- | Per candidate proposal, the 'BlockNo' in which it became a candidate
--
-- The HFC needs to know when a candidate proposal becomes stable. We
-- cannot reliably do this using 'SlotNo': doing so would mean that if we
-- were to switch to a denser fork, something that was previously deemed
-- stable is suddenly not deemed stable anymore (although in actuality it
-- still is). We therefore must do this based on 'BlockNo' instead, but
-- unfortunately the Byron ledger does not record this information.
-- Therefore, we record it here instead.
--
-- Invariant: the domain of this map should equal the set of candidate
-- proposals.
perCandidateProposals :: !(Map Update.ProtocolVersion BlockNo)
, -- | Block number of the last applied block, used to compute when a
-- proposal got stable.
byronLedgerTipBlockNo :: !(WithOrigin BlockNo)
}
deriving (Eq, Show, Generic, NoThunks)

instance UpdateLedger ByronBlock
Expand All @@ -121,8 +124,7 @@ initByronLedgerState :: Gen.Config
-> LedgerState ByronBlock
initByronLedgerState genesis mUtxo = ByronLedgerState {
byronLedgerState = override mUtxo initState
, byronLedgerTipBlockNo = Origin
, byronLedgerTransition = ByronTransitionInfo Map.empty
, byronLedgerTransition = ByronTransitionInfo Map.empty Origin
}
where
initState :: CC.ChainValidationState
Expand Down Expand Up @@ -249,7 +251,7 @@ instance LedgerSupportsProtocol ByronBlock where
--
-- To create a forecast, take the delegation state from the given ledger
-- state, and apply the updates that should be applied by the given slot.
ledgerViewForecastAt cfg (ByronLedgerState _tipBlkNo st _) = Forecast at $ \for ->
ledgerViewForecastAt cfg (ByronLedgerState st _) = Forecast at $ \for ->
toTickedPBftLedgerView <$> if
| for == lastSlot ->
return $ CC.getDelegationMap st
Expand Down Expand Up @@ -358,19 +360,23 @@ applyABlock validationMode cfg blk blkHash blkNo TickedByronLedgerState{..} = do
aux candidate = (UPE.cpuProtocolVersion candidate, blkNo)

transition' :: ByronTransition
transition' =
case untickedByronLedgerTransition of
ByronTransitionInfo oldEntries -> ByronTransitionInfo $
transition' = ByronTransitionInfo {
perCandidateProposals =
-- Candidates that have /just/ become candidates
let newEntries :: Map Update.ProtocolVersion BlockNo
newEntries = ifNew `Map.difference` oldEntries

-- Remove any entries that aren't candidates anymore
in (oldEntries `Map.intersection` ifNew) `Map.union` newEntries
, byronLedgerTipBlockNo = NotOrigin blkNo
}
where
ByronTransitionInfo {
perCandidateProposals = oldEntries
} = untickedByronLedgerTransition

return ByronLedgerState {
byronLedgerTipBlockNo = NotOrigin blkNo
, byronLedgerState = st'
byronLedgerState = st'
, byronLedgerTransition = transition'
}

Expand All @@ -386,9 +392,10 @@ applyABoundaryBlock :: Gen.Config
applyABoundaryBlock cfg blk blkNo TickedByronLedgerState{..} = do
st' <- CC.validateBoundary cfg blk tickedByronLedgerState
return ByronLedgerState {
byronLedgerTipBlockNo = NotOrigin blkNo
, byronLedgerState = st'
, byronLedgerTransition = untickedByronLedgerTransition
byronLedgerState = st'
, byronLedgerTransition = untickedByronLedgerTransition {
byronLedgerTipBlockNo = NotOrigin blkNo
}
}

{-------------------------------------------------------------------------------
Expand All @@ -412,7 +419,7 @@ encodeByronHeaderState = encodeHeaderState
encodeByronChainDepState
encodeByronAnnTip

-- | Encode transition info
-- | Encode candidate proposals (in 'ByronTransition').
--
-- We encode the absence of any info separately. This gives us a bit more
-- wiggle room to change our mind about what we store in snapshots, as they
Expand All @@ -422,8 +429,8 @@ encodeByronHeaderState = encodeHeaderState
-- inclusion of a list length. We didn't, so the decoder is a bit awkward :/
--
-- TODO: If we break compatibility anyway, we might decide to clean this up.
encodeByronTransition :: ByronTransition -> Encoding
encodeByronTransition (ByronTransitionInfo bNos)
encodeByronCandidateProposals :: Map Update.ProtocolVersion BlockNo -> Encoding
encodeByronCandidateProposals bNos
| Map.null bNos = CBOR.encodeWord8 0
| otherwise =
CBOR.encodeListLen (fromIntegral (Map.size bNos))
Expand All @@ -438,13 +445,13 @@ encodeByronTransition (ByronTransitionInfo bNos)
, encode bno
]

-- | Decode Byron transition info
-- | Decode candidate proposals (in 'ByronTransition')
--
-- See comments for 'encodeByronTransition'.
decodeByronTransition :: Decoder s ByronTransition
decodeByronTransition = do
decodeByronCandidateProposals :: Decoder s (Map Update.ProtocolVersion BlockNo)
decodeByronCandidateProposals = do
ttype <- CBOR.peekTokenType
fmap ByronTransitionInfo $ case ttype of
case ttype of
CBOR.TypeUInt -> do
tag <- CBOR.decodeWord8
case tag of
Expand All @@ -470,16 +477,19 @@ encodeByronLedgerState ByronLedgerState{..} = mconcat [
encodeListLen 3
, encode byronLedgerTipBlockNo
, encode byronLedgerState
, encodeByronTransition byronLedgerTransition
, encodeByronCandidateProposals perCandidateProposals
]
where
ByronTransitionInfo{..} = byronLedgerTransition

decodeByronLedgerState :: Decoder s (LedgerState ByronBlock)
decodeByronLedgerState = do
enforceSize "ByronLedgerState" 3
ByronLedgerState
<$> decode
<*> decode
<*> decodeByronTransition
tipBlockNo <- decode
ledgerState <- decode
candidateProposals <- decodeByronCandidateProposals
let transitionInfo = ByronTransitionInfo candidateProposals tipBlockNo
pure $ ByronLedgerState ledgerState transitionInfo

encodeByronQuery :: BlockQuery ByronBlock result -> Encoding
encodeByronQuery query = case query of
Expand Down
Original file line number Diff line number Diff line change
Expand Up @@ -139,7 +139,7 @@ byronTransition ByronPartialLedgerConfig{..} shelleyMajorVersion state =
. Byron.Inspect.protocolUpdates byronLedgerConfig
$ state
where
ByronTransitionInfo transitionInfo = byronLedgerTransition state
ByronTransitionInfo transitionInfo _tipBlockNo = byronLedgerTransition state

genesis = byronLedgerConfig
k = CC.Genesis.gdK $ CC.Genesis.configGenesisData genesis
Expand Down Expand Up @@ -192,7 +192,7 @@ byronTransition ByronPartialLedgerConfig{..} shelleyMajorVersion state =
isReallyStable (BlockNo bno) = distance >= CC.unBlockCount k
where
distance :: Word64
distance = case byronLedgerTipBlockNo state of
distance = case byronLedgerTipBlockNo $ byronLedgerTransition state of
Origin -> bno + 1
NotOrigin (BlockNo tip) -> tip - bno

Expand Down Expand Up @@ -393,7 +393,7 @@ translateLedgerStateByronToShelleyWrapper =
shelleyLedgerTip =
translatePointByronToShelley
(ledgerTipPoint ledgerByron)
(byronLedgerTipBlockNo ledgerByron)
(byronLedgerTipBlockNo $ byronLedgerTransition ledgerByron)
, shelleyLedgerState =
SL.translateToShelleyLedgerState
(toFromByronTranslationContext (shelleyLedgerGenesis cfgShelley))
Expand Down
Original file line number Diff line number Diff line change
Expand Up @@ -168,9 +168,8 @@ exampleChainDepState = S.fromList signers

emptyLedgerState :: LedgerState ByronBlock
emptyLedgerState = ByronLedgerState {
byronLedgerTipBlockNo = Origin
, byronLedgerState = initState
, byronLedgerTransition = ByronTransitionInfo Map.empty
byronLedgerState = initState
, byronLedgerTransition = ByronTransitionInfo Map.empty Origin
}
where
initState :: CC.Block.ChainValidationState
Expand Down
Original file line number Diff line number Diff line change
Expand Up @@ -260,10 +260,12 @@ instance Arbitrary CC.Del.Map where
arbitrary = CC.Del.fromList <$> arbitrary

instance Arbitrary ByronTransition where
arbitrary = ByronTransitionInfo . Map.fromList <$> arbitrary
arbitrary = ByronTransitionInfo
<$> (Map.fromList <$> arbitrary)
<*> arbitrary

instance Arbitrary (LedgerState ByronBlock) where
arbitrary = ByronLedgerState <$> arbitrary <*> arbitrary <*> arbitrary
arbitrary = ByronLedgerState <$> arbitrary <*> arbitrary

instance Arbitrary (TipInfoIsEBB ByronBlock) where
arbitrary = TipInfoIsEBB <$> arbitrary <*> elements [IsEBB, IsNotEBB]
Expand Down

0 comments on commit 2f88679

Please sign in to comment.