Skip to content

Commit

Permalink
TxSubmission - delay initial request for transactions
Browse files Browse the repository at this point in the history
This change delays initial request for transactions from the client,
whom may disconnect relatively quickly for reasons described in
IntersectMBO/ouroboros-network issue #4927.
  • Loading branch information
crocodile-dentist authored and johnalotoski committed Aug 13, 2024
1 parent f22edb3 commit 81ce4ed
Showing 1 changed file with 9 additions and 1 deletion.
10 changes: 9 additions & 1 deletion ouroboros-network/src/Ouroboros/Network/TxSubmission/Inbound.hs
Original file line number Diff line number Diff line change
Expand Up @@ -5,6 +5,7 @@
{-# LANGUAGE KindSignatures #-}
{-# LANGUAGE NamedFieldPuns #-}
{-# LANGUAGE ScopedTypeVariables #-}
{-# LANGUAGE TypeApplications #-}

{-# OPTIONS_GHC -Wno-partial-fields #-}

Expand All @@ -20,6 +21,7 @@ import Data.Foldable (foldl', toList)
import Data.List.NonEmpty qualified as NonEmpty
import Data.Map.Strict (Map)
import Data.Map.Strict qualified as Map
import Data.Maybe
import Data.Sequence.Strict (StrictSeq)
import Data.Sequence.Strict qualified as Seq
import Data.Set qualified as Set
Expand All @@ -34,11 +36,13 @@ import Control.Exception (assert)
import Control.Monad (unless)
import Control.Monad.Class.MonadSTM
import Control.Monad.Class.MonadThrow
import Control.Monad.Class.MonadTimer
import Control.Tracer (Tracer, traceWith)

import Network.TypedProtocol.Pipelined (N, Nat (..), natToInt)

import Ouroboros.Network.NodeToNode.Version (NodeToNodeVersion)
import Ouroboros.Network.Protocol.Limits
import Ouroboros.Network.Protocol.TxSubmission2.Server
import Ouroboros.Network.TxSubmission.Mempool.Reader (MempoolSnapshot (..),
TxSubmissionMempoolReader (..))
Expand Down Expand Up @@ -175,6 +179,7 @@ txSubmissionInbound
, NoThunks tx
, MonadSTM m
, MonadThrow m
, MonadDelay m
)
=> Tracer m (TraceTxSubmissionInbound txid tx)
-> Word16 -- ^ Maximum number of unacknowledged txids allowed
Expand All @@ -183,7 +188,10 @@ txSubmissionInbound
-> NodeToNodeVersion
-> TxSubmissionServerPipelined txid tx m ()
txSubmissionInbound tracer maxUnacked mpReader mpWriter _version =
TxSubmissionServerPipelined $
TxSubmissionServerPipelined $ do
-- make the client linger before asking for tx's and expending
-- our resources as well, as he may disconnect for some reason
threadDelay (round @Double . realToFrac . fromMaybe (-1) $ longWait)
continueWithStateM (serverIdle Zero) initialServerState
where
-- TODO #1656: replace these fixed limits by policies based on
Expand Down

0 comments on commit 81ce4ed

Please sign in to comment.