Skip to content

Commit 483e931

Browse files
committed
consensus: remove the ref script mempool hotfix
1 parent adc3474 commit 483e931

File tree

16 files changed

+11
-191
lines changed

16 files changed

+11
-191
lines changed

ouroboros-consensus-cardano/src/byron/Ouroboros/Consensus/Byron/Ledger/Mempool.hs

Lines changed: 0 additions & 2 deletions
Original file line numberDiff line numberDiff line change
@@ -143,8 +143,6 @@ instance LedgerSupportsMempool ByronBlock where
143143

144144
txForgetValidated = forgetValidatedByronTx
145145

146-
txRefScriptSize _ _ _ = 0
147-
148146
data instance TxId (GenTx ByronBlock)
149147
= ByronTxId !Utxo.TxId
150148
| ByronDlgId !Delegation.CertificateId

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

Lines changed: 1 addition & 85 deletions
Original file line numberDiff line numberDiff line change
@@ -5,7 +5,6 @@
55
{-# LANGUAGE GADTs #-}
66
{-# LANGUAGE LambdaCase #-}
77
{-# LANGUAGE MultiParamTypeClasses #-}
8-
{-# LANGUAGE NumericUnderscores #-}
98
{-# LANGUAGE ScopedTypeVariables #-}
109
{-# LANGUAGE TypeApplications #-}
1110
{-# LANGUAGE TypeFamilies #-}
@@ -29,7 +28,6 @@ module Ouroboros.Consensus.Shelley.Eras (
2928
, StandardMary
3029
, StandardShelley
3130
-- * Shelley-based era
32-
, BabbageTxDict (..)
3331
, ConwayEraGovDict (..)
3432
, ShelleyBasedEra (..)
3533
, WrapTx (..)
@@ -47,7 +45,6 @@ import Cardano.Ledger.Alonzo (AlonzoEra)
4745
import qualified Cardano.Ledger.Alonzo.Rules as Alonzo
4846
import qualified Cardano.Ledger.Alonzo.Translation as Alonzo
4947
import qualified Cardano.Ledger.Alonzo.Tx as Alonzo
50-
import qualified Cardano.Ledger.Api as SL
5148
import qualified Cardano.Ledger.Api.Era as L
5249
import Cardano.Ledger.Babbage (BabbageEra)
5350
import qualified Cardano.Ledger.Babbage.Rules as Babbage
@@ -60,8 +57,6 @@ import qualified Cardano.Ledger.Conway.Rules as Conway
6057
import qualified Cardano.Ledger.Conway.Rules as SL
6158
(ConwayLedgerPredFailure (..))
6259
import qualified Cardano.Ledger.Conway.Translation as Conway
63-
import qualified Cardano.Ledger.Conway.Tx as SL
64-
import qualified Cardano.Ledger.Conway.UTxO as SL
6560
import Cardano.Ledger.Core as Core
6661
import Cardano.Ledger.Crypto (StandardCrypto)
6762
import Cardano.Ledger.Keys (DSignable, Hash)
@@ -73,13 +68,11 @@ import Cardano.Ledger.Shelley.Core as Core
7368
import qualified Cardano.Ledger.Shelley.LedgerState as SL
7469
import qualified Cardano.Ledger.Shelley.Rules as SL
7570
import qualified Cardano.Ledger.Shelley.Transition as SL
76-
import qualified Cardano.Ledger.Val as SL
7771
import qualified Cardano.Protocol.TPraos.API as SL
7872
import Control.Monad.Except
7973
import Control.State.Transition (PredicateFailure)
8074
import Data.Data (Proxy (Proxy))
8175
import Data.List.NonEmpty (NonEmpty ((:|)))
82-
import Lens.Micro ((^.))
8376
import NoThunks.Class (NoThunks)
8477
import Ouroboros.Consensus.Ledger.SupportsMempool
8578
(WhetherToIntervene (..))
@@ -169,16 +162,6 @@ class ( Core.EraSegWits era
169162
-- | Whether the era has an instance of 'CG.ConwayEraGov'
170163
getConwayEraGovDict :: proxy era -> Maybe (ConwayEraGovDict era)
171164

172-
getBabbageTxDict :: proxy era -> Maybe (BabbageTxDict era)
173-
174-
data BabbageTxDict era where
175-
BabbageTxDict ::
176-
SL.BabbageEraTxBody era
177-
=> (Integer -> Integer -> SL.ApplyTxError era)
178-
-- ^ Construct an arbitrary ledger error with two integers as its
179-
-- payload.
180-
-> BabbageTxDict era
181-
182165
data ConwayEraGovDict era where
183166
ConwayEraGovDict :: CG.ConwayEraGov era => ConwayEraGovDict era
184167

@@ -189,7 +172,7 @@ isBeforeConway _ =
189172
-- | The default implementation of 'applyShelleyBasedTx', a thin wrapper around
190173
-- 'SL.applyTx'
191174
defaultApplyShelleyBasedTx ::
192-
forall era. ShelleyBasedEra era
175+
ShelleyBasedEra era
193176
=> SL.Globals
194177
-> SL.LedgerEnv era
195178
-> SL.LedgerState era
@@ -201,55 +184,11 @@ defaultApplyShelleyBasedTx ::
201184
, SL.Validated (Core.Tx era)
202185
)
203186
defaultApplyShelleyBasedTx globals ledgerEnv mempoolState _wti tx = do
204-
refScriptPredicate
205187
SL.applyTx
206188
globals
207189
ledgerEnv
208190
mempoolState
209191
tx
210-
where
211-
refScriptPredicate = case getBabbageTxDict (Proxy @era) of
212-
Nothing -> pure ()
213-
Just (BabbageTxDict mkError)
214-
-- The ledger rules of Conway (and later eras) already handle ref
215-
-- scripts appropriately, so we only need to perform the checks below
216-
-- for Babbage.
217-
| not $ isBeforeConway (Proxy @era)
218-
-> pure ()
219-
-- Reject it if it has more than 100 kibibytes of ref script.
220-
| refScriptsSize > totalRefScriptsSizeLimit
221-
-> throwError $ mkError
222-
-- As we are reusing an existing error message, we add a large
223-
-- number to make users running into this are productively irritated
224-
-- and post this error message somewhere where they can receive
225-
-- help/context.
226-
(toInteger refScriptsSize + 1_000_000_000)
227-
(toInteger totalRefScriptsSizeLimit + 1_000_000_000)
228-
-- Reject it if it has more than 50 kibibytes of ref script and does not
229-
-- satisfy an additional fee as calculated in the table below.
230-
| refScriptsSize > freeOfChargeRefScriptsBytes
231-
, actualFee < expectedFee
232-
-> throwError $ mkError
233-
-- See above for why we add a large constant.
234-
(SL.unCoin actualFee + 100_000_000)
235-
(SL.unCoin expectedFee + 100_000_000)
236-
| otherwise -> pure ()
237-
where
238-
totalRefScriptsSizeLimit :: Int
239-
totalRefScriptsSizeLimit = 100 * 1024
240-
241-
freeOfChargeRefScriptsBytes :: Int
242-
freeOfChargeRefScriptsBytes = 50 * 1024
243-
244-
actualFee = tx ^. SL.bodyTxL . SL.feeTxBodyL
245-
expectedFee = minFee SL.<+> refScriptsFee
246-
where
247-
minFee = SL.getMinFeeTx (SL.ledgerPp ledgerEnv) tx 0
248-
refScriptsFee = SL.tierRefScriptFee 1.2 25600 15 refScriptsSize
249-
250-
refScriptsSize = SL.txNonDistinctRefScriptsSize utxo tx
251-
252-
utxo = SL.utxosUtxo . SL.lsUTxOState $ mempoolState
253192

254193
defaultGetConwayEraGovDict :: proxy era -> Maybe (ConwayEraGovDict era)
255194
defaultGetConwayEraGovDict _ = Nothing
@@ -260,57 +199,34 @@ instance (SL.PraosCrypto c, DSignable c (Hash c EraIndependentTxBody))
260199

261200
getConwayEraGovDict = defaultGetConwayEraGovDict
262201

263-
getBabbageTxDict _ = Nothing
264-
265202
instance (SL.PraosCrypto c, DSignable c (Hash c EraIndependentTxBody))
266203
=> ShelleyBasedEra (AllegraEra c) where
267204
applyShelleyBasedTx = defaultApplyShelleyBasedTx
268205

269206
getConwayEraGovDict = defaultGetConwayEraGovDict
270207

271-
getBabbageTxDict _ = Nothing
272-
273208
instance (SL.PraosCrypto c, DSignable c (Hash c EraIndependentTxBody))
274209
=> ShelleyBasedEra (MaryEra c) where
275210
applyShelleyBasedTx = defaultApplyShelleyBasedTx
276211

277212
getConwayEraGovDict = defaultGetConwayEraGovDict
278213

279-
getBabbageTxDict _ = Nothing
280-
281214
instance (SL.PraosCrypto c, DSignable c (Hash c EraIndependentTxBody))
282215
=> ShelleyBasedEra (AlonzoEra c) where
283216
applyShelleyBasedTx = applyAlonzoBasedTx
284217

285218
getConwayEraGovDict = defaultGetConwayEraGovDict
286219

287-
getBabbageTxDict _ = Nothing
288-
289220
instance (Praos.PraosCrypto c) => ShelleyBasedEra (BabbageEra c) where
290221
applyShelleyBasedTx = applyAlonzoBasedTx
291222

292223
getConwayEraGovDict = defaultGetConwayEraGovDict
293224

294-
getBabbageTxDict _ = Just $ BabbageTxDict $ \a b ->
295-
SL.ApplyTxError
296-
$ pure
297-
$ SL.UtxowFailure
298-
$ Babbage.UtxoFailure
299-
$ Babbage.AlonzoInBabbageUtxoPredFailure
300-
$ Alonzo.MaxTxSizeUTxO a b
301-
302225
instance (Praos.PraosCrypto c) => ShelleyBasedEra (ConwayEra c) where
303226
applyShelleyBasedTx = applyAlonzoBasedTx
304227

305228
getConwayEraGovDict _ = Just ConwayEraGovDict
306229

307-
getBabbageTxDict _ = Just $ BabbageTxDict $ \a b ->
308-
SL.ApplyTxError
309-
$ pure
310-
$ Conway.ConwayUtxowFailure
311-
$ Conway.UtxoFailure
312-
$ Conway.MaxTxSizeUTxO a b
313-
314230
applyAlonzoBasedTx :: forall era.
315231
( ShelleyBasedEra era,
316232
SupportsTwoPhaseValidation era,

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

Lines changed: 0 additions & 6 deletions
Original file line numberDiff line numberDiff line change
@@ -149,12 +149,6 @@ instance ShelleyCompatible proto era
149149

150150
txForgetValidated (ShelleyValidatedTx txid vtx) = ShelleyTx txid (SL.extractTx vtx)
151151

152-
txRefScriptSize _cfg st (ShelleyTx _ tx) = case getBabbageTxDict (Proxy @era) of
153-
Nothing -> 0
154-
Just BabbageTxDict{} -> SL.txNonDistinctRefScriptsSize utxo tx
155-
where
156-
utxo = SL.getUTxO . tickedShelleyLedgerState $ st
157-
158152
mkShelleyTx :: forall era proto. ShelleyBasedEra era => Tx era -> GenTx (ShelleyBlock proto era)
159153
mkShelleyTx tx = ShelleyTx (SL.txIdTxBody @era (tx ^. bodyTxL)) tx
160154

ouroboros-consensus-cardano/src/unstable-byronspec/Ouroboros/Consensus/ByronSpec/Ledger/Mempool.hs

Lines changed: 0 additions & 2 deletions
Original file line numberDiff line numberDiff line change
@@ -56,5 +56,3 @@ instance LedgerSupportsMempool ByronSpecBlock where
5656
txInBlockSize = const 0
5757

5858
txForgetValidated = forgetValidatedByronSpecGenTx
59-
60-
txRefScriptSize _cfg _tlst _tx = 0

ouroboros-consensus-diffusion/test/consensus-test/Test/Consensus/HardFork/Combinator/A.hs

Lines changed: 0 additions & 2 deletions
Original file line numberDiff line numberDiff line change
@@ -331,8 +331,6 @@ instance LedgerSupportsMempool BlockA where
331331

332332
txForgetValidated = forgetValidatedGenTxA
333333

334-
txRefScriptSize _cfg _tlst _tx = 0
335-
336334
newtype instance TxId (GenTx BlockA) = TxIdA Int
337335
deriving stock (Show, Eq, Ord, Generic)
338336
deriving newtype (NoThunks, Serialise)

ouroboros-consensus-diffusion/test/consensus-test/Test/Consensus/HardFork/Combinator/B.hs

Lines changed: 0 additions & 2 deletions
Original file line numberDiff line numberDiff line change
@@ -267,8 +267,6 @@ instance LedgerSupportsMempool BlockB where
267267

268268
txForgetValidated = \case {}
269269

270-
txRefScriptSize _cfg _tlst _tx = 0
271-
272270
data instance TxId (GenTx BlockB)
273271
deriving stock (Show, Eq, Ord, Generic)
274272
deriving anyclass (NoThunks, Serialise)

ouroboros-consensus/bench/mempool-bench/Bench/Consensus/Mempool/TestBlock.hs

Lines changed: 0 additions & 2 deletions
Original file line numberDiff line numberDiff line change
@@ -152,8 +152,6 @@ instance Ledger.LedgerSupportsMempool TestBlock where
152152

153153
txForgetValidated (ValidatedGenTx tx) = tx
154154

155-
txRefScriptSize _cfg _tlst _tx = 0
156-
157155
newtype instance Ledger.TxId (Ledger.GenTx TestBlock) = TestBlockTxId Tx
158156
deriving stock (Generic)
159157
deriving newtype (Show, Ord, Eq)

ouroboros-consensus/src/ouroboros-consensus/Ouroboros/Consensus/HardFork/Combinator/Mempool.hs

Lines changed: 0 additions & 35 deletions
Original file line numberDiff line numberDiff line change
@@ -5,7 +5,6 @@
55
{-# LANGUAGE FlexibleContexts #-}
66
{-# LANGUAGE FlexibleInstances #-}
77
{-# LANGUAGE GADTs #-}
8-
{-# LANGUAGE NamedFieldPuns #-}
98
{-# LANGUAGE RankNTypes #-}
109
{-# LANGUAGE RecordWildCards #-}
1110
{-# LANGUAGE ScopedTypeVariables #-}
@@ -125,40 +124,6 @@ instance CanHardFork xs => LedgerSupportsMempool (HardForkBlock xs) where
125124
. getOneEraValidatedGenTx
126125
. getHardForkValidatedGenTx
127126

128-
txRefScriptSize cfg st tx = case matchPolyTx injs tx' hardForkState of
129-
Left {} ->
130-
-- This is ugly/adhoc, but fine, as in the mempool, we only call
131-
-- txRefScriptSize after applyTx (which internall also calls
132-
-- matchPolyTx), so this case is unreachable.
133-
0
134-
Right matched ->
135-
hcollapse
136-
$ hczipWith proxySingle
137-
(\(WrapLedgerConfig eraCfg) (Pair eraTx (Comp eraSt)) ->
138-
K $ txRefScriptSize eraCfg eraSt eraTx)
139-
cfgs
140-
(State.tip matched)
141-
where
142-
HardForkLedgerConfig {
143-
hardForkLedgerConfigPerEra
144-
, hardForkLedgerConfigShape
145-
} = cfg
146-
TickedHardForkLedgerState transition hardForkState = st
147-
tx' = getOneEraGenTx . getHardForkGenTx $ tx
148-
149-
pcfgs = getPerEraLedgerConfig hardForkLedgerConfigPerEra
150-
cfgs = hcmap proxySingle (completeLedgerConfig'' ei) pcfgs
151-
ei = State.epochInfoPrecomputedTransitionInfo
152-
hardForkLedgerConfigShape
153-
transition
154-
hardForkState
155-
156-
injs :: InPairs (InjectPolyTx GenTx) xs
157-
injs =
158-
InPairs.hmap
159-
(\(Pair2 injTx _injValidatedTx) -> injTx)
160-
(InPairs.requiringBoth cfgs hardForkInjectTxs)
161-
162127
-- | A private type used only to clarify the parameterization of 'applyHelper'
163128
data ApplyHelperMode :: (Type -> Type) -> Type where
164129
ModeApply :: ApplyHelperMode GenTx

ouroboros-consensus/src/ouroboros-consensus/Ouroboros/Consensus/Ledger/Dual.hs

Lines changed: 0 additions & 6 deletions
Original file line numberDiff line numberDiff line change
@@ -624,12 +624,6 @@ instance Bridge m a => LedgerSupportsMempool (DualBlock m a) where
624624
, vDualGenTxBridge
625625
} = vtx
626626

627-
txRefScriptSize cfg st tx =
628-
txRefScriptSize
629-
(dualLedgerConfigMain cfg)
630-
(tickedDualLedgerStateMain st)
631-
(dualGenTxMain tx)
632-
633627
-- We don't need a pair of IDs, as long as we can unique ID the transaction
634628
newtype instance TxId (GenTx (DualBlock m a)) = DualGenTxId {
635629
dualGenTxIdMain :: GenTxId m

ouroboros-consensus/src/ouroboros-consensus/Ouroboros/Consensus/Ledger/SupportsMempool.hs

Lines changed: 0 additions & 2 deletions
Original file line numberDiff line numberDiff line change
@@ -127,8 +127,6 @@ class ( UpdateLedger blk
127127
-- | Discard the evidence that transaction has been previously validated
128128
txForgetValidated :: Validated (GenTx blk) -> GenTx blk
129129

130-
txRefScriptSize :: LedgerConfig blk -> TickedLedgerState blk -> GenTx blk -> Int
131-
132130
-- | A generalized transaction, 'GenTx', identifier.
133131
data family TxId tx :: Type
134132

0 commit comments

Comments
 (0)