-
Notifications
You must be signed in to change notification settings - Fork 86
Commit
This commit does not belong to any branch on this repository, and may belong to a fork outside of the repository.
Previously, we knew the current slot and were able to tell that a block was from the future by comparing the block's slot against the current slot. For such blocks we would schedule a chain selection at the block's slot, which would be performed by a background thread. Now, we no longer know the current slot. Instead, we validate candidate chains and use the resulting ledgers to call `CheckInFuture`, which returns the headers in the candidate fragment that are from the future. We truncate these headers from the fragment, record that they're from the future (`cdbFutureBlocks`), and repeat chain selection without them. Headers that are too far into the future, i.e., exceeding the max clock skew, are not recorded in `cdbFutureBlocks`, but are recorded as invalid blocks (with `InFutureExceedsClockSkew` as the `InvalidBlockReason`). For each new block we receive, we perform chain selection for all future blocks before performing chain selection for the new block. * Rename `CandidateSuffix` to `ChainDiff`, split it off into a separate module, and use it throughout chain selection instead of only partially. A `ChainDiff` is the number of headers to roll back the current chain + a fragment containing the new headers to add, i.e., a diff w.r.t. the current chain. Previously, we converted such a `ChainDiff` to a `ChainAndLedger`, i.e., a fragment starting from the immutable tip (typically containing >= k headers) + a ledger matching the tip. Now, we stick to the `ChainDiff` until the end, when we actually install the candidate as the new chain by applying the diff. Also introduce `ValidatedChainDiff` and use that instead of `ChainAndLedger` for the validated candidate. We still use `ChainAndLedger` for the current chain. * Simplify `trySwitchTo` because there is no concurrency thanks to the queue introduced in #1709. Remove the obsolete trace message `ChainChangedInBg`. * New trace messages: - `ChainSelectionForFutureBlock` - `CandidateContainsFutureBlocks` - `CandidateContainsFutureBlocksExceedingClockSkew` * Remove `chainSelectionPerformed` from `AddBlockPromise` as it was not really used and complicated our new handling of blocks from the future. * Don't mark successors of an invalid block as invalid, as this is redundant, see why in `ChainDB.md`. This means we remove the `InChainAfterInvalidBlock` constructor of `InvalidBlockReason`. * Introduce `ChainSelEnv` to reduce the number of parameters to pass around.
- Loading branch information
Showing
24 changed files
with
1,000 additions
and
1,118 deletions.
There are no files selected for viewing
This file contains bidirectional Unicode text that may be interpreted or compiled differently than what appears below. To review, open the file in an editor that reveals hidden Unicode characters.
Learn more about bidirectional Unicode characters
This file contains bidirectional Unicode text that may be interpreted or compiled differently than what appears below. To review, open the file in an editor that reveals hidden Unicode characters.
Learn more about bidirectional Unicode characters
This file contains bidirectional Unicode text that may be interpreted or compiled differently than what appears below. To review, open the file in an editor that reveals hidden Unicode characters.
Learn more about bidirectional Unicode characters
This file contains bidirectional Unicode text that may be interpreted or compiled differently than what appears below. To review, open the file in an editor that reveals hidden Unicode characters.
Learn more about bidirectional Unicode characters
This file contains bidirectional Unicode text that may be interpreted or compiled differently than what appears below. To review, open the file in an editor that reveals hidden Unicode characters.
Learn more about bidirectional Unicode characters
173 changes: 173 additions & 0 deletions
173
ouroboros-consensus/src/Ouroboros/Consensus/Fragment/Diff.hs
This file contains bidirectional Unicode text that may be interpreted or compiled differently than what appears below. To review, open the file in an editor that reveals hidden Unicode characters.
Learn more about bidirectional Unicode characters
Original file line number | Diff line number | Diff line change |
---|---|---|
@@ -0,0 +1,173 @@ | ||
{-# LANGUAGE FlexibleContexts #-} | ||
{-# LANGUAGE PatternSynonyms #-} | ||
{-# LANGUAGE StandaloneDeriving #-} | ||
{-# LANGUAGE UndecidableInstances #-} | ||
-- | Intended for qualified import | ||
-- | ||
-- > import Ouroboros.Consensus.Fragment.Diff (ChainDiff (..)) | ||
-- > import qualified Ouroboros.Consensus.Fragment.Diff as Diff | ||
module Ouroboros.Consensus.Fragment.Diff | ||
( ChainDiff(ChainDiff) | ||
-- * Queries | ||
, getRollback | ||
, getSuffix | ||
, getTip | ||
, getAnchorPoint | ||
-- * Constructors | ||
, extend | ||
, diff | ||
-- * Application | ||
, apply | ||
-- * Manipulation | ||
, truncate | ||
, takeWhileOldest | ||
) where | ||
|
||
import Prelude hiding (truncate) | ||
|
||
import Data.Word (Word64) | ||
import GHC.Stack (HasCallStack) | ||
|
||
import Ouroboros.Network.AnchoredFragment (AnchoredFragment (..)) | ||
import qualified Ouroboros.Network.AnchoredFragment as AF | ||
import Ouroboros.Network.Block (HasHeader, Point, castPoint) | ||
|
||
import Ouroboros.Consensus.Block (Header) | ||
|
||
|
||
-- | A diff of a chain (fragment). | ||
-- | ||
-- INVARIANT: the length of the suffix must always be >= the rollback | ||
-- | ||
-- Note: we allow the suffix with new headers to be empty, even though it is | ||
-- rather pointless. Allowing empty ones makes working with them easier: fewer | ||
-- cases to deal with. Without any headers, the rollback must be 0, so such a | ||
-- diff would be an empty diff. | ||
data ChainDiff blk = UnsafeChainDiff | ||
{ getRollback :: !Word64 | ||
-- ^ The number of headers to roll back the current chain | ||
, getSuffix :: !(AnchoredFragment (Header blk)) | ||
-- ^ The new headers to add after rolling back the current chain. | ||
} | ||
|
||
deriving instance (HasHeader blk, Eq (Header blk)) | ||
=> Eq (ChainDiff blk) | ||
deriving instance (HasHeader blk, Show (Header blk)) | ||
=> Show (ChainDiff blk) | ||
|
||
-- | Allow for pattern matching on a 'ChainDiff' without exposing the (unsafe) | ||
-- constructor. Use 'extend' and 'diff' to construct a 'ChainDiff'. | ||
pattern ChainDiff | ||
:: Word64 -> AnchoredFragment (Header blk) -> ChainDiff blk | ||
pattern ChainDiff r s <- UnsafeChainDiff r s | ||
{-# COMPLETE ChainDiff #-} | ||
|
||
-- | Internal. Return 'Nothing' if the length of the suffix < the rollback. | ||
mkRollback | ||
:: HasHeader (Header blk) | ||
=> Word64 | ||
-> AnchoredFragment (Header blk) | ||
-> Maybe (ChainDiff blk) | ||
mkRollback nbRollback suffix | ||
| fromIntegral (AF.length suffix) >= nbRollback | ||
= Just $ UnsafeChainDiff nbRollback suffix | ||
| otherwise | ||
= Nothing | ||
|
||
{------------------------------------------------------------------------------- | ||
Queries | ||
-------------------------------------------------------------------------------} | ||
|
||
-- | Return the tip of the new suffix | ||
getTip :: HasHeader (Header blk) => ChainDiff blk -> Point blk | ||
getTip = castPoint . AF.headPoint . getSuffix | ||
|
||
-- | Return the anchor point of the new suffix | ||
getAnchorPoint :: ChainDiff blk -> Point blk | ||
getAnchorPoint = castPoint . AF.anchorPoint . getSuffix | ||
|
||
{------------------------------------------------------------------------------- | ||
Constructors | ||
-------------------------------------------------------------------------------} | ||
|
||
-- | Make an extension-only (no rollback) 'ChainDiff'. | ||
extend :: AnchoredFragment (Header blk) -> ChainDiff blk | ||
extend = UnsafeChainDiff 0 | ||
|
||
-- | Diff a candidate chain with the current chain. | ||
-- | ||
-- If the candidate fragment is shorter than the current chain, 'Nothing' is | ||
-- returned (this would violate the invariant of 'ChainDiff'). | ||
-- | ||
-- PRECONDITION: the candidate fragment must intersect with the current chain | ||
-- fragment. | ||
diff | ||
:: (HasHeader (Header blk), HasCallStack) | ||
=> AnchoredFragment (Header blk) -- ^ Current chain | ||
-> AnchoredFragment (Header blk) -- ^ Candidate chain | ||
-> Maybe (ChainDiff blk) | ||
diff curChain candChain = | ||
case AF.intersect curChain candChain of | ||
Just (_curChainPrefix, _candPrefix, curChainSuffix, candSuffix) | ||
-> mkRollback | ||
(fromIntegral (AF.length curChainSuffix)) | ||
candSuffix | ||
-- Precondition violated. | ||
_ -> error "candidate fragment doesn't intersect with current chain" | ||
|
||
{------------------------------------------------------------------------------- | ||
Application | ||
-------------------------------------------------------------------------------} | ||
|
||
-- | Apply the 'ChainDiff' on the given chain fragment. | ||
-- | ||
-- The fragment is first rolled back a number of blocks before appending the | ||
-- new suffix. | ||
-- | ||
-- If the 'ChainDiff' doesn't fit (anchor point mismatch), 'Nothing' is | ||
-- returned. | ||
-- | ||
-- The returned fragment will have the same anchor point as the given | ||
-- fragment. | ||
apply | ||
:: HasHeader (Header blk) | ||
=> AnchoredFragment (Header blk) | ||
-> ChainDiff blk | ||
-> Maybe (AnchoredFragment (Header blk)) | ||
apply curChain (ChainDiff nbRollback suffix) = | ||
AF.join (AF.dropNewest (fromIntegral nbRollback) curChain) suffix | ||
|
||
{------------------------------------------------------------------------------- | ||
Manipulation | ||
-------------------------------------------------------------------------------} | ||
|
||
-- | Truncate the diff by rolling back the new suffix to the given point. | ||
-- | ||
-- PRECONDITION: the given point must correspond to one of the new headers of | ||
-- the new suffix or its anchor (i.e, @'AF.withinFragmentBounds' pt (getSuffix | ||
-- diff)@). | ||
-- | ||
-- If the length of the truncated suffix is shorter than the rollback, | ||
-- 'Nothing' is returned. | ||
truncate | ||
:: (HasHeader (Header blk), HasCallStack, HasHeader blk) | ||
=> Point blk | ||
-> ChainDiff blk | ||
-> Maybe (ChainDiff blk) | ||
truncate pt (ChainDiff nbRollback suffix) | ||
| Just suffix' <- AF.rollback (castPoint pt) suffix | ||
= mkRollback nbRollback suffix' | ||
| otherwise | ||
= error $ "rollback point not on the candidate suffix: " <> show pt | ||
|
||
-- | Return the longest prefix of the suffix matching the given predicate, | ||
-- starting from the left, i.e., the \"oldest\" blocks. | ||
-- | ||
-- If the new suffix is shorter than the diff's rollback, return 'Nothing'. | ||
takeWhileOldest | ||
:: HasHeader (Header blk) | ||
=> (Header blk -> Bool) | ||
-> ChainDiff blk | ||
-> Maybe (ChainDiff blk) | ||
takeWhileOldest accept (ChainDiff nbRollback suffix) = | ||
mkRollback nbRollback (AF.takeWhileOldest accept suffix) |
69 changes: 69 additions & 0 deletions
69
ouroboros-consensus/src/Ouroboros/Consensus/Fragment/ValidatedDiff.hs
This file contains bidirectional Unicode text that may be interpreted or compiled differently than what appears below. To review, open the file in an editor that reveals hidden Unicode characters.
Learn more about bidirectional Unicode characters
Original file line number | Diff line number | Diff line change |
---|---|---|
@@ -0,0 +1,69 @@ | ||
{-# LANGUAGE PatternSynonyms #-} | ||
-- | Intended for qualified import | ||
-- | ||
-- > import Ouroboros.Consensus.Fragment.ValidatedDiff (ValidatedChainDiff (..)) | ||
-- > import qualified Ouroboros.Consensus.Fragment.ValidatedDiff as ValidatedDiff | ||
module Ouroboros.Consensus.Fragment.ValidatedDiff | ||
( ValidatedChainDiff(ValidatedChainDiff) | ||
, getChainDiff | ||
, getLedger | ||
, new | ||
, toValidatedFragment | ||
) where | ||
|
||
import Control.Monad.Except (throwError) | ||
import GHC.Stack (HasCallStack) | ||
|
||
import Ouroboros.Consensus.Fragment.Diff | ||
import Ouroboros.Consensus.Fragment.Validated (ValidatedFragment) | ||
import qualified Ouroboros.Consensus.Fragment.Validated as VF | ||
import Ouroboros.Consensus.Ledger.Abstract | ||
import Ouroboros.Consensus.Util.Assert | ||
|
||
-- | A 'ChainDiff' along with the ledger state after validation. | ||
-- | ||
-- INVARIANT: | ||
-- | ||
-- > getTip chainDiff == ledgerTipPoint ledger | ||
data ValidatedChainDiff blk l = UnsafeValidatedChainDiff | ||
{ getChainDiff :: ChainDiff blk | ||
, getLedger :: l | ||
} | ||
|
||
-- | Allow for pattern matching on a 'ValidatedChainDiff' without exposing the | ||
-- (unsafe) constructor. Use 'new' to construct a 'ValidatedChainDiff'. | ||
pattern ValidatedChainDiff | ||
:: ChainDiff blk -> l -> ValidatedChainDiff blk l | ||
pattern ValidatedChainDiff d l <- UnsafeValidatedChainDiff d l | ||
{-# COMPLETE ValidatedChainDiff #-} | ||
|
||
-- | Create a 'ValidatedChainDiff'. | ||
-- | ||
-- PRECONDITION: | ||
-- | ||
-- > getTip chainDiff == ledgerTipPoint ledger | ||
new | ||
:: (ApplyBlock l blk, HasCallStack) | ||
=> ChainDiff blk | ||
-> l | ||
-> ValidatedChainDiff blk l | ||
new chainDiff ledger = | ||
assertWithMsg precondition $ | ||
UnsafeValidatedChainDiff chainDiff ledger | ||
where | ||
chainDiffTip = getTip chainDiff | ||
ledgerTip = ledgerTipPoint ledger | ||
precondition | ||
| chainDiffTip == ledgerTip | ||
= return () | ||
| otherwise | ||
= throwError $ | ||
"tip of ChainDiff doesn't match ledger: " <> | ||
show chainDiffTip <> " /= " <> show ledgerTip | ||
|
||
toValidatedFragment | ||
:: (ApplyBlock l blk, HasCallStack) | ||
=> ValidatedChainDiff blk l | ||
-> ValidatedFragment blk l | ||
toValidatedFragment (UnsafeValidatedChainDiff cs l) = | ||
VF.new (getSuffix cs) l |
Oops, something went wrong.