Skip to content

Commit

Permalink
Extend ValidatorAdd with a suspended field (#1302)
Browse files Browse the repository at this point in the history
Closes #1246 . Validators can now be added already suspended. We also discovered a bug in this PR: `updateSuspend` needs to be run before `updateCapital` in `newUpdateValidator`. If `updateCapital` sets the capital to zero, the validator is removed and a call to `updateSuspend` would error afterwards.
  • Loading branch information
drsk0 authored Jan 9, 2025
1 parent 44c84f2 commit 49088c7
Show file tree
Hide file tree
Showing 8 changed files with 52 additions and 24 deletions.
1 change: 1 addition & 0 deletions CHANGELOG.md
Original file line number Diff line number Diff line change
Expand Up @@ -6,6 +6,7 @@
- Automatically suspend validators from the consensus that missed too many
rounds in the previous payday.
- Add support for suspend/resume to validator configuration updates.
- Add support to add a validator in a suspended state.
- Validators that are suspended are paused from participating in the consensus algorithm.
- Add suspension info to `BakerPoolStatus` / `CurrentPaydayBakerPoolStatus` query results.
- Add `GetConsensusDetailedStatus` gRPC endpoint for getting detailed information on the status
Expand Down
5 changes: 3 additions & 2 deletions concordium-consensus/src/Concordium/GlobalState/BakerInfo.hs
Original file line number Diff line number Diff line change
Expand Up @@ -219,8 +219,9 @@ data ValidatorAdd = ValidatorAdd
-- | The metadata URL for the validator.
vaMetadataURL :: !UrlText,
-- | The commission rates for the validator.
vaCommissionRates :: !CommissionRates
-- TODO (drsk) Github issue #1246. Support suspend/resume for ValidatorAdd.
vaCommissionRates :: !CommissionRates,
-- | Whether the validator should be added as suspended.
vaSuspended :: !Bool
}
deriving (Eq, Show)

Expand Down
15 changes: 8 additions & 7 deletions concordium-consensus/src/Concordium/GlobalState/BlockState.hs
Original file line number Diff line number Diff line change
Expand Up @@ -1084,8 +1084,15 @@ class (BlockStateQuery m) => BlockStateOperations m where
-- (2) update the account's finalization reward commission rate to the the supplied value @frc@;
--
-- (3) append @BakerConfigureFinalizationRewardCommission frc@ to @events@.

-- 7. (>= P8) If the suspended/resumed flag is set:

-- (1) Suspend/resume the validator according to the flag.

-- (2) Append @BakerConfigureSuspended@ or @BakerConfigureResumed@ accordingly to @events@.
--
--
-- 7. If the capital is supplied: if there is a pending change to the baker's capital, return
-- 8. If the capital is supplied: if there is a pending change to the baker's capital, return
-- @VCFChangePending@; otherwise:
--
-- * if the capital is 0
Expand Down Expand Up @@ -1121,12 +1128,6 @@ class (BlockStateQuery m) => BlockStateOperations m where
-- is (preferentially) reactivated from the inactive stake, updating the global indices
-- accordingly.
--
-- 8. (>= P8) If the suspended/resumed flag is set:

-- (1) Suspend/resume the validator according to the flag.

-- (2) Append @BakerConfigureSuspended@ or @BakerConfigureResumed@ accordingly to @events@.
--
-- 9. Return @events@ with the updated block state.
bsoUpdateValidator ::
(PVSupportsDelegation (MPV m)) =>
Expand Down
Original file line number Diff line number Diff line change
Expand Up @@ -1632,7 +1632,7 @@ newAddValidator pbs ai va@ValidatorAdd{..} = do
BaseAccounts.BakerInfoExV1
{ _bieBakerPoolInfo = poolInfo,
_bieBakerInfo = bakerInfo,
_bieIsSuspended = conditionally hasValidatorSuspension False
_bieIsSuspended = conditionally hasValidatorSuspension vaSuspended
}
-- The precondition guaranties that the account exists
acc <- fromJust <$> Accounts.indexedAccount ai (bspAccounts bsp)
Expand Down Expand Up @@ -1783,7 +1783,13 @@ updateValidatorChecks bsp baker ValidatorUpdate{..} = do
--
-- (3) append @BakerConfigureFinalizationRewardCommission frc@ to @events@.
--
-- 8. If the capital is supplied: if there is a pending change to the baker's capital, return
-- 8. (>= P8) If the suspended/resumed flag is set:

-- (1) Suspend/resume the validator according to the flag.

-- (2) Append @BakerConfigureSuspended@ or @BakerConfigureResumed@ accordingly to @events@.
--
-- 9. If the capital is supplied: if there is a pending change to the baker's capital, return
-- @VCFChangePending@; otherwise:
--
-- * if the capital is 0
Expand Down Expand Up @@ -1820,12 +1826,6 @@ updateValidatorChecks bsp baker ValidatorUpdate{..} = do
-- index by adding the difference between the new and old capital) and append
-- @BakerConfigureStakeIncreased capital@ to @events@.

-- 9. (>= P8) If the suspended/resumed flag is set:

-- (1) Suspend/resume the validator according to the flag.

-- (2) Append @BakerConfigureSuspended@ or @BakerConfigureResumed@ accordingly to @events@.
--
-- 10. Return @events@ with the updated block state.
newUpdateValidator ::
forall pv m.
Expand Down Expand Up @@ -1853,8 +1853,11 @@ newUpdateValidator pbs curTimestamp ai vu@ValidatorUpdate{..} = do
updateKeys existingBaker (bsp, acc)
>>= updateRestakeEarnings
>>= updatePoolInfo existingBaker
>>= updateCapital existingBaker
-- NOTE: updateSuspend needs to be executed before updateCapital.
-- Because if we update the stake to 0, the validator gets
-- removed. After this, a call to updateSuspend will error.
>>= updateSuspend
>>= updateCapital existingBaker
newAccounts <- Accounts.setAccountAtIndex ai newAcc (bspAccounts newBSP)
return newBSP{bspAccounts = newAccounts}
(events,) <$> storePBS pbs newBSP
Expand Down
1 change: 1 addition & 0 deletions concordium-consensus/src/Concordium/Scheduler.hs
Original file line number Diff line number Diff line change
Expand Up @@ -2114,6 +2114,7 @@ handleConfigureBaker
let vaCommissionRates = CommissionRates{..}
vaOpenForDelegation <- cbOpenForDelegation
vaMetadataURL <- cbMetadataURL
let vaSuspended = fromMaybe False cbSuspend
return
CBCAdd
{ cbcRemoveDelegator = removeDelegator,
Expand Down
Original file line number Diff line number Diff line change
Expand Up @@ -531,3 +531,6 @@ tests = parallel $ describe "Configure delegator" $ do
describe "P7" $ do
it "bsoAddDelegator" $ testAddDelegator SP7
it "bsoUpdateDelegator" $ testUpdateDelegator SP7
describe "P8" $ do
it "bsoAddDelegator" $ testAddDelegator SP8
it "bsoUpdateDelegator" $ testUpdateDelegator SP8
Original file line number Diff line number Diff line change
Expand Up @@ -105,10 +105,12 @@ testAddValidatorAllCases ::
Spec
testAddValidatorAllCases spv = describe "bsoAddValidator" $ do
forM_ validatorConditions $ \vc -> do
it (show vc) $ runTest False vc
when supportCooldown $ it (show vc <> " with cooldown") $ runTest True vc
it (show vc) $ runTest False False vc
when supportCooldown $ it (show vc <> " with cooldown") $ runTest True False vc
when supportSuspension $ it (show vc <> " with suspended validator") $ runTest True True vc
where
supportCooldown = supportsFlexibleCooldown $ accountVersionFor $ demoteProtocolVersion (protocolVersion @pv)
supportSuspension = supportsValidatorSuspension $ accountVersionFor $ demoteProtocolVersion (protocolVersion @pv)
minEquity = 1_000_000_000
chainParams =
DummyData.dummyChainParameters @(ChainParametersVersionFor pv)
Expand All @@ -129,7 +131,7 @@ testAddValidatorAllCases spv = describe "bsoAddValidator" $ do
DummyData.dummyArs
(withIsAuthorizationsVersionForPV spv DummyData.dummyKeyCollection)
chainParams
runTest withCooldown ValidatorConditions{..} = runTestBlockState @pv $ do
runTest withCooldown suspended ValidatorConditions{..} = runTestBlockState @pv $ do
let va =
ValidatorAdd
{ vaKeys = if vcAggregationKeyDuplicate then badKeys else goodKeys,
Expand All @@ -142,7 +144,8 @@ testAddValidatorAllCases spv = describe "bsoAddValidator" $ do
{ _finalizationCommission = makeAmountFraction $ if vcFinalizationRewardNotInRange then 100 else 300,
_bakingCommission = makeAmountFraction $ if vcBakingRewardNotInRange then 100 else 500,
_transactionCommission = makeAmountFraction $ if vcTransactionFeeNotInRange then 300 else 100
}
},
vaSuspended = suspended
}
initialAccounts <- mapM makeDummyAccount (addValidatorTestAccounts withCooldown)
initialBS <- mkInitialState initialAccounts
Expand Down Expand Up @@ -189,7 +192,7 @@ testAddValidatorAllCases spv = describe "bsoAddValidator" $ do
_poolMetadataUrl = vaMetadataURL va,
_poolCommissionRates = vaCommissionRates va
},
_bieIsSuspended = conditionally (sSupportsValidatorSuspension (accountVersion @(AccountVersionFor pv))) False
_bieIsSuspended = conditionally (sSupportsValidatorSuspension (accountVersion @(AccountVersionFor pv))) suspended
}
}
bkr <- getAccountBaker (fromJust acc)
Expand Down Expand Up @@ -488,6 +491,11 @@ runUpdateValidatorTest spv commissionRanges ValidatorUpdateConfig{vucValidatorUp
forM_ (vuTransactionFeeCommission vu) $ \fee -> tell [BakerConfigureTransactionFeeCommission fee]
forM_ (vuBakingRewardCommission vu) $ \fee -> tell [BakerConfigureBakingRewardCommission fee]
forM_ (vuFinalizationRewardCommission vu) $ \fee -> tell [BakerConfigureFinalizationRewardCommission fee]
forM_ (vuSuspend vu) $ \suspended ->
tell
[ if suspended then BakerConfigureSuspended else BakerConfigureResumed
| STrue <- [hasValidatorSuspension]
]
forM_ (vuCapital vu) $ \capital ->
tell $
if capital >= initialStakedAmount
Expand Down Expand Up @@ -526,6 +534,9 @@ runUpdateValidatorTest spv commissionRanges ValidatorUpdateConfig{vucValidatorUp
.~ (if newCapital == 0 then RemoveStake else ReduceStake newCapital)
(PendingChangeEffectiveV1 (24 * 60 * 60 * 1000 + 1000))
| otherwise = stakedAmount .~ newCapital
let updateSuspended suspend
| STrue <- hasValidatorSuspension = accountBakerInfo . bieIsSuspended .~ suspend
| otherwise = id
let expectedAccountBaker
| STrue <- flexibleCooldown, vuCapital vu == Just 0 = Nothing
| otherwise =
Expand All @@ -546,10 +557,12 @@ runUpdateValidatorTest spv commissionRanges ValidatorUpdateConfig{vucValidatorUp
& maybe id (poolCommissionRates . finalizationCommission .~) (vuFinalizationRewardCommission vu)
& maybe id (poolCommissionRates . bakingCommission .~) (vuBakingRewardCommission vu)
& maybe id (poolCommissionRates . transactionCommission .~) (vuTransactionFeeCommission vu)
& maybe id updateSuspended (vuSuspend vu)
actualAccountBaker <- getAccountBaker acc0
liftIO $ actualAccountBaker `shouldBe` expectedAccountBaker
where
flexibleCooldown = sSupportsFlexibleCooldown (accountVersion @(AccountVersionFor pv))
hasValidatorSuspension = sSupportsValidatorSuspension (accountVersion @(AccountVersionFor pv))
minEquity = 1_000_000_000
chainParams =
DummyData.dummyChainParameters @(ChainParametersVersionFor pv)
Expand Down Expand Up @@ -577,3 +590,7 @@ tests lvl = parallel $ describe "Validator" $ do
testAddValidatorAllCases SP7
testUpdateValidator SP7 (lvl > 1)
testUpdateValidatorOverlappingCommissions SP7
describe "P8" $ do
testAddValidatorAllCases SP8
testUpdateValidator SP8 (lvl > 1)
testUpdateValidatorOverlappingCommissions SP8
Original file line number Diff line number Diff line change
Expand Up @@ -143,7 +143,8 @@ addBakerWith am (bs, ai) = do
{ _transactionCommission = makeAmountFraction 0,
_finalizationCommission = makeAmountFraction 0,
_bakingCommission = makeAmountFraction 0
}
},
vaSuspended = False
}
res <- bsoAddValidator bs ai conf
return ((,ai) <$> res)
Expand Down

0 comments on commit 49088c7

Please sign in to comment.