Skip to content

Commit 2af09b3

Browse files
committed
makeSnapShot and individual versions of updateILC for particular changes.
1 parent f30072d commit 2af09b3

File tree

2 files changed

+125
-123
lines changed

2 files changed

+125
-123
lines changed

libs/cardano-ledger-core/src/Cardano/Ledger/UMapCompact.hs

+6-2
Original file line numberDiff line numberDiff line change
@@ -307,8 +307,12 @@ instance Show (Trip c) where
307307

308308
-- =====================================================
309309

310-
-- | A unified map represents 4 Maps with domain @(Credential 'Staking c)@ for
311-
-- keys and one more in the inverse direction with @Ptr@ for keys and @(Credential 'Staking c)@ for values.
310+
-- | A unified map represents 4 Maps with domain @(Credential 'Staking c)@
311+
-- 1) Map (Credential 'Staking c) RDPair -- (RDPair rewardCoin depositCoin)
312+
-- 2) Map (Credential 'Staking c) (Set Ptr)
313+
-- 3) Map (Credential 'Staking c) (StrictMaybe (KeyHash 'StakePool c))
314+
-- 4) Map (Credential 'Staking c) (StrictMaybe (KeyHash 'Voting c))
315+
-- and one more map in the inverse direction with @Ptr@ for keys and @(Credential 'Staking c)@ for values.
312316
data UMap c = UMap !(Map (Credential 'Staking c) (Trip c)) !(Map Ptr (Credential 'Staking c))
313317
deriving (Show, Eq, Generic, NoThunks, NFData)
314318

libs/cardano-ledger-test/src/Test/Cardano/Ledger/Incremental.hs

+119-121
Original file line numberDiff line numberDiff line change
@@ -24,11 +24,11 @@ module Test.Cardano.Ledger.Incremental where
2424

2525
import Cardano.Ledger.Address (Addr (..))
2626
import Cardano.Ledger.Coin (Coin (..), Diff (DiffCoin))
27-
import Cardano.Ledger.Core (EraTxOut (..), TxOut, coinTxOutL)
27+
import Cardano.Ledger.Core (EraTxOut (..), TxOut, coinTxOutL, EraPParams(..),PParams(..),ppProtocolVersionL)
2828
import Cardano.Ledger.Credential (Credential (..), Ptr (..), StakeReference (..))
2929
import Cardano.Ledger.Era (Era (..))
3030
import Cardano.Ledger.Keys (KeyHash, KeyRole (..))
31-
import Cardano.Ledger.Shelley.LedgerState (LedgerState (..)) -- DPState (..), DState (..), PState (..), UTxOState (..))
31+
import Cardano.Ledger.Shelley.LedgerState (LedgerState (..),DState (..),DPState (..),PState (..),delegations) -- UTxOState (..))
3232
import Cardano.Ledger.TxIn (TxIn (..))
3333
import Cardano.Ledger.UMapCompact (MapLike (..), View (..))
3434
import qualified Cardano.Ledger.UMapCompact as UM
@@ -55,6 +55,10 @@ import Test.Cardano.Ledger.Core.Arbitrary ()
5555
import Test.Cardano.Ledger.Generic.Proof (ShelleyEra, Standard)
5656
import Test.Tasty
5757
import Test.Tasty.QuickCheck hiding (Fixed, total)
58+
import Cardano.Ledger.EpochBoundary (SnapShot (..),Stake(..))
59+
import qualified Data.VMap as VMap
60+
import qualified Cardano.Ledger.Shelley.HardForks as HardForks
61+
import Control.Exception (assert)
5862

5963
type TT = ShelleyEra Standard
6064

@@ -104,107 +108,8 @@ try cred x =
104108
then trace ("cred=" ++ show cred ++ " " ++ show x) x
105109
else x
106110

107-
{-
108-
changeDm ::
109-
(Show cred, Ord cred, Ord drep, Show drep) =>
110-
Map cred Coin ->
111-
Map cred drep ->
112-
Map drep (MonoidRngD (Diff Coin)) ->
113-
cred ->
114-
MonoidRngD (Diff Coin) ->
115-
Map drep (MonoidRngD (Diff Coin))
116-
changeDm m n ans cred dcoin = case try cred (dcoin, Map.lookup cred m, Map.lookup cred n) of
117-
(Del, Nothing, Nothing) -> ans
118-
(Del, Nothing, Just _) -> ans
119-
(Del, Just _, Nothing) -> ans
120-
(Del, Just (Coin c2), Just r2) -> insertC r2 (Comb (DiffCoin (-c2))) ans
121-
(Write _, Nothing, Nothing) -> ans
122-
(Write c1, Nothing, Just r2) -> insertC r2 (Comb c1) ans
123-
(Write _, Just _, Nothing) -> ans
124-
(Write (DiffCoin c1), Just (Coin c2), Just r2) ->
125-
insertC r2 (Comb (DiffCoin (c1 - c2))) ans
126-
(Comb _, Nothing, Nothing) -> ans
127-
(Comb c1, Nothing, Just r2) -> insertC r2 (Comb c1) ans
128-
(Comb _, Just _, Nothing) -> ans
129-
(Comb (DiffCoin c1), Just _, Just r2) -> insertC r2 (Comb (DiffCoin c1)) ans
130-
131-
changeDmDn ::
132-
(Show cred, Ord cred, Show drep, Ord drep) =>
133-
Map cred Coin ->
134-
Map cred drep ->
135-
Map drep (MonoidRngD (Diff Coin)) ->
136-
cred ->
137-
(MonoidRngD (Diff Coin), BinaryRngD drep) ->
138-
Map drep (MonoidRngD (Diff Coin))
139-
changeDmDn m n ans cred (dcoin, drep) = case try cred (dcoin, drep, Map.lookup cred m, Map.lookup cred n) of
140-
(Del, Omit, Nothing, Nothing) -> ans
141-
(Del, Omit, Nothing, Just _) -> ans
142-
(Del, Omit, Just _, Nothing) -> ans
143-
(Del, Omit, Just (Coin c2), Just r2) ->
144-
insertC r2 (Comb (DiffCoin (-c2))) ans
145-
(Del, Edit _, Nothing, Nothing) -> ans
146-
(Del, Edit _, Nothing, Just _) -> ans
147-
(Del, Edit _, Just _, Nothing) -> ans
148-
(Del, Edit _, Just (Coin c2), Just r2) ->
149-
insertC r2 (Comb (DiffCoin (-c2))) ans
150-
(Write _, Omit, Nothing, Nothing) -> ans
151-
(Write _, Omit, Nothing, Just _) -> ans
152-
(Write _, Omit, Just _, Nothing) -> ans
153-
(Write _, Omit, Just (Coin c2), Just r2) ->
154-
insertC r2 (Comb (DiffCoin (-c2))) ans
155-
(Write c1, Edit r1, Nothing, Nothing) ->
156-
insertC r1 (Comb c1) ans
157-
(Write c1, Edit r1, Nothing, Just _) ->
158-
insertC r1 (Comb c1) ans
159-
(Write c1, Edit r1, Just _, Nothing) -> insertC r1 (Comb c1) ans
160-
(Write c1, Edit r1, Just (Coin c2), Just r2) ->
161-
insertC r1 (Comb c1) (insertC r2 (Comb (DiffCoin (-c2))) ans)
162-
(Comb _, Omit, Nothing, Nothing) -> ans
163-
(Comb _, Omit, Nothing, Just _) -> ans
164-
(Comb _, Omit, Just _, Nothing) -> ans
165-
(Comb _, Omit, Just (Coin c2), Just r2) ->
166-
insertC r2 (Comb (DiffCoin (-c2))) ans
167-
(Comb c1, Edit r1, Nothing, Nothing) ->
168-
insertC r1 (Comb c1) ans
169-
(Comb c1, Edit r1, Nothing, Just _) -> insertC r1 (Comb c1) ans
170-
(Comb (DiffCoin c1), Edit r1, Just (Coin c2), Nothing) ->
171-
insertC r1 (Comb (DiffCoin (c1 + c2))) ans
172-
(Comb (DiffCoin c3), Edit r1, Just (Coin c2), Just r2) ->
173-
insertC r1 (Comb (DiffCoin (c3 + c2))) (insertC r2 (Comb (DiffCoin (-c2))) ans)
174-
175-
changeDn ::
176-
(Show cred, Ord cred, Ord drep, Show drep) =>
177-
Map cred Coin ->
178-
Map cred drep ->
179-
Map drep (MonoidRngD (Diff Coin)) ->
180-
cred ->
181-
BinaryRngD drep ->
182-
Map drep (MonoidRngD (Diff Coin))
183-
changeDn m n ans cred dd = case try cred (dd, Map.lookup cred m, Map.lookup cred n) of
184-
(Omit, Nothing, Nothing) -> ans
185-
(Omit, Nothing, Just _) -> ans
186-
(Omit, Just _, Nothing) -> ans
187-
(Omit, Just (Coin c2), Just r2) ->
188-
insertC r2 (Comb (DiffCoin (-c2))) ans
189-
(Edit _, Nothing, Nothing) -> ans
190-
(Edit _, Nothing, Just _) -> ans
191-
(Edit r1, Just (Coin c2), Nothing) ->
192-
insertC r1 (Comb (DiffCoin c2)) ans
193-
(Edit r1, Just (Coin c2), Just r2) ->
194-
insertC r2 (Comb (DiffCoin (-c2))) (insertC r1 (Comb (DiffCoin c2)) ans)
195-
-}
196111
-- ======================================================
197-
198-
{-
199-
-- | A stub type, until we decide what a DRep is.
200-
newtype DRep era = DRep Integer
201-
deriving (Eq, Ord, Show)
202-
203-
deriving newtype instance NFData (DRep era)
204-
205-
instance (Arbitrary (DRep era)) where
206-
arbitrary = DRep <$> resize 5000 arbitrary
207-
-}
112+
208113

209114
instance (Arbitrary (Diff Coin)) where
210115
arbitrary = DiffCoin <$> arbitrary
@@ -495,19 +400,6 @@ computeDRepDistr' ::
495400
computeDRepDistr' = f0'
496401

497402
-- =========================================================================
498-
{-
499-
{ isUtxo :: !(Map (TxIn (EraCrypto era)) (TxOut era))
500-
, isDelegate :: !(Map (Cred era) (Pool era))
501-
, isVoteProxy :: !(Map (Cred era) (DRep era))
502-
-}
503-
504-
data ILCState era = ILCState
505-
{ ilcCredDistr :: !(MonoidMap (Cred era) Coin)
506-
, ilcPtrDistr :: !(MonoidMap Ptr Coin)
507-
, ilcPoolDistr :: !(MonoidMap (Pool era) Coin)
508-
, ilcDRepDistr :: !(MonoidMap (DRep era) Coin)
509-
}
510-
511403
utxoL :: Lens' (LedgerState era) (UTxO era)
512404
utxoL = lsUTxOStateL . utxosUtxoL
513405

@@ -523,8 +415,15 @@ drepL = lsDPStateL . dpsDStateL . dsUnifiedL . umapD
523415
umapD :: Lens' (UM.UMap c) (View c (Credential 'Staking c) (KeyHash 'Voting c))
524416
umapD = lens Dreps (\_umap (Dreps um) -> um)
525417

418+
526419
ilcL :: Lens' (LedgerState era) (ILCState era)
527420
ilcL = lsDPStateL . undefined
421+
data ILCState era = ILCState
422+
{ ilcCredDistr :: !(MonoidMap (Cred era) Coin)
423+
, ilcPtrDistr :: !(MonoidMap Ptr Coin)
424+
, ilcPoolDistr :: !(MonoidMap (Pool era) Coin)
425+
, ilcDRepDistr :: !(MonoidMap (DRep era) Coin)
426+
}
528427

529428
updateILC ::
530429
forall era.
@@ -542,18 +441,60 @@ updateILC dUtxo dPool dDrep ls =
542441
& drepL .~ voteNew
543442
where
544443
UTxO utxo = ls ^. utxoL
545-
del = ls ^. poolL
546-
vote = ls ^. drepL
444+
delegs = ls ^. poolL
445+
votes = ls ^. drepL
547446
(ILCState credDistr ptrDistr poolDistr drepDistr) = ls ^. ilcL
548447
utxoNew = utxo `applyDiff` dUtxo
549-
delNew = del `applyDiff` dPool
550-
voteNew = vote `applyDiff` dDrep
448+
delNew = delegs `applyDiff` dPool
449+
voteNew = votes `applyDiff` dDrep
551450
cdiff :: Diff (MonoidMap (Cred era) Coin)
552451
cdiff = credDistrFromUtxo' utxo dUtxo
553452
cred' = credDistr `applyDiff` cdiff
554453
ptr' = ptrDistr `applyDiff` (ptrDistrFromUtxo' utxo dUtxo)
555-
pool' = poolDistr `applyDiff` (computePoolDistr'2 del dPool cred' cdiff)
556-
drep' = drepDistr `applyDiff` (computeDRepDistr'2 vote dDrep cred' cdiff)
454+
pool' = poolDistr `applyDiff` (computePoolDistr'2 delegs dPool cred' cdiff)
455+
drep' = drepDistr `applyDiff` (computeDRepDistr'2 votes dDrep cred' cdiff)
456+
457+
addStakingDelegation
458+
:: EraTxOut era =>
459+
Credential 'Staking (EraCrypto era)
460+
-> KeyHash 'StakePool (EraCrypto era)
461+
-> LedgerState era
462+
-> LedgerState era
463+
addStakingDelegation cred kh = updateILC (Dn Map.empty) (Dl (Map.singleton cred (Edit kh))) (Dl Map.empty)
464+
465+
removeStakingDelegation
466+
:: EraTxOut era =>
467+
Credential 'Staking (EraCrypto era)
468+
-> LedgerState era
469+
-> LedgerState era
470+
removeStakingDelegation cred = updateILC (Dn Map.empty) (Dl (Map.singleton cred Omit)) (Dl Map.empty)
471+
472+
addVotingProxy
473+
:: EraTxOut era =>
474+
Credential 'Staking (EraCrypto era)
475+
-> KeyHash 'Voting (EraCrypto era)
476+
-> LedgerState era
477+
-> LedgerState era
478+
addVotingProxy cred kh = updateILC (Dn Map.empty) (Dl Map.empty) (Dl (Map.singleton cred (Edit kh)))
479+
480+
removeVotingProxy
481+
:: EraTxOut era =>
482+
Credential 'Staking (EraCrypto era)
483+
-> LedgerState era
484+
-> LedgerState era
485+
removeVotingProxy cred = updateILC (Dn Map.empty) (Dl Map.empty) (Dl (Map.singleton cred Omit))
486+
487+
updateUTxO ::
488+
EraTxOut era =>
489+
UTxO era ->
490+
UTxO era ->
491+
LedgerState era ->
492+
LedgerState era
493+
updateUTxO (UTxO utxoDel) (UTxO utxoAdd) = updateILC (Dn diffs2) (Dl Map.empty) (Dl Map.empty)
494+
where diffs1 = Map.foldlWithKey remove Map.empty utxoDel
495+
remove ans txin _txout = Map.insert txin Omit ans
496+
diffs2 = Map.foldlWithKey add diffs1 utxoAdd
497+
add ans txin txout = Map.insert txin (Edit txout) ans
557498

558499
-- The derivative of computePoolDistr adjusted for the fact that the the first
559500
-- arg is a View, rather than a Map.
@@ -691,3 +632,60 @@ changeDn2 m n ans cred dd = case try cred (dd, lookupLike cred m, lookupLike cre
691632
insertC r1 (Comb (DiffCoin c2)) ans
692633
(Edit r1, Just (Coin c2), Just r2) ->
693634
insertC r2 (Comb (DiffCoin (-c2))) (insertC r1 (Comb (DiffCoin c2)) ans)
635+
636+
-------------------------------------------------------------------
637+
638+
makeSnapShot ::
639+
forall era.
640+
EraPParams era =>
641+
PParams era ->
642+
LedgerState era ->
643+
SnapShot (EraCrypto era)
644+
makeSnapShot pp ledgerState =
645+
SnapShot
646+
(Stake $ VMap.fromMap (UM.compactCoinOrError <$> step2))
647+
delegate
648+
(VMap.fromMap poolParams)
649+
where
650+
dstate = (dpsDState . lsDPState) ledgerState
651+
UM.UMap triplesMap ptrsMap = dsUnified dstate
652+
poolParams = (psStakePoolParams . dpsPState . lsDPState) ledgerState
653+
ILCState (MM credDistr) (MM ptrDistr) _poolDistr _voteDistr = ledgerState ^. ilcL
654+
delegate = UM.viewToVMap (delegations dstate)
655+
ignorePtrs = HardForks.forgoPointerAddressResolution (pp ^. ppProtocolVersionL)
656+
-- pre Conway: (dom activeDelegs ◁ credStake) ∪ (dom activeDelegs ◁ ptrStake)
657+
-- afterwards we forgo ptr resolution: (dom activeDelegs ◁ credStake)
658+
step1 =
659+
if ignorePtrs
660+
then credDistr
661+
else -- Resolve inserts and deletes which were indexed by ptrs, by looking them up
662+
-- in the ptrsMap and combining the result of the lookup with the credDistr.
663+
Map.foldlWithKey' addResolvedPointer credDistr ptrDistr
664+
addResolvedPointer ans ptr coin =
665+
case Map.lookup ptr ptrsMap of
666+
Just cred | VMap.member cred delegate -> Map.insertWith (<>) cred coin ans
667+
_ -> ans
668+
step2 = addRewardsAndCreds triplesMap step1
669+
670+
671+
-- | Aggregate active stake by merging two maps. The rewards map from the
672+
-- UMap, and the computed incremental stake. Only keep the active stake of
673+
-- the rewards. This can be determined by if there is a (SJust deleg) in
674+
-- the Triple. The incemental stake is alway active, since it is recomputed
675+
-- on every change.
676+
addRewardsAndCreds :: Ord k => Map k (UM.Trip c) -> Map k Coin -> Map k Coin
677+
addRewardsAndCreds m1 m2 = assert (Map.valid m) m
678+
where
679+
m =
680+
Map.mergeWithKey
681+
-- How to merge the ranges of the two maps where they have a common key. Below
682+
-- 'coin1' and 'coin2' have the same key, '_k', and the stake is active if the delegation is SJust
683+
(\_k trip coin2 -> extractAndAdd coin2 <$> UM.tripRewardActiveDelegation trip)
684+
-- what to do when a key appears just in 'tripmap', we only add the coin if the key is active
685+
(Map.mapMaybe (\trip -> UM.fromCompact . UM.rdReward <$> UM.tripRewardActiveDelegation trip))
686+
-- what to do when a key is only in 'incremental', keep everything, because we know it is active.
687+
id
688+
m1
689+
m2
690+
extractAndAdd :: Coin -> UM.RDPair -> Coin
691+
extractAndAdd coin (UM.RDPair rew _dep) = coin <> UM.fromCompact rew

0 commit comments

Comments
 (0)