Skip to content

Commit

Permalink
Check Contest tx is within contestation deadline bounds
Browse files Browse the repository at this point in the history
  • Loading branch information
abailly authored and ch1bo committed May 19, 2022
1 parent 4e3ce74 commit 312ac0f
Show file tree
Hide file tree
Showing 6 changed files with 32 additions and 8 deletions.
6 changes: 4 additions & 2 deletions hydra-node/src/Hydra/Chain/Direct.hs
Original file line number Diff line number Diff line change
Expand Up @@ -647,8 +647,10 @@ fromPostChainTx TimeHandle{currentSlot, convertSlot} cardanoKeys wallet someHead
slot <- (+ closeGraceTime) <$> currentSlot
posixTime <- convertSlot slot
pure (close confirmedSnapshot (slot, posixTime) st)
(ContestTx{confirmedSnapshot}, TkClosed) ->
pure (contest confirmedSnapshot st)
(ContestTx{confirmedSnapshot}, TkClosed) -> do
slot <- (+ closeGraceTime) <$> currentSlot
posixTime <- convertSlot slot
pure (contest confirmedSnapshot (slot, posixTime) st)
(FanoutTx{utxo}, TkClosed) ->
pure (fanout utxo st)
(_, _) ->
Expand Down
8 changes: 6 additions & 2 deletions hydra-node/src/Hydra/Chain/Direct/Context.hs
Original file line number Diff line number Diff line change
Expand Up @@ -22,13 +22,14 @@ import Hydra.Chain.Direct.State (
collect,
commit,
contest,
getContestationDeadline,
idleOnChainHeadState,
initialize,
observeTx,
)
import qualified Hydra.Crypto as Hydra
import Hydra.Ledger.Cardano (genOneUTxOFor, genTxIn, genVerificationKey, renderTx)
import Hydra.Ledger.Cardano.Evaluate (genPointInTime)
import Hydra.Ledger.Cardano.Evaluate (genPointInTime, slotNoToPOSIXTime)
import Hydra.Party (Party, deriveParty)
import Hydra.Snapshot (ConfirmedSnapshot (..), Snapshot (..), SnapshotNumber, genConfirmedSnapshot, getSnapshot)
import Test.QuickCheck (choose, elements, frequency, suchThat, vector)
Expand Down Expand Up @@ -151,7 +152,10 @@ genContestTx numParties = do
utxo <- arbitrary
(closedSnapshotNumber, stClosed) <- genStClosed ctx utxo
snapshot <- genConfirmedSnapshot closedSnapshotNumber utxo (ctxHydraSigningKeys ctx)
pure (stClosed, contest snapshot stClosed)
pointInTime <-
genPointInTime `suchThat` \(slot, _) ->
slotNoToPOSIXTime slot < getContestationDeadline stClosed
pure (stClosed, contest snapshot pointInTime stClosed)

genStOpen ::
HydraContext ->
Expand Down
12 changes: 10 additions & 2 deletions hydra-node/src/Hydra/Chain/Direct/State.hs
Original file line number Diff line number Diff line change
Expand Up @@ -32,6 +32,7 @@ module Hydra.Chain.Direct.State (
ObserveTx (..),
HasTransition (..),
TransitionFrom (..),
getContestationDeadline,
) where

import Hydra.Cardano.Api
Expand Down Expand Up @@ -70,6 +71,7 @@ import Hydra.Chain.Direct.Tx (
import Hydra.Ledger.Cardano (hashTxOuts)
import Hydra.Party (Party)
import Hydra.Snapshot (ConfirmedSnapshot (..), Snapshot (..))
import Plutus.V1.Ledger.Api (POSIXTime)
import qualified Text.Show

-- | An opaque on-chain head state, which records information and events
Expand Down Expand Up @@ -135,6 +137,11 @@ getKnownUTxO OnChainHeadState{stateMachine} =
Closed{closedThreadOutput = ClosedThreadOutput{closedThreadUTxO = (i, o, _)}} ->
UTxO.singleton (i, o)

getContestationDeadline :: OnChainHeadState 'StClosed -> POSIXTime
getContestationDeadline
OnChainHeadState{stateMachine = Closed{closedThreadOutput = ClosedThreadOutput{closedContestationDeadline}}} =
closedContestationDeadline

-- Working with opaque states

-- | An existential wrapping /some/ 'OnChainHeadState' into a value that carry
Expand Down Expand Up @@ -322,10 +329,11 @@ close confirmedSnapshot pointInTime OnChainHeadState{ownVerificationKey, stateMa

contest ::
ConfirmedSnapshot Tx ->
PointInTime ->
OnChainHeadState 'StClosed ->
Tx
contest confirmedSnapshot OnChainHeadState{ownVerificationKey, stateMachine} = do
contestTx ownVerificationKey sn sigs closedThreadOutput
contest confirmedSnapshot pointInTime OnChainHeadState{ownVerificationKey, stateMachine} = do
contestTx ownVerificationKey sn sigs pointInTime closedThreadOutput
where
(sn, sigs) =
case confirmedSnapshot of
Expand Down
5 changes: 4 additions & 1 deletion hydra-node/src/Hydra/Chain/Direct/Tx.hs
Original file line number Diff line number Diff line change
Expand Up @@ -353,15 +353,18 @@ contestTx ::
Snapshot Tx ->
-- | Multi-signature of the whole snapshot
MultiSignature (Snapshot Tx) ->
-- | Current slot and posix time to be recorded as the closing time.
PointInTime ->
-- | Everything needed to spend the Head state-machine output.
ClosedThreadOutput ->
Tx
contestTx vk Snapshot{number, utxo} sig ClosedThreadOutput{closedThreadUTxO = (headInput, headOutputBefore, ScriptDatumForTxIn -> headDatumBefore), closedParties, closedContestationDeadline} =
contestTx vk Snapshot{number, utxo} sig (slotNo, _) ClosedThreadOutput{closedThreadUTxO = (headInput, headOutputBefore, ScriptDatumForTxIn -> headDatumBefore), closedParties, closedContestationDeadline} =
unsafeBuildTransaction $
emptyTxBody
& addInputs [(headInput, headWitness)]
& addOutputs [headOutputAfter]
& addExtraRequiredSigners [verificationKeyHash vk]
& setValiditityUpperBound slotNo
where
headWitness =
BuildTxWith $ ScriptWitness scriptWitnessCtx $ mkScriptWitness headScript headDatumBefore headRedeemer
Expand Down
1 change: 1 addition & 0 deletions hydra-node/test/Hydra/Chain/Direct/Contract/Contest.hs
Original file line number Diff line number Diff line change
Expand Up @@ -45,6 +45,7 @@ healthyContestTx =
somePartyCardanoVerificationKey
healthyContestSnapshot
(healthySignature healthyContestSnapshotNumber)
(healthySlotNo, slotNoToPOSIXTime healthySlotNo)
closedThreadOutput

headInput = generateWith arbitrary 42
Expand Down
8 changes: 7 additions & 1 deletion hydra-plutus/src/Hydra/Contract/Head.hs
Original file line number Diff line number Diff line change
Expand Up @@ -351,18 +351,24 @@ checkContest ::
BuiltinByteString ->
[Signature] ->
Bool
checkContest ctx headContext contestationDeadline parties closedSnapshotNumber contestSnapshotNumber contestUtxoHash sig =
checkContest ctx@ScriptContext{scriptContextTxInfo} headContext contestationDeadline parties closedSnapshotNumber contestSnapshotNumber contestUtxoHash sig =
mustBeNewer
&& mustBeMultiSigned
&& checkHeadOutputDatum ctx (Closed{parties, snapshotNumber = contestSnapshotNumber, utxoHash = contestUtxoHash, contestationDeadline})
&& mustBeSignedByParticipant ctx headContext
&& mustBeWithinContestationPeriod
where
mustBeNewer =
traceIfFalse "too old snapshot" $
contestSnapshotNumber > closedSnapshotNumber

mustBeMultiSigned =
verifySnapshotSignature parties contestSnapshotNumber contestUtxoHash sig

mustBeWithinContestationPeriod =
case ivTo (txInfoValidRange scriptContextTxInfo) of
UpperBound (Finite time) _ -> traceIfFalse "upper bound validity beyond contestation deadline" $ time < contestationDeadline
_ -> traceError "no upper bound validity interval defined for close"
{-# INLINEABLE checkContest #-}

checkHeadOutputDatum :: ToData a => ScriptContext -> a -> Bool
Expand Down

0 comments on commit 312ac0f

Please sign in to comment.