Skip to content
Open
Show file tree
Hide file tree
Changes from all commits
Commits
File filter

Filter by extension

Filter by extension

Conversations
Failed to load comments.
Loading
Jump to
Jump to file
Failed to load files.
Loading
Diff view
Diff view
Original file line number Diff line number Diff line change
Expand Up @@ -56,8 +56,13 @@ data NodeToClientVersion
-- ^ new codecs for @PParams@ and @CompactGenesis@
| NodeToClientV_22
-- ^ support SRV records in @GetBigLedgerPeerSnapshot@ query
-- TODO: remove CBOR instances from LedgerPeers.Type when V22 support
-- is removed, update {To,From}JSON LedgerPeerSnapshot instances
-- and update LedgerPeerSnapshot query encoding in consensus.
-- marked with TODO's.
| NodeToClientV_23
-- ^ added @QueryDRepsDelegations@,
-- LedgerPeerSnapshot CBOR encoding contains block hash and NetworkMagic
deriving (Eq, Ord, Enum, Bounded, Show, Generic, NFData)

-- | We set 16ths bit to distinguish `NodeToNodeVersion` and
Expand Down
1 change: 1 addition & 0 deletions cardano-diffusion/cardano-diffusion.cabal
Original file line number Diff line number Diff line change
Expand Up @@ -151,6 +151,7 @@ library
aeson,
base >=4.14 && <4.22,
bytestring,
cardano-crypto-class,
cardano-diffusion:{api, protocols},
containers,
contra-tracer,
Expand Down
Original file line number Diff line number Diff line change
@@ -0,0 +1,16 @@
<!--
A new scriv changelog fragment.

Uncomment the section that is right (remove the HTML comment wrapper).
For top level release notes, leave all the headers commented out.
-->

### Breaking

cardano-diffusion:
- added `lpGetBlockInfo` to `LedgerPeersConsensusInterface`

### Non-Breaking

cardano-diffusion:
- moved `jobVerifyPeerSnapshot` from o-n
Original file line number Diff line number Diff line change
@@ -1,3 +1,5 @@
{-# LANGUAGE RankNTypes #-}

module Cardano.Network.LedgerPeerConsensusInterface
( LedgerPeersConsensusInterface (..)
-- * Re-exports
Expand All @@ -8,11 +10,14 @@ module Cardano.Network.LedgerPeerConsensusInterface

import Control.Concurrent.Class.MonadSTM (MonadSTM (..))

import Ouroboros.Network.BlockFetch.ConsensusInterface (FetchMode (..))

import Cardano.Crypto.Hash (Blake2b_256, Hash)
import Cardano.Network.LedgerStateJudgement
import Cardano.Network.PeerSelection.LocalRootPeers
(OutboundConnectionsState (..))
import Ouroboros.Network.Block (SlotNo)
import Ouroboros.Network.BlockFetch.ConsensusInterface (FetchMode (..))
import Ouroboros.Network.Point (Block)


-- | Cardano Node specific consensus interface actions.
--
Expand All @@ -31,4 +36,7 @@ data LedgerPeersConsensusInterface m =
-- it only has local peers.
--
, updateOutboundConnectionsState :: OutboundConnectionsState -> STM m ()

, getBlockHash
:: forall r. SlotNo -> (forall a. STM m (Block SlotNo (Hash Blake2b_256 a)) -> r) -> r
}
Original file line number Diff line number Diff line change
@@ -1,6 +1,10 @@
{-# LANGUAGE LambdaCase #-}
{-# LANGUAGE NamedFieldPuns #-}
{-# LANGUAGE ScopedTypeVariables #-}
{-# LANGUAGE DataKinds #-}
{-# LANGUAGE DisambiguateRecordFields #-}
{-# LANGUAGE GADTs #-}
{-# LANGUAGE LambdaCase #-}
{-# LANGUAGE NamedFieldPuns #-}
{-# LANGUAGE PatternSynonyms #-}
{-# LANGUAGE ScopedTypeVariables #-}

-- | This module contains governor decisions for monitoring tasks:
--
Expand All @@ -18,14 +22,18 @@ module Cardano.Network.PeerSelection.Governor.Monitor
, ExtraTrace (..)
) where

import Data.Set qualified as Set

import Control.Concurrent.JobPool (Job (..))
import Control.Exception (assert)
import Control.Monad.Class.MonadSTM
import Control.Monad.Class.MonadTime.SI
import Control.Monad.Class.MonadTimer.SI
import Data.Map.Strict (Map)
import Data.Map.Strict qualified as Map
import Data.Set (Set)
import Data.Set qualified as Set

import Cardano.Crypto.Hash as Crypto (castHash)
import Cardano.Network.ConsensusMode
import Cardano.Network.Diffusion.Configuration qualified as Cardano (srvPrefix)
import Cardano.Network.LedgerPeerConsensusInterface qualified as Cardano
import Cardano.Network.LedgerStateJudgement
import Cardano.Network.PeerSelection.Bootstrap (UseBootstrapPeers (..),
Expand All @@ -37,23 +45,22 @@ import Cardano.Network.PeerSelection.Governor.PeerSelectionState qualified as Ca
import Cardano.Network.PeerSelection.PeerTrustable (PeerTrustable (..))
import Cardano.Network.PeerSelection.PublicRootPeers qualified as Cardano.PublicRootPeers
import Cardano.Network.PeerSelection.State.LocalRootPeers qualified as LocalRootPeers
import Control.Exception (assert)
import Data.Map.Strict (Map)
import Data.Map.Strict qualified as Map
import Data.Set (Set)
import Ouroboros.Network.Block (HeaderHash, SlotNo, atSlot, pattern BlockPoint,
withHash)
import Ouroboros.Network.PeerSelection.Governor.ActivePeers
(jobDemoteActivePeer)
import Ouroboros.Network.PeerSelection.Governor.Monitor (jobVerifyPeerSnapshot)
import Ouroboros.Network.PeerSelection.Governor.Types hiding
(PeerSelectionCounters)
import Ouroboros.Network.PeerSelection.LedgerPeers.Type
(LedgerPeersConsensusInterface (..))
(LedgerPeerSnapshot (..), LedgerPeersConsensusInterface (..),
LedgerPeersKind (..))
import Ouroboros.Network.PeerSelection.PublicRootPeers qualified as PublicRootPeers
import Ouroboros.Network.PeerSelection.State.EstablishedPeers qualified as EstablishedPeers
import Ouroboros.Network.PeerSelection.State.KnownPeers qualified as KnownPeers
import Ouroboros.Network.PeerSelection.State.LocalRootPeers
(LocalRootConfig (..))
import Ouroboros.Network.PeerSelection.Types
import Ouroboros.Network.Point (Block (..))


-- | Used to set 'bootstrapPeersTimeout' for crashing the node in a critical
Expand Down Expand Up @@ -495,8 +502,8 @@ monitorLedgerStateJudgement
(TimedDecision m Cardano.ExtraState extraDebugState extraFlags
(Cardano.ExtraPeers peeraddr) ExtraTrace peeraddr peerconn)
monitorLedgerStateJudgement PeerSelectionActions{
getLedgerStateCtx = ledgerCtx@LedgerPeersConsensusInterface {
lpExtraAPI = Cardano.LedgerPeersConsensusInterface {
getLedgerStateCtx = LedgerPeersConsensusInterface {
lpExtraAPI = lpExtraAPI@Cardano.LedgerPeersConsensusInterface {
Cardano.getLedgerStateJudgement = readLedgerStateJudgement
}
}
Expand All @@ -523,8 +530,9 @@ monitorLedgerStateJudgement PeerSelectionActions{
Decision {
decisionTrace = [ExtraTrace (TraceLedgerStateJudgementChanged lsj)],
decisionJobs = case (lsj, ledgerPeerSnapshot) of
(TooOld, Just ledgerPeerSnapshot') ->
[jobVerifyPeerSnapshot Cardano.srvPrefix ledgerPeerSnapshot' ledgerCtx]
(TooOld, Just (LedgerBigPeerSnapshotV23 point _magic _pools))
| BlockPoint { atSlot, withHash } <- point ->
[jobVerifyPeerSnapshot (atSlot, withHash) lpExtraAPI]
_otherwise -> [],
decisionState = st {
extraState = cpst {
Expand Down Expand Up @@ -675,6 +683,36 @@ waitForSystemToQuiesce st@PeerSelectionState{
| otherwise = GuardedSkip Nothing


-- |This job, which is initiated by monitorLedgerStateJudgement job,
-- verifies whether the provided big ledger pools match up with the
-- ledger state once the node catches up to the slot at which the
-- snapshot was ostensibly taken
--
jobVerifyPeerSnapshot :: (MonadSTM m)
=> (SlotNo, HeaderHash (LedgerPeerSnapshot BigLedgerPeers))
-> Cardano.LedgerPeersConsensusInterface m
-> Job () m (Completion m extraState extraDebugState extraFlags extraPeers extraTrace peeraddr peerconn)
jobVerifyPeerSnapshot (slotNo, theHash)
Cardano.LedgerPeersConsensusInterface { getBlockHash }
= Job job (const (completion False)) () "jobVerifyPeerSnapshot"
where
completion result = return . Completion $ \st _now ->
Decision {
decisionTrace = [TraceVerifyPeerSnapshot result],
decisionState = st,
decisionJobs = [] }

job = do
getBlockHash slotNo $ \elo -> do
Block { blockPointHash } <- atomically elo
let result = theHash == Crypto.castHash blockPointHash
return . Completion $ \st _now ->
Decision {
decisionTrace = [TraceVerifyPeerSnapshot result],
decisionState = st,
decisionJobs = [] }


-- | Extra trace points for `TracePeerSelection`.
--
-- TODO: it ought to be moved to `Types`, but that introduces a circular
Expand Down
Original file line number Diff line number Diff line change
Expand Up @@ -19,7 +19,7 @@ versionTable = { * versionNumber => nodeToClientVersionData }


; as of version 2 (which is no longer supported) we set 16th bit to 1
; 16 / 17 / 18 / 19 / 20 / 21 / 22 / 23
; 16 / 17 / 18 / 19 / 20 / 21 / 22 / 23
versionNumber = 32784 / 32785 / 32786 / 32787 / 32788 / 32789 / 32790 / 32791

; As of version 15 and higher
Expand Down
Original file line number Diff line number Diff line change
Expand Up @@ -1245,6 +1245,7 @@ diffusionSimulationM
Cardano.LedgerPeersConsensusInterface {
Cardano.readFetchMode = pure (PraosFetchMode FetchModeDeadline)
, Cardano.getLedgerStateJudgement = pure TooOld
, Cardano.getBlockHash = \slotNo k -> k retry
, Cardano.updateOutboundConnectionsState =
\a -> do
a' <- readTVar onlyOutboundConnectionsStateVar
Expand Down
Original file line number Diff line number Diff line change
Expand Up @@ -69,6 +69,7 @@ import Ouroboros.Network.PeerSelection.State.KnownPeers qualified as KnownPeers
import Ouroboros.Network.PeerSelection.State.LocalRootPeers
(LocalRootPeers (..))
import Ouroboros.Network.Point
import Ouroboros.Network.Socket ()

import Test.Cardano.Network.PeerSelection.MockEnvironment hiding (tests)
import Test.Cardano.Network.PeerSelection.Utils
Expand Down Expand Up @@ -4382,6 +4383,7 @@ _governorFindingPublicRoots targetNumberOfRootPeers readDomains readUseBootstrap
lpExtraAPI = Cardano.LedgerPeersConsensusInterface {
readFetchMode = pure (PraosFetchMode FetchModeDeadline),
getLedgerStateJudgement = readLedgerStateJudgement,
getBlockHash = \slotNo k -> k retry
updateOutboundConnectionsState = \a -> do
a' <- readTVar olocVar
when (a /= a') $
Expand Down
Original file line number Diff line number Diff line change
Expand Up @@ -485,6 +485,8 @@ mockPeerSelectionActions' tracer
lpExtraAPI = Cardano.LedgerPeersConsensusInterface {
readFetchMode = pure (PraosFetchMode FetchModeDeadline),
getLedgerStateJudgement = readLedgerStateJudgement,
getBlockHash = \slot k ->
k retry,
updateOutboundConnectionsState = \a -> do
a' <- readTVar outboundConnectionsStateVar
when (a /= a') $
Expand Down
Original file line number Diff line number Diff line change
@@ -0,0 +1,11 @@
<!--
A new scriv changelog fragment.
Uncomment the section that is right (remove the HTML comment wrapper).
For top level release notes, leave all the headers commented out.
-->


### Breaking

- Added `NodeToClientVersionV23`
Loading
Loading