Skip to content

Commit e477ed0

Browse files
committed
Remove legacy HardForkSpecificNodeToClientVersions
1 parent a368da1 commit e477ed0

File tree

10 files changed

+41
-87
lines changed

10 files changed

+41
-87
lines changed

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

Lines changed: 4 additions & 6 deletions
Original file line numberDiff line numberDiff line change
@@ -291,11 +291,11 @@ instance CardanoHardForkConstraints c
291291
--
292292
-- PRECONDITION: 'supportedNodeToClientVersions' must include a version that
293293
-- satisfies this condition.
294-
genWithHardForkSpecificNodeToClientVersion ::
294+
_genWithHardForkSpecificNodeToClientVersion ::
295295
forall c. CardanoHardForkConstraints c
296296
=> (HardForkSpecificNodeToClientVersion -> Bool)
297297
-> Gen (HardForkNodeToClientVersion (CardanoEras c))
298-
genWithHardForkSpecificNodeToClientVersion p =
298+
_genWithHardForkSpecificNodeToClientVersion p =
299299
elements
300300
. filter p'
301301
. Map.elems
@@ -488,8 +488,7 @@ instance CardanoHardForkConstraints c
488488
arbitrary = frequency
489489
[ (1, do version <- getHardForkEnabledNodeToClientVersion <$> arbitrary
490490
return $ WithVersion version (Some GetInterpreter))
491-
, (1, do version <- genWithHardForkSpecificNodeToClientVersion
492-
(>= HardForkSpecificNodeToClientVersion2)
491+
, (1, do version <- getHardForkEnabledNodeToClientVersion <$> arbitrary
493492
return $ WithVersion version (Some GetCurrentEra))
494493
]
495494

@@ -700,8 +699,7 @@ instance c ~ MockCryptoCompatByron
700699
(SomeResult (CardanoBlock c)))
701700
genQueryHardForkResult = oneof
702701
[ WithVersion
703-
<$> genWithHardForkSpecificNodeToClientVersion
704-
(>= HardForkSpecificNodeToClientVersion3)
702+
<$> (getHardForkEnabledNodeToClientVersion <$> arbitrary)
705703
<*> (SomeResult (QueryHardFork GetInterpreter) <$> arbitrary)
706704
, WithVersion
707705
<$> (getHardForkEnabledNodeToClientVersion <$> arbitrary)

ouroboros-consensus-cardano/src/unstable-cardano-testlib/Test/ThreadNet/Infra/ShelleyBasedHardFork.hs

Lines changed: 12 additions & 2 deletions
Original file line numberDiff line numberDiff line change
@@ -100,12 +100,17 @@ pattern ShelleyBasedHardForkNodeToNodeVersionMax ::
100100
BlockNodeToNodeVersion (ShelleyBasedHardForkBlock proto1 era1 proto2 era2)
101101
pattern ShelleyBasedHardForkNodeToNodeVersionMax =
102102
HardForkNodeToNodeEnabled
103-
HardForkSpecificNodeToNodeVersion1
103+
HardForkSpecificNodeToNodeVersionMax
104104
( WrapNodeToNodeVersion ShelleyNodeToNodeVersionMax
105105
:* WrapNodeToNodeVersion ShelleyNodeToNodeVersionMax
106106
:* Nil
107107
)
108108

109+
pattern HardForkSpecificNodeToNodeVersionMax :: HardForkSpecificNodeToNodeVersion
110+
pattern HardForkSpecificNodeToNodeVersionMax <- ((== maxBound) -> True)
111+
where
112+
HardForkSpecificNodeToNodeVersionMax = maxBound
113+
109114
pattern ShelleyNodeToNodeVersionMax :: ShelleyNodeToNodeVersion
110115
pattern ShelleyNodeToNodeVersionMax <- ((== maxBound) -> True)
111116
where
@@ -115,12 +120,17 @@ pattern ShelleyBasedHardForkNodeToClientVersionMax ::
115120
BlockNodeToClientVersion (ShelleyBasedHardForkBlock proto1 era1 proto2 era2)
116121
pattern ShelleyBasedHardForkNodeToClientVersionMax =
117122
HardForkNodeToClientEnabled
118-
HardForkSpecificNodeToClientVersion2
123+
HardForkSpecificNodeToClientVersionMax
119124
( EraNodeToClientEnabled ShelleyNodeToClientVersionMax
120125
:* EraNodeToClientEnabled ShelleyNodeToClientVersionMax
121126
:* Nil
122127
)
123128

129+
pattern HardForkSpecificNodeToClientVersionMax :: HardForkSpecificNodeToClientVersion
130+
pattern HardForkSpecificNodeToClientVersionMax <- ((== maxBound) -> True)
131+
where
132+
HardForkSpecificNodeToClientVersionMax = maxBound
133+
124134
pattern ShelleyNodeToClientVersionMax :: ShelleyNodeToClientVersion
125135
pattern ShelleyNodeToClientVersionMax <- ((== maxBound) -> True)
126136
where
Lines changed: 3 additions & 0 deletions
Original file line numberDiff line numberDiff line change
@@ -0,0 +1,3 @@
1+
### Breaking
2+
3+
- Removed legacy `HardForkSpecificNodeToClientVersion`s and related code.

ouroboros-consensus/ouroboros-consensus.cabal

Lines changed: 0 additions & 1 deletion
Original file line numberDiff line numberDiff line change
@@ -301,7 +301,6 @@ library
301301
psqueues ^>=0.2.3,
302302
quiet ^>=0.2,
303303
rawlock ^>=0.1,
304-
reflection,
305304
resource-registry ^>=0.1,
306305
semialign >=1.1,
307306
serialise ^>=0.2,

ouroboros-consensus/src/ouroboros-consensus/Ouroboros/Consensus/HardFork/Combinator/Ledger/Query.hs

Lines changed: 6 additions & 11 deletions
Original file line numberDiff line numberDiff line change
@@ -41,7 +41,6 @@ import Data.Bifunctor
4141
import Data.Functor.Product
4242
import Data.Kind (Type)
4343
import Data.Proxy
44-
import Data.Reflection (give)
4544
import Data.SOP.BasicFunctors
4645
import Data.SOP.Constraint
4746
import Data.SOP.Counting (getExactly)
@@ -65,8 +64,6 @@ import qualified Ouroboros.Consensus.HardFork.Combinator.State as State
6564
import Ouroboros.Consensus.HardFork.History (Bound (..), EraParams,
6665
Shape (..))
6766
import qualified Ouroboros.Consensus.HardFork.History as History
68-
import Ouroboros.Consensus.HardFork.History.EraParams
69-
(EraParamsFormat (..))
7067
import Ouroboros.Consensus.HeaderValidation
7168
import Ouroboros.Consensus.Ledger.Extended
7269
import Ouroboros.Consensus.Ledger.Query
@@ -366,18 +363,16 @@ decodeQueryAnytimeResult GetEraStart = decode
366363

367364
encodeQueryHardForkResult ::
368365
SListI xs
369-
=> EraParamsFormat
370-
-> QueryHardFork xs result -> result -> Encoding
371-
encodeQueryHardForkResult epf = \case
372-
GetInterpreter -> give epf encode
366+
=> QueryHardFork xs result -> result -> Encoding
367+
encodeQueryHardForkResult = \case
368+
GetInterpreter -> encode
373369
GetCurrentEra -> encode
374370

375371
decodeQueryHardForkResult ::
376372
SListI xs
377-
=> EraParamsFormat
378-
-> QueryHardFork xs result -> forall s. Decoder s result
379-
decodeQueryHardForkResult epf = \case
380-
GetInterpreter -> give epf decode
373+
=> QueryHardFork xs result -> forall s. Decoder s result
374+
decodeQueryHardForkResult = \case
375+
GetInterpreter -> decode
381376
GetCurrentEra -> decode
382377

383378
{-------------------------------------------------------------------------------

ouroboros-consensus/src/ouroboros-consensus/Ouroboros/Consensus/HardFork/Combinator/Serialisation/Common.hs

Lines changed: 1 addition & 6 deletions
Original file line numberDiff line numberDiff line change
@@ -140,13 +140,8 @@ data HardForkSpecificNodeToNodeVersion =
140140
-- | Versioning of the specific additions made by the HFC to the @NodeToClient@
141141
-- protocols, e.g., the era tag or the hard-fork specific queries.
142142
data HardForkSpecificNodeToClientVersion =
143-
HardForkSpecificNodeToClientVersion1
144-
145-
-- | Enable the 'GetCurrentEra' query in 'QueryHardFork'.
146-
| HardForkSpecificNodeToClientVersion2
147-
148143
-- | Include the Genesis window in 'EraParams'.
149-
| HardForkSpecificNodeToClientVersion3
144+
HardForkSpecificNodeToClientVersion3
150145
deriving (Eq, Ord, Show, Enum, Bounded)
151146

152147
data HardForkNodeToNodeVersion xs where

ouroboros-consensus/src/ouroboros-consensus/Ouroboros/Consensus/HardFork/Combinator/Serialisation/SerialiseNodeToClient.hs

Lines changed: 6 additions & 21 deletions
Original file line numberDiff line numberDiff line change
@@ -37,7 +37,6 @@ import Ouroboros.Consensus.HardFork.Combinator.Ledger.Query
3737
import Ouroboros.Consensus.HardFork.Combinator.Mempool
3838
import Ouroboros.Consensus.HardFork.Combinator.Serialisation.Common
3939
import Ouroboros.Consensus.HardFork.Combinator.Serialisation.SerialiseDisk ()
40-
import Ouroboros.Consensus.HardFork.History (EraParamsFormat (..))
4140
import Ouroboros.Consensus.Ledger.SupportsMempool (GenTxId)
4241
import Ouroboros.Consensus.Node.NetworkProtocolVersion
4342
import Ouroboros.Consensus.Node.Run
@@ -185,15 +184,12 @@ encodeQueryHardFork ::
185184
HardForkSpecificNodeToClientVersion
186185
-> Some (QueryHardFork xs)
187186
-> Encoding
188-
encodeQueryHardFork vHfc = \case
187+
encodeQueryHardFork _vHfc = \case
189188
Some GetInterpreter -> mconcat [
190189
Enc.encodeListLen 1
191190
, Enc.encodeWord8 0
192191
]
193-
Some GetCurrentEra
194-
| vHfc < HardForkSpecificNodeToClientVersion2 ->
195-
throw HardForkEncoderQueryWrongVersion
196-
| otherwise -> mconcat [
192+
Some GetCurrentEra -> mconcat [
197193
Enc.encodeListLen 1
198194
, Enc.encodeWord8 1
199195
]
@@ -296,10 +292,8 @@ instance SerialiseHFC xs
296292
where
297293
ccfgs = getPerEraCodecConfig $ hardForkCodecConfigPerEra ccfg
298294

299-
encodeResult _ _ (QueryAnytime qry _) = encodeQueryAnytimeResult qry
300-
encodeResult _ version (QueryHardFork qry) = encodeQueryHardForkResult epf qry
301-
where
302-
epf = eraParamsFormatFromVersion version
295+
encodeResult _ _ (QueryAnytime qry _) = encodeQueryAnytimeResult qry
296+
encodeResult _ _ (QueryHardFork qry) = encodeQueryHardForkResult qry
303297

304298
decodeResult ccfg version (QueryIfCurrent qry) =
305299
case isNonEmpty (Proxy @xs) of
@@ -315,17 +309,8 @@ instance SerialiseHFC xs
315309
where
316310
ccfgs = getPerEraCodecConfig $ hardForkCodecConfigPerEra ccfg
317311

318-
decodeResult _ _ (QueryAnytime qry _) = decodeQueryAnytimeResult qry
319-
decodeResult _ version (QueryHardFork qry) = decodeQueryHardForkResult epf qry
320-
where
321-
epf = eraParamsFormatFromVersion version
322-
323-
eraParamsFormatFromVersion :: HardForkNodeToClientVersion xs -> EraParamsFormat
324-
eraParamsFormatFromVersion = \case
325-
HardForkNodeToClientDisabled _ -> throw HardForkEncoderQueryHfcDisabled
326-
HardForkNodeToClientEnabled v _
327-
| v >= HardForkSpecificNodeToClientVersion3 -> EraParamsWithGenesisWindow
328-
| otherwise -> EraParamsWithoutGenesisWindow
312+
decodeResult _ _ (QueryAnytime qry _) = decodeQueryAnytimeResult qry
313+
decodeResult _ _ (QueryHardFork qry) = decodeQueryHardForkResult qry
329314

330315
encodeQueryIfCurrentResult ::
331316
All SerialiseConstraintsHFC xs

ouroboros-consensus/src/ouroboros-consensus/Ouroboros/Consensus/HardFork/History/EraParams.hs

Lines changed: 6 additions & 35 deletions
Original file line numberDiff line numberDiff line change
@@ -2,7 +2,6 @@
22
{-# LANGUAGE DeriveGeneric #-}
33
{-# LANGUAGE DerivingStrategies #-}
44
{-# LANGUAGE FlexibleContexts #-}
5-
{-# LANGUAGE InstanceSigs #-}
65
{-# LANGUAGE LambdaCase #-}
76
{-# LANGUAGE OverloadedStrings #-}
87
{-# LANGUAGE RecordWildCards #-}
@@ -15,16 +14,13 @@ module Ouroboros.Consensus.HardFork.History.EraParams (
1514
, SafeZone (..)
1615
-- * Defaults
1716
, defaultEraParams
18-
-- * Serialisation
19-
, EraParamsFormat (..)
2017
) where
2118

2219
import Cardano.Binary (enforceSize)
2320
import Codec.CBOR.Decoding (Decoder, decodeListLen, decodeWord8)
2421
import Codec.CBOR.Encoding (Encoding, encodeListLen, encodeWord8)
2522
import Codec.Serialise (Serialise (..))
2623
import Control.Monad (void)
27-
import Data.Reflection (Given (..))
2824
import Data.Word
2925
import GHC.Generics (Generic)
3026
import NoThunks.Class (NoThunks)
@@ -233,44 +229,19 @@ decodeSafeBeforeEpoch = do
233229
(2, 1) -> void $ decode @EpochNo
234230
_ -> fail $ "SafeBeforeEpoch: invalid size and tag " <> show (size, tag)
235231

236-
-- | Older versions are not aware of the Genesis window as part of 'EraParams',
237-
-- so we need to stay backwards-compatible for now. This type can be removed
238-
-- once mainnet is in Conway (as we can then always use the behavior of
239-
-- 'EraParamsWithGenesisWindow').
240-
data EraParamsFormat =
241-
EraParamsWithoutGenesisWindow
242-
| EraParamsWithGenesisWindow
243-
deriving stock (Show, Eq)
244-
245-
instance Given EraParamsFormat => Serialise EraParams where
232+
instance Serialise EraParams where
246233
encode EraParams{..} = mconcat $ [
247-
encodeListLen $ case epf of
248-
EraParamsWithoutGenesisWindow -> 3
249-
EraParamsWithGenesisWindow -> 4
234+
encodeListLen 4
250235
, encode (unEpochSize eraEpochSize)
251236
, encode eraSlotLength
252237
, encode eraSafeZone
253-
] <> case epf of
254-
EraParamsWithoutGenesisWindow -> []
255-
EraParamsWithGenesisWindow ->
256-
[encode (unGenesisWindow eraGenesisWin)]
257-
where
258-
epf :: EraParamsFormat
259-
epf = given
238+
, encode (unGenesisWindow eraGenesisWin)
239+
]
260240

261241
decode = do
262-
enforceSize "EraParams" $ case epf of
263-
EraParamsWithoutGenesisWindow -> 3
264-
EraParamsWithGenesisWindow -> 4
242+
enforceSize "EraParams" 4
265243
eraEpochSize <- EpochSize <$> decode
266244
eraSlotLength <- decode
267245
eraSafeZone <- decode
268-
eraGenesisWin <- GenesisWindow <$> case epf of
269-
-- Note that only the client will ever decode 'EraParams', as part of the
270-
-- 'GetInterpreter' query.
271-
EraParamsWithoutGenesisWindow -> pure 0
272-
EraParamsWithGenesisWindow -> decode
246+
eraGenesisWin <- GenesisWindow <$> decode
273247
return EraParams{..}
274-
where
275-
epf :: EraParamsFormat
276-
epf = given

ouroboros-consensus/src/ouroboros-consensus/Ouroboros/Consensus/HardFork/History/Qry.hs

Lines changed: 1 addition & 2 deletions
Original file line numberDiff line numberDiff line change
@@ -49,7 +49,6 @@ import Data.Fixed (divMod')
4949
import Data.Foldable (toList)
5050
import Data.Functor.Identity
5151
import Data.Kind (Type)
52-
import Data.Reflection (Given)
5352
import Data.SOP.NonEmpty (NonEmpty (..))
5453
import Data.SOP.Sing (SListI)
5554
import Data.Time hiding (UTCTime)
@@ -423,7 +422,7 @@ runQueryPure q = either throw id . runQuery q
423422
newtype Interpreter xs = Interpreter (Summary xs)
424423
deriving (Eq)
425424

426-
deriving instance (SListI xs, Given EraParamsFormat) => Serialise (Interpreter xs)
425+
deriving instance SListI xs => Serialise (Interpreter xs)
427426

428427
instance Show (Interpreter xs) where
429428
show _ = "<Interpreter>"

ouroboros-consensus/src/ouroboros-consensus/Ouroboros/Consensus/HardFork/History/Summary.hs

Lines changed: 2 additions & 3 deletions
Original file line numberDiff line numberDiff line change
@@ -53,7 +53,6 @@ import Data.Bifunctor
5353
import Data.Foldable (toList)
5454
import Data.Kind (Type)
5555
import Data.Proxy
56-
import Data.Reflection (Given)
5756
import Data.SOP.Counting
5857
import Data.SOP.NonEmpty
5958
import Data.SOP.Sing (SListI, lengthSList)
@@ -474,7 +473,7 @@ instance Serialise EraEnd where
474473
return EraUnbounded
475474
_ -> EraEnd <$> decode
476475

477-
instance Given EraParamsFormat => Serialise EraSummary where
476+
instance Serialise EraSummary where
478477
encode EraSummary{..} = mconcat [
479478
encodeListLen 3
480479
, encode eraStart
@@ -489,7 +488,7 @@ instance Given EraParamsFormat => Serialise EraSummary where
489488
eraParams <- decode
490489
return EraSummary{..}
491490

492-
instance (SListI xs, Given EraParamsFormat) => Serialise (Summary xs) where
491+
instance SListI xs => Serialise (Summary xs) where
493492
encode (Summary eraSummaries) = encode (toList eraSummaries)
494493

495494
-- @xs@ is the list of eras that is statically known to us; the server has a

0 commit comments

Comments
 (0)