Skip to content

Commit

Permalink
Add the check for tMax/tMin in the close validator
Browse files Browse the repository at this point in the history
  • Loading branch information
ch1bo committed Nov 29, 2022
1 parent 0e2ac35 commit d107340
Showing 1 changed file with 19 additions and 6 deletions.
25 changes: 19 additions & 6 deletions hydra-plutus/src/Hydra/Contract/Head.hs
Expand Up @@ -10,7 +10,7 @@ import PlutusTx.Prelude
import Hydra.Contract.Commit (Commit (..))
import qualified Hydra.Contract.Commit as Commit
import Hydra.Contract.HeadState (Input (..), Signature, SnapshotNumber, State (..))
import Hydra.Data.ContestationPeriod (ContestationPeriod, addContestationPeriod)
import Hydra.Data.ContestationPeriod (ContestationPeriod, addContestationPeriod, milliseconds)
import Hydra.Data.Party (Party (vkey))
import Plutus.Extras (ValidatorType, scriptValidatorHash, wrapValidator)
import Plutus.V2.Ledger.Api (
Expand Down Expand Up @@ -47,6 +47,8 @@ import qualified PlutusTx.AssocMap as Map
import qualified PlutusTx.Builtins as Builtins

-- REVIEW: Functions not re-exported "as V2", but using the same data types.

import Plutus.V1.Ledger.Time (fromMilliSeconds)
import Plutus.V1.Ledger.Value (assetClass, assetClassValue, valueOf)

type DatumType = State
Expand Down Expand Up @@ -273,12 +275,11 @@ checkClose ::
ContestationPeriod ->
Bool
checkClose ctx headContext parties initialUtxoHash snapshotNumber closedUtxoHash sig cperiod =
hasBoundedValidity && checkSnapshot && mustBeSignedByParticipant ctx headContext
hasBoundedValidity
&& checkSnapshot
&& mustBeSignedByParticipant ctx headContext
where
hasBoundedValidity =
tMax <= tMin + cperiod
tMax = traceError "define tMax"
tMin = traceError "define tMin"
hasBoundedValidity = tMax - tMin <= cp

checkSnapshot
| snapshotNumber == 0 =
Expand All @@ -303,6 +304,18 @@ checkClose ctx headContext parties initialUtxoHash snapshotNumber closedUtxoHash
verifySnapshotSignature parties snapshotNumber closedUtxoHash sig
&& checkHeadOutputDatum ctx expectedOutputDatum
| otherwise = traceError "negative snapshot number"

cp = fromMilliSeconds (milliseconds cperiod)

tMax = case ivTo $ txInfoValidRange txInfo of
UpperBound (Finite t) _ -> t
_InfiniteBound -> traceError "infinite upper bound"

tMin = case ivFrom $ txInfoValidRange txInfo of
LowerBound (Finite t) _ -> t
_InfiniteBound -> traceError "infinite lower bound"

ScriptContext{scriptContextTxInfo = txInfo} = ctx
{-# INLINEABLE checkClose #-}

makeContestationDeadline :: ContestationPeriod -> ScriptContext -> POSIXTime
Expand Down

0 comments on commit d107340

Please sign in to comment.