Skip to content

Commit 18f186d

Browse files
Lucsanszkydisassembler
authored andcommitted
Utilize new PParams prediction functionality for HFC
* Use the updated behavior * Fixup haddock to reflect generality of protocol version update
1 parent 2353df1 commit 18f186d

File tree

4 files changed

+40
-187
lines changed

4 files changed

+40
-187
lines changed

ouroboros-consensus-cardano/src/shelley/Ouroboros/Consensus/Shelley/Eras.hs

Lines changed: 1 addition & 27 deletions
Original file line numberDiff line numberDiff line change
@@ -72,7 +72,6 @@ import Control.Monad.Except
7272
import Control.State.Transition (PredicateFailure)
7373
import Data.Data (Proxy (Proxy))
7474
import Data.List.NonEmpty (NonEmpty ((:|)))
75-
import Lens.Micro ((^.))
7675
import NoThunks.Class (NoThunks)
7776
import Ouroboros.Consensus.Ledger.SupportsMempool
7877
(WhetherToIntervene (..))
@@ -159,14 +158,6 @@ class ( Core.EraSegWits era
159158
, SL.Validated (Core.Tx era)
160159
)
161160

162-
-- | Get the protocol version out of a 'Core.PParamsUpdate', used to detect
163-
-- whether we should perform a HF. This will likely be removed/changed once we
164-
-- implement HF enactment in Conway (see
165-
-- <https://github.com/IntersectMBO/ouroboros-consensus/issues/61>).
166-
--
167-
-- For now, this always returns 'Nothing' for Conway (see the instance below).
168-
getProposedProtocolVersion :: Core.PParamsUpdate era -> Maybe ProtVer
169-
170161
-- | Whether the era has an instance of 'CG.ConwayEraGov'
171162
getConwayEraGovDict :: proxy era -> Maybe (ConwayEraGovDict era)
172163

@@ -194,58 +185,41 @@ defaultApplyShelleyBasedTx globals ledgerEnv mempoolState _wti tx =
194185
mempoolState
195186
tx
196187

197-
defaultGetProposedProtocolVersion ::
198-
(EraPParams era, ProtVerAtMost era 8)
199-
=> Core.PParamsUpdate era
200-
-> Maybe ProtVer
201-
defaultGetProposedProtocolVersion proposal =
202-
strictMaybeToMaybe $ proposal ^. ppuProtocolVersionL
203-
204188
defaultGetConwayEraGovDict :: proxy era -> Maybe (ConwayEraGovDict era)
205189
defaultGetConwayEraGovDict _ = Nothing
206190

207191
instance (SL.PraosCrypto c, DSignable c (Hash c EraIndependentTxBody))
208192
=> ShelleyBasedEra (ShelleyEra c) where
209193
applyShelleyBasedTx = defaultApplyShelleyBasedTx
210194

211-
getProposedProtocolVersion = defaultGetProposedProtocolVersion
212-
213195
getConwayEraGovDict = defaultGetConwayEraGovDict
214196

215197
instance (SL.PraosCrypto c, DSignable c (Hash c EraIndependentTxBody))
216198
=> ShelleyBasedEra (AllegraEra c) where
217199
applyShelleyBasedTx = defaultApplyShelleyBasedTx
218200

219-
getProposedProtocolVersion = defaultGetProposedProtocolVersion
220-
221201
getConwayEraGovDict = defaultGetConwayEraGovDict
222202

223203
instance (SL.PraosCrypto c, DSignable c (Hash c EraIndependentTxBody))
224204
=> ShelleyBasedEra (MaryEra c) where
225205
applyShelleyBasedTx = defaultApplyShelleyBasedTx
226206

227-
getProposedProtocolVersion = defaultGetProposedProtocolVersion
228-
229207
getConwayEraGovDict = defaultGetConwayEraGovDict
230208

231209
instance (SL.PraosCrypto c, DSignable c (Hash c EraIndependentTxBody))
232210
=> ShelleyBasedEra (AlonzoEra c) where
233211
applyShelleyBasedTx = applyAlonzoBasedTx
234212

235-
getProposedProtocolVersion = defaultGetProposedProtocolVersion
236-
237213
getConwayEraGovDict = defaultGetConwayEraGovDict
238214

239215
instance (Praos.PraosCrypto c) => ShelleyBasedEra (BabbageEra c) where
240216
applyShelleyBasedTx = applyAlonzoBasedTx
241217

242-
getProposedProtocolVersion = defaultGetProposedProtocolVersion
243-
244218
getConwayEraGovDict = defaultGetConwayEraGovDict
245219

246220
instance (Praos.PraosCrypto c) => ShelleyBasedEra (ConwayEra c) where
247221
applyShelleyBasedTx = applyAlonzoBasedTx
248-
getProposedProtocolVersion _ = Nothing
222+
249223
getConwayEraGovDict _ = Just ConwayEraGovDict
250224

251225
applyAlonzoBasedTx :: forall era.

ouroboros-consensus-cardano/src/shelley/Ouroboros/Consensus/Shelley/Ledger/Inspect.hs

Lines changed: 26 additions & 137 deletions
Original file line numberDiff line numberDiff line change
@@ -8,166 +8,55 @@
88

99
{-# OPTIONS_GHC -Wno-orphans #-}
1010
module Ouroboros.Consensus.Shelley.Ledger.Inspect (
11-
ProtocolUpdate (..)
12-
, ShelleyLedgerUpdate (..)
13-
, UpdateProposal (..)
14-
, UpdateState (..)
15-
, protocolUpdates
11+
ShelleyLedgerUpdate (..)
12+
, pparamsUpdate
1613
) where
1714

15+
import Cardano.Ledger.BaseTypes (StrictMaybe (..))
1816
import qualified Cardano.Ledger.Shelley.API as SL
1917
import qualified Cardano.Ledger.Shelley.Core as Core
18+
import qualified Cardano.Ledger.Shelley.Governance as SL
2019
import qualified Cardano.Ledger.Shelley.LedgerState as SL
21-
import qualified Cardano.Ledger.Shelley.PParams as SL
2220
import Control.Monad
23-
import Data.Map.Strict (Map)
24-
import qualified Data.Map.Strict as Map
25-
import Data.Maybe (fromMaybe)
2621
import Data.Void
27-
import Data.Word (Word64)
28-
import Lens.Micro.Extras (view)
22+
import Lens.Micro ((^.))
2923
import Ouroboros.Consensus.Block
30-
import Ouroboros.Consensus.Config
3124
import Ouroboros.Consensus.Ledger.Abstract
3225
import Ouroboros.Consensus.Ledger.Inspect
33-
import Ouroboros.Consensus.Shelley.Eras (EraCrypto,
34-
ShelleyBasedEra (..))
3526
import Ouroboros.Consensus.Shelley.Ledger.Block
3627
import Ouroboros.Consensus.Shelley.Ledger.Ledger
3728
import Ouroboros.Consensus.Util.Condense
3829

39-
data ProtocolUpdate era = ProtocolUpdate {
40-
protocolUpdateProposal :: UpdateProposal era
41-
, protocolUpdateState :: UpdateState (EraCrypto era)
42-
}
43-
deriving instance Eq (Core.PParamsUpdate era) => Eq (ProtocolUpdate era)
44-
deriving instance Show (Core.PParamsUpdate era) => Show (ProtocolUpdate era)
45-
46-
-- | Update proposal
47-
--
48-
-- As in Byron, a proposal is a partial map from parameters to their values.
49-
data UpdateProposal era = UpdateProposal {
50-
-- | The protocol parameters changed by this update proposal
51-
--
52-
-- An update is /identified/ by how it updates the protocol parameters.
53-
proposalParams :: Core.PParamsUpdate era
54-
55-
-- | New version (if changed by this proposal)
56-
--
57-
-- The protocol version itself is also considered to be just another
58-
-- parameter, and parameters can change /without/ changing the protocol
59-
-- version, although a convention /could/ be established that the protocol
60-
-- version must change if any of the parameters do; but the specification
61-
-- itself does not mandate this.
62-
--
63-
-- We record the version separately for the convenience of the HFC.
64-
, proposalVersion :: Maybe SL.ProtVer
65-
66-
-- | The 'EpochNo' the proposal becomes active in, if it is adopted
67-
, proposalEpoch :: EpochNo
68-
}
69-
70-
deriving instance Eq (Core.PParamsUpdate era) => Eq (UpdateProposal era)
71-
deriving instance Show (Core.PParamsUpdate era) => Show (UpdateProposal era)
72-
73-
-- | Proposal state
74-
--
75-
-- The update mechanism in Shelley is simpler than it is in Byron. There is no
76-
-- distinction between votes and proposals: to \"vote\" for a proposal one
77-
-- merely submits the exact same proposal. There is also no separate
78-
-- endorsement step. The procedure is as follows:
79-
--
80-
-- 1. During each epoch, a genesis key can submit (via its delegates) zero,
81-
-- one, or many proposals; each submission overrides the previous one.
82-
-- 2. \"Voting\" (submitting of proposals) ends @2 * stabilityWindow@ slots
83-
-- (i.e. @6k/f@) before the end of the epoch. In other words, proposals
84-
-- for the upcoming epoch must be submitted within the first @4k/f@ slots
85-
-- of this one.
86-
-- 3. At the end of an epoch, if the majority of nodes (as determined by the
87-
-- @Quorum@ specification constant, which must be greater than half the
88-
-- nodes) have most recently submitted the same exact proposal, then it is
89-
-- adopted.
90-
-- 4. The next epoch is always started with a clean slate, proposals from the
91-
-- previous epoch that didn't make it are discarded (except for "future
92-
-- proposals" that are explicitly marked for future epochs).
93-
data UpdateState c = UpdateState {
94-
-- | The genesis delegates that voted for this proposal
95-
proposalVotes :: [SL.KeyHash 'SL.Genesis c]
96-
97-
-- | Has this proposal reached sufficient votes to be adopted?
98-
, proposalReachedQuorum :: Bool
99-
}
100-
deriving (Show, Eq)
101-
102-
protocolUpdates ::
103-
forall era proto. ShelleyBasedEra era
104-
=> SL.ShelleyGenesis (EraCrypto era)
105-
-> LedgerState (ShelleyBlock proto era)
106-
-> [ProtocolUpdate era]
107-
protocolUpdates genesis st = [
108-
ProtocolUpdate {
109-
protocolUpdateProposal = UpdateProposal {
110-
proposalParams = proposal
111-
, proposalEpoch = succ currentEpoch
112-
, proposalVersion = getProposedProtocolVersion proposal
113-
}
114-
, protocolUpdateState = UpdateState {
115-
proposalVotes = votes
116-
, proposalReachedQuorum = length votes >= fromIntegral quorum
117-
}
118-
}
119-
| (proposal, votes) <- Map.toList $ invertMap proposals
120-
]
121-
where
122-
invertMap :: Ord b => Map a b -> Map b [a]
123-
invertMap = Map.fromListWith (<>) . fmap swizzle . Map.toList
124-
where
125-
swizzle (a, b) = (b, [a])
126-
127-
-- Updated proposed within the proposal window
128-
proposals :: Map (SL.KeyHash 'SL.Genesis (EraCrypto era)) (Core.PParamsUpdate era)
129-
SL.ProposedPPUpdates proposals =
130-
fromMaybe SL.emptyPPPUpdates
131-
. Core.getProposedPPUpdates
132-
. view SL.newEpochStateGovStateL
133-
. shelleyLedgerState
134-
$ st
135-
136-
-- A proposal is accepted if the number of votes is equal to or greater
137-
-- than the quorum. The quorum itself must be strictly greater than half
138-
-- the number of genesis keys, but we do not rely on that property here.
139-
quorum :: Word64
140-
quorum = SL.sgUpdateQuorum genesis
141-
142-
-- The proposals in 'SL.proposals' are for the upcoming epoch
143-
-- (we ignore 'futureProposals')
144-
currentEpoch :: EpochNo
145-
currentEpoch = SL.nesEL . shelleyLedgerState $ st
146-
147-
{-------------------------------------------------------------------------------
148-
Inspection
149-
-------------------------------------------------------------------------------}
150-
15130
data ShelleyLedgerUpdate era =
152-
ShelleyUpdatedProtocolUpdates [ProtocolUpdate era]
31+
ShelleyUpdatedPParams
32+
!(StrictMaybe (Core.PParams era))
33+
!EpochNo
15334

154-
deriving instance Eq (Core.PParamsUpdate era) => Eq (ShelleyLedgerUpdate era)
155-
deriving instance Show (Core.PParamsUpdate era) => Show (ShelleyLedgerUpdate era)
35+
deriving instance Eq (Core.PParams era) => Eq (ShelleyLedgerUpdate era)
36+
deriving instance Show (Core.PParams era) => Show (ShelleyLedgerUpdate era)
15637

157-
instance Show (Core.PParamsUpdate era) => Condense (ShelleyLedgerUpdate era) where
38+
instance Show (Core.PParams era) => Condense (ShelleyLedgerUpdate era) where
15839
condense = show
15940

16041
instance ShelleyBasedEra era => InspectLedger (ShelleyBlock proto era) where
16142
type LedgerWarning (ShelleyBlock proto era) = Void
16243
type LedgerUpdate (ShelleyBlock proto era) = ShelleyLedgerUpdate era
16344

164-
inspectLedger tlc before after = do
45+
inspectLedger _tlc before after = do
16546
guard $ updatesBefore /= updatesAfter
166-
return $ LedgerUpdate $ ShelleyUpdatedProtocolUpdates updatesAfter
47+
return $ LedgerUpdate updatesAfter
16748
where
168-
genesis :: SL.ShelleyGenesis (EraCrypto era)
169-
genesis = shelleyLedgerGenesis (configLedger tlc)
17049

171-
updatesBefore, updatesAfter :: [ProtocolUpdate era]
172-
updatesBefore = protocolUpdates genesis before
173-
updatesAfter = protocolUpdates genesis after
50+
updatesBefore, updatesAfter :: ShelleyLedgerUpdate era
51+
updatesBefore = pparamsUpdate before
52+
updatesAfter = pparamsUpdate after
53+
54+
pparamsUpdate ::
55+
forall era proto. ShelleyBasedEra era
56+
=> LedgerState (ShelleyBlock proto era)
57+
-> ShelleyLedgerUpdate era
58+
pparamsUpdate st =
59+
let nes = shelleyLedgerState st
60+
in ShelleyUpdatedPParams
61+
(SL.nextEpochUpdatedPParams (nes ^. SL.newEpochStateGovStateL))
62+
(succ (SL.nesEL nes))

ouroboros-consensus-cardano/src/shelley/Ouroboros/Consensus/Shelley/Ledger/Ledger.hs

Lines changed: 4 additions & 3 deletions
Original file line numberDiff line numberDiff line change
@@ -229,9 +229,10 @@ newtype ShelleyTransition = ShelleyTransitionInfo {
229229
-- 3. If we count how many blocks we have seen post deadline, and we have
230230
-- reached k of them, we know that that last pre-deadline block won't
231231
-- be rolled back anymore.
232-
-- 4. At this point we can look at the ledger state and see which
233-
-- proposals we accepted in the voting period, if any, and notify the
234-
-- HFC is one of them indicates a transition.
232+
-- 4. At this point we can look at the ledger state and see if there is
233+
-- a new protocol version update scheduled on the next epoch boundary,
234+
-- and notify the HFC that we need to transition into a new era at that
235+
-- point.
235236
shelleyAfterVoting :: Word32
236237
}
237238
deriving stock (Eq, Show, Generic)

ouroboros-consensus-cardano/src/shelley/Ouroboros/Consensus/Shelley/ShelleyHFC.hs

Lines changed: 9 additions & 20 deletions
Original file line numberDiff line numberDiff line change
@@ -32,13 +32,13 @@ import Cardano.Slotting.EpochInfo (hoistEpochInfo)
3232
import Control.Monad (guard)
3333
import Control.Monad.Except (runExcept, throwError, withExceptT)
3434
import qualified Data.Map.Strict as Map
35-
import Data.Maybe
3635
import Data.SOP.BasicFunctors
3736
import Data.SOP.InPairs (RequiringBoth (..), ignoringBoth)
3837
import qualified Data.Text as T (pack)
3938
import Data.Void (Void)
4039
import Data.Word
4140
import GHC.Generics (Generic)
41+
import Lens.Micro ((^.))
4242
import NoThunks.Class (NoThunks)
4343
import Ouroboros.Consensus.Block
4444
import Ouroboros.Consensus.Config
@@ -137,9 +137,8 @@ shelleyTransition ::
137137
shelleyTransition ShelleyPartialLedgerConfig{..}
138138
transitionMajorVersionRaw
139139
state =
140-
takeAny
141-
. mapMaybe isTransition
142-
. Shelley.Inspect.protocolUpdates genesis
140+
isTransition
141+
. Shelley.Inspect.pparamsUpdate
143142
$ state
144143
where
145144
ShelleyTransitionInfo{..} = shelleyLedgerTransition state
@@ -152,24 +151,14 @@ shelleyTransition ShelleyPartialLedgerConfig{..}
152151
k :: Word64
153152
k = SL.sgSecurityParam genesis
154153

155-
isTransition :: Shelley.Inspect.ProtocolUpdate era -> Maybe EpochNo
156-
isTransition Shelley.Inspect.ProtocolUpdate{..} = do
157-
SL.ProtVer major _minor <- proposalVersion
154+
isTransition :: ShelleyLedgerUpdate era -> Maybe EpochNo
155+
isTransition (ShelleyUpdatedPParams maybePParams newPParamsEpochNo) = do
156+
SL.SJust pp <- Just maybePParams
157+
let protVer = pp ^. SL.ppProtocolVersionL
158158
transitionMajorVersion <- SL.mkVersion transitionMajorVersionRaw
159-
guard $ major == transitionMajorVersion
160-
guard $ proposalReachedQuorum
159+
guard $ SL.pvMajor protVer == transitionMajorVersion
161160
guard $ shelleyAfterVoting >= fromIntegral k
162-
return proposalEpoch
163-
where
164-
Shelley.Inspect.UpdateProposal{..} = protocolUpdateProposal
165-
Shelley.Inspect.UpdateState{..} = protocolUpdateState
166-
167-
-- In principle there could be multiple proposals that all change the
168-
-- major protocol version. In practice this can't happen because each
169-
-- delegate can only vote for one proposal, but the types don't guarantee
170-
-- this. We don't need to worry about this, and just pick any of them.
171-
takeAny :: [a] -> Maybe a
172-
takeAny = listToMaybe
161+
return newPParamsEpochNo
173162

174163
instance
175164
( ShelleyCompatible proto era,

0 commit comments

Comments
 (0)