Skip to content

Commit 16ef624

Browse files
committed
fix merge conflict errors
1 parent 99fa0a2 commit 16ef624

File tree

9 files changed

+65
-55
lines changed

9 files changed

+65
-55
lines changed

cardano-db-sync/src/Cardano/DbSync/Cache.hs

Lines changed: 3 additions & 3 deletions
Original file line numberDiff line numberDiff line change
@@ -120,11 +120,11 @@ insertStakeAddress _syncEnv rewardAddr stakeCredBs = do
120120
DB.insertStakeAddress $
121121
DB.StakeAddress
122122
{ DB.stakeAddressHashRaw = addrBs
123-
, DB.stakeAddressView = Generic.renderRewardAcnt rewardAddr
124-
, DB.stakeAddressScriptHash = Generic.getCredentialScriptHash $ Ledger.getRwdCred rewardAddr
123+
, DB.stakeAddressView = Generic.renderRewardAccount rewardAddr
124+
, DB.stakeAddressScriptHash = Generic.getCredentialScriptHash $ Ledger.raCredential rewardAddr
125125
}
126126
where
127-
addrBs = fromMaybe (Ledger.serialiseRewardAcnt rewardAddr) stakeCredBs
127+
addrBs = fromMaybe (Ledger.serialiseRewardAccount rewardAddr) stakeCredBs
128128

129129
------------------------------------------------------------------------------------------------
130130
queryRewardAccountWithCacheRetBs ::

cardano-db-sync/src/Cardano/DbSync/Era/Universal/Epoch.hs

Lines changed: 9 additions & 7 deletions
Original file line numberDiff line numberDiff line change
@@ -76,10 +76,11 @@ insertOnNewEpoch syncEnv blkId slotNo epochNo newEpoch = do
7676
whenStrictJust (Generic.neDRepState newEpoch) $ \dreps -> when (ioGov iopts) $ do
7777
let (drepSnapshot, ratifyState) = finishDRepPulser dreps
7878
lift $ insertDrepDistr epochNo drepSnapshot
79-
updateEnacted syncEn
79+
updateRatified syncEnv epochNo (toList $ rsEnacted ratifyState)
80+
updateExpired syncEnv epochNo (toList $ rsExpired ratifyState)
8081
whenStrictJust (Generic.neEnacted newEpoch) $ \enactedSt ->
8182
when (ioGov iopts) $
82-
updateEnacted syncEnv True epochNo enactedSt
83+
updateEnacted syncEnv epochNo enactedSt
8384
where
8485
epochUpdate :: Generic.EpochUpdate
8586
epochUpdate = Generic.neEpochUpdate newEpoch
@@ -217,7 +218,7 @@ insertEpochStake syncEnv nw epochNo stakeChunk = do
217218
ExceptT SyncNodeError (ReaderT SqlBackend m) (Maybe DB.EpochStake)
218219
mkStake cache (saddr, (coin, pool)) =
219220
-- Check if the stake address is in the shelley whitelist
220-
if shelleyStakeAddrWhitelistCheck syncEnv $ Ledger.RewardAcnt nw saddr
221+
if shelleyStakeAddrWhitelistCheck syncEnv $ Ledger.RewardAccount nw saddr
221222
then
222223
( do
223224
saId <- lift $ queryOrInsertStakeAddress syncEnv cache CacheNew nw saddr
@@ -257,7 +258,7 @@ insertRewards syncEnv nw earnedEpoch spendableEpoch cache rewardsChunk = do
257258
ExceptT SyncNodeError (ReaderT SqlBackend m) [DB.Reward]
258259
mkRewards (saddr, rset) =
259260
-- Check if the stake address is in the shelley whitelist
260-
if shelleyStakeAddrWhitelistCheck syncEnv $ Ledger.RewardAcnt nw saddr
261+
if shelleyStakeAddrWhitelistCheck syncEnv $ Ledger.RewardAccount nw saddr
261262
then do
262263
saId <- lift $ queryOrInsertStakeAddress syncEnv cache CacheNew nw saddr
263264
mapM (prepareReward saId) (Set.toList rset)
@@ -298,7 +299,7 @@ insertRewardRests ::
298299
Cache ->
299300
[(StakeCred, Set Generic.RewardRest)] ->
300301
ExceptT SyncNodeError (ReaderT SqlBackend m) ()
301-
insertInstantRewards syncEnv nw earnedEpoch spendableEpoch cache rewardsChunk = do
302+
insertRewardRests syncEnv nw earnedEpoch spendableEpoch cache rewardsChunk = do
302303
dbRewards <- concatMapM mkRewards rewardsChunk
303304
let chunckDbRewards = splittRecordsEvery 100000 dbRewards
304305
-- minimising the bulk inserts into hundred thousand chunks to improve performance
@@ -331,13 +332,14 @@ insertInstantRewards syncEnv nw earnedEpoch spendableEpoch cache rewardsChunk =
331332

332333
insertProposalRefunds ::
333334
(MonadBaseControl IO m, MonadIO m) =>
335+
SyncEnv ->
334336
Network ->
335337
EpochNo ->
336338
EpochNo ->
337339
Cache ->
338340
[GovActionRefunded] ->
339341
ExceptT SyncNodeError (ReaderT SqlBackend m) ()
340-
insertProposalRefunds nw earnedEpoch spendableEpoch cache refunds = do
342+
insertProposalRefunds syncEnv nw earnedEpoch spendableEpoch cache refunds = do
341343
dbRewards <- mapM mkReward refunds
342344
lift $ DB.insertManyRewardRests dbRewards
343345
where
@@ -346,7 +348,7 @@ insertProposalRefunds nw earnedEpoch spendableEpoch cache refunds = do
346348
GovActionRefunded ->
347349
ExceptT SyncNodeError (ReaderT SqlBackend m) DB.RewardRest
348350
mkReward refund = do
349-
saId <- lift $ queryOrInsertStakeAddress cache CacheNew nw (raCredential $ garReturnAddr refund)
351+
saId <- lift $ queryOrInsertStakeAddress syncEnv cache CacheNew nw (Ledger.raCredential $ garReturnAddr refund)
350352
pure $
351353
DB.RewardRest
352354
{ DB.rewardRestAddrId = saId

cardano-db-sync/src/Cardano/DbSync/Era/Universal/Genesis.hs

Lines changed: 3 additions & 3 deletions
Original file line numberDiff line numberDiff line change
@@ -292,12 +292,12 @@ insertStaking syncEnv blkId genesis = do
292292
let params = zip [0 ..] $ ListMap.elems $ sgsPools $ sgStaking genesis
293293
let network = sgNetworkId genesis
294294
-- TODO: add initial deposits for genesis pools.
295-
forM_ params $ uncurry (insertPoolRegister syncEnv UninitiatedCache (const False) Nothing network (Epoch 0) blkId txId)
295+
forM_ params $ uncurry (insertPoolRegister syncEnv UninitiatedCache (const False) Nothing network (EpochNo 0) blkId txId)
296296
let stakes = zip [0 ..] $ ListMap.toList (sgsStake $ sgStaking genesis)
297297
forM_ stakes $ \(n, (keyStaking, keyPool)) -> do
298298
-- TODO: add initial deposits for genesis stake keys.
299-
insertStakeRegistration syncEnv (EpochNo 0) txId (2 * n) (Generic.annotateStakingCred network (KeyHashObj keyStaking))
300-
insertDelegation syncEnv UninitiatedCache network 0 0 txId (2 * n + 1) Nothing (KeyHashObj keyStaking) keyPool
299+
insertStakeRegistration syncEnv (EpochNo 0) Nothing txId (2 * n) (Generic.annotateStakingCred network (KeyHashObj keyStaking))
300+
insertDelegation syncEnv UninitiatedCache network (EpochNo 0) 0 txId (2 * n + 1) Nothing (KeyHashObj keyStaking) keyPool
301301

302302
-- -----------------------------------------------------------------------------
303303

cardano-db-sync/src/Cardano/DbSync/Era/Universal/Insert/Certificate.hs

Lines changed: 11 additions & 11 deletions
Original file line numberDiff line numberDiff line change
@@ -83,9 +83,9 @@ insertCertificate ::
8383
insertCertificate syncEnv isMember mDeposits blkId txId epochNo slotNo redeemers (Generic.TxCertificate ridx idx cert) =
8484
case cert of
8585
Left (ShelleyTxCertDelegCert deleg) ->
86-
when (isShelleyModeActive $ ioShelley iopts) $ insertDelegCert syncEnv network txId idx mRedeemerId epochNo slotNo deleg
86+
when (isShelleyModeActive $ ioShelley iopts) $ insertDelegCert syncEnv mDeposits network txId idx mRedeemerId epochNo slotNo deleg
8787
Left (ShelleyTxCertPool pool) ->
88-
when (isShelleyModeActive $ ioShelley iopts) $ insertPoolCert syncEnv cache isMember network epochNo blkId txId idx pool
88+
when (isShelleyModeActive $ ioShelley iopts) $ insertPoolCert syncEnv cache isMember mDeposits network epochNo blkId txId idx pool
8989
Left (ShelleyTxCertMir mir) ->
9090
when (isShelleyModeActive $ ioShelley iopts) $ insertMirCert syncEnv network txId idx mir
9191
Left (ShelleyTxCertGenesisDeleg _gen) ->
@@ -96,7 +96,7 @@ insertCertificate syncEnv isMember mDeposits blkId txId epochNo slotNo redeemers
9696
when (isShelleyModeActive $ ioShelley iopts) $
9797
insertConwayDelegCert syncEnv mDeposits txId idx mRedeemerId epochNo slotNo deleg
9898
Right (ConwayTxCertPool pool) ->
99-
when (isShelleyModeActive $ ioShelley iopts) $ insertPoolCert syncEnv cache isMember network epochNo blkId txId idx pool
99+
when (isShelleyModeActive $ ioShelley iopts) $ insertPoolCert syncEnv cache isMember mDeposits network epochNo blkId txId idx pool
100100
Right (ConwayTxCertGov c) ->
101101
when (ioGov iopts) $ case c of
102102
ConwayRegDRep cred coin anchor ->
@@ -130,7 +130,7 @@ insertDelegCert ::
130130
ExceptT SyncNodeError (ReaderT SqlBackend m) ()
131131
insertDelegCert syncEnv mDeposits network txId idx mRedeemerId epochNo slotNo dCert =
132132
case dCert of
133-
ShelleyRegCert cred -> insertStakeRegistration syncEnv epochNo txId idx $ Generic.annotateStakingCred network cred
133+
ShelleyRegCert cred -> insertStakeRegistration syncEnv epochNo mDeposits txId idx $ Generic.annotateStakingCred network cred
134134
ShelleyUnRegCert cred -> insertStakeDeregistration syncEnv network epochNo txId idx mRedeemerId cred
135135
ShelleyDelegCert cred poolkh -> insertDelegation syncEnv (envCache syncEnv) network epochNo slotNo txId idx mRedeemerId cred poolkh
136136

@@ -149,15 +149,15 @@ insertConwayDelegCert syncEnv mDeposits txId idx mRedeemerId epochNo slotNo dCer
149149
case dCert of
150150
ConwayRegCert cred _dep ->
151151
when (isShelleyModeActive $ ioShelley iopts) $
152-
insertStakeRegistration syncEnv epochNo txId idx $
152+
insertStakeRegistration syncEnv epochNo mDeposits txId idx $
153153
Generic.annotateStakingCred network cred
154154
ConwayUnRegCert cred _dep ->
155155
when (isShelleyModeActive $ ioShelley iopts) $
156156
insertStakeDeregistration syncEnv network epochNo txId idx mRedeemerId cred
157157
ConwayDelegCert cred delegatee -> insertDeleg cred delegatee
158158
ConwayRegDelegCert cred delegatee _dep -> do
159159
when (isShelleyModeActive $ ioShelley iopts) $
160-
insertStakeRegistration syncEnv epochNo txId idx $
160+
insertStakeRegistration syncEnv epochNo mDeposits txId idx $
161161
Generic.annotateStakingCred network cred
162162
insertDeleg cred delegatee
163163
where
@@ -202,7 +202,7 @@ insertMirCert syncEnv network txId idx mcert = do
202202
ExceptT SyncNodeError (ReaderT SqlBackend m) ()
203203
insertMirReserves (cred, dcoin) =
204204
-- Check if the stake address is in the shelley whitelist
205-
when (shelleyStakeAddrWhitelistCheck syncEnv $ Ledger.RewardAcnt network cred) $ do
205+
when (shelleyStakeAddrWhitelistCheck syncEnv $ Ledger.RewardAccount network cred) $ do
206206
addrId <- lift $ queryOrInsertStakeAddress syncEnv (envCache syncEnv) CacheNew network cred
207207
void . lift . DB.insertReserve $
208208
DB.Reserve
@@ -218,7 +218,7 @@ insertMirCert syncEnv network txId idx mcert = do
218218
ExceptT SyncNodeError (ReaderT SqlBackend m) ()
219219
insertMirTreasury (cred, dcoin) =
220220
-- Check if the stake address is in the shelley whitelist
221-
when (shelleyStakeAddrWhitelistCheck syncEnv $ Ledger.RewardAcnt network cred) $ do
221+
when (shelleyStakeAddrWhitelistCheck syncEnv $ Ledger.RewardAccount network cred) $ do
222222
addrId <- lift $ queryOrInsertStakeAddress syncEnv (envCache syncEnv) CacheNew network cred
223223
void . lift . DB.insertTreasury $
224224
DB.Treasury
@@ -336,7 +336,7 @@ insertStakeDeregistration ::
336336
ExceptT SyncNodeError (ReaderT SqlBackend m) ()
337337
insertStakeDeregistration syncEnv network epochNo txId idx mRedeemerId cred = do
338338
-- Check if the stake address is in the shelley whitelist
339-
when (shelleyCustomStakeWhitelistCheck syncEnv $ Ledger.RewardAcnt network cred) $ do
339+
when (shelleyCustomStakeWhitelistCheck syncEnv $ Ledger.RewardAccount network cred) $ do
340340
scId <- lift $ queryOrInsertStakeAddress syncEnv (envCache syncEnv) EvictAndReturn network cred
341341
void . lift . DB.insertStakeDeregistration $
342342
DB.StakeDeregistration
@@ -429,7 +429,7 @@ insertDelegation ::
429429
ExceptT SyncNodeError (ReaderT SqlBackend m) ()
430430
insertDelegation syncEnv cache network (EpochNo epoch) slotNo txId idx mRedeemerId cred poolkh =
431431
-- Check if the stake address is in the shelley whitelist
432-
when (shelleyCustomStakeWhitelistCheck syncEnv $ Ledger.RewardAcnt network cred) $ do
432+
when (shelleyCustomStakeWhitelistCheck syncEnv $ Ledger.RewardAccount network cred) $ do
433433
addrId <- lift $ queryOrInsertStakeAddress syncEnv cache CacheNew network cred
434434
poolHashId <- lift $ queryPoolKeyOrInsert "insertDelegation" syncEnv cache CacheNew True poolkh
435435
void . lift . DB.insertDelegation $
@@ -454,7 +454,7 @@ insertDelegationVote ::
454454
ExceptT SyncNodeError (ReaderT SqlBackend m) ()
455455
insertDelegationVote syncEnv network txId idx cred drep =
456456
-- Check if the stake address is in the shelley whitelist
457-
when (shelleyStakeAddrWhitelistCheck syncEnv $ Ledger.RewardAcnt network cred) $ do
457+
when (shelleyStakeAddrWhitelistCheck syncEnv $ Ledger.RewardAccount network cred) $ do
458458
addrId <- lift $ queryOrInsertStakeAddress syncEnv (envCache syncEnv) CacheNew network cred
459459
drepId <- lift $ insertDrep drep
460460
void

cardano-db-sync/src/Cardano/DbSync/Era/Universal/Insert/GovAction.hs

Lines changed: 22 additions & 15 deletions
Original file line numberDiff line numberDiff line change
@@ -128,7 +128,7 @@ insertGovActionProposal syncEnv blkId txId govExpiresAt mmCommittee (index, pp)
128128

129129
insertTreasuryWithdrawal ::
130130
DB.GovActionProposalId ->
131-
(Ledger.RewardAcnt StandardCrypto, Coin) ->
131+
(Ledger.RewardAccount StandardCrypto, Coin) ->
132132
ReaderT SqlBackend m DB.TreasuryWithdrawalId
133133
insertTreasuryWithdrawal gaId (rwdAcc, coin) = do
134134
addrId <- queryOrInsertRewardAccount syncEnv cache CacheNew rwdAcc
@@ -405,63 +405,70 @@ insertCostModel _blkId cms =
405405
updateRatified ::
406406
forall m.
407407
MonadIO m =>
408+
SyncEnv ->
408409
EpochNo ->
409410
[GovActionState StandardConway] ->
410411
ExceptT SyncNodeError (ReaderT SqlBackend m) ()
411-
updateRatified epochNo ratifiedActions = do
412+
updateRatified syncEnv epochNo ratifiedActions = do
412413
forM_ ratifiedActions $ \action -> do
413-
gaId <- resolveGovActionProposal $ gasId action
414-
lift $ DB.updateGovActionRatified gaId (unEpochNo epochNo)
414+
mGaId <- resolveGovActionProposal syncEnv $ gasId action
415+
whenJust mGaId $ \gaId ->
416+
lift $ DB.updateGovActionRatified gaId (unEpochNo epochNo)
415417

416418
updateExpired ::
417419
forall m.
418420
MonadIO m =>
421+
SyncEnv ->
419422
EpochNo ->
420423
[GovActionId StandardCrypto] ->
421424
ExceptT SyncNodeError (ReaderT SqlBackend m) ()
422-
updateExpired epochNo ratifiedActions = do
425+
updateExpired syncEnv epochNo ratifiedActions = do
423426
forM_ ratifiedActions $ \action -> do
424-
gaId <- resolveGovActionProposal action
425-
lift $ DB.updateGovActionExpired gaId (unEpochNo epochNo)
427+
mGaId <- resolveGovActionProposal syncEnv action
428+
whenJust mGaId $ \gaId ->
429+
lift $ DB.updateGovActionExpired gaId (unEpochNo epochNo)
426430

427431
updateDropped ::
428432
forall m.
429433
MonadIO m =>
434+
SyncEnv ->
430435
EpochNo ->
431436
[GovActionId StandardCrypto] ->
432437
ExceptT SyncNodeError (ReaderT SqlBackend m) ()
433-
updateDropped epochNo ratifiedActions = do
438+
updateDropped syncEnv epochNo ratifiedActions = do
434439
forM_ ratifiedActions $ \action -> do
435-
gaId <- resolveGovActionProposal action
436-
lift $ DB.updateGovActionDropped gaId (unEpochNo epochNo)
440+
mGaId <- resolveGovActionProposal syncEnv action
441+
whenJust mGaId $ \gaId ->
442+
lift $ DB.updateGovActionDropped gaId (unEpochNo epochNo)
437443

438444
updateEnacted ::
439445
forall m.
440446
(MonadBaseControl IO m, MonadIO m) =>
447+
SyncEnv ->
441448
EpochNo ->
442449
GovRelation StrictMaybe StandardConway ->
443450
ExceptT SyncNodeError (ReaderT SqlBackend m) ()
444-
updateEnacted epochNo enactedState = do
451+
updateEnacted syncEnv epochNo enactedState = do
445452
whenJust (strictMaybeToMaybe (grPParamUpdate enactedState)) $ \prevId -> do
446-
mGaId <- resolveGovActionProposal syncEnv $ getPrevId prevId
453+
maybeGaId <- resolveGovActionProposal syncEnv $ unGovPurposeId prevId
447454
case maybeGaId of
448455
Nothing -> pure ()
449456
Just gaId -> lift $ DB.updateGovActionEnacted gaId (unEpochNo epochNo)
450457

451458
whenJust (strictMaybeToMaybe (grHardFork enactedState)) $ \prevId -> do
452-
mGaId <- resolveGovActionProposal syncEnv $ getPrevId prevId
459+
maybeGaId <- resolveGovActionProposal syncEnv $ unGovPurposeId prevId
453460
case maybeGaId of
454461
Nothing -> pure ()
455462
Just gaId -> lift $ DB.updateGovActionEnacted gaId (unEpochNo epochNo)
456463

457464
whenJust (strictMaybeToMaybe (grCommittee enactedState)) $ \prevId -> do
458-
mGaId <- resolveGovActionProposal syncEnv $ getPrevId prevId
465+
maybeGaId <- resolveGovActionProposal syncEnv $ unGovPurposeId prevId
459466
case maybeGaId of
460467
Nothing -> pure ()
461468
Just gaId -> lift $ DB.updateGovActionEnacted gaId (unEpochNo epochNo)
462469

463470
whenJust (strictMaybeToMaybe (grConstitution enactedState)) $ \prevId -> do
464-
mGaId <- resolveGovActionProposal syncEnv $ getPrevId prevId
471+
maybeGaId <- resolveGovActionProposal syncEnv $ unGovPurposeId prevId
465472
case maybeGaId of
466473
Nothing -> pure ()
467474
Just gaId -> lift $ DB.updateGovActionEnacted gaId (unEpochNo epochNo)

cardano-db-sync/src/Cardano/DbSync/Era/Universal/Insert/LedgerEvent.hs

Lines changed: 2 additions & 2 deletions
Original file line numberDiff line numberDiff line change
@@ -97,10 +97,10 @@ insertBlockLedgerEvents syncEnv currentEpochNo@(EpochNo curEpoch) =
9797
liftIO $
9898
logInfo tracer $
9999
"Found " <> textShow (Set.size uncl) <> " unclaimed proposal refunds"
100-
updateDropped (EpochNo curEpoch) (garGovActionId <$> (en <> ex))
100+
updateDropped syncEnv (EpochNo curEpoch) (garGovActionId <$> (en <> ex))
101101
let en' = filter (\e -> Set.notMember (garGovActionId e) uncl) en
102102
ex' = filter (\e -> Set.notMember (garGovActionId e) uncl) ex
103-
insertProposalRefunds ntw (subFromCurrentEpoch 1) currentEpochNo cache (en' <> ex') -- TODO: check if they are disjoint to avoid double entries.
103+
insertProposalRefunds syncEnv ntw (subFromCurrentEpoch 1) currentEpochNo cache (en' <> ex') -- TODO: check if they are disjoint to avoid double entries.
104104
LedgerMirDist rwd -> do
105105
unless (Map.null rwd) $ do
106106
let rewards = Map.toList rwd

cardano-db-sync/src/Cardano/DbSync/Era/Universal/Insert/Other.hs

Lines changed: 1 addition & 1 deletion
Original file line numberDiff line numberDiff line change
@@ -164,7 +164,7 @@ insertStakeAddressRefIfMissing syncEnv cache addr = do
164164
case sref of
165165
Ledger.StakeRefBase cred -> do
166166
-- Check if the stake address is in the shelley whitelist
167-
if shelleyStakeAddrWhitelistCheck syncEnv $ Ledger.RewardAcnt nw cred
167+
if shelleyStakeAddrWhitelistCheck syncEnv $ Ledger.RewardAccount nw cred
168168
then do
169169
Just <$> queryOrInsertStakeAddress syncEnv cache DontCacheNew nw cred
170170
else pure Nothing

cardano-db-sync/src/Cardano/DbSync/Era/Universal/Insert/Pool.hs

Lines changed: 6 additions & 5 deletions
Original file line numberDiff line numberDiff line change
@@ -63,15 +63,15 @@ insertPoolRegister ::
6363
ExceptT SyncNodeError (ReaderT SqlBackend m) ()
6464
insertPoolRegister syncEnv cache isMember mdeposits network (EpochNo epoch) blkId txId idx params =
6565
-- Check if the stake address is in the shelley whitelist
66-
when (shelleyStakeAddrWhitelistCheck syncEnv $ adjustNetworkTag (PoolP.ppRewardAcnt params)) $ do
66+
when (shelleyStakeAddrWhitelistCheck syncEnv $ adjustNetworkTag (PoolP.ppRewardAccount params)) $ do
6767
poolHashId <- lift $ insertPoolKeyWithCache cache CacheNew (PoolP.ppId params)
6868
mdId <- case strictMaybeToMaybe $ PoolP.ppMetadata params of
6969
Just md -> Just <$> insertPoolMetaDataRef poolHashId txId md
7070
Nothing -> pure Nothing
7171
isRegistration <- isPoolRegistration poolHashId
7272
let epochActivationDelay = if isRegistration then 2 else 3
7373
deposit = if isRegistration then Generic.coinToDbLovelace . Generic.poolDeposit <$> mdeposits else Nothing
74-
saId <- lift $ queryOrInsertRewardAccount syncEnv cache CacheNew (adjustNetworkTag $ PoolP.ppRewardAcnt params)
74+
saId <- lift $ queryOrInsertRewardAccount syncEnv cache CacheNew (adjustNetworkTag $ PoolP.ppRewardAccount params)
7575
poolUpdateId <-
7676
lift
7777
. DB.insertPoolUpdate
@@ -85,6 +85,7 @@ insertPoolRegister syncEnv cache isMember mdeposits network (EpochNo epoch) blkI
8585
, DB.poolUpdateMetaId = mdId
8686
, DB.poolUpdateMargin = realToFrac $ Ledger.unboundRational (PoolP.ppMargin params)
8787
, DB.poolUpdateFixedCost = Generic.coinToDbLovelace (PoolP.ppCost params)
88+
, DB.poolUpdateDeposit = deposit
8889
, DB.poolUpdateRegisteredTxId = txId
8990
}
9091
mapM_ (insertPoolOwner syncEnv cache network poolUpdateId) $ toList (PoolP.ppOwners params)
@@ -151,7 +152,7 @@ insertPoolOwner ::
151152
ExceptT SyncNodeError (ReaderT SqlBackend m) ()
152153
insertPoolOwner syncEnv cache network poolUpdateId skh =
153154
-- Check if the stake address is in the shelley whitelist
154-
when (shelleyStakeAddrWhitelistCheck syncEnv $ Ledger.RewardAcnt network (Ledger.KeyHashObj skh)) $ do
155+
when (shelleyStakeAddrWhitelistCheck syncEnv $ Ledger.RewardAccount network (Ledger.KeyHashObj skh)) $ do
155156
saId <- lift $ queryOrInsertStakeAddress syncEnv cache CacheNew network (Ledger.KeyHashObj skh)
156157
void . lift . DB.insertPoolOwner $
157158
DB.PoolOwner
@@ -210,7 +211,7 @@ insertPoolCert ::
210211
Word16 ->
211212
PoolCert StandardCrypto ->
212213
ExceptT SyncNodeError (ReaderT SqlBackend m) ()
213-
insertPoolCert syncEnv cache isMember network epoch blkId txId idx pCert =
214+
insertPoolCert syncEnv cache isMember mdeposits network epoch blkId txId idx pCert =
214215
case pCert of
215-
RegPool pParams -> insertPoolRegister syncEnv (envCache syncEnv) isMember network epoch blkId txId idx pParams
216+
RegPool pParams -> insertPoolRegister syncEnv (envCache syncEnv) isMember mdeposits network epoch blkId txId idx pParams
216217
RetirePool keyHash epochNum -> insertPoolRetire syncEnv cache txId epochNum idx keyHash

0 commit comments

Comments
 (0)