|
7 | 7 | {-# LANGUAGE FlexibleInstances #-} |
8 | 8 | {-# LANGUAGE GeneralizedNewtypeDeriving #-} |
9 | 9 | {-# LANGUAGE NamedFieldPuns #-} |
10 | | -{-# LANGUAGE NumericUnderscores #-} |
11 | 10 | {-# LANGUAGE OverloadedStrings #-} |
12 | 11 | {-# LANGUAGE Rank2Types #-} |
13 | 12 | {-# LANGUAGE ScopedTypeVariables #-} |
@@ -52,14 +51,12 @@ import Cardano.Ledger.Binary (Annotator (..), DecCBOR (..), |
52 | 51 | ToCBOR (..), toPlainDecoder) |
53 | 52 | import qualified Cardano.Ledger.Conway.Rules as ConwayEra |
54 | 53 | import qualified Cardano.Ledger.Conway.Rules as SL |
55 | | -import qualified Cardano.Ledger.Conway.Tx as SL (tierRefScriptFee) |
56 | 54 | import qualified Cardano.Ledger.Conway.UTxO as SL |
57 | 55 | import qualified Cardano.Ledger.Core as SL (txIdTxBody) |
58 | 56 | import Cardano.Ledger.Crypto (Crypto) |
59 | 57 | import qualified Cardano.Ledger.SafeHash as SL |
60 | 58 | import qualified Cardano.Ledger.Shelley.API as SL |
61 | 59 | import qualified Cardano.Ledger.Shelley.Rules as ShelleyEra |
62 | | -import qualified Cardano.Ledger.Val as SL (zero, (<+>)) |
63 | 60 | import Control.Arrow ((+++)) |
64 | 61 | import Control.Monad (guard) |
65 | 62 | import Control.Monad.Except (Except, liftEither) |
@@ -303,12 +300,6 @@ validateMaybe :: |
303 | 300 | -> V.Validation (TxErrorSG era) a |
304 | 301 | validateMaybe err mb = V.validate (TxErrorSG err) id mb |
305 | 302 |
|
306 | | -validateGuard :: |
307 | | - SL.ApplyTxError era |
308 | | - -> Bool |
309 | | - -> V.Validation (TxErrorSG era) () |
310 | | -validateGuard err b = validateMaybe err $ guard b |
311 | | - |
312 | 303 | runValidation :: |
313 | 304 | V.Validation (TxErrorSG era) a |
314 | 305 | -> Except (SL.ApplyTxError era) a |
@@ -573,57 +564,18 @@ txMeasureBabbage :: |
573 | 564 | -> GenTx (ShelleyBlock proto era) |
574 | 565 | -> V.Validation (TxErrorSG era) ConwayMeasure |
575 | 566 | txMeasureBabbage st tx@(ShelleyTx _txid tx') = |
576 | | - ConwayMeasure <$> txMeasureAlonzo st tx <*> refScriptBytes |
| 567 | + (\x -> ConwayMeasure x refScriptBytes) <$> txMeasureAlonzo st tx |
577 | 568 | where |
578 | 569 | utxo = SL.getUTxO $ tickedShelleyLedgerState st |
579 | | - txsz = SL.txNonDistinctRefScriptsSize utxo tx' :: Int |
580 | 570 |
|
581 | | - -- TODO recall the assertion in this module header that this logic should |
582 | | - -- be owned by Ledger, not by Consensus: Ledger prefers to delete these |
583 | | - -- checks after mainnet hard forks to Conway, rather than introduce the |
584 | | - -- necessary 'SL.PredicateFailure' constructors for Babbage (which would in |
585 | | - -- turn require a bump to "Ouroboros.Network.NodeToNode.Version" and |
586 | | - -- "Ouroboros.Network.NodeToClient.Version") |
587 | | - -- |
588 | | - -- -- Babbage should have enforced a per-tx limit here, but did not. |
589 | | - -- refScriptBytes = pure $ ByteSize $ fromIntegral txsz |
590 | | - refScriptBytes :: |
591 | | - V.Validation (TxErrorSG era) (IgnoringOverflow ByteSize32) |
| 571 | + -- The Babbage rules should have checked this ref script size against a |
| 572 | + -- limit, but they did not. Now that Cardano @mainnet@ is in Conway, that |
| 573 | + -- omission is no longer an attack vector. Any other chain intending to |
| 574 | + -- ever use Babbage as its current era ought to patch this. |
592 | 575 | refScriptBytes = |
593 | | - (IgnoringOverflow $ ByteSize32 $ fromIntegral txsz) |
594 | | - -- Reject it if it has more than 100 kibibytes of ref script. |
595 | | - <$ validateGuard |
596 | | - (err 1_000_000 (fromIntegral txsz) (fromIntegral limit)) |
597 | | - (txsz <= limit) |
598 | | - -- Reject it if it has more than 50 kibibytes of ref script and does |
599 | | - -- not satisfy an additional fee of 'SL.tierRefScriptFee'. |
600 | | - -- |
601 | | - -- TODO this additional fee check in particular doesn't truly belong |
602 | | - -- in 'txMeasure' (which only needs to enforce per-tx limits); |
603 | | - -- however, it's less confusing and less duplication to put it here |
604 | | - -- rather than |
605 | | - -- 'Ouroboros.Consensus.Shelley.Eras.defaultApplyShelleyBasedTx' |
606 | | - <* validateGuard |
607 | | - (err 100_000 (SL.unCoin fee) (SL.unCoin reqFee)) |
608 | | - (reqFee <= fee) |
609 | | - where |
610 | | - limit = 100 * 1024 |
611 | | - |
612 | | - fee = tx' ^. L.bodyTxL . L.feeTxBodyL :: SL.Coin |
613 | | - |
614 | | - reqFee :: SL.Coin |
615 | | - reqFee = if txsz <= 50 * 1024 then SL.zero else minFee SL.<+> addlFee |
616 | | - |
617 | | - pparams = getPParams $ tickedShelleyLedgerState st |
618 | | - minFee = L.getMinFeeTx pparams tx' 0 |
619 | | - addlFee = SL.tierRefScriptFee 1.2 25600 15 txsz |
620 | | - |
621 | | - -- As we are reusing an existing error message, we add a large number |
622 | | - -- to ensure users running into this are productively irritated and |
623 | | - -- post this error message somewhere where they can receive |
624 | | - -- help/context. |
625 | | - err :: Integer -> Integer -> Integer -> SL.ApplyTxError era |
626 | | - err shift l r = maxTxSizeUTxO (l + shift) (r + shift) |
| 576 | + IgnoringOverflow |
| 577 | + $ ByteSize32 |
| 578 | + $ fromIntegral (SL.txNonDistinctRefScriptsSize utxo tx' :: Int) |
627 | 579 |
|
628 | 580 | -- | We anachronistically use 'ConwayMeasure' in Babbage. |
629 | 581 | instance ( ShelleyCompatible p (BabbageEra c) |
|
0 commit comments