Skip to content

Commit

Permalink
Merge pull request #5821 from IntersectMBO/mgalazyn/test/cc-keys-reg
Browse files Browse the repository at this point in the history
cardano-testnet: Add new constitutional committee
  • Loading branch information
carbolymer authored May 10, 2024
2 parents b8c8695 + f482c10 commit e918562
Show file tree
Hide file tree
Showing 8 changed files with 308 additions and 17 deletions.
1 change: 1 addition & 0 deletions cardano-testnet/cardano-testnet.cabal
Original file line number Diff line number Diff line change
Expand Up @@ -186,6 +186,7 @@ test-suite cardano-testnet-test
Cardano.Testnet.Test.Cli.Query
Cardano.Testnet.Test.Cli.QuerySlotNumber
Cardano.Testnet.Test.FoldEpochState
Cardano.Testnet.Test.Gov.CommitteeAddNew
Cardano.Testnet.Test.Gov.DRepActivity
Cardano.Testnet.Test.Gov.DRepDeposit
Cardano.Testnet.Test.Gov.DRepRetirement
Expand Down
2 changes: 1 addition & 1 deletion cardano-testnet/src/Testnet/Components/DRep.hs
Original file line number Diff line number Diff line change
Expand Up @@ -163,7 +163,7 @@ generateVoteFiles
generateVoteFiles execConfig work prefix governanceActionTxId governanceActionIndex allVotes = do
baseDir <- H.createDirectoryIfMissing $ work </> prefix
forM (zip [(1 :: Integer)..] allVotes) $ \(idx, (drepKeyPair, vote)) -> do
let path = File (baseDir </> "vote-" <> show idx)
let path = File (baseDir </> "vote-drep-" <> show idx)
void $ H.execCli' execConfig
[ "conway", "governance", "vote", "create"
, "--" ++ vote
Expand Down
16 changes: 15 additions & 1 deletion cardano-testnet/src/Testnet/Components/Query.hs
Original file line number Diff line number Diff line change
Expand Up @@ -10,6 +10,7 @@ module Testnet.Components.Query
, checkDRepState
, getEpochState
, getMinDRepDeposit
, getMinGovActionDeposit
, getGovState
, getCurrentEpochNo
, waitUntilEpoch
Expand Down Expand Up @@ -312,6 +313,19 @@ getGovState epochStateView ceo = withFrozenCallStack $ do
Refl <- H.leftFail $ assertErasEqual sbe sbe'
pure $ conwayEraOnwardsConstraints ceo $ newEpochState ^. L.newEpochStateGovStateL

-- | Obtain minimum deposit amount for governance action from node
getMinGovActionDeposit
:: HasCallStack
=> MonadAssertion m
=> MonadIO m
=> MonadTest m
=> EpochStateView
-> ConwayEraOnwards era
-> m Integer -- ^ The minimum deposit
getMinGovActionDeposit epochStateView ceo = withFrozenCallStack $ do
govState <- getGovState epochStateView ceo
pure $ conwayEraOnwardsConstraints ceo $ govState ^. L.cgsCurPParamsL . L.ppGovActionDepositL . to L.unCoin

-- | Obtain minimum deposit amount for DRep registration from node
getMinDRepDeposit
:: HasCallStack
Expand All @@ -320,7 +334,7 @@ getMinDRepDeposit
=> MonadTest m
=> EpochStateView
-> ConwayEraOnwards era
-> m Integer -- ^ The governance state
-> m Integer -- ^ The minimum deposit
getMinDRepDeposit epochStateView ceo = withFrozenCallStack $ do
govState <- getGovState epochStateView ceo
pure $ conwayEraOnwardsConstraints ceo $ govState ^. L.cgsCurPParamsL . L.ppDRepDepositL . to L.unCoin
Expand Down
2 changes: 1 addition & 1 deletion cardano-testnet/src/Testnet/Components/SPO.hs
Original file line number Diff line number Diff line change
Expand Up @@ -427,7 +427,7 @@ generateVoteFiles :: (MonadTest m, MonadIO m, MonadCatch m)
generateVoteFiles ceo execConfig work prefix governanceActionTxId governanceActionIndex allVotes = do
baseDir <- H.createDirectoryIfMissing $ work </> prefix
forM (zip [(1 :: Integer)..] allVotes) $ \(idx, (spoKeys, vote)) -> do
let path = File (baseDir </> "vote-" <> show idx)
let path = File (baseDir </> "vote-spo-" <> show idx)
void $ H.execCli' execConfig
[ eraToString $ toCardanoEra ceo , "governance", "vote", "create"
, "--" ++ vote
Expand Down
1 change: 0 additions & 1 deletion cardano-testnet/src/Testnet/EpochStateProcessing.hs
Original file line number Diff line number Diff line change
@@ -1,5 +1,4 @@
{-# LANGUAGE DataKinds #-}
{-# LANGUAGE RankNTypes #-}
{-# LANGUAGE ScopedTypeVariables #-}
{-# LANGUAGE TypeFamilies #-}

Expand Down
24 changes: 13 additions & 11 deletions cardano-testnet/src/Testnet/Start/Cardano.hs
Original file line number Diff line number Diff line change
Expand Up @@ -273,25 +273,32 @@ cardanoTestnet

_ <- createSPOGenesisAndFiles nPools nDReps era shelleyGenesis alonzoGenesis conwayGenesis (TmpAbsolutePath tmpAbsPath)

-- TODO: This should come from the configuration!
let poolKeyDir :: Int -> FilePath
poolKeyDir i = "pools-keys" </> mkNodeName i
mkNodeName :: Int -> String
mkNodeName i = "pool" <> show i

poolKeys <- H.noteShow $ flip fmap [1..numPoolNodes] $ \n ->
-- TODO: use Testnet.Defaults.defaultSpoKeys here
PoolNodeKeys
{ poolNodeKeysCold =
KeyPair
{ verificationKey = File $ tmpAbsPath </> "pools-keys" </> "cold" <> show n <> ".vkey"
, signingKey = File $ tmpAbsPath </> "pools-keys" </> "cold" <> show n <> ".skey"
{ verificationKey = File $ tmpAbsPath </> poolKeyDir n </> "cold.vkey"
, signingKey = File $ tmpAbsPath </> poolKeyDir n </> "cold.skey"
}
, poolNodeKeysVrf =
KeyPair
{ verificationKey = File $ tmpAbsPath </> "pools-keys" </> "vrf" <> show n <> ".vkey"
, signingKey = File $ tmpAbsPath </> "pools-keys" </> "vrf" <> show n <> ".skey"
{ verificationKey = File $ tmpAbsPath </> poolKeyDir n </> "vrf.vkey"
, signingKey = File $ tmpAbsPath </> poolKeyDir n </> "vrf.skey"
}
, poolNodeKeysStaking =
KeyPair
{ verificationKey = File $ tmpAbsPath </> "pools-keys" </> "staking-reward" <> show n <> ".vkey"
, signingKey = File $ tmpAbsPath </> "pools-keys" </> "staking-reward" <> show n <> ".skey"
{ verificationKey = File $ tmpAbsPath </> poolKeyDir n </> "staking-reward.vkey"
, signingKey = File $ tmpAbsPath </> poolKeyDir n </> "staking-reward.skey"
}
}

let makeUTxOVKeyFp :: Int -> FilePath
makeUTxOVKeyFp n = tmpAbsPath </> "utxo-keys" </> "utxo" <> show n </> "utxo.vkey"

Expand Down Expand Up @@ -332,11 +339,6 @@ cardanoTestnet
}
}

-- TODO: This should come from the configuration!
let poolKeyDir :: Int -> FilePath
poolKeyDir i = "pools-keys" </> mkNodeName i
mkNodeName :: Int -> String
mkNodeName i = "pool" <> show i

-- Add Byron, Shelley and Alonzo genesis hashes to node configuration
config <- createConfigJson (TmpAbsolutePath tmpAbsPath) era
Expand Down
Original file line number Diff line number Diff line change
@@ -0,0 +1,274 @@
{-# LANGUAGE DataKinds #-}
{-# LANGUAGE NamedFieldPuns #-}
{-# LANGUAGE NumericUnderscores #-}
{-# LANGUAGE OverloadedStrings #-}
{-# LANGUAGE ScopedTypeVariables #-}
{-# LANGUAGE TupleSections #-}
{-# LANGUAGE TypeApplications #-}

module Cardano.Testnet.Test.Gov.CommitteeAddNew
( hprop_constitutional_committee_add_new
) where

import Cardano.Api as Api
import qualified Cardano.Api.Ledger as L
import Cardano.Api.Shelley (ShelleyLedgerEra)

import qualified Cardano.Ledger.Conway.Governance as L
import qualified Cardano.Ledger.Credential as L
import qualified Cardano.Ledger.Shelley.LedgerState as L
import Cardano.Testnet

import Prelude

import Control.Monad
import qualified Data.Char as C
import qualified Data.Map as Map
import Data.Maybe.Strict
import Data.Set (Set)
import Data.String
import qualified Data.Text as Text
import GHC.Exts (IsList (..))
import GHC.Stack
import Lens.Micro
import System.FilePath ((</>))

import Testnet.Components.Configuration
import qualified Testnet.Components.DRep as DRep
import Testnet.Components.Query
import qualified Testnet.Components.SPO as SPO
import Testnet.Components.TestWatchdog
import Testnet.Defaults
import qualified Testnet.Process.Cli as P
import qualified Testnet.Process.Run as H
import qualified Testnet.Property.Util as H
import Testnet.Types

import Hedgehog
import qualified Hedgehog.Extras as H

hprop_constitutional_committee_add_new :: Property
hprop_constitutional_committee_add_new = H.integrationWorkspace "constitutional-committee-add-new" $ \tempAbsBasePath' -> runWithDefaultWatchdog_ $ do
conf@Conf { tempAbsPath } <- mkConf tempAbsBasePath'
let tempAbsPath' = unTmpAbsPath tempAbsPath
tempBaseAbsPath = makeTmpBaseAbsPath tempAbsPath

work <- H.createDirectoryIfMissing $ tempAbsPath' </> "work"

-- how many votes to cast
let drepVotes, spoVotes :: [(String, Int)]
drepVotes = zip (concatMap (uncurry replicate) [(5, "yes"), (3, "no"), (2, "abstain")]) [1..]
spoVotes = zip (concatMap (uncurry replicate) [(1, "yes")]) [1..]
H.noteShow_ drepVotes

let nDrepVotes :: Int
nDrepVotes = length drepVotes
H.noteShow_ nDrepVotes

let ceo = ConwayEraOnwardsConway
sbe = conwayEraOnwardsToShelleyBasedEra ceo
era = toCardanoEra sbe
cEra = AnyCardanoEra era
eraName = eraToString era
fastTestnetOptions = cardanoDefaultTestnetOptions
{ cardanoEpochLength = 100
, cardanoNodeEra = cEra
, cardanoNumDReps = nDrepVotes
}

TestnetRuntime
{ testnetMagic
, poolNodes
, wallets=wallet0:_
, configurationFile
}
<- cardanoTestnetDefault fastTestnetOptions conf

PoolNode{poolRuntime, poolKeys} <- H.headM poolNodes
poolSprocket1 <- H.noteShow $ nodeSprocket poolRuntime
execConfig <- H.mkExecConfig tempBaseAbsPath poolSprocket1 testnetMagic
let socketPath = nodeSocketPath poolRuntime

epochStateView <- getEpochStateView configurationFile socketPath

H.note_ $ "Sprocket: " <> show poolSprocket1
H.note_ $ "Abs path: " <> tempAbsBasePath'
H.note_ $ "Socketpath: " <> unFile socketPath
H.note_ $ "Foldblocks config file: " <> unFile configurationFile

gov <- H.createDirectoryIfMissing $ work </> "governance"
proposalAnchorFp <- H.note $ gov </> "sample-proposal-anchor"
proposalDataFp <- H.note $ gov </> "sample-proposal-data"
updateCommitteeFp <- H.note $ gov </> "update-cc.action"

H.writeFile proposalAnchorFp "dummy anchor data"
H.writeFile proposalDataFp "dummy proposal data"

proposalAnchorDataHash <- H.execCli' execConfig
[ eraName, "governance" , "hash", "anchor-data"
, "--file-text", proposalAnchorFp
]

let ccColdSKeyFp n = gov </> "cc-" <> show n <> "-cold.skey"
ccColdVKeyFp n = gov </> "cc-" <> show n <> "-cold.vkey"
stakeVkeyFp = gov </> "stake.vkey"
stakeSKeyFp = gov </> "stake.skey"

P.cliStakeAddressKeyGen
$ KeyPair { verificationKey = File stakeVkeyFp
, signingKey = File stakeSKeyFp
}

minGovActDeposit <- getMinGovActionDeposit epochStateView ceo

ccColdKeys <- H.noteShowM $
H.forConcurrently [1..3] $ \(i :: Int) -> do
let coldVKey = ccColdVKeyFp i
_ <- H.execCli' execConfig
[ eraName, "governance", "committee", "key-gen-cold"
, "--cold-verification-key-file", ccColdVKeyFp i
, "--cold-signing-key-file", ccColdSKeyFp i
]
fmap (coldVKey, i,) $
parseKeyHashCred =<< H.execCli' execConfig
[ eraName, "governance", "committee", "key-hash"
, "--verification-key-file", ccColdVKeyFp i
]
let (ccColdKeyFps, _, ccCredentials) = unzip3 ccColdKeys

EpochNo epochNo <- H.noteShowM $ getCurrentEpochNo epochStateView
let ccExpiryEpoch = epochNo + 200
deadlineEpoch = EpochNo $ epochNo + 10

_ <- H.execCli' execConfig $
[ eraName, "governance", "action" , "update-committee"
, "--testnet"
, "--anchor-url", "https://tinyurl.com/3wrwb2as"
, "--anchor-data-hash", proposalAnchorDataHash
, "--governance-action-deposit", show minGovActDeposit
, "--deposit-return-stake-verification-key-file", stakeVkeyFp
, "--threshold", "0.2"
, "--out-file", updateCommitteeFp
]
<> concatMap
(\fp -> ["--add-cc-cold-verification-key-file", fp, "--epoch", show ccExpiryEpoch])
ccColdKeyFps

txbodyFp <- H.note $ work </> "tx.body"
txin1 <- findLargestUtxoForPaymentKey epochStateView sbe wallet0
void $ H.execCli' execConfig
[ eraToString era, "transaction", "build"
, "--change-address", Text.unpack $ paymentKeyInfoAddr wallet0
, "--tx-in", Text.unpack $ renderTxIn txin1
, "--tx-out", Text.unpack (paymentKeyInfoAddr wallet0) <> "+" <> show @Int 5_000_000
, "--proposal-file", updateCommitteeFp
, "--out-file", txbodyFp
]

-- double check that we're starting with an empty committee
committeeMembers <- getCommitteeMembers epochStateView ceo
committeeMembers `H.assertWith` null

signedProposalTx <-
DRep.signTx execConfig cEra work "signed-proposal" (File txbodyFp) [SomeKeyPair $ paymentKeyInfoPair wallet0]
DRep.submitTx execConfig cEra signedProposalTx

governanceActionTxId <- H.noteM $ DRep.retrieveTransactionId execConfig signedProposalTx

governanceActionIx <-
H.nothingFailM .
H.leftFailM $
findCondition
(maybeExtractGovernanceActionIndex (fromString governanceActionTxId))
configurationFile
socketPath
deadlineEpoch

dRepVoteFiles <-
DRep.generateVoteFiles
execConfig work "vote-files" governanceActionTxId governanceActionIx
[(defaultDRepKeyPair idx, vote) | (vote, idx) <- drepVotes]

spoVoteFiles <-
SPO.generateVoteFiles
ceo execConfig work "vote-files" governanceActionTxId governanceActionIx
[(poolKeys, vote) | (vote, _idx) <- spoVotes]

let voteFiles = dRepVoteFiles <> spoVoteFiles

voteTxBodyFp <-
DRep.createVotingTxBody
execConfig epochStateView sbe work "vote-tx-body" voteFiles wallet0

-- FIXME: remove dependence of signTx on PaymentKeyPair
let poolNodePaymentKeyPair = KeyPair
{ signingKey = File . signingKeyFp $ poolNodeKeysCold poolKeys
, verificationKey = error "unused"
}
drepSKeys = map (defaultDRepKeyPair . snd) drepVotes
signingKeys = SomeKeyPair <$> paymentKeyInfoPair wallet0:poolNodePaymentKeyPair:drepSKeys
voteTxFp <- DRep.signTx
execConfig cEra gov "signed-vote-tx" voteTxBodyFp signingKeys

DRep.submitTx execConfig cEra voteTxFp

_ <- waitForEpochs epochStateView (L.EpochInterval 1)

govState <- getGovState epochStateView ceo
govActionState <- H.headM $ govState ^. L.cgsProposalsL . L.pPropsL . to toList
let gaDRepVotes = govActionState ^. L.gasDRepVotesL . to toList
gaSpoVotes = govActionState ^. L.gasStakePoolVotesL . to toList

length (filter ((== L.VoteYes) . snd) gaDRepVotes) === 5
length (filter ((== L.VoteNo) . snd) gaDRepVotes) === 3
length (filter ((== L.Abstain) . snd) gaDRepVotes) === 2
length drepVotes === length gaDRepVotes
length (filter ((== L.VoteYes) . snd) gaSpoVotes) === 1
length spoVotes === length gaSpoVotes

H.nothingFailM . H.leftFailM $
findCondition committeeIsPresent configurationFile socketPath deadlineEpoch

-- show proposed committe meembers
H.noteShow_ ccCredentials

newCommitteeMembers :: Set (L.Credential L.ColdCommitteeRole L.StandardCrypto)
<- fromList <$> getCommitteeMembers epochStateView ceo

-- check that the committee is actually what we expect
newCommitteeMembers === fromList ccCredentials

parseKeyHashCred :: MonadFail m => String -> m (L.Credential kr L.StandardCrypto)
parseKeyHashCred hash = L.parseCredential $ "keyHash-" <> Text.pack (trim hash)

trim :: String -> String
trim = f . f
where f = reverse . dropWhile C.isSpace

getCommitteeMembers
:: HasCallStack
=> H.MonadAssertion m
=> MonadIO m
=> MonadTest m
=> EpochStateView
-> ConwayEraOnwards era
-> m [L.Credential L.ColdCommitteeRole (L.EraCrypto (ShelleyLedgerEra era))]
getCommitteeMembers epochStateView ceo = withFrozenCallStack $ do
govState <- getGovState epochStateView ceo
fmap (Map.keys . L.committeeMembers) . H.nothingFail $ strictMaybeToMaybe $ govState ^. L.cgsCommitteeL

committeeIsPresent :: AnyNewEpochState -> Maybe ()
committeeIsPresent (AnyNewEpochState sbe newEpochState) =
caseShelleyToBabbageOrConwayEraOnwards
(const $ error "Constitutional committee does not exist pre-Conway era")
(\_ -> do
let mCommittee = newEpochState
^. L.nesEsL
. L.esLStateL
. L.lsUTxOStateL
. L.utxosGovStateL
. L.cgsCommitteeL
members <- L.committeeMembers <$> strictMaybeToMaybe mCommittee
when (Map.null members) Nothing
)
sbe
Loading

0 comments on commit e918562

Please sign in to comment.