Skip to content
Open
Show file tree
Hide file tree
Changes from 4 commits
Commits
Show all changes
24 commits
Select commit Hold shift + click to select a range
5d2e86d
Add behind firewall flag to local root config
the-headless-ghost Nov 8, 2025
c2e3eec
Add ConnectionMode to AcquireOutboundConnection
the-headless-ghost Nov 9, 2025
a12338a
CM and jobPromoteColdPeer fixes
the-headless-ghost Nov 17, 2025
405b005
Add diffusion property test
the-headless-ghost Nov 17, 2025
e8fcd54
Update cardano-diffusion/tests/lib/Test/Cardano/Network/Diffusion/Tes…
the-headless-ghost Dec 5, 2025
a496ced
Update ouroboros-network/framework/lib/Ouroboros/Network/ConnectionMa…
the-headless-ghost Dec 5, 2025
c3e7c29
Update cardano-diffusion/tests/lib/Test/Cardano/Network/Diffusion/Tes…
the-headless-ghost Dec 5, 2025
f0ef9bb
Update cardano-diffusion/tests/lib/Test/Cardano/Network/Diffusion/Tes…
the-headless-ghost Dec 5, 2025
b82fd8d
Naming fix
the-headless-ghost Dec 5, 2025
baa81e7
Update ouroboros-network/framework/lib/Ouroboros/Network/ConnectionMa…
the-headless-ghost Dec 5, 2025
b843f5c
swap establishPeerConnection arguments
the-headless-ghost Dec 5, 2025
1fedb07
Replace ConnectionMode with Provenance
the-headless-ghost Dec 5, 2025
00072a1
correct var binding name
the-headless-ghost Dec 5, 2025
09c19d2
Reuse FromJSON instance for RootConfig
the-headless-ghost Dec 5, 2025
a0b92e2
Remove ConnectionMode from the behind firewall changelog fragment
the-headless-ghost Dec 5, 2025
cc2519c
remove mutableConnState from failed aqcuire outbound connection
the-headless-ghost Dec 5, 2025
6858015
Rename connection mode variables
the-headless-ghost Dec 5, 2025
53beda8
EstablishedPeers cleanup
the-headless-ghost Dec 10, 2025
01d2727
Fix comment for AcquireOutboundConnection
the-headless-ghost Dec 10, 2025
34a5105
Replace local root peers fields with provenance fields
the-headless-ghost Dec 10, 2025
0ef4c30
Update changelog fragment
the-headless-ghost Dec 10, 2025
2e20fd0
Fix naming around TrInboundConnectionNotFound
the-headless-ghost Dec 10, 2025
8fecf76
Cleanup: Formatting, comments
the-headless-ghost Dec 10, 2025
0364702
Remove provenance from InboundConnectionNotFound
the-headless-ghost Dec 11, 2025
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
@@ -0,0 +1,10 @@
<!--
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.
-->

### Non-Breaking

- Added a property test to verify that the node never connects to peers behind a firewall.
Original file line number Diff line number Diff line change
Expand Up @@ -30,5 +30,6 @@ isValidTrustedPeerConfiguration
IsTrustable -> not
. null
. rootAccessPoints
. rootConfig
$ localRoots
) lprgs
155 changes: 125 additions & 30 deletions cardano-diffusion/tests/lib/Test/Cardano/Network/Diffusion/Testnet.hs

Large diffs are not rendered by default.

Original file line number Diff line number Diff line change
Expand Up @@ -3206,7 +3206,6 @@ prop_governor_target_established_above (MaxTime maxTime) env =
<*> govInProgressIneligibleSig
<*> demotionOpportunitiesIgnoredTooLong)


-- | Like 'prop_governor_target_established_above' but for big ledger peers.
--
prop_governor_target_established_big_ledger_peers_above
Expand Down Expand Up @@ -4431,8 +4430,8 @@ prop_issue_3550 = prop_governor_target_established_below defaultMaxTime $
(PeerAddr 29,[],GovernorScripts {peerShareScript = Script (Nothing :| []), peerSharingScript = Script (PeerSharingDisabled :| []), connectionScript = Script ((ToWarm,NoDelay) :| [(ToCold,NoDelay),(Noop,NoDelay)])})
],
localRootPeers = LocalRootPeers.fromGroups
[ (1, 1, Map.fromList [(PeerAddr 16, LocalRootConfig DoAdvertisePeer InitiatorAndResponderDiffusionMode IsNotTrustable)])
, (1, 1, Map.fromList [(PeerAddr 4, LocalRootConfig DoAdvertisePeer InitiatorAndResponderDiffusionMode IsNotTrustable)])
[ (1, 1, Map.fromList [(PeerAddr 16, LocalRootConfig DoAdvertisePeer InitiatorAndResponderDiffusionMode False IsNotTrustable)])
, (1, 1, Map.fromList [(PeerAddr 4, LocalRootConfig DoAdvertisePeer InitiatorAndResponderDiffusionMode False IsNotTrustable)])
],
publicRootPeers = Cardano.PublicRootPeers.fromPublicRootPeers
(Map.fromList [ (PeerAddr 14, DoNotAdvertisePeer)
Expand Down Expand Up @@ -4479,7 +4478,7 @@ prop_issue_3515 = prop_governor_nolivelock $
peerSharingScript = Script (PeerSharingDisabled :| []),
connectionScript = Script ((ToCold,NoDelay) :| [(Noop,NoDelay)])
})],
localRootPeers = LocalRootPeers.fromGroups [(1,1,Map.fromList [(PeerAddr 10, LocalRootConfig DoAdvertisePeer InitiatorAndResponderDiffusionMode IsNotTrustable)])],
localRootPeers = LocalRootPeers.fromGroups [(1,1,Map.fromList [(PeerAddr 10, LocalRootConfig DoAdvertisePeer InitiatorAndResponderDiffusionMode False IsNotTrustable)])],
publicRootPeers = PublicRootPeers.empty Cardano.ExtraPeers.empty,
targets = Script . NonEmpty.fromList $ targets'',
pickKnownPeersForPeerShare = Script (PickFirst :| []),
Expand Down Expand Up @@ -4521,7 +4520,7 @@ prop_issue_3494 = prop_governor_nofail $
peerSharingScript = Script (PeerSharingDisabled :| []),
connectionScript = Script ((ToCold,NoDelay) :| [(Noop,NoDelay)])
})],
localRootPeers = LocalRootPeers.fromGroups [(1,1,Map.fromList [(PeerAddr 64, LocalRootConfig DoAdvertisePeer InitiatorAndResponderDiffusionMode IsNotTrustable)])],
localRootPeers = LocalRootPeers.fromGroups [(1,1,Map.fromList [(PeerAddr 64, LocalRootConfig DoAdvertisePeer InitiatorAndResponderDiffusionMode False IsNotTrustable)])],
publicRootPeers = PublicRootPeers.empty Cardano.ExtraPeers.empty,
targets = Script . NonEmpty.fromList $ targets'',
pickKnownPeersForPeerShare = Script (PickFirst :| []),
Expand Down Expand Up @@ -4571,8 +4570,8 @@ prop_issue_3233 = prop_governor_nolivelock $
(PeerAddr 15,[],GovernorScripts {peerShareScript = Script (Just ([],PeerShareTimeSlow) :| []), peerSharingScript = Script (PeerSharingDisabled :| []), connectionScript = Script ((Noop,NoDelay) :| [])})
],
localRootPeers = LocalRootPeers.fromGroups
[ (1, 1, Map.fromList [(PeerAddr 15, LocalRootConfig DoAdvertisePeer InitiatorAndResponderDiffusionMode IsNotTrustable)])
, (1, 1, Map.fromList [(PeerAddr 13, LocalRootConfig DoAdvertisePeer InitiatorAndResponderDiffusionMode IsNotTrustable)])
[ (1, 1, Map.fromList [(PeerAddr 15, LocalRootConfig DoAdvertisePeer InitiatorAndResponderDiffusionMode False IsNotTrustable)])
, (1, 1, Map.fromList [(PeerAddr 13, LocalRootConfig DoAdvertisePeer InitiatorAndResponderDiffusionMode False IsNotTrustable)])
],
publicRootPeers = Cardano.PublicRootPeers.fromPublicRootPeers
(Map.fromList [(PeerAddr 4, DoNotAdvertisePeer)]),
Expand Down
Original file line number Diff line number Diff line change
Expand Up @@ -62,6 +62,7 @@ import Control.Monad.IOSim
import Control.Tracer (Tracer (..), contramap, traceWith)

import Ouroboros.Network.BlockFetch (FetchMode (..), PraosFetchMode (..))
import Ouroboros.Network.ConnectionManager.Types (ConnectionMode (..))
import Ouroboros.Network.DiffusionMode
import Ouroboros.Network.ExitPolicy
import Ouroboros.Network.PeerSelection hiding (requestPublicRootPeers)
Expand Down Expand Up @@ -550,8 +551,8 @@ mockPeerSelectionActions' tracer
traceWith tracer (TraceEnvPeerShareResult addr peeraddrs)
return (PeerSharingResult peeraddrs)

establishPeerConnection :: IsBigLedgerPeer -> DiffusionMode -> PeerAddr -> m (PeerConn m)
establishPeerConnection _ _ peeraddr = do
establishPeerConnection :: IsBigLedgerPeer -> DiffusionMode -> PeerAddr -> ConnectionMode -> m (PeerConn m)
establishPeerConnection _ _ peeraddr _ = do
--TODO: add support for variable delays and synchronous failure
traceWith tracer (TraceEnvEstablishConn peeraddr)
threadDelay 1
Expand Down
Original file line number Diff line number Diff line change
@@ -0,0 +1,22 @@
<!--
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

- Changed the type of `localRoots` to `LocalRoots`.
- Modified `AcquireOutboundConnection` to include an additional parameter: `ConnectionMode`.
- `acquireOutboundConnectionImpl` only creates a new connection if the `ConnectionMode` function permits it.
- `jobPromoteColdPeer` only creates a new connection if no inbound connection is found and the peer is not behind a firewall.

### Non-Breaking

- Added `LocalRoots` type in `Ouroboros.Network.PeerSelection.State.LocalRootPeers` with the following fields:
- `rootConfig` of type `RootConfig`
- `behindFirewall` of type `Bool`
- Added `localRootBehindFirewall` field to `LocalRootConfig`.
- Added a new sum type: `ConnectionMode`.
- Added a new constructor `InboundConnectionNotFound` for `ConnectionManagerError`.
4 changes: 2 additions & 2 deletions ouroboros-network/demo/connection-manager.hs
Original file line number Diff line number Diff line change
Expand Up @@ -569,9 +569,9 @@ bidirectionalExperiment
(HandlerError
UnversionedProtocol))
connect n cm | n <= 1 =
acquireOutboundConnection cm InitiatorAndResponderDiffusionMode remoteAddr
acquireOutboundConnection cm InitiatorAndResponderDiffusionMode remoteAddr CreateNewIfNoInbound
connect n cm =
acquireOutboundConnection cm InitiatorAndResponderDiffusionMode remoteAddr
acquireOutboundConnection cm InitiatorAndResponderDiffusionMode remoteAddr CreateNewIfNoInbound
`catch` \(_ :: IOException) -> threadDelay 1
>> connect (pred n) cm
`catch` \(_ :: Mux.Error) -> threadDelay 1
Expand Down
Original file line number Diff line number Diff line change
Expand Up @@ -1338,8 +1338,9 @@ with args@Arguments {
-> ConnectionHandlerFn handlerTrace socket peerAddr handle handleError version versionData m
-> DiffusionMode
-> peerAddr
-> ConnectionMode
-> m (Connected peerAddr handle handleError)
acquireOutboundConnectionImpl stateVar stdGenVar handler diffusionMode peerAddr = do
acquireOutboundConnectionImpl stateVar stdGenVar handler diffusionMode peerAddr connectionMode = do
let provenance = Outbound
traceWith tracer (TrIncludeConnection provenance peerAddr)
(trace, mutableConnState@MutableConnState { connVar, connStateId }
Expand Down Expand Up @@ -1463,20 +1464,30 @@ with args@Arguments {
:: MutableConnState peerAddr handle handleError
version m)
<- State.newMutableConnState peerAddr connStateIdSupply connState'
-- TODO: label `connVar` using 'ConnectionId'
labelTVar connVar ("conn-state-" ++ show peerAddr)

writeTMVar stateVar
(State.insertUnknownLocalAddr peerAddr mutableConnState state)
return ( Just (Left (TransitionTrace
connStateId
Transition {
fromState = Unknown,
toState = Known connState'
}))
, mutableConnState
, Right Nowhere
)

-- Only proceed if creating a new connection is allowed
if inboundRequired connectionMode
then do
return ( Just (Right (TrInboundConnectionNotFound connectionMode peerAddr))
, mutableConnState
, Left (withCallStack
(InboundConnectionNotFound connectionMode peerAddr))
)
else do
-- TODO: label `connVar` using 'ConnectionId'
labelTVar connVar ("conn-state-" ++ show peerAddr)

writeTMVar stateVar
(State.insertUnknownLocalAddr peerAddr mutableConnState state)
return ( Just (Left (TransitionTrace
connStateId
Transition {
fromState = Unknown,
toState = Known connState'
}))
, mutableConnState
, Right Nowhere
)

traverse_ (either (traceWith trTracer) (traceWith tracer)) trace
traceCounters stateVar
Expand Down Expand Up @@ -2468,6 +2479,7 @@ withCallStack k = k callStack
--
data Trace peerAddr handlerTrace
= TrIncludeConnection Provenance peerAddr
| TrInboundConnectionNotFound ConnectionMode peerAddr
| TrReleaseConnection Provenance (ConnectionId peerAddr)
| TrConnect (Maybe peerAddr) -- ^ local address
peerAddr -- ^ remote address
Expand Down
Original file line number Diff line number Diff line change
Expand Up @@ -114,6 +114,8 @@ module Ouroboros.Network.ConnectionManager.Types
, resultInState
, DemotedToColdRemoteTr (..)
, AcquireOutboundConnection
, ConnectionMode (..)
, inboundRequired
, IncludeInboundConnection
-- *** Outbound side
, acquireOutboundConnection
Expand Down Expand Up @@ -497,9 +499,24 @@ data Connected peerAddr handle handleError =
--
| Disconnected !(ConnectionId peerAddr) !(DisconnectionException handleError)

-- | Describes the behavior for handling connections when no inbound connection
-- is found.
-- - 'CreateNewIfNoInbound': If no inbound connection exists, create a new
-- conection.
-- - 'RequireInbound': Strictly require an inbound connection; fail if none
-- exists.
data ConnectionMode
= CreateNewIfNoInbound
| RequireInbound
deriving Show

inboundRequired :: ConnectionMode -> Bool
inboundRequired RequireInbound = True
inboundRequired _other = False

type AcquireOutboundConnection peerAddr handle handleError m
= DiffusionMode -> peerAddr -> m (Connected peerAddr handle handleError)
= DiffusionMode -> peerAddr -> ConnectionMode -> m (Connected peerAddr handle handleError)

type IncludeInboundConnection socket peerAddr handle handleError m
= Word32
-- ^ inbound connections hard limit.
Expand Down Expand Up @@ -723,6 +740,11 @@ data ConnectionManagerError peerAddr
--
| ForbiddenConnection !(ConnectionId peerAddr) !CallStack

-- | No matching inbound connection found and creating new connection is
-- not allowed.
--
| InboundConnectionNotFound !ConnectionMode !peerAddr !CallStack

-- | Connections that would be forbidden by the kernel (@TCP@ semantics).
--
| ImpossibleConnection !(ConnectionId peerAddr) !CallStack
Expand Down Expand Up @@ -774,6 +796,14 @@ instance ( Show peerAddr
, "\n"
, prettyCallStack cs
]
displayException (InboundConnectionNotFound connMode peerAddr cs) =
concat [ "No matching inbound connection found and creating new connection is not allowed with peer "
, show connMode
, "\n"
, show peerAddr
, "\n"
, prettyCallStack cs
]
displayException (ConnectionTerminating connId cs) =
concat [ "Connection terminating "
, show connId
Expand Down
Original file line number Diff line number Diff line change
Expand Up @@ -817,7 +817,7 @@ prop_valid_transitions (Fixed rnd) (SkewedBool bindToLocalAddress) scheduleMap =
-- handshake negotiation.
timeout (1 + 5 + testTimeWaitTimeout)
(acquireOutboundConnection
connectionManager InitiatorAndResponderDiffusionMode addr))
connectionManager InitiatorAndResponderDiffusionMode addr CreateNewIfNoInbound))
`catches`
[ Handler $ \(e :: IOException) -> return (Left (toException e))
, Handler $ \(e :: SomeConnectionManagerError) ->
Expand Down Expand Up @@ -983,10 +983,11 @@ prop_valid_transitions (Fixed rnd) (SkewedBool bindToLocalAddress) scheduleMap =
Just (SomeConnectionManagerError e@UnknownPeer {}) -> throwIO e

-- If 'ForbiddenConnection' is thrown we let the test continue.
Just (SomeConnectionManagerError ForbiddenConnection {}) -> pure ()
Just (SomeConnectionManagerError ConnectionExists {}) -> pure ()
Just (SomeConnectionManagerError ConnectionTerminating {}) -> pure ()
Just (SomeConnectionManagerError ConnectionTerminated {}) -> pure ()
Just (SomeConnectionManagerError ForbiddenConnection {}) -> pure ()
Just (SomeConnectionManagerError ConnectionExists {}) -> pure ()
Just (SomeConnectionManagerError ConnectionTerminating {}) -> pure ()
Just (SomeConnectionManagerError ConnectionTerminated {}) -> pure ()
Just (SomeConnectionManagerError InboundConnectionNotFound {}) -> pure ()


-- | This includes the @Overwritten@ transition.
Expand Down
Original file line number Diff line number Diff line change
Expand Up @@ -879,7 +879,7 @@ multinodeExperiment inboundTrTracer trTracer inboundTracer debugTracer cmTracer
case fromException e of
Just SomeAsyncException {} -> Nothing
_ -> Just e)
$ acquireOutboundConnection cm InitiatorAndResponderDiffusionMode remoteAddr
$ acquireOutboundConnection cm InitiatorAndResponderDiffusionMode remoteAddr CreateNewIfNoInbound
case connHandle of
Left _ ->
go connMap
Expand Down
Original file line number Diff line number Diff line change
Expand Up @@ -770,7 +770,7 @@ unidirectionalExperiment stdGen timeouts snocket makeBearer confSock socket clie
replicateM
(numberOfRounds clientAndServerData)
(bracket
(acquireOutboundConnection connectionManager InitiatorOnlyDiffusionMode serverAddr)
(acquireOutboundConnection connectionManager InitiatorOnlyDiffusionMode serverAddr CreateNewIfNoInbound)
(\case
Connected connId _ _ -> releaseOutboundConnection connectionManager connId
Disconnected {} -> error "unidirectionalExperiment: impossible happened")
Expand Down Expand Up @@ -876,7 +876,8 @@ bidirectionalExperiment
(acquireOutboundConnection
connectionManager0
InitiatorAndResponderDiffusionMode
localAddr1))
localAddr1
CreateNewIfNoInbound))
(\case
Connected connId _ _ ->
releaseOutboundConnection
Expand All @@ -902,7 +903,8 @@ bidirectionalExperiment
(acquireOutboundConnection
connectionManager1
InitiatorAndResponderDiffusionMode
localAddr0))
localAddr0
CreateNewIfNoInbound))
(\case
Connected connId _ _ ->
releaseOutboundConnection
Expand Down
Original file line number Diff line number Diff line change
Expand Up @@ -300,43 +300,45 @@ connectionManagerTraceMap
ntnAddr
(ConnectionHandlerTrace ntnVersion ntnVersionData)
-> String
connectionManagerTraceMap (TrIncludeConnection p _) =
connectionManagerTraceMap (TrInboundConnectionNotFound cm _) =
"TrInboundConnectionNotFound " ++ show cm
connectionManagerTraceMap (TrIncludeConnection p _) =
"TrIncludeConnection " ++ show p
connectionManagerTraceMap (TrReleaseConnection p _) =
connectionManagerTraceMap (TrReleaseConnection p _) =
"TrUnregisterConnection " ++ show p
connectionManagerTraceMap TrConnect {} =
connectionManagerTraceMap TrConnect {} =
"TrConnect"
connectionManagerTraceMap (TrConnectError _ _ _) =
connectionManagerTraceMap (TrConnectError _ _ _) =
"TrConnectError"
connectionManagerTraceMap (TrTerminatingConnection p _) =
connectionManagerTraceMap (TrTerminatingConnection p _) =
"TrTerminatingConnection " ++ show p
connectionManagerTraceMap (TrTerminatedConnection p _) =
connectionManagerTraceMap (TrTerminatedConnection p _) =
"TrTerminatedConnection " ++ show p
connectionManagerTraceMap (TrConnectionHandler _ _) =
connectionManagerTraceMap (TrConnectionHandler _ _) =
"TrConnectionHandler"
connectionManagerTraceMap TrShutdown =
connectionManagerTraceMap TrShutdown =
"TrShutdown"
connectionManagerTraceMap (TrConnectionExists p _ as) =
connectionManagerTraceMap (TrConnectionExists p _ as) =
"TrConnectionExists " ++ show p ++ " " ++ show as
connectionManagerTraceMap (TrForbiddenConnection _) =
connectionManagerTraceMap (TrForbiddenConnection _) =
"TrForbiddenConnection"
connectionManagerTraceMap (TrConnectionFailure _) =
connectionManagerTraceMap (TrConnectionFailure _) =
"TrConnectionFailure"
connectionManagerTraceMap (TrConnectionNotFound p _) =
connectionManagerTraceMap (TrConnectionNotFound p _) =
"TrConnectionNotFound " ++ show p
connectionManagerTraceMap (TrForbiddenOperation _ as) =
connectionManagerTraceMap (TrForbiddenOperation _ as) =
"TrForbiddenOperation" ++ show as
connectionManagerTraceMap (TrPruneConnections _ _ _) =
connectionManagerTraceMap (TrPruneConnections _ _ _) =
"TrPruneConnections"
connectionManagerTraceMap (TrConnectionCleanup _) =
connectionManagerTraceMap (TrConnectionCleanup _) =
"TrConnectionCleanup"
connectionManagerTraceMap (TrConnectionTimeWait _) =
connectionManagerTraceMap (TrConnectionTimeWait _) =
"TrConnectionTimeWait"
connectionManagerTraceMap (TrConnectionTimeWaitDone _) =
connectionManagerTraceMap (TrConnectionTimeWaitDone _) =
"TrConnectionTimeWaitDone"
connectionManagerTraceMap (TrConnectionManagerCounters _) =
connectionManagerTraceMap (TrConnectionManagerCounters _) =
"TrConnectionManagerCounters"
connectionManagerTraceMap (TrState _) =
connectionManagerTraceMap (TrState _) =
"TrState"
connectionManagerTraceMap (TrUnexpectedlyFalseAssertion _) =
connectionManagerTraceMap (TrUnexpectedlyFalseAssertion _) =
"TrUnexpectedlyFalseAssertion"
Loading
Loading