Skip to content

Commit

Permalink
Fixes required by rebasing
Browse files Browse the repository at this point in the history
  • Loading branch information
palas committed Apr 25, 2024
1 parent e7aecaf commit 03bffb9
Show file tree
Hide file tree
Showing 6 changed files with 61 additions and 50 deletions.
14 changes: 8 additions & 6 deletions cardano-testnet/src/Testnet/EpochStateProcessing.hs
Original file line number Diff line number Diff line change
Expand Up @@ -5,10 +5,10 @@ module Testnet.EpochStateProcessing
, findCondition
) where

import Cardano.Api (AnyNewEpochState (..), ConwayEra, EpochNo, File (File),
FoldBlocksError, LedgerStateCondition (..), MonadIO, ShelleyBasedEra,
ValidationMode (FullValidation), foldEpochState, runExceptT,
shelleyBasedEraConstraints)
import Cardano.Api (AnyNewEpochState (..), ConwayEra, ConwayEraOnwards, EpochNo,
File (File), FoldBlocksError, LedgerStateCondition (..), MonadIO,
ValidationMode (FullValidation), conwayEraOnwardsToShelleyBasedEra,
foldEpochState, runExceptT, shelleyBasedEraConstraints)
import qualified Cardano.Api as Api
import Cardano.Api.Ledger (GovActionId (..))
import qualified Cardano.Api.Ledger as L
Expand Down Expand Up @@ -58,11 +58,13 @@ findCondition epochStateFoldFunc configurationFile socketPath maxEpochNo = withF
Just x -> put (Just x) >> pure ConditionMet
Nothing -> pure ConditionNotMet

maybeExtractGovernanceActionIndex :: ShelleyBasedEra ConwayEra -- ^ The era in which the test runs
maybeExtractGovernanceActionIndex :: ()
=> ConwayEraOnwards ConwayEra -- ^ The era in which the test runs
-> Api.TxId
-> AnyNewEpochState
-> Maybe Word32
maybeExtractGovernanceActionIndex sbe txid (AnyNewEpochState actualEra newEpochState) =
maybeExtractGovernanceActionIndex ceo txid (AnyNewEpochState actualEra newEpochState) =
let sbe = conwayEraOnwardsToShelleyBasedEra ceo in
case testEquality sbe actualEra of
Just Refl -> do
let proposals = shelleyBasedEraConstraints sbe newEpochState
Expand Down
Original file line number Diff line number Diff line change
Expand Up @@ -307,7 +307,7 @@ makeActivityChangeProposal execConfig epochStateView configurationFile socketPat

governanceActionTxId <- retrieveTransactionId execConfig signedProposalTx

!propSubmittedResult <- findCondition (maybeExtractGovernanceActionIndex sbe (fromString governanceActionTxId))
!propSubmittedResult <- findCondition (maybeExtractGovernanceActionIndex ceo (fromString governanceActionTxId))
(unFile configurationFile)
(unFile socketPath)
(EpochNo timeout)
Expand Down
Original file line number Diff line number Diff line change
Expand Up @@ -55,7 +55,8 @@ hprop_ledger_events_info_action = H.integrationRetryWorkspace 0 "info-hash" $ \t

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

let sbe = ShelleyBasedEraConway
let ceo = ConwayEraOnwardsConway
sbe = conwayEraOnwardsToShelleyBasedEra ceo
era = toCardanoEra sbe
fastTestnetOptions = cardanoDefaultTestnetOptions
{ cardanoEpochLength = 100
Expand Down Expand Up @@ -149,7 +150,7 @@ hprop_ledger_events_info_action = H.integrationRetryWorkspace 0 "info-hash" $ \t
, "--tx-file", txbodySignedFp
]

!propSubmittedResult <- findCondition (maybeExtractGovernanceActionIndex sbe (fromString txidString))
!propSubmittedResult <- findCondition (maybeExtractGovernanceActionIndex ceo (fromString txidString))
configurationFile
socketPath
(EpochNo 10)
Expand Down
Original file line number Diff line number Diff line change
Expand Up @@ -25,6 +25,7 @@ import Control.Monad.Catch (MonadCatch)
import qualified Data.Aeson as Aeson
import qualified Data.Aeson.Lens as AL
import Data.ByteString.Lazy.Char8 (pack)
import Data.Data (Typeable)
import Data.String (fromString)
import qualified Data.Text as Text
import Data.Word (Word32)
Expand Down Expand Up @@ -60,7 +61,8 @@ hprop_check_predefined_abstain_drep = H.integrationWorkspace "test-activity" $ \
work <- H.createDirectoryIfMissing $ tempAbsPath' </> "work"

-- Create default testnet with 3 DReps and 3 stake holders delegated, one to each DRep.
let sbe = ShelleyBasedEraConway
let ceo = ConwayEraOnwardsConway
sbe = conwayEraOnwardsToShelleyBasedEra ceo
era = toCardanoEra sbe
cEra = AnyCardanoEra era
fastTestnetOptions = cardanoDefaultTestnetOptions
Expand Down Expand Up @@ -102,7 +104,7 @@ hprop_check_predefined_abstain_drep = H.integrationWorkspace "test-activity" $ \

-- Do some proposal and vote yes with the first DRep only
-- and assert that proposal does NOT pass.
void $ desiredPoolNumberProposalTest execConfig epochStateView configurationFile socketPath sbe gov "firstProposal"
void $ desiredPoolNumberProposalTest execConfig epochStateView configurationFile socketPath ceo gov "firstProposal"
wallet0 Nothing [(1, "yes")] newNumberOfDesiredPools initialDesiredNumberOfPools 2

-- Take the last two stake delegators and delegate them to "Abstain".
Expand All @@ -114,7 +116,7 @@ hprop_check_predefined_abstain_drep = H.integrationWorkspace "test-activity" $ \
-- Do some other proposal and vote yes with first DRep only
-- and assert the new proposal passes now.
let newNumberOfDesiredPools2 = fromIntegral (newNumberOfDesiredPools + 1)
void $ desiredPoolNumberProposalTest execConfig epochStateView configurationFile socketPath sbe gov "secondProposal"
void $ desiredPoolNumberProposalTest execConfig epochStateView configurationFile socketPath ceo gov "secondProposal"
wallet0 Nothing [(1, "yes")] newNumberOfDesiredPools2 newNumberOfDesiredPools2 2

delegateToAlwaysAbstain
Expand Down Expand Up @@ -185,7 +187,7 @@ desiredPoolNumberProposalTest
-> EpochStateView
-> FilePath
-> FilePath
-> ShelleyBasedEra ConwayEra
-> ConwayEraOnwards ConwayEra
-> FilePath
-> FilePath
-> PaymentKeyInfo
Expand All @@ -195,7 +197,7 @@ desiredPoolNumberProposalTest
-> Integer
-> Integer
-> m (String, Word32)
desiredPoolNumberProposalTest execConfig epochStateView configurationFile socketPath sbe work prefix
desiredPoolNumberProposalTest execConfig epochStateView configurationFile socketPath ceo work prefix
wallet previousProposalInfo votes change expected epochsToWait = do

baseDir <- H.createDirectoryIfMissing $ work </> prefix
Expand All @@ -206,9 +208,9 @@ desiredPoolNumberProposalTest execConfig epochStateView configurationFile socket

thisProposal@(governanceActionTxId, governanceActionIndex) <-
makeDesiredPoolNumberChangeProposal execConfig epochStateView (File configurationFile) (File socketPath)
sbe baseDir "proposal" previousProposalInfo (fromIntegral change) wallet
ceo baseDir "proposal" previousProposalInfo (fromIntegral change) wallet

voteChangeProposal execConfig epochStateView sbe baseDir "vote"
voteChangeProposal execConfig epochStateView ceo baseDir "vote"
governanceActionTxId governanceActionIndex propVotes [] wallet

(EpochNo epochAfterProp) <- getCurrentEpochNo epochStateView
Expand All @@ -227,17 +229,18 @@ makeDesiredPoolNumberChangeProposal
-> EpochStateView
-> NodeConfigFile 'In
-> SocketPath
-> ShelleyBasedEra ConwayEra
-> ConwayEraOnwards ConwayEra
-> FilePath
-> String
-> Maybe (String, Word32)
-> Word32
-> PaymentKeyInfo
-> m (String, Word32)
makeDesiredPoolNumberChangeProposal execConfig epochStateView configurationFile socketPath
sbe work prefix prevGovActionInfo desiredPoolNumber wallet = do
ceo work prefix prevGovActionInfo desiredPoolNumber wallet = do

let era = toCardanoEra sbe
let sbe = conwayEraOnwardsToShelleyBasedEra ceo
era = toCardanoEra sbe
cEra = AnyCardanoEra era

baseDir <- H.createDirectoryIfMissing $ work </> prefix
Expand All @@ -258,7 +261,7 @@ makeDesiredPoolNumberChangeProposal execConfig epochStateView configurationFile
, "hash", "anchor-data", "--file-text", proposalAnchorFile
]

minDRepDeposit <- getMinDRepDeposit execConfig
minDRepDeposit <- getMinDRepDeposit execConfig ceo

proposalFile <- H.note $ baseDir </> "sample-proposal-file"

Expand Down Expand Up @@ -295,7 +298,7 @@ makeDesiredPoolNumberChangeProposal execConfig epochStateView configurationFile

governanceActionTxId <- retrieveTransactionId execConfig signedProposalTx

!propSubmittedResult <- findCondition (maybeExtractGovernanceActionIndex sbe (fromString governanceActionTxId))
!propSubmittedResult <- findCondition (maybeExtractGovernanceActionIndex ceo (fromString governanceActionTxId))
(unFile configurationFile)
(unFile socketPath)
(EpochNo 30)
Expand All @@ -310,10 +313,10 @@ makeDesiredPoolNumberChangeProposal execConfig epochStateView configurationFile

return (governanceActionTxId, governanceActionIndex)

voteChangeProposal :: (MonadTest m, MonadIO m, MonadCatch m, H.MonadAssertion m)
voteChangeProposal :: (Typeable era, MonadTest m, MonadIO m, MonadCatch m, H.MonadAssertion m)
=> H.ExecConfig
-> EpochStateView
-> ShelleyBasedEra ConwayEra
-> ConwayEraOnwards era
-> FilePath
-> FilePath
-> String
Expand All @@ -322,10 +325,11 @@ voteChangeProposal :: (MonadTest m, MonadIO m, MonadCatch m, H.MonadAssertion m)
-> [(String, Int)]
-> PaymentKeyInfo
-> m ()
voteChangeProposal execConfig epochStateView sbe work prefix governanceActionTxId governanceActionIndex drepVotes spoVotes wallet = do
voteChangeProposal execConfig epochStateView ceo work prefix governanceActionTxId governanceActionIndex drepVotes spoVotes wallet = do
baseDir <- H.createDirectoryIfMissing $ work </> prefix

let era = toCardanoEra sbe
let sbe = conwayEraOnwardsToShelleyBasedEra ceo
era = toCardanoEra sbe
cEra = AnyCardanoEra era

drepVoteFiles <- DRep.generateVoteFiles execConfig baseDir "drep-vote-files"
Expand Down
Original file line number Diff line number Diff line change
Expand Up @@ -59,7 +59,8 @@ hprop_check_predefined_no_confidence_drep = H.integrationWorkspace "test-activit
work <- H.createDirectoryIfMissing $ tempAbsPath' </> "work"

-- Create default testnet with 3 DReps and 3 stake holders delegated, one to each DRep.
let sbe = ShelleyBasedEraConway
let ceo = ConwayEraOnwardsConway
sbe = conwayEraOnwardsToShelleyBasedEra ceo
era = toCardanoEra sbe
cEra = AnyCardanoEra era
fastTestnetOptions = cardanoDefaultTestnetOptions
Expand Down Expand Up @@ -96,7 +97,7 @@ hprop_check_predefined_no_confidence_drep = H.integrationWorkspace "test-activit
gov <- H.createDirectoryIfMissing $ work </> "governance"

-- Create constitutional committee and check it exists
constitutionalAction <- updateConstitutionalCommittee execConfig epochStateView configurationFile socketPath sbe work "committeeUpdate"
constitutionalAction <- updateConstitutionalCommittee execConfig epochStateView configurationFile socketPath ceo work "committeeUpdate"
wallet0 Nothing [(3, "yes")] 10

-- Do some proposal and vote yes with all the DReps
Expand All @@ -105,7 +106,7 @@ hprop_check_predefined_no_confidence_drep = H.integrationWorkspace "test-activit

let newNumberOfDesiredPools = fromIntegral (initialDesiredNumberOfPools + 1)

firstProposalInfo <- desiredPoolNumberProposalTest execConfig epochStateView configurationFile socketPath sbe gov "firstProposal"
firstProposalInfo <- desiredPoolNumberProposalTest execConfig epochStateView configurationFile socketPath ceo gov "firstProposal"
wallet1 Nothing [(3, "yes")] newNumberOfDesiredPools newNumberOfDesiredPools 3

-- Take the last two stake delegators and delegate them to "No Confidence".
Expand All @@ -118,12 +119,12 @@ hprop_check_predefined_no_confidence_drep = H.integrationWorkspace "test-activit
-- and assert the new proposal does NOT pass.
let newNumberOfDesiredPools2 = fromIntegral (newNumberOfDesiredPools + 1)

void $ desiredPoolNumberProposalTest execConfig epochStateView configurationFile socketPath sbe gov "secondProposal"
void $ desiredPoolNumberProposalTest execConfig epochStateView configurationFile socketPath ceo gov "secondProposal"
wallet0 (Just firstProposalInfo) [(3, "yes")] newNumberOfDesiredPools2 newNumberOfDesiredPools 3

-- Create a no confidence proposal and vote "no" to the proposal with all DReps.
-- Assert the no confidence proposal passes.
void $ testNoConfidenceProposal execConfig epochStateView configurationFile socketPath sbe gov "noConfidenceProposal"
void $ testNoConfidenceProposal execConfig epochStateView configurationFile socketPath ceo gov "noConfidenceProposal"
wallet1 constitutionalAction [(3, "no")] 10

waitTillCommittee
Expand Down Expand Up @@ -177,15 +178,15 @@ updateConstitutionalCommittee
-> EpochStateView
-> FilePath
-> FilePath
-> ShelleyBasedEra ConwayEra
-> ConwayEraOnwards ConwayEra
-> FilePath
-> FilePath
-> PaymentKeyInfo
-> Maybe (String, Word32)
-> t (Int, String)
-> Integer
-> m (String, Word32)
updateConstitutionalCommittee execConfig epochStateView configurationFile socketPath sbe work prefix
updateConstitutionalCommittee execConfig epochStateView configurationFile socketPath ceo work prefix
wallet previousProposalInfo votes waitTillEpoch = do

baseDir <- H.createDirectoryIfMissing $ work </> prefix
Expand All @@ -210,9 +211,9 @@ updateConstitutionalCommittee execConfig epochStateView configurationFile socket

thisProposal@(governanceActionTxId, governanceActionIndex) <-
makeUpdateConstitutionalCommitteeProposal execConfig epochStateView (File configurationFile) (File socketPath)
sbe baseDir "proposal" previousProposalInfo [coldKeyHash] wallet
ceo baseDir "proposal" previousProposalInfo [coldKeyHash] wallet

voteChangeProposal execConfig epochStateView sbe baseDir "vote"
voteChangeProposal execConfig epochStateView ceo baseDir "vote"
governanceActionTxId governanceActionIndex propVotes (zip (repeat "yes") [1..3]) wallet

(EpochNo epochAfterProp) <- getCurrentEpochNo epochStateView
Expand All @@ -229,17 +230,18 @@ makeUpdateConstitutionalCommitteeProposal
-> EpochStateView
-> NodeConfigFile 'In
-> SocketPath
-> ShelleyBasedEra ConwayEra
-> ConwayEraOnwards ConwayEra
-> FilePath
-> String
-> Maybe (String, Word32)
-> f String
-> PaymentKeyInfo
-> m (String, Word32)
makeUpdateConstitutionalCommitteeProposal execConfig epochStateView configurationFile socketPath
sbe work prefix prevGovActionInfo coldKeyHashes wallet = do
ceo work prefix prevGovActionInfo coldKeyHashes wallet = do

let era = toCardanoEra sbe
let sbe = conwayEraOnwardsToShelleyBasedEra ceo
era = toCardanoEra sbe
cEra = AnyCardanoEra era

baseDir <- H.createDirectoryIfMissing $ work </> prefix
Expand All @@ -260,7 +262,7 @@ makeUpdateConstitutionalCommitteeProposal execConfig epochStateView configuratio
, "hash", "anchor-data", "--file-text", proposalAnchorFile
]

minDRepDeposit <- getMinDRepDeposit execConfig
minDRepDeposit <- getMinDRepDeposit execConfig ceo

proposalFile <- H.note $ baseDir </> "sample-proposal-file"

Expand Down Expand Up @@ -301,7 +303,7 @@ makeUpdateConstitutionalCommitteeProposal execConfig epochStateView configuratio

governanceActionTxId <- retrieveTransactionId execConfig signedProposalTx

!propSubmittedResult <- findCondition (maybeExtractGovernanceActionIndex sbe (fromString governanceActionTxId))
!propSubmittedResult <- findCondition (maybeExtractGovernanceActionIndex ceo (fromString governanceActionTxId))
(unFile configurationFile)
(unFile socketPath)
(EpochNo 10)
Expand Down Expand Up @@ -338,16 +340,17 @@ testNoConfidenceProposal
-> EpochStateView
-> FilePath
-> FilePath
-> ShelleyBasedEra ConwayEra
-> ConwayEraOnwards ConwayEra
-> FilePath
-> FilePath
-> PaymentKeyInfo
-> (String, Word32)
-> t (Int, String)
-> Integer
-> m (String, Word32)
testNoConfidenceProposal execConfig epochStateView configurationFile socketPath sbe work prefix
testNoConfidenceProposal execConfig epochStateView configurationFile socketPath ceo work prefix
wallet previousProposalInfo votes waitTillEpoch = do

baseDir <- H.createDirectoryIfMissing $ work </> prefix

let propVotes :: [(String, Int)]
Expand All @@ -356,9 +359,9 @@ testNoConfidenceProposal execConfig epochStateView configurationFile socketPath

thisProposal@(governanceActionTxId, governanceActionIndex) <-
makeNoConfidenceProposal execConfig epochStateView (File configurationFile) (File socketPath)
sbe baseDir "proposal" previousProposalInfo wallet
ceo baseDir "proposal" previousProposalInfo wallet

voteChangeProposal execConfig epochStateView sbe baseDir "vote"
voteChangeProposal execConfig epochStateView ceo baseDir "vote"
governanceActionTxId governanceActionIndex propVotes (zip (repeat "yes") [1..3]) wallet

(EpochNo epochAfterProp) <- getCurrentEpochNo epochStateView
Expand All @@ -376,15 +379,16 @@ makeNoConfidenceProposal
-> EpochStateView
-> NodeConfigFile 'In
-> SocketPath
-> ShelleyBasedEra ConwayEra
-> ConwayEraOnwards ConwayEra
-> FilePath
-> String
-> (String, Word32)
-> PaymentKeyInfo
-> m (String, Word32)
makeNoConfidenceProposal execConfig epochStateView configurationFile socketPath
sbe work prefix (prevGovernanceActionTxId, prevGovernanceActionIndex) wallet = do
let era = toCardanoEra sbe
ceo work prefix (prevGovernanceActionTxId, prevGovernanceActionIndex) wallet = do
let sbe = conwayEraOnwardsToShelleyBasedEra ceo
era = toCardanoEra sbe
cEra = AnyCardanoEra era

baseDir <- H.createDirectoryIfMissing $ work </> prefix
Expand All @@ -405,7 +409,7 @@ makeNoConfidenceProposal execConfig epochStateView configurationFile socketPath
, "hash", "anchor-data", "--file-text", proposalAnchorFile
]

minDRepDeposit <- getMinDRepDeposit execConfig
minDRepDeposit <- getMinDRepDeposit execConfig ceo

proposalFile <- H.note $ baseDir </> "sample-proposal-file"

Expand Down Expand Up @@ -439,7 +443,7 @@ makeNoConfidenceProposal execConfig epochStateView configurationFile socketPath

governanceActionTxId <- retrieveTransactionId execConfig signedProposalTx

!propSubmittedResult <- findCondition (maybeExtractGovernanceActionIndex sbe (fromString governanceActionTxId))
!propSubmittedResult <- findCondition (maybeExtractGovernanceActionIndex ceo (fromString governanceActionTxId))
(unFile configurationFile)
(unFile socketPath)
(EpochNo 30)
Expand Down
Original file line number Diff line number Diff line change
Expand Up @@ -174,7 +174,7 @@ hprop_ledger_events_propose_new_constitution = H.integrationWorkspace "propose-n

governanceActionTxId <- retrieveTransactionId execConfig signedProposalTx

!propSubmittedResult <- findCondition (maybeExtractGovernanceActionIndex sbe (fromString governanceActionTxId))
!propSubmittedResult <- findCondition (maybeExtractGovernanceActionIndex ceo (fromString governanceActionTxId))
configurationFile
socketPath
(EpochNo 10)
Expand Down Expand Up @@ -207,7 +207,7 @@ hprop_ledger_events_propose_new_constitution = H.integrationWorkspace "propose-n
(File configurationFile)
(File socketPath)
FullValidation
(EpochNo 10)
(EpochNo 30)
()
(\epochState _ _ -> foldBlocksCheckConstitutionWasRatified constitutionHash constitutionScriptHash epochState)

Expand Down

0 comments on commit 03bffb9

Please sign in to comment.