Skip to content

Commit 76be017

Browse files
committed
head logic process inputs only when node state's current slot is within the contestation period window relative to the latest known tip
1 parent 8a6b1ab commit 76be017

File tree

3 files changed

+144
-70
lines changed

3 files changed

+144
-70
lines changed

hydra-node/src/Hydra/HeadLogic.hs

Lines changed: 3 additions & 1 deletion
Original file line numberDiff line numberDiff line change
@@ -29,6 +29,7 @@ import Data.Set qualified as Set
2929
import Hydra.API.ClientInput (ClientInput (..))
3030
import Hydra.API.ServerOutput (DecommitInvalidReason (..))
3131
import Hydra.API.ServerOutput qualified as ServerOutput
32+
import Hydra.Cardano.Api (ChainPoint)
3233
import Hydra.Chain (
3334
ChainEvent (..),
3435
ChainStateHistory,
@@ -1336,12 +1337,13 @@ update ::
13361337
IsChainState tx =>
13371338
Environment ->
13381339
Ledger tx ->
1340+
ChainPoint ->
13391341
-- | Current NodeState to validate the command against.
13401342
NodeState tx ->
13411343
-- | Input to be processed.
13421344
Input tx ->
13431345
Outcome tx
1344-
update env ledger NodeState{headState = st, pendingDeposits, currentSlot} ev = case (st, ev) of
1346+
update env ledger _knownTip NodeState{headState = st, pendingDeposits, currentSlot} ev = case (st, ev) of
13451347
(_, NetworkInput _ (ConnectivityEvent conn)) ->
13461348
onConnectionEvent env.configuredPeers conn
13471349
(Idle _, ClientInput Init) ->

hydra-node/src/Hydra/Node.hs

Lines changed: 9 additions & 4 deletions
Original file line numberDiff line numberDiff line change
@@ -30,6 +30,7 @@ import Hydra.Chain (
3030
initHistory,
3131
)
3232
import Hydra.Chain.ChainState (ChainStateType, IsChainState)
33+
import Hydra.Chain.SyncedStatus (SyncedStatus (..))
3334
import Hydra.Events (EventId, EventSink (..), EventSource (..), getEventId, putEventsToSinks)
3435
import Hydra.Events.Rotation (EventStore (..))
3536
import Hydra.HeadLogic (
@@ -306,7 +307,8 @@ stepHydraNode ::
306307
stepHydraNode node = do
307308
i@Queued{queuedId, queuedItem} <- dequeue
308309
traceWith tracer $ BeginInput{by = party, inputId = queuedId, input = queuedItem}
309-
outcome <- atomically $ processNextInput node queuedItem
310+
syncedStatus <- chainSyncedStatus
311+
outcome <- atomically $ processNextInput node queuedItem syncedStatus
310312
traceWith tracer (LogicOutcome party outcome)
311313
case outcome of
312314
Continue{stateChanges, effects} -> do
@@ -326,7 +328,9 @@ stepHydraNode node = do
326328

327329
Environment{party} = env
328330

329-
HydraNode{tracer, inputQueue = InputQueue{dequeue, reenqueue}, env} = node
331+
Chain{chainSyncedStatus} = oc
332+
333+
HydraNode{tracer, inputQueue = InputQueue{dequeue, reenqueue}, env, oc} = node
330334

331335
-- | The maximum number of times to re-enqueue a network messages upon 'Wait'.
332336
-- outcome.
@@ -347,15 +351,16 @@ processNextInput ::
347351
IsChainState tx =>
348352
HydraNode tx m ->
349353
Input tx ->
354+
SyncedStatus ->
350355
STM m (Outcome tx)
351-
processNextInput HydraNode{nodeStateHandler, ledger, env} e =
356+
processNextInput HydraNode{nodeStateHandler, ledger, env} e SyncedStatus{tip} =
352357
modifyNodeState $ \s ->
353358
let outcome = computeOutcome s e
354359
in (outcome, aggregateState s outcome)
355360
where
356361
NodeStateHandler{modifyNodeState} = nodeStateHandler
357362

358-
computeOutcome = HeadLogic.update env ledger
363+
computeOutcome = HeadLogic.update env ledger tip
359364

360365
processStateChanges :: (MonadSTM m, MonadTime m) => HydraNode tx m -> [StateChanged tx] -> m ()
361366
processStateChanges node stateChanges = do

0 commit comments

Comments
 (0)