Skip to content

Commit 3b8f972

Browse files
authored
Simplify CardanoHardForkTriggers (#1282)
Closes #1281 Instead of letting the user provide several `TriggerHardFork`s, only let them provide `CardanoHardForkTrigger`s, a restricted version that should make `protocolInfoCardano` more straightforward and less error-prone. ```haskell data CardanoHardForkTrigger blk = -- | Trigger the hard fork when the ledger protocol version is updated to -- the default for that era (@'L.eraProtVerLow' \@('ShelleyBlockLedgerEra' -- blk)@). Also see 'TriggerHardForkAtVersion'. CardanoTriggerHardForkAtDefaultVersion | -- | Trigger the hard fork at the given epoch. For testing only. Also see -- 'TriggerHardForkAtEpoch'. CardanoTriggerHardForkAtEpoch EpochNo ``` It is (intentionally) no longer possible to directly (though still manually, also see the changelog entry) to use a non-default version trigger. However, this feature was used in the Cardano ThreadNet test (as Byron had an intra-era HF), which we resolve by modifying the initial Byron protocol version (see the corresponding Haddocks). In the node, this will result in the removal of the (unused) `TestXxxHardForkAtVersion` config fields.
2 parents 69e8d0f + c600f30 commit 3b8f972

File tree

10 files changed

+167
-249
lines changed

10 files changed

+167
-249
lines changed
Lines changed: 16 additions & 0 deletions
Original file line numberDiff line numberDiff line change
@@ -0,0 +1,16 @@
1+
### Breaking
2+
3+
- Changed `CardanoHardTriggers` to contain `CardanoHardForkTrigger`s which are a
4+
simpler version of the previous `TriggerHardForkAt`. In particular, this will
5+
affect call sites of `protocolInfoCardano`.
6+
7+
Migration notes:
8+
9+
- Change `TriggerHardForkAtEpoch` to `CardanoTriggerHardForkAtEpoch`.
10+
- Change `TriggerHardForkAtVersion` to `CardanoTriggerHardForkAtDefaultVersion`.
11+
12+
This constructor does not take a version argument, but rather defaults to
13+
the corresponding first ledger protocol version. We are not aware of any
14+
use case that requires a different value, but if there is, it is still
15+
possible to manually modify the returned `LedgerConfig`s of
16+
`protocolInfoCardano` directly.

ouroboros-consensus-cardano/src/ouroboros-consensus-cardano/Ouroboros/Consensus/Cardano.hs

Lines changed: 1 addition & 0 deletions
Original file line numberDiff line numberDiff line change
@@ -8,6 +8,7 @@ module Ouroboros.Consensus.Cardano (
88
, ProtocolCardano
99
, ProtocolShelley
1010
-- * Abstract over the various protocols
11+
, CardanoHardForkTrigger (..)
1112
, CardanoHardForkTriggers (..)
1213
, module X
1314
) where

ouroboros-consensus-cardano/src/ouroboros-consensus-cardano/Ouroboros/Consensus/Cardano/Node.hs

Lines changed: 46 additions & 19 deletions
Original file line numberDiff line numberDiff line change
@@ -1,5 +1,6 @@
11
{-# LANGUAGE CPP #-}
22
{-# LANGUAGE DataKinds #-}
3+
{-# LANGUAGE DerivingStrategies #-}
34
{-# LANGUAGE FlexibleContexts #-}
45
{-# LANGUAGE FlexibleInstances #-}
56
{-# LANGUAGE LambdaCase #-}
@@ -33,6 +34,7 @@
3334

3435
module Ouroboros.Consensus.Cardano.Node (
3536
CardanoHardForkConstraints
37+
, CardanoHardForkTrigger (..)
3638
, CardanoHardForkTriggers (.., CardanoHardForkTriggers', triggerHardForkShelley, triggerHardForkAllegra, triggerHardForkMary, triggerHardForkAlonzo, triggerHardForkBabbage, triggerHardForkConway)
3739
, CardanoProtocolParams (..)
3840
, MaxMajorProtVer (..)
@@ -518,17 +520,42 @@ instance CardanoHardForkConstraints c
518520
ProtocolInfo
519521
-------------------------------------------------------------------------------}
520522

523+
-- | When to trigger a hard fork to a Cardano era.
524+
data CardanoHardForkTrigger blk =
525+
-- | Trigger the hard fork when the ledger protocol version is updated to
526+
-- the default for that era (@'L.eraProtVerLow' \@('ShelleyBlockLedgerEra'
527+
-- blk)@). Also see 'TriggerHardForkAtVersion'.
528+
CardanoTriggerHardForkAtDefaultVersion
529+
|
530+
-- | Trigger the hard fork at the given epoch. For testing only. Also see
531+
-- 'TriggerHardForkAtEpoch'.
532+
CardanoTriggerHardForkAtEpoch EpochNo
533+
deriving stock (Show)
534+
535+
toTriggerHardFork ::
536+
forall blk. L.Era (ShelleyBlockLedgerEra blk)
537+
=> CardanoHardForkTrigger blk
538+
-> TriggerHardFork
539+
toTriggerHardFork = \case
540+
CardanoTriggerHardForkAtDefaultVersion ->
541+
TriggerHardForkAtVersion $
542+
SL.getVersion (L.eraProtVerLow @(ShelleyBlockLedgerEra blk))
543+
CardanoTriggerHardForkAtEpoch epochNo ->
544+
TriggerHardForkAtEpoch epochNo
545+
521546
newtype CardanoHardForkTriggers = CardanoHardForkTriggers {
522-
getCardanoHardForkTriggers :: NP (K TriggerHardFork) (CardanoShelleyEras StandardCrypto)
547+
getCardanoHardForkTriggers ::
548+
NP CardanoHardForkTrigger (CardanoShelleyEras StandardCrypto)
523549
}
524550

525551
pattern CardanoHardForkTriggers' ::
526-
TriggerHardFork
527-
-> TriggerHardFork
528-
-> TriggerHardFork
529-
-> TriggerHardFork
530-
-> TriggerHardFork
531-
-> TriggerHardFork
552+
(c ~ StandardCrypto)
553+
=> CardanoHardForkTrigger (ShelleyBlock (TPraos c) (ShelleyEra c))
554+
-> CardanoHardForkTrigger (ShelleyBlock (TPraos c) (AllegraEra c))
555+
-> CardanoHardForkTrigger (ShelleyBlock (TPraos c) (MaryEra c))
556+
-> CardanoHardForkTrigger (ShelleyBlock (TPraos c) (AlonzoEra c))
557+
-> CardanoHardForkTrigger (ShelleyBlock (Praos c) (BabbageEra c))
558+
-> CardanoHardForkTrigger (ShelleyBlock (Praos c) (ConwayEra c))
532559
-> CardanoHardForkTriggers
533560
pattern CardanoHardForkTriggers' {
534561
triggerHardForkShelley
@@ -539,12 +566,12 @@ pattern CardanoHardForkTriggers' {
539566
, triggerHardForkConway
540567
} =
541568
CardanoHardForkTriggers
542-
( K triggerHardForkShelley
543-
:* K triggerHardForkAllegra
544-
:* K triggerHardForkMary
545-
:* K triggerHardForkAlonzo
546-
:* K triggerHardForkBabbage
547-
:* K triggerHardForkConway
569+
( triggerHardForkShelley
570+
:* triggerHardForkAllegra
571+
:* triggerHardForkMary
572+
:* triggerHardForkAlonzo
573+
:* triggerHardForkBabbage
574+
:* triggerHardForkConway
548575
:* Nil
549576
)
550577
{-# COMPLETE CardanoHardForkTriggers' #-}
@@ -684,7 +711,7 @@ protocolInfoCardano paramsCardano
684711
partialLedgerConfigByron :: PartialLedgerConfig ByronBlock
685712
partialLedgerConfigByron = ByronPartialLedgerConfig {
686713
byronLedgerConfig = ledgerConfigByron
687-
, byronTriggerHardFork = triggerHardForkShelley
714+
, byronTriggerHardFork = toTriggerHardFork triggerHardForkShelley
688715
}
689716

690717
kByron :: SecurityParam
@@ -737,7 +764,7 @@ protocolInfoCardano paramsCardano
737764
partialLedgerConfigShelley =
738765
mkPartialLedgerConfigShelley
739766
transitionConfigShelley
740-
triggerHardForkAllegra
767+
(toTriggerHardFork triggerHardForkAllegra)
741768

742769
kShelley :: SecurityParam
743770
kShelley = SecurityParam $ sgSecurityParam genesisShelley
@@ -759,7 +786,7 @@ protocolInfoCardano paramsCardano
759786
partialLedgerConfigAllegra =
760787
mkPartialLedgerConfigShelley
761788
transitionConfigAllegra
762-
triggerHardForkMary
789+
(toTriggerHardFork triggerHardForkMary)
763790

764791
-- Mary
765792

@@ -778,7 +805,7 @@ protocolInfoCardano paramsCardano
778805
partialLedgerConfigMary =
779806
mkPartialLedgerConfigShelley
780807
transitionConfigMary
781-
triggerHardForkAlonzo
808+
(toTriggerHardFork triggerHardForkAlonzo)
782809

783810
-- Alonzo
784811

@@ -797,7 +824,7 @@ protocolInfoCardano paramsCardano
797824
partialLedgerConfigAlonzo =
798825
mkPartialLedgerConfigShelley
799826
transitionConfigAlonzo
800-
triggerHardForkBabbage
827+
(toTriggerHardFork triggerHardForkBabbage)
801828

802829
-- Babbage
803830

@@ -826,7 +853,7 @@ protocolInfoCardano paramsCardano
826853
partialLedgerConfigBabbage =
827854
mkPartialLedgerConfigShelley
828855
transitionConfigBabbage
829-
triggerHardForkConway
856+
(toTriggerHardFork triggerHardForkConway)
830857

831858
-- Conway
832859

ouroboros-consensus-cardano/src/unstable-cardano-testlib/Test/Consensus/Cardano/ProtocolInfo.hs

Lines changed: 31 additions & 67 deletions
Original file line numberDiff line numberDiff line change
@@ -1,7 +1,6 @@
11
{-# LANGUAGE DataKinds #-}
22
{-# LANGUAGE FlexibleContexts #-}
33
{-# LANGUAGE GADTs #-}
4-
{-# LANGUAGE NamedFieldPuns #-}
54
{-# LANGUAGE ScopedTypeVariables #-}
65
{-# LANGUAGE TypeApplications #-}
76
{-# LANGUAGE TypeOperators #-}
@@ -14,9 +13,8 @@ module Test.Consensus.Cardano.ProtocolInfo (
1413
, ShelleySlotLengthInSeconds (..)
1514
-- ** Hard-fork specification
1615
, Era (..)
17-
, HardForkSpec (..)
1816
, hardForkInto
19-
, stayInByron
17+
, hardForkOnDefaultProtocolVersions
2018
-- * ProtocolInfo elaboration
2119
, mkSimpleTestProtocolInfo
2220
, mkTestProtocolInfo
@@ -31,6 +29,7 @@ import qualified Cardano.Ledger.BaseTypes as SL
3129
import qualified Cardano.Protocol.TPraos.OCert as SL
3230
import qualified Cardano.Slotting.Time as Time
3331
import Data.Proxy (Proxy (..))
32+
import Data.SOP.Strict
3433
import Data.Word (Word64)
3534
import Ouroboros.Consensus.Block.Forging (BlockForging)
3635
import Ouroboros.Consensus.BlockchainTime (SlotLength)
@@ -39,9 +38,8 @@ import Ouroboros.Consensus.Byron.Node (ByronLeaderCredentials,
3938
byronPbftSignatureThreshold, byronSoftwareVersion)
4039
import Ouroboros.Consensus.Cardano.Block (CardanoBlock)
4140
import Ouroboros.Consensus.Cardano.Node (CardanoHardForkConstraints,
42-
CardanoHardForkTriggers (..), CardanoProtocolParams (..),
43-
TriggerHardFork (TriggerHardForkAtEpoch, TriggerHardForkNotDuringThisExecution),
44-
protocolInfoCardano)
41+
CardanoHardForkTrigger (..), CardanoHardForkTriggers (..),
42+
CardanoProtocolParams (..), protocolInfoCardano)
4543
import Ouroboros.Consensus.Config (emptyCheckpointsMap)
4644
import Ouroboros.Consensus.Config.SecurityParam (SecurityParam (..))
4745
import Ouroboros.Consensus.Node.ProtocolInfo (NumCoreNodes (..),
@@ -77,19 +75,6 @@ instance ToSlotLength ByronSlotLengthInSeconds where
7775
instance ToSlotLength ShelleySlotLengthInSeconds where
7876
toSlotLength (ShelleySlotLengthInSeconds n) = Time.slotLengthFromSec $ fromIntegral n
7977

80-
-- | This data structure is used to specify if and when hardforks should take
81-
-- place, and the version used at each era. See 'stayInByron' and 'hardForkInto'
82-
-- for examples.
83-
data HardForkSpec =
84-
HardForkSpec {
85-
shelleyHardForkSpec :: TriggerHardFork
86-
, allegraHardForkSpec :: TriggerHardFork
87-
, maryHardForkSpec :: TriggerHardFork
88-
, alonzoHardForkSpec :: TriggerHardFork
89-
, babbageHardForkSpec :: TriggerHardFork
90-
, conwayHardForkSpec :: TriggerHardFork
91-
}
92-
9378
data Era = Byron
9479
| Shelley
9580
| Allegra
@@ -99,52 +84,37 @@ data Era = Byron
9984
| Conway
10085
deriving (Show, Eq, Ord, Enum)
10186

102-
selectEra :: Era -> HardForkSpec -> TriggerHardFork
103-
selectEra Byron _ = error "Byron is the first era, therefore there is no hard fork spec."
104-
selectEra Shelley HardForkSpec { shelleyHardForkSpec } = shelleyHardForkSpec
105-
selectEra Allegra HardForkSpec { allegraHardForkSpec } = allegraHardForkSpec
106-
selectEra Mary HardForkSpec { maryHardForkSpec } = maryHardForkSpec
107-
selectEra Alonzo HardForkSpec { alonzoHardForkSpec } = alonzoHardForkSpec
108-
selectEra Babbage HardForkSpec { babbageHardForkSpec } = babbageHardForkSpec
109-
selectEra Conway HardForkSpec { conwayHardForkSpec } = conwayHardForkSpec
110-
111-
stayInByron :: HardForkSpec
112-
stayInByron =
113-
HardForkSpec {
114-
shelleyHardForkSpec = TriggerHardForkNotDuringThisExecution
115-
, allegraHardForkSpec = TriggerHardForkNotDuringThisExecution
116-
, maryHardForkSpec = TriggerHardForkNotDuringThisExecution
117-
, alonzoHardForkSpec = TriggerHardForkNotDuringThisExecution
118-
, babbageHardForkSpec = TriggerHardForkNotDuringThisExecution
119-
, conwayHardForkSpec = TriggerHardForkNotDuringThisExecution
120-
}
121-
12287
protocolVersionZero :: SL.ProtVer
12388
protocolVersionZero = SL.ProtVer versionZero 0
12489
where
12590
versionZero :: SL.Version
12691
versionZero = SL.natVersion @0
12792

128-
hardForkInto :: Era -> HardForkSpec
129-
hardForkInto Byron = stayInByron
93+
hardForkOnDefaultProtocolVersions :: CardanoHardForkTriggers
94+
hardForkOnDefaultProtocolVersions =
95+
CardanoHardForkTriggers
96+
$ hpure CardanoTriggerHardForkAtDefaultVersion
97+
98+
hardForkInto :: Era -> CardanoHardForkTriggers
99+
hardForkInto Byron = hardForkOnDefaultProtocolVersions
130100
hardForkInto Shelley =
131-
stayInByron
132-
{ shelleyHardForkSpec = TriggerHardForkAtEpoch 0 }
101+
hardForkOnDefaultProtocolVersions
102+
{ triggerHardForkShelley = CardanoTriggerHardForkAtEpoch 0 }
133103
hardForkInto Allegra =
134104
(hardForkInto Shelley)
135-
{ allegraHardForkSpec = TriggerHardForkAtEpoch 0 }
105+
{ triggerHardForkAllegra = CardanoTriggerHardForkAtEpoch 0 }
136106
hardForkInto Mary =
137107
(hardForkInto Allegra)
138-
{ maryHardForkSpec = TriggerHardForkAtEpoch 0 }
108+
{ triggerHardForkMary = CardanoTriggerHardForkAtEpoch 0 }
139109
hardForkInto Alonzo =
140110
(hardForkInto Mary)
141-
{ alonzoHardForkSpec = TriggerHardForkAtEpoch 0 }
111+
{ triggerHardForkAlonzo = CardanoTriggerHardForkAtEpoch 0 }
142112
hardForkInto Babbage =
143113
(hardForkInto Alonzo)
144-
{ babbageHardForkSpec = TriggerHardForkAtEpoch 0 }
114+
{ triggerHardForkBabbage = CardanoTriggerHardForkAtEpoch 0 }
145115
hardForkInto Conway =
146116
(hardForkInto Babbage)
147-
{ conwayHardForkSpec = TriggerHardForkAtEpoch 0 }
117+
{ triggerHardForkConway = CardanoTriggerHardForkAtEpoch 0 }
148118

149119
{-------------------------------------------------------------------------------
150120
ProtocolInfo elaboration
@@ -167,9 +137,10 @@ hardForkInto Conway =
167137
-- If you want to tweak the resulting protocol info further see
168138
-- 'mkTestProtocolInfo'.
169139
--
170-
-- The resulting 'ProtocolInfo' contains a ledger state. The 'HardForkSpec'
171-
-- parameter will determine to which era this ledger state belongs. See
172-
-- 'HardForkSpec' for more details on how to specify a value of this type.
140+
-- The resulting 'ProtocolInfo' contains a ledger state. The
141+
-- 'CardanoHardForkTriggers' parameter will determine to which era this ledger
142+
-- state belongs. See 'hardForkInto' and 'hardForkOnDefaultProtocolVersions' for
143+
-- more details on how to specify a value of this type.
173144
--
174145
mkSimpleTestProtocolInfo ::
175146
forall c
@@ -180,28 +151,28 @@ mkSimpleTestProtocolInfo ::
180151
-> ByronSlotLengthInSeconds
181152
-> ShelleySlotLengthInSeconds
182153
-> SL.ProtVer
183-
-> HardForkSpec
154+
-> CardanoHardForkTriggers
184155
-> ProtocolInfo (CardanoBlock c)
185156
mkSimpleTestProtocolInfo
186157
decentralizationParam
187158
securityParam
188159
byronSlotLenghtInSeconds
189160
shelleySlotLengthInSeconds
190161
protocolVersion
191-
hardForkSpec
162+
hardForkTriggers
192163
= fst
193164
$ mkTestProtocolInfo @IO
194165
(CoreNodeId 0, coreNodeShelley)
195166
shelleyGenesis
196-
byronProtocolVersion
167+
aByronProtocolVersion
197168
SL.NeutralNonce
198169
genesisByron
199170
generatedSecretsByron
200171
(Just $ PBftSignatureThreshold 1)
201172
protocolVersion
202-
hardForkSpec
173+
hardForkTriggers
203174
where
204-
byronProtocolVersion =
175+
aByronProtocolVersion =
205176
CC.Update.ProtocolVersion 0 0 0
206177

207178
coreNodeShelley = runGen initSeed $ Shelley.genCoreNode initialKESPeriod
@@ -258,8 +229,8 @@ mkTestProtocolInfo ::
258229
-> SL.ProtVer
259230
-- ^ See 'protocolInfoCardano' for the details of what is the
260231
-- relation between this version and any 'TriggerHardForkAtVersion'
261-
-- that __might__ appear in the 'HardForkSpec' parameter.
262-
-> HardForkSpec
232+
-- that __might__ appear in the 'CardanoHardForkTriggers' parameter.
233+
-> CardanoHardForkTriggers
263234
-- ^ Specification of the era to which the initial state should hard-fork to.
264235
-> (ProtocolInfo (CardanoBlock c), m [BlockForging m (CardanoBlock c)])
265236
mkTestProtocolInfo
@@ -271,7 +242,7 @@ mkTestProtocolInfo
271242
generatedSecretsByron
272243
aByronPbftSignatureThreshold
273244
protocolVersion
274-
hardForkSpec
245+
hardForkTriggers
275246
=
276247
protocolInfoCardano
277248
(CardanoProtocolParams
@@ -286,14 +257,7 @@ mkTestProtocolInfo
286257
shelleyBasedInitialNonce = initialNonce
287258
, shelleyBasedLeaderCredentials = [leaderCredentialsShelley]
288259
}
289-
CardanoHardForkTriggers' {
290-
triggerHardForkShelley = selectEra Shelley hardForkSpec
291-
, triggerHardForkAllegra = selectEra Allegra hardForkSpec
292-
, triggerHardForkMary = selectEra Mary hardForkSpec
293-
, triggerHardForkAlonzo = selectEra Alonzo hardForkSpec
294-
, triggerHardForkBabbage = selectEra Babbage hardForkSpec
295-
, triggerHardForkConway = selectEra Conway hardForkSpec
296-
}
260+
hardForkTriggers
297261
( L.mkLatestTransitionConfig
298262
shelleyGenesis
299263
-- These example genesis objects might need to become more

0 commit comments

Comments
 (0)