Skip to content

Commit 1454b61

Browse files
committed
consensus: consolidate transaction limits in the mempool
Transaction size, block capacity, and mempool capacity are multi-dimensional vectors (incl ExUnits, etc), instead of merely bytes: see `TxMeasure`. `TxLimits` has fittingly been promoted from the `Capacity` module to the proper `SupportsMempool` module, cannibalizing some methds from the `LedgerSupporstMempool` class. A transaction cannot be added if it would push any component of the size over that component's capacity. The capacity override is still only specified in byte size, but the value is interpreted as a block count (rounded up). Enforce block capacity _before_ the forging logic. Now the forging logic simply includes whatever transactions its given, which is reasonable and simpler. It's the NodeKernel logic that uses the mempool's finger tree in order to slice an appropriately-sized prefix, which is then passed to the now-dumb forging function. Explicit attention is given to overflow and the DoS vector of providing an erroneously massive tx that would block the mempool's growth, were it not for the new guards. Also, anachronistically use ConwayMeasure in Babbage, since it should have been counting ref script bytes, as Conway now does. Many comments are improved and also updated for the new scheme.
1 parent c785816 commit 1454b61

File tree

42 files changed

+1326
-657
lines changed

Some content is hidden

Large Commits have some content hidden by default. Use the searchbox below for content that may be hidden.

42 files changed

+1326
-657
lines changed

ouroboros-consensus-cardano/ouroboros-consensus-cardano.cabal

Lines changed: 1 addition & 0 deletions
Original file line numberDiff line numberDiff line change
@@ -167,6 +167,7 @@ library
167167
strict-sop-core ^>=0.1,
168168
text,
169169
these ^>=1.2,
170+
validation,
170171
vector-map,
171172

172173
-- GHC 8.10.7 on aarch64-darwin cannot use text-2

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

Lines changed: 3 additions & 3 deletions
Original file line numberDiff line numberDiff line change
@@ -48,7 +48,7 @@ forgeByronBlock ::
4848
-> BlockNo -- ^ Current block number
4949
-> SlotNo -- ^ Current slot number
5050
-> TickedLedgerState ByronBlock -- ^ Current ledger
51-
-> [Validated (GenTx ByronBlock)] -- ^ Txs to consider adding in the block
51+
-> [Validated (GenTx ByronBlock)] -- ^ Txs to include
5252
-> PBftIsLeader PBftByronCrypto -- ^ Leader proof ('IsLeader')
5353
-> ByronBlock
5454
forgeByronBlock cfg = forgeRegularBlock (configBlock cfg)
@@ -123,7 +123,7 @@ forgeRegularBlock ::
123123
-> BlockNo -- ^ Current block number
124124
-> SlotNo -- ^ Current slot number
125125
-> TickedLedgerState ByronBlock -- ^ Current ledger
126-
-> [Validated (GenTx ByronBlock)] -- ^ Txs to consider adding in the block
126+
-> [Validated (GenTx ByronBlock)] -- ^ Txs to include
127127
-> PBftIsLeader PBftByronCrypto -- ^ Leader proof ('IsLeader')
128128
-> ByronBlock
129129
forgeRegularBlock cfg bno sno st txs isLeader =
@@ -141,7 +141,7 @@ forgeRegularBlock cfg bno sno st txs isLeader =
141141
foldr
142142
extendBlockPayloads
143143
initBlockPayloads
144-
(takeLargestPrefixThatFits st txs)
144+
txs
145145

146146
txPayload :: CC.UTxO.TxPayload
147147
txPayload = CC.UTxO.mkTxPayload (bpTxs blockPayloads)

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

Lines changed: 33 additions & 20 deletions
Original file line numberDiff line numberDiff line change
@@ -48,13 +48,13 @@ import Cardano.Ledger.Binary (ByteSpan, DecoderError (..),
4848
byronProtVer, fromByronCBOR, serialize, slice, toByronCBOR,
4949
unsafeDeserialize)
5050
import Cardano.Ledger.Binary.Plain (enforceSize)
51-
import Cardano.Prelude (cborError)
51+
import Cardano.Prelude (Natural, cborError)
5252
import Codec.CBOR.Decoding (Decoder)
5353
import qualified Codec.CBOR.Decoding as CBOR
5454
import Codec.CBOR.Encoding (Encoding)
5555
import qualified Codec.CBOR.Encoding as CBOR
5656
import Control.Monad (void)
57-
import Control.Monad.Except (Except)
57+
import Control.Monad.Except (Except, throwError)
5858
import Data.ByteString (ByteString)
5959
import qualified Data.ByteString as Strict
6060
import qualified Data.ByteString.Lazy as Lazy
@@ -71,19 +71,9 @@ import Ouroboros.Consensus.Byron.Ledger.Serialisation
7171
(byronBlockEncodingOverhead)
7272
import Ouroboros.Consensus.Ledger.Abstract
7373
import Ouroboros.Consensus.Ledger.SupportsMempool
74-
import Ouroboros.Consensus.Mempool
7574
import Ouroboros.Consensus.Util (ShowProxy (..))
7675
import Ouroboros.Consensus.Util.Condense
7776

78-
{-------------------------------------------------------------------------------
79-
TxLimits
80-
-------------------------------------------------------------------------------}
81-
82-
instance TxLimits ByronBlock where
83-
type TxMeasure ByronBlock = ByteSize
84-
txMeasure _st = ByteSize . txInBlockSize . txForgetValidated
85-
txsBlockCapacity = ByteSize . txsMaxBytes
86-
8777
{-------------------------------------------------------------------------------
8878
Transactions
8979
-------------------------------------------------------------------------------}
@@ -132,16 +122,39 @@ instance LedgerSupportsMempool ByronBlock where
132122
where
133123
validationMode = CC.ValidationMode CC.NoBlockValidation Utxo.TxValidationNoCrypto
134124

135-
txsMaxBytes st =
136-
CC.getMaxBlockSize (tickedByronLedgerState st) - byronBlockEncodingOverhead
125+
txForgetValidated = forgetValidatedByronTx
137126

138-
txInBlockSize =
139-
fromIntegral
140-
. Strict.length
141-
. CC.mempoolPayloadRecoverBytes
142-
. toMempoolPayload
127+
instance TxLimits ByronBlock where
128+
type TxMeasure ByronBlock = IgnoringOverflow ByteSize32
143129

144-
txForgetValidated = forgetValidatedByronTx
130+
blockCapacityTxMeasure _cfg st =
131+
IgnoringOverflow
132+
$ ByteSize32
133+
$ CC.getMaxBlockSize cvs - byronBlockEncodingOverhead
134+
where
135+
cvs = tickedByronLedgerState st
136+
137+
txMeasure _cfg st tx =
138+
if txszNat > maxTxSize then throwError err else
139+
pure $ IgnoringOverflow $ ByteSize32 $ fromIntegral txsz
140+
where
141+
maxTxSize =
142+
Update.ppMaxTxSize
143+
$ CC.adoptedProtocolParameters
144+
$ CC.cvsUpdateState
145+
$ tickedByronLedgerState st
146+
147+
txszNat = fromIntegral txsz :: Natural
148+
149+
txsz =
150+
Strict.length
151+
$ CC.mempoolPayloadRecoverBytes
152+
$ toMempoolPayload tx
153+
154+
err =
155+
CC.MempoolTxErr
156+
$ Utxo.UTxOValidationTxValidationError
157+
$ Utxo.TxValidationTxTooLarge txszNat maxTxSize
145158

146159
data instance TxId (GenTx ByronBlock)
147160
= ByronTxId !Utxo.TxId

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

Lines changed: 36 additions & 2 deletions
Original file line numberDiff line numberDiff line change
@@ -2,8 +2,10 @@
22
{-# LANGUAGE DataKinds #-}
33
{-# LANGUAGE DeriveAnyClass #-}
44
{-# LANGUAGE DeriveGeneric #-}
5+
{-# LANGUAGE EmptyCase #-}
56
{-# LANGUAGE FlexibleContexts #-}
67
{-# LANGUAGE FlexibleInstances #-}
8+
{-# LANGUAGE LambdaCase #-}
79
{-# LANGUAGE MultiParamTypeClasses #-}
810
{-# LANGUAGE NamedFieldPuns #-}
911
{-# LANGUAGE OverloadedStrings #-}
@@ -57,7 +59,7 @@ import Data.Maybe (listToMaybe, mapMaybe)
5759
import Data.Proxy
5860
import Data.SOP.BasicFunctors
5961
import Data.SOP.InPairs (RequiringBoth (..), ignoringBoth)
60-
import Data.SOP.Strict (hpure)
62+
import qualified Data.SOP.Strict as SOP
6163
import Data.SOP.Tails (Tails (..))
6264
import qualified Data.SOP.Tails as Tails
6365
import Data.Void
@@ -78,6 +80,8 @@ import Ouroboros.Consensus.HardFork.History (Bound (boundSlot),
7880
addSlots)
7981
import Ouroboros.Consensus.HardFork.Simple
8082
import Ouroboros.Consensus.Ledger.Abstract
83+
import Ouroboros.Consensus.Ledger.SupportsMempool (ByteSize32,
84+
IgnoringOverflow, TxMeasure)
8185
import Ouroboros.Consensus.Ledger.SupportsProtocol
8286
(LedgerSupportsProtocol)
8387
import Ouroboros.Consensus.Protocol.Abstract
@@ -283,6 +287,8 @@ type CardanoHardForkConstraints c =
283287
)
284288

285289
instance CardanoHardForkConstraints c => CanHardFork (CardanoEras c) where
290+
type HardForkTxMeasure (CardanoEras c) = ConwayMeasure
291+
286292
hardForkEraTranslation = EraTranslation {
287293
translateLedgerState =
288294
PCons translateLedgerStateByronToShelleyWrapper
@@ -311,7 +317,7 @@ instance CardanoHardForkConstraints c => CanHardFork (CardanoEras c) where
311317
}
312318
hardForkChainSel =
313319
-- Byron <-> Shelley, ...
314-
TCons (hpure CompareBlockNo)
320+
TCons (SOP.hpure CompareBlockNo)
315321
-- Inter-Shelley-based
316322
$ Tails.hcpure (Proxy @(HasPraosSelectView c)) CompareSameSelectView
317323
hardForkInjectTxs =
@@ -349,6 +355,34 @@ instance CardanoHardForkConstraints c => CanHardFork (CardanoEras c) where
349355
)
350356
$ PNil
351357

358+
hardForkInjTxMeasure =
359+
fromByteSize `o`
360+
fromByteSize `o`
361+
fromByteSize `o`
362+
fromByteSize `o`
363+
fromAlonzo `o`
364+
fromConway `o`
365+
fromConway `o`
366+
nil
367+
where
368+
nil :: SOP.NS f '[] -> a
369+
nil = \case {}
370+
371+
infixr `o`
372+
o ::
373+
(TxMeasure x -> a)
374+
-> (SOP.NS WrapTxMeasure xs -> a)
375+
-> SOP.NS WrapTxMeasure (x : xs)
376+
-> a
377+
o f g = \case
378+
SOP.Z (WrapTxMeasure x) -> f x
379+
SOP.S y -> g y
380+
381+
fromByteSize :: IgnoringOverflow ByteSize32 -> ConwayMeasure
382+
fromByteSize x = fromAlonzo $ AlonzoMeasure x mempty
383+
fromAlonzo x = fromConway $ ConwayMeasure x mempty
384+
fromConway x = x
385+
352386
class (SelectView (BlockProtocol blk) ~ PraosChainSelectView c) => HasPraosSelectView c blk
353387
instance (SelectView (BlockProtocol blk) ~ PraosChainSelectView c) => HasPraosSelectView c blk
354388

Lines changed: 7 additions & 28 deletions
Original file line numberDiff line numberDiff line change
@@ -1,6 +1,5 @@
11
{-# LANGUAGE DisambiguateRecordFields #-}
22
{-# LANGUAGE FlexibleContexts #-}
3-
{-# LANGUAGE OverloadedStrings #-}
43
{-# LANGUAGE ScopedTypeVariables #-}
54
{-# LANGUAGE TypeApplications #-}
65
{-# LANGUAGE TypeFamilies #-}
@@ -13,14 +12,11 @@ import qualified Cardano.Ledger.Shelley.API as SL (Block (..), extractTx)
1312
import qualified Cardano.Ledger.Shelley.BlockChain as SL (bBodySize)
1413
import qualified Cardano.Protocol.TPraos.BHeader as SL
1514
import Control.Exception
16-
import Control.Monad.Except
17-
import Data.List as List (foldl')
1815
import qualified Data.Sequence.Strict as Seq
1916
import Ouroboros.Consensus.Block
2017
import Ouroboros.Consensus.Config
2118
import Ouroboros.Consensus.Ledger.Abstract
2219
import Ouroboros.Consensus.Ledger.SupportsMempool
23-
import Ouroboros.Consensus.Mempool (TxLimits)
2420
import Ouroboros.Consensus.Protocol.Abstract (CanBeLeader, IsLeader)
2521
import Ouroboros.Consensus.Protocol.Ledger.HotKey (HotKey)
2622
import Ouroboros.Consensus.Shelley.Eras (EraCrypto)
@@ -32,22 +28,21 @@ import Ouroboros.Consensus.Shelley.Ledger.Mempool
3228
import Ouroboros.Consensus.Shelley.Protocol.Abstract (ProtoCrypto,
3329
ProtocolHeaderSupportsKES (configSlotsPerKESPeriod),
3430
mkHeader)
35-
import Ouroboros.Consensus.Util.Assert
3631

3732
{-------------------------------------------------------------------------------
3833
Forging
3934
-------------------------------------------------------------------------------}
4035

4136
forgeShelleyBlock ::
4237
forall m era proto.
43-
(ShelleyCompatible proto era, TxLimits (ShelleyBlock proto era), Monad m)
38+
(ShelleyCompatible proto era, Monad m)
4439
=> HotKey (EraCrypto era) m
4540
-> CanBeLeader proto
4641
-> TopLevelConfig (ShelleyBlock proto era)
4742
-> BlockNo -- ^ Current block number
4843
-> SlotNo -- ^ Current slot number
4944
-> TickedLedgerState (ShelleyBlock proto era) -- ^ Current ledger
50-
-> [Validated (GenTx (ShelleyBlock proto era))] -- ^ Txs to add in the block
45+
-> [Validated (GenTx (ShelleyBlock proto era))] -- ^ Txs to include
5146
-> IsLeader proto
5247
-> m (ShelleyBlock proto era)
5348
forgeShelleyBlock
@@ -64,15 +59,16 @@ forgeShelleyBlock
6459
let blk = mkShelleyBlock $ SL.Block hdr body
6560
return $
6661
assert (verifyBlockIntegrity (configSlotsPerKESPeriod $ configConsensus cfg) blk) $
67-
assertWithMsg bodySizeEstimate blk
62+
blk
6863
where
6964
protocolVersion = shelleyProtocolVersion $ configBlock cfg
7065

7166
body =
7267
SL.toTxSeq @era
73-
. Seq.fromList
74-
. fmap extractTx
75-
$ takeLargestPrefixThatFits tickedLedger txs
68+
$ Seq.fromList
69+
$ fmap extractTx txs
70+
71+
actualBodySize = SL.bBodySize protocolVersion body
7672

7773
extractTx :: Validated (GenTx (ShelleyBlock proto era)) -> Core.Tx era
7874
extractTx (ShelleyValidatedTx _txid vtx) = SL.extractTx vtx
@@ -83,20 +79,3 @@ forgeShelleyBlock
8379
. castHash
8480
. getTipHash
8581
$ tickedLedger
86-
87-
bodySizeEstimate :: Either String ()
88-
bodySizeEstimate
89-
| actualBodySize > estimatedBodySize + fixedBlockBodyOverhead
90-
= throwError $
91-
"Actual block body size > Estimated block body size + fixedBlockBodyOverhead: "
92-
<> show actualBodySize
93-
<> " > "
94-
<> show estimatedBodySize
95-
<> " + "
96-
<> show (fixedBlockBodyOverhead :: Int)
97-
| otherwise
98-
= return ()
99-
100-
estimatedBodySize, actualBodySize :: Int
101-
estimatedBodySize = fromIntegral $ List.foldl' (+) 0 $ map (txInBlockSize . txForgetValidated) txs
102-
actualBodySize = SL.bBodySize protocolVersion body

0 commit comments

Comments
 (0)