Skip to content

Commit 99fa0a2

Browse files
committed
changes to plutus whitelist
1 parent 62f890a commit 99fa0a2

File tree

10 files changed

+147
-146
lines changed

10 files changed

+147
-146
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: 2 additions & 2 deletions
Original file line numberDiff line numberDiff line change
@@ -18,7 +18,7 @@ import Cardano.DbSync.Api.Types (InsertOptions (..), SyncEnv (..), SyncOptions (
1818
import Cardano.DbSync.Cache (insertBlockAndCache, queryPoolKeyWithCache, queryPrevBlockWithCache)
1919
import Cardano.DbSync.Cache.Epoch (writeEpochBlockDiffToCache)
2020
import Cardano.DbSync.Cache.Types (Cache (..), CacheNew (..), EpochBlockDiff (..))
21-
import Cardano.DbSync.Config.Types (isShelleyNotDisabled)
21+
import Cardano.DbSync.Config.Types (isShelleyModeActive)
2222
import qualified Cardano.DbSync.Era.Shelley.Generic as Generic
2323
import Cardano.DbSync.Era.Universal.Epoch
2424
import Cardano.DbSync.Era.Universal.Insert.Grouped
@@ -66,7 +66,7 @@ insertBlockUniversal syncEnv shouldLog withinTwoMins withinHalfHour blk details
6666
mPhid <- lift $ queryPoolKeyWithCache syncEnv CacheNew $ 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: 3 additions & 3 deletions
Original file line numberDiff line numberDiff line change
@@ -28,7 +28,7 @@ import Cardano.DbSync.Api
2828
import Cardano.DbSync.Api.Types (InsertOptions (..), SyncEnv (..))
2929
import Cardano.DbSync.Cache (queryOrInsertStakeAddress, queryPoolKeyOrInsert)
3030
import Cardano.DbSync.Cache.Types (Cache, CacheNew (..))
31-
import Cardano.DbSync.Config.Types (isShelleyNotDisabled)
31+
import Cardano.DbSync.Config.Types (isShelleyModeActive)
3232
import qualified Cardano.DbSync.Era.Shelley.Generic as Generic
3333
import Cardano.DbSync.Era.Universal.Insert.Certificate (insertPots)
3434
import Cardano.DbSync.Era.Universal.Insert.GovAction (insertCostModel, insertDrepDistr, updateEnacted, updateExpired, updateRatified)
@@ -221,7 +221,7 @@ insertEpochStake syncEnv nw epochNo stakeChunk = do
221221
then
222222
( do
223223
saId <- lift $ queryOrInsertStakeAddress syncEnv cache CacheNew nw saddr
224-
poolId <- lift $ queryPoolKeyOrInsert "insertEpochStake" syncEnv cache CacheNew (isShelleyNotDisabled $ ioShelley iopts) pool
224+
poolId <- lift $ queryPoolKeyOrInsert "insertEpochStake" syncEnv cache CacheNew (isShelleyModeActive $ ioShelley iopts) pool
225225
pure $
226226
Just $
227227
DB.EpochStake
@@ -285,7 +285,7 @@ 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 CacheNew (isShelleyNotDisabled $ ioShelley iopts) poolHash)
288+
lift (queryPoolKeyOrInsert "insertRewards" syncEnv cache CacheNew (isShelleyModeActive $ ioShelley iopts) poolHash)
289289

290290
iopts = getInsertOptions syncEnv
291291

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

Lines changed: 13 additions & 17 deletions
Original file line numberDiff line numberDiff line change
@@ -32,7 +32,7 @@ import Cardano.DbSync.Cache (
3232
queryPoolKeyOrInsert,
3333
)
3434
import Cardano.DbSync.Cache.Types (Cache, CacheNew (..))
35-
import Cardano.DbSync.Config.Types (isShelleyNotDisabled)
35+
import Cardano.DbSync.Config.Types (isShelleyModeActive)
3636
import qualified Cardano.DbSync.Era.Shelley.Generic as Generic
3737
import Cardano.DbSync.Era.Universal.Insert.GovAction (
3838
insertCommitteeHash,
@@ -83,24 +83,20 @@ 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 (isShelleyNotDisabled $ ioShelley iopts) $ insertDelegCert syncEnv network txId idx mRedeemerId epochNo slotNo deleg
86+
when (isShelleyModeActive $ ioShelley iopts) $ insertDelegCert syncEnv network txId idx mRedeemerId epochNo slotNo deleg
8787
Left (ShelleyTxCertPool pool) ->
88-
when (isShelleyNotDisabled $ ioShelley iopts) $ insertPoolCert syncEnv cache isMember network epochNo blkId txId idx pool
88+
when (isShelleyModeActive $ ioShelley iopts) $ insertPoolCert syncEnv cache isMember network epochNo blkId txId idx pool
8989
Left (ShelleyTxCertMir mir) ->
90-
when (isShelleyNotDisabled $ ioShelley iopts) $ insertMirCert syncEnv network txId idx mir
90+
when (isShelleyModeActive $ ioShelley iopts) $ insertMirCert syncEnv network txId idx mir
9191
Left (ShelleyTxCertGenesisDeleg _gen) ->
92-
when (isShelleyNotDisabled $ ioShelley iopts) $
92+
when (isShelleyModeActive $ ioShelley iopts) $
9393
liftIO $
9494
logWarning tracer "insertCertificate: Unhandled DCertGenesis certificate"
9595
Right (ConwayTxCertDeleg deleg) ->
96-
<<<<<<< HEAD
97-
insertConwayDelegCert syncEnv mDeposits txId idx mRedeemerId epochNo slotNo deleg
98-
=======
99-
when (isShelleyNotDisabled $ ioShelley iopts) $
100-
insertConwayDelegCert syncEnv txId idx mRedeemerId epochNo slotNo deleg
101-
>>>>>>> 78b028ed (rework shelley stake address whitelist)
96+
when (isShelleyModeActive $ ioShelley iopts) $
97+
insertConwayDelegCert syncEnv mDeposits txId idx mRedeemerId epochNo slotNo deleg
10298
Right (ConwayTxCertPool pool) ->
103-
when (isShelleyNotDisabled $ ioShelley iopts) $ insertPoolCert syncEnv cache isMember network epochNo blkId txId idx pool
99+
when (isShelleyModeActive $ ioShelley iopts) $ insertPoolCert syncEnv cache isMember network epochNo blkId txId idx pool
104100
Right (ConwayTxCertGov c) ->
105101
when (ioGov iopts) $ case c of
106102
ConwayRegDRep cred coin anchor ->
@@ -152,28 +148,28 @@ insertConwayDelegCert ::
152148
insertConwayDelegCert syncEnv mDeposits txId idx mRedeemerId epochNo slotNo dCert =
153149
case dCert of
154150
ConwayRegCert cred _dep ->
155-
when (isShelleyNotDisabled $ ioShelley iopts) $
151+
when (isShelleyModeActive $ ioShelley iopts) $
156152
insertStakeRegistration syncEnv epochNo txId idx $
157153
Generic.annotateStakingCred network cred
158154
ConwayUnRegCert cred _dep ->
159-
when (isShelleyNotDisabled $ ioShelley iopts) $
155+
when (isShelleyModeActive $ ioShelley iopts) $
160156
insertStakeDeregistration syncEnv network epochNo txId idx mRedeemerId cred
161157
ConwayDelegCert cred delegatee -> insertDeleg cred delegatee
162158
ConwayRegDelegCert cred delegatee _dep -> do
163-
when (isShelleyNotDisabled $ ioShelley iopts) $
159+
when (isShelleyModeActive $ ioShelley iopts) $
164160
insertStakeRegistration syncEnv epochNo txId idx $
165161
Generic.annotateStakingCred network cred
166162
insertDeleg cred delegatee
167163
where
168164
insertDeleg cred = \case
169165
DelegStake poolkh ->
170-
when (isShelleyNotDisabled $ ioShelley iopts) $
166+
when (isShelleyModeActive $ ioShelley iopts) $
171167
insertDelegation syncEnv cache network epochNo slotNo txId idx mRedeemerId cred poolkh
172168
DelegVote drep ->
173169
when (ioGov iopts) $
174170
insertDelegationVote syncEnv network txId idx cred drep
175171
DelegStakeVote poolkh drep -> do
176-
when (isShelleyNotDisabled $ ioShelley iopts) $
172+
when (isShelleyModeActive $ ioShelley iopts) $
177173
insertDelegation syncEnv cache network epochNo slotNo txId idx mRedeemerId cred poolkh
178174
when (ioGov iopts) $
179175
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
@@ -67,6 +67,7 @@ import qualified Data.Map.Strict as Map
6767
import qualified Data.Text.Encoding as Text
6868
import Database.Persist.Sql (SqlBackend)
6969
import Ouroboros.Consensus.Cardano.Block (StandardConway, StandardCrypto)
70+
import Prelude (zip3)
7071

7172
insertGovActionProposal ::
7273
forall m.
@@ -283,48 +284,51 @@ insertVotingProcedures ::
283284
(MonadIO m, MonadBaseControl IO m) =>
284285
SyncEnv ->
285286
DB.TxId ->
287+
[ProposalProcedure StandardConway] ->
286288
(Voter StandardCrypto, [(GovActionId StandardCrypto, VotingProcedure StandardConway)]) ->
287289
ExceptT SyncNodeError (ReaderT SqlBackend m) ()
288-
insertVotingProcedures syncEnv txId (voter, actions) =
289-
mapM_ (insertVotingProcedure syncEnv txId voter) (zip [0 ..] actions)
290+
insertVotingProcedures syncEnv txId proposalPs (voter, actions) =
291+
mapM_ (insertVotingProcedure syncEnv txId voter) (zip3 [0 ..] actions proposalPs)
290292

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

329333
insertVotingAnchor :: (MonadIO m, MonadBaseControl IO m) => DB.TxId -> DB.AnchorType -> Anchor StandardCrypto -> ReaderT SqlBackend m DB.VotingAnchorId
330334
insertVotingAnchor txId 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 (..))
@@ -205,22 +205,27 @@ insertScript ::
205205
SyncEnv ->
206206
DB.TxId ->
207207
Generic.TxScript ->
208-
ReaderT SqlBackend m DB.ScriptId
209-
insertScript syncEnv txId script = do
210-
mScriptId <- DB.queryScript $ Generic.txScriptHash script
211-
case mScriptId of
212-
Just scriptId -> pure scriptId
213-
Nothing -> do
214-
json <- scriptConvert script
215-
DB.insertScript $
216-
DB.Script
217-
{ DB.scriptTxId = txId
218-
, DB.scriptHash = Generic.txScriptHash script
219-
, DB.scriptType = Generic.txScriptType script
220-
, DB.scriptSerialisedSize = Generic.txScriptPlutusSize script
221-
, DB.scriptJson = json
222-
, DB.scriptBytes = Generic.txScriptCBOR script
223-
}
208+
ReaderT SqlBackend m (Maybe DB.ScriptId)
209+
insertScript syncEnv txId script =
210+
if isSimplePlutusScriptHashInWhitelist syncEnv $ Generic.txScriptHash script
211+
then do
212+
mScriptId <- DB.queryScript $ Generic.txScriptHash script
213+
case mScriptId of
214+
Just scriptId -> pure $ Just scriptId
215+
Nothing -> do
216+
json <- scriptConvert script
217+
mInScript <-
218+
DB.insertScript $
219+
DB.Script
220+
{ DB.scriptTxId = txId
221+
, DB.scriptHash = Generic.txScriptHash script
222+
, DB.scriptType = Generic.txScriptType script
223+
, DB.scriptSerialisedSize = Generic.txScriptPlutusSize script
224+
, DB.scriptJson = json
225+
, DB.scriptBytes = Generic.txScriptCBOR script
226+
}
227+
pure $ Just mInScript
228+
else pure Nothing
224229
where
225230
scriptConvert :: (MonadIO m) => Generic.TxScript -> m (Maybe Text)
226231
scriptConvert s =

0 commit comments

Comments
 (0)