Skip to content

Commit d21bc45

Browse files
committed
cardano-testnet | remove fromString where not needed
1 parent 4fc73bb commit d21bc45

File tree

18 files changed

+51
-57
lines changed

18 files changed

+51
-57
lines changed

cardano-testnet/src/Testnet/Components/Query.hs

Lines changed: 10 additions & 5 deletions
Original file line numberDiff line numberDiff line change
@@ -49,7 +49,6 @@ import qualified Cardano.Api.Ledger as L
4949
import Cardano.Api.Shelley (LedgerProtocolParameters (..), ShelleyLedgerEra)
5050
import qualified Cardano.Api.Tx.UTxO as Utxo
5151

52-
import Cardano.Crypto.Hash (hashToStringAsHex)
5352
import Cardano.Ledger.Api (ConwayGovState)
5453
import qualified Cardano.Ledger.Api as L
5554
import qualified Cardano.Ledger.Conway.Governance as L
@@ -609,13 +608,19 @@ getDelegationState epochStateView = do
609608
pure $ L.toStakeCredentials pools
610609

611610
-- | Returns the transaction index of a transaction with a given amount and ID.
612-
getTxIx :: forall m era. HasCallStack => MonadTest m => ShelleyBasedEra era -> String -> L.Coin -> (AnyNewEpochState, SlotNo, BlockNo) -> m (Maybe Int)
611+
getTxIx :: forall m era. HasCallStack
612+
=> MonadTest m
613+
=> ShelleyBasedEra era
614+
-> TxId
615+
-> L.Coin
616+
-> (AnyNewEpochState, SlotNo, BlockNo)
617+
-> m (Maybe TxIx)
613618
getTxIx sbe txId amount (AnyNewEpochState sbe' _ tbs, _, _) = do
614619
Refl <- H.leftFail $ assertErasEqual sbe sbe'
615620
shelleyBasedEraConstraints sbe' $ do
616-
return $ Map.foldlWithKey (\acc (TxIn (TxId thisTxId) (TxIx thisTxIx)) (TxOut _ txOutValue _ _) ->
621+
return $ Map.foldlWithKey (\acc (TxIn thisTxId thisTxIx) (TxOut _ txOutValue _ _) ->
617622
case acc of
618-
Nothing | hashToStringAsHex thisTxId == txId &&
619-
txOutValueToLovelace txOutValue == amount -> Just $ fromIntegral thisTxIx
623+
Nothing | thisTxId == txId &&
624+
txOutValueToLovelace txOutValue == amount -> Just thisTxIx
620625
| otherwise -> Nothing
621626
x -> x) Nothing $ getLedgerTablesUTxOValues sbe' tbs

cardano-testnet/src/Testnet/Process/Cli/DRep.hs

Lines changed: 5 additions & 6 deletions
Original file line numberDiff line numberDiff line change
@@ -34,7 +34,6 @@ import Data.Text (Text)
3434
import qualified Data.Text as Text
3535
import Data.Typeable (Typeable)
3636
import Data.Word (Word16)
37-
import GHC.Exts (fromString)
3837
import GHC.Stack
3938
import Lens.Micro ((^?))
4039
import System.Directory (makeAbsolute)
@@ -155,7 +154,7 @@ generateVoteFiles
155154
-- stored.
156155
-> String -- ^ Name for the subfolder that will be created under 'work' to store
157156
-- the output voting files.
158-
-> String -- ^ Transaction ID string of the governance action.
157+
-> TxId -- ^ Transaction ID string of the governance action.
159158
-> Word16 -- ^ Index of the governance action.
160159
-> [(KeyPair PaymentKey, [Char])] -- ^ List of tuples where each tuple contains a 'PaymentKeyPair'
161160
-- representing the DRep key pair and a 'String' representing the
@@ -168,8 +167,8 @@ generateVoteFiles execConfig work prefix governanceActionTxId governanceActionIn
168167
void $ execCli' execConfig
169168
[ "conway", "governance", "vote", "create"
170169
, "--" ++ vote
171-
, "--governance-action-tx-id", governanceActionTxId
172-
, "--governance-action-index", show @Word16 governanceActionIndex
170+
, "--governance-action-tx-id", prettyShow governanceActionTxId
171+
, "--governance-action-index", show governanceActionIndex
173172
, "--drep-verification-key-file", verificationKeyFp drepKeyPair
174173
, "--out-file", unFile path
175174
]
@@ -354,7 +353,7 @@ makeActivityChangeProposal
354353
-> KeyPair StakeKey -- ^ registered staking keys
355354
-> PaymentKeyInfo -- ^ Wallet that will pay for the transaction.
356355
-> EpochInterval -- ^ Number of epochs to wait for the proposal to be registered by the chain.
357-
-> m (String, Word16) -- ^ The transaction id and the index of the governance action.
356+
-> m (TxId, Word16) -- ^ The transaction id and the index of the governance action.
358357
makeActivityChangeProposal execConfig epochStateView ceo work
359358
prevGovActionInfo drepActivity stakeKeyPair wallet timeout = do
360359

@@ -421,6 +420,6 @@ makeActivityChangeProposal execConfig epochStateView ceo work
421420

422421
governanceActionIndex <-
423422
H.nothingFailM $ watchEpochStateUpdate epochStateView timeout $ \(anyNewEpochState, _, _) ->
424-
return $ maybeExtractGovernanceActionIndex (fromString governanceActionTxId) anyNewEpochState
423+
return $ maybeExtractGovernanceActionIndex governanceActionTxId anyNewEpochState
425424

426425
return (governanceActionTxId, governanceActionIndex)

cardano-testnet/src/Testnet/Process/Cli/SPO.hs

Lines changed: 2 additions & 2 deletions
Original file line numberDiff line numberDiff line change
@@ -433,7 +433,7 @@ generateVoteFiles :: (HasCallStack, MonadTest m, MonadIO m, MonadCatch m)
433433
-- stored.
434434
-> String -- ^ Name for the subfolder that will be created under 'work' to store
435435
-- the output voting files.
436-
-> String -- ^ Transaction ID string of the governance action.
436+
-> TxId -- ^ Transaction ID string of the governance action.
437437
-> Word16 -- ^ Index of the governance action.
438438
-> [(SpoNodeKeys, [Char])] -- ^ List of tuples where each tuple contains a 'SpoNodeKeys'
439439
-- representing the SPO keys and a 'String' representing the
@@ -446,7 +446,7 @@ generateVoteFiles ceo execConfig work prefix governanceActionTxId governanceActi
446446
void $ execCli' execConfig
447447
[ eraToString $ toCardanoEra ceo , "governance", "vote", "create"
448448
, "--" ++ vote
449-
, "--governance-action-tx-id", governanceActionTxId
449+
, "--governance-action-tx-id", prettyShow governanceActionTxId
450450
, "--governance-action-index", show @Word16 governanceActionIndex
451451
, "--cold-verification-key-file", verificationKeyFp $ poolNodeKeysCold spoKeys
452452
, "--out-file", unFile path

cardano-testnet/src/Testnet/Process/Cli/Transaction.hs

Lines changed: 2 additions & 2 deletions
Original file line numberDiff line numberDiff line change
@@ -231,12 +231,12 @@ retrieveTransactionId
231231
=> MonadIO m
232232
=> H.ExecConfig -- ^ Specifies the CLI execution configuration.
233233
-> File SignedTx In -- ^ Signed transaction to be submitted, obtained using 'signTx'.
234-
-> m String
234+
-> m TxId
235235
retrieveTransactionId execConfig signedTxBody = do
236236
txidOutput <- execCli' execConfig
237237
[ "latest", "transaction", "txid"
238238
, "--tx-file", unFile signedTxBody
239239
]
240240
result <- H.leftFail $ A.decodeEither' @A.Value $ fromString txidOutput
241-
H.nothingFail . fmap T.unpack $ result ^? A.key "txhash" . A._String
241+
H.nothingFail $ result ^? A.key "txhash" . A._JSON
242242

cardano-testnet/src/Testnet/Process/Run.hs

Lines changed: 1 addition & 0 deletions
Original file line numberDiff line numberDiff line change
@@ -122,6 +122,7 @@ execCliStdoutToJson :: ()
122122
-> m a
123123
execCliStdoutToJson execConfig cmd = GHC.withFrozenCallStack $ do
124124
result <- execCli' execConfig cmd
125+
H.note_ result
125126
H.leftFail . Aeson.eitherDecode $ fromString result
126127

127128
-- | Create a 'CreateProcess' describing how to start the cardano-cli process

cardano-testnet/test/cardano-testnet-test/Cardano/Testnet/Test/Cli/Plutus/CostCalculation.hs

Lines changed: 7 additions & 12 deletions
Original file line numberDiff line numberDiff line change
@@ -12,11 +12,7 @@ module Cardano.Testnet.Test.Cli.Plutus.CostCalculation
1212
)
1313
where
1414

15-
import Cardano.Api (AnyCardanoEra (AnyCardanoEra),
16-
AnyShelleyBasedEra (AnyShelleyBasedEra), ExceptT, File (File), MonadIO (liftIO),
17-
ShelleyBasedEra (ShelleyBasedEraConway), ToCardanoEra (toCardanoEra),
18-
deserialiseAnyVerificationKey, liftEither, mapSomeAddressVerificationKey,
19-
renderTxIn, serialiseToRawBytesHex, unFile, verificationKeyHash)
15+
import Cardano.Api hiding (Value)
2016
import Cardano.Api.Experimental (Some (Some))
2117
import Cardano.Api.Ledger (EpochInterval (EpochInterval), unCoin)
2218

@@ -25,7 +21,6 @@ import Cardano.Testnet
2521
import Prelude
2622

2723
import Control.Monad (void)
28-
import Control.Monad.Except (runExceptT)
2924
import Data.Aeson (Value, encodeFile)
3025
import qualified Data.Aeson.KeyMap as KeyMap
3126
import Data.Aeson.Types (Value (..), object)
@@ -156,12 +151,12 @@ hprop_ref_plutus_cost_calculation = integrationRetryWorkspace 2 "ref plutus scri
156151
[ eraName
157152
, "transaction", "build"
158153
, "--change-address", Text.unpack $ paymentKeyInfoAddr wallet1
159-
, "--tx-in", txIdLock <> "#" <> show txIxLock
154+
, "--tx-in", prettyShow (TxIn txIdLock txIxLock)
160155
, "--spending-reference-tx-in-inline-datum-present"
161-
, "--spending-tx-in-reference", txIdPublishRefScript <> "#" <> show txIxPublishRefScript
156+
, "--spending-tx-in-reference", prettyShow (TxIn txIdPublishRefScript txIxPublishRefScript)
162157
, "--spending-plutus-script-v3"
163158
, "--spending-reference-tx-in-redeemer-value", "42"
164-
, "--tx-in-collateral", Text.unpack $ renderTxIn largestUTxO
159+
, "--tx-in-collateral", prettyShow largestUTxO
165160
, "--tx-out", Text.unpack (paymentKeyInfoAddr wallet1) <> "+" <> show (unCoin (transferAmount - enoughAmountForFees))
166161
, "--out-file", unFile unsignedUnlockTx
167162
]
@@ -281,10 +276,10 @@ hprop_included_plutus_cost_calculation = integrationRetryWorkspace 2 "included p
281276
[ eraName
282277
, "transaction", "build"
283278
, "--change-address", Text.unpack $ paymentKeyInfoAddr wallet1
284-
, "--tx-in", txIdIncludedScriptLock <> "#" <> show txIxIncludedScriptLock
279+
, "--tx-in", prettyShow (TxIn txIdIncludedScriptLock txIxIncludedScriptLock)
285280
, "--tx-in-script-file", unFile plutusV3Script
286281
, "--tx-in-redeemer-value", "42"
287-
, "--tx-in-collateral", Text.unpack $ renderTxIn newLargestUTxO
282+
, "--tx-in-collateral", prettyShow newLargestUTxO
288283
, "--tx-out", Text.unpack (paymentKeyInfoAddr wallet1) <> "+" <> show (unCoin (includedScriptLockAmount - enoughAmountForFees))
289284
, "--out-file", unFile unsignedIncludedScript
290285
]
@@ -396,7 +391,7 @@ hprop_included_simple_script_cost_calculation = integrationRetryWorkspace 2 "inc
396391
[ eraName
397392
, "transaction", "build"
398393
, "--change-address", Text.unpack $ paymentKeyInfoAddr wallet1
399-
, "--tx-in", txIdSimpleScriptLock <> "#" <> show txIxSimpleScriptLock
394+
, "--tx-in", prettyShow (TxIn txIdSimpleScriptLock txIxSimpleScriptLock)
400395
, "--tx-in-script-file", unFile simpleScript
401396
, "--tx-out", Text.unpack (paymentKeyInfoAddr wallet1) <> "+" <> show (unCoin (lockedAmount - enoughAmountForFees))
402397
, "--witness-override", "2"

cardano-testnet/test/cardano-testnet-test/Cardano/Testnet/Test/Cli/Query.hs

Lines changed: 2 additions & 2 deletions
Original file line numberDiff line numberDiff line change
@@ -319,7 +319,7 @@ hprop_cli_queries = integrationWorkspace "cli-queries" $ \tempAbsBasePath' -> H.
319319
submitTx execConfig cEra signedTx
320320
txId <- retrieveTransactionId execConfig signedTx
321321
-- And we check
322-
H.noteM_ $ execCli' execConfig [ eraName, "query", "tx-mempool", "tx-exists", txId ]
322+
H.noteM_ $ execCli' execConfig [ eraName, "query", "tx-mempool", "tx-exists", prettyShow txId ]
323323

324324
TestQuerySlotNumberCmd ->
325325
-- slot-number
@@ -346,7 +346,7 @@ hprop_cli_queries = integrationWorkspace "cli-queries" $ \tempAbsBasePath' -> H.
346346
-- Query the reference script size
347347
let protocolParametersOutFile = refScriptSizeWork </> "ref-script-size-out.json"
348348
H.noteM_ $ execCli' execConfig [ eraName, "query", "ref-script-size"
349-
, "--tx-in", txId ++ "#" ++ show (txIx :: Int)
349+
, "--tx-in", prettyShow (TxIn txId txIx)
350350
, "--out-file", protocolParametersOutFile
351351
]
352352
H.diffFileVsGoldenFile

cardano-testnet/test/cardano-testnet-test/Cardano/Testnet/Test/Gov/CommitteeAddNew.hs

Lines changed: 2 additions & 3 deletions
Original file line numberDiff line numberDiff line change
@@ -27,7 +27,6 @@ import Data.Default.Class
2727
import qualified Data.Map as Map
2828
import Data.Maybe.Strict
2929
import Data.Set (Set)
30-
import Data.String
3130
import qualified Data.Text as Text
3231
import GHC.Exts (IsList (..))
3332
import GHC.Stack
@@ -227,11 +226,11 @@ hprop_constitutional_committee_add_new = integrationWorkspace "constitutional-co
227226
signTx execConfig cEra work "signed-proposal" (File txbodyFp) [Some $ paymentKeyInfoPair wallet0]
228227
submitTx execConfig cEra signedProposalTx
229228

230-
governanceActionTxId <- H.noteM $ retrieveTransactionId execConfig signedProposalTx
229+
governanceActionTxId <- H.noteShowM $ retrieveTransactionId execConfig signedProposalTx
231230

232231
governanceActionIx <-
233232
H.nothingFailM . watchEpochStateUpdate epochStateView (L.EpochInterval 1) $ \(anyNewEpochState, _, _) ->
234-
pure $ maybeExtractGovernanceActionIndex (fromString governanceActionTxId) anyNewEpochState
233+
pure $ maybeExtractGovernanceActionIndex governanceActionTxId anyNewEpochState
235234

236235
dRepVoteFiles <-
237236
DRep.generateVoteFiles

cardano-testnet/test/cardano-testnet-test/Cardano/Testnet/Test/Gov/DRepActivity.hs

Lines changed: 2 additions & 2 deletions
Original file line numberDiff line numberDiff line change
@@ -217,7 +217,7 @@ activityChangeProposalTest
217217
-- the proposal.
218218
-> EpochInterval -- ^ The maximum number of epochs to wait for the DRep activity interval to
219219
-- become expected value.
220-
-> m (String, Word16) -- ^ The transaction id and the index of the governance action.
220+
-> m (TxId, Word16) -- ^ The transaction id and the index of the governance action.
221221
activityChangeProposalTest execConfig epochStateView ceo work prefix
222222
stakeKeys wallet votes change minWait mExpected maxWait = do
223223
let sbe = convert ceo
@@ -261,7 +261,7 @@ voteChangeProposal
261261
-> ShelleyBasedEra era -- ^ The 'ShelleyBasedEra' witness for current era.
262262
-> FilePath -- ^ Base directory path where generated files will be stored.
263263
-> String -- ^ Name for the subfolder that will be created under 'work' folder.
264-
-> String -- ^ The transaction id of the governance action to vote.
264+
-> TxId -- ^ The transaction id of the governance action to vote.
265265
-> Word16 -- ^ The index of the governance action to vote.
266266
-> [([Char], Int)] -- ^ Votes to be casted for the proposal. Each tuple contains the index
267267
-- of the default DRep that will make the vote and the type of the vote

cardano-testnet/test/cardano-testnet-test/Cardano/Testnet/Test/Gov/GovActionTimeout.hs

Lines changed: 1 addition & 2 deletions
Original file line numberDiff line numberDiff line change
@@ -19,7 +19,6 @@ import Prelude
1919

2020
import Control.Monad (void)
2121
import Data.Default.Class
22-
import Data.String (fromString)
2322
import qualified Data.Text as Text
2423
import System.FilePath ((</>))
2524

@@ -138,7 +137,7 @@ hprop_check_gov_action_timeout = integrationWorkspace "gov-action-timeout" $ \te
138137

139138
-- Check proposal expired
140139
mGovernanceActionTxIx <- watchEpochStateUpdate epochStateView (EpochInterval 2) $ \(anyNewEpochState, _, _) ->
141-
return $ maybeExtractGovernanceActionIndex (fromString governanceActionTxId) anyNewEpochState
140+
return $ maybeExtractGovernanceActionIndex governanceActionTxId anyNewEpochState
142141

143142
mGovernanceActionTxIx H.=== Nothing
144143

cardano-testnet/test/cardano-testnet-test/Cardano/Testnet/Test/Gov/InfoAction.hs

Lines changed: 4 additions & 5 deletions
Original file line numberDiff line numberDiff line change
@@ -27,7 +27,6 @@ import Data.Bifunctor (first)
2727
import Data.Default.Class
2828
import Data.Foldable
2929
import qualified Data.Map.Strict as Map
30-
import Data.String
3130
import qualified Data.Text as Text
3231
import Data.Word
3332
import GHC.Stack
@@ -190,11 +189,11 @@ hprop_ledger_events_info_action = integrationRetryWorkspace 2 "info-hash" $ \tem
190189
, "--tx-file", txbodySignedFp
191190
]
192191

193-
txIdString <- H.noteShowM $ retrieveTransactionId execConfig (File txbodySignedFp)
192+
txId <- H.noteShowM $ retrieveTransactionId execConfig (File txbodySignedFp)
194193

195194
governanceActionIndex <-
196195
H.nothingFailM $ watchEpochStateUpdate epochStateView (EpochInterval 1) $ \(anyNewEpochState, _, _) ->
197-
pure $ maybeExtractGovernanceActionIndex (fromString txIdString) anyNewEpochState
196+
pure $ maybeExtractGovernanceActionIndex txId anyNewEpochState
198197

199198
let voteFp :: Int -> FilePath
200199
voteFp n = work </> gov </> "vote-" <> show n
@@ -204,8 +203,8 @@ hprop_ledger_events_info_action = integrationRetryWorkspace 2 "info-hash" $ \tem
204203
execCli' execConfig
205204
[ eraName, "governance", "vote", "create"
206205
, "--yes"
207-
, "--governance-action-tx-id", txIdString
208-
, "--governance-action-index", show @Word16 governanceActionIndex
206+
, "--governance-action-tx-id", prettyShow txId
207+
, "--governance-action-index", show governanceActionIndex
209208
, "--drep-verification-key-file", verificationKeyFp $ defaultDRepKeyPair n
210209
, "--out-file", voteFp n
211210
]

cardano-testnet/test/cardano-testnet-test/Cardano/Testnet/Test/Gov/NoConfidence.hs

Lines changed: 1 addition & 2 deletions
Original file line numberDiff line numberDiff line change
@@ -26,7 +26,6 @@ import qualified Data.ByteString.Char8 as BSC
2626
import Data.Default.Class
2727
import qualified Data.Map.Strict as Map
2828
import Data.Maybe.Strict
29-
import Data.String
3029
import qualified Data.Text as Text
3130
import GHC.Exts (IsList (toList))
3231
import Lens.Micro
@@ -193,7 +192,7 @@ hprop_gov_no_confidence = integrationWorkspace "no-confidence" $ \tempAbsBasePat
193192

194193
governanceActionIndex <-
195194
H.nothingFailM $ watchEpochStateUpdate epochStateView (EpochInterval 10) $ \(anyNewEpochState, _, _) ->
196-
pure $ maybeExtractGovernanceActionIndex (fromString governanceActionTxId) anyNewEpochState
195+
pure $ maybeExtractGovernanceActionIndex governanceActionTxId anyNewEpochState
197196

198197
let spoVotes :: [(String, Int)]
199198
spoVotes = [("yes", 1), ("yes", 2), ("no", 3)]

cardano-testnet/test/cardano-testnet-test/Cardano/Testnet/Test/Gov/PParamChangeFailsSPO.hs

Lines changed: 1 addition & 1 deletion
Original file line numberDiff line numberDiff line change
@@ -154,7 +154,7 @@ failToVoteChangeProposalWithSPOs
154154
-- using the 'getEpochStateView' function.
155155
-> FilePath -- ^ Base directory path where generated files will be stored.
156156
-> String -- ^ Name for the subfolder that will be created under 'work' folder.
157-
-> String -- ^ The transaction id of the governance action to vote.
157+
-> TxId -- ^ The transaction id of the governance action to vote.
158158
-> Word16 -- ^ The index of the governance action to vote.
159159
-> [([Char], Int)] -- ^ Votes to be casted for the proposal. Each tuple contains the index
160160
-- of the default SPO that will make the vote and the type of the vote

cardano-testnet/test/cardano-testnet-test/Cardano/Testnet/Test/Gov/PredefinedAbstainDRep.hs

Lines changed: 4 additions & 5 deletions
Original file line numberDiff line numberDiff line change
@@ -26,7 +26,6 @@ import Control.Monad
2626
import Control.Monad.Catch (MonadCatch)
2727
import Data.Data (Typeable)
2828
import Data.Default.Class
29-
import Data.String (fromString)
3029
import qualified Data.Text as Text
3130
import Data.Word (Word16)
3231
import GHC.Stack (HasCallStack)
@@ -183,7 +182,7 @@ desiredPoolNumberProposalTest
183182
-> Integer -- ^ Minimum number of epochs to wait before checking the result
184183
-> Maybe Integer -- ^ What the expected result is of the change (if anything)
185184
-> Integer -- ^ Maximum number of epochs to wait while waiting for the result
186-
-> m (String, Word16)
185+
-> m (TxId, Word16)
187186
desiredPoolNumberProposalTest execConfig epochStateView ceo work prefix wallet
188187
previousProposalInfo votes change minWait mExpected maxWait = do
189188
let sbe = convert ceo
@@ -225,7 +224,7 @@ makeDesiredPoolNumberChangeProposal
225224
-- governance action if any.
226225
-> Word16 -- ^ What to change the @desiredPoolNumber@ to
227226
-> PaymentKeyInfo -- ^ Wallet that will pay for the transaction.
228-
-> m (String, Word16)
227+
-> m (TxId, Word16)
229228
makeDesiredPoolNumberChangeProposal execConfig epochStateView ceo work prefix
230229
prevGovActionInfo desiredPoolNumber wallet = do
231230

@@ -290,7 +289,7 @@ makeDesiredPoolNumberChangeProposal execConfig epochStateView ceo work prefix
290289

291290
governanceActionIndex <-
292291
H.nothingFailM $ watchEpochStateUpdate epochStateView (EpochInterval 1) $ \(anyNewEpochState, _, _) ->
293-
pure $ maybeExtractGovernanceActionIndex (fromString governanceActionTxId) anyNewEpochState
292+
pure $ maybeExtractGovernanceActionIndex governanceActionTxId anyNewEpochState
294293

295294
pure (governanceActionTxId, governanceActionIndex)
296295

@@ -307,7 +306,7 @@ voteChangeProposal :: (MonadTest m, MonadIO m, MonadCatch m, H.MonadAssertion m)
307306
-> ShelleyBasedEra ConwayEra -- ^ The Shelley-based witness for ConwayEra (i.e: ShelleyBasedEraConway).
308307
-> FilePath -- ^ Base directory path where the subdirectory with the intermediate files will be created.
309308
-> String -- ^ Name for the subdirectory that will be created for storing the intermediate files.
310-
-> String -- ^ Transaction id of the governance action to vote.
309+
-> TxId -- ^ Transaction id of the governance action to vote.
311310
-> Word16 -- ^ Index of the governance action to vote in the transaction.
312311
-> [DefaultDRepVote] -- ^ List of votes to issue as pairs of the vote and the number of DRep that votes it.
313312
-> PaymentKeyInfo -- ^ Wallet that will pay for the transactions

0 commit comments

Comments
 (0)