Skip to content

Commit f557aeb

Browse files
committed
cardano-testnet | Refactor: Remove SomeKeyPair
1 parent b092ee3 commit f557aeb

File tree

15 files changed

+66
-49
lines changed

15 files changed

+66
-49
lines changed

cardano-testnet/src/Testnet/Defaults.hs

Lines changed: 0 additions & 1 deletion
Original file line numberDiff line numberDiff line change
@@ -44,7 +44,6 @@ import qualified Cardano.Api.Shelley as Api
4444
import Cardano.Ledger.Alonzo.Core (PParams (..))
4545
import Cardano.Ledger.Alonzo.Genesis (AlonzoGenesis)
4646
import qualified Cardano.Ledger.Alonzo.Genesis as Ledger
47-
import qualified Cardano.Ledger.Api as L
4847
import Cardano.Ledger.BaseTypes
4948
import qualified Cardano.Ledger.BaseTypes as Ledger
5049
import Cardano.Ledger.Binary.Version ()

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

Lines changed: 5 additions & 4 deletions
Original file line numberDiff line numberDiff line change
@@ -17,6 +17,7 @@ module Testnet.Process.Cli.DRep
1717
) where
1818

1919
import Cardano.Api hiding (Certificate, TxBody)
20+
import Cardano.Api.Experimental (Some (..))
2021
import Cardano.Api.Ledger (EpochInterval (EpochInterval, unEpochInterval))
2122

2223
import Cardano.Testnet (maybeExtractGovernanceActionIndex)
@@ -239,7 +240,7 @@ registerDRep execConfig epochStateView ceo work prefix wallet = do
239240
drepRegTxBody <- createCertificatePublicationTxBody execConfig epochStateView sbe baseDir "reg-cert-txbody"
240241
drepRegCert wallet
241242
drepSignedRegTx <- signTx execConfig cEra baseDir "signed-reg-tx"
242-
drepRegTxBody [SomeKeyPair drepKeyPair, SomeKeyPair $ paymentKeyInfoPair wallet]
243+
drepRegTxBody [Some drepKeyPair, Some $ paymentKeyInfoPair wallet]
243244
submitTx execConfig cEra drepSignedRegTx
244245

245246
return drepKeyPair
@@ -286,8 +287,8 @@ delegateToDRep execConfig epochStateView sbe work prefix
286287

287288
-- Sign transaction
288289
repRegSignedRegTx1 <- signTx execConfig cEra baseDir "signed-reg-tx"
289-
repRegTxBody1 [ SomeKeyPair $ paymentKeyInfoPair payingWallet
290-
, SomeKeyPair skeyPair]
290+
repRegTxBody1 [ Some $ paymentKeyInfoPair payingWallet
291+
, Some skeyPair]
291292

292293
-- Submit transaction
293294
submitTx execConfig cEra repRegSignedRegTx1
@@ -398,7 +399,7 @@ makeActivityChangeProposal execConfig epochStateView ceo work
398399
]
399400

400401
signedProposalTx <- signTx execConfig cEra baseDir "signed-proposal"
401-
(File proposalBody) [SomeKeyPair $ paymentKeyInfoPair wallet]
402+
(File proposalBody) [Some $ paymentKeyInfoPair wallet]
402403

403404
submitTx execConfig cEra signedProposalTx
404405

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

Lines changed: 3 additions & 2 deletions
Original file line numberDiff line numberDiff line change
@@ -15,6 +15,7 @@ module Testnet.Process.Cli.Transaction
1515
) where
1616

1717
import Cardano.Api hiding (Certificate, TxBody)
18+
import Cardano.Api.Experimental (Some (..))
1819
import Cardano.Api.Ledger (Coin (unCoin))
1920

2021
import Prelude
@@ -146,14 +147,14 @@ signTx
146147
-> FilePath -- ^ Base directory path where the signed transaction file will be stored.
147148
-> String -- ^ Prefix for the output signed transaction file name. The extension will be @.tx@.
148149
-> File TxBody In -- ^ Transaction body to be signed, obtained using 'createCertificatePublicationTxBody' or similar.
149-
-> [SomeKeyPair] -- ^ List of key pairs used for signing the transaction.
150+
-> [Some KeyPair] -- ^ List of key pairs used for signing the transaction.
150151
-> m (File SignedTx In)
151152
signTx execConfig cEra work prefix txBody signatoryKeyPairs = do
152153
let signedTx = File (work </> prefix <> ".tx")
153154
void $ execCli' execConfig $
154155
[ anyEraToString cEra, "transaction", "sign"
155156
, "--tx-body-file", unFile txBody
156-
] ++ (concat [["--signing-key-file", signingKeyFp kp] | SomeKeyPair kp <- signatoryKeyPairs]) ++
157+
] ++ (concat [["--signing-key-file", signingKeyFp kp] | Some kp <- signatoryKeyPairs]) ++
157158
[ "--out-file", unFile signedTx
158159
]
159160
return signedTx

cardano-testnet/src/Testnet/Types.hs

Lines changed: 10 additions & 4 deletions
Original file line numberDiff line numberDiff line change
@@ -3,6 +3,7 @@
33
{-# LANGUAGE DeriveGeneric #-}
44
{-# LANGUAGE ExistentialQuantification #-}
55
{-# LANGUAGE FlexibleContexts #-}
6+
{-# LANGUAGE FlexibleInstances #-}
67
{-# LANGUAGE LambdaCase #-}
78
{-# LANGUAGE NamedFieldPuns #-}
89
{-# LANGUAGE RankNTypes #-}
@@ -26,7 +27,6 @@ module Testnet.Types
2627
, KeyPair(..)
2728
, verificationKeyFp
2829
, signingKeyFp
29-
, SomeKeyPair(..)
3030
, VKey
3131
, SKey
3232
, VrfKey
@@ -43,6 +43,7 @@ module Testnet.Types
4343
) where
4444

4545
import Cardano.Api
46+
import Cardano.Api.Experimental (Some (..))
4647
import Cardano.Api.Shelley (VrfKey)
4748

4849
import qualified Cardano.Chain.Genesis as G
@@ -91,15 +92,20 @@ instance MonoFunctor (KeyPair k) where
9192
deriving instance Show (KeyPair k)
9293
deriving instance Eq (KeyPair k)
9394

95+
instance {-# OVERLAPPING #-} Show (Some KeyPair) where
96+
show (Some kp) = show kp
97+
98+
instance {-# OVERLAPPING #-} Eq (Some KeyPair) where
99+
(Some KeyPair{verificationKey=File vk1, signingKey=File sk1})
100+
== (Some KeyPair{verificationKey=File vk2, signingKey=File sk2}) =
101+
vk1 == vk2 && sk1 == sk2
102+
94103
verificationKeyFp :: KeyPair k -> FilePath
95104
verificationKeyFp = unFile . verificationKey
96105

97106
signingKeyFp :: KeyPair k -> FilePath
98107
signingKeyFp = unFile . signingKey
99108

100-
data SomeKeyPair = forall a. SomeKeyPair (KeyPair a)
101-
deriving instance Show SomeKeyPair
102-
103109
-- | Verification key tag
104110
data VKey k
105111

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

Lines changed: 1 addition & 1 deletion
Original file line numberDiff line numberDiff line change
@@ -94,7 +94,7 @@ hprop_kes_period_info = integrationRetryWorkspace 2 "kes-period-info" $ \tempAbs
9494
let node1SocketPath = Api.File $ IO.sprocketSystemName node1sprocket
9595
termEpoch = EpochNo 3
9696
epochStateView <- getEpochStateView configurationFile node1SocketPath
97-
(stakePoolId, stakePoolColdSigningKey, stakePoolColdVKey, _, _)
97+
(stakePoolId, KeyPair{signingKey=File stakePoolColdSigningKey, verificationKey=File stakePoolColdVKey}, _)
9898
<- registerSingleSpo asbe 1 tempAbsPath
9999
configurationFile
100100
node1SocketPath

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

Lines changed: 17 additions & 15 deletions
Original file line numberDiff line numberDiff line change
@@ -101,7 +101,7 @@ hprop_leadershipSchedule = integrationRetryWorkspace 2 "leadership-schedule" $ \
101101
let node1SocketPath = Api.File $ IO.sprocketSystemName node1sprocket
102102
termEpoch = EpochNo 15
103103
epochStateView <- getEpochStateView configurationFile node1SocketPath
104-
(stakePoolIdNewSpo, stakePoolColdSigningKey, stakePoolColdVKey, vrfSkey, _)
104+
(stakePoolIdNewSpo, KeyPair{signingKey=File stakePoolColdSigningKey, verificationKey=File stakePoolColdVKey}, KeyPair{signingKey=File vrfSkey})
105105
<- registerSingleSpo asbe 1 tempAbsPath
106106
configurationFile
107107
node1SocketPath
@@ -117,30 +117,32 @@ hprop_leadershipSchedule = integrationRetryWorkspace 2 "leadership-schedule" $ \
117117
let testStakeDelegator = work </> "test-delegator"
118118

119119
H.createDirectoryIfMissing_ testStakeDelegator
120-
let testDelegatorVkeyFp = testStakeDelegator </> "test-delegator.vkey"
121-
testDelegatorSKeyFp = testStakeDelegator </> "test-delegator.skey"
122-
testDelegatorPaymentVKeyFp = testStakeDelegator </> "test-delegator-payment.vkey"
123-
testDelegatorPaymentSKeyFp = testStakeDelegator </> "test-delegator-payment.skey"
120+
let testDelegatorKeys = KeyPair
121+
{ signingKey = File $ testStakeDelegator </> "test-delegator.skey"
122+
, verificationKey = File $ testStakeDelegator </> "test-delegator.vkey"
123+
}
124+
testDelegatorPaymentKeys = KeyPair
125+
{ signingKey = File $ testStakeDelegator </> "test-delegator-payment.skey"
126+
, verificationKey = File $ testStakeDelegator </> "test-delegator-payment.vkey"
127+
}
124128
testDelegatorRegCertFp = testStakeDelegator </> "test-delegator.regcert"
125129
testDelegatorDelegCert = testStakeDelegator </> "test-delegator.delegcert"
126130

127-
cliStakeAddressKeyGen
128-
$ KeyPair (File testDelegatorVkeyFp) (File testDelegatorSKeyFp)
129-
cliAddressKeyGen
130-
$ KeyPair (File testDelegatorPaymentVKeyFp) (File testDelegatorPaymentSKeyFp)
131+
cliStakeAddressKeyGen testDelegatorKeys
132+
cliAddressKeyGen testDelegatorPaymentKeys
131133

132134
-- NB: We must include the stake credential
133135
testDelegatorPaymentAddr <- execCli
134136
[ "latest", "address", "build"
135137
, "--testnet-magic", show @Int testnetMagic
136-
, "--payment-verification-key-file", testDelegatorPaymentVKeyFp
137-
, "--stake-verification-key-file", testDelegatorVkeyFp
138+
, "--payment-verification-key-file", verificationKeyFp testDelegatorPaymentKeys
139+
, "--stake-verification-key-file", verificationKeyFp testDelegatorKeys
138140
]
139141
testDelegatorStakeAddress
140142
<- filter (/= '\n')
141143
<$> execCli
142144
[ "latest", "stake-address", "build"
143-
, "--stake-verification-key-file", testDelegatorVkeyFp
145+
, "--stake-verification-key-file", verificationKeyFp testDelegatorKeys
144146
, "--testnet-magic", show @Int testnetMagic
145147
]
146148

@@ -149,15 +151,15 @@ hprop_leadershipSchedule = integrationRetryWorkspace 2 "leadership-schedule" $ \
149151
createStakeKeyRegistrationCertificate
150152
tempAbsPath
151153
(cardanoNodeEra cTestnetOptions)
152-
testDelegatorVkeyFp
154+
(verificationKey testDelegatorKeys)
153155
keyDeposit
154156
testDelegatorRegCertFp
155157

156158
-- Test stake address deleg cert
157159
createStakeDelegationCertificate
158160
tempAbsPath
159161
sbe
160-
testDelegatorVkeyFp
162+
(verificationKey testDelegatorKeys)
161163
stakePoolIdNewSpo
162164
testDelegatorDelegCert
163165

@@ -197,7 +199,7 @@ hprop_leadershipSchedule = integrationRetryWorkspace 2 "leadership-schedule" $ \
197199
, "--tx-body-file", delegRegTestDelegatorTxBodyFp
198200
, "--testnet-magic", show @Int testnetMagic
199201
, "--signing-key-file", utxoSKeyFile
200-
, "--signing-key-file", testDelegatorSKeyFp
202+
, "--signing-key-file", signingKeyFp testDelegatorKeys
201203
, "--out-file", delegRegTestDelegatorTxFp
202204
]
203205

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

Lines changed: 3 additions & 2 deletions
Original file line numberDiff line numberDiff line change
@@ -14,6 +14,7 @@ module Cardano.Testnet.Test.Cli.Query
1414
) where
1515

1616
import Cardano.Api
17+
import Cardano.Api.Experimental (Some (..))
1718
import qualified Cardano.Api.Genesis as Api
1819
import Cardano.Api.Ledger (Coin (Coin), EpochInterval (EpochInterval), StandardCrypto,
1920
extractHash, unboundRational)
@@ -327,7 +328,7 @@ hprop_cli_queries = integrationWorkspace "cli-queries" $ \tempAbsBasePath' -> H.
327328
-- Now we create a transaction and check if it exists in the mempool
328329
mempoolWork <- H.createDirectoryIfMissing $ work </> "mempool-test"
329330
txBody <- mkSimpleSpendOutputsOnlyTx execConfig epochStateView sbe mempoolWork "tx-body" wallet0 wallet1 10_000_000
330-
signedTx <- signTx execConfig cEra mempoolWork "signed-tx" txBody [SomeKeyPair $ paymentKeyInfoPair wallet0]
331+
signedTx <- signTx execConfig cEra mempoolWork "signed-tx" txBody [Some $ paymentKeyInfoPair wallet0]
331332
submitTx execConfig cEra signedTx
332333
txId <- retrieveTransactionId execConfig signedTx
333334
-- And we check
@@ -349,7 +350,7 @@ hprop_cli_queries = integrationWorkspace "cli-queries" $ \tempAbsBasePath' -> H.
349350
-- Submit a transaction to publish the reference script
350351
txBody <- mkSpendOutputsOnlyTx execConfig epochStateView sbe refScriptSizeWork "tx-body" wallet1
351352
[(ReferenceScriptAddress plutusV3Script, transferAmount)]
352-
signedTx <- signTx execConfig cEra refScriptSizeWork "signed-tx" txBody [SomeKeyPair $ paymentKeyInfoPair wallet1]
353+
signedTx <- signTx execConfig cEra refScriptSizeWork "signed-tx" txBody [Some $ paymentKeyInfoPair wallet1]
353354
submitTx execConfig cEra signedTx
354355
-- Wait until transaction is on chain and obtain transaction identifier
355356
txId <- retrieveTransactionId execConfig signedTx

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

Lines changed: 3 additions & 2 deletions
Original file line numberDiff line numberDiff line change
@@ -11,6 +11,7 @@ module Cardano.Testnet.Test.Gov.CommitteeAddNew
1111
) where
1212

1313
import Cardano.Api as Api
14+
import Cardano.Api.Experimental (Some (..))
1415
import qualified Cardano.Api.Ledger as L
1516
import Cardano.Api.Shelley (ShelleyLedgerEra)
1617

@@ -214,7 +215,7 @@ hprop_constitutional_committee_add_new = integrationWorkspace "constitutional-co
214215
committeeMembers `H.assertWith` null
215216

216217
signedProposalTx <-
217-
signTx execConfig cEra work "signed-proposal" (File txbodyFp) [SomeKeyPair $ paymentKeyInfoPair wallet0]
218+
signTx execConfig cEra work "signed-proposal" (File txbodyFp) [Some $ paymentKeyInfoPair wallet0]
218219
submitTx execConfig cEra signedProposalTx
219220

220221
governanceActionTxId <- H.noteM $ retrieveTransactionId execConfig signedProposalTx
@@ -245,7 +246,7 @@ hprop_constitutional_committee_add_new = integrationWorkspace "constitutional-co
245246
, verificationKey = error "unused"
246247
}
247248
drepSKeys = map (defaultDRepKeyPair . snd) drepVotes
248-
signingKeys = SomeKeyPair <$> paymentKeyInfoPair wallet0:poolNodePaymentKeyPair:drepSKeys
249+
signingKeys = Some <$> paymentKeyInfoPair wallet0:poolNodePaymentKeyPair:drepSKeys
249250
voteTxFp <- signTx
250251
execConfig cEra gov "signed-vote-tx" voteTxBodyFp signingKeys
251252

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

Lines changed: 2 additions & 1 deletion
Original file line numberDiff line numberDiff line change
@@ -12,6 +12,7 @@ module Cardano.Testnet.Test.Gov.DRepActivity
1212

1313
import Cardano.Api as Api
1414
import Cardano.Api.Eon.ShelleyBasedEra (ShelleyLedgerEra)
15+
import Cardano.Api.Experimental (Some (..))
1516
import Cardano.Api.Ledger (EpochInterval (EpochInterval, unEpochInterval), drepExpiry)
1617

1718
import Cardano.Ledger.Conway.Core (EraGov, curPParamsGovStateL)
@@ -286,7 +287,7 @@ voteChangeProposal execConfig epochStateView sbe work prefix governanceActionTxI
286287
voteTxBodyFp <- createVotingTxBody execConfig epochStateView sbe baseDir "vote-tx-body"
287288
voteFiles wallet
288289

289-
let signingKeys = SomeKeyPair <$> (paymentKeyInfoPair wallet:(defaultDRepKeyPair . snd <$> votes))
290+
let signingKeys = Some <$> (paymentKeyInfoPair wallet:(defaultDRepKeyPair . snd <$> votes))
290291
voteTxFp <- signTx execConfig cEra baseDir "signed-vote-tx" voteTxBodyFp signingKeys
291292

292293
submitTx execConfig cEra voteTxFp

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

Lines changed: 2 additions & 1 deletion
Original file line numberDiff line numberDiff line change
@@ -5,6 +5,7 @@ module Cardano.Testnet.Test.Gov.DRepDeposit
55
) where
66

77
import Cardano.Api
8+
import Cardano.Api.Experimental (Some (..))
89
import qualified Cardano.Api.Ledger as L
910

1011
import Cardano.Testnet
@@ -84,7 +85,7 @@ hprop_ledger_events_drep_deposits = integrationWorkspace "drep-deposits" $ \temp
8485
drepRegTxBody1 <- createCertificatePublicationTxBody execConfig epochStateView sbe drepDir1 "reg-cert-txbody"
8586
drepRegCert1 wallet0
8687
drepSignedRegTx1 <- signTx execConfig cEra drepDir1 "signed-reg-tx"
87-
drepRegTxBody1 [SomeKeyPair drepKeyPair1, SomeKeyPair $ paymentKeyInfoPair wallet0]
88+
drepRegTxBody1 [Some drepKeyPair1, Some $ paymentKeyInfoPair wallet0]
8889

8990
failToSubmitTx execConfig cEra drepSignedRegTx1 "ConwayDRepIncorrectDeposit"
9091

0 commit comments

Comments
 (0)