Skip to content

Commit

Permalink
WIP
Browse files Browse the repository at this point in the history
  • Loading branch information
Jimbo4350 committed May 7, 2024
1 parent 33af30d commit 5b91eeb
Show file tree
Hide file tree
Showing 2 changed files with 48 additions and 1 deletion.
4 changes: 4 additions & 0 deletions cardano-testnet/src/Testnet/Defaults.hs
Original file line number Diff line number Diff line change
Expand Up @@ -14,6 +14,7 @@ module Testnet.Defaults
, defaultByronProtocolParamsJsonValue
, defaultYamlConfig
, defaultConwayGenesis
, defaultCommitteeKeyPair
, defaultCommitteeVkeyFp
, defaultCommitteeSkeyFp
, defaultDRepVkeyFp
Expand Down Expand Up @@ -528,6 +529,9 @@ defaultDRepSkeyFp
-> FilePath
defaultDRepSkeyFp n = "drep-keys" </> ("drep" <> show n) </> "drep.skey"

defaultCommitteeKeyPair :: Int -> PaymentKeyPair
defaultCommitteeKeyPair n = PaymentKeyPair (defaultCommitteeVkeyFp n) (defaultCommitteeSkeyFp n)

-- | The relative path to DRep key pairs in directories created by cardano-testnet
defaultDRepKeyPair :: Int -> PaymentKeyPair
defaultDRepKeyPair n = PaymentKeyPair (defaultDRepVkeyFp n) (defaultDRepSkeyFp n)
Expand Down
Original file line number Diff line number Diff line change
@@ -1,3 +1,4 @@
{-# LANGUAGE BangPatterns #-}
{-# LANGUAGE NamedFieldPuns #-}
{-# LANGUAGE NumericUnderscores #-}
{-# LANGUAGE OverloadedStrings #-}
Expand All @@ -9,6 +10,7 @@ module Cardano.Testnet.Test.Gov.UpdateCommittee
) where

import Cardano.Api as Api
import Cardano.Api.Error
import Cardano.Api.Shelley

import qualified Cardano.Ledger.Conway.Genesis as L
Expand All @@ -22,12 +24,15 @@ import Control.Monad
import Data.Bifunctor
import qualified Data.ByteString.Char8 as BSC
import qualified Data.Map.Strict as Map
import Data.String
import qualified Data.Text as Text
import GHC.Stack
import System.FilePath ((</>))

import Testnet.Components.Configuration
import Testnet.Components.DReps
import Testnet.Components.DReps as DRep
import Testnet.Components.Query
import Testnet.Components.SPO as SPO
import Testnet.Components.TestWatchdog
import Testnet.Defaults
import qualified Testnet.Process.Cli as P
Expand Down Expand Up @@ -191,6 +196,44 @@ hprop_gov_update_committee = H.integrationWorkspace "update-committee" $ \tempAb

submitTx execConfig cEra signedProposalTx

-- Create and submit votes on committee update proposal
-- Proposal was successfully submitted, now we vote on the proposal and confirm it was ratified

governanceActionTxId <- retrieveTransactionId execConfig signedProposalTx

!propSubmittedResult <- findCondition (maybeExtractGovernanceActionIndex sbe (fromString governanceActionTxId))
configurationFile
socketPath
(EpochNo 10)

governanceActionIndex <- case propSubmittedResult of
Left e ->
H.failMessage callStack
$ "findCondition failed with: " <> displayError e
Right Nothing ->
H.failMessage callStack "Couldn't find proposal."
Right (Just a) -> return a

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

annotateShow spoVotes
annotateShow drepVotes

voteFiles <- generateVoteFiles execConfig work "vote-files"
governanceActionTxId governanceActionIndex
[(defaultSPOKeys idx, vote) | (vote, idx) <- spoVotes]

-- Submit votes
voteTxBodyFp <- createVotingTxBody execConfig epochStateView sbe work "vote-tx-body"
voteFiles wallet0

voteTxFp <- signTx execConfig cEra work "signed-vote-tx" voteTxBodyFp
(paymentKeyInfoPair wallet0:[defaultCommitteeKeyPair n | (_, n) <- allVotes])

submitTx execConfig cEra voteTxFp
-- Confirm the proposal has been ratified

return ()
Expand Down

0 comments on commit 5b91eeb

Please sign in to comment.