Skip to content

Commit

Permalink
Move KeyPair class to Testnet.Runtime
Browse files Browse the repository at this point in the history
  • Loading branch information
palas committed Apr 25, 2024
1 parent b589817 commit 644e050
Show file tree
Hide file tree
Showing 2 changed files with 23 additions and 22 deletions.
25 changes: 3 additions & 22 deletions cardano-testnet/src/Testnet/Components/DReps.hs
Original file line number Diff line number Diff line change
@@ -1,12 +1,10 @@
{-# LANGUAGE DataKinds #-}
{-# LANGUAGE ExistentialQuantification #-}
{-# LANGUAGE InstanceSigs #-}
{-# LANGUAGE OverloadedStrings #-}
{-# LANGUAGE TypeApplications #-}

module Testnet.Components.DReps
( SomeKeyPair(..)
, VoteFile
( VoteFile
, generateDRepKeyPair
, generateRegistrationCertificate
, createCertificatePublicationTxBody
Expand Down Expand Up @@ -46,8 +44,8 @@ import System.FilePath ((</>))
import Testnet.Components.Query (EpochStateView, findLargestUtxoForPaymentKey,
getCurrentEpochNo, getMinDRepDeposit, waitUntilEpoch)
import qualified Testnet.Process.Run as H
import Testnet.Runtime (PaymentKeyInfo (paymentKeyInfoAddr, paymentKeyInfoPair),
PaymentKeyPair (..), StakingKeyPair (StakingKeyPair, stakingSKey))
import Testnet.Runtime (KeyPair(..), PaymentKeyInfo (paymentKeyInfoAddr, paymentKeyInfoPair),
PaymentKeyPair (..), StakingKeyPair (..), SomeKeyPair (..))
import Testnet.Start.Types (anyEraToString)

import Hedgehog (MonadTest, evalMaybe)
Expand Down Expand Up @@ -201,23 +199,6 @@ createVotingTxBody execConfig epochStateView sbe work prefix votes wallet = do

data SignedTx

class KeyPair a where
secretKey :: a -> FilePath

instance KeyPair PaymentKeyPair where
secretKey :: PaymentKeyPair -> FilePath
secretKey = paymentSKey

instance KeyPair StakingKeyPair where
secretKey :: StakingKeyPair -> FilePath
secretKey = stakingSKey

data SomeKeyPair = forall a . KeyPair a => SomeKeyPair a

instance KeyPair SomeKeyPair where
secretKey :: SomeKeyPair -> FilePath
secretKey (SomeKeyPair x) = secretKey x

-- | Calls @cardano-cli@ to signs a transaction body using the specified key pairs.
--
-- This function takes five parameters:
Expand Down
20 changes: 20 additions & 0 deletions cardano-testnet/src/Testnet/Runtime.hs
Original file line number Diff line number Diff line change
Expand Up @@ -6,6 +6,8 @@
{-# LANGUAGE NamedFieldPuns #-}
{-# LANGUAGE OverloadedStrings #-}
{-# LANGUAGE ScopedTypeVariables #-}
{-# LANGUAGE ExistentialQuantification #-}
{-# LANGUAGE InstanceSigs #-}

module Testnet.Runtime
( LeadershipSlot(..)
Expand All @@ -18,6 +20,8 @@ module Testnet.Runtime
, PoolNode(..)
, PoolNodeKeys(..)
, Delegator(..)
, KeyPair(..)
, SomeKeyPair(..)
, allNodes
, poolSprockets
, poolNodeStdout
Expand Down Expand Up @@ -134,6 +138,22 @@ data LeadershipSlot = LeadershipSlot
, slotTime :: Text
} deriving (Eq, Show, Generic, FromJSON)

class KeyPair a where
secretKey :: a -> FilePath

instance KeyPair PaymentKeyPair where
secretKey :: PaymentKeyPair -> FilePath
secretKey = paymentSKey

instance KeyPair StakingKeyPair where
secretKey :: StakingKeyPair -> FilePath
secretKey = stakingSKey

data SomeKeyPair = forall a . KeyPair a => SomeKeyPair a

instance KeyPair SomeKeyPair where
secretKey :: SomeKeyPair -> FilePath
secretKey (SomeKeyPair x) = secretKey x

poolNodeStdout :: PoolNode -> FilePath
poolNodeStdout = nodeStdout . poolRuntime
Expand Down

0 comments on commit 644e050

Please sign in to comment.