Skip to content

Commit

Permalink
Restore traces
Browse files Browse the repository at this point in the history
  • Loading branch information
pgrange authored and ffakenz committed Jan 5, 2023
1 parent 918a0db commit 964a54c
Showing 1 changed file with 33 additions and 4 deletions.
37 changes: 33 additions & 4 deletions hydra-plutus/src/Hydra/Contract/Initial.hs
Original file line number Diff line number Diff line change
Expand Up @@ -10,6 +10,7 @@ import PlutusTx.Prelude
import Hydra.Contract.Commit (Commit (..))
import qualified Hydra.Contract.Commit as Commit
import Plutus.Extras (ValidatorType, scriptValidatorHash, wrapValidator)
import Plutus.V1.Ledger.Value (assetClass, assetClassValueOf)
import Plutus.V2.Ledger.Api (
CurrencySymbol,
Datum (..),
Expand All @@ -28,6 +29,8 @@ import Plutus.V2.Ledger.Api (
Validator (getValidator),
ValidatorHash,
Value (getValue),
adaSymbol,
adaToken,
mkValidatorScript,
)
import Plutus.V2.Ledger.Contexts (findDatum, findOwnInput, findTxInByTxOutRef, scriptOutputsAt, valueLockedBy)
Expand Down Expand Up @@ -85,7 +88,8 @@ checkAuthorAndHeadPolicy ::
CurrencySymbol ->
Bool
checkAuthorAndHeadPolicy context@ScriptContext{scriptContextTxInfo = txInfo} headId =
unTokenName ourParticipationTokenName `elem` (getPubKeyHash <$> txInfoSignatories txInfo)
traceIfFalse "Missing or invalid commit author" $
unTokenName ourParticipationTokenName `elem` (getPubKeyHash <$> txInfoSignatories txInfo)
where
ourParticipationTokenName =
case AssocMap.lookup headId (getValue initialValue) of
Expand All @@ -110,7 +114,10 @@ checkCommit commitValidator committedRef context@ScriptContext{scriptContextTxIn
where
checkCommittedValue =
traceIfFalse "lockedValue does not match" $
lockedValue == initialValue + committedValue
traceIfFalse ("lockedValue: " `appendString` debugValue lockedValue) $
traceIfFalse ("initialValue: " `appendString` debugValue initialValue) $
traceIfFalse ("comittedValue: " `appendString` debugValue committedValue) $
lockedValue == initialValue + committedValue

checkLockedCommit =
case (committedTxOut, lockedCommit) of
Expand All @@ -121,8 +128,9 @@ checkCommit commitValidator committedRef context@ScriptContext{scriptContextTxIn
(Just{}, Nothing) ->
traceError "committed TxOut, but nothing in output datum"
(Just (ref, txOut), Just Commit{input, preSerializedOutput}) ->
Builtins.serialiseData (toBuiltinData txOut) == preSerializedOutput
&& ref == input
traceIfFalse "mismatch committed TxOut in datum" $
Builtins.serialiseData (toBuiltinData txOut) == preSerializedOutput
&& ref == input

initialValue =
maybe mempty (txOutValue . txInInfoResolved) $ findOwnInput context
Expand Down Expand Up @@ -152,6 +160,27 @@ checkCommit commitValidator committedRef context@ScriptContext{scriptContextTxIn
mCommit
_ -> traceError "expected single commit output"

debugValue v =
debugInteger . assetClassValueOf v $ assetClass adaSymbol adaToken

-- | Show an 'Integer' as decimal number. This is very inefficient and only
-- should be used for debugging.
debugInteger :: Integer -> BuiltinString
debugInteger i
| i == 0 = "0"
| i == 1 = "1"
| i == 2 = "2"
| i == 3 = "3"
| i == 4 = "4"
| i == 5 = "5"
| i == 6 = "6"
| i == 7 = "7"
| i == 8 = "8"
| i == 9 = "9"
| i >= 10 = debugInteger (i `quotient` 10) `appendString` "0"
| otherwise = "-" `appendString` debugInteger (negate i)
{-# INLINEABLE debugInteger #-}

compiledValidator :: CompiledCode ValidatorType
compiledValidator =
$$(PlutusTx.compile [||wrap . validator||])
Expand Down

0 comments on commit 964a54c

Please sign in to comment.