Skip to content

Commit

Permalink
Re-add commit tx metadata and re-format the code
Browse files Browse the repository at this point in the history
  • Loading branch information
v0d1ch authored and Sasha Bogicevic committed Apr 17, 2024
1 parent a18dd88 commit e20dc7d
Show file tree
Hide file tree
Showing 6 changed files with 20 additions and 25 deletions.
2 changes: 1 addition & 1 deletion hydra-cluster/src/HydraNode.hs
Expand Up @@ -24,7 +24,7 @@ import Hydra.API.HTTPServer (DraftCommitTxRequest (..), DraftCommitTxResponse (.
import Hydra.Cluster.Util (readConfigFile)
import Hydra.ContestationPeriod (ContestationPeriod)
import Hydra.Crypto (HydraKey)
import Hydra.Ledger.Cardano (TxOutWithWitness(..))
import Hydra.Ledger.Cardano (TxOutWithWitness (..))
import Hydra.Logging (Tracer, Verbosity (..), traceWith)
import Hydra.Network (Host (Host), NodeId (NodeId))
import Hydra.Network qualified as Network
Expand Down
2 changes: 1 addition & 1 deletion hydra-node/src/Hydra/API/Server.hs
Expand Up @@ -38,9 +38,9 @@ import Network.Wai.Handler.Warp (
defaultSettings,
runSettings,
setBeforeMainLoop,
setOnExceptionResponse,
setHost,
setOnException,
setOnExceptionResponse,
setPort,
)
import Network.Wai.Handler.WebSockets (websocketsOr)
Expand Down
11 changes: 3 additions & 8 deletions hydra-node/src/Hydra/Chain/Direct/Tx.hs
Expand Up @@ -19,19 +19,15 @@ import Cardano.Ledger.Api (
AlonzoPlutusPurpose (..),
AsIndex (..),
Redeemers (..),
TxDats (..),
auxDataHashTxBodyL,
auxDataTxL,
bodyTxL,
datsTxWitsL,
hashData,
hashScript,
inputsTxBodyL,
mkAlonzoTxAuxData,
outputsTxBodyL,
rdmrsTxWitsL,
referenceInputsTxBodyL,
reqSignerHashesTxBodyL,
scriptTxWitsL,
unRedeemers,
witsTxL,
)
Expand All @@ -41,7 +37,6 @@ import Control.Lens ((%~), (.~), (<>~), (^.))
import Data.Aeson qualified as Aeson
import Data.ByteString qualified as BS
import Data.ByteString.Base16 qualified as Base16
import Data.List qualified as List
import Data.Map qualified as Map
import Data.Sequence.Strict ((<|))
import Data.Set qualified as Set
Expand Down Expand Up @@ -263,8 +258,8 @@ commitTx networkId scriptRegistry headId party utxoToCommit blueprintTx (initial
& bodyTxL . referenceInputsTxBodyL <>~ Set.fromList [toLedgerTxIn initialScriptRef]
& bodyTxL . outputsTxBodyL %~ (toLedgerTxOut commitOutput <|)
& bodyTxL . reqSignerHashesTxBodyL <>~ Set.singleton (toLedgerKeyHash vkh)
-- TODO: construct metadata properly
-- & bodyTxL . auxDataHashTxBodyL .~ SJust (hashAlonzoTxAuxData txAuxMetadata)
& bodyTxL . auxDataHashTxBodyL .~ (SJust $ hashAlonzoTxAuxData txAuxMetadata)
& auxDataTxL .~ SJust txAuxMetadata
existingWits = ledgerBlueprintTx ^. witsTxL
currentInputs = ledgerBlueprintTx ^. bodyTxL . inputsTxBodyL
commitInputs = UTxO.inputSet utxoToCommit
Expand Down
5 changes: 3 additions & 2 deletions hydra-node/test/Hydra/Chain/Direct/Contract/Commit.hs
Expand Up @@ -29,11 +29,12 @@ import Hydra.Contract.Initial qualified as Initial
import Hydra.Contract.InitialError (InitialError (..))
import Hydra.Ledger.Cardano (
genAddressInEra,
genSigningKey,
genUTxOAdaOnlyOfSize,
genValue,
genVerificationKey,
mkBlueprintTxFromUTxOAndWitness,
toUTxOWithWitness, genSigningKey,
toUTxOWithWitness,
)
import Hydra.Party (Party)
import Test.QuickCheck (elements, oneof, scale, suchThat)
Expand Down Expand Up @@ -75,7 +76,7 @@ healthyCommitTx =
commitParty = generateWith arbitrary 42

commitSigningKey :: SigningKey PaymentKey
commitSigningKey = genSigningKey `generateWith ` 42
commitSigningKey = genSigningKey `generateWith` 42

commitVerificationKey :: VerificationKey PaymentKey
commitVerificationKey = getVerificationKey commitSigningKey
Expand Down
2 changes: 0 additions & 2 deletions hydra-node/test/Hydra/Chain/Direct/HandlersSpec.hs
Expand Up @@ -10,14 +10,12 @@ import Data.Maybe (fromJust)
import Hydra.Cardano.Api (
BlockHeader (..),
ChainPoint (ChainPointAtGenesis),
KeyWitnessInCtx (..),
PaymentKey,
SlotNo (..),
Tx,
VerificationKey,
genTxIn,
getChainPoint,
pattern KeyWitness,
)

import Hydra.Chain (ChainEvent (..), HeadParameters, OnChainTx (..), chainStateSlot, currentState, initHistory, maximumNumberOfParties)
Expand Down
23 changes: 12 additions & 11 deletions hydra-node/test/Hydra/Chain/Direct/TxSpec.hs
Expand Up @@ -53,6 +53,7 @@ import Test.QuickCheck (
property,
vectorOf,
withMaxSuccess,
(=/=),
(===),
)
import Test.QuickCheck.Instances.Semigroup ()
Expand Down Expand Up @@ -187,17 +188,17 @@ spec =
<> registryUTxO scriptRegistry

checkCoverage $
conjoin
[ transactionEvaluates (blueprintTx', utxoToCommit)
, transactionEvaluates (signedCommitTx, commitUTxO)
, blueprintTx ^. isValidTxL === tx ^. isValidTxL
, blueprintTx ^. auxDataTxL =/= tx ^. auxDataTxL
, property (length (blueprintBody ^. inputsTxBodyL) <= length (commitTxBody ^. inputsTxBodyL))
, property (length (blueprintBody ^. outputsTxBodyL) <= length (commitTxBody ^. outputsTxBodyL))
, property (length (blueprintBody ^. referenceInputsTxBodyL) <= length (commitTxBody ^. referenceInputsTxBodyL))
, property (length (blueprintBody ^. reqSignerHashesTxBodyL) <= length (commitTxBody ^. reqSignerHashesTxBodyL))
]
& cover 50 (containsScript utxoWithWitnesses) "TxOutWithWitness contains script witness"
conjoin
[ transactionEvaluates (blueprintTx', utxoToCommit)
, transactionEvaluates (signedCommitTx, commitUTxO)
, blueprintTx ^. isValidTxL === tx ^. isValidTxL
, blueprintTx ^. auxDataTxL =/= tx ^. auxDataTxL
, property (length (blueprintBody ^. inputsTxBodyL) <= length (commitTxBody ^. inputsTxBodyL))
, property (length (blueprintBody ^. outputsTxBodyL) <= length (commitTxBody ^. outputsTxBodyL))
, property (length (blueprintBody ^. referenceInputsTxBodyL) <= length (commitTxBody ^. referenceInputsTxBodyL))
, property (length (blueprintBody ^. reqSignerHashesTxBodyL) <= length (commitTxBody ^. reqSignerHashesTxBodyL))
]
& cover 50 (containsScript utxoWithWitnesses) "TxOutWithWitness contains script witness"

withinTxExecutionBudget :: EvaluationReport -> Property
withinTxExecutionBudget report =
Expand Down

0 comments on commit e20dc7d

Please sign in to comment.