Skip to content

Commit

Permalink
Refactor network/consensus versioning
Browse files Browse the repository at this point in the history
Fixes #2309.

Previously, we had a list of supported `BlockNodeToNodeVersion`s and a method
to translate them to a `NodeToNodeVersion`. This meant that there were two
layers of "support": (1) include the version in `BlockNodeToNodeVersion`
and (2) return a non-`error` for it in the translation function.

Replace these methods by a map from `NodeToNodeVersion` to
`BlockNodeToNodeVersion`. Similarly for `NodeToClient`. An important insight
is that not each network version requires a consensus-side block version. For
example, enabling the `LocalStateQuery` `NodeToClient` protocol requires a new
network version, but no block version, as the serialisation format doesn't
change. A new block version is only needed when the serialisation changes, so
not when protocols get added/removed or the protocol messages are
added/removed.

This means we don't need separate Byron (nor Cardano) versions for
`NodeToClientV_2`, as the serialisation format didn't change, so remove these
redundant versions and map `NodeToClientV_2` to `ByronNodeToClientVersion1`.

The `mostRecentSupportedNodeToNode` method was only used for the ThreadNet
tests to make sure we were testing the most recent version. Remove this method
in favour of randomly picking a supported version in the tests. The
`Test.ThreadNet.Util.NodeToNodeVersion` was added to aid in picking a version.

* Rewrite `foldMapVersions` and `combineVersions` to work for any `Foldable`
  instead of a `NonEmpty`, as we now use a `Map` instead of a `NonEmpty` for
  the supported versions.

* Rewrite `Cardano.Client.Subscription` to take a `CodecConfig` +
  `NetworkMagic` instead of an entire `TopLevelConfig`. Producing a
  `TopLevelConfig` is a lot of work for clients. The whole point of
  introducing the `CodecConfig` was to make it easier for clients.
  • Loading branch information
mrBliss committed Jul 3, 2020
1 parent 1361bb9 commit 9e26bb1
Show file tree
Hide file tree
Showing 34 changed files with 394 additions and 341 deletions.
1 change: 1 addition & 0 deletions cardano-client/cardano-client.cabal
Expand Up @@ -21,6 +21,7 @@ library
default-language: Haskell2010
build-depends: base,
bytestring >=0.10 && <0.11,
containers,
io-sim-classes,
ouroboros-consensus,
ouroboros-network,
Expand Down
87 changes: 44 additions & 43 deletions cardano-client/src/Cardano/Client/Subscription.hs
@@ -1,5 +1,6 @@
{-# LANGUAGE DataKinds #-}
{-# LANGUAGE ScopedTypeVariables #-}
{-# LANGUAGE TypeApplications #-}
{-# LANGUAGE TypeFamilies #-}

module Cardano.Client.Subscription (
Expand All @@ -23,91 +24,91 @@ module Cardano.Client.Subscription (
import Control.Monad.Class.MonadST (MonadST)
import Control.Monad.Class.MonadSTM
import qualified Data.ByteString.Lazy as BSL
import qualified Data.Map.Strict as Map
import Data.Proxy
import Data.Void (Void)

import Network.Mux.Trace (MuxTrace, WithMuxBearer)

import Ouroboros.Network.Magic (NetworkMagic)
import Ouroboros.Network.Mux (MuxMode (..), MuxPeer (..),
OuroborosApplication, RunMiniProtocol (..),
RunOrStop (..))
import Ouroboros.Network.NodeToClient (ClientSubscriptionParams (..),
ConnectionId, LocalAddress,
NetworkClientSubcriptionTracers,
NodeToClientProtocols (..), NodeToClientVersionData (..),
NodeToClientProtocols (..),
NodeToClientVersionData (NodeToClientVersionData),
ncSubscriptionWorker, newNetworkMutableState,
versionedNodeToClientProtocols)
import qualified Ouroboros.Network.NodeToClient (NodeToClientVersion)
import Ouroboros.Network.NodeToClient (NodeToClientVersion)
import Ouroboros.Network.Protocol.Handshake.Version (DictVersion,
Versions, foldMapVersions)
import qualified Ouroboros.Network.Snocket as Snocket

import Ouroboros.Consensus.Config (TopLevelConfig, configBlock,
configCodec)
import Ouroboros.Consensus.Config.SupportsNode (getNetworkMagic)
import Ouroboros.Consensus.Block (CodecConfig)
import Ouroboros.Consensus.Network.NodeToClient (ClientCodecs,
cChainSyncCodec, cStateQueryCodec, cTxSubmissionCodec,
clientCodecs)
import Ouroboros.Consensus.Node.NetworkProtocolVersion
(BlockNodeToClientVersion, nodeToClientProtocolVersion,
supportedNodeToClientVersions)
(BlockNodeToClientVersion, supportedNodeToClientVersions)
import Ouroboros.Consensus.Node.Run (RunNode)

subscribe ::
RunNode blk
=> Snocket.LocalSnocket
-> TopLevelConfig blk
-> CodecConfig blk
-> NetworkMagic
-> NetworkClientSubcriptionTracers
-> ClientSubscriptionParams ()
-> (BlockNodeToClientVersion blk
-> ( NodeToClientVersion
-> ClientCodecs blk IO
-> ConnectionId LocalAddress
-> NodeToClientProtocols 'InitiatorMode BSL.ByteString IO x y)
-> IO Void
subscribe
sn
topLevelConfig
tracers
subscriptionParams
protocols
= do
subscribe snocket codecConfig networkMagic tracers subscriptionParams protocols = do
networkState <- newNetworkMutableState
ncSubscriptionWorker
sn
tracers
networkState
subscriptionParams
(versionedProtocols (Proxy :: Proxy blk) topLevelConfig
(\version codecs connectionId _ -> protocols version codecs connectionId))

snocket
tracers
networkState
subscriptionParams
(versionedProtocols codecConfig networkMagic
(\version codecs connectionId _ ->
protocols version codecs connectionId))

versionedProtocols ::
( MonadST m
, RunNode blk
)
=> Proxy blk
-> TopLevelConfig blk
-> (BlockNodeToClientVersion blk
forall blk m appType bytes a b. (MonadST m, RunNode blk)
=> CodecConfig blk
-> NetworkMagic
-> ( NodeToClientVersion
-> ClientCodecs blk m
-> ConnectionId LocalAddress
-> STM m RunOrStop
-> NodeToClientProtocols appType bytes m a b)
-- ^ callback which recieves codecs, connection id and STM action which can be
-- checked if the networking runtime system requests the protocols to stop.
--
-- TODO: the `RunOrStop` might not be needed for `node-to-client`, hence it's
-- not exposed in `subscribe`. We should provide
-- `OuroborosClientApplication`, which does not include it.
-- ^ callback which receives codecs, connection id and STM action which
-- can be checked if the networking runtime system requests the protocols
-- to stop.
--
-- TODO: the 'RunOrStop' might not be needed for @node-to-client@, hence
-- it's not exposed in 'subscribe'. We should provide
-- 'OuroborosClientApplication', which does not include it.
-> Versions
Ouroboros.Network.NodeToClient.NodeToClientVersion
NodeToClientVersion
DictVersion
(OuroborosApplication appType LocalAddress bytes m a b)
versionedProtocols blkProxy topLevelConfig p
= foldMapVersions applyVersion $ supportedNodeToClientVersions blkProxy
versionedProtocols codecConfig networkMagic callback =
foldMapVersions applyVersion $
Map.toList $ supportedNodeToClientVersions (Proxy @blk)
where
blockConfig = configBlock topLevelConfig
applyVersion v =
applyVersion ::
(NodeToClientVersion, BlockNodeToClientVersion blk)
-> Versions
NodeToClientVersion
DictVersion
(OuroborosApplication appType LocalAddress bytes m a b)
applyVersion (version, blockVersion) =
versionedNodeToClientProtocols
(nodeToClientProtocolVersion blkProxy v)
(NodeToClientVersionData { networkMagic = getNetworkMagic blockConfig })
(p v $ clientCodecs (configCodec topLevelConfig) v)
version
(NodeToClientVersionData networkMagic)
(callback version (clientCodecs codecConfig blockVersion))
Expand Up @@ -44,13 +44,9 @@ instance HasNetworkProtocolVersion DualByronBlock where
type BlockNodeToNodeVersion DualByronBlock = BlockNodeToNodeVersion ByronBlock
type BlockNodeToClientVersion DualByronBlock = BlockNodeToClientVersion ByronBlock

instance TranslateNetworkProtocolVersion DualByronBlock where
instance SupportedNetworkProtocolVersion DualByronBlock where
supportedNodeToNodeVersions _ = supportedNodeToNodeVersions pb
supportedNodeToClientVersions _ = supportedNodeToClientVersions pb
mostRecentSupportedNodeToNode _ = mostRecentSupportedNodeToNode pb
mostRecentSupportedNodeToClient _ = mostRecentSupportedNodeToClient pb
nodeToNodeProtocolVersion _ = nodeToNodeProtocolVersion pb
nodeToClientProtocolVersion _ = nodeToClientProtocolVersion pb

{-------------------------------------------------------------------------------
EncodeDisk & DecodeDisk
Expand Down
Expand Up @@ -14,6 +14,7 @@ import Crypto.Number.Generate as Cryptonite
import Crypto.Random (MonadRandom)
import Data.ByteString (ByteString)
import qualified Data.Map as Map
import Data.Proxy
import qualified Data.Set as Set
import Data.Word
import qualified Hedgehog
Expand Down Expand Up @@ -64,6 +65,7 @@ import qualified Test.ThreadNet.Ref.PBFT as Ref
import Test.ThreadNet.TxGen
import Test.ThreadNet.Util
import Test.ThreadNet.Util.NodeRestarts (noRestarts)
import Test.ThreadNet.Util.NodeToNodeVersion (newestVersion)

import Test.Util.HardFork.Future (singleEraFuture)
import Test.Util.Slots (NumSlots (..))
Expand Down Expand Up @@ -146,6 +148,7 @@ setupTestConfigB SetupDualPBft{..} = TestConfigB
, nodeJoinPlan = setupNodeJoinPlan
, nodeRestarts = setupNodeRestarts
, txGenExtra = ()
, version = newestVersion (Proxy @DualByronBlock)
}
where
RealPBFT.TestSetup{..} = setupRealPBft
Expand Down

0 comments on commit 9e26bb1

Please sign in to comment.