Skip to content

Commit

Permalink
Integrate Bootstrap Peers
Browse files Browse the repository at this point in the history
  • Loading branch information
bolt12 committed Sep 27, 2023
1 parent 8e7d591 commit f0938b7
Show file tree
Hide file tree
Showing 13 changed files with 261 additions and 155 deletions.
86 changes: 65 additions & 21 deletions cardano-node/src/Cardano/Node/Configuration/TopologyP2P.hs
Original file line number Diff line number Diff line change
Expand Up @@ -46,7 +46,9 @@ import Cardano.Node.Types
import Cardano.Tracing.OrphanInstances.Network ()
import Control.Applicative (Alternative (..))
import Ouroboros.Network.NodeToNode (PeerAdvertise (..))
import Ouroboros.Network.PeerSelection.LedgerPeers (UseLedgerAfter (..))
import Ouroboros.Network.PeerSelection.Bootstrap (UseBootstrapPeers (..))
import Ouroboros.Network.PeerSelection.LedgerPeers.Type (UseLedgerPeers (..))
import Ouroboros.Network.PeerSelection.PeerTrustable (PeerTrustable (..))
import Ouroboros.Network.PeerSelection.RelayAccessPoint (RelayAccessPoint (..))
import Ouroboros.Network.PeerSelection.State.LocalRootPeers (HotValency (..),
WarmValency (..))
Expand All @@ -56,7 +58,7 @@ data NodeSetup = NodeSetup
, nodeIPv4Address :: !(Maybe NodeIPv4Address)
, nodeIPv6Address :: !(Maybe NodeIPv6Address)
, producers :: ![RootConfig]
, useLedger :: !UseLedger
, useLedger :: !UseLedgerPeers
} deriving (Eq, Show)

instance FromJSON NodeSetup where
Expand All @@ -66,16 +68,16 @@ instance FromJSON NodeSetup where
<*> o .: "nodeIPv4Address"
<*> o .: "nodeIPv6Address"
<*> o .: "producers"
<*> o .:? "useLedgerAfterSlot" .!= UseLedger DontUseLedger
<*> o .:? "useLedgerPeers" .!= DontUseLedgerPeers

instance ToJSON NodeSetup where
toJSON ns =
object
[ "nodeId" .= nodeId ns
, "nodeIPv4Address" .= nodeIPv4Address ns
, "nodeIPv6Address" .= nodeIPv6Address ns
, "producers" .= producers ns
, "useLedgerAfterSlot" .= useLedger ns
[ "nodeId" .= nodeId ns
, "nodeIPv4Address" .= nodeIPv4Address ns
, "nodeIPv6Address" .= nodeIPv6Address ns
, "producers" .= producers ns
, "useLedgerPeers" .= useLedger ns
]


Expand All @@ -88,7 +90,7 @@ data RootConfig = RootConfig
-- or domain name and a port number.
, rootAdvertise :: PeerAdvertise
-- ^ 'advertise' configures whether the root should be advertised through
-- gossip.
-- peer sharing.
} deriving (Eq, Show)

instance FromJSON RootConfig where
Expand Down Expand Up @@ -124,6 +126,9 @@ data LocalRootPeersGroup = LocalRootPeersGroup
{ localRoots :: RootConfig
, hotValency :: HotValency
, warmValency :: WarmValency
, peerTrustable :: PeerTrustable
-- ^ 'trustable' configures whether the root should be trusted in fallback
-- state.
} deriving (Eq, Show)

-- | Does not use the 'FromJSON' instance of 'RootConfig', so that
Expand All @@ -137,6 +142,7 @@ instance FromJSON LocalRootPeersGroup where
<$> parseJSON (Object o)
<*> pure hv
<*> o .:? "warmValency" .!= WarmValency v
<*> o .:? "peerTrustable" .!= IsNotTrustable

instance ToJSON LocalRootPeersGroup where
toJSON lrpg =
Expand All @@ -145,6 +151,7 @@ instance ToJSON LocalRootPeersGroup where
, "advertise" .= rootAdvertise (localRoots lrpg)
, "hotValency" .= hotValency lrpg
, "warmValency" .= warmValency lrpg
, "peerTrustable" .= peerTrustable lrpg
]

newtype LocalRootPeersGroups = LocalRootPeersGroups
Expand All @@ -167,21 +174,23 @@ instance FromJSON PublicRootPeers where
instance ToJSON PublicRootPeers where
toJSON = toJSON . publicRoots

data NetworkTopology = RealNodeTopology !LocalRootPeersGroups ![PublicRootPeers] !UseLedger
data NetworkTopology = RealNodeTopology !LocalRootPeersGroups ![PublicRootPeers] !UseLedgerPeers !UseBootstrapPeers
deriving (Eq, Show)

instance FromJSON NetworkTopology where
parseJSON = withObject "NetworkTopology" $ \o ->
RealNodeTopology <$> (o .: "localRoots" )
<*> (o .: "publicRoots" )
<*> (o .:? "useLedgerAfterSlot" .!= UseLedger DontUseLedger)
RealNodeTopology <$> (o .: "localRoots" )
<*> (o .: "publicRoots" )
<*> (o .:? "useLedgerPeers" .!= DontUseLedgerPeers )
<*> (o .:? "useBootstrapPeers" .!= DontUseBootstrapPeers)

instance ToJSON NetworkTopology where
toJSON top =
case top of
RealNodeTopology lrpg prp ul -> object [ "localRoots" .= lrpg
, "publicRoots" .= prp
, "useLedgerAfterSlot" .= ul
RealNodeTopology lrpg prp ul ubp -> object [ "localRoots" .= lrpg
, "publicRoots" .= prp
, "useLedgerPeers" .= ul
, "useBootstrapPeers" .= ubp
]

--
Expand All @@ -198,10 +207,12 @@ instance FromJSON (Legacy a) => FromJSON (Legacy [a]) where
instance FromJSON (Legacy LocalRootPeersGroup) where
parseJSON = withObject "LocalRootPeersGroup" $ \o -> do
hv@(HotValency v) <- o .: "hotValency"
wv <- o .:? "warmValency" .!= WarmValency v
fmap Legacy $ LocalRootPeersGroup
<$> o .: "localRoots"
<*> pure hv
<*> pure (WarmValency v)
<*> pure wv
<*> o .: "peerTrustable"

instance FromJSON (Legacy LocalRootPeersGroups) where
parseJSON = withObject "LocalRootPeersGroups" $ \o ->
Expand All @@ -216,9 +227,10 @@ instance FromJSON (Legacy PublicRootPeers) where
instance FromJSON (Legacy NetworkTopology) where
parseJSON = fmap Legacy
. withObject "NetworkTopology" (\o ->
RealNodeTopology <$> fmap getLegacy (o .: "LocalRoots")
<*> fmap getLegacy (o .: "PublicRoots")
<*> (o .:? "useLedgerAfterSlot" .!= UseLedger DontUseLedger))
RealNodeTopology <$> fmap getLegacy (o .: "LocalRoots")
<*> fmap getLegacy (o .: "PublicRoots")
<*> (o .:? "useLedgerPeers" .!= DontUseLedgerPeers)
<*> pure DontUseBootstrapPeers)

-- | Read the `NetworkTopology` configuration from the specified file.
--
Expand All @@ -231,7 +243,12 @@ readTopologyFile tr nc = do
Left e -> return . Left $ handler e
Right bs ->
let bs' = LBS.fromStrict bs in
first handlerJSON (eitherDecode bs')
(case eitherDecode bs' of
Left err -> Left (handlerJSON err)
Right t
| hasBootstrapChance t -> Right t
| otherwise -> Left handlerBootstrap
)
`combine`
first handlerJSON (eitherDecode bs')

Expand Down Expand Up @@ -259,6 +276,14 @@ readTopologyFile tr nc = do
, "configuration flag. "
, Text.pack err
]
handlerBootstrap :: Text
handlerBootstrap = mconcat
[ "You seem to have not configured any trustable peer. "
, "This is important in order for the node to make progress "
, "in bootstrap mode. Make sure you provide at least one bootstrap peer "
, "source (by setting useBootstrapPeer topology file option) "
, "or mark a local root peer as trustable. "
]

readTopologyFileOrError :: Tracer IO (StartupTrace blk)
-> NodeConfiguration -> IO NetworkTopology
Expand All @@ -267,3 +292,22 @@ readTopologyFileOrError tr nc =
>>= either (\err -> error $ "Cardano.Node.Configuration.TopologyP2P.readTopologyFile: "
<> Text.unpack err)
pure

--
-- Checking for chance of progress in bootstrap phase
--

-- | This function returns false if non-trustable peers are configured
--
hasBootstrapChance :: NetworkTopology -> Bool
hasBootstrapChance (RealNodeTopology (LocalRootPeersGroups lprgs) _ _ ubp) =
case ubp of
DontUseBootstrapPeers -> anyTrustable
UseBootstrapPeers [] -> anyTrustable
UseBootstrapPeers (_:_) -> True
where
anyTrustable =
any (\(LocalRootPeersGroup _ _ _ pt) -> case pt of
IsNotTrustable -> False
IsTrustable -> True
) lprgs
52 changes: 33 additions & 19 deletions cardano-node/src/Cardano/Node/Run.hs
Original file line number Diff line number Diff line change
Expand Up @@ -11,6 +11,7 @@
{-# LANGUAGE TypeApplications #-}

{-# OPTIONS_GHC -Wno-unused-imports #-}
{-# LANGUAGE TupleSections #-}

#if !defined(mingw32_HOST_OS)
#define UNIX
Expand Down Expand Up @@ -100,7 +101,6 @@ import qualified Ouroboros.Network.Diffusion.P2P as P2P
import Ouroboros.Network.NodeToClient (LocalAddress (..), LocalSocket (..))
import Ouroboros.Network.NodeToNode (AcceptedConnectionsLimit (..), ConnectionId,
PeerSelectionTargets (..), RemoteAddress)
import Ouroboros.Network.PeerSelection.LedgerPeers (UseLedgerAfter (..))
import Ouroboros.Network.PeerSelection.RelayAccessPoint (RelayAccessPoint (..))
import Ouroboros.Network.Subscription (DnsSubscriptionTarget (..),
IPSubscriptionTarget (..))
Expand All @@ -122,6 +122,9 @@ import Cardano.Node.TraceConstraints (TraceConstraints)
import Cardano.Tracing.Tracers
import Ouroboros.Network.PeerSelection.PeerSharing (PeerSharing (..))
import Ouroboros.Network.PeerSelection.State.LocalRootPeers (HotValency, WarmValency)
import Ouroboros.Network.PeerSelection.LedgerPeers.Type (UseLedgerPeers)
import Ouroboros.Network.PeerSelection.PeerTrustable (PeerTrustable)
import Ouroboros.Network.PeerSelection.Bootstrap (UseBootstrapPeers)

{- HLINT ignore "Fuse concatMap/map" -}
{- HLINT ignore "Redundant <$>" -}
Expand Down Expand Up @@ -434,10 +437,11 @@ handleSimpleNode blockType runP p2pMode tracers nc onKernel = do
traceWith (startupTracer tracers)
$ NetworkConfig localRoots
publicRoots
(useLedgerAfterSlot nt)
(useLedgerPeers nt)
localRootsVar <- newTVarIO localRoots
publicRootsVar <- newTVarIO publicRoots
useLedgerVar <- newTVarIO (useLedgerAfterSlot nt)
useLedgerVar <- newTVarIO (useLedgerPeers nt)
useBootstrapVar <- newTVarIO (useBootstrapPeers nt)
#ifdef UNIX
-- initial `SIGHUP` handler, which only rereads the topology file but
-- doesn't update block forging. The latter is only possible once
Expand All @@ -458,6 +462,7 @@ handleSimpleNode blockType runP p2pMode tracers nc onKernel = do
(readTVar localRootsVar)
(readTVar publicRootsVar)
(readTVar useLedgerVar)
(readTVar useBootstrapVar)
in
Node.run
nodeArgs {
Expand Down Expand Up @@ -586,9 +591,9 @@ installP2PSigHUPHandler :: Tracer IO (StartupTrace blk)
-> Api.BlockType blk
-> NodeConfiguration
-> NodeKernel IO RemoteAddress (ConnectionId LocalAddress) blk
-> StrictTVar IO [(HotValency, WarmValency, Map RelayAccessPoint PeerAdvertise)]
-> StrictTVar IO [(HotValency, WarmValency, Map RelayAccessPoint (PeerAdvertise, PeerTrustable))]
-> StrictTVar IO (Map RelayAccessPoint PeerAdvertise)
-> StrictTVar IO UseLedgerAfter
-> StrictTVar IO UseLedgerPeers
-> IO ()
#ifndef UNIX
installP2PSigHUPHandler _ _ _ _ _ _ _ = return ()
Expand Down Expand Up @@ -675,9 +680,9 @@ updateBlockForging startupTracer blockType nodeKernel nc = do

updateTopologyConfiguration :: Tracer IO (StartupTrace blk)
-> NodeConfiguration
-> StrictTVar IO [(HotValency, WarmValency, Map RelayAccessPoint PeerAdvertise)]
-> StrictTVar IO [(HotValency, WarmValency, Map RelayAccessPoint (PeerAdvertise, PeerTrustable))]
-> StrictTVar IO (Map RelayAccessPoint PeerAdvertise)
-> StrictTVar IO UseLedgerAfter
-> StrictTVar IO UseLedgerPeers
-> IO ()
updateTopologyConfiguration startupTracer nc localRootsVar publicRootsVar useLedgerVar = do
traceWith startupTracer NetworkConfigUpdate
Expand All @@ -690,11 +695,11 @@ updateTopologyConfiguration startupTracer nc localRootsVar publicRootsVar useLed
Right nt -> do
let (localRoots, publicRoots) = producerAddresses nt
traceWith startupTracer
$ NetworkConfig localRoots publicRoots (useLedgerAfterSlot nt)
$ NetworkConfig localRoots publicRoots (useLedgerPeers nt)
atomically $ do
writeTVar localRootsVar localRoots
writeTVar publicRootsVar publicRoots
writeTVar useLedgerVar (useLedgerAfterSlot nt)
writeTVar useLedgerVar (useLedgerPeers nt)
#endif

--------------------------------------------------------------------------------
Expand Down Expand Up @@ -748,11 +753,12 @@ checkVRFFilePermissions (File vrfPrivKey) = do

mkP2PArguments
:: NodeConfiguration
-> STM IO [(HotValency, WarmValency, Map RelayAccessPoint PeerAdvertise)]
-> STM IO [(HotValency, WarmValency, Map RelayAccessPoint (PeerAdvertise, PeerTrustable))]
-- ^ non-overlapping local root peers groups; the 'Int' denotes the
-- valency of its group.
-> STM IO (Map RelayAccessPoint PeerAdvertise)
-> STM IO UseLedgerAfter
-> STM IO UseLedgerPeers
-> STM IO UseBootstrapPeers
-> Diffusion.ExtraArguments 'Diffusion.P2P IO
mkP2PArguments NodeConfiguration {
ncTargetNumberOfRootPeers,
Expand All @@ -768,12 +774,14 @@ mkP2PArguments NodeConfiguration {
}
daReadLocalRootPeers
daReadPublicRootPeers
daReadUseLedgerAfter =
daReadUseLedgerPeers
daReadUseBootstrapPeers =
Diffusion.P2PArguments P2P.ArgumentsExtra
{ P2P.daPeerSelectionTargets
, P2P.daReadLocalRootPeers
, P2P.daReadPublicRootPeers
, P2P.daReadUseLedgerAfter
, P2P.daReadUseLedgerPeers
, P2P.daReadUseBootstrapPeers
, P2P.daProtocolIdleTimeout = ncProtocolIdleTimeout
, P2P.daTimeWaitTimeout = ncTimeWaitTimeout
, P2P.daDeadlineChurnInterval = 3300
Expand Down Expand Up @@ -821,21 +829,27 @@ producerAddressesNonP2P nt =

producerAddresses
:: NetworkTopology
-> ([(HotValency, WarmValency, Map RelayAccessPoint PeerAdvertise)], Map RelayAccessPoint PeerAdvertise)
-> ([(HotValency, WarmValency, Map RelayAccessPoint (PeerAdvertise, PeerTrustable))], Map RelayAccessPoint PeerAdvertise)
producerAddresses nt =
case nt of
RealNodeTopology lrpg prp _ ->
RealNodeTopology lrpg prp _ _ ->
( map (\lrp -> ( hotValency lrp
, warmValency lrp
, Map.fromList $ rootConfigToRelayAccessPoint
, Map.fromList $ map (fmap (, peerTrustable lrp))
$ rootConfigToRelayAccessPoint
$ localRoots lrp
)
)
(groups lrpg)
, foldMap (Map.fromList . rootConfigToRelayAccessPoint . publicRoots) prp
)

useLedgerAfterSlot
useLedgerPeers
:: NetworkTopology
-> UseLedgerAfter
useLedgerAfterSlot (RealNodeTopology _ _ (UseLedger ul)) = ul
-> UseLedgerPeers
useLedgerPeers (RealNodeTopology _ _ ulp _) = ulp

useBootstrapPeers
:: NetworkTopology
-> UseBootstrapPeers
useBootstrapPeers (RealNodeTopology _ _ _ ubp) = ubp
7 changes: 4 additions & 3 deletions cardano-node/src/Cardano/Node/Startup.hs
Original file line number Diff line number Diff line change
Expand Up @@ -42,7 +42,6 @@ import Ouroboros.Network.Magic (NetworkMagic (..))
import Ouroboros.Network.NodeToClient (LocalAddress (..), LocalSocket,
NodeToClientVersion)
import Ouroboros.Network.NodeToNode (DiffusionMode (..), NodeToNodeVersion, PeerAdvertise)
import Ouroboros.Network.PeerSelection.LedgerPeers (UseLedgerAfter (..))
import Ouroboros.Network.PeerSelection.RelayAccessPoint (RelayAccessPoint)
import Ouroboros.Network.Subscription.Dns (DnsSubscriptionTarget (..))
import Ouroboros.Network.Subscription.Ip (IPSubscriptionTarget (..))
Expand All @@ -54,6 +53,8 @@ import Cardano.Node.Protocol (ProtocolInstantiationError)
import Cardano.Node.Protocol.Types (SomeConsensusProtocol (..))

import Cardano.Git.Rev (gitRev)
import Ouroboros.Network.PeerSelection.LedgerPeers.Type (UseLedgerPeers)
import Ouroboros.Network.PeerSelection.PeerTrustable (PeerTrustable)
import Ouroboros.Network.PeerSelection.State.LocalRootPeers (HotValency, WarmValency)
import Paths_cardano_node (version)

Expand Down Expand Up @@ -111,9 +112,9 @@ data StartupTrace blk =
-- | Log peer-to-peer network configuration, either on startup or when its
-- updated.
--
| NetworkConfig [(HotValency, WarmValency, Map RelayAccessPoint PeerAdvertise)]
| NetworkConfig [(HotValency, WarmValency, Map RelayAccessPoint (PeerAdvertise, PeerTrustable))]
(Map RelayAccessPoint PeerAdvertise)
UseLedgerAfter
UseLedgerPeers

-- | Warn when 'EnableP2P' is set.
| P2PWarning
Expand Down
Loading

0 comments on commit f0938b7

Please sign in to comment.