Skip to content

Commit

Permalink
Adjust conway Imp tests to an existent initial committee
Browse files Browse the repository at this point in the history
  • Loading branch information
teodanciu committed Apr 25, 2024
1 parent 9ff328d commit 8f31f71
Show file tree
Hide file tree
Showing 8 changed files with 232 additions and 212 deletions.
Original file line number Diff line number Diff line change
Expand Up @@ -24,6 +24,7 @@ import Control.Monad (forM)
import Control.State.Transition.Extended (STS (..))
import Data.Default.Class (def)
import Data.Foldable (foldl', traverse_)
import Data.List.NonEmpty (NonEmpty (..))
import qualified Data.List.NonEmpty as NE
import qualified Data.Map.Strict as Map
import Data.Ratio ((%))
Expand Down Expand Up @@ -104,13 +105,14 @@ treasuryWithdrawalsSpec =
ensTreasury enactState'' `shouldBe` Coin 1

it "Withdrawals exceeding treasury submitted in a single proposal" $ do
(drepC, committeeC, _) <- electBasicCommittee
(committeeC :| _) <- registerInitialCommittee
(drepKh, _, _) <- setupSingleDRep 1_000_000
modifyPParams $ ppGovActionLifetimeL .~ EpochInterval 5
initialTreasury <- getTreasury
numWithdrawals <- choose (1, 10)
withdrawals <- genWithdrawalsExceeding initialTreasury numWithdrawals

void $ enactTreasuryWithdrawals withdrawals drepC committeeC
void $ enactTreasuryWithdrawals withdrawals (KeyHashObj drepKh) committeeC
checkNoWithdrawal initialTreasury withdrawals

let sumRequested = foldMap snd withdrawals
Expand All @@ -125,16 +127,18 @@ treasuryWithdrawalsSpec =
sumRewardAccounts withdrawals `shouldReturn` sumRequested

it "Withdrawals exceeding maxBound Word64 submitted in a single proposal" $ do
(drepC, committeeC, _) <- electBasicCommittee
(committeeC :| _) <- registerInitialCommittee
(drepKh, _, _) <- setupSingleDRep 1_000_000
modifyPParams $ ppGovActionLifetimeL .~ EpochInterval 5
initialTreasury <- getTreasury
numWithdrawals <- choose (1, 10)
withdrawals <- genWithdrawalsExceeding (Coin (fromIntegral (maxBound :: Word64))) numWithdrawals
void $ enactTreasuryWithdrawals withdrawals drepC committeeC
void $ enactTreasuryWithdrawals withdrawals (KeyHashObj drepKh) committeeC
checkNoWithdrawal initialTreasury withdrawals

it "Withdrawals exceeding treasury submitted in several proposals within the same epoch" $ do
(drepC, committeeC, _) <- electBasicCommittee
(committeeC :| _) <- registerInitialCommittee
(drepKh, _, _) <- setupSingleDRep 1_000_000
modifyPParams $ ppGovActionLifetimeL .~ EpochInterval 5
initialTreasury <- getTreasury
numWithdrawals <- choose (1, 10)
Expand All @@ -144,7 +148,7 @@ treasuryWithdrawalsSpec =
traverse_
( \w -> do
gaId <- submitTreasuryWithdrawals @era [w]
submitYesVote_ (DRepVoter drepC) gaId
submitYesVote_ (DRepVoter (KeyHashObj drepKh)) gaId
submitYesVote_ (CommitteeVoter committeeC) gaId
)
withdrawals
Expand Down Expand Up @@ -183,7 +187,7 @@ treasuryWithdrawalsSpec =
hardForkInitiationSpec :: ConwayEraImp era => SpecWith (ImpTestState era)
hardForkInitiationSpec =
it "HardForkInitiation" $ do
(_, committeeMember, _) <- electBasicCommittee
(committeeC :| _) <- registerInitialCommittee
modifyPParams $ \pp ->
pp
& ppDRepVotingThresholdsL
Expand All @@ -209,7 +213,7 @@ hardForkInitiationSpec =
nextMajorVersion <- succVersion $ pvMajor curProtVer
let nextProtVer = curProtVer {pvMajor = nextMajorVersion}
govActionId <- submitGovAction $ HardForkInitiation SNothing nextProtVer
submitYesVote_ (CommitteeVoter committeeMember) govActionId
submitYesVote_ (CommitteeVoter committeeC) govActionId
submitYesVote_ (DRepVoter (KeyHashObj dRep1)) govActionId
submitYesVote_ (StakePoolVoter stakePoolId1) govActionId
passNEpochs 2
Expand Down Expand Up @@ -238,8 +242,9 @@ noConfidenceSpec =
do
committee <- getCommittee
impAnn "There should not be a committee" $ committee `shouldBe` SNothing
assertNoCommittee
khCC <- freshKeyHash
initialCommitteeMembers <- getCommitteeMembers

(drep, _, _) <- setupSingleDRep 1_000_000
let committeeMap =
Map.fromList
Expand All @@ -249,7 +254,7 @@ noConfidenceSpec =
electCommittee
SNothing
drep
mempty
initialCommitteeMembers
committeeMap
(khSPO, _, _) <- setupPoolWithStake $ Coin 42_000_000
logStakeDistr
Expand All @@ -276,26 +281,27 @@ noConfidenceSpec =
constitutionSpec :: ConwayEraImp era => SpecWith (ImpTestState era)
constitutionSpec =
it "Constitution" $ do
(dRep, committeeMember, _) <- electBasicCommittee
(committeeC :| _) <- registerInitialCommittee
(drepKh, _, _) <- setupSingleDRep 1_000_000
(govActionId, constitution) <- submitConstitution SNothing

proposalsBeforeVotes <- getsNES $ newEpochStateGovStateL . proposalsGovStateL
pulserBeforeVotes <- getsNES newEpochStateDRepPulsingStateL

submitYesVote_ (DRepVoter dRep) govActionId
submitYesVote_ (CommitteeVoter committeeMember) govActionId
submitYesVote_ (DRepVoter (KeyHashObj drepKh)) govActionId
submitYesVote_ (CommitteeVoter committeeC) govActionId

proposalsAfterVotes <- getsNES $ newEpochStateGovStateL . proposalsGovStateL
pulserAfterVotes <- getsNES newEpochStateDRepPulsingStateL

impAnn "Votes are recorded in the proposals" $ do
let proposalsWithVotes =
proposalsAddVote
(CommitteeVoter committeeMember)
(CommitteeVoter committeeC)
VoteYes
govActionId
( proposalsAddVote
(DRepVoter dRep)
(DRepVoter (KeyHashObj drepKh))
VoteYes
govActionId
proposalsBeforeVotes
Expand Down Expand Up @@ -339,20 +345,20 @@ actionPrioritySpec =
it
"higher action priority wins"
$ do
(drepC, _, gpi) <- electBasicCommittee
(drepKh, _, _) <- setupSingleDRep 1_000_000
(poolKH, _, _) <- setupPoolWithStake $ Coin 1_000_000
modifyPParams $ ppGovActionLifetimeL .~ EpochInterval 5
cc <- KeyHashObj <$> freshKeyHash
gai1 <-
submitGovAction $
UpdateCommittee (SJust gpi) mempty (Map.singleton cc (EpochNo 30)) $
UpdateCommittee SNothing mempty (Map.singleton cc (EpochNo 30)) $
1 %! 2
-- gai2 is the first action of a higher priority
gai2 <- submitGovAction $ NoConfidence $ SJust gpi
gai3 <- submitGovAction $ NoConfidence $ SJust gpi
gai2 <- submitGovAction $ NoConfidence SNothing
gai3 <- submitGovAction $ NoConfidence SNothing
traverse_ @[]
( \gaid -> do
submitYesVote_ (DRepVoter drepC) gaid
submitYesVote_ (DRepVoter (KeyHashObj drepKh)) gaid
submitYesVote_ (StakePoolVoter poolKH) gaid
)
[gai1, gai2, gai3]
Expand All @@ -371,7 +377,8 @@ actionPrioritySpec =
let val3 = Coin 1_000_003

it "proposals of same priority are enacted in order of submission" $ do
(drepC, committeeC, _) <- electBasicCommittee
(committeeC :| _) <- registerInitialCommittee
(drepKh, _, _) <- setupSingleDRep 1_000_000
modifyPParams $ ppGovActionLifetimeL .~ EpochInterval 5
pGai0 <-
submitParameterChange
Expand All @@ -387,7 +394,7 @@ actionPrioritySpec =
$ def & ppuDRepDepositL .~ SJust val3
traverse_ @[]
( \gaid -> do
submitYesVote_ (DRepVoter drepC) gaid
submitYesVote_ (DRepVoter (KeyHashObj drepKh)) gaid
submitYesVote_ (CommitteeVoter committeeC) gaid
)
[pGai0, pGai1, pGai2]
Expand All @@ -399,7 +406,8 @@ actionPrioritySpec =
`shouldReturn` val3

it "only the first action of a transaction gets enacted" $ do
(drepC, committeeC, _) <- electBasicCommittee
(committeeC :| _) <- registerInitialCommittee
(drepKh, _, _) <- setupSingleDRep 1_000_000
modifyPParams $ ppGovActionLifetimeL .~ EpochInterval 5
gaids <-
submitGovActions $
Expand All @@ -419,7 +427,7 @@ actionPrioritySpec =
]
traverse_
( \gaid -> do
submitYesVote_ (DRepVoter drepC) gaid
submitYesVote_ (DRepVoter (KeyHashObj drepKh)) gaid
submitYesVote_ (CommitteeVoter committeeC) gaid
)
gaids
Expand Down
Original file line number Diff line number Diff line change
Expand Up @@ -31,14 +31,15 @@ import Cardano.Ledger.Val
import Control.Monad.Writer (listen)
import Data.Data (cast)
import Data.Default.Class (Default (..))
import Data.List.NonEmpty (NonEmpty (..))
import qualified Data.List.NonEmpty as NE
import qualified Data.Map.Strict as Map
import Data.Maybe (fromJust)
import Data.Maybe.Strict (StrictMaybe (..))
import qualified Data.Sequence.Strict as SSeq
import qualified Data.Set as Set
import Data.Tree
import Lens.Micro ((&), (.~))
import Lens.Micro ((%~), (&), (.~))
import Test.Cardano.Ledger.Conway.ImpTest
import Test.Cardano.Ledger.Core.Rational (IsRatio (..))
import Test.Cardano.Ledger.Imp.Common
Expand Down Expand Up @@ -121,7 +122,7 @@ dRepSpec ::
SpecWith (ImpTestState era)
dRepSpec =
describe "DRep" $ do
it "is updated based on to number of dormant epochs" $ do
it "expiry is updated based on the number of dormant epochs" $ do
modifyPParams $ ppGovActionLifetimeL .~ EpochInterval 2
(drep, _, _) <- setupSingleDRep 1_000_000

Expand Down Expand Up @@ -187,14 +188,18 @@ dRepSpec =
logEntry "Stake distribution after DRep registration:"
logStakeDistr
passEpoch

treasurySpec ::
forall era.
ConwayEraImp era =>
SpecWith (ImpTestState era)
treasurySpec =
describe "Treasury" $ do
it "constitution is accepted after two epochs" $ do
modifyPParams $ \pp ->
pp
& ppDRepVotingThresholdsL
%~ ( \dvt ->
dvt
{ dvtCommitteeNormal = 1 %! 1
, dvtCommitteeNoConfidence = 1 %! 2
, dvtUpdateToConstitution = 1 %! 2
}
)

constitutionHash <- freshSafeHash
let
constitutionAction =
Expand All @@ -212,13 +217,14 @@ treasurySpec =
logEntry "Submitting new constitution"
gaidConstitutionProp <- submitGovAction constitutionAction

(dRepCred, committeeHotCred, _) <- electBasicCommittee

(committeeHotCred :| _) <- registerInitialCommittee
(drepKh, _, _) <- setupSingleDRep 1_000_000
passEpoch
logRatificationChecks gaidConstitutionProp
do
isAccepted <- isDRepAccepted gaidConstitutionProp
assertBool "Gov action should not be accepted" $ not isAccepted
submitYesVote_ (DRepVoter dRepCred) gaidConstitutionProp
submitYesVote_ (DRepVoter (KeyHashObj drepKh)) gaidConstitutionProp
submitYesVote_ (CommitteeVoter committeeHotCred) gaidConstitutionProp
logAcceptedRatio gaidConstitutionProp
do
Expand All @@ -236,6 +242,12 @@ treasurySpec =
passEpoch
constitutionShouldBe "constitution.0"

treasurySpec ::
forall era.
ConwayEraImp era =>
SpecWith (ImpTestState era)
treasurySpec =
describe "Treasury" $ do
it "TreasuryWithdrawal" $ do
treasuryWithdrawalExpectation []

Expand All @@ -258,7 +270,8 @@ treasuryWithdrawalExpectation ::
[GovAction era] ->
ImpTestM era ()
treasuryWithdrawalExpectation extraWithdrawals = do
(dRepCred, committeeHotCred, _) <- electBasicCommittee
(committeeHotCred :| _) <- registerInitialCommittee
(drepKh, _, _) <- setupSingleDRep 1_000_000
treasuryStart <- getsNES $ nesEsL . esAccountStateL . asTreasuryL
rewardAccount <- registerRewardAccount
govPolicy <- getGovPolicy
Expand All @@ -267,7 +280,7 @@ treasuryWithdrawalExpectation extraWithdrawals = do
submitGovActions $
TreasuryWithdrawals (Map.singleton rewardAccount withdrawalAmount) govPolicy
NE.:| extraWithdrawals
submitYesVote_ (DRepVoter dRepCred) govActionId
submitYesVote_ (DRepVoter (KeyHashObj drepKh)) govActionId
submitYesVote_ (CommitteeVoter committeeHotCred) govActionId
passEpoch -- 1st epoch crossing starts DRep pulser
impAnn "Withdrawal should not be received yet" $
Expand Down Expand Up @@ -328,7 +341,8 @@ eventsSpec ::
eventsSpec = describe "Events" $ do
describe "emits event" $ do
it "GovInfoEvent" $ do
(drepCred, ccCred, _) <- electBasicCommittee
(ccCred :| _) <- registerInitialCommittee
(drepKh, _, _) <- setupSingleDRep 1_000_000
let actionLifetime = 10
modifyPParams $ \pp ->
pp
Expand Down Expand Up @@ -367,7 +381,7 @@ eventsSpec = describe "Events" $ do
]
replicateM_ (fromIntegral actionLifetime) passEpochWithNoDroppedActions
logAcceptedRatio proposalA
submitYesVote_ (DRepVoter drepCred) proposalA
submitYesVote_ (DRepVoter (KeyHashObj drepKh)) proposalA
submitYesVote_ (CommitteeVoter ccCred) proposalA
gasA <- getGovActionState proposalA
gasB <- getGovActionState proposalB
Expand Down

0 comments on commit 8f31f71

Please sign in to comment.