Skip to content

Commit 6c24032

Browse files
authored
Merge pull request #5316 from IntersectMBO/td/store-delegs-in-stakepoolstate
Store delegators in pool state
2 parents 04632c6 + 5197446 commit 6c24032

File tree

31 files changed

+568
-214
lines changed

31 files changed

+568
-214
lines changed

eras/conway/impl/CHANGELOG.md

Lines changed: 2 additions & 0 deletions
Original file line numberDiff line numberDiff line change
@@ -2,6 +2,8 @@
22

33
## 1.21.0.0
44

5+
* Add `unDelegReDelegDRep` to `VState` module
6+
* Expose `conwayRegisterInitialAccounts`
57
* Add `TxLevel` argument to `Tx` and `TxBody`
68
* Add `HasEraTxLevel` instances for `Tx` and `TxBody`
79
* Add `EraTxLevel` instance

eras/conway/impl/src/Cardano/Ledger/Conway/Rules/Deleg.hs

Lines changed: 32 additions & 48 deletions
Original file line numberDiff line numberDiff line change
@@ -54,6 +54,7 @@ import Cardano.Ledger.Conway.TxCert (
5454
Delegatee (DelegStake, DelegStakeVote, DelegVote),
5555
)
5656
import Cardano.Ledger.Credential (Credential)
57+
import Cardano.Ledger.DRep
5758
import Control.DeepSeq (NFData)
5859
import Control.Monad (forM_, guard, unless)
5960
import Control.State.Transition (
@@ -66,6 +67,7 @@ import Control.State.Transition (
6667
State,
6768
TRC (TRC),
6869
TransitionRule,
70+
failBecause,
6971
failOnJust,
7072
judgmentContext,
7173
transitionRules,
@@ -200,10 +202,6 @@ conwayDelegTransition = do
200202
else IncorrectDepositDELEG deposit
201203
checkStakeKeyNotRegistered stakeCred =
202204
not (isAccountRegistered stakeCred accounts) ?! StakeKeyRegisteredDELEG stakeCred
203-
checkStakeKeyIsRegistered stakeCred = do
204-
let mAccountState = lookupAccountState stakeCred accounts
205-
isJust mAccountState ?! StakeKeyNotRegisteredDELEG stakeCred
206-
pure $ mAccountState >>= accountStateDelegatee
207205
checkStakeDelegateeRegistered =
208206
let checkPoolRegistered targetPool =
209207
targetPool `Map.member` pools ?! DelegateeStakePoolNotRegisteredDELEG targetPool
@@ -229,7 +227,6 @@ conwayDelegTransition = do
229227
%~ registerConwayAccount stakeCred ppKeyDepositCompact Nothing
230228
ConwayUnRegCert stakeCred sMayRefund -> do
231229
let (mAccountState, newAccounts) = unregisterConwayAccount stakeCred accounts
232-
mCurDelegatee = mAccountState >>= accountStateDelegatee
233230
checkInvalidRefund = do
234231
SJust suppliedRefund <- Just sMayRefund
235232
-- we don't want to report invalid refund when stake credential is not registered:
@@ -252,16 +249,23 @@ conwayDelegTransition = do
252249
guard (balanceCompact /= mempty)
253250
Just $ fromCompact balanceCompact
254251
failOnJust checkInvalidRefund id
255-
isJust mAccountState ?! StakeKeyNotRegisteredDELEG stakeCred
256252
failOnJust checkStakeKeyHasZeroRewardBalance StakeKeyHasNonZeroRewardAccountBalanceDELEG
257-
pure $
258-
processDRepUnDelegation stakeCred mCurDelegatee $
259-
certState & certDStateL . accountsL .~ newAccounts
253+
case mAccountState of
254+
Nothing -> do
255+
failBecause $ StakeKeyNotRegisteredDELEG stakeCred
256+
pure certState
257+
Just accountState ->
258+
pure $
259+
certState
260+
& certDStateL . accountsL .~ newAccounts
261+
& certVStateL %~ unDelegReDelegDRep stakeCred accountState Nothing
262+
& certPStateL %~ unDelegReDelegStakePool stakeCred accountState Nothing
260263
ConwayDelegCert stakeCred delegatee -> do
261-
mCurDelegatee <- checkStakeKeyIsRegistered stakeCred
264+
let mAccountState = lookupAccountState stakeCred accounts
265+
isJust mAccountState ?! StakeKeyNotRegisteredDELEG stakeCred
262266
checkStakeDelegateeRegistered delegatee
263267
pure $
264-
processDelegationInternal (pvMajor pv < natVersion @10) stakeCred mCurDelegatee delegatee certState
268+
processDelegationInternal (pvMajor pv < natVersion @10) stakeCred mAccountState delegatee certState
265269
ConwayRegDelegCert stakeCred delegatee deposit -> do
266270
checkDepositAgainstPParams deposit
267271
checkStakeKeyNotRegistered stakeCred
@@ -284,9 +288,8 @@ processDelegation ::
284288
CertState era
285289
processDelegation stakeCred newDelegatee !certState = certState'
286290
where
287-
!certState' = processDelegationInternal False stakeCred mCurDelegatee newDelegatee certState
291+
!certState' = processDelegationInternal False stakeCred mAccountState newDelegatee certState
288292
mAccountState = Map.lookup stakeCred (certState ^. certDStateL . accountsL . accountsMapL)
289-
mCurDelegatee = mAccountState >>= accountStateDelegatee
290293

291294
-- | Same as `processDelegation`, except it expects the current delegation supplied as an
292295
-- argument, because in ledger rules we already have it readily available.
@@ -296,13 +299,13 @@ processDelegationInternal ::
296299
Bool ->
297300
-- | Delegator
298301
Credential 'Staking ->
299-
-- | Current delegatee for the above stake credential that needs to be cleaned up.
300-
Maybe Delegatee ->
302+
-- | Account state for the above stake credential
303+
Maybe (AccountState era) ->
301304
-- | New delegatee
302305
Delegatee ->
303306
CertState era ->
304307
CertState era
305-
processDelegationInternal preserveIncorrectDelegation stakeCred mCurDelegatee newDelegatee =
308+
processDelegationInternal preserveIncorrectDelegation stakeCred mAccountState newDelegatee =
306309
case newDelegatee of
307310
DelegStake sPool -> delegStake sPool
308311
DelegVote dRep -> delegVote dRep
@@ -312,37 +315,18 @@ processDelegationInternal preserveIncorrectDelegation stakeCred mCurDelegatee ne
312315
cState
313316
& certDStateL . accountsL
314317
%~ adjustAccountState (stakePoolDelegationAccountStateL ?~ stakePool) stakeCred
318+
& maybe
319+
(certPStateL . psStakePoolsL %~ Map.adjust (spsDelegatorsL %~ Set.insert stakeCred) stakePool)
320+
(\accountState -> certPStateL %~ unDelegReDelegStakePool stakeCred accountState (Just stakePool))
321+
mAccountState
315322
delegVote dRep cState =
316-
let cState' =
317-
processDRepUnDelegation stakeCred mCurDelegatee cState
318-
& certDStateL . accountsL
319-
%~ adjustAccountState (dRepDelegationAccountStateL ?~ dRep) stakeCred
320-
dReps
321-
| preserveIncorrectDelegation = cState ^. certVStateL . vsDRepsL
322-
| otherwise = cState' ^. certVStateL . vsDRepsL
323-
in case dRep of
324-
DRepCredential targetDRep
325-
| Just dRepState <- Map.lookup targetDRep dReps ->
326-
let dRepState' = dRepState {drepDelegs = Set.insert stakeCred (drepDelegs dRepState)}
327-
in cState' & certVStateL . vsDRepsL .~ Map.insert targetDRep dRepState' dReps
328-
_ -> cState'
329-
330-
processDRepUnDelegation ::
331-
ConwayEraCertState era =>
332-
Credential 'Staking ->
333-
Maybe Delegatee ->
334-
CertState era ->
335-
CertState era
336-
processDRepUnDelegation _ Nothing cState = cState
337-
processDRepUnDelegation stakeCred (Just delegatee) cState =
338-
case delegatee of
339-
DelegStake _ -> cState
340-
DelegVote dRep -> cState & certVStateL .~ unDelegVote (cState ^. certVStateL) dRep
341-
DelegStakeVote _sPool dRep -> cState & certVStateL .~ unDelegVote (cState ^. certVStateL) dRep
342-
where
343-
unDelegVote vState = \case
323+
cState
324+
& certDStateL . accountsL %~ adjustAccountState (dRepDelegationAccountStateL ?~ dRep) stakeCred
325+
& maybe
326+
(certVStateL %~ insertDRepDeleg dRep)
327+
(\accountState -> certVStateL %~ unDelegReDelegDRep stakeCred accountState (Just dRep))
328+
(guard (not preserveIncorrectDelegation) >> mAccountState)
329+
insertDRepDeleg dRep = case dRep of
344330
DRepCredential dRepCred ->
345-
let removeDelegation dRepState =
346-
dRepState {drepDelegs = Set.delete stakeCred (drepDelegs dRepState)}
347-
in vState & vsDRepsL %~ Map.adjust removeDelegation dRepCred
348-
_ -> vState
331+
vsDRepsL %~ Map.adjust (drepDelegsL %~ Set.insert stakeCred) dRepCred
332+
_ -> id

eras/conway/impl/src/Cardano/Ledger/Conway/State/VState.hs

Lines changed: 34 additions & 1 deletion
Original file line numberDiff line numberDiff line change
@@ -17,6 +17,7 @@ module Cardano.Ledger.Conway.State.VState (
1717
vsNumDormantEpochsL,
1818
vsActualDRepExpiry,
1919
lookupDepositVState,
20+
unDelegReDelegDRep,
2021
) where
2122

2223
import Cardano.Ledger.BaseTypes (KeyValuePairs (..), ToKeyValuePairs (..), binOpEpochNo)
@@ -33,17 +34,21 @@ import Cardano.Ledger.Binary (
3334
import Cardano.Ledger.Binary.Coders (Decode (..), Encode (..), decode, encode, (!>), (<!))
3435
import Cardano.Ledger.Coin (Coin (..))
3536
import Cardano.Ledger.Compactible (Compactible (..))
37+
import Cardano.Ledger.Conway.State.Account
3638
import Cardano.Ledger.Core
3739
import Cardano.Ledger.Credential (Credential (..))
40+
import Cardano.Ledger.DRep (drepDelegsL)
3841
import Cardano.Ledger.Shelley.State
3942
import Cardano.Ledger.Slot (EpochNo (..))
4043
import Control.DeepSeq (NFData (..))
4144
import Data.Aeson (ToJSON (..), (.=))
4245
import Data.Default (Default (def))
4346
import Data.Map.Strict (Map)
4447
import qualified Data.Map.Strict as Map
48+
import Data.Maybe (fromMaybe)
49+
import qualified Data.Set as Set
4550
import GHC.Generics (Generic)
46-
import Lens.Micro (Lens', lens, (^.))
51+
import Lens.Micro
4752
import NoThunks.Class (NoThunks (..))
4853

4954
-- | The state that tracks the voting entities (DReps and Constitutional Committee
@@ -109,6 +114,34 @@ instance ToKeyValuePairs (VState era) where
109114
, "numDormantEpochs" .= vsNumDormantEpochs
110115
]
111116

117+
-- | Reverses DRep delegation.
118+
-- To be called when a stake credential is unregistered or its delegation target changes.
119+
-- If the new delegation matches the previous one, this is a noop.
120+
unDelegReDelegDRep ::
121+
ConwayEraAccounts era =>
122+
Credential 'Staking ->
123+
-- | Account that is losing its current delegation and/or acquiring a new one
124+
AccountState era ->
125+
-- | Potential new delegation. In case when stake credential unregisters this must be `Nothing`.
126+
Maybe DRep ->
127+
VState era ->
128+
VState era
129+
unDelegReDelegDRep stakeCred accountState mNewDRep =
130+
fromMaybe (vsDRepsL %~ addNewDelegation) $ do
131+
dRep@(DRepCredential dRepCred) <- accountState ^. dRepDelegationAccountStateL
132+
pure $
133+
-- There is no need to update set of delegations if delegation is unchanged
134+
if Just dRep == mNewDRep
135+
then id
136+
else
137+
vsDRepsL %~ addNewDelegation . Map.adjust (drepDelegsL %~ Set.delete stakeCred) dRepCred
138+
where
139+
addNewDelegation =
140+
case mNewDRep of
141+
Just (DRepCredential dRepCred) ->
142+
Map.adjust (drepDelegsL %~ Set.insert stakeCred) dRepCred
143+
_ -> id
144+
112145
vsDRepsL :: Lens' (VState era) (Map (Credential 'DRepRole) DRepState)
113146
vsDRepsL = lens vsDReps (\vs u -> vs {vsDReps = u})
114147

eras/conway/impl/src/Cardano/Ledger/Conway/Transition.hs

Lines changed: 12 additions & 4 deletions
Original file line numberDiff line numberDiff line change
@@ -16,6 +16,7 @@ module Cardano.Ledger.Conway.Transition (
1616
TransitionConfig (..),
1717
toConwayTransitionConfigPairs,
1818
registerDRepsThenDelegs,
19+
conwayRegisterInitialAccounts,
1920
conwayRegisterInitialFundsThenStaking,
2021
) where
2122

@@ -44,6 +45,7 @@ import Data.Aeson (KeyValue (..))
4445
import Data.ListMap (ListMap)
4546
import qualified Data.ListMap as ListMap
4647
import qualified Data.Map.Strict as Map
48+
import qualified Data.Set as Set
4749
import GHC.Generics
4850
import GHC.Stack
4951
import Lens.Micro
@@ -127,14 +129,20 @@ conwayRegisterInitialAccounts ::
127129
NewEpochState era
128130
conwayRegisterInitialAccounts ShelleyGenesisStaking {sgsStake} nes =
129131
nes
130-
& nesEsL . esLStateL . lsCertStateL . certDStateL . accountsL %~ \initAccounts ->
131-
foldr registerAndDelegate initAccounts $ ListMap.toList sgsStake
132+
& nesEsL . esLStateL . lsCertStateL . certDStateL . accountsL .~ updatedAccounts
133+
& nesEsL . esLStateL . lsCertStateL . certPStateL . psStakePoolsL .~ updatedStakePoolStates
132134
where
133135
stakePools = nes ^. nesEsL . esLStateL . lsCertStateL . certPStateL . psStakePoolsL
136+
initialAccounts = nes ^. nesEsL . esLStateL . lsCertStateL . certDStateL . accountsL
134137
deposit = compactCoinOrError $ nes ^. nesEsL . curPParamsEpochStateL . ppKeyDepositL
135-
registerAndDelegate (stakeKeyHash, stakePool) !accounts
138+
139+
!(!updatedAccounts, !updatedStakePoolStates) =
140+
foldr registerAndDelegate (initialAccounts, stakePools) (ListMap.toList sgsStake)
141+
registerAndDelegate (stakeKeyHash, stakePool) (!accounts, !stakePoolMap)
136142
| stakePool `Map.member` stakePools =
137-
registerConwayAccount (KeyHashObj stakeKeyHash) deposit (Just (DelegStake stakePool)) accounts
143+
( (registerConwayAccount (KeyHashObj stakeKeyHash) deposit (Just (DelegStake stakePool)) accounts)
144+
, Map.adjust (spsDelegatorsL %~ Set.insert (KeyHashObj stakeKeyHash)) stakePool stakePoolMap
145+
)
138146
| otherwise =
139147
error $
140148
"Invariant of a delegation of "

0 commit comments

Comments
 (0)