Skip to content

Commit baacab6

Browse files
committed
changes to plutus whitelist
1 parent 5029a8f commit baacab6

File tree

10 files changed

+146
-135
lines changed

10 files changed

+146
-135
lines changed

cardano-db-sync/src/Cardano/DbSync/Config/Types.hs

Lines changed: 24 additions & 24 deletions
Original file line numberDiff line numberDiff line change
@@ -44,10 +44,10 @@ module Cardano.DbSync.Config.Types (
4444
isTxOutEnabled,
4545
hasLedger,
4646
shouldUseLedger,
47-
isShelleyNotDisabled,
48-
isMultiAssetEnabled,
49-
isMetadataEnabled,
50-
isPlutusEnabled,
47+
isShelleyModeActive,
48+
isMultiAssetModeActive,
49+
isMetadataModeActive,
50+
isPlutusModeActive,
5151
isTxOutBootstrap,
5252
isTxOutConsumed,
5353
isTxOutPrune,
@@ -325,25 +325,25 @@ shouldUseLedger LedgerDisable = False
325325
shouldUseLedger LedgerEnable = True
326326
shouldUseLedger LedgerIgnore = False
327327

328-
isShelleyNotDisabled :: ShelleyInsertConfig -> Bool
329-
isShelleyNotDisabled ShelleyDisable = False
330-
isShelleyNotDisabled ShelleyEnable = True
331-
isShelleyNotDisabled (ShelleyStakeAddrs _) = True
328+
isShelleyModeActive :: ShelleyInsertConfig -> Bool
329+
isShelleyModeActive ShelleyDisable = False
330+
isShelleyModeActive ShelleyEnable = True
331+
isShelleyModeActive (ShelleyStakeAddrs _) = True
332332

333-
isMultiAssetEnabled :: MultiAssetConfig -> Bool
334-
isMultiAssetEnabled MultiAssetDisable = False
335-
isMultiAssetEnabled MultiAssetEnable = True
336-
isMultiAssetEnabled (MultiAssetPolicies _) = True
333+
isMultiAssetModeActive :: MultiAssetConfig -> Bool
334+
isMultiAssetModeActive MultiAssetDisable = False
335+
isMultiAssetModeActive MultiAssetEnable = True
336+
isMultiAssetModeActive (MultiAssetPolicies _) = True
337337

338-
isMetadataEnabled :: MetadataConfig -> Bool
339-
isMetadataEnabled MetadataDisable = False
340-
isMetadataEnabled MetadataEnable = True
341-
isMetadataEnabled (MetadataKeys _) = True
338+
isMetadataModeActive :: MetadataConfig -> Bool
339+
isMetadataModeActive MetadataDisable = False
340+
isMetadataModeActive MetadataEnable = True
341+
isMetadataModeActive (MetadataKeys _) = True
342342

343-
isPlutusEnabled :: PlutusConfig -> Bool
344-
isPlutusEnabled PlutusDisable = False
345-
isPlutusEnabled PlutusEnable = True
346-
isPlutusEnabled (PlutusScripts _) = True
343+
isPlutusModeActive :: PlutusConfig -> Bool
344+
isPlutusModeActive PlutusDisable = False
345+
isPlutusModeActive PlutusEnable = True
346+
isPlutusModeActive (PlutusScripts _) = True
347347

348348
-- -------------------------------------------------------------------------------------------------
349349

@@ -463,7 +463,7 @@ instance FromJSON LedgerInsertConfig where
463463
instance ToJSON ShelleyInsertConfig where
464464
toJSON cfg =
465465
Aeson.object
466-
[ "enable" .= isShelleyNotDisabled cfg
466+
[ "enable" .= isShelleyModeActive cfg
467467
, "stake_addresses" .= stakeAddrs cfg
468468
]
469469
where
@@ -485,7 +485,7 @@ instance FromJSON ShelleyInsertConfig where
485485
instance ToJSON MultiAssetConfig where
486486
toJSON cfg =
487487
Aeson.object
488-
[ "enable" .= isMultiAssetEnabled cfg
488+
[ "enable" .= isMultiAssetModeActive cfg
489489
, "policies" .= policies cfg
490490
]
491491
where
@@ -507,7 +507,7 @@ instance FromJSON MultiAssetConfig where
507507
instance ToJSON MetadataConfig where
508508
toJSON cfg =
509509
Aeson.object
510-
[ "enable" .= isMetadataEnabled cfg
510+
[ "enable" .= isMetadataModeActive cfg
511511
, "keys" .= keys cfg
512512
]
513513
where
@@ -528,7 +528,7 @@ instance FromJSON MetadataConfig where
528528
instance ToJSON PlutusConfig where
529529
toJSON cfg =
530530
Aeson.object
531-
[ "enable" .= isPlutusEnabled cfg
531+
[ "enable" .= isPlutusModeActive cfg
532532
, "script_hashes" .= scriptHashes cfg
533533
]
534534
where

cardano-db-sync/src/Cardano/DbSync/Era/Shelley/Generic/Tx/Alonzo.hs

Lines changed: 2 additions & 2 deletions
Original file line numberDiff line numberDiff line change
@@ -27,7 +27,7 @@ module Cardano.DbSync.Era.Shelley.Generic.Tx.Alonzo (
2727

2828
import qualified Cardano.Crypto.Hash as Crypto
2929
import Cardano.Db (ScriptType (..))
30-
import Cardano.DbSync.Config.Types (PlutusConfig, isPlutusEnabled)
30+
import Cardano.DbSync.Config.Types (PlutusConfig, isPlutusModeActive)
3131
import Cardano.DbSync.Era.Shelley.Generic.Metadata
3232
import Cardano.DbSync.Era.Shelley.Generic.Script (fromTimelock)
3333
import Cardano.DbSync.Era.Shelley.Generic.ScriptData (ScriptData (..))
@@ -185,7 +185,7 @@ resolveRedeemers ::
185185
(TxCert era -> Cert) ->
186186
(RedeemerMaps, [(Word64, TxRedeemer)])
187187
resolveRedeemers plutusConfig mprices tx toCert =
188-
if not $ isPlutusEnabled plutusConfig
188+
if not $ isPlutusModeActive plutusConfig
189189
then (initRedeemersMaps, [])
190190
else
191191
mkRdmrAndUpdateRec (initRedeemersMaps, []) $

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

Lines changed: 1 addition & 1 deletion
Original file line numberDiff line numberDiff line change
@@ -66,7 +66,7 @@ insertBlockUniversal syncEnv shouldLog withinTwoMins withinHalfHour blk details
6666
mPhid <- lift $ queryPoolKeyWithCache syncEnv UpdateCache $ coerceKeyRole $ Generic.blkSlotLeader blk
6767
let epochNo = sdEpochNo details
6868

69-
slid <- lift . DB.insertSlotLeader $ Generic.mkSlotLeader (isShelleyNotDisabled $ ioShelley iopts) (Generic.unKeyHashRaw $ Generic.blkSlotLeader blk) (eitherToMaybe mPhid)
69+
slid <- lift . DB.insertSlotLeader $ Generic.mkSlotLeader (isShelleyModeActive $ ioShelley iopts) (Generic.unKeyHashRaw $ Generic.blkSlotLeader blk) (eitherToMaybe mPhid)
7070
blkId <-
7171
lift . insertBlockAndCache cache $
7272
DB.Block

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

Lines changed: 4 additions & 3 deletions
Original file line numberDiff line numberDiff line change
@@ -29,7 +29,7 @@ import Cardano.DbSync.Api.Types (InsertOptions (..), SyncEnv (..))
2929
import Cardano.DbSync.Cache (queryOrInsertStakeAddress, queryPoolKeyOrInsert)
3030
import Cardano.DbSync.Cache.Types (CacheStatus, CacheUpdateAction (..))
3131
import Cardano.DbSync.Era.Conway.Insert.GovAction (insertCostModel, insertDrepDistr, updateEnacted)
32-
import Cardano.DbSync.Config.Types (isShelleyEnabled)
32+
import Cardano.DbSync.Config.Types (isShelleyModeActive)
3333
import qualified Cardano.DbSync.Era.Shelley.Generic as Generic
3434
import Cardano.DbSync.Era.Universal.Insert.Certificate (insertPots)
3535
import Cardano.DbSync.Era.Universal.Insert.GovAction (insertCostModel, insertDrepDistr, insertUpdateEnacted, updateExpired, updateRatified)
@@ -222,7 +222,7 @@ insertEpochStake syncEnv nw epochNo stakeChunk = do
222222
then
223223
( do
224224
saId <- lift $ queryOrInsertStakeAddress syncEnv cache UpdateCache nw saddr
225-
poolId <- lift $ queryPoolKeyOrInsert "insertEpochStake" syncEnv cache UpdateCache (isShelleyNotDisabled $ ioShelley iopts) pool
225+
poolId <- lift $ queryPoolKeyOrInsert "insertEpochStake" syncEnv cache UpdateCache (isShelleyModeActive $ ioShelley iopts) pool
226226
pure $
227227
Just $
228228
DB.EpochStake
@@ -285,7 +285,8 @@ insertRewards syncEnv nw earnedEpoch spendableEpoch cache rewardsChunk = do
285285
PoolKeyHash ->
286286
ExceptT SyncNodeError (ReaderT SqlBackend m) DB.PoolHashId
287287
queryPool poolHash =
288-
lift (queryPoolKeyOrInsert "insertRewards" syncEnv cache UpdateCache (isShelleyEnabled $ ioShelley iopts) poolHash)
288+
lift (queryPoolKeyOrInsert "insertRewards" syncEnv cache UpdateCache (isShelleyModeActive $ ioShelley iopts) poolHash)
289+
289290
iopts = getInsertOptions syncEnv
290291

291292
insertRewardRests ::

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

Lines changed: 12 additions & 12 deletions
Original file line numberDiff line numberDiff line change
@@ -33,7 +33,7 @@ import Cardano.DbSync.Cache (
3333
)
3434
import Cardano.DbSync.Era.Conway.Insert.GovAction (
3535
import Cardano.DbSync.Cache.Types (CacheStatus (..), CacheUpdateAction (..))
36-
import Cardano.DbSync.Config.Types (isShelleyEnabled)
36+
import Cardano.DbSync.Config.Types (isShelleyModeActive)
3737
import qualified Cardano.DbSync.Era.Shelley.Generic as Generic
3838
import Cardano.DbSync.Era.Universal.Insert.GovAction (
3939
insertCommitteeHash,
@@ -84,20 +84,20 @@ 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 (isShelleyNotDisabled $ ioShelley iopts) $ insertDelegCert syncEnv network txId idx mRedeemerId epochNo slotNo deleg
87+
when (isShelleyModeActive $ ioShelley iopts) $ insertDelegCert syncEnv network txId idx mRedeemerId epochNo slotNo deleg
8888
Left (ShelleyTxCertPool pool) ->
89-
when (isShelleyNotDisabled $ ioShelley iopts) $ insertPoolCert syncEnv cache isMember network epochNo blkId txId idx pool
89+
when (isShelleyModeActive $ ioShelley iopts) $ insertPoolCert syncEnv cache isMember network epochNo blkId txId idx pool
9090
Left (ShelleyTxCertMir mir) ->
91-
when (isShelleyNotDisabled $ ioShelley iopts) $ insertMirCert syncEnv network txId idx mir
91+
when (isShelleyModeActive $ ioShelley iopts) $ insertMirCert syncEnv network txId idx mir
9292
Left (ShelleyTxCertGenesisDeleg _gen) ->
93-
when (isShelleyNotDisabled $ ioShelley iopts) $
93+
when (isShelleyModeActive $ ioShelley iopts) $
9494
liftIO $
9595
logWarning tracer "insertCertificate: Unhandled DCertGenesis certificate"
9696
Right (ConwayTxCertDeleg deleg) ->
97-
when (isShelleyNotDisabled $ ioShelley iopts) $
97+
when (isShelleyModeActive $ ioShelley iopts) $
9898
insertConwayDelegCert syncEnv mDeposits txId idx mRedeemerId epochNo slotNo deleg
9999
Right (ConwayTxCertPool pool) ->
100-
when (isShelleyNotDisabled $ ioShelley iopts) $ insertPoolCert syncEnv cache isMember network epochNo blkId txId idx pool
100+
when (isShelleyModeActive $ ioShelley iopts) $ insertPoolCert syncEnv cache isMember network epochNo blkId txId idx pool
101101
Right (ConwayTxCertGov c) ->
102102
when (ioGov iopts) $ case c of
103103
ConwayRegDRep cred coin anchor ->
@@ -149,28 +149,28 @@ insertConwayDelegCert ::
149149
insertConwayDelegCert syncEnv mDeposits txId idx mRedeemerId epochNo slotNo dCert =
150150
case dCert of
151151
ConwayRegCert cred _dep ->
152-
when (isShelleyNotDisabled $ ioShelley iopts) $
152+
when (isShelleyModeActive $ ioShelley iopts) $
153153
insertStakeRegistration syncEnv epochNo txId idx $
154154
Generic.annotateStakingCred network cred
155155
ConwayUnRegCert cred _dep ->
156-
when (isShelleyNotDisabled $ ioShelley iopts) $
156+
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
160-
when (isShelleyNotDisabled $ ioShelley iopts) $
160+
when (isShelleyModeActive $ ioShelley iopts) $
161161
insertStakeRegistration syncEnv epochNo txId idx $
162162
Generic.annotateStakingCred network cred
163163
insertDeleg cred delegatee
164164
where
165165
insertDeleg cred = \case
166166
DelegStake poolkh ->
167-
when (isShelleyNotDisabled $ ioShelley iopts) $
167+
when (isShelleyModeActive $ ioShelley iopts) $
168168
insertDelegation syncEnv cache network epochNo slotNo txId idx mRedeemerId cred poolkh
169169
DelegVote drep ->
170170
when (ioGov iopts) $
171171
insertDelegationVote syncEnv network txId idx cred drep
172172
DelegStakeVote poolkh drep -> do
173-
when (isShelleyNotDisabled $ ioShelley iopts) $
173+
when (isShelleyModeActive $ ioShelley iopts) $
174174
insertDelegation syncEnv cache network epochNo slotNo txId idx mRedeemerId cred poolkh
175175
when (ioGov iopts) $
176176
insertDelegationVote syncEnv network txId idx cred drep

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

Lines changed: 37 additions & 33 deletions
Original file line numberDiff line numberDiff line change
@@ -68,6 +68,7 @@ import qualified Data.Map.Strict as Map
6868
import qualified Data.Text.Encoding as Text
6969
import Database.Persist.Sql (SqlBackend)
7070
import Ouroboros.Consensus.Cardano.Block (StandardConway, StandardCrypto)
71+
import Prelude (zip3)
7172

7273
insertGovActionProposal ::
7374
forall m.
@@ -286,48 +287,51 @@ insertVotingProcedures ::
286287
(MonadIO m, MonadBaseControl IO m) =>
287288
SyncEnv ->
288289
DB.TxId ->
290+
[ProposalProcedure StandardConway] ->
289291
(Voter StandardCrypto, [(GovActionId StandardCrypto, VotingProcedure StandardConway)]) ->
290292
ExceptT SyncNodeError (ReaderT SqlBackend m) ()
291-
insertVotingProcedures syncEnv txId (voter, actions) =
292-
mapM_ (insertVotingProcedure syncEnv txId voter) (zip [0 ..] actions)
293+
insertVotingProcedures syncEnv txId proposalPs (voter, actions) =
294+
mapM_ (insertVotingProcedure syncEnv txId voter) (zip3 [0 ..] actions proposalPs)
293295

294296
insertVotingProcedure ::
295297
(MonadIO m, MonadBaseControl IO m) =>
296298
SyncEnv ->
297299
DB.TxId ->
298300
Voter StandardCrypto ->
299-
(Word16, (GovActionId StandardCrypto, VotingProcedure StandardConway)) ->
301+
(Word16, (GovActionId StandardCrypto, VotingProcedure StandardConway), ProposalProcedure StandardConway) ->
300302
ExceptT SyncNodeError (ReaderT SqlBackend m) ()
301-
insertVotingProcedure syncEnv txId voter (index, (gaId, vp)) = do
302-
maybeGovActionId <- resolveGovActionProposal syncEnv gaId
303-
case maybeGovActionId of
304-
Nothing -> pure ()
305-
Just govActionId -> do
306-
votingAnchorId <- whenMaybe (strictMaybeToMaybe $ vProcAnchor vp) $ lift . insertVotingAnchor txId DB.OtherAnchor
307-
(mCommitteeVoterId, mDRepVoter, mStakePoolVoter) <- case voter of
308-
CommitteeVoter cred -> do
309-
khId <- lift $ insertCommitteeHash cred
310-
pure (Just khId, Nothing, Nothing)
311-
DRepVoter cred -> do
312-
drep <- lift $ insertCredDrepHash cred
313-
pure (Nothing, Just drep, Nothing)
314-
StakePoolVoter poolkh -> do
315-
poolHashId <- lift $ queryPoolKeyOrInsert "insertVotingProcedure" syncEnv (envCache syncEnv) UpdateCache False poolkh
316-
pure (Nothing, Nothing, Just poolHashId)
317-
void
318-
. lift
319-
. DB.insertVotingProcedure
320-
$ DB.VotingProcedure
321-
{ DB.votingProcedureTxId = txId
322-
, DB.votingProcedureIndex = index
323-
, DB.votingProcedureGovActionProposalId = govActionId
324-
, DB.votingProcedureCommitteeVoter = mCommitteeVoterId
325-
, DB.votingProcedureDrepVoter = mDRepVoter
326-
, DB.votingProcedurePoolVoter = mStakePoolVoter
327-
, DB.votingProcedureVoterRole = Generic.toVoterRole voter
328-
, DB.votingProcedureVote = Generic.toVote $ vProcVote vp
329-
, DB.votingProcedureVotingAnchorId = votingAnchorId
330-
}
303+
insertVotingProcedure syncEnv txId voter (index, (gaId, vp), proposalP) = do
304+
-- check if shelley stake address is in the whitelist
305+
when (shelleyStakeAddrWhitelistCheck syncEnv $ pProcReturnAddr proposalP) $ do
306+
maybeGovActionId <- resolveGovActionProposal syncEnv gaId
307+
case maybeGovActionId of
308+
Nothing -> pure ()
309+
Just govActionId -> do
310+
votingAnchorId <- whenMaybe (strictMaybeToMaybe $ vProcAnchor vp) $ lift . insertVotingAnchor txId DB.OtherAnchor
311+
(mCommitteeVoterId, mDRepVoter, mStakePoolVoter) <- case voter of
312+
CommitteeVoter cred -> do
313+
khId <- lift $ insertCommitteeHash cred
314+
pure (Just khId, Nothing, Nothing)
315+
DRepVoter cred -> do
316+
drep <- lift $ insertCredDrepHash cred
317+
pure (Nothing, Just drep, Nothing)
318+
StakePoolVoter poolkh -> do
319+
poolHashId <- lift $ queryPoolKeyOrInsert "insertVotingProcedure" syncEnv (envCache syncEnv) UpdateCache False poolkh
320+
pure (Nothing, Nothing, Just poolHashId)
321+
void
322+
. lift
323+
. DB.insertVotingProcedure
324+
$ DB.VotingProcedure
325+
{ DB.votingProcedureTxId = txId
326+
, DB.votingProcedureIndex = index
327+
, DB.votingProcedureGovActionProposalId = govActionId
328+
, DB.votingProcedureCommitteeVoter = mCommitteeVoterId
329+
, DB.votingProcedureDrepVoter = mDRepVoter
330+
, DB.votingProcedurePoolVoter = mStakePoolVoter
331+
, DB.votingProcedureVoterRole = Generic.toVoterRole voter
332+
, DB.votingProcedureVote = Generic.toVote $ vProcVote vp
333+
, DB.votingProcedureVotingAnchorId = votingAnchorId
334+
}
331335

332336
insertVotingAnchor :: (MonadIO m, MonadBaseControl IO m) => DB.BlockId -> DB.AnchorType -> Anchor StandardCrypto -> ReaderT SqlBackend m DB.VotingAnchorId
333337
insertVotingAnchor blockId anchorType anchor =

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

Lines changed: 22 additions & 17 deletions
Original file line numberDiff line numberDiff line change
@@ -29,7 +29,7 @@ import Cardano.DbSync.Era.Universal.Insert.Grouped
2929
import Cardano.DbSync.Era.Util (safeDecodeToJson)
3030
import Cardano.DbSync.Error
3131
import Cardano.DbSync.Util
32-
import Cardano.DbSync.Util.Whitelist (shelleyStakeAddrWhitelistCheck)
32+
import Cardano.DbSync.Util.Whitelist (isSimplePlutusScriptHashInWhitelist, shelleyStakeAddrWhitelistCheck)
3333
import qualified Cardano.Ledger.Address as Ledger
3434
import qualified Cardano.Ledger.BaseTypes as Ledger
3535
import Cardano.Ledger.Coin (Coin (..))
@@ -206,22 +206,27 @@ insertScript ::
206206
SyncEnv ->
207207
DB.TxId ->
208208
Generic.TxScript ->
209-
ReaderT SqlBackend m DB.ScriptId
210-
insertScript syncEnv txId script = do
211-
mScriptId <- DB.queryScript $ Generic.txScriptHash script
212-
case mScriptId of
213-
Just scriptId -> pure scriptId
214-
Nothing -> do
215-
json <- scriptConvert script
216-
DB.insertScript $
217-
DB.Script
218-
{ DB.scriptTxId = txId
219-
, DB.scriptHash = Generic.txScriptHash script
220-
, DB.scriptType = Generic.txScriptType script
221-
, DB.scriptSerialisedSize = Generic.txScriptPlutusSize script
222-
, DB.scriptJson = json
223-
, DB.scriptBytes = Generic.txScriptCBOR script
224-
}
209+
ReaderT SqlBackend m (Maybe DB.ScriptId)
210+
insertScript syncEnv txId script =
211+
if isSimplePlutusScriptHashInWhitelist syncEnv $ Generic.txScriptHash script
212+
then do
213+
mScriptId <- DB.queryScript $ Generic.txScriptHash script
214+
case mScriptId of
215+
Just scriptId -> pure $ Just scriptId
216+
Nothing -> do
217+
json <- scriptConvert script
218+
mInScript <-
219+
DB.insertScript $
220+
DB.Script
221+
{ DB.scriptTxId = txId
222+
, DB.scriptHash = Generic.txScriptHash script
223+
, DB.scriptType = Generic.txScriptType script
224+
, DB.scriptSerialisedSize = Generic.txScriptPlutusSize script
225+
, DB.scriptJson = json
226+
, DB.scriptBytes = Generic.txScriptCBOR script
227+
}
228+
pure $ Just mInScript
229+
else pure Nothing
225230
where
226231
scriptConvert :: (MonadIO m) => Generic.TxScript -> m (Maybe Text)
227232
scriptConvert s =

0 commit comments

Comments
 (0)