Skip to content

Commit

Permalink
Use ledger types for hashing scripts
Browse files Browse the repository at this point in the history
This avoids use of 'ValidatorHash' et al and uses only 'Script' to
serialize it into a ledger 'Script era' and take it from there.
  • Loading branch information
ch1bo authored and abailly-iohk committed Oct 14, 2021
1 parent 51fea9c commit 4042fdc
Show file tree
Hide file tree
Showing 3 changed files with 18 additions and 24 deletions.
37 changes: 14 additions & 23 deletions hydra-node/src/Hydra/Chain/Direct/Tx.hs
Expand Up @@ -11,16 +11,15 @@ module Hydra.Chain.Direct.Tx where
import Hydra.Prelude

import Cardano.Binary (serialize)
import Cardano.Crypto.Hash (Hash, hashFromBytes)
import Cardano.Ledger.Address (Addr (Addr))
import Cardano.Ledger.Alonzo (AlonzoEra, Script)
import Cardano.Ledger.Alonzo.Data (Data (Data), hashData)
import Cardano.Ledger.Alonzo.Scripts (ExUnits (..), Script (PlutusScript), Tag (Spend))
import Cardano.Ledger.Alonzo.Tx (IsValid (IsValid), ValidatedTx (..))
import Cardano.Ledger.Alonzo.TxBody (TxBody (..), TxOut (TxOut))
import Cardano.Ledger.Alonzo.TxWitness (RdmrPtr (RdmrPtr), Redeemers (..), TxDats (..), TxWitness (..), unTxDats)
import Cardano.Ledger.Crypto (ADDRHASH, StandardCrypto)
import Cardano.Ledger.Hashes (EraIndependentScript)
import Cardano.Ledger.Crypto (StandardCrypto)
import Cardano.Ledger.Era (hashScript)
import Cardano.Ledger.ShelleyMA.Timelocks (ValidityInterval (..))
import Cardano.Ledger.Val (inject)
import qualified Data.Map as Map
Expand All @@ -31,12 +30,13 @@ import Hydra.Contract.Head (State (Initial))
import Hydra.Data.ContestationPeriod (contestationPeriodFromDiffTime, contestationPeriodToDiffTime)
import Hydra.Data.Party (partyFromVerKey, partyToVerKey)
import Hydra.Party (anonymousParty, vkey)
import Plutus.V1.Ledger.Api (PubKeyHash (..), ValidatorHash (ValidatorHash), fromBuiltin, fromData, toData)
import Plutus.V1.Ledger.Api (PubKeyHash (..), fromData, toData)
import qualified Plutus.V1.Ledger.Api as Plutus
import Shelley.Spec.Ledger.API (
Coin (..),
Credential (ScriptHashObj),
Network (Testnet),
ScriptHash (ScriptHash),
ScriptHash,
StakeReference (StakeRefNull),
StrictMaybe (..),
TxIn,
Expand Down Expand Up @@ -93,7 +93,7 @@ initTx HeadParameters{contestationPeriod, parties} txIn =
-- thread token eventually. For now, this is just the initial script as well,
-- although this could be really some arbitrary address. After all it is also
-- later quite arbitrary/different per Head.
headAddress = validatorHashToAddr Initial.validatorHash
headAddress = scriptAddr $ PlutusScript "foo"

-- REVIEW(SN): how much to store here / minUtxoValue / depending on assets?
headValue = inject (Coin 0)
Expand Down Expand Up @@ -139,13 +139,9 @@ abortTx (txIn, pkh) =

scripts = Map.singleton initialScriptHash initialScript

-- FIXME(SN): Ideally use the ledgers `hashScript` here, but it seems to be
-- different from what the Plutus ValidatorHash wraps and fails lookup
initialScriptHash = case validatorHashToHash Initial.validatorHash of
Nothing -> error "ValidatorHash does not hold a proper hash" -- should not happen^TM
Just h -> ScriptHash h
initialScriptHash = hashScript @Era initialScript

initialScript = PlutusScript . toShort . fromLazy $ serialize Initial.validatorScript
initialScript = plutusScript Initial.validatorScript

dats = TxDats $ Map.singleton initialDatumHash initialDatum

Expand Down Expand Up @@ -203,19 +199,14 @@ mkUnsignedTx body datums redeemers scripts =
, auxiliaryData = SNothing
}

-- | Convert a plutus address to its ledger representation.
validatorHashToAddr :: ValidatorHash -> Addr StandardCrypto
validatorHashToAddr vh =
-- | Get the ledger address for a given plutus script.
scriptAddr :: Script Era -> Addr StandardCrypto
scriptAddr script =
Addr
network
(ScriptHashObj $ ScriptHash hash)
(ScriptHashObj $ hashScript @Era script)
-- REVIEW(SN): stake head funds?
StakeRefNull
where
hash = case validatorHashToHash vh of
Nothing -> error $ "ValidatorHash is not (the right) hash: " <> show vh
Just h -> h

validatorHashToHash :: ValidatorHash -> Maybe (Hash (ADDRHASH StandardCrypto) EraIndependentScript)
validatorHashToHash (ValidatorHash builtinByteString) =
hashFromBytes @(ADDRHASH StandardCrypto) (fromBuiltin builtinByteString)
plutusScript :: Plutus.Script -> Script Era
plutusScript = PlutusScript . toShort . fromLazy . serialize
2 changes: 1 addition & 1 deletion hydra-node/test/Hydra/Chain/Direct/TxSpec.hs
Expand Up @@ -94,7 +94,7 @@ spec =
-- input governed by initial script and a 'Plutus.PubKeyHash' datum
utxo = UTxO $ Map.singleton txIn txOut
txOut = TxOut initialAddress initialValue (SJust initialDatumHash)
initialAddress = validatorHashToAddr Initial.validatorHash
initialAddress = scriptAddr $ plutusScript Initial.validatorScript
initialValue = inject (Coin 0)
initialDatumHash = hashData @Era . Data $ toData pkh
results = validateTxScriptsUnlimited tx utxo
Expand Down
3 changes: 3 additions & 0 deletions hydra-plutus/src/Hydra/Contract/Initial.hs
Expand Up @@ -87,12 +87,15 @@ typedValidator = Scripts.mkTypedValidator @Initial
wrap = Scripts.wrapValidator @(DatumType Initial) @(RedeemerType Initial)
{- ORMOLU_ENABLE -}

-- | Do not use this outside of plutus land.
validatorHash :: ValidatorHash
validatorHash = Scripts.validatorHash typedValidator

-- | Do not use this outside of plutus land.
datum :: DatumType Initial -> Datum
datum a = Datum (toBuiltinData a)

-- | Do not use this outside of plutus land.
address :: Address
address = scriptHashAddress validatorHash

Expand Down

0 comments on commit 4042fdc

Please sign in to comment.