Skip to content

Commit

Permalink
ouroboros-network: tx-submission module structure
Browse files Browse the repository at this point in the history
Export everything from the `Ouroboros.Network.TxSubmission.Inbound`
module.
  • Loading branch information
coot committed Jul 30, 2024
1 parent f369e4a commit 188be50
Show file tree
Hide file tree
Showing 6 changed files with 98 additions and 67 deletions.
5 changes: 3 additions & 2 deletions ouroboros-network/ouroboros-network.cabal
Original file line number Diff line number Diff line change
Expand Up @@ -64,11 +64,12 @@ library
Ouroboros.Network.PeerSelection.RootPeersDNS.PublicRootPeers
Ouroboros.Network.PeerSharing
Ouroboros.Network.TxSubmission.Inbound
Ouroboros.Network.TxSubmission.Inbound.Server
Ouroboros.Network.TxSubmission.Inbound.Decision
Ouroboros.Network.TxSubmission.Inbound.Policy
Ouroboros.Network.TxSubmission.Inbound.State
Ouroboros.Network.TxSubmission.Inbound.Registry
Ouroboros.Network.TxSubmission.Inbound.Server
Ouroboros.Network.TxSubmission.Inbound.State
Ouroboros.Network.TxSubmission.Inbound.Types
Ouroboros.Network.TxSubmission.Mempool.Reader
Ouroboros.Network.TxSubmission.Outbound
other-modules: Ouroboros.Network.Diffusion.Common
Expand Down
Original file line number Diff line number Diff line change
Expand Up @@ -66,9 +66,7 @@ import Ouroboros.Network.Protocol.TxSubmission2.Codec
import Ouroboros.Network.Protocol.TxSubmission2.Server
import Ouroboros.Network.Protocol.TxSubmission2.Type
import Ouroboros.Network.TxSubmission.Inbound
import Ouroboros.Network.TxSubmission.Inbound.Decision
import Ouroboros.Network.TxSubmission.Inbound.Decision qualified as TXS
import Ouroboros.Network.TxSubmission.Inbound.Policy
import Ouroboros.Network.TxSubmission.Inbound.State (PeerTxState (..),
SharedTxState (..))
import Ouroboros.Network.TxSubmission.Inbound.State qualified as TXS
Expand Down
75 changes: 14 additions & 61 deletions ouroboros-network/src/Ouroboros/Network/TxSubmission/Inbound.hs
Original file line number Diff line number Diff line change
Expand Up @@ -11,10 +11,14 @@
-- | Legacy `tx-submission` inbound peer.
--
module Ouroboros.Network.TxSubmission.Inbound
( txSubmissionInbound
, TxSubmissionMempoolWriter (..)
, TraceTxSubmissionInbound (..)
, TxSubmissionProtocolError (..)
( -- * New Tx-Submission server
module Server
, module Types
, module Decision
, module Registry
, module Policy
-- * Legacy Tx-Submission server
, txSubmissionInbound
, ProcessedTxCount (..)
) where

Expand Down Expand Up @@ -43,70 +47,19 @@ import Network.TypedProtocol.Pipelined (N, Nat (..), natToInt)
import Ouroboros.Network.NodeToNode.Version (NodeToNodeVersion)
import Ouroboros.Network.Protocol.TxSubmission2.Server
import Ouroboros.Network.Protocol.TxSubmission2.Type
import Ouroboros.Network.TxSubmission.Inbound.Decision (TxDecision)
import Ouroboros.Network.TxSubmission.Mempool.Reader (MempoolSnapshot (..),
TxSubmissionMempoolReader (..))

-- | The consensus layer functionality that the inbound side of the tx
-- submission logic requires.
--
-- This is provided to the tx submission logic by the consensus layer.
-- re-exports
--
data TxSubmissionMempoolWriter txid tx idx m =
TxSubmissionMempoolWriter {

-- | Compute the transaction id from a transaction.
--
-- This is used in the protocol handler to verify a full transaction
-- matches a previously given transaction id.
--
txId :: tx -> txid,
import Ouroboros.Network.TxSubmission.Inbound.Types as Types
import Ouroboros.Network.TxSubmission.Inbound.Decision as Decision
import Ouroboros.Network.TxSubmission.Inbound.Registry as Registry
import Ouroboros.Network.TxSubmission.Inbound.Policy as Policy
import Ouroboros.Network.TxSubmission.Inbound.Server as Server

-- | Supply a batch of transactions to the mempool. They are either
-- accepted or rejected individually, but in the order supplied.
--
-- The 'txid's of all transactions that were added successfully are
-- returned.
mempoolAddTxs :: [tx] -> m [txid]
}

data ProcessedTxCount = ProcessedTxCount {
-- | Just accepted this many transactions.
ptxcAccepted :: Int
-- | Just rejected this many transactions.
, ptxcRejected :: Int
}
deriving (Eq, Show)

data TraceTxSubmissionInbound txid tx =
-- | Number of transactions just about to be inserted.
TraceTxSubmissionCollected Int
-- | Just processed transaction pass/fail breakdown.
| TraceTxSubmissionProcessed ProcessedTxCount
-- | Server received 'MsgDone'
| TraceTxInboundCanRequestMoreTxs Int
| TraceTxInboundCannotRequestMoreTxs Int

--
-- messages emitted by the new implementation of the server in
-- "Ouroboros.Network.TxSubmission.Inbound.Server"; some of them are also
-- used in this module.
--

| TraceTxInboundTerminated
| TraceTxInboundDecision (TxDecision txid tx)
deriving (Eq, Show)

data TxSubmissionProtocolError =
ProtocolErrorTxNotRequested
| ProtocolErrorTxIdsNotRequested
deriving Show

instance Exception TxSubmissionProtocolError where
displayException ProtocolErrorTxNotRequested =
"The peer replied with a transaction we did not ask for."
displayException ProtocolErrorTxIdsNotRequested =
"The peer replied with more txids than we asked for."


-- | Information maintained internally in the 'txSubmissionInbound' server
Expand Down
Original file line number Diff line number Diff line change
Expand Up @@ -7,6 +7,8 @@
module Ouroboros.Network.TxSubmission.Inbound.Registry
( SharedTxStateVar
, newSharedTxStateVar
, TxChannelsVar
, newTxChannelsVar
, PeerTxAPI (..)
, decisionLogicThread
, withPeer
Expand Down Expand Up @@ -43,6 +45,9 @@ newtype TxChannels m peeraddr txid tx = TxChannels {

type TxChannelsVar m peeraddr txid tx = StrictMVar m (TxChannels m peeraddr txid tx)

newTxChannelsVar :: MonadMVar m => m (TxChannelsVar m peeraddr txid tx)
newTxChannelsVar = newMVar (TxChannels Map.empty)

-- | API to access `PeerTxState` inside `PeerTxStateVar`.
--
data PeerTxAPI m txid tx = PeerTxAPI {
Expand Down
Original file line number Diff line number Diff line change
Expand Up @@ -22,8 +22,7 @@ import Network.TypedProtocol.Pipelined

import Control.Monad (unless)
import Ouroboros.Network.Protocol.TxSubmission2.Server
import Ouroboros.Network.TxSubmission.Inbound (TraceTxSubmissionInbound (..),
TxSubmissionMempoolWriter (..), TxSubmissionProtocolError (..))
import Ouroboros.Network.TxSubmission.Inbound.Types
import Ouroboros.Network.TxSubmission.Inbound.Decision (TxDecision (..))
import Ouroboros.Network.TxSubmission.Inbound.Registry (PeerTxAPI (..))

Expand Down
Original file line number Diff line number Diff line change
@@ -0,0 +1,75 @@
module Ouroboros.Network.TxSubmission.Inbound.Types
( ProcessedTxCount (..)
, TxSubmissionMempoolWriter (..)
, TraceTxSubmissionInbound (..)
, TxSubmissionProtocolError (..)
) where

import Control.Exception (Exception (..))

import Ouroboros.Network.TxSubmission.Inbound.Decision (TxDecision (..))


data ProcessedTxCount = ProcessedTxCount {
-- | Just accepted this many transactions.
ptxcAccepted :: Int
-- | Just rejected this many transactions.
, ptxcRejected :: Int
}
deriving (Eq, Show)


-- | The consensus layer functionality that the inbound side of the tx
-- submission logic requires.
--
-- This is provided to the tx submission logic by the consensus layer.
--
data TxSubmissionMempoolWriter txid tx idx m =
TxSubmissionMempoolWriter {

-- | Compute the transaction id from a transaction.
--
-- This is used in the protocol handler to verify a full transaction
-- matches a previously given transaction id.
--
txId :: tx -> txid,

-- | Supply a batch of transactions to the mempool. They are either
-- accepted or rejected individually, but in the order supplied.
--
-- The 'txid's of all transactions that were added successfully are
-- returned.
mempoolAddTxs :: [tx] -> m [txid]
}


data TraceTxSubmissionInbound txid tx =
-- | Number of transactions just about to be inserted.
TraceTxSubmissionCollected Int
-- | Just processed transaction pass/fail breakdown.
| TraceTxSubmissionProcessed ProcessedTxCount
-- | Server received 'MsgDone'
| TraceTxInboundCanRequestMoreTxs Int
| TraceTxInboundCannotRequestMoreTxs Int

--
-- messages emitted by the new implementation of the server in
-- "Ouroboros.Network.TxSubmission.Inbound.Server"; some of them are also
-- used in this module.
--

| TraceTxInboundTerminated
| TraceTxInboundDecision (TxDecision txid tx)
deriving (Eq, Show)


data TxSubmissionProtocolError =
ProtocolErrorTxNotRequested
| ProtocolErrorTxIdsNotRequested
deriving Show

instance Exception TxSubmissionProtocolError where
displayException ProtocolErrorTxNotRequested =
"The peer replied with a transaction we did not ask for."
displayException ProtocolErrorTxIdsNotRequested =
"The peer replied with more txids than we asked for."

0 comments on commit 188be50

Please sign in to comment.