Skip to content

Commit 3bd2cbe

Browse files
authored
Conway: restrict VRF tiebreaker based on slot distance (#1047)
Closes #524 This is a revived version of IntersectMBO/ouroboros-network#3721 Based on top of #1063
2 parents 69c7e6d + 55ea208 commit 3bd2cbe

File tree

9 files changed

+213
-42
lines changed

9 files changed

+213
-42
lines changed
Lines changed: 3 additions & 0 deletions
Original file line numberDiff line numberDiff line change
@@ -0,0 +1,3 @@
1+
### Breaking
2+
3+
- Restricted the VRF tiebreaker based on slot distance starting in Conway.

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

Lines changed: 7 additions & 0 deletions
Original file line numberDiff line numberDiff line change
@@ -35,6 +35,8 @@ module Ouroboros.Consensus.Shelley.Eras (
3535
, WrapTx (..)
3636
-- * Type synonyms for convenience
3737
, EraCrypto
38+
-- * Convenience functions
39+
, isBeforeConway
3840
-- * Re-exports
3941
, StandardCrypto
4042
) where
@@ -45,6 +47,7 @@ import Cardano.Ledger.Alonzo (AlonzoEra)
4547
import qualified Cardano.Ledger.Alonzo.Rules as Alonzo
4648
import qualified Cardano.Ledger.Alonzo.Translation as Alonzo
4749
import qualified Cardano.Ledger.Alonzo.Tx as Alonzo
50+
import qualified Cardano.Ledger.Api.Era as L
4851
import Cardano.Ledger.Babbage (BabbageEra)
4952
import qualified Cardano.Ledger.Babbage.Rules as Babbage
5053
import qualified Cardano.Ledger.Babbage.Translation as Babbage
@@ -164,6 +167,10 @@ class ( Core.EraSegWits era
164167
data ConwayEraGovDict era where
165168
ConwayEraGovDict :: CG.ConwayEraGov era => ConwayEraGovDict era
166169

170+
isBeforeConway :: forall era. L.Era era => Proxy era -> Bool
171+
isBeforeConway _ =
172+
L.eraProtVerLow @era < L.eraProtVerLow @(L.ConwayEra (L.EraCrypto era))
173+
167174
-- | The default implementation of 'applyShelleyBasedTx', a thin wrapper around
168175
-- 'SL.applyTx'
169176
defaultApplyShelleyBasedTx ::

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

Lines changed: 26 additions & 11 deletions
Original file line numberDiff line numberDiff line change
@@ -4,7 +4,10 @@
44
{-# LANGUAGE DerivingVia #-}
55
{-# LANGUAGE FlexibleInstances #-}
66
{-# LANGUAGE GeneralizedNewtypeDeriving #-}
7+
{-# LANGUAGE NamedFieldPuns #-}
8+
{-# LANGUAGE ScopedTypeVariables #-}
79
{-# LANGUAGE StandaloneDeriving #-}
10+
{-# LANGUAGE TypeApplications #-}
811
{-# LANGUAGE TypeFamilies #-}
912
{-# OPTIONS_GHC -Wno-orphans #-}
1013
module Ouroboros.Consensus.Shelley.Ledger.Config (
@@ -29,7 +32,9 @@ import NoThunks.Class (NoThunks (..))
2932
import Ouroboros.Consensus.Block
3033
import Ouroboros.Consensus.BlockchainTime
3134
import Ouroboros.Consensus.Config
32-
import Ouroboros.Consensus.Shelley.Eras (EraCrypto)
35+
import Ouroboros.Consensus.Protocol.Praos.Common
36+
(VRFTiebreakerFlavor (..))
37+
import Ouroboros.Consensus.Shelley.Eras (EraCrypto, isBeforeConway)
3338
import Ouroboros.Consensus.Shelley.Ledger.Block
3439
import Ouroboros.Network.Magic (NetworkMagic (..))
3540

@@ -40,35 +45,45 @@ import Ouroboros.Network.Magic (NetworkMagic (..))
4045
data instance BlockConfig (ShelleyBlock proto era) = ShelleyConfig {
4146
-- | The highest protocol version this node supports. It will be stored
4247
-- the headers of produced blocks.
43-
shelleyProtocolVersion :: !SL.ProtVer
44-
, shelleySystemStart :: !SystemStart
45-
, shelleyNetworkMagic :: !NetworkMagic
48+
shelleyProtocolVersion :: !SL.ProtVer
49+
, shelleySystemStart :: !SystemStart
50+
, shelleyNetworkMagic :: !NetworkMagic
4651
-- | For nodes that can produce blocks, this should be set to the
4752
-- verification key(s) corresponding to the node's signing key(s). For non
4853
-- block producing nodes, this can be set to the empty map.
49-
, shelleyBlockIssuerVKeys :: !(Map (SL.KeyHash 'SL.BlockIssuer (EraCrypto era))
50-
(SL.VKey 'SL.BlockIssuer (EraCrypto era)))
54+
, shelleyBlockIssuerVKeys :: !(Map (SL.KeyHash 'SL.BlockIssuer (EraCrypto era))
55+
(SL.VKey 'SL.BlockIssuer (EraCrypto era)))
56+
, shelleyVRFTiebreakerFlavor :: !VRFTiebreakerFlavor
5157
}
5258
deriving stock (Generic)
5359

5460
deriving instance ShelleyBasedEra era => Show (BlockConfig (ShelleyBlock proto era))
5561
deriving instance ShelleyBasedEra era => NoThunks (BlockConfig (ShelleyBlock proto era))
5662

5763
mkShelleyBlockConfig ::
58-
ShelleyBasedEra era
64+
forall proto era. ShelleyBasedEra era
5965
=> SL.ProtVer
6066
-> SL.ShelleyGenesis (EraCrypto era)
6167
-> [SL.VKey 'SL.BlockIssuer (EraCrypto era)]
6268
-> BlockConfig (ShelleyBlock proto era)
6369
mkShelleyBlockConfig protVer genesis blockIssuerVKeys = ShelleyConfig {
64-
shelleyProtocolVersion = protVer
65-
, shelleySystemStart = SystemStart $ SL.sgSystemStart genesis
66-
, shelleyNetworkMagic = NetworkMagic $ SL.sgNetworkMagic genesis
67-
, shelleyBlockIssuerVKeys = Map.fromList
70+
shelleyProtocolVersion = protVer
71+
, shelleySystemStart = SystemStart $ SL.sgSystemStart genesis
72+
, shelleyNetworkMagic = NetworkMagic $ SL.sgNetworkMagic genesis
73+
, shelleyBlockIssuerVKeys = Map.fromList
6874
[ (SL.hashKey k, k)
6975
| k <- blockIssuerVKeys
7076
]
77+
, shelleyVRFTiebreakerFlavor
7178
}
79+
where
80+
shelleyVRFTiebreakerFlavor
81+
| isBeforeConway (Proxy @era)
82+
= UnrestrictedVRFTiebreaker
83+
| otherwise
84+
-- See 'RestrictedVRFTiebreaker' for context. 5 slots is the "usual" value
85+
-- we consider when talking about the maximum propagation delay.
86+
= RestrictedVRFTiebreaker 5
7287

7388
{-------------------------------------------------------------------------------
7489
Codec config

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

Lines changed: 3 additions & 1 deletion
Original file line numberDiff line numberDiff line change
@@ -15,7 +15,7 @@ import Ouroboros.Consensus.Protocol.Signed
1515
import Ouroboros.Consensus.Protocol.TPraos
1616
import Ouroboros.Consensus.Shelley.Eras (EraCrypto)
1717
import Ouroboros.Consensus.Shelley.Ledger.Block
18-
import Ouroboros.Consensus.Shelley.Ledger.Config ()
18+
import Ouroboros.Consensus.Shelley.Ledger.Config (BlockConfig (..))
1919
import Ouroboros.Consensus.Shelley.Protocol.Abstract
2020
(ShelleyProtocolHeader, pHeaderIssueNo, pHeaderIssuer,
2121
pTieBreakVRFValue, protocolHeaderView)
@@ -40,6 +40,8 @@ instance ShelleyCompatible proto era => BlockSupportsProtocol (ShelleyBlock prot
4040
hdrIssuer :: SL.VKey 'SL.BlockIssuer (EraCrypto era)
4141
hdrIssuer = pHeaderIssuer shdr
4242

43+
projectChainOrderConfig = shelleyVRFTiebreakerFlavor
44+
4345
-- TODO correct place for these two?
4446
type instance Signed (Header (ShelleyBlock proto era)) =
4547
Signed (ShelleyProtocolHeader proto)

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

Lines changed: 1 addition & 7 deletions
Original file line numberDiff line numberDiff line change
@@ -16,11 +16,8 @@ module Ouroboros.Consensus.Shelley.Node.DiffusionPipelining (
1616
HotIdentity (..)
1717
, ShelleyTentativeHeaderState (..)
1818
, ShelleyTentativeHeaderView (..)
19-
-- * Testing
20-
, isBeforeConway
2119
) where
2220

23-
import qualified Cardano.Ledger.Api.Era as L
2421
import qualified Cardano.Ledger.Shelley.API as SL
2522
import Control.Monad (guard)
2623
import Data.Set (Set)
@@ -30,6 +27,7 @@ import GHC.Generics (Generic)
3027
import NoThunks.Class
3128
import Ouroboros.Consensus.Block
3229
import Ouroboros.Consensus.Protocol.Abstract
30+
import Ouroboros.Consensus.Shelley.Eras (isBeforeConway)
3331
import Ouroboros.Consensus.Shelley.Ledger.Block
3432
import Ouroboros.Consensus.Shelley.Ledger.Protocol ()
3533
import Ouroboros.Consensus.Shelley.Protocol.Abstract
@@ -78,10 +76,6 @@ data ShelleyTentativeHeaderView proto =
7876
deriving stock instance ConsensusProtocol proto => Show (ShelleyTentativeHeaderView proto)
7977
deriving stock instance ConsensusProtocol proto => Eq (ShelleyTentativeHeaderView proto)
8078

81-
isBeforeConway :: forall era. L.Era era => Proxy era -> Bool
82-
isBeforeConway _ =
83-
L.eraProtVerLow @era < L.eraProtVerLow @(L.ConwayEra (L.EraCrypto era))
84-
8579
-- | This is currently a hybrid instance:
8680
--
8781
-- - For eras before Conway, this uses the logic from

ouroboros-consensus-cardano/test/cardano-test/Test/Consensus/Cardano/DiffusionPipelining.hs

Lines changed: 1 addition & 1 deletion
Original file line numberDiff line numberDiff line change
@@ -10,7 +10,6 @@
1010

1111
module Test.Consensus.Cardano.DiffusionPipelining (tests) where
1212

13-
import Cardano.Ledger.Crypto (StandardCrypto)
1413
import Control.Monad (replicateM)
1514
import Data.Containers.ListUtils (nubOrd)
1615
import Data.List (sort)
@@ -25,6 +24,7 @@ import Ouroboros.Consensus.Cardano (CardanoBlock)
2524
import Ouroboros.Consensus.HardFork.Combinator
2625
import Ouroboros.Consensus.HardFork.Combinator.AcrossEras
2726
import Ouroboros.Consensus.Protocol.PBFT
27+
import Ouroboros.Consensus.Shelley.Eras
2828
import Ouroboros.Consensus.Shelley.Ledger (ShelleyBlock,
2929
ShelleyCompatible)
3030
import Ouroboros.Consensus.Shelley.Ledger.SupportsProtocol ()
Lines changed: 4 additions & 0 deletions
Original file line numberDiff line numberDiff line change
@@ -0,0 +1,4 @@
1+
### Breaking
2+
3+
- Allowed to configure Praos chain order to restrict the VRF tiebreaker based on
4+
slot distance.

ouroboros-consensus-protocol/src/ouroboros-consensus-protocol/Ouroboros/Consensus/Protocol/Praos/Common.hs

Lines changed: 153 additions & 22 deletions
Original file line numberDiff line numberDiff line change
@@ -13,6 +13,7 @@ module Ouroboros.Consensus.Protocol.Praos.Common (
1313
MaxMajorProtVer (..)
1414
, PraosCanBeLeader (..)
1515
, PraosChainSelectView (..)
16+
, VRFTiebreakerFlavor (..)
1617
-- * node support
1718
, PraosNonces (..)
1819
, PraosProtocolSupportsNode (..)
@@ -54,36 +55,166 @@ data PraosChainSelectView c = PraosChainSelectView
5455
}
5556
deriving (Show, Eq, Generic, NoThunks)
5657

58+
-- | When to compare the VRF tiebreakers.
59+
data VRFTiebreakerFlavor =
60+
-- | Always compare the VRF tiebreakers. This is the behavior of all eras
61+
-- before Conway. Once mainnet has transitioned to Conway, we can remove
62+
-- this option. (The honest /historical/ Ouroboros chain cannot rely on
63+
-- tiebreakers to win, so /retroactively/ disabling the tiebreaker won't
64+
-- matter.)
65+
UnrestrictedVRFTiebreaker
66+
| -- | Only compare the VRF tiebreakers when the slot numbers differ by at
67+
-- most the given number of slots.
68+
--
69+
-- The main motivation is as follows:
70+
--
71+
-- When two blocks A and B with the same block number differ in their slot
72+
-- number by more than Δ (the maximum message delay from Praos), say
73+
-- @slot(A) + Δ < slot(B)@, the issuer of B should have been able to mint a
74+
-- block with a block number higher than A (eg by minting on top of A) under
75+
-- normal circumstances. The reason for this not being the case might have
76+
-- been due to A being sent very late, or due to the issuer of B ignoring A
77+
-- (intentionally, or due to poor configuration/resource provision). In any
78+
-- case, we do not want to allow the block that was diffused later to still
79+
-- win by having a better VRF tiebreaker. This makes it less likely for
80+
-- properly configured pools to lose blocks because of poorly configured
81+
-- pools.
82+
RestrictedVRFTiebreaker SlotNo
83+
deriving stock (Show, Eq, Generic)
84+
deriving anyclass (NoThunks)
85+
86+
-- Used to implement the 'Ord' and 'ChainOrder' instances for Praos.
87+
comparePraos ::
88+
Crypto c
89+
=> VRFTiebreakerFlavor
90+
-> PraosChainSelectView c
91+
-> PraosChainSelectView c
92+
-> Ordering
93+
comparePraos tiebreakerFlavor =
94+
(compare `on` csvChainLength)
95+
<> when' ((==) `on` csvIssuer) (compare `on` csvIssueNo)
96+
<> when' vrfArmed (compare `on` Down . csvTieBreakVRF)
97+
where
98+
-- When the predicate @p@ returns 'True', use the given comparison function,
99+
-- otherwise, no preference.
100+
when' ::
101+
(a -> a -> Bool)
102+
-> (a -> a -> Ordering)
103+
-> (a -> a -> Ordering)
104+
when' p comp a1 a2 =
105+
if p a1 a2 then comp a1 a2 else EQ
106+
107+
-- Whether to do a VRF comparison.
108+
vrfArmed v1 v2 = case tiebreakerFlavor of
109+
UnrestrictedVRFTiebreaker -> True
110+
RestrictedVRFTiebreaker maxDist ->
111+
slotDist (csvSlotNo v1) (csvSlotNo v2) <= maxDist
112+
113+
slotDist :: SlotNo -> SlotNo -> SlotNo
114+
slotDist s t
115+
-- slot numbers are unsigned, so have to take care with subtraction
116+
| s >= t = s - t
117+
| otherwise = t - s
118+
57119
-- | We order between chains as follows:
58120
--
59121
-- 1. By chain length, with longer chains always preferred.
122+
--
60123
-- 2. If the tip of each chain was issued by the same agent, then we prefer
61124
-- the chain whose tip has the highest ocert issue number.
125+
--
62126
-- 3. By a VRF value from the chain tip, with lower values preferred. See
63127
-- @pTieBreakVRFValue@ for which one is used.
128+
--
129+
-- IMPORTANT: This is not a complete picture of the Praos chain order, do also
130+
-- consult the documentation of 'ChainOrder'.
64131
instance Crypto c => Ord (PraosChainSelectView c) where
65-
compare =
66-
mconcat
67-
[ compare `on` csvChainLength,
68-
whenSame csvIssuer (compare `on` csvIssueNo),
69-
compare `on` Down . csvTieBreakVRF
70-
]
71-
where
72-
-- When the @a@s are equal, use the given comparison function,
73-
-- otherwise, no preference.
74-
whenSame ::
75-
Eq a =>
76-
(view -> a) ->
77-
(view -> view -> Ordering) ->
78-
(view -> view -> Ordering)
79-
whenSame f comp v1 v2
80-
| f v1 == f v2 =
81-
comp v1 v2
82-
| otherwise =
83-
EQ
84-
85-
deriving via SimpleChainOrder (PraosChainSelectView c)
86-
instance Crypto c => ChainOrder (PraosChainSelectView c)
132+
compare = comparePraos UnrestrictedVRFTiebreaker
133+
134+
-- | IMPORTANT: This is not a 'SimpleChainOrder'; rather, there are
135+
-- 'PraosChainSelectView's @a, b@ such that @a < b@, but @'not' $
136+
-- 'preferCandidate' cfg a b@, namely for @cfg = 'RestrictedVRFTiebreaker'@.
137+
--
138+
-- === Rules
139+
--
140+
-- Concretely, we have @'preferCandidate' cfg ours cand@ based on the following
141+
-- lexicographical criteria:
142+
--
143+
-- 1. Chain length, with longer chains always preferred.
144+
--
145+
-- 2. If the tip of each chain was issued by the same agent, then we prefer the
146+
-- candidate if it has a higher ocert issue number.
147+
--
148+
-- 3. Depending on the 'VRFTiebreakerFlavor':
149+
--
150+
-- * If 'UnrestrictedVRFTiebreaker': Compare via a VRF value from the chain
151+
-- tip, with lower values preferred. See @pTieBreakVRFValue@ for which one
152+
-- is used.
153+
--
154+
-- * If @'RestrictedVRFTiebreaker' maxDist@: Only do the VRF comparison (as
155+
-- in the previous step) if the slot numbers differ by at most @maxDist@.
156+
--
157+
-- === Non-transitivity of 'RestrictedVRFTiebreaker'
158+
--
159+
-- When using @cfg = 'RestrictedVRFTiebreaker' maxDist@, the chain order is not
160+
-- transitive. As an example, suppose @maxDist = 5@ and consider three
161+
-- 'PraosChainSelectView's with the same chain length and pairwise different
162+
-- issuers and, as well as
163+
--
164+
-- +------+---+---+---+
165+
-- | | a | b | c |
166+
-- +======+===+===+===+
167+
-- | Slot | 0 | 3 | 6 |
168+
-- +------+---+---+---+
169+
-- | VRF | 3 | 2 | 1 |
170+
-- +------+---+---+---+
171+
--
172+
-- Then we have @'preferCandidate' cfg a b@ and @'preferCandidate' b c@, but
173+
-- __not__ @'preferCandidate' a c@ (despite @a < c@).
174+
--
175+
-- === Rationale for the rules
176+
--
177+
-- 1. The abstract Consensus layer requires that we first compare based on chain
178+
-- length (see __Chain extension precedence__ in 'ChainOrder').
179+
--
180+
-- 2. Consider the scenario where the hot key of a block issuer was compromised,
181+
-- and the attacker is now minting blocks using that identity. The actual
182+
-- block issuer can use their cold key to issue a new hot key with a higher
183+
-- opcert issue number and set up a new pool. Due to this tiebreaker rule,
184+
-- the blocks minted by that pool will take precedence (allowing the actual
185+
-- block issuer to decide on eg the block contents and the predecessor), and
186+
-- they will end up on the honest chain quickly, which means that the
187+
-- adversary can't extend any chain containing such a block as it would
188+
-- violate the monotonicity requirement on opcert issue numbers.
189+
--
190+
-- See "3.7 Block Validity and Operational Key Certificates" in "Design
191+
-- Specification for Delegation and Incentives in Cardano" by Kant et al for
192+
-- more context.
193+
--
194+
-- 3. The main motivation to do VRF comparisons is to avoid the "Frankfurt
195+
-- problem":
196+
--
197+
-- With only the first two rules for the chain order, almost all blocks with
198+
-- equal block number are equally preferrable. Consider two block issuers
199+
-- minting blocks in very nearby slots. As we never change our selection
200+
-- from one chain to an equally preferrable one, the first block to arrive
201+
-- at another pool is the one to be adopted, and will be extended the next
202+
-- time the pool is elected if no blocks with a higher block number arrive
203+
-- in the meantime. We observed that this effectively incentivizes block
204+
-- producers to concentrate geographically (historically, in Frankfurt) in
205+
-- order to minimize their diffusion times. This works against the goal of
206+
-- geographic decentralisation.
207+
--
208+
-- Also, with the VRF tiebreaker, a block with a somewhat lower propagation
209+
-- speed has a random chance to be selected instead of the one that arrived
210+
-- first by pools before the next block is forged.
211+
--
212+
-- See 'VRFTiebreakerFlavor' for more context on the exact conditions under
213+
-- which the VRF comparison takes place.
214+
instance Crypto c => ChainOrder (PraosChainSelectView c) where
215+
type ChainOrderConfig (PraosChainSelectView c) = VRFTiebreakerFlavor
216+
217+
preferCandidate cfg ours cand = comparePraos cfg ours cand == LT
87218

88219
data PraosCanBeLeader c = PraosCanBeLeader
89220
{ -- | Certificate delegating rights from the stake pool cold key (or

ouroboros-consensus-protocol/test/protocol-test/Test/Consensus/Protocol/Praos/SelectView.hs

Lines changed: 15 additions & 0 deletions
Original file line numberDiff line numberDiff line change
@@ -89,3 +89,18 @@ instance Crypto c => Arbitrary (PraosChainSelectView c) where
8989
$ Crypto.hashWithSerialiser encode slot
9090
where
9191
SL.KeyHash issuerHash = SL.hashKey issuer
92+
93+
-- | 'ChainOrderConfig' 'PraosChainSelectView'
94+
instance Arbitrary VRFTiebreakerFlavor where
95+
arbitrary = oneof
96+
[ pure UnrestrictedVRFTiebreaker
97+
, do
98+
size <- max 1 . fromIntegral <$> getSize
99+
RestrictedVRFTiebreaker . SlotNo <$> choose (1, size)
100+
]
101+
102+
shrink = \case
103+
UnrestrictedVRFTiebreaker -> []
104+
RestrictedVRFTiebreaker maxDist ->
105+
UnrestrictedVRFTiebreaker
106+
: (RestrictedVRFTiebreaker <$> shrink maxDist)

0 commit comments

Comments
 (0)