Skip to content

Commit

Permalink
Add depositDeadline to Environment and usages in hydra-node
Browse files Browse the repository at this point in the history
  • Loading branch information
v0d1ch committed Jan 22, 2025
1 parent d131ffb commit e09f618
Show file tree
Hide file tree
Showing 7 changed files with 37 additions and 20 deletions.
8 changes: 3 additions & 5 deletions docs/docs/dev/commit_to_a_Head.md
Original file line number Diff line number Diff line change
Expand Up @@ -64,12 +64,10 @@ up and made available inside of L2 by posting a **increment** transaction. This
also happens automatically but here we want to describe this process and bring
it closer to Hydra users.

It is worthwhile mentioning that deposit deadline is double the value used for
contestation period. This gives the users control by specifying the
contestation period it in the arguments to `hydra-node` executable.

::::info
Deadline information is present in the `CommitRecorded` API server output.
Deposit deadline is specified as argument to `hydra-node` executable eg.
`--deposit-deadline "100s"`. Deadline information is present in the
`CommitRecorded` API server output.
::::


Expand Down
5 changes: 2 additions & 3 deletions docs/docs/dev/incremental-commits-and-decommits.md
Original file line number Diff line number Diff line change
Expand Up @@ -59,9 +59,8 @@ The deposit transaction contains a deadline - time window in which we expect
the hydra-node to be able to observe this deposit and issue a _increment_
transaction that will do the heavy lifting and bring the specified input on L2.

Currently, _contestation period_ value is used to specify a deposit deadline
but this should be made available as a separate argument to hydra-node since it
heavily depends on the network we are running on.
Deposit deadline value is specified as the `hydra-node` option eg.
`--deposit-deadline "100s"`

Once a hydra-node observes a deposit transaction it will record the deposit as
pending into the local state. There can be many pending deposits but the new
Expand Down
8 changes: 3 additions & 5 deletions hydra-node/src/Hydra/API/HTTPServer.hs
Original file line number Diff line number Diff line change
Expand Up @@ -39,6 +39,7 @@ import Network.Wai (
rawPathInfo,
responseLBS,
)
import Hydra.Tx.DepositDeadline (depositToNominalDiffTime)

newtype DraftCommitTxResponse tx = DraftCommitTxResponse
{ commitTx :: tx
Expand Down Expand Up @@ -216,10 +217,7 @@ handleDraftCommitUtxo env directChain getCommitInfo body = do
CannotCommit -> pure $ responseLBS status500 [] (Aeson.encode (FailedToDraftTxNotInitializing :: PostTxError tx))
where
deposit headId commitBlueprint = do
-- NOTE: We double the contestation period and use it for the deadline
-- value in order to give enough time for the increment to be valid in
-- terms of deadline.
deadline <- addUTCTime (toNominalDiffTime contestationPeriod * 2) <$> getCurrentTime
deadline <- addUTCTime (depositToNominalDiffTime depositDeadline) <$> getCurrentTime
draftDepositTx headId commitBlueprint deadline <&> \case
Left e -> responseLBS status400 [] (Aeson.encode $ toJSON e)
Right depositTx -> okJSON $ DraftCommitTxResponse depositTx
Expand All @@ -237,7 +235,7 @@ handleDraftCommitUtxo env directChain getCommitInfo body = do
Right commitTx ->
okJSON $ DraftCommitTxResponse commitTx
Chain{draftCommitTx, draftDepositTx} = directChain
Environment{contestationPeriod} = env
Environment{depositDeadline} = env

-- | Handle request to recover a pending deposit.
handleRecoverCommitUtxo ::
Expand Down
10 changes: 8 additions & 2 deletions hydra-node/test/Hydra/BehaviorSpec.hs
Original file line number Diff line number Diff line change
Expand Up @@ -51,6 +51,7 @@ import Hydra.Node.InputQueue (InputQueue (enqueue))
import Hydra.NodeSpec (createPersistenceInMemory)
import Hydra.Tx.ContestationPeriod (ContestationPeriod (UnsafeContestationPeriod), toNominalDiffTime)
import Hydra.Tx.Crypto (HydraKey, aggregate, sign)
import Hydra.Tx.DepositDeadline (DepositDeadline (UnsafeDepositDeadline))
import Hydra.Tx.Environment (Environment (..))
import Hydra.Tx.IsTx (IsTx (..))
import Hydra.Tx.Party (Party (..), deriveParty, getParty)
Expand Down Expand Up @@ -1152,6 +1153,9 @@ toOnChainTx now = \case
testContestationPeriod :: ContestationPeriod
testContestationPeriod = UnsafeContestationPeriod 10

testDepositDeadline :: DepositDeadline
testDepositDeadline = UnsafeDepositDeadline 10

nothingHappensFor ::
(MonadTimer m, MonadThrow m, IsChainState tx) =>
TestHydraClient tx m ->
Expand All @@ -1171,7 +1175,7 @@ withHydraNode signingKey otherParties chain action = do
outputs <- atomically newTQueue
outputHistory <- newTVarIO mempty
let initialChainState = SimpleChainState{slot = ChainSlot 0}
node <- createHydraNode traceInIOSim simpleLedger initialChainState signingKey otherParties outputs outputHistory chain testContestationPeriod
node <- createHydraNode traceInIOSim simpleLedger initialChainState signingKey otherParties outputs outputHistory chain testContestationPeriod testDepositDeadline
withAsync (runHydraNode node) $ \_ ->
action (createTestHydraClient outputs outputHistory node)

Expand Down Expand Up @@ -1201,8 +1205,9 @@ createHydraNode ::
TVar m [ServerOutput tx] ->
SimulatedChainNetwork tx m ->
ContestationPeriod ->
DepositDeadline ->
m (HydraNode tx m)
createHydraNode tracer ledger chainState signingKey otherParties outputs outputHistory chain cp = do
createHydraNode tracer ledger chainState signingKey otherParties outputs outputHistory chain cp depositDeadline = do
persistence <- createPersistenceInMemory
(eventSource, eventSink) <- eventPairFromPersistenceIncremental persistence
node <- connectNode chain =<< hydrate tracer env ledger chainState eventSource [eventSink]
Expand All @@ -1223,6 +1228,7 @@ createHydraNode tracer ledger chainState signingKey otherParties outputs outputH
, otherParties
, contestationPeriod = cp
, participants
, depositDeadline
}
party = deriveParty signingKey

Expand Down
20 changes: 15 additions & 5 deletions hydra-node/test/Hydra/Model.hs
Original file line number Diff line number Diff line change
@@ -1,6 +1,7 @@
{-# LANGUAGE DuplicateRecordFields #-}
{-# LANGUAGE UndecidableInstances #-}
{-# OPTIONS_GHC -Wno-orphans #-}
{-# OPTIONS_GHC -Wno-unused-matches #-}

-- | A /Model/ of the Hydra head Protocol.
--
Expand Down Expand Up @@ -67,6 +68,7 @@ import Hydra.Model.Payment (CardanoSigningKey (..), Payment (..), applyTx, genAd
import Hydra.Node (runHydraNode)
import Hydra.Tx.ContestationPeriod (ContestationPeriod (UnsafeContestationPeriod))
import Hydra.Tx.Crypto (HydraKey)
import Hydra.Tx.DepositDeadline (DepositDeadline (UnsafeDepositDeadline))
import Hydra.Tx.HeadParameters (HeadParameters (..))
import Hydra.Tx.IsTx (IsTx (..))
import Hydra.Tx.Party (Party (..), deriveParty)
Expand Down Expand Up @@ -147,6 +149,7 @@ instance StateModel WorldState where
Seed ::
{ seedKeys :: [(SigningKey HydraKey, CardanoSigningKey)]
, seedContestationPeriod :: ContestationPeriod
, seedDepositDeadline :: DepositDeadline
, toCommit :: Uncommitted
} ->
Action WorldState ()
Expand Down Expand Up @@ -415,8 +418,9 @@ genSeed :: Gen (Action WorldState ())
genSeed = do
seedKeys <- resize maximumNumberOfParties partyKeys
seedContestationPeriod <- genContestationPeriod
seedDepositDeadline <- genDepositDeadline
toCommit <- mconcat <$> mapM genToCommit seedKeys
pure $ Seed{seedKeys, seedContestationPeriod, toCommit}
pure $ Seed{seedKeys, seedContestationPeriod, seedDepositDeadline, toCommit}

genToCommit :: (SigningKey HydraKey, CardanoSigningKey) -> Gen (Map Party [(CardanoSigningKey, Value)])
genToCommit (hk, ck) = do
Expand All @@ -428,6 +432,11 @@ genContestationPeriod = do
n <- choose (1, 200)
pure $ UnsafeContestationPeriod $ wordToNatural n

genDepositDeadline :: Gen DepositDeadline
genDepositDeadline = do
n <- choose (1, 200)
pure $ UnsafeDepositDeadline $ wordToNatural n

genInit :: [(SigningKey HydraKey, b)] -> Gen (Action WorldState ())
genInit hydraParties = do
key <- fst <$> elements hydraParties
Expand Down Expand Up @@ -554,8 +563,8 @@ instance

perform st action lookup = do
case action of
Seed{seedKeys, seedContestationPeriod, toCommit} ->
seedWorld seedKeys seedContestationPeriod toCommit
Seed{seedKeys, seedContestationPeriod, seedDepositDeadline, toCommit} ->
seedWorld seedKeys seedContestationPeriod seedDepositDeadline toCommit
Commit party utxo ->
performCommit (snd <$> hydraParties st) party utxo
Decommit party tx ->
Expand Down Expand Up @@ -606,9 +615,10 @@ seedWorld ::
) =>
[(SigningKey HydraKey, CardanoSigningKey)] ->
ContestationPeriod ->
DepositDeadline ->
Uncommitted ->
RunMonad m ()
seedWorld seedKeys seedCP futureCommits = do
seedWorld seedKeys seedCP depositDeadline futureCommits = do
tr <- gets logger

mockChain@SimulatedChainNetwork{tickThread} <-
Expand All @@ -624,7 +634,7 @@ seedWorld seedKeys seedCP futureCommits = do
labelTQueueIO outputs ("outputs-" <> shortLabel hsk)
outputHistory <- newTVarIO []
labelTVarIO outputHistory ("history-" <> shortLabel hsk)
node <- createHydraNode (contramap Node tr) ledger initialChainState hsk otherParties outputs outputHistory mockChain seedCP
node <- createHydraNode (contramap Node tr) ledger initialChainState hsk otherParties outputs outputHistory mockChain seedCP depositDeadline
let testClient = createTestHydraClient outputs outputHistory node
nodeThread <- async $ labelThisThread ("node-" <> shortLabel hsk) >> runHydraNode node
link nodeThread
Expand Down
4 changes: 4 additions & 0 deletions hydra-tx/src/Hydra/Tx/Environment.hs
Original file line number Diff line number Diff line change
Expand Up @@ -4,6 +4,7 @@ import Hydra.Prelude

import Hydra.Tx.ContestationPeriod (ContestationPeriod)
import Hydra.Tx.Crypto (HydraKey, SigningKey)
import Hydra.Tx.DepositDeadline (DepositDeadline)
import Hydra.Tx.OnChainId (OnChainId)
import Hydra.Tx.Party (HasParty (..), Party, deriveParty)

Expand All @@ -17,6 +18,7 @@ data Environment = Environment
, -- XXX: Improve naming
participants :: [OnChainId]
, contestationPeriod :: ContestationPeriod
, depositDeadline :: DepositDeadline
}
deriving stock (Show, Eq)

Expand All @@ -26,13 +28,15 @@ instance Arbitrary Environment where
otherParties <- arbitrary
participants <- arbitrary
contestationPeriod <- arbitrary
depositDeadline <- arbitrary
pure $
Environment
{ signingKey
, party = deriveParty signingKey
, otherParties
, contestationPeriod
, participants
, depositDeadline
}

instance HasParty Environment where
Expand Down
2 changes: 2 additions & 0 deletions hydra-tx/testlib/Test/Hydra/Tx/Fixture.hs
Original file line number Diff line number Diff line change
Expand Up @@ -40,6 +40,7 @@ import Hydra.Tx.HeadParameters (HeadParameters (..))
import Hydra.Tx.OnChainId (AsType (..), OnChainId)
import Hydra.Tx.Party (deriveParty)
import System.IO.Unsafe (unsafePerformIO)
import Hydra.Tx.DepositDeadline (DepositDeadline(..))

-- | Our beloved alice, bob, and carol.
alice, bob, carol :: Party
Expand Down Expand Up @@ -83,6 +84,7 @@ testEnvironment =
, signingKey = aliceSk
, otherParties = [bob, carol]
, contestationPeriod = cperiod
, depositDeadline = UnsafeDepositDeadline 20
, participants = deriveOnChainId <$> [alice, bob, carol]
}

Expand Down

0 comments on commit e09f618

Please sign in to comment.