Skip to content

Commit

Permalink
Address review comments
Browse files Browse the repository at this point in the history
  • Loading branch information
bolt12 committed Oct 30, 2023
1 parent ce94809 commit 50bab68
Show file tree
Hide file tree
Showing 19 changed files with 252 additions and 137 deletions.
7 changes: 5 additions & 2 deletions docs/network-spec/miniprotocols.tex
Original file line number Diff line number Diff line change
Expand Up @@ -1399,8 +1399,11 @@ \subsection{Server Implementation Details}
function application all the way to diffusion and share the relevant parts of
\texttt{PeerSelectionState} with this function via a \texttt{TVar}.

\subsection{CDDL encoding specification}
\lstinputlisting[style=cddl]{../../ouroboros-network-protocols/test-cddl/specs/peer-sharing.cddl}
\subsection{CDDL encoding specification ($11$ to $12$)}\label{peersharing-cddl}
\lstinputlisting[style=cddl]{../../ouroboros-network-protocols/test-cddl/specs/peer-sharing-v11-12.cddl}

\subsection{CDDL encoding specification ($\geq 13$)}\label{peersharing-cddl}
\lstinputlisting[style=cddl]{../../ouroboros-network-protocols/test-cddl/specs/peer-sharing-v13.cddl}

\section{Pipelining of Mini Protocols}
\label{pipelining}
Expand Down
8 changes: 5 additions & 3 deletions ouroboros-network-api/CHANGELOG.md
Original file line number Diff line number Diff line change
Expand Up @@ -4,11 +4,13 @@

### Breaking changes

- Remote `PeerSharingPrivate` option from the `PeerSharing` data type.
- Rename `NoPeerSharing` and `PeerSharingPublic` to `PeerSharingDisabled` and
* Remote `PeerSharingPrivate` option from the `PeerSharing` data type.
* Rename `NoPeerSharing` and `PeerSharingPublic` to `PeerSharingDisabled` and
`PeerSharingEnabled`, respectively.
- Add new `NodeToNodeV_13` that encodes and decodes the updated `PeerSharing` flag data
* Add new `NodeToNodeV_13` that encodes and decodes the updated `PeerSharing` flag data
type.
* Move remote address codec to 'src/Ouroboros/Network/NodeToNode/Version.hs'.
* Make remote address codec receive 'NodeToNodeVersion'.

### Non-breaking changes

Expand Down
1 change: 1 addition & 0 deletions ouroboros-network-api/ouroboros-network-api.cabal
Original file line number Diff line number Diff line change
Expand Up @@ -45,6 +45,7 @@ library
Ouroboros.Network.PeerSelection.PeerMetric.Type
Ouroboros.Network.PeerSelection.PeerAdvertise
Ouroboros.Network.PeerSelection.PeerSharing
Ouroboros.Network.PeerSelection.PeerSharing.Codec
Ouroboros.Network.PeerSelection.RelayAccessPoint
default-language: Haskell2010
build-depends: base >=4.14 && <4.19,
Expand Down
Original file line number Diff line number Diff line change
Expand Up @@ -23,9 +23,7 @@ import Ouroboros.Network.Handshake.Acceptable (Accept (..),
Acceptable (..))
import Ouroboros.Network.Handshake.Queryable (Queryable (..))
import Ouroboros.Network.Magic
import Ouroboros.Network.PeerSelection.PeerSharing (PeerSharing (..),
combinePeerSharing)

import Ouroboros.Network.PeerSelection.PeerSharing (PeerSharing (..))

-- | Enumeration of node to node protocol versions.
--
Expand Down Expand Up @@ -62,7 +60,7 @@ data NodeToNodeVersion
| NodeToNodeV_13
-- ^ Changes:
--
-- * Adds a fix for PeerSharing handshake negotiation
-- * Added `localPeerSharing` negotiation flag.
deriving (Eq, Ord, Enum, Bounded, Show, Typeable)

nodeToNodeVersionCodec :: CodecCBORTerm (Text, Maybe Int) NodeToNodeVersion
Expand Down Expand Up @@ -134,8 +132,7 @@ instance Acceptable NodeToNodeVersionData where
= Accept NodeToNodeVersionData
{ networkMagic = networkMagic local
, diffusionMode = diffusionMode local `min` diffusionMode remote
, peerSharing = combinePeerSharing (peerSharing local)
(peerSharing remote)
, peerSharing = peerSharing local <> peerSharing remote
, query = query local || query remote
}
| otherwise
Expand Down Expand Up @@ -267,7 +264,6 @@ nodeToNodeCodecCBORTerm version

data ConnectionMode = UnidirectionalMode | DuplexMode


-- | Check whether a version enabling diffusion pipelining has been
-- negotiated.
--
Expand Down
Original file line number Diff line number Diff line change
@@ -1,24 +1,11 @@
{-# LANGUAGE DeriveGeneric #-}

{-# OPTIONS_GHC -Wno-orphans #-}
{-# LANGUAGE InstanceSigs #-}

module Ouroboros.Network.PeerSelection.PeerSharing
( PeerSharing (..)
, combinePeerSharing
, encodePortNumber
, decodePortNumber
, encodeRemoteAddress
, decodeRemoteAddress
) where
module Ouroboros.Network.PeerSelection.PeerSharing (PeerSharing (..)) where

import qualified Codec.CBOR.Decoding as CBOR
import qualified Codec.CBOR.Encoding as CBOR
import Data.Aeson.Types (FromJSON (..), ToJSON (..), Value (..),
withText)
import qualified Data.Text as Text
import GHC.Generics (Generic)
import Network.Socket (PortNumber, SockAddr (..))
import Text.Read (readMaybe)

-- | Is a peer willing to participate in Peer Sharing? If yes are others allowed
-- to share this peer's address?
Expand All @@ -32,69 +19,23 @@ data PeerSharing = PeerSharingDisabled -- ^ Peer does not participate in Peer Sh
| PeerSharingEnabled -- ^ Peer participates in Peer Sharing
deriving (Eq, Show, Read, Generic)

instance FromJSON PeerSharing where
parseJSON = withText "PeerSharing" $ \t ->
case readMaybe (Text.unpack t) of
Nothing -> fail ("PeerSharing.parseJSON: could not parse value: "
++ Text.unpack t)
Just ps -> return ps

instance ToJSON PeerSharing where
toJSON = String . Text.pack . show

-- | Combine two 'PeerSharing' values
--
-- 'PeerSharingDisabled' is the absorbing element
combinePeerSharing :: PeerSharing -> PeerSharing -> PeerSharing
combinePeerSharing PeerSharingDisabled _ = PeerSharingDisabled
combinePeerSharing _ PeerSharingDisabled = PeerSharingDisabled
combinePeerSharing _ _ = PeerSharingEnabled

encodePortNumber :: PortNumber -> CBOR.Encoding
encodePortNumber = CBOR.encodeWord16 . fromIntegral

decodePortNumber :: CBOR.Decoder s PortNumber
decodePortNumber = fromIntegral <$> CBOR.decodeWord16


-- | This encoder should be faithful to the PeerSharing
-- CDDL Specification.
-- | The combination of two 'PeerSharing' values forms a Monoid where the unit
-- is 'PeerSharingEnabled'.
--
-- See the network design document for more details
-- This operation is used in the connection handshake.
--
encodeRemoteAddress :: SockAddr -> CBOR.Encoding
encodeRemoteAddress (SockAddrInet pn w) = CBOR.encodeListLen 3
<> CBOR.encodeWord 0
<> CBOR.encodeWord32 w
<> encodePortNumber pn
encodeRemoteAddress (SockAddrInet6 pn _ (w1, w2, w3, w4) _) = CBOR.encodeListLen 6
<> CBOR.encodeWord 1
<> CBOR.encodeWord32 w1
<> CBOR.encodeWord32 w2
<> CBOR.encodeWord32 w3
<> CBOR.encodeWord32 w4
<> encodePortNumber pn
encodeRemoteAddress (SockAddrUnix _) = error "Should never be encoding a SockAddrUnix!"
instance Semigroup PeerSharing where
(<>) :: PeerSharing -> PeerSharing -> PeerSharing
PeerSharingDisabled <> _ = PeerSharingDisabled
_ <> PeerSharingDisabled = PeerSharingDisabled
_ <> _ = PeerSharingEnabled

-- | This decoder should be faithful to the PeerSharing
-- CDDL Specification.
-- | The Monoid laws are witnessed by the following denotation function:
--
-- See the network design document for more details
-- ⟦_⟧ :: PeerSharing -> All
-- ⟦ PeerSharingDisabled ⟧ = All False
-- ⟦ PeerSharingEnabled ⟧ = All True
--
decodeRemoteAddress :: CBOR.Decoder s SockAddr
decodeRemoteAddress = do
_ <- CBOR.decodeListLen
tok <- CBOR.decodeWord
case tok of
0 -> do
w <- CBOR.decodeWord32
pn <- decodePortNumber
return (SockAddrInet pn w)
1 -> do
w1 <- CBOR.decodeWord32
w2 <- CBOR.decodeWord32
w3 <- CBOR.decodeWord32
w4 <- CBOR.decodeWord32
pn <- decodePortNumber
return (SockAddrInet6 pn 0 (w1, w2, w3, w4) 0)
_ -> fail ("Serialise.decode.SockAddr unexpected tok " ++ show tok)
instance Monoid PeerSharing where
mempty :: PeerSharing
mempty = PeerSharingEnabled
Original file line number Diff line number Diff line change
@@ -0,0 +1,102 @@
module Ouroboros.Network.PeerSelection.PeerSharing.Codec
( encodePortNumber
, decodePortNumber
, encodeRemoteAddress
, decodeRemoteAddress
) where

import qualified Codec.CBOR.Decoding as CBOR
import qualified Codec.CBOR.Encoding as CBOR

import Network.Socket (PortNumber, SockAddr (..))
import Ouroboros.Network.NodeToNode.Version (NodeToNodeVersion (..))

encodePortNumber :: PortNumber -> CBOR.Encoding
encodePortNumber = CBOR.encodeWord16 . fromIntegral

decodePortNumber :: CBOR.Decoder s PortNumber
decodePortNumber = fromIntegral <$> CBOR.decodeWord16


-- | This encoder should be faithful to the PeerSharing
-- CDDL Specification.
--
-- See the network design document for more details
---
-- /Invariant:/ not a unix socket address type.
---
encodeRemoteAddress :: NodeToNodeVersion -> SockAddr -> CBOR.Encoding
encodeRemoteAddress ntnVersion sockAddr
| ntnVersion >= NodeToNodeV_13 =
case sockAddr of
SockAddrInet pn w -> CBOR.encodeListLen 3
<> CBOR.encodeWord 0
<> CBOR.encodeWord32 w
<> encodePortNumber pn
SockAddrInet6 pn _ (w1, w2, w3, w4) _ -> CBOR.encodeListLen 6
<> CBOR.encodeWord 1
<> CBOR.encodeWord32 w1
<> CBOR.encodeWord32 w2
<> CBOR.encodeWord32 w3
<> CBOR.encodeWord32 w4
<> encodePortNumber pn
SockAddrUnix _ -> error "Should never be encoding a SockAddrUnix!"
| otherwise =
case sockAddr of
SockAddrInet pn w -> CBOR.encodeListLen 3
<> CBOR.encodeWord 0
<> CBOR.encodeWord32 w
<> encodePortNumber pn
SockAddrInet6 pn fi (w1, w2, w3, w4) si -> CBOR.encodeListLen 8
<> CBOR.encodeWord 1
<> CBOR.encodeWord32 w1
<> CBOR.encodeWord32 w2
<> CBOR.encodeWord32 w3
<> CBOR.encodeWord32 w4
<> CBOR.encodeWord32 fi
<> CBOR.encodeWord32 si
<> encodePortNumber pn
SockAddrUnix _ -> error "Should never be encoding a SockAddrUnix!"

-- | This decoder should be faithful to the PeerSharing
-- CDDL Specification.
--
-- See the network design document for more details
--
decodeRemoteAddress :: NodeToNodeVersion -> CBOR.Decoder s SockAddr
decodeRemoteAddress ntnVersion
| ntnVersion >= NodeToNodeV_13 = do
_ <- CBOR.decodeListLen
tok <- CBOR.decodeWord
case tok of
0 -> do
w <- CBOR.decodeWord32
pn <- decodePortNumber
return (SockAddrInet pn w)
1 -> do
w1 <- CBOR.decodeWord32
w2 <- CBOR.decodeWord32
w3 <- CBOR.decodeWord32
w4 <- CBOR.decodeWord32
pn <- decodePortNumber
return (SockAddrInet6 pn 0 (w1, w2, w3, w4) 0)
_ -> fail ("Serialise.decode.SockAddr unexpected tok " ++ show tok)
| otherwise = do
_ <- CBOR.decodeListLen
tok <- CBOR.decodeWord
case tok of
0 -> do
w <- CBOR.decodeWord32
pn <- decodePortNumber
return (SockAddrInet pn w)
1 -> do
w1 <- CBOR.decodeWord32
w2 <- CBOR.decodeWord32
w3 <- CBOR.decodeWord32
w4 <- CBOR.decodeWord32
_fi <- CBOR.decodeWord32
_si <- CBOR.decodeWord32
pn <- decodePortNumber
return (SockAddrInet6 pn 0 (w1, w2, w3, w4) 0)
_ -> fail ("Serialise.decode.SockAddr unexpected tok " ++ show tok)

Original file line number Diff line number Diff line change
Expand Up @@ -1844,11 +1844,11 @@ withConnectionManager ConnectionManagerArguments {
let connState' = OutboundDupState connId connThread handle Ticking
notifyInboundGov =
case provenance' of
Inbound -> False
-- This is a connection to oneself; We don't
-- need to notify the inbound governor, as
-- it's already done by
-- `includeInboundConnectionImpl`
Inbound -> False
Outbound -> True
writeTVar connVar connState'
case inboundGovernorInfoChannel of
Expand Down
Original file line number Diff line number Diff line change
@@ -1,4 +1,5 @@
{-# LANGUAGE NamedFieldPuns #-}
{-# LANGUAGE NamedFieldPuns #-}
{-# LANGUAGE OverloadedStrings #-}

-- | Unversioned protocol, used in tests and demo applications.
--
Expand Down Expand Up @@ -26,8 +27,7 @@ import Network.TypedProtocol.Codec

import Ouroboros.Network.CodecCBORTerm
import Ouroboros.Network.ConnectionManager.Types (DataFlow (..))
import Ouroboros.Network.PeerSelection.PeerSharing (PeerSharing (..),
combinePeerSharing)
import Ouroboros.Network.PeerSelection.PeerSharing (PeerSharing (..))
import Ouroboros.Network.Protocol.Handshake.Codec
import Ouroboros.Network.Protocol.Handshake.Type
import Ouroboros.Network.Protocol.Handshake.Version
Expand Down Expand Up @@ -84,7 +84,7 @@ data DataFlowProtocolData =

instance Acceptable DataFlowProtocolData where
acceptableVersion (DataFlowProtocolData local lps) (DataFlowProtocolData remote rps) =
Accept (DataFlowProtocolData (local `min` remote) (combinePeerSharing lps rps))
Accept (DataFlowProtocolData (local `min` remote) (lps <> rps))

instance Queryable DataFlowProtocolData where
queryVersion (DataFlowProtocolData _ _) = False
Expand All @@ -104,14 +104,14 @@ dataFlowProtocolDataCodec _ = CodecCBORTerm {encodeTerm, decodeTerm}
PeerSharingEnabled -> 1
in CBOR.TList [CBOR.TBool True, CBOR.TInt peerSharing]

toPeerSharing :: Int -> PeerSharing
toPeerSharing 0 = PeerSharingDisabled
toPeerSharing 1 = PeerSharingEnabled
toPeerSharing _ = error "toPeerSharing: out of bounds"
toPeerSharing :: Int -> Either Text PeerSharing
toPeerSharing 0 = Right PeerSharingDisabled
toPeerSharing 1 = Right PeerSharingEnabled
toPeerSharing _ = Left "toPeerSharing: out of bounds"

decodeTerm :: CBOR.Term -> Either Text DataFlowProtocolData
decodeTerm (CBOR.TList [CBOR.TBool False, CBOR.TInt a]) = Right (DataFlowProtocolData Unidirectional (toPeerSharing a))
decodeTerm (CBOR.TList [CBOR.TBool True, CBOR.TInt a]) = Right (DataFlowProtocolData Duplex (toPeerSharing a))
decodeTerm (CBOR.TList [CBOR.TBool False, CBOR.TInt a]) = DataFlowProtocolData Unidirectional <$> (toPeerSharing a)
decodeTerm (CBOR.TList [CBOR.TBool True, CBOR.TInt a]) = DataFlowProtocolData Duplex <$> (toPeerSharing a)
decodeTerm t = Left $ T.pack $ "unexpected term: " ++ show t

dataFlowProtocol :: DataFlow
Expand Down
6 changes: 4 additions & 2 deletions ouroboros-network-protocols/CHANGELOG.md
Original file line number Diff line number Diff line change
Expand Up @@ -16,9 +16,11 @@
* Add a 3673s timeout to chainsync's StIdle state.
* Add a 97s timeout to keepalive's StClient state.

- Add a test to check that Peer Sharing values after handshake are symmetric
* Added a test to check that Peer Sharing values after handshake are symmetric
relative to the initiator and responder side.
- Adds cddl specs and tests for `NodeToNodeV_13` and handshake
* Added cddl specs and tests for `NodeToNodeV_13` and handshake

* Refactored cddl tests for `PeerSharing` to include versioning.

## 0.5.2.0 -- 2023-09-08

Expand Down
Loading

0 comments on commit 50bab68

Please sign in to comment.