Skip to content

Commit 09f9979

Browse files
committed
fix merge conflict errors
1 parent baacab6 commit 09f9979

File tree

9 files changed

+76
-53
lines changed

9 files changed

+76
-53
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: 11 additions & 11 deletions
Original file line numberDiff line numberDiff line change
@@ -76,11 +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-
updateRatified epochNo (toList $ rsEnacted ratifyState)
80-
updateExpired epochNo (toList $ rsExpired ratifyState)
81-
whenStrictJust (Generic.neEnacted newEpoch) $ \enactedSt -> do
82-
when (ioGov iopts) $ do
83-
insertUpdateEnacted tracer blkId epochNo enactedSt
79+
updateRatified syncEnv epochNo (toList $ rsEnacted ratifyState)
80+
updateExpired syncEnv epochNo (toList $ rsExpired ratifyState)
81+
whenStrictJust (Generic.neEnacted newEpoch) $ \enactedSt ->
82+
when (ioGov iopts) $
83+
updateEnacted syncEnv epochNo enactedSt
8484
where
8585
epochUpdate :: Generic.EpochUpdate
8686
epochUpdate = Generic.neEpochUpdate newEpoc
@@ -218,7 +218,7 @@ insertEpochStake syncEnv nw epochNo stakeChunk = do
218218
ExceptT SyncNodeError (ReaderT SqlBackend m) (Maybe DB.EpochStake)
219219
mkStake cache (saddr, (coin, pool)) =
220220
-- Check if the stake address is in the shelley whitelist
221-
if shelleyStakeAddrWhitelistCheck syncEnv $ Ledger.RewardAcnt nw saddr
221+
if shelleyStakeAddrWhitelistCheck syncEnv $ Ledger.RewardAccount nw saddr
222222
then
223223
( do
224224
saId <- lift $ queryOrInsertStakeAddress syncEnv cache UpdateCache nw saddr
@@ -257,7 +257,7 @@ insertRewards syncEnv nw earnedEpoch spendableEpoch cache rewardsChunk = do
257257
ExceptT SyncNodeError (ReaderT SqlBackend m) [DB.Reward]
258258
mkRewards (saddr, rset) =
259259
-- Check if the stake address is in the shelley whitelist
260-
if shelleyStakeAddrWhitelistCheck syncEnv $ Ledger.RewardAcnt nw saddr
260+
if shelleyStakeAddrWhitelistCheck syncEnv $ Ledger.RewardAccount nw saddr
261261
then do
262262
saId <- lift $ queryOrInsertStakeAddress syncEnv cache UpdateCache nw saddr
263263
mapM (prepareReward saId) (Set.toList rset)
@@ -298,7 +298,7 @@ insertRewardRests ::
298298
CacheStatus ->
299299
[(StakeCred, Set Generic.RewardRest)] ->
300300
ExceptT SyncNodeError (ReaderT SqlBackend m) ()
301-
insertInstantRewards syncEnv nw earnedEpoch spendableEpoch cache rewardsChunk = do
301+
insertRewardRests syncEnv nw earnedEpoch spendableEpoch cache rewardsChunk = do
302302
dbRewards <- concatMapM mkRewards rewardsChunk
303303
let chunckDbRewards = splittRecordsEvery 100000 dbRewards
304304
-- minimising the bulk inserts into hundred thousand chunks to improve performance
@@ -331,14 +331,14 @@ insertInstantRewards syncEnv nw earnedEpoch spendableEpoch cache rewardsChunk =
331331

332332
insertProposalRefunds ::
333333
(MonadBaseControl IO m, MonadIO m) =>
334-
Trace IO Text ->
334+
SyncEnv ->
335335
Network ->
336336
EpochNo ->
337337
EpochNo ->
338338
CacheStatus ->
339339
[GovActionRefunded] ->
340340
ExceptT SyncNodeError (ReaderT SqlBackend m) ()
341-
insertProposalRefunds trce nw earnedEpoch spendableEpoch cache refunds = do
341+
insertProposalRefunds syncEnv nw earnedEpoch spendableEpoch cache refunds = do
342342
dbRewards <- mapM mkReward refunds
343343
lift $ DB.insertManyRewardRests dbRewards
344344
where
@@ -347,7 +347,7 @@ insertProposalRefunds trce nw earnedEpoch spendableEpoch cache refunds = do
347347
GovActionRefunded ->
348348
ExceptT SyncNodeError (ReaderT SqlBackend m) DB.RewardRest
349349
mkReward refund = do
350-
saId <- lift $ queryOrInsertStakeAddress trce cache UpdateCache nw (raCredential $ garReturnAddr refund)
350+
saId <- lift $ queryOrInsertStakeAddress syncEnv cache UpdateCache nw (Ledger.raCredential $ garReturnAddr refund)
351351
pure $
352352
DB.RewardRest
353353
{ DB.rewardRestAddrId = saId

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

Lines changed: 2 additions & 2 deletions
Original file line numberDiff line numberDiff line change
@@ -296,8 +296,8 @@ insertStaking syncEnv blkId genesis = do
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
@@ -84,9 +84,9 @@ insertCertificate ::
8484
insertCertificate syncEnv isMember mDeposits blkId txId epochNo slotNo redeemers (Generic.TxCertificate ridx idx cert) =
8585
case cert of
8686
Left (ShelleyTxCertDelegCert deleg) ->
87-
when (isShelleyModeActive $ ioShelley iopts) $ insertDelegCert syncEnv network txId idx mRedeemerId epochNo slotNo deleg
87+
when (isShelleyModeActive $ ioShelley iopts) $ insertDelegCert syncEnv mDeposits network txId idx mRedeemerId epochNo slotNo deleg
8888
Left (ShelleyTxCertPool pool) ->
89-
when (isShelleyModeActive $ ioShelley iopts) $ insertPoolCert syncEnv cache isMember network epochNo blkId txId idx pool
89+
when (isShelleyModeActive $ ioShelley iopts) $ insertPoolCert syncEnv cache isMember mDeposits network epochNo blkId txId idx pool
9090
Left (ShelleyTxCertMir mir) ->
9191
when (isShelleyModeActive $ ioShelley iopts) $ insertMirCert syncEnv network txId idx mir
9292
Left (ShelleyTxCertGenesisDeleg _gen) ->
@@ -97,7 +97,7 @@ insertCertificate syncEnv isMember mDeposits blkId txId epochNo slotNo redeemers
9797
when (isShelleyModeActive $ ioShelley iopts) $
9898
insertConwayDelegCert syncEnv mDeposits txId idx mRedeemerId epochNo slotNo deleg
9999
Right (ConwayTxCertPool pool) ->
100-
when (isShelleyModeActive $ ioShelley iopts) $ insertPoolCert syncEnv cache isMember network epochNo blkId txId idx pool
100+
when (isShelleyModeActive $ ioShelley iopts) $ insertPoolCert syncEnv cache isMember mDeposits network epochNo blkId txId idx pool
101101
Right (ConwayTxCertGov c) ->
102102
when (ioGov iopts) $ case c of
103103
ConwayRegDRep cred coin anchor ->
@@ -131,7 +131,7 @@ insertDelegCert ::
131131
ExceptT SyncNodeError (ReaderT SqlBackend m) ()
132132
insertDelegCert syncEnv mDeposits network txId idx mRedeemerId epochNo slotNo dCert =
133133
case dCert of
134-
ShelleyRegCert cred -> insertStakeRegistration syncEnv epochNo txId idx $ Generic.annotateStakingCred network cred
134+
ShelleyRegCert cred -> insertStakeRegistration syncEnv epochNo mDeposits txId idx $ Generic.annotateStakingCred network cred
135135
ShelleyUnRegCert cred -> insertStakeDeregistration syncEnv network epochNo txId idx mRedeemerId cred
136136
ShelleyDelegCert cred poolkh -> insertDelegation syncEnv (envCache syncEnv) network epochNo slotNo txId idx mRedeemerId cred poolkh
137137

@@ -150,15 +150,15 @@ insertConwayDelegCert syncEnv mDeposits txId idx mRedeemerId epochNo slotNo dCer
150150
case dCert of
151151
ConwayRegCert cred _dep ->
152152
when (isShelleyModeActive $ ioShelley iopts) $
153-
insertStakeRegistration syncEnv epochNo txId idx $
153+
insertStakeRegistration syncEnv epochNo mDeposits txId idx $
154154
Generic.annotateStakingCred network cred
155155
ConwayUnRegCert cred _dep ->
156156
when (isShelleyModeActive $ ioShelley iopts) $
157157
insertStakeDeregistration syncEnv network epochNo txId idx mRedeemerId cred
158158
ConwayDelegCert cred delegatee -> insertDeleg cred delegatee
159159
ConwayRegDelegCert cred delegatee _dep -> do
160160
when (isShelleyModeActive $ ioShelley iopts) $
161-
insertStakeRegistration syncEnv epochNo txId idx $
161+
insertStakeRegistration syncEnv epochNo mDeposits txId idx $
162162
Generic.annotateStakingCred network cred
163163
insertDeleg cred delegatee
164164
where
@@ -203,7 +203,7 @@ insertMirCert syncEnv network txId idx mcert = do
203203
ExceptT SyncNodeError (ReaderT SqlBackend m) ()
204204
insertMirReserves (cred, dcoin) =
205205
-- Check if the stake address is in the shelley whitelist
206-
when (shelleyStakeAddrWhitelistCheck syncEnv $ Ledger.RewardAcnt network cred) $ do
206+
when (shelleyStakeAddrWhitelistCheck syncEnv $ Ledger.RewardAccount network cred) $ do
207207
addrId <- lift $ queryOrInsertStakeAddress syncEnv (envCache syncEnv) CacheNew network cred
208208
void . lift . DB.insertReserve $
209209
DB.Reserve
@@ -219,7 +219,7 @@ insertMirCert syncEnv network txId idx mcert = do
219219
ExceptT SyncNodeError (ReaderT SqlBackend m) ()
220220
insertMirTreasury (cred, dcoin) =
221221
-- Check if the stake address is in the shelley whitelist
222-
when (shelleyStakeAddrWhitelistCheck syncEnv $ Ledger.RewardAcnt network cred) $ do
222+
when (shelleyStakeAddrWhitelistCheck syncEnv $ Ledger.RewardAccount network cred) $ do
223223
addrId <- lift $ queryOrInsertStakeAddress syncEnv (envCache syncEnv) CacheNew network cred
224224
void . lift . DB.insertTreasury $
225225
DB.Treasury
@@ -339,7 +339,7 @@ insertStakeDeregistration ::
339339
ExceptT SyncNodeError (ReaderT SqlBackend m) ()
340340
insertStakeDeregistration syncEnv network epochNo txId idx mRedeemerId cred = do
341341
-- Check if the stake address is in the shelley whitelist
342-
when (shelleyCustomStakeWhitelistCheck syncEnv $ Ledger.RewardAcnt network cred) $ do
342+
when (shelleyCustomStakeWhitelistCheck syncEnv $ Ledger.RewardAccount network cred) $ do
343343
scId <- lift $ queryOrInsertStakeAddress syncEnv (envCache syncEnv) EvictAndReturn network cred
344344
void . lift . DB.insertStakeDeregistration $
345345
DB.StakeDeregistration
@@ -432,7 +432,7 @@ insertDelegation ::
432432
ExceptT SyncNodeError (ReaderT SqlBackend m) ()
433433
insertDelegation syncEnv cache network (EpochNo epoch) slotNo txId idx mRedeemerId cred poolkh =
434434
-- Check if the stake address is in the shelley whitelist
435-
when (shelleyCustomStakeWhitelistCheck syncEnv $ Ledger.RewardAcnt network cred) $ do
435+
when (shelleyCustomStakeWhitelistCheck syncEnv $ Ledger.RewardAccount network cred) $ do
436436
addrId <- lift $ queryOrInsertStakeAddress syncEnv cache CacheNew network cred
437437
poolHashId <- lift $ queryPoolKeyOrInsert "insertDelegation" syncEnv cache CacheNew True poolkh
438438
void . lift . DB.insertDelegation $
@@ -457,7 +457,7 @@ insertDelegationVote ::
457457
ExceptT SyncNodeError (ReaderT SqlBackend m) ()
458458
insertDelegationVote syncEnv network txId idx cred drep =
459459
-- Check if the stake address is in the shelley whitelist
460-
when (shelleyStakeAddrWhitelistCheck syncEnv $ Ledger.RewardAcnt network cred) $ do
460+
when (shelleyStakeAddrWhitelistCheck syncEnv $ Ledger.RewardAccount network cred) $ do
461461
addrId <- lift $ queryOrInsertStakeAddress syncEnv (envCache syncEnv) UpdateCache network cred
462462
drepId <- lift $ insertDrep drep
463463
void

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

Lines changed: 35 additions & 13 deletions
Original file line numberDiff line numberDiff line change
@@ -127,6 +127,10 @@ insertGovActionProposal syncEnv blkId txId govExpiresAt mmCommittee (index, pp)
127127
NewConstitution prv _ -> unGovPurposeId <$> strictMaybeToMaybe prv
128128
_ -> Nothing
129129

130+
insertTreasuryWithdrawal ::
131+
DB.GovActionProposalId ->
132+
(Ledger.RewardAccount StandardCrypto, Coin) ->
133+
ReaderT SqlBackend m DB.TreasuryWithdrawalId
130134
insertTreasuryWithdrawal gaId (rwdAcc, coin) = do
131135
addrId <-
132136
queryOrInsertRewardAccount cache UpdateCache rwdAcc
@@ -408,35 +412,41 @@ insertCostModel _blkId cms =
408412
updateRatified ::
409413
forall m.
410414
MonadIO m =>
415+
SyncEnv ->
411416
EpochNo ->
412417
[GovActionState StandardConway] ->
413418
ExceptT SyncNodeError (ReaderT SqlBackend m) ()
414-
updateRatified epochNo ratifiedActions = do
419+
updateRatified syncEnv epochNo ratifiedActions = do
415420
forM_ ratifiedActions $ \action -> do
416-
gaId <- resolveGovActionProposal $ gasId action
417-
lift $ DB.updateGovActionRatified gaId (unEpochNo epochNo)
421+
mGaId <- resolveGovActionProposal syncEnv $ gasId action
422+
whenJust mGaId $ \gaId ->
423+
lift $ DB.updateGovActionRatified gaId (unEpochNo epochNo)
418424

419425
updateExpired ::
420426
forall m.
421427
MonadIO m =>
428+
SyncEnv ->
422429
EpochNo ->
423430
[GovActionId StandardCrypto] ->
424431
ExceptT SyncNodeError (ReaderT SqlBackend m) ()
425-
updateExpired epochNo ratifiedActions = do
432+
updateExpired syncEnv epochNo ratifiedActions = do
426433
forM_ ratifiedActions $ \action -> do
427-
gaId <- resolveGovActionProposal action
428-
lift $ DB.updateGovActionExpired gaId (unEpochNo epochNo)
434+
mGaId <- resolveGovActionProposal syncEnv action
435+
whenJust mGaId $ \gaId ->
436+
lift $ DB.updateGovActionExpired gaId (unEpochNo epochNo)
429437

430438
updateDropped ::
431439
forall m.
432440
MonadIO m =>
441+
SyncEnv ->
433442
EpochNo ->
434443
[GovActionId StandardCrypto] ->
435444
ExceptT SyncNodeError (ReaderT SqlBackend m) ()
436-
updateDropped epochNo ratifiedActions = do
445+
updateDropped syncEnv epochNo ratifiedActions = do
437446
forM_ ratifiedActions $ \action -> do
438-
gaId <- resolveGovActionProposal action
439-
lift $ DB.updateGovActionDropped gaId (unEpochNo epochNo)
447+
mGaId <- resolveGovActionProposal syncEnv action
448+
whenJust mGaId $ \gaId ->
449+
lift $ DB.updateGovActionDropped gaId (unEpochNo epochNo)
440450

441451
insertUpdateEnacted ::
442452
forall m.
@@ -448,17 +458,16 @@ insertUpdateEnacted ::
448458
ExceptT SyncNodeError (ReaderT SqlBackend m) ()
449459
insertUpdateEnacted syncEnv blkId epochNo enactedState = do
450460
whenJust (strictMaybeToMaybe (grPParamUpdate govIds)) $ \prevId -> do
451-
mGaId <- resolveGovActionProposal syncEnv $ getPrevId prevId
461+
maybeGaId <- resolveGovActionProposal syncEnv $ getPrevId prevId
452462
case maybeGaId of
453463
Nothing -> pure ()
454464
Just gaId -> lift $ DB.updateGovActionEnacted gaId (unEpochNo epochNo)
455465

456466
whenJust (strictMaybeToMaybe (grHardFork govIds)) $ \prevId -> do
457-
mGaId <- resolveGovActionProposal $ unGovPurposeId prevId
458-
case mGaId of
467+
maybeGaId <- resolveGovActionProposal $ unGovPurposeId prevId
468+
case maybeGaId of
459469
Nothing -> pure ()
460470
Just gaId -> void $ lift $ DB.updateGovActionEnacted gaId (unEpochNo epochNo)
461-
462471
(mcommitteeId, mnoConfidenceGaId) <- handleCommittee syncEnv blkId
463472

464473
constitutionId <- handleConstitution syncEnv blkId
@@ -545,3 +554,16 @@ handleConstitution syncEnv govIds = do
545554
, textShow constitutionIds
546555
]
547556
pure constitutionId
557+
=======
558+
whenJust (strictMaybeToMaybe (grCommittee enactedState)) $ \prevId -> do
559+
maybeGaId <- resolveGovActionProposal syncEnv $ unGovPurposeId prevId
560+
case maybeGaId of
561+
Nothing -> pure ()
562+
Just gaId -> lift $ DB.updateGovActionEnacted gaId (unEpochNo epochNo)
563+
564+
whenJust (strictMaybeToMaybe (grConstitution enactedState)) $ \prevId -> do
565+
maybeGaId <- resolveGovActionProposal syncEnv $ unGovPurposeId prevId
566+
case maybeGaId of
567+
Nothing -> pure ()
568+
Just gaId -> lift $ DB.updateGovActionEnacted gaId (unEpochNo epochNo)
569+
>>>>>>> 328815aa (fix merge conflict errors)

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
@@ -99,15 +99,15 @@ insertNewEpochLedgerEvents syncEnv currentEpochNo@(EpochNo curEpoch) =
9999
liftIO $
100100
logInfo tracer $
101101
"Found " <> textShow (Set.size uncl) <> " unclaimed proposal refunds"
102-
updateDropped (EpochNo curEpoch) (garGovActionId <$> (en <> ex))
102+
updateDropped syncEnv (EpochNo curEpoch) (garGovActionId <$> (en <> ex))
103103
let en' = filter (\e -> Set.notMember (garGovActionId e) uncl) en
104104
ex' = filter (\e -> Set.notMember (garGovActionId e) uncl) ex
105105
insertProposalRefunds tracer ntw (subFromCurrentEpoch 1) currentEpochNo cache (en' <> ex') -- TODO: check if they are disjoint to avoid double entries.
106106
forM_ en $ \gar -> whenJust (garMTreasury gar) $ \treasuryMap -> do
107107
gaId <- resolveGovActionProposal (garGovActionId gar)
108108
lift $ void $ DB.updateGovActionEnacted gaId (unEpochNo currentEpochNo)
109109
let rewards = Map.mapKeys Ledger.raCredential $ Map.map (Set.singleton . mkTreasuryReward) treasuryMap
110-
insertRewardRests tracer ntw (subFromCurrentEpoch 1) currentEpochNo cache (Map.toList rewards)
110+
insertRewardRests syncEnv ntw (subFromCurrentEpoch 1) currentEpochNo cache (Map.toList rewards)
111111
LedgerMirDist rwd -> do
112112
unless (Map.null rwd) $ do
113113
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 =
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 DoNotUpdateCache nw cred
170170
else pure Nothing

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

Lines changed: 4 additions & 3 deletions
Original file line numberDiff line numberDiff line change
@@ -63,7 +63,7 @@ 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 UpdateCache (PoolP.ppId params)
6868
mdId <- case strictMaybeToMaybe $ PoolP.ppMetadata params of
6969
Just md -> Just <$> insertPoolMetaDataRef poolHashId txId md
@@ -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)
@@ -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)