Skip to content

Commit 2772d9f

Browse files
committed
fix error resolveGovActionProposal.queryGovActionProposalId
1 parent efa38c2 commit 2772d9f

File tree

4 files changed

+68
-45
lines changed

4 files changed

+68
-45
lines changed

Diff for: cardano-chain-gen/src/Cardano/Mock/Query.hs

+1-1
Original file line numberDiff line numberDiff line change
@@ -17,7 +17,7 @@ module Cardano.Mock.Query (
1717
) where
1818

1919
import qualified Cardano.Db as Db
20-
import Cardano.Prelude hiding (isNothing, from)
20+
import Cardano.Prelude hiding (from, isNothing)
2121
import qualified Data.ByteString.Base16 as Base16
2222
import Data.ByteString.Short (ShortByteString, toShort)
2323
import Database.Esqueleto.Experimental

Diff for: cardano-db-sync/src/Cardano/DbSync/Era/Universal/Block.hs

+1-1
Original file line numberDiff line numberDiff line change
@@ -142,7 +142,7 @@ insertBlockUniversal syncEnv shouldLog withinTwoMins withinHalfHour blk details
142142
]
143143

144144
whenStrictJust (apNewEpoch applyResult) $ \newEpoch -> do
145-
insertOnNewEpoch tracer iopts blkId (Generic.blkSlotNo blk) epochNo newEpoch
145+
insertOnNewEpoch syncEnv blkId (Generic.blkSlotNo blk) epochNo newEpoch
146146

147147
insertStakeSlice syncEnv $ apStakeSlice applyResult
148148

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

+6-5
Original file line numberDiff line numberDiff line change
@@ -65,28 +65,29 @@ import Database.Persist.Sql (SqlBackend)
6565
--------------------------------------------------------------------------------------------
6666
insertOnNewEpoch ::
6767
(MonadBaseControl IO m, MonadIO m) =>
68-
Trace IO Text ->
69-
InsertOptions ->
68+
SyncEnv ->
7069
DB.BlockId ->
7170
SlotNo ->
7271
EpochNo ->
7372
Generic.NewEpoch ->
7473
ExceptT SyncNodeError (ReaderT SqlBackend m) ()
75-
insertOnNewEpoch tracer iopts blkId slotNo epochNo newEpoch = do
74+
insertOnNewEpoch syncEnv blkId slotNo epochNo newEpoch = do
7675
whenStrictJust (Generic.euProtoParams epochUpdate) $ \params ->
7776
lift $ insertEpochParam tracer blkId epochNo params (Generic.euNonce epochUpdate)
7877
whenStrictJust (Generic.neAdaPots newEpoch) $ \pots ->
7978
insertPots blkId slotNo epochNo pots
8079
whenStrictJust (Generic.neDRepState newEpoch) $ \dreps -> when (ioGov iopts) $ do
8180
let (drepSnapshot, ratifyState) = finishDRepPulser dreps
8281
lift $ insertDrepDistr epochNo drepSnapshot
83-
updateEnacted False epochNo (rsEnactState ratifyState)
82+
updateEnacted syncEnv False epochNo (rsEnactState ratifyState)
8483
whenStrictJust (Generic.neEnacted newEpoch) $ \enactedSt ->
8584
when (ioGov iopts) $
86-
updateEnacted True epochNo enactedSt
85+
updateEnacted syncEnv True epochNo enactedSt
8786
where
8887
epochUpdate :: Generic.EpochUpdate
8988
epochUpdate = Generic.neEpochUpdate newEpoch
89+
tracer = getTrace syncEnv
90+
iopts = getInsertOptions syncEnv
9091

9192
insertEpochParam ::
9293
(MonadBaseControl IO m, MonadIO m) =>

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

+60-38
Original file line numberDiff line numberDiff line change
@@ -27,9 +27,10 @@ where
2727
import qualified Cardano.Crypto as Crypto
2828
import Cardano.Db (DbWord64 (..))
2929
import qualified Cardano.Db as DB
30-
import Cardano.DbSync.Api.Types (SyncEnv (..))
30+
import Cardano.DbSync.Api.Types (SyncEnv (..), SyncOptions (..), ioShelley)
3131
import Cardano.DbSync.Cache (queryOrInsertRewardAccount, queryPoolKeyOrInsert)
3232
import Cardano.DbSync.Cache.Types (CacheNew (..))
33+
import Cardano.DbSync.Config.Types (ShelleyInsertConfig (..))
3334
import qualified Cardano.DbSync.Era.Shelley.Generic as Generic
3435
import Cardano.DbSync.Era.Shelley.Generic.ParamProposal
3536
import Cardano.DbSync.Era.Universal.Insert.Other (toDouble)
@@ -87,7 +88,7 @@ insertGovActionProposal syncEnv blkId txId govExpiresAt mmCommittee (index, pp)
8788
_ -> pure Nothing
8889
prevGovActionDBId <- case mprevGovAction of
8990
Nothing -> pure Nothing
90-
Just prevGovActionId -> Just <$> resolveGovActionProposal prevGovActionId
91+
Just prevGovActionId -> resolveGovActionProposal syncEnv prevGovActionId
9192
govActionProposalId <-
9293
lift $
9394
DB.insertGovActionProposal $
@@ -178,17 +179,25 @@ insertGovActionProposal syncEnv blkId txId govExpiresAt mmCommittee (index, pp)
178179
--------------------------------------------------------------------------------------
179180
resolveGovActionProposal ::
180181
MonadIO m =>
182+
SyncEnv ->
181183
GovActionId StandardCrypto ->
182-
ExceptT SyncNodeError (ReaderT SqlBackend m) DB.GovActionProposalId
183-
resolveGovActionProposal gaId = do
184+
ExceptT SyncNodeError (ReaderT SqlBackend m) (Maybe DB.GovActionProposalId)
185+
resolveGovActionProposal syncEnv gaId = do
184186
gaTxId <-
185187
liftLookupFail "resolveGovActionProposal.queryTxId" $
186188
DB.queryTxId $
187189
Generic.unTxHash $
188190
gaidTxId gaId
189191
let (GovActionIx index) = gaidGovActionIx gaId
190-
liftLookupFail "resolveGovActionProposal.queryGovActionProposalId" $
191-
DB.queryGovActionProposalId gaTxId (fromIntegral index) -- TODO: Use Word32?
192+
case ioShelley insertOpts of
193+
ShelleyStakeAddrs _ -> pure Nothing
194+
_ -> do
195+
result <-
196+
liftLookupFail "resolveGovActionProposal.queryGovActionProposalId" $
197+
DB.queryGovActionProposalId gaTxId (fromIntegral index) -- TODO: Use Word32?
198+
pure $ Just result
199+
where
200+
insertOpts = soptInsertOptions $ envOptions syncEnv
192201

193202
insertParamProposal ::
194203
(MonadBaseControl IO m, MonadIO m) =>
@@ -287,32 +296,35 @@ insertVotingProcedure ::
287296
(Word16, (GovActionId StandardCrypto, VotingProcedure StandardConway)) ->
288297
ExceptT SyncNodeError (ReaderT SqlBackend m) ()
289298
insertVotingProcedure syncEnv txId voter (index, (gaId, vp)) = do
290-
govActionId <- resolveGovActionProposal gaId
291-
votingAnchorId <- whenMaybe (strictMaybeToMaybe $ vProcAnchor vp) $ lift . insertVotingAnchor txId DB.OtherAnchor
292-
(mCommitteeVoterId, mDRepVoter, mStakePoolVoter) <- case voter of
293-
CommitteeVoter cred -> do
294-
khId <- lift $ insertCommitteeHash cred
295-
pure (Just khId, Nothing, Nothing)
296-
DRepVoter cred -> do
297-
drep <- lift $ insertCredDrepHash cred
298-
pure (Nothing, Just drep, Nothing)
299-
StakePoolVoter poolkh -> do
300-
poolHashId <- lift $ queryPoolKeyOrInsert "insertVotingProcedure" syncEnv (envCache syncEnv) CacheNew False poolkh
301-
pure (Nothing, Nothing, Just poolHashId)
302-
void
303-
. lift
304-
. DB.insertVotingProcedure
305-
$ DB.VotingProcedure
306-
{ DB.votingProcedureTxId = txId
307-
, DB.votingProcedureIndex = index
308-
, DB.votingProcedureGovActionProposalId = govActionId
309-
, DB.votingProcedureCommitteeVoter = mCommitteeVoterId
310-
, DB.votingProcedureDrepVoter = mDRepVoter
311-
, DB.votingProcedurePoolVoter = mStakePoolVoter
312-
, DB.votingProcedureVoterRole = Generic.toVoterRole voter
313-
, DB.votingProcedureVote = Generic.toVote $ vProcVote vp
314-
, DB.votingProcedureVotingAnchorId = votingAnchorId
315-
}
299+
maybeGovActionId <- resolveGovActionProposal syncEnv gaId
300+
case maybeGovActionId of
301+
Nothing -> pure ()
302+
Just govActionId -> do
303+
votingAnchorId <- whenMaybe (strictMaybeToMaybe $ vProcAnchor vp) $ lift . insertVotingAnchor txId DB.OtherAnchor
304+
(mCommitteeVoterId, mDRepVoter, mStakePoolVoter) <- case voter of
305+
CommitteeVoter cred -> do
306+
khId <- lift $ insertCommitteeHash cred
307+
pure (Just khId, Nothing, Nothing)
308+
DRepVoter cred -> do
309+
drep <- lift $ insertCredDrepHash cred
310+
pure (Nothing, Just drep, Nothing)
311+
StakePoolVoter poolkh -> do
312+
poolHashId <- lift $ queryPoolKeyOrInsert "insertVotingProcedure" syncEnv (envCache syncEnv) CacheNew False poolkh
313+
pure (Nothing, Nothing, Just poolHashId)
314+
void
315+
. lift
316+
. DB.insertVotingProcedure
317+
$ DB.VotingProcedure
318+
{ DB.votingProcedureTxId = txId
319+
, DB.votingProcedureIndex = index
320+
, DB.votingProcedureGovActionProposalId = govActionId
321+
, DB.votingProcedureCommitteeVoter = mCommitteeVoterId
322+
, DB.votingProcedureDrepVoter = mDRepVoter
323+
, DB.votingProcedurePoolVoter = mStakePoolVoter
324+
, DB.votingProcedureVoterRole = Generic.toVoterRole voter
325+
, DB.votingProcedureVote = Generic.toVote $ vProcVote vp
326+
, DB.votingProcedureVotingAnchorId = votingAnchorId
327+
}
316328

317329
insertVotingAnchor :: (MonadIO m, MonadBaseControl IO m) => DB.TxId -> DB.AnchorType -> Anchor StandardCrypto -> ReaderT SqlBackend m DB.VotingAnchorId
318330
insertVotingAnchor txId anchorType anchor =
@@ -386,12 +398,22 @@ insertCostModel _blkId cms =
386398
, DB.costModelCosts = Text.decodeUtf8 $ LBS.toStrict $ Aeson.encode cms
387399
}
388400

389-
updateEnacted :: forall m. (MonadBaseControl IO m, MonadIO m) => Bool -> EpochNo -> EnactState StandardConway -> ExceptT SyncNodeError (ReaderT SqlBackend m) ()
390-
updateEnacted isEnacted epochNo enactedState = do
401+
updateEnacted ::
402+
forall m.
403+
(MonadBaseControl IO m, MonadIO m) =>
404+
SyncEnv ->
405+
Bool ->
406+
EpochNo ->
407+
EnactState StandardConway ->
408+
ExceptT SyncNodeError (ReaderT SqlBackend m) ()
409+
updateEnacted syncEnv isEnacted epochNo enactedState = do
391410
whenJust (strictMaybeToMaybe (enactedState ^. ensPrevPParamUpdateL)) $ \prevId -> do
392-
gaId <- resolveGovActionProposal $ getPrevId prevId
393-
if isEnacted
394-
then lift $ DB.updateGovActionEnacted gaId (unEpochNo epochNo)
395-
else lift $ DB.updateGovActionRatified gaId (unEpochNo epochNo)
411+
maybeGaId <- resolveGovActionProposal syncEnv $ getPrevId prevId
412+
case maybeGaId of
413+
Nothing -> pure ()
414+
Just gaId ->
415+
if isEnacted
416+
then lift $ DB.updateGovActionEnacted gaId (unEpochNo epochNo)
417+
else lift $ DB.updateGovActionRatified gaId (unEpochNo epochNo)
396418
where
397419
getPrevId = unGovPurposeId

0 commit comments

Comments
 (0)