@@ -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'.
64131instance 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
88219data PraosCanBeLeader c = PraosCanBeLeader
89220 { -- | Certificate delegating rights from the stake pool cold key (or
0 commit comments