Skip to content

Commit

Permalink
Avoid passing network id to options and faucet keys on generators
Browse files Browse the repository at this point in the history
As we forcing the bench to run on devnet for the moment.
  • Loading branch information
ffakenz committed Aug 13, 2024
1 parent 48fb896 commit c623c2a
Show file tree
Hide file tree
Showing 7 changed files with 39 additions and 50 deletions.
10 changes: 4 additions & 6 deletions hydra-cluster/bench/Bench/EndToEnd.hs
Original file line number Diff line number Diff line change
Expand Up @@ -28,7 +28,7 @@ import Data.Scientific (Scientific)
import Data.Set ((\\))
import Data.Set qualified as Set
import Data.Time (UTCTime (UTCTime), utctDayTime)
import Hydra.Cardano.Api (NetworkId, PaymentKey, SocketPath, Tx, TxId, UTxO, VerificationKey, getVerificationKey, signTx)
import Hydra.Cardano.Api (NetworkId, SocketPath, Tx, TxId, UTxO, getVerificationKey, signTx)
import Hydra.Cluster.Faucet (FaucetLog (..), publishHydraScriptsAs, returnFundsToFaucet', seedFromFaucet)
import Hydra.Cluster.Fixture (Actor (..))
import Hydra.Cluster.Scenarios (
Expand Down Expand Up @@ -102,12 +102,11 @@ benchDemo ::
NetworkId ->
SocketPath ->
NominalDiffTime ->
VerificationKey PaymentKey ->
[SigningKey HydraKey] ->
FilePath ->
Dataset ->
IO Summary
benchDemo networkId nodeSocket timeoutSeconds faucetVk hydraKeys workDir dataset@Dataset{clientDatasets, fundingTransaction} = do
benchDemo networkId nodeSocket timeoutSeconds hydraKeys workDir dataset@Dataset{clientDatasets, fundingTransaction} = do
putStrLn $ "Test logs available in: " <> (workDir </> "test.log")
withFile (workDir </> "test.log") ReadWriteMode $ \hdl ->
withTracerOutputTo hdl "Test" $ \tracer ->
Expand Down Expand Up @@ -135,11 +134,10 @@ benchDemo networkId nodeSocket timeoutSeconds faucetVk hydraKeys workDir dataset
returnFaucetFunds tracer node cKeys = do
putTextLn "Returning funds to faucet"
let faucetTracer = contramap FromFaucet tracer
let toSenders (ClientKeys sk esk) = [(getVerificationKey sk, sk), (getVerificationKey esk, esk)]
let senders = concatMap @[] toSenders cKeys
let senders = concatMap @[] (\(ClientKeys sk esk) -> [sk, esk]) cKeys
mapM_
( \sender -> do
returnAmount <- returnFundsToFaucet' faucetTracer node faucetVk sender
returnAmount <- returnFundsToFaucet' faucetTracer node sender
traceWith faucetTracer $ ReturnedFunds{actor = show sender, returnAmount}
)
senders
Expand Down
11 changes: 6 additions & 5 deletions hydra-cluster/bench/Bench/Options.hs
Original file line number Diff line number Diff line change
Expand Up @@ -2,9 +2,9 @@ module Bench.Options where

import Hydra.Prelude

import Hydra.Cardano.Api (NetworkId, SocketPath)
import Hydra.Cardano.Api (SocketPath)
import Hydra.Chain (maximumNumberOfParties)
import Hydra.Options (networkIdParser, nodeSocketParser)
import Hydra.Options (nodeSocketParser)
import Options.Applicative (
Parser,
ParserInfo,
Expand Down Expand Up @@ -48,7 +48,6 @@ data Options
{ outputDirectory :: Maybe FilePath
, scalingFactor :: Int
, timeoutSeconds :: NominalDiffTime
, networkId :: NetworkId
, nodeSocket :: SocketPath
, hydraSigningKeys :: [FilePath]
}
Expand Down Expand Up @@ -173,7 +172,10 @@ demoOptionsInfo =
info
demoOptionsParser
( progDesc
"Run scenarios from local running demo."
"Run bench scenario over local demo. \
\ This requires having in the background: \
\ * cardano node running on specified node-socket. \
\ * three hydra nodes listening on ports 4001, 4002 and 4003."
)

demoOptionsParser :: Parser Options
Expand All @@ -182,7 +184,6 @@ demoOptionsParser =
<$> optional outputDirectoryParser
<*> scalingFactorParser
<*> timeoutParser
<*> networkIdParser
<*> nodeSocketParser
<*> many hydraSigningKeyFileParser

Expand Down
13 changes: 6 additions & 7 deletions hydra-cluster/bench/Main.hs
Original file line number Diff line number Diff line change
Expand Up @@ -11,7 +11,7 @@ import Bench.Summary (Summary (..), markdownReport, textReport)
import Data.Aeson (eitherDecodeFileStrict', encodeFile)
import Hydra.Cardano.Api (AsType (..))
import Hydra.Chain.Direct.Util (readFileTextEnvelopeThrow)
import Hydra.Cluster.Fixture (Actor (..))
import Hydra.Cluster.Fixture (Actor (..), defaultNetworkId)
import Hydra.Cluster.Util (keysFor)
import Hydra.Crypto (AsType (..))
import Hydra.Generator (ClientKeys (..), Dataset (..), genDatasetConstantUTxODemo, generateConstantUTxODataset)
Expand Down Expand Up @@ -39,7 +39,7 @@ main =
DatasetOptions{datasetFiles, outputDirectory, timeoutSeconds, startingNodeId} -> do
let action = bench startingNodeId timeoutSeconds
run outputDirectory datasetFiles action
DemoOptions{outputDirectory, scalingFactor, timeoutSeconds, networkId, nodeSocket, hydraSigningKeys} -> do
DemoOptions{outputDirectory, scalingFactor, timeoutSeconds, nodeSocket, hydraSigningKeys} -> do
workDir <- createSystemTempDirectory "demo-bench"
clientKeys <- do
let actors = [(Alice, AliceFunds), (Bob, BobFunds), (Carol, CarolFunds)]
Expand All @@ -49,16 +49,15 @@ main =
pure $ ClientKeys sk fundsSk
forM actors toClientKeys
hydraKeys <- mapM (readFileTextEnvelopeThrow (AsSigningKey AsHydraKey)) hydraSigningKeys
playDemo outputDirectory timeoutSeconds scalingFactor clientKeys workDir networkId nodeSocket hydraKeys
playDemo outputDirectory timeoutSeconds scalingFactor clientKeys workDir nodeSocket hydraKeys
where
playDemo outputDirectory timeoutSeconds scalingFactor clientKeys workDir networkId nodeSocket hydraKeys = do
(faucetVk, faucetSk) <- keysFor Faucet
playDemo outputDirectory timeoutSeconds scalingFactor clientKeys workDir nodeSocket hydraKeys = do
putStrLn $ "Generating single dataset in work directory: " <> workDir
numberOfTxs <- generate $ scale (* scalingFactor) getSize
dataset <- genDatasetConstantUTxODemo (faucetVk, faucetSk) clientKeys numberOfTxs networkId nodeSocket
dataset <- genDatasetConstantUTxODemo clientKeys numberOfTxs defaultNetworkId nodeSocket
let datasetPath = workDir </> "dataset.json"
saveDataset datasetPath dataset
let action = benchDemo networkId nodeSocket timeoutSeconds faucetVk hydraKeys
let action = benchDemo defaultNetworkId nodeSocket timeoutSeconds hydraKeys
run outputDirectory [datasetPath] action

play outputDirectory timeoutSeconds scalingFactor clusterSize startingNodeId workDir = do
Expand Down
28 changes: 6 additions & 22 deletions hydra-cluster/src/CardanoClient.hs
Original file line number Diff line number Diff line change
Expand Up @@ -111,20 +111,21 @@ waitForUTxO node utxo =
txOut ->
error $ "Unexpected TxOut " <> show txOut

mkInitialTx ::
-- | Helper used to generate transaction datasets for use in hydra-cluster benchmarks.
buildRawTransaction ::
NetworkId ->
-- | Initial input from which to spend
TxIn ->
-- | Owner of the 'initialFund'.
SigningKey PaymentKey ->
-- | Amount of initialFunds
Coin ->
-- | Recipients and amounts to pay in this transaction.
[(VerificationKey PaymentKey, Coin)] ->
TxIn ->
-- | Initial input from which to spend
Tx
mkInitialTx networkId signingKey initialAmount recipients initialInput =
buildRawTransaction networkId initialInput signingKey initialAmount recipients =
case buildRaw [initialInput] (recipientOutputs <> [changeOutput]) of
Left err -> error $ "Fail to build genesis transations: " <> show err
Left err -> error $ "Fail to build raw transations: " <> show err
Right tx -> sign signingKey tx
where
totalSent = foldMap snd recipients
Expand All @@ -145,23 +146,6 @@ mkInitialTx networkId signingKey initialAmount recipients initialInput =
TxOutDatumNone
ReferenceScriptNone

mkGenesisTx ::
NetworkId ->
-- | Owner of the 'initialFund'.
SigningKey PaymentKey ->
-- | Amount of initialFunds
Coin ->
-- | Recipients and amounts to pay in this transaction.
[(VerificationKey PaymentKey, Coin)] ->
Tx
mkGenesisTx networkId signingKey initialAmount recipients =
mkInitialTx networkId signingKey initialAmount recipients initialInput
where
initialInput =
genesisUTxOPseudoTxIn
networkId
(unsafeCastHash $ verificationKeyHash $ getVerificationKey signingKey)

data RunningNode = RunningNode
{ nodeSocket :: SocketPath
, networkId :: NetworkId
Expand Down
2 changes: 2 additions & 0 deletions hydra-cluster/src/CardanoNode.hs
Original file line number Diff line number Diff line change
Expand Up @@ -140,6 +140,8 @@ findRunningCardanoNode tracer workDir knownNetwork = do

CardanoNodeArgs{nodeSocket} = defaultCardanoNodeArgs

-- | Tries to find an communicate with an existing cardano-node running in given
-- network id and socket path.
findRunningCardanoNode' :: Tracer IO NodeLog -> NetworkId -> SocketPath -> IO (Maybe RunningNode)
findRunningCardanoNode' tracer networkId nodeSocket = do
try (queryGenesisParameters networkId nodeSocket QueryTip) >>= \case
Expand Down
10 changes: 5 additions & 5 deletions hydra-cluster/src/Hydra/Cluster/Faucet.hs
Original file line number Diff line number Diff line change
Expand Up @@ -107,19 +107,19 @@ returnFundsToFaucet ::
Actor ->
IO ()
returnFundsToFaucet tracer node sender = do
(faucetVk, _) <- keysFor Faucet
senderKeys <- keysFor sender
returnAmount <- returnFundsToFaucet' tracer node faucetVk senderKeys
returnAmount <- returnFundsToFaucet' tracer node (snd senderKeys)
traceWith tracer $ ReturnedFunds{actor = actorName sender, returnAmount}

returnFundsToFaucet' ::
Tracer IO FaucetLog ->
RunningNode ->
VerificationKey PaymentKey ->
(VerificationKey PaymentKey, SigningKey PaymentKey) ->
SigningKey PaymentKey ->
IO Coin
returnFundsToFaucet' tracer RunningNode{networkId, nodeSocket} faucetVk (senderVk, senderSk) = do
returnFundsToFaucet' tracer RunningNode{networkId, nodeSocket} senderSk = do
(faucetVk, _) <- keysFor Faucet
let faucetAddress = mkVkAddress networkId faucetVk
let senderVk = getVerificationKey senderSk
utxo <- queryUTxOFor networkId nodeSocket QueryTip senderVk
if null utxo
then pure 0
Expand Down
15 changes: 10 additions & 5 deletions hydra-cluster/src/Hydra/Generator.hs
Original file line number Diff line number Diff line change
Expand Up @@ -5,7 +5,7 @@ import Hydra.Prelude hiding (size)

import Cardano.Api.Ledger (PParams)
import Cardano.Api.UTxO qualified as UTxO
import CardanoClient (buildTransaction, mkGenesisTx, sign)
import CardanoClient (buildRawTransaction, buildTransaction, sign)
import Control.Monad (foldM)
import Data.Aeson (object, withObject, (.:), (.=))
import Data.Default (def)
Expand Down Expand Up @@ -138,24 +138,29 @@ makeGenesisFundingTx faucetSk clientKeys = do
-- i.e. like "0001010100010001000000010100000001010001000101000000010101010001".
pure (getVerificationKey externalSigningKey, amount)
let fundingTransaction =
mkGenesisTx
buildRawTransaction
networkId
initialInput
faucetSk
(Coin availableInitialFunds)
clientFunds
pure fundingTransaction
where
initialInput =
genesisUTxOPseudoTxIn
networkId
(unsafeCastHash $ verificationKeyHash $ getVerificationKey faucetSk)

genDatasetConstantUTxODemo ::
-- | The faucet keys
(VerificationKey PaymentKey, SigningKey PaymentKey) ->
-- | Clients
[ClientKeys] ->
-- | Number of transactions
Int ->
NetworkId ->
SocketPath ->
IO Dataset
genDatasetConstantUTxODemo (faucetVk, faucetSk) allClientKeys nTxs networkId' nodeSocket = do
genDatasetConstantUTxODemo allClientKeys nTxs networkId' nodeSocket = do
(faucetVk, faucetSk) <- keysFor Faucet
let nClients = length allClientKeys
faucetUTxO <- queryUTxOFor networkId nodeSocket QueryTip faucetVk
let (Coin fundsAvailable) = selectLovelace (balance @Tx faucetUTxO)
Expand Down

0 comments on commit c623c2a

Please sign in to comment.