diff --git a/cardano-chain-gen/test/Test/Cardano/Db/Mock/Config.hs b/cardano-chain-gen/test/Test/Cardano/Db/Mock/Config.hs index 12e512b70..7442ebb30 100644 --- a/cardano-chain-gen/test/Test/Cardano/Db/Mock/Config.hs +++ b/cardano-chain-gen/test/Test/Cardano/Db/Mock/Config.hs @@ -17,9 +17,24 @@ module Test.Cardano.Db.Mock.Config ( fingerprintRoot, getDBSyncPGPass, getPoolLayer, + + -- * Configs mkConfig, mkSyncNodeConfig, mkConfigDir, + configPruneForceTxIn, + configPrune, + configConsume, + configBootstrap, + configPlutusDisable, + configMultiAssetsDisable, + configShelleyDisable, + configRemoveJsonFromSchema, + configRemoveJsonFromSchemaFalse, + configLedgerIgnore, + configMetadataEnable, + configMetadataDisable, + configMetadataKeys, mkFingerPrint, mkMutableDir, mkDBSyncEnv, @@ -50,13 +65,14 @@ import qualified Cardano.Db as Db import Cardano.DbSync import Cardano.DbSync.Config import Cardano.DbSync.Config.Cardano +import Cardano.DbSync.Config.Types import Cardano.DbSync.Error (runOrThrowIO) import Cardano.DbSync.Types (CardanoBlock, MetricSetters (..)) import Cardano.Mock.ChainSync.Server import Cardano.Mock.Forging.Interpreter import Cardano.Node.Protocol.Shelley (readLeaderCredentials) import Cardano.Node.Types (ProtocolFilepaths (..)) -import Cardano.Prelude (ReaderT, panic, stderr, textShow) +import Cardano.Prelude (NonEmpty ((:|)), ReaderT, panic, stderr, textShow) import Cardano.SMASH.Server.PoolDataLayer import Control.Concurrent.Async (Async, async, cancel, poll) import Control.Concurrent.STM (atomically) @@ -116,7 +132,6 @@ data CommandLineArgs = CommandLineArgs , claFullMode :: Bool , claMigrateConsumed :: Bool , claPruneTxOut :: Bool - , claBootstrap :: Bool } data WithConfigArgs = WithConfigArgs @@ -279,10 +294,65 @@ mkSyncNodeParams staticDir mutableDir CommandLineArgs {..} = do , enpMaybeRollback = Nothing } +------------------------------------------------------------------------------ +-- Custom Configs +------------------------------------------------------------------------------ mkConfigFile :: FilePath -> FilePath -> ConfigFile mkConfigFile staticDir cliConfigFilename = ConfigFile $ staticDir cliConfigFilename +configPruneForceTxIn :: SyncNodeConfig -> SyncNodeConfig +configPruneForceTxIn cfg = do + cfg {dncInsertOptions = (dncInsertOptions cfg) {sioTxOut = TxOutPrune (ForceTxIn True)}} + +configPrune :: SyncNodeConfig -> SyncNodeConfig +configPrune cfg = do + cfg {dncInsertOptions = (dncInsertOptions cfg) {sioTxOut = TxOutPrune (ForceTxIn False)}} + +configConsume :: SyncNodeConfig -> SyncNodeConfig +configConsume cfg = do + cfg {dncInsertOptions = (dncInsertOptions cfg) {sioTxOut = TxOutConsumed (ForceTxIn False)}} + +configBootstrap :: SyncNodeConfig -> SyncNodeConfig +configBootstrap cfg = do + cfg {dncInsertOptions = (dncInsertOptions cfg) {sioTxOut = TxOutBootstrap (ForceTxIn False)}} + +configPlutusDisable :: SyncNodeConfig -> SyncNodeConfig +configPlutusDisable cfg = do + cfg {dncInsertOptions = (dncInsertOptions cfg) {sioPlutus = PlutusDisable}} + +configMultiAssetsDisable :: SyncNodeConfig -> SyncNodeConfig +configMultiAssetsDisable cfg = do + cfg {dncInsertOptions = (dncInsertOptions cfg) {sioMultiAsset = MultiAssetDisable}} + +configShelleyDisable :: SyncNodeConfig -> SyncNodeConfig +configShelleyDisable cfg = do + cfg {dncInsertOptions = (dncInsertOptions cfg) {sioShelley = ShelleyDisable}} + +configRemoveJsonFromSchema :: SyncNodeConfig -> SyncNodeConfig +configRemoveJsonFromSchema cfg = do + cfg {dncInsertOptions = (dncInsertOptions cfg) {sioRemoveJsonbFromSchema = RemoveJsonbFromSchemaConfig True}} + +configRemoveJsonFromSchemaFalse :: SyncNodeConfig -> SyncNodeConfig +configRemoveJsonFromSchemaFalse cfg = do + cfg {dncInsertOptions = (dncInsertOptions cfg) {sioRemoveJsonbFromSchema = RemoveJsonbFromSchemaConfig False}} + +configLedgerIgnore :: SyncNodeConfig -> SyncNodeConfig +configLedgerIgnore cfg = do + cfg {dncInsertOptions = (dncInsertOptions cfg) {sioLedger = LedgerIgnore}} + +configMetadataEnable :: SyncNodeConfig -> SyncNodeConfig +configMetadataEnable cfg = do + cfg {dncInsertOptions = (dncInsertOptions cfg) {sioMetadata = MetadataEnable}} + +configMetadataDisable :: SyncNodeConfig -> SyncNodeConfig +configMetadataDisable cfg = do + cfg {dncInsertOptions = (dncInsertOptions cfg) {sioMetadata = MetadataDisable}} + +configMetadataKeys :: SyncNodeConfig -> SyncNodeConfig +configMetadataKeys cfg = do + cfg {dncInsertOptions = (dncInsertOptions cfg) {sioMetadata = MetadataKeys $ 1 :| []}} + initCommandLineArgs :: CommandLineArgs initCommandLineArgs = CommandLineArgs @@ -301,7 +371,6 @@ initCommandLineArgs = , claFullMode = True , claMigrateConsumed = False , claPruneTxOut = False - , claBootstrap = False } emptyMetricsSetters :: MetricSetters @@ -377,7 +446,7 @@ withFullConfigAndLogs = withCustomConfig :: CommandLineArgs -> -- | custom SyncNodeConfig - Maybe SyncNodeConfig -> + Maybe (SyncNodeConfig -> SyncNodeConfig) -> -- | config filepath FilePath -> -- | test label @@ -398,7 +467,7 @@ withCustomConfig = withCustomConfigAndDropDB :: CommandLineArgs -> -- | custom SyncNodeConfig - Maybe SyncNodeConfig -> + Maybe (SyncNodeConfig -> SyncNodeConfig) -> -- | config filepath FilePath -> -- | test label @@ -420,7 +489,7 @@ withCustomConfigAndDropDB = withCustomConfigAndLogs :: CommandLineArgs -> -- | custom SyncNodeConfig - Maybe SyncNodeConfig -> + Maybe (SyncNodeConfig -> SyncNodeConfig) -> -- | config filepath FilePath -> -- | test label @@ -441,7 +510,7 @@ withCustomConfigAndLogs = withCustomConfigAndLogsAndDropDB :: CommandLineArgs -> -- | custom SyncNodeConfig - Maybe SyncNodeConfig -> + Maybe (SyncNodeConfig -> SyncNodeConfig) -> -- | config filepath FilePath -> -- | test label @@ -463,7 +532,7 @@ withFullConfig' :: WithConfigArgs -> CommandLineArgs -> -- | custom SyncNodeConfig - Maybe SyncNodeConfig -> + Maybe (SyncNodeConfig -> SyncNodeConfig) -> -- | config filepath FilePath -> -- | test label @@ -477,7 +546,9 @@ withFullConfig' WithConfigArgs {..} cmdLineArgs mSyncNodeConfig configFilePath t -- check if custom syncNodeConfigs have been passed or not syncNodeConfig <- case mSyncNodeConfig of - Just snc -> pure snc + Just updateFn -> do + initConfigFile <- mkSyncNodeConfig configFilePath cmdLineArgs + pure $ updateFn initConfigFile Nothing -> mkSyncNodeConfig configFilePath cmdLineArgs cfg <- mkConfig configFilePath mutableDir cmdLineArgs syncNodeConfig diff --git a/cardano-chain-gen/test/Test/Cardano/Db/Mock/Unit/Babbage/Config/MigrateConsumedPruneTxOut.hs b/cardano-chain-gen/test/Test/Cardano/Db/Mock/Unit/Babbage/Config/MigrateConsumedPruneTxOut.hs index e392e2ff1..55db4e6c9 100644 --- a/cardano-chain-gen/test/Test/Cardano/Db/Mock/Unit/Babbage/Config/MigrateConsumedPruneTxOut.hs +++ b/cardano-chain-gen/test/Test/Cardano/Db/Mock/Unit/Babbage/Config/MigrateConsumedPruneTxOut.hs @@ -21,7 +21,6 @@ module Test.Cardano.Db.Mock.Unit.Babbage.Config.MigrateConsumedPruneTxOut ( ) where import qualified Cardano.Db as DB -import Cardano.DbSync.Config.Types import Cardano.Mock.ChainSync.Server (IOManager, addBlock) import Cardano.Mock.Forging.Interpreter (forgeNext) import qualified Cardano.Mock.Forging.Tx.Babbage as Babbage @@ -32,10 +31,12 @@ import Control.Monad (void) import Data.Text (Text) import Ouroboros.Consensus.Block (blockPoint) import Test.Cardano.Db.Mock.Config ( - CommandLineArgs (..), babbageConfigDir, + configBootstrap, + configConsume, + configPrune, + configPruneForceTxIn, initCommandLineArgs, - mkSyncNodeConfig, replaceConfigFile, startDBSync, stopDBSync, @@ -54,9 +55,12 @@ import Test.Cardano.Db.Mock.UnifiedApi ( import Test.Cardano.Db.Mock.Validate (assertBlockNoBackoff, assertEqQuery, assertTxCount, assertTxInCount, assertTxOutCount, assertUnspentTx, checkStillRuns) import Test.Tasty.HUnit (Assertion) +------------------------------------------------------------------------------ +-- Tests +------------------------------------------------------------------------------ txConsumedColumnCheck :: IOManager -> [(Text, Text)] -> Assertion txConsumedColumnCheck = do - withCustomConfigAndDropDB cmdLineArgs Nothing babbageConfigDir testLabel $ \interpreter mockServer dbSyncEnv -> do + withCustomConfigAndDropDB cmdLineArgs (Just configConsume) babbageConfigDir testLabel $ \interpreter mockServer dbSyncEnv -> do void $ withBabbageFindLeaderAndSubmitTx interpreter mockServer $ Babbage.mkPaymentTx (UTxOIndex 0) (UTxOIndex 1) 10000 500 @@ -65,15 +69,12 @@ txConsumedColumnCheck = do assertBlockNoBackoff dbSyncEnv 1 assertEqQuery dbSyncEnv DB.queryTxConsumedColumnExists True "missing consumed_by_tx_id column when flag --consumed-tx-out active" where - cmdLineArgs = - initCommandLineArgs - { claConfigFilename = "test-db-sync-config-consumed.json" - } + cmdLineArgs = initCommandLineArgs testLabel = "configTxConsumedColumnCheck" basicPrune :: IOManager -> [(Text, Text)] -> Assertion basicPrune = do - withCustomConfig cmdLineArgs Nothing babbageConfigDir testLabel $ \interpreter mockServer dbSyncEnv -> do + withCustomConfig cmdLineArgs (Just configPruneForceTxIn) babbageConfigDir testLabel $ \interpreter mockServer dbSyncEnv -> do startDBSync dbSyncEnv -- add 50 block b1 <- forgeAndSubmitBlocks interpreter mockServer 50 @@ -92,15 +93,12 @@ basicPrune = do -- check Unspent tx match after pruning assertUnspentTx dbSyncEnv where - cmdLineArgs = - initCommandLineArgs - { claConfigFilename = "test-db-sync-config-prune.json" - } + cmdLineArgs = initCommandLineArgs testLabel = "configPrune" pruneWithSimpleRollback :: IOManager -> [(Text, Text)] -> Assertion pruneWithSimpleRollback = do - withCustomConfig cmdLineArgs Nothing babbageConfigDir testLabel $ \interpreter mockServer dbSyncEnv -> do + withCustomConfig cmdLineArgs (Just configPruneForceTxIn) babbageConfigDir testLabel $ \interpreter mockServer dbSyncEnv -> do blk0 <- forgeNext interpreter mockBlock0 blk1 <- forgeNext interpreter mockBlock1 atomically $ addBlock mockServer blk0 @@ -120,15 +118,12 @@ pruneWithSimpleRollback = do assertBlockNoBackoff dbSyncEnv $ fullBlockSize b1 where fullBlockSize b = fromIntegral $ length b + 4 - cmdLineArgs = - initCommandLineArgs - { claConfigFilename = "test-db-sync-config-prune.json" - } + cmdLineArgs = initCommandLineArgs testLabel = "configPruneSimpleRollback" pruneWithFullTxRollback :: IOManager -> [(Text, Text)] -> Assertion pruneWithFullTxRollback = do - withCustomConfig cmdLineArgs Nothing babbageConfigDir testLabel $ \interpreter mockServer dbSyncEnv -> do + withCustomConfig cmdLineArgs (Just configPruneForceTxIn) babbageConfigDir testLabel $ \interpreter mockServer dbSyncEnv -> do startDBSync dbSyncEnv blk0 <- forgeNextFindLeaderAndSubmit interpreter mockServer [] void $ withBabbageFindLeaderAndSubmit interpreter mockServer $ \st -> do @@ -150,19 +145,14 @@ pruneWithFullTxRollback = do assertEqQuery dbSyncEnv DB.queryTxOutCount 16 "new epoch didn't prune tx_out column that are null" assertUnspentTx dbSyncEnv where - cmdLineArgs = - initCommandLineArgs - { claConfigFilename = "test-db-sync-config-prune.json" - } + cmdLineArgs = initCommandLineArgs testLabel = "configPruneOnFullRollback" -- The tx in the last, 2 x securityParam worth of blocks should not be pruned. -- In these tests, 2 x securityParam = 20 blocks. pruningShouldKeepSomeTx :: IOManager -> [(Text, Text)] -> Assertion -pruningShouldKeepSomeTx ioManager names = do - syncNodeConfig <- mkSyncNodeConfig' - - withConfig' syncNodeConfig $ \interpreter mockServer dbSyncEnv -> do +pruningShouldKeepSomeTx = do + withCustomConfig cmdLineArgs (Just configPrune) babbageConfigDir testLabel $ \interpreter mockServer dbSyncEnv -> do startDBSync dbSyncEnv b1 <- forgeAndSubmitBlocks interpreter mockServer 80 -- these two blocs + tx will fall withing the last 20 blocks so should not be pruned @@ -179,30 +169,13 @@ pruningShouldKeepSomeTx ioManager names = do assertTxInCount dbSyncEnv 0 assertEqQuery dbSyncEnv DB.queryTxOutConsumedCount 0 "Unexpected TxOutConsumedByTxId count after prune" where - withConfig' cfg f = - withCustomConfig cmdLineArgs (Just cfg) babbageConfigDir testLabel f ioManager names - - mkSyncNodeConfig' :: IO SyncNodeConfig - mkSyncNodeConfig' = do - initCfg <- mkSyncNodeConfig babbageConfigDir cmdLineArgs - pure $ - initCfg - { dncInsertOptions = - (dncInsertOptions initCfg) - { sioTxOut = TxOutPrune (ForceTxIn False) - } - } - - cmdLineArgs = - initCommandLineArgs - { claConfigFilename = "test-db-sync-config-prune.json" - } + cmdLineArgs = initCommandLineArgs testLabel = "configPruneCorrectAmount" -- prune with rollback pruneAndRollBackOneBlock :: IOManager -> [(Text, Text)] -> Assertion pruneAndRollBackOneBlock = do - withCustomConfig cmdLineArgs Nothing babbageConfigDir testLabel $ \interpreter mockServer dbSyncEnv -> do + withCustomConfig cmdLineArgs (Just configPruneForceTxIn) babbageConfigDir testLabel $ \interpreter mockServer dbSyncEnv -> do startDBSync dbSyncEnv void $ forgeAndSubmitBlocks interpreter mockServer 98 -- add 2 blocks with tx @@ -228,16 +201,13 @@ pruneAndRollBackOneBlock = do -- everything should be pruned assertEqQuery dbSyncEnv DB.queryTxOutConsumedCount 0 "Unexpected TxOutConsumedByTxId count after rollback" where - cmdLineArgs = - initCommandLineArgs - { claConfigFilename = "test-db-sync-config-prune.json" - } + cmdLineArgs = initCommandLineArgs testLabel = "configPruneAndRollBack" -- consume with rollback noPruneAndRollBack :: IOManager -> [(Text, Text)] -> Assertion noPruneAndRollBack = do - withCustomConfig cmdLineArgs Nothing babbageConfigDir testLabel $ \interpreter mockServer dbSyncEnv -> do + withCustomConfig cmdLineArgs (Just configConsume) babbageConfigDir testLabel $ \interpreter mockServer dbSyncEnv -> do startDBSync dbSyncEnv void $ forgeAndSubmitBlocks interpreter mockServer 98 -- add 2 blocks with tx @@ -263,15 +233,12 @@ noPruneAndRollBack = do -- everything should be pruned assertEqQuery dbSyncEnv DB.queryTxOutConsumedCount 1 "Unexpected TxOutConsumedByTxId count after rollback" where - cmdLineArgs = - initCommandLineArgs - { claConfigFilename = "test-db-sync-config-consumed.json" - } + cmdLineArgs = initCommandLineArgs testLabel = "configPruneAndRollBack" pruneSameBlock :: IOManager -> [(Text, Text)] -> Assertion pruneSameBlock = - withCustomConfig cmdLineArgs Nothing babbageConfigDir testLabel $ \interpreter mockServer dbSyncEnv -> do + withCustomConfig cmdLineArgs (Just configPruneForceTxIn) babbageConfigDir testLabel $ \interpreter mockServer dbSyncEnv -> do startDBSync dbSyncEnv void $ forgeAndSubmitBlocks interpreter mockServer 76 blk77 <- forgeNextFindLeaderAndSubmit interpreter mockServer [] @@ -291,15 +258,12 @@ pruneSameBlock = assertTxInCount dbSyncEnv 0 assertEqQuery dbSyncEnv DB.queryTxOutConsumedCount 0 "Unexpected TxOutConsumedByTxId after rollback" where - cmdLineArgs = - initCommandLineArgs - { claConfigFilename = "test-db-sync-config-prune.json" - } + cmdLineArgs = initCommandLineArgs testLabel = "configPruneSameBlock" noPruneSameBlock :: IOManager -> [(Text, Text)] -> Assertion noPruneSameBlock = - withCustomConfig cmdLineArgs Nothing babbageConfigDir testLabel $ \interpreter mockServer dbSyncEnv -> do + withCustomConfig cmdLineArgs (Just configConsume) babbageConfigDir testLabel $ \interpreter mockServer dbSyncEnv -> do startDBSync dbSyncEnv void $ forgeAndSubmitBlocks interpreter mockServer 96 blk97 <- forgeNextFindLeaderAndSubmit interpreter mockServer [] @@ -316,15 +280,12 @@ noPruneSameBlock = assertBlockNoBackoff dbSyncEnv 98 assertEqQuery dbSyncEnv DB.queryTxOutConsumedCount 0 "Unexpected TxOutConsumedByTxId after rollback" where - cmdLineArgs = - initCommandLineArgs - { claConfigFilename = "test-db-sync-config-consumed.json" - } + cmdLineArgs = initCommandLineArgs testLabel = "configNoPruneSameBlock" migrateAndPruneRestart :: IOManager -> [(Text, Text)] -> Assertion migrateAndPruneRestart = do - withCustomConfig cmdLineArgs Nothing babbageConfigDir testLabel $ \interpreter mockServer dbSyncEnv -> do + withCustomConfig cmdLineArgs (Just configConsume) babbageConfigDir testLabel $ \interpreter mockServer dbSyncEnv -> do startDBSync dbSyncEnv void $ forgeAndSubmitBlocks interpreter mockServer 50 assertBlockNoBackoff dbSyncEnv 50 @@ -338,15 +299,12 @@ migrateAndPruneRestart = do -- checkStillRuns uses `poll` due to this being inside Async and passes along our thrown exception checkStillRuns dbSyncEnv where - cmdLineArgs = - initCommandLineArgs - { claConfigFilename = "test-db-sync-config-consumed.json" - } + cmdLineArgs = initCommandLineArgs testLabel = "configMigrateAndPruneRestart" pruneRestartMissingFlag :: IOManager -> [(Text, Text)] -> Assertion pruneRestartMissingFlag = do - withCustomConfig cmdLineArgs Nothing babbageConfigDir testLabel $ \interpreter mockServer dbSyncEnv -> do + withCustomConfig cmdLineArgs (Just configPruneForceTxIn) babbageConfigDir testLabel $ \interpreter mockServer dbSyncEnv -> do startDBSync dbSyncEnv void $ forgeAndSubmitBlocks interpreter mockServer 50 assertBlockNoBackoff dbSyncEnv 50 @@ -360,15 +318,12 @@ pruneRestartMissingFlag = do -- checkStillRuns uses `poll` due to this being inside Async and passes along our thrown exception checkStillRuns dbSyncEnv where - cmdLineArgs = - initCommandLineArgs - { claConfigFilename = "test-db-sync-config-prune.json" - } + cmdLineArgs = initCommandLineArgs testLabel = "configPruneRestartMissingFlag" bootstrapRestartMissingFlag :: IOManager -> [(Text, Text)] -> Assertion bootstrapRestartMissingFlag = do - withCustomConfig cmdLineArgs Nothing babbageConfigDir testLabel $ \interpreter mockServer dbSyncEnv -> do + withCustomConfig cmdLineArgs (Just configBootstrap) babbageConfigDir testLabel $ \interpreter mockServer dbSyncEnv -> do startDBSync dbSyncEnv void $ forgeAndSubmitBlocks interpreter mockServer 50 assertBlockNoBackoff dbSyncEnv 50 @@ -383,9 +338,5 @@ bootstrapRestartMissingFlag = do -- checkStillRuns uses `poll` due to this being inside Async and passes along our thrown exception checkStillRuns dbSyncEnv where - cmdLineArgs = - initCommandLineArgs - { claConfigFilename = "test-db-sync-config-bootstrap.json" - , claBootstrap = True - } + cmdLineArgs = initCommandLineArgs testLabel = "configBootstrapRestartMissingFlag" diff --git a/cardano-chain-gen/test/Test/Cardano/Db/Mock/Unit/Conway/Config/JsonbInSchema.hs b/cardano-chain-gen/test/Test/Cardano/Db/Mock/Unit/Conway/Config/JsonbInSchema.hs index 0679b0de7..330d4b7ec 100644 --- a/cardano-chain-gen/test/Test/Cardano/Db/Mock/Unit/Conway/Config/JsonbInSchema.hs +++ b/cardano-chain-gen/test/Test/Cardano/Db/Mock/Unit/Conway/Config/JsonbInSchema.hs @@ -17,40 +17,26 @@ import Test.Cardano.Db.Mock.Validate import Test.Tasty.HUnit (Assertion ()) configRemoveJsonbFromSchemaEnabled :: IOManager -> [(Text, Text)] -> Assertion -configRemoveJsonbFromSchemaEnabled ioManager metadata = do - syncNodeConfig <- mksNodeConfig - withCustomConfigAndDropDB args (Just syncNodeConfig) cfgDir testLabel action ioManager metadata +configRemoveJsonbFromSchemaEnabled = do + withCustomConfigAndDropDB args (Just configRemoveJsonFromSchema) cfgDir testLabel $ \_interpreter _mockServer dbSync -> do + startDBSync dbSync + threadDelay 7_000_000 + assertEqQuery + dbSync + DB.queryJsonbInSchemaExists + False + "There should be no jsonb data types in database if option is enabled" + checkStillRuns dbSync where - action = \_interpreter _mockServer dbSync -> do - startDBSync dbSync - threadDelay 7_000_000 - assertEqQuery - dbSync - DB.queryJsonbInSchemaExists - False - "There should be no jsonb data types in database if option is enabled" - checkStillRuns dbSync - args = initCommandLineArgs {claFullMode = False} testLabel = "conwayConfigRemoveJsonbFromSchemaEnabled" cfgDir = conwayConfigDir - mksNodeConfig :: IO SyncNodeConfig - mksNodeConfig = do - initConfigFile <- mkSyncNodeConfig cfgDir args - let dncInsertOptions' = dncInsertOptions initConfigFile - pure $ - initConfigFile - { dncInsertOptions = dncInsertOptions' {sioRemoveJsonbFromSchema = RemoveJsonbFromSchemaConfig True} - } - configRemoveJsonbFromSchemaDisabled :: IOManager -> [(Text, Text)] -> Assertion -configRemoveJsonbFromSchemaDisabled ioManager metadata = do - syncNodeConfig <- mksNodeConfig - withCustomConfigAndDropDB args (Just syncNodeConfig) cfgDir testLabel action ioManager metadata - where - action = \_interpreter _mockServer dbSync -> do +configRemoveJsonbFromSchemaDisabled = do + withCustomConfigAndDropDB args (Just configRemoveJsonFromSchemaFalse) cfgDir testLabel $ + \_interpreter _mockServer dbSync -> do startDBSync dbSync threadDelay 7_000_000 assertEqQuery @@ -59,65 +45,42 @@ configRemoveJsonbFromSchemaDisabled ioManager metadata = do True "There should be jsonb types in database if option is disabled" checkStillRuns dbSync - + where args = initCommandLineArgs {claFullMode = False} testLabel = "conwayConfigRemoveJsonbFromSchemaDisabled" - cfgDir = conwayConfigDir - mksNodeConfig :: IO SyncNodeConfig - mksNodeConfig = do - initConfigFile <- mkSyncNodeConfig cfgDir args - let dncInsertOptions' = dncInsertOptions initConfigFile - pure $ - initConfigFile - { dncInsertOptions = dncInsertOptions' {sioRemoveJsonbFromSchema = RemoveJsonbFromSchemaConfig False} - } - configJsonbInSchemaShouldRemoveThenAdd :: IOManager -> [(Text, Text)] -> Assertion -configJsonbInSchemaShouldRemoveThenAdd ioManager metadata = do - syncNodeConfig <- mksNodeConfig - withCustomConfigAndDropDB args (Just syncNodeConfig) cfgDir testLabel action ioManager metadata +configJsonbInSchemaShouldRemoveThenAdd = + withCustomConfigAndDropDB args (Just configRemoveJsonFromSchema) cfgDir testLabel $ \_interpreter _mockServer dbSyncEnv -> do + startDBSync dbSyncEnv + threadDelay 7_000_000 + assertEqQuery + dbSyncEnv + DB.queryJsonbInSchemaExists + False + "There should be no jsonb types in database if option has been enabled" + stopDBSync dbSyncEnv + let newDbSyncEnv = + dbSyncEnv + { dbSyncConfig = + (dbSyncConfig dbSyncEnv) + { dncInsertOptions = + (dncInsertOptions $ dbSyncConfig dbSyncEnv) + { sioRemoveJsonbFromSchema = RemoveJsonbFromSchemaConfig False + } + } + } + startDBSync newDbSyncEnv + threadDelay 7_000_000 + assertEqQuery + dbSyncEnv + DB.queryJsonbInSchemaExists + True + "There should be jsonb types in database if option has been disabled" + -- Expected to fail + checkStillRuns dbSyncEnv where - action = \_interpreter _mockServer dbSync -> do - startDBSync dbSync - threadDelay 7_000_000 - assertEqQuery - dbSync - DB.queryJsonbInSchemaExists - False - "There should be no jsonb types in database if option has been enabled" - stopDBSync dbSync - let newDbSyncEnv = - dbSync - { dbSyncConfig = - (dbSyncConfig dbSync) - { dncInsertOptions = - (dncInsertOptions $ dbSyncConfig dbSync) - { sioRemoveJsonbFromSchema = RemoveJsonbFromSchemaConfig False - } - } - } - startDBSync newDbSyncEnv - threadDelay 7_000_000 - assertEqQuery - dbSync - DB.queryJsonbInSchemaExists - True - "There should be jsonb types in database if option has been disabled" - -- Expected to fail - checkStillRuns dbSync - args = initCommandLineArgs {claFullMode = False} testLabel = "configJsonbInSchemaShouldRemoveThenAdd" - cfgDir = conwayConfigDir - - mksNodeConfig :: IO SyncNodeConfig - mksNodeConfig = do - initConfigFile <- mkSyncNodeConfig cfgDir args - let dncInsertOptions' = dncInsertOptions initConfigFile - pure $ - initConfigFile - { dncInsertOptions = dncInsertOptions' {sioRemoveJsonbFromSchema = RemoveJsonbFromSchemaConfig True} - } diff --git a/cardano-chain-gen/test/Test/Cardano/Db/Mock/Unit/Conway/Config/MigrateConsumedPruneTxOut.hs b/cardano-chain-gen/test/Test/Cardano/Db/Mock/Unit/Conway/Config/MigrateConsumedPruneTxOut.hs index f1eb3e156..e9f54c627 100644 --- a/cardano-chain-gen/test/Test/Cardano/Db/Mock/Unit/Conway/Config/MigrateConsumedPruneTxOut.hs +++ b/cardano-chain-gen/test/Test/Cardano/Db/Mock/Unit/Conway/Config/MigrateConsumedPruneTxOut.hs @@ -21,7 +21,6 @@ module Test.Cardano.Db.Mock.Unit.Conway.Config.MigrateConsumedPruneTxOut ( ) where import qualified Cardano.Db as DB -import Cardano.DbSync.Config.Types import Cardano.Mock.ChainSync.Server (IOManager (), addBlock) import Cardano.Mock.Forging.Interpreter (forgeNext) import qualified Cardano.Mock.Forging.Tx.Conway as Conway @@ -36,46 +35,33 @@ import Test.Tasty.HUnit (Assertion ()) import Prelude () import qualified Prelude +------------------------------------------------------------------------------ +-- Tests +----------------------------------------------------------------------------- txConsumedColumnCheck :: IOManager -> [(Text, Text)] -> Assertion -txConsumedColumnCheck ioManager names = do +txConsumedColumnCheck = do -- be mindful that you have to manually pass the ioManager + names - syncNodeConfig <- mkSynNodeConfig - withCustomConfigAndDropDB - cmdLineArgs - (Just syncNodeConfig) - conwayConfigDir - testLabel - ( \interpreter mockServer dbSync -> do - startDBSync dbSync - - void $ - withConwayFindLeaderAndSubmitTx interpreter mockServer $ - Conway.mkPaymentTx (UTxOIndex 0) (UTxOIndex 1) 10_000 500 0 - - assertBlockNoBackoff dbSync 1 - assertEqQuery - dbSync - DB.queryTxConsumedColumnExists - True - "missing consumed_by_tx_id column when tx-out = consumed" - ) - ioManager - names + withCustomConfigAndDropDB cmdLineArgs (Just configConsume) conwayConfigDir testLabel $ + \interpreter mockServer dbSync -> do + startDBSync dbSync + + void $ + withConwayFindLeaderAndSubmitTx interpreter mockServer $ + Conway.mkPaymentTx (UTxOIndex 0) (UTxOIndex 1) 10_000 500 0 + + assertBlockNoBackoff dbSync 1 + assertEqQuery + dbSync + DB.queryTxConsumedColumnExists + True + "missing consumed_by_tx_id column when tx-out = consumed" where - -- an example of how we will pass our custom configs overwriting the init file - mkSynNodeConfig :: IO SyncNodeConfig - mkSynNodeConfig = do - initConfigFile <- mkSyncNodeConfig conwayConfigDir cmdLineArgs - pure $ initConfigFile {dncEnableLogging = True} - cmdLineArgs = - initCommandLineArgs - { claConfigFilename = "test-db-sync-config-consumed.json" - } + cmdLineArgs = initCommandLineArgs testLabel = "conwayTxConsumedColumnCheck" basicPrune :: IOManager -> [(Text, Text)] -> Assertion basicPrune = do - withCustomConfig args Nothing cfgDir testLabel $ \interpreter mockServer dbSync -> do + withCustomConfig args (Just configPruneForceTxIn) cfgDir testLabel $ \interpreter mockServer dbSync -> do startDBSync dbSync -- Add some blocks @@ -101,17 +87,14 @@ basicPrune = do -- Check unspent tx assertUnspentTx dbSync where - args = - initCommandLineArgs - { claConfigFilename = "test-db-sync-config-prune.json" - } + args = initCommandLineArgs testLabel = "conwayConfigPrune" fullBlockSize b = fromIntegral $ length b + 2 cfgDir = conwayConfigDir pruneWithSimpleRollback :: IOManager -> [(Text, Text)] -> Assertion pruneWithSimpleRollback = - withCustomConfig cmdLineArgs Nothing conwayConfigDir testLabel $ \interpreter mockServer dbSync -> do + withCustomConfig cmdLineArgs (Just configPruneForceTxIn) conwayConfigDir testLabel $ \interpreter mockServer dbSync -> do -- Forge some blocks blk0 <- forgeNext interpreter mockBlock0 blk1 <- forgeNext interpreter mockBlock1 @@ -141,16 +124,13 @@ pruneWithSimpleRollback = assertEqQuery dbSync DB.queryTxOutConsumedCount 0 "Unexpected TxOutConsumedByTxId count after rollback" assertBlockNoBackoff dbSync (fullBlockSize blks) where - cmdLineArgs = - initCommandLineArgs - { claConfigFilename = "test-db-sync-config-prune.json" - } + cmdLineArgs = initCommandLineArgs testLabel = "conwayConfigPruneSimpleRollback" fullBlockSize b = fromIntegral $ length b + 4 pruneWithFullTxRollback :: IOManager -> [(Text, Text)] -> Assertion pruneWithFullTxRollback = - withCustomConfig cmdLineArgs Nothing conwayConfigDir testLabel $ \interpreter mockServer dbSync -> do + withCustomConfig cmdLineArgs (Just configPruneForceTxIn) conwayConfigDir testLabel $ \interpreter mockServer dbSync -> do startDBSync dbSync -- Forge a block blk0 <- forgeNextFindLeaderAndSubmit interpreter mockServer [] @@ -181,18 +161,13 @@ pruneWithFullTxRollback = assertEqQuery dbSync DB.queryTxOutCount 16 "new epoch didn't prune tx_out column that are null" assertUnspentTx dbSync where - cmdLineArgs = - initCommandLineArgs - { claConfigFilename = "test-db-sync-config-prune.json" - } + cmdLineArgs = initCommandLineArgs testLabel = "conwayConfigPruneOnFullRollback" -- The transactions in the last `2 * securityParam` blocks should not be pruned pruningShouldKeepSomeTx :: IOManager -> [(Text, Text)] -> Assertion -pruningShouldKeepSomeTx ioManager names = do - syncNodeConfig <- mkSyncNodeConfig' - - withConfig' syncNodeConfig $ \interpreter mockServer dbSync -> do +pruningShouldKeepSomeTx = do + withCustomConfig cmdLineArgs (Just configPrune) conwayConfigDir testLabel $ \interpreter mockServer dbSync -> do startDBSync dbSync -- Forge some blocks @@ -217,29 +192,12 @@ pruningShouldKeepSomeTx ioManager names = do assertTxInCount dbSync 0 assertEqQuery dbSync DB.queryTxOutConsumedCount 0 "Unexpected TxOutConsumedByTxId count after prune" where - withConfig' cfg f = - withCustomConfig cmdLineArgs (Just cfg) conwayConfigDir testLabel f ioManager names - - mkSyncNodeConfig' :: IO SyncNodeConfig - mkSyncNodeConfig' = do - initCfg <- mkSyncNodeConfig conwayConfigDir cmdLineArgs - pure $ - initCfg - { dncInsertOptions = - (dncInsertOptions initCfg) - { sioTxOut = TxOutPrune (ForceTxIn False) - } - } - - cmdLineArgs = - initCommandLineArgs - { claConfigFilename = "test-db-sync-config-prune.json" - } + cmdLineArgs = initCommandLineArgs testLabel = "conwayConfigPruneCorrectAmount" pruneAndRollBackOneBlock :: IOManager -> [(Text, Text)] -> Assertion pruneAndRollBackOneBlock = - withCustomConfig cmdLineArgs Nothing conwayConfigDir testLabel $ \interpreter mockServer dbSync -> do + withCustomConfig cmdLineArgs (Just configPruneForceTxIn) conwayConfigDir testLabel $ \interpreter mockServer dbSync -> do startDBSync dbSync -- Forge some blocks @@ -273,15 +231,12 @@ pruneAndRollBackOneBlock = assertBlockNoBackoff dbSync 203 assertEqQuery dbSync DB.queryTxOutConsumedCount 0 "Unexpected TxOutConsumedByTxId count after rollback" where - cmdLineArgs = - initCommandLineArgs - { claConfigFilename = "test-db-sync-config-prune.json" - } + cmdLineArgs = initCommandLineArgs testLabel = "conwayConfigPruneAndRollBack" noPruneAndRollBack :: IOManager -> [(Text, Text)] -> Assertion noPruneAndRollBack = - withCustomConfig cmdLineArgs Nothing conwayConfigDir testLabel $ \interpreter mockServer dbSync -> do + withCustomConfig cmdLineArgs (Just configConsume) conwayConfigDir testLabel $ \interpreter mockServer dbSync -> do startDBSync dbSync -- Forge some blocks @@ -315,15 +270,12 @@ noPruneAndRollBack = assertBlockNoBackoff dbSync 203 assertEqQuery dbSync DB.queryTxOutConsumedCount 1 "Unexpected TxOutConsumedByTxId count after rollback" where - cmdLineArgs = - initCommandLineArgs - { claConfigFilename = "test-db-sync-config-consumed.json" - } + cmdLineArgs = initCommandLineArgs testLabel = "conwayConfigNoPruneAndRollBack" pruneSameBlock :: IOManager -> [(Text, Text)] -> Assertion pruneSameBlock = - withCustomConfig cmdLineArgs Nothing conwayConfigDir testLabel $ \interpreter mockServer dbSync -> do + withCustomConfig cmdLineArgs (Just configPruneForceTxIn) conwayConfigDir testLabel $ \interpreter mockServer dbSync -> do startDBSync dbSync -- Forge some blocks @@ -354,15 +306,12 @@ pruneSameBlock = assertTxInCount dbSync 0 assertEqQuery dbSync DB.queryTxOutConsumedCount 0 "Unexpected TxOutConsumedByTxId after rollback" where - cmdLineArgs = - initCommandLineArgs - { claConfigFilename = "test-db-sync-config-prune.json" - } + cmdLineArgs = initCommandLineArgs testLabel = "conwayConfigPruneSameBlock" noPruneSameBlock :: IOManager -> [(Text, Text)] -> Assertion noPruneSameBlock = - withCustomConfig cmdLineArgs Nothing conwayConfigDir testLabel $ \interpreter mockServer dbSync -> do + withCustomConfig cmdLineArgs (Just configConsume) conwayConfigDir testLabel $ \interpreter mockServer dbSync -> do startDBSync dbSync -- Forge some blocks @@ -389,15 +338,12 @@ noPruneSameBlock = assertBlockNoBackoff dbSync 98 assertEqQuery dbSync DB.queryTxOutConsumedCount 0 "Unexpected TxOutConsumedByTxId after rollback" where - cmdLineArgs = - initCommandLineArgs - { claConfigFilename = "test-db-sync-config-consumed.json" - } + cmdLineArgs = initCommandLineArgs testLabel = "conwayConfigNoPruneSameBlock" migrateAndPruneRestart :: IOManager -> [(Text, Text)] -> Assertion migrateAndPruneRestart = - withCustomConfig cmdLineArgs Nothing conwayConfigDir testLabel $ \interpreter mockServer dbSync -> do + withCustomConfig cmdLineArgs (Just configConsume) conwayConfigDir testLabel $ \interpreter mockServer dbSync -> do startDBSync dbSync -- Forge some blocks @@ -415,15 +361,12 @@ migrateAndPruneRestart = -- Expected to fail checkStillRuns dbSync where - cmdLineArgs = - initCommandLineArgs - { claConfigFilename = "test-db-sync-config-consumed.json" - } + cmdLineArgs = initCommandLineArgs testLabel = "conwayConfigMigrateAndPruneRestart" pruneRestartMissingFlag :: IOManager -> [(Text, Text)] -> Assertion pruneRestartMissingFlag = - withCustomConfig cmdLineArgs Nothing conwayConfigDir testLabel $ \interpreter mockServer dbSync -> do + withCustomConfig cmdLineArgs (Just configPruneForceTxIn) conwayConfigDir testLabel $ \interpreter mockServer dbSync -> do startDBSync dbSync -- Forge some blocks @@ -441,15 +384,12 @@ pruneRestartMissingFlag = -- Expected to fail checkStillRuns dbSync where - cmdLineArgs = - initCommandLineArgs - { claConfigFilename = "test-db-sync-config-prune.json" - } + cmdLineArgs = initCommandLineArgs testLabel = "conwayConfigPruneRestartMissingFlag" bootstrapRestartMissingFlag :: IOManager -> [(Text, Text)] -> Assertion bootstrapRestartMissingFlag = - withCustomConfig cmdLineArgs Nothing conwayConfigDir testLabel $ \interpreter mockServer dbSync -> do + withCustomConfig cmdLineArgs (Just configBootstrap) conwayConfigDir testLabel $ \interpreter mockServer dbSync -> do startDBSync dbSync -- Forge some blocks @@ -467,9 +407,5 @@ bootstrapRestartMissingFlag = -- Expected to fail checkStillRuns dbSync where - cmdLineArgs = - initCommandLineArgs - { claConfigFilename = "test-db-sync-config-bootstrap.json" - , claBootstrap = True - } + cmdLineArgs = initCommandLineArgs testLabel = "conwayConfigBootstrapRestartMissingFlag" diff --git a/cardano-chain-gen/test/Test/Cardano/Db/Mock/Unit/Conway/Plutus.hs b/cardano-chain-gen/test/Test/Cardano/Db/Mock/Unit/Conway/Plutus.hs index 8cd95e76c..1570bd764 100644 --- a/cardano-chain-gen/test/Test/Cardano/Db/Mock/Unit/Conway/Plutus.hs +++ b/cardano-chain-gen/test/Test/Cardano/Db/Mock/Unit/Conway/Plutus.hs @@ -53,12 +53,25 @@ import qualified Data.Map as Map import Data.Maybe.Strict (StrictMaybe (..)) import Ouroboros.Consensus.Shelley.Eras (StandardConway ()) import Ouroboros.Network.Block (genesisPoint) -import Test.Cardano.Db.Mock.Config +import Test.Cardano.Db.Mock.Config ( + CommandLineArgs (..), + configMultiAssetsDisable, + configPlutusDisable, + conwayConfigDir, + initCommandLineArgs, + startDBSync, + withCustomConfig, + withFullConfig, + withFullConfigAndDropDB, + ) import qualified Test.Cardano.Db.Mock.UnifiedApi as Api import Test.Cardano.Db.Mock.Validate import Test.Tasty.HUnit (Assertion ()) import Prelude (head, tail, (!!)) +------------------------------------------------------------------------------ +-- Tests +------------------------------------------------------------------------------ simpleScript :: IOManager -> [(Text, Text)] -> Assertion simpleScript = withFullConfigAndDropDB conwayConfigDir testLabel $ \interpreter mockServer dbSync -> do @@ -133,7 +146,7 @@ unlockScriptSameBlock = unlockScriptNoPlutus :: IOManager -> [(Text, Text)] -> Assertion unlockScriptNoPlutus = - withCustomConfig args Nothing conwayConfigDir testLabel $ \interpreter mockServer dbSync -> do + withCustomConfig args (Just configPlutusDisable) conwayConfigDir testLabel $ \interpreter mockServer dbSync -> do startDBSync dbSync -- Forge a block with stake credentials @@ -163,8 +176,7 @@ unlockScriptNoPlutus = where args = initCommandLineArgs - { claConfigFilename = "test-db-sync-config-no-plutus.json" - , claFullMode = False + { claFullMode = False } testLabel = "conwayConfigPlutusDisbaled" @@ -769,7 +781,7 @@ swapMultiAssets = swapMultiAssetsDisabled :: IOManager -> [(Text, Text)] -> Assertion swapMultiAssetsDisabled = - withCustomConfig args Nothing cfgDir testLabel $ \interpreter mockServer dbSync -> do + withCustomConfig args (Just configMultiAssetsDisable) cfgDir testLabel $ \interpreter mockServer dbSync -> do startDBSync dbSync -- Forge a block with multiple multi-asset scripts @@ -800,8 +812,7 @@ swapMultiAssetsDisabled = where args = initCommandLineArgs - { claConfigFilename = "test-db-sync-config-no-multi-assets.json" - , claFullMode = False + { claFullMode = False } testLabel = "conwayConfigMultiAssetsDisabled" diff --git a/cardano-chain-gen/test/Test/Cardano/Db/Mock/Unit/Conway/Stake.hs b/cardano-chain-gen/test/Test/Cardano/Db/Mock/Unit/Conway/Stake.hs index ab9dce6c7..778d3eb5e 100644 --- a/cardano-chain-gen/test/Test/Cardano/Db/Mock/Unit/Conway/Stake.hs +++ b/cardano-chain-gen/test/Test/Cardano/Db/Mock/Unit/Conway/Stake.hs @@ -416,7 +416,7 @@ registerStakeCreds = do registerStakeCredsNoShelley :: IOManager -> [(Text, Text)] -> Assertion registerStakeCredsNoShelley = do - withCustomConfig args Nothing cfgDir testLabel $ \interpreter mockServer dbSync -> do + withCustomConfig args (Just configShelleyDisable) cfgDir testLabel $ \interpreter mockServer dbSync -> do startDBSync dbSync -- These should not be saved when shelley is disabled @@ -431,8 +431,7 @@ registerStakeCredsNoShelley = do where args = initCommandLineArgs - { claConfigFilename = "test-db-sync-config-no-shelley.json" - , claFullMode = False + { claFullMode = False } testLabel = "conwayConfigShelleyDisabled" cfgDir = conwayConfigDir diff --git a/cardano-chain-gen/test/Test/Cardano/Db/Mock/Unit/Conway/Tx.hs b/cardano-chain-gen/test/Test/Cardano/Db/Mock/Unit/Conway/Tx.hs index 0079f1e8d..4adeac2b3 100644 --- a/cardano-chain-gen/test/Test/Cardano/Db/Mock/Unit/Conway/Tx.hs +++ b/cardano-chain-gen/test/Test/Cardano/Db/Mock/Unit/Conway/Tx.hs @@ -16,8 +16,6 @@ module Test.Cardano.Db.Mock.Unit.Conway.Tx ( addTxMetadataWhitelist, ) where -import Cardano.DbSync.Config (SyncNodeConfig (..)) -import Cardano.DbSync.Config.Types (MetadataConfig (..), SyncInsertOptions (..)) import Cardano.Ledger.Shelley.TxAuxData (Metadatum (..)) import Cardano.Mock.ChainSync.Server (IOManager ()) import qualified Cardano.Mock.Forging.Tx.Conway as Conway @@ -67,7 +65,7 @@ addSimpleTxShelley = addSimpleTxNoLedger :: IOManager -> [(Text, Text)] -> Assertion addSimpleTxNoLedger = do - withCustomConfig args Nothing conwayConfigDir testLabel $ \interpreter mockServer dbSync -> do + withCustomConfig args (Just configLedgerIgnore) conwayConfigDir testLabel $ \interpreter mockServer dbSync -> do -- Forge a block void $ UnifiedApi.withConwayFindLeaderAndSubmitTx interpreter mockServer $ @@ -82,8 +80,7 @@ addSimpleTxNoLedger = do where args = initCommandLineArgs - { claConfigFilename = "test-db-sync-config-no-ledger.json" - , claFullMode = False + { claFullMode = False } testLabel = "conwayConfigLedgerDisabled" @@ -126,11 +123,9 @@ consumeSameBlock = testLabel = "conwayConsumeSameBlock" addTxMetadata :: IOManager -> [(Text, Text)] -> Assertion -addTxMetadata ioManager metadata = do - syncNodeConfig <- mksNodeConfig - withCustomConfigAndDropDB args (Just syncNodeConfig) cfgDir testLabel action ioManager metadata - where - action = \interpreter mockServer dbSync -> do +addTxMetadata = do + withCustomConfigAndDropDB args (Just configMetadataEnable) cfgDir testLabel $ + \interpreter mockServer dbSync -> do startDBSync dbSync -- Add blocks with transactions void $ @@ -143,24 +138,14 @@ addTxMetadata ioManager metadata = do assertBlockNoBackoff dbSync 1 -- Should have tx metadata assertEqBackoff dbSync queryTxMetadataCount 2 [] "Expected tx metadata" - + where args = initCommandLineArgs {claFullMode = False} testLabel = "conwayConfigMetadataEnabled" - cfgDir = conwayConfigDir - mksNodeConfig :: IO SyncNodeConfig - mksNodeConfig = do - initConfigFile <- mkSyncNodeConfig cfgDir args - let dncInsertOptions' = dncInsertOptions initConfigFile - pure $ - initConfigFile - { dncInsertOptions = dncInsertOptions' {sioMetadata = MetadataEnable} - } - addTxMetadataWhitelist :: IOManager -> [(Text, Text)] -> Assertion addTxMetadataWhitelist = do - withCustomConfigAndDropDB args Nothing cfgDir testLabel $ \interpreter mockServer dbSync -> do + withCustomConfigAndDropDB args (Just configMetadataKeys) cfgDir testLabel $ \interpreter mockServer dbSync -> do startDBSync dbSync -- Add blocks with transactions @@ -177,18 +162,15 @@ addTxMetadataWhitelist = do where args = initCommandLineArgs - { claConfigFilename = "test-db-sync-config-keep-metadata.json" - , claFullMode = False + { claFullMode = False } testLabel = "conwayConfigMetadataKeep" cfgDir = conwayConfigDir addTxMetadataDisabled :: IOManager -> [(Text, Text)] -> Assertion -addTxMetadataDisabled ioManager metadata = do - syncNodeConfig <- mksNodeConfig - withCustomConfigAndDropDB args (Just syncNodeConfig) cfgDir testLabel action ioManager metadata - where - action = \interpreter mockServer dbSync -> do +addTxMetadataDisabled = do + withCustomConfigAndDropDB args (Just configMetadataDisable) cfgDir testLabel $ + \interpreter mockServer dbSync -> do startDBSync dbSync -- Add blocks with transactions void $ @@ -201,17 +183,7 @@ addTxMetadataDisabled ioManager metadata = do assertBlockNoBackoff dbSync 1 -- Should have tx metadata assertEqBackoff dbSync queryTxMetadataCount 0 [] "Expected tx metadata" - + where args = initCommandLineArgs {claFullMode = False} testLabel = "conwayConfigMetadataDisabled" - cfgDir = conwayConfigDir - - mksNodeConfig :: IO SyncNodeConfig - mksNodeConfig = do - initConfigFile <- mkSyncNodeConfig cfgDir args - let dncInsertOptions' = dncInsertOptions initConfigFile - pure $ - initConfigFile - { dncInsertOptions = dncInsertOptions' {sioMetadata = MetadataDisable} - } diff --git a/cardano-chain-gen/test/testfiles/config-conway/test-db-sync-config-bootstrap.json b/cardano-chain-gen/test/testfiles/config-conway/test-db-sync-config-bootstrap.json deleted file mode 100644 index 43e6c11bc..000000000 --- a/cardano-chain-gen/test/testfiles/config-conway/test-db-sync-config-bootstrap.json +++ /dev/null @@ -1,119 +0,0 @@ -{ - "EnableLogMetrics": false, - "EnableLogging": true, - "NetworkName": "testing", - "NodeConfigFile": "test-config.json", - "PrometheusPort": 8080, - "RequiresNetworkMagic": "RequiresMagic", - "defaultBackends": [ - "KatipBK" - ], - "defaultScribes": [ - [ - "StdoutSK", - "stdout" - ] - ], - "minSeverity": "Info", - "options": { - "cfokey": { - "value": "Release-1.0.0" - }, - "mapBackends": {}, - "mapSeverity": { - "db-sync-node": "Info", - "db-sync-node.Mux": "Error", - "db-sync-node.Subscription": "Error" - }, - "mapSubtrace": { - "#ekgview": { - "contents": [ - [ - { - "contents": "cardano.epoch-validation.benchmark", - "tag": "Contains" - }, - [ - { - "contents": ".monoclock.basic.", - "tag": "Contains" - } - ] - ], - [ - { - "contents": "cardano.epoch-validation.benchmark", - "tag": "Contains" - }, - [ - { - "contents": "diff.RTS.cpuNs.timed.", - "tag": "Contains" - } - ] - ], - [ - { - "contents": "#ekgview.#aggregation.cardano.epoch-validation.benchmark", - "tag": "StartsWith" - }, - [ - { - "contents": "diff.RTS.gcNum.timed.", - "tag": "Contains" - } - ] - ] - ], - "subtrace": "FilterTrace" - }, - "#messagecounters.aggregation": { - "subtrace": "NoTrace" - }, - "#messagecounters.ekgview": { - "subtrace": "NoTrace" - }, - "#messagecounters.katip": { - "subtrace": "NoTrace" - }, - "#messagecounters.monitoring": { - "subtrace": "NoTrace" - }, - "#messagecounters.switchboard": { - "subtrace": "NoTrace" - }, - "benchmark": { - "contents": [ - "GhcRtsStats", - "MonotonicClock" - ], - "subtrace": "ObservableTrace" - }, - "cardano.epoch-validation.utxo-stats": { - "subtrace": "NoTrace" - } - } - }, - "rotation": { - "rpKeepFilesNum": 10, - "rpLogLimitBytes": 5000000, - "rpMaxAgeHours": 24 - }, - "setupBackends": [ - "AggregationBK", - "KatipBK" - ], - "setupScribes": [ - { - "scFormat": "ScText", - "scKind": "StdoutSK", - "scName": "stdout", - "scRotation": null - } - ], - "insert_options": { - "tx_out": { - "value": "bootstrap" - } - } -} diff --git a/cardano-chain-gen/test/testfiles/config-conway/test-db-sync-config-consumed.json b/cardano-chain-gen/test/testfiles/config-conway/test-db-sync-config-consumed.json deleted file mode 100644 index 2f2f682ac..000000000 --- a/cardano-chain-gen/test/testfiles/config-conway/test-db-sync-config-consumed.json +++ /dev/null @@ -1,119 +0,0 @@ -{ - "EnableLogMetrics": false, - "EnableLogging": true, - "NetworkName": "testing", - "NodeConfigFile": "test-config.json", - "PrometheusPort": 8080, - "RequiresNetworkMagic": "RequiresMagic", - "defaultBackends": [ - "KatipBK" - ], - "defaultScribes": [ - [ - "StdoutSK", - "stdout" - ] - ], - "minSeverity": "Info", - "options": { - "cfokey": { - "value": "Release-1.0.0" - }, - "mapBackends": {}, - "mapSeverity": { - "db-sync-node": "Info", - "db-sync-node.Mux": "Error", - "db-sync-node.Subscription": "Error" - }, - "mapSubtrace": { - "#ekgview": { - "contents": [ - [ - { - "contents": "cardano.epoch-validation.benchmark", - "tag": "Contains" - }, - [ - { - "contents": ".monoclock.basic.", - "tag": "Contains" - } - ] - ], - [ - { - "contents": "cardano.epoch-validation.benchmark", - "tag": "Contains" - }, - [ - { - "contents": "diff.RTS.cpuNs.timed.", - "tag": "Contains" - } - ] - ], - [ - { - "contents": "#ekgview.#aggregation.cardano.epoch-validation.benchmark", - "tag": "StartsWith" - }, - [ - { - "contents": "diff.RTS.gcNum.timed.", - "tag": "Contains" - } - ] - ] - ], - "subtrace": "FilterTrace" - }, - "#messagecounters.aggregation": { - "subtrace": "NoTrace" - }, - "#messagecounters.ekgview": { - "subtrace": "NoTrace" - }, - "#messagecounters.katip": { - "subtrace": "NoTrace" - }, - "#messagecounters.monitoring": { - "subtrace": "NoTrace" - }, - "#messagecounters.switchboard": { - "subtrace": "NoTrace" - }, - "benchmark": { - "contents": [ - "GhcRtsStats", - "MonotonicClock" - ], - "subtrace": "ObservableTrace" - }, - "cardano.epoch-validation.utxo-stats": { - "subtrace": "NoTrace" - } - } - }, - "rotation": { - "rpKeepFilesNum": 10, - "rpLogLimitBytes": 5000000, - "rpMaxAgeHours": 24 - }, - "setupBackends": [ - "AggregationBK", - "KatipBK" - ], - "setupScribes": [ - { - "scFormat": "ScText", - "scKind": "StdoutSK", - "scName": "stdout", - "scRotation": null - } - ], - "insert_options": { - "tx_out": { - "value": "consumed" - } - } -} diff --git a/cardano-chain-gen/test/testfiles/config-conway/test-db-sync-config-keep-metadata.json b/cardano-chain-gen/test/testfiles/config-conway/test-db-sync-config-keep-metadata.json deleted file mode 100644 index 670309b67..000000000 --- a/cardano-chain-gen/test/testfiles/config-conway/test-db-sync-config-keep-metadata.json +++ /dev/null @@ -1,120 +0,0 @@ -{ - "EnableLogMetrics": false, - "EnableLogging": true, - "NetworkName": "testing", - "NodeConfigFile": "test-config.json", - "PrometheusPort": 8080, - "RequiresNetworkMagic": "RequiresMagic", - "defaultBackends": [ - "KatipBK" - ], - "defaultScribes": [ - [ - "StdoutSK", - "stdout" - ] - ], - "minSeverity": "Info", - "options": { - "cfokey": { - "value": "Release-1.0.0" - }, - "mapBackends": {}, - "mapSeverity": { - "db-sync-node": "Info", - "db-sync-node.Mux": "Error", - "db-sync-node.Subscription": "Error" - }, - "mapSubtrace": { - "#ekgview": { - "contents": [ - [ - { - "contents": "cardano.epoch-validation.benchmark", - "tag": "Contains" - }, - [ - { - "contents": ".monoclock.basic.", - "tag": "Contains" - } - ] - ], - [ - { - "contents": "cardano.epoch-validation.benchmark", - "tag": "Contains" - }, - [ - { - "contents": "diff.RTS.cpuNs.timed.", - "tag": "Contains" - } - ] - ], - [ - { - "contents": "#ekgview.#aggregation.cardano.epoch-validation.benchmark", - "tag": "StartsWith" - }, - [ - { - "contents": "diff.RTS.gcNum.timed.", - "tag": "Contains" - } - ] - ] - ], - "subtrace": "FilterTrace" - }, - "#messagecounters.aggregation": { - "subtrace": "NoTrace" - }, - "#messagecounters.ekgview": { - "subtrace": "NoTrace" - }, - "#messagecounters.katip": { - "subtrace": "NoTrace" - }, - "#messagecounters.monitoring": { - "subtrace": "NoTrace" - }, - "#messagecounters.switchboard": { - "subtrace": "NoTrace" - }, - "benchmark": { - "contents": [ - "GhcRtsStats", - "MonotonicClock" - ], - "subtrace": "ObservableTrace" - }, - "cardano.epoch-validation.utxo-stats": { - "subtrace": "NoTrace" - } - } - }, - "rotation": { - "rpKeepFilesNum": 10, - "rpLogLimitBytes": 5000000, - "rpMaxAgeHours": 24 - }, - "setupBackends": [ - "AggregationBK", - "KatipBK" - ], - "setupScribes": [ - { - "scFormat": "ScText", - "scKind": "StdoutSK", - "scName": "stdout", - "scRotation": null - } - ], - "insert_options": { - "metadata": { - "enable": true, - "keys": [1] - } - } -} diff --git a/cardano-chain-gen/test/testfiles/config-conway/test-db-sync-config-no-ledger.json b/cardano-chain-gen/test/testfiles/config-conway/test-db-sync-config-no-ledger.json deleted file mode 100644 index 9a183b7df..000000000 --- a/cardano-chain-gen/test/testfiles/config-conway/test-db-sync-config-no-ledger.json +++ /dev/null @@ -1,117 +0,0 @@ -{ - "EnableLogMetrics": false, - "EnableLogging": true, - "NetworkName": "testing", - "NodeConfigFile": "test-config.json", - "PrometheusPort": 8080, - "RequiresNetworkMagic": "RequiresMagic", - "defaultBackends": [ - "KatipBK" - ], - "defaultScribes": [ - [ - "StdoutSK", - "stdout" - ] - ], - "minSeverity": "Info", - "options": { - "cfokey": { - "value": "Release-1.0.0" - }, - "mapBackends": {}, - "mapSeverity": { - "db-sync-node": "Info", - "db-sync-node.Mux": "Error", - "db-sync-node.Subscription": "Error" - }, - "mapSubtrace": { - "#ekgview": { - "contents": [ - [ - { - "contents": "cardano.epoch-validation.benchmark", - "tag": "Contains" - }, - [ - { - "contents": ".monoclock.basic.", - "tag": "Contains" - } - ] - ], - [ - { - "contents": "cardano.epoch-validation.benchmark", - "tag": "Contains" - }, - [ - { - "contents": "diff.RTS.cpuNs.timed.", - "tag": "Contains" - } - ] - ], - [ - { - "contents": "#ekgview.#aggregation.cardano.epoch-validation.benchmark", - "tag": "StartsWith" - }, - [ - { - "contents": "diff.RTS.gcNum.timed.", - "tag": "Contains" - } - ] - ] - ], - "subtrace": "FilterTrace" - }, - "#messagecounters.aggregation": { - "subtrace": "NoTrace" - }, - "#messagecounters.ekgview": { - "subtrace": "NoTrace" - }, - "#messagecounters.katip": { - "subtrace": "NoTrace" - }, - "#messagecounters.monitoring": { - "subtrace": "NoTrace" - }, - "#messagecounters.switchboard": { - "subtrace": "NoTrace" - }, - "benchmark": { - "contents": [ - "GhcRtsStats", - "MonotonicClock" - ], - "subtrace": "ObservableTrace" - }, - "cardano.epoch-validation.utxo-stats": { - "subtrace": "NoTrace" - } - } - }, - "rotation": { - "rpKeepFilesNum": 10, - "rpLogLimitBytes": 5000000, - "rpMaxAgeHours": 24 - }, - "setupBackends": [ - "AggregationBK", - "KatipBK" - ], - "setupScribes": [ - { - "scFormat": "ScText", - "scKind": "StdoutSK", - "scName": "stdout", - "scRotation": null - } - ], - "insert_options": { - "ledger": "ignore" - } -} diff --git a/cardano-chain-gen/test/testfiles/config-conway/test-db-sync-config-no-metadata.json b/cardano-chain-gen/test/testfiles/config-conway/test-db-sync-config-no-metadata.json deleted file mode 100644 index 730e364de..000000000 --- a/cardano-chain-gen/test/testfiles/config-conway/test-db-sync-config-no-metadata.json +++ /dev/null @@ -1,119 +0,0 @@ -{ - "EnableLogMetrics": false, - "EnableLogging": true, - "NetworkName": "testing", - "NodeConfigFile": "test-config.json", - "PrometheusPort": 8080, - "RequiresNetworkMagic": "RequiresMagic", - "defaultBackends": [ - "KatipBK" - ], - "defaultScribes": [ - [ - "StdoutSK", - "stdout" - ] - ], - "minSeverity": "Info", - "options": { - "cfokey": { - "value": "Release-1.0.0" - }, - "mapBackends": {}, - "mapSeverity": { - "db-sync-node": "Info", - "db-sync-node.Mux": "Error", - "db-sync-node.Subscription": "Error" - }, - "mapSubtrace": { - "#ekgview": { - "contents": [ - [ - { - "contents": "cardano.epoch-validation.benchmark", - "tag": "Contains" - }, - [ - { - "contents": ".monoclock.basic.", - "tag": "Contains" - } - ] - ], - [ - { - "contents": "cardano.epoch-validation.benchmark", - "tag": "Contains" - }, - [ - { - "contents": "diff.RTS.cpuNs.timed.", - "tag": "Contains" - } - ] - ], - [ - { - "contents": "#ekgview.#aggregation.cardano.epoch-validation.benchmark", - "tag": "StartsWith" - }, - [ - { - "contents": "diff.RTS.gcNum.timed.", - "tag": "Contains" - } - ] - ] - ], - "subtrace": "FilterTrace" - }, - "#messagecounters.aggregation": { - "subtrace": "NoTrace" - }, - "#messagecounters.ekgview": { - "subtrace": "NoTrace" - }, - "#messagecounters.katip": { - "subtrace": "NoTrace" - }, - "#messagecounters.monitoring": { - "subtrace": "NoTrace" - }, - "#messagecounters.switchboard": { - "subtrace": "NoTrace" - }, - "benchmark": { - "contents": [ - "GhcRtsStats", - "MonotonicClock" - ], - "subtrace": "ObservableTrace" - }, - "cardano.epoch-validation.utxo-stats": { - "subtrace": "NoTrace" - } - } - }, - "rotation": { - "rpKeepFilesNum": 10, - "rpLogLimitBytes": 5000000, - "rpMaxAgeHours": 24 - }, - "setupBackends": [ - "AggregationBK", - "KatipBK" - ], - "setupScribes": [ - { - "scFormat": "ScText", - "scKind": "StdoutSK", - "scName": "stdout", - "scRotation": null - } - ], - "insert_options": { - "metadata": { - "enable": false - } - } -} diff --git a/cardano-chain-gen/test/testfiles/config-conway/test-db-sync-config-no-multi-assets.json b/cardano-chain-gen/test/testfiles/config-conway/test-db-sync-config-no-multi-assets.json deleted file mode 100644 index ef96054a6..000000000 --- a/cardano-chain-gen/test/testfiles/config-conway/test-db-sync-config-no-multi-assets.json +++ /dev/null @@ -1,119 +0,0 @@ -{ - "EnableLogMetrics": false, - "EnableLogging": true, - "NetworkName": "testing", - "NodeConfigFile": "test-config.json", - "PrometheusPort": 8080, - "RequiresNetworkMagic": "RequiresMagic", - "defaultBackends": [ - "KatipBK" - ], - "defaultScribes": [ - [ - "StdoutSK", - "stdout" - ] - ], - "minSeverity": "Info", - "options": { - "cfokey": { - "value": "Release-1.0.0" - }, - "mapBackends": {}, - "mapSeverity": { - "db-sync-node": "Info", - "db-sync-node.Mux": "Error", - "db-sync-node.Subscription": "Error" - }, - "mapSubtrace": { - "#ekgview": { - "contents": [ - [ - { - "contents": "cardano.epoch-validation.benchmark", - "tag": "Contains" - }, - [ - { - "contents": ".monoclock.basic.", - "tag": "Contains" - } - ] - ], - [ - { - "contents": "cardano.epoch-validation.benchmark", - "tag": "Contains" - }, - [ - { - "contents": "diff.RTS.cpuNs.timed.", - "tag": "Contains" - } - ] - ], - [ - { - "contents": "#ekgview.#aggregation.cardano.epoch-validation.benchmark", - "tag": "StartsWith" - }, - [ - { - "contents": "diff.RTS.gcNum.timed.", - "tag": "Contains" - } - ] - ] - ], - "subtrace": "FilterTrace" - }, - "#messagecounters.aggregation": { - "subtrace": "NoTrace" - }, - "#messagecounters.ekgview": { - "subtrace": "NoTrace" - }, - "#messagecounters.katip": { - "subtrace": "NoTrace" - }, - "#messagecounters.monitoring": { - "subtrace": "NoTrace" - }, - "#messagecounters.switchboard": { - "subtrace": "NoTrace" - }, - "benchmark": { - "contents": [ - "GhcRtsStats", - "MonotonicClock" - ], - "subtrace": "ObservableTrace" - }, - "cardano.epoch-validation.utxo-stats": { - "subtrace": "NoTrace" - } - } - }, - "rotation": { - "rpKeepFilesNum": 10, - "rpLogLimitBytes": 5000000, - "rpMaxAgeHours": 24 - }, - "setupBackends": [ - "AggregationBK", - "KatipBK" - ], - "setupScribes": [ - { - "scFormat": "ScText", - "scKind": "StdoutSK", - "scName": "stdout", - "scRotation": null - } - ], - "insert_options": { - "multi_asset": { - "enable": false - } - } -} diff --git a/cardano-chain-gen/test/testfiles/config-conway/test-db-sync-config-no-plutus.json b/cardano-chain-gen/test/testfiles/config-conway/test-db-sync-config-no-plutus.json deleted file mode 100644 index f8fbe0c44..000000000 --- a/cardano-chain-gen/test/testfiles/config-conway/test-db-sync-config-no-plutus.json +++ /dev/null @@ -1,119 +0,0 @@ -{ - "EnableLogMetrics": false, - "EnableLogging": true, - "NetworkName": "testing", - "NodeConfigFile": "test-config.json", - "PrometheusPort": 8080, - "RequiresNetworkMagic": "RequiresMagic", - "defaultBackends": [ - "KatipBK" - ], - "defaultScribes": [ - [ - "StdoutSK", - "stdout" - ] - ], - "minSeverity": "Info", - "options": { - "cfokey": { - "value": "Release-1.0.0" - }, - "mapBackends": {}, - "mapSeverity": { - "db-sync-node": "Info", - "db-sync-node.Mux": "Error", - "db-sync-node.Subscription": "Error" - }, - "mapSubtrace": { - "#ekgview": { - "contents": [ - [ - { - "contents": "cardano.epoch-validation.benchmark", - "tag": "Contains" - }, - [ - { - "contents": ".monoclock.basic.", - "tag": "Contains" - } - ] - ], - [ - { - "contents": "cardano.epoch-validation.benchmark", - "tag": "Contains" - }, - [ - { - "contents": "diff.RTS.cpuNs.timed.", - "tag": "Contains" - } - ] - ], - [ - { - "contents": "#ekgview.#aggregation.cardano.epoch-validation.benchmark", - "tag": "StartsWith" - }, - [ - { - "contents": "diff.RTS.gcNum.timed.", - "tag": "Contains" - } - ] - ] - ], - "subtrace": "FilterTrace" - }, - "#messagecounters.aggregation": { - "subtrace": "NoTrace" - }, - "#messagecounters.ekgview": { - "subtrace": "NoTrace" - }, - "#messagecounters.katip": { - "subtrace": "NoTrace" - }, - "#messagecounters.monitoring": { - "subtrace": "NoTrace" - }, - "#messagecounters.switchboard": { - "subtrace": "NoTrace" - }, - "benchmark": { - "contents": [ - "GhcRtsStats", - "MonotonicClock" - ], - "subtrace": "ObservableTrace" - }, - "cardano.epoch-validation.utxo-stats": { - "subtrace": "NoTrace" - } - } - }, - "rotation": { - "rpKeepFilesNum": 10, - "rpLogLimitBytes": 5000000, - "rpMaxAgeHours": 24 - }, - "setupBackends": [ - "AggregationBK", - "KatipBK" - ], - "setupScribes": [ - { - "scFormat": "ScText", - "scKind": "StdoutSK", - "scName": "stdout", - "scRotation": null - } - ], - "insert_options": { - "plutus": { - "enable": false - } - } -} diff --git a/cardano-chain-gen/test/testfiles/config-conway/test-db-sync-config-no-shelley.json b/cardano-chain-gen/test/testfiles/config-conway/test-db-sync-config-no-shelley.json deleted file mode 100644 index 08b8a98e0..000000000 --- a/cardano-chain-gen/test/testfiles/config-conway/test-db-sync-config-no-shelley.json +++ /dev/null @@ -1,119 +0,0 @@ -{ - "EnableLogMetrics": false, - "EnableLogging": true, - "NetworkName": "testing", - "NodeConfigFile": "test-config.json", - "PrometheusPort": 8080, - "RequiresNetworkMagic": "RequiresMagic", - "defaultBackends": [ - "KatipBK" - ], - "defaultScribes": [ - [ - "StdoutSK", - "stdout" - ] - ], - "minSeverity": "Info", - "options": { - "cfokey": { - "value": "Release-1.0.0" - }, - "mapBackends": {}, - "mapSeverity": { - "db-sync-node": "Info", - "db-sync-node.Mux": "Error", - "db-sync-node.Subscription": "Error" - }, - "mapSubtrace": { - "#ekgview": { - "contents": [ - [ - { - "contents": "cardano.epoch-validation.benchmark", - "tag": "Contains" - }, - [ - { - "contents": ".monoclock.basic.", - "tag": "Contains" - } - ] - ], - [ - { - "contents": "cardano.epoch-validation.benchmark", - "tag": "Contains" - }, - [ - { - "contents": "diff.RTS.cpuNs.timed.", - "tag": "Contains" - } - ] - ], - [ - { - "contents": "#ekgview.#aggregation.cardano.epoch-validation.benchmark", - "tag": "StartsWith" - }, - [ - { - "contents": "diff.RTS.gcNum.timed.", - "tag": "Contains" - } - ] - ] - ], - "subtrace": "FilterTrace" - }, - "#messagecounters.aggregation": { - "subtrace": "NoTrace" - }, - "#messagecounters.ekgview": { - "subtrace": "NoTrace" - }, - "#messagecounters.katip": { - "subtrace": "NoTrace" - }, - "#messagecounters.monitoring": { - "subtrace": "NoTrace" - }, - "#messagecounters.switchboard": { - "subtrace": "NoTrace" - }, - "benchmark": { - "contents": [ - "GhcRtsStats", - "MonotonicClock" - ], - "subtrace": "ObservableTrace" - }, - "cardano.epoch-validation.utxo-stats": { - "subtrace": "NoTrace" - } - } - }, - "rotation": { - "rpKeepFilesNum": 10, - "rpLogLimitBytes": 5000000, - "rpMaxAgeHours": 24 - }, - "setupBackends": [ - "AggregationBK", - "KatipBK" - ], - "setupScribes": [ - { - "scFormat": "ScText", - "scKind": "StdoutSK", - "scName": "stdout", - "scRotation": null - } - ], - "insert_options": { - "shelley": { - "enable": false - } - } -} diff --git a/cardano-chain-gen/test/testfiles/config-conway/test-db-sync-config-prune.json b/cardano-chain-gen/test/testfiles/config-conway/test-db-sync-config-prune.json deleted file mode 100644 index ba6cbd27c..000000000 --- a/cardano-chain-gen/test/testfiles/config-conway/test-db-sync-config-prune.json +++ /dev/null @@ -1,120 +0,0 @@ -{ - "EnableLogMetrics": false, - "EnableLogging": true, - "NetworkName": "testing", - "NodeConfigFile": "test-config.json", - "PrometheusPort": 8080, - "RequiresNetworkMagic": "RequiresMagic", - "defaultBackends": [ - "KatipBK" - ], - "defaultScribes": [ - [ - "StdoutSK", - "stdout" - ] - ], - "minSeverity": "Info", - "options": { - "cfokey": { - "value": "Release-1.0.0" - }, - "mapBackends": {}, - "mapSeverity": { - "db-sync-node": "Info", - "db-sync-node.Mux": "Error", - "db-sync-node.Subscription": "Error" - }, - "mapSubtrace": { - "#ekgview": { - "contents": [ - [ - { - "contents": "cardano.epoch-validation.benchmark", - "tag": "Contains" - }, - [ - { - "contents": ".monoclock.basic.", - "tag": "Contains" - } - ] - ], - [ - { - "contents": "cardano.epoch-validation.benchmark", - "tag": "Contains" - }, - [ - { - "contents": "diff.RTS.cpuNs.timed.", - "tag": "Contains" - } - ] - ], - [ - { - "contents": "#ekgview.#aggregation.cardano.epoch-validation.benchmark", - "tag": "StartsWith" - }, - [ - { - "contents": "diff.RTS.gcNum.timed.", - "tag": "Contains" - } - ] - ] - ], - "subtrace": "FilterTrace" - }, - "#messagecounters.aggregation": { - "subtrace": "NoTrace" - }, - "#messagecounters.ekgview": { - "subtrace": "NoTrace" - }, - "#messagecounters.katip": { - "subtrace": "NoTrace" - }, - "#messagecounters.monitoring": { - "subtrace": "NoTrace" - }, - "#messagecounters.switchboard": { - "subtrace": "NoTrace" - }, - "benchmark": { - "contents": [ - "GhcRtsStats", - "MonotonicClock" - ], - "subtrace": "ObservableTrace" - }, - "cardano.epoch-validation.utxo-stats": { - "subtrace": "NoTrace" - } - } - }, - "rotation": { - "rpKeepFilesNum": 10, - "rpLogLimitBytes": 5000000, - "rpMaxAgeHours": 24 - }, - "setupBackends": [ - "AggregationBK", - "KatipBK" - ], - "setupScribes": [ - { - "scFormat": "ScText", - "scKind": "StdoutSK", - "scName": "stdout", - "scRotation": null - } - ], - "insert_options": { - "tx_out": { - "value": "prune", - "force_tx_in": true - } - } -} diff --git a/cardano-chain-gen/test/testfiles/config/test-db-sync-config-bootstrap.json b/cardano-chain-gen/test/testfiles/config/test-db-sync-config-bootstrap.json deleted file mode 100644 index 43e6c11bc..000000000 --- a/cardano-chain-gen/test/testfiles/config/test-db-sync-config-bootstrap.json +++ /dev/null @@ -1,119 +0,0 @@ -{ - "EnableLogMetrics": false, - "EnableLogging": true, - "NetworkName": "testing", - "NodeConfigFile": "test-config.json", - "PrometheusPort": 8080, - "RequiresNetworkMagic": "RequiresMagic", - "defaultBackends": [ - "KatipBK" - ], - "defaultScribes": [ - [ - "StdoutSK", - "stdout" - ] - ], - "minSeverity": "Info", - "options": { - "cfokey": { - "value": "Release-1.0.0" - }, - "mapBackends": {}, - "mapSeverity": { - "db-sync-node": "Info", - "db-sync-node.Mux": "Error", - "db-sync-node.Subscription": "Error" - }, - "mapSubtrace": { - "#ekgview": { - "contents": [ - [ - { - "contents": "cardano.epoch-validation.benchmark", - "tag": "Contains" - }, - [ - { - "contents": ".monoclock.basic.", - "tag": "Contains" - } - ] - ], - [ - { - "contents": "cardano.epoch-validation.benchmark", - "tag": "Contains" - }, - [ - { - "contents": "diff.RTS.cpuNs.timed.", - "tag": "Contains" - } - ] - ], - [ - { - "contents": "#ekgview.#aggregation.cardano.epoch-validation.benchmark", - "tag": "StartsWith" - }, - [ - { - "contents": "diff.RTS.gcNum.timed.", - "tag": "Contains" - } - ] - ] - ], - "subtrace": "FilterTrace" - }, - "#messagecounters.aggregation": { - "subtrace": "NoTrace" - }, - "#messagecounters.ekgview": { - "subtrace": "NoTrace" - }, - "#messagecounters.katip": { - "subtrace": "NoTrace" - }, - "#messagecounters.monitoring": { - "subtrace": "NoTrace" - }, - "#messagecounters.switchboard": { - "subtrace": "NoTrace" - }, - "benchmark": { - "contents": [ - "GhcRtsStats", - "MonotonicClock" - ], - "subtrace": "ObservableTrace" - }, - "cardano.epoch-validation.utxo-stats": { - "subtrace": "NoTrace" - } - } - }, - "rotation": { - "rpKeepFilesNum": 10, - "rpLogLimitBytes": 5000000, - "rpMaxAgeHours": 24 - }, - "setupBackends": [ - "AggregationBK", - "KatipBK" - ], - "setupScribes": [ - { - "scFormat": "ScText", - "scKind": "StdoutSK", - "scName": "stdout", - "scRotation": null - } - ], - "insert_options": { - "tx_out": { - "value": "bootstrap" - } - } -} diff --git a/cardano-chain-gen/test/testfiles/config/test-db-sync-config-consumed.json b/cardano-chain-gen/test/testfiles/config/test-db-sync-config-consumed.json deleted file mode 100644 index 2f2f682ac..000000000 --- a/cardano-chain-gen/test/testfiles/config/test-db-sync-config-consumed.json +++ /dev/null @@ -1,119 +0,0 @@ -{ - "EnableLogMetrics": false, - "EnableLogging": true, - "NetworkName": "testing", - "NodeConfigFile": "test-config.json", - "PrometheusPort": 8080, - "RequiresNetworkMagic": "RequiresMagic", - "defaultBackends": [ - "KatipBK" - ], - "defaultScribes": [ - [ - "StdoutSK", - "stdout" - ] - ], - "minSeverity": "Info", - "options": { - "cfokey": { - "value": "Release-1.0.0" - }, - "mapBackends": {}, - "mapSeverity": { - "db-sync-node": "Info", - "db-sync-node.Mux": "Error", - "db-sync-node.Subscription": "Error" - }, - "mapSubtrace": { - "#ekgview": { - "contents": [ - [ - { - "contents": "cardano.epoch-validation.benchmark", - "tag": "Contains" - }, - [ - { - "contents": ".monoclock.basic.", - "tag": "Contains" - } - ] - ], - [ - { - "contents": "cardano.epoch-validation.benchmark", - "tag": "Contains" - }, - [ - { - "contents": "diff.RTS.cpuNs.timed.", - "tag": "Contains" - } - ] - ], - [ - { - "contents": "#ekgview.#aggregation.cardano.epoch-validation.benchmark", - "tag": "StartsWith" - }, - [ - { - "contents": "diff.RTS.gcNum.timed.", - "tag": "Contains" - } - ] - ] - ], - "subtrace": "FilterTrace" - }, - "#messagecounters.aggregation": { - "subtrace": "NoTrace" - }, - "#messagecounters.ekgview": { - "subtrace": "NoTrace" - }, - "#messagecounters.katip": { - "subtrace": "NoTrace" - }, - "#messagecounters.monitoring": { - "subtrace": "NoTrace" - }, - "#messagecounters.switchboard": { - "subtrace": "NoTrace" - }, - "benchmark": { - "contents": [ - "GhcRtsStats", - "MonotonicClock" - ], - "subtrace": "ObservableTrace" - }, - "cardano.epoch-validation.utxo-stats": { - "subtrace": "NoTrace" - } - } - }, - "rotation": { - "rpKeepFilesNum": 10, - "rpLogLimitBytes": 5000000, - "rpMaxAgeHours": 24 - }, - "setupBackends": [ - "AggregationBK", - "KatipBK" - ], - "setupScribes": [ - { - "scFormat": "ScText", - "scKind": "StdoutSK", - "scName": "stdout", - "scRotation": null - } - ], - "insert_options": { - "tx_out": { - "value": "consumed" - } - } -} diff --git a/cardano-chain-gen/test/testfiles/config/test-db-sync-config-prune.json b/cardano-chain-gen/test/testfiles/config/test-db-sync-config-prune.json deleted file mode 100644 index ba6cbd27c..000000000 --- a/cardano-chain-gen/test/testfiles/config/test-db-sync-config-prune.json +++ /dev/null @@ -1,120 +0,0 @@ -{ - "EnableLogMetrics": false, - "EnableLogging": true, - "NetworkName": "testing", - "NodeConfigFile": "test-config.json", - "PrometheusPort": 8080, - "RequiresNetworkMagic": "RequiresMagic", - "defaultBackends": [ - "KatipBK" - ], - "defaultScribes": [ - [ - "StdoutSK", - "stdout" - ] - ], - "minSeverity": "Info", - "options": { - "cfokey": { - "value": "Release-1.0.0" - }, - "mapBackends": {}, - "mapSeverity": { - "db-sync-node": "Info", - "db-sync-node.Mux": "Error", - "db-sync-node.Subscription": "Error" - }, - "mapSubtrace": { - "#ekgview": { - "contents": [ - [ - { - "contents": "cardano.epoch-validation.benchmark", - "tag": "Contains" - }, - [ - { - "contents": ".monoclock.basic.", - "tag": "Contains" - } - ] - ], - [ - { - "contents": "cardano.epoch-validation.benchmark", - "tag": "Contains" - }, - [ - { - "contents": "diff.RTS.cpuNs.timed.", - "tag": "Contains" - } - ] - ], - [ - { - "contents": "#ekgview.#aggregation.cardano.epoch-validation.benchmark", - "tag": "StartsWith" - }, - [ - { - "contents": "diff.RTS.gcNum.timed.", - "tag": "Contains" - } - ] - ] - ], - "subtrace": "FilterTrace" - }, - "#messagecounters.aggregation": { - "subtrace": "NoTrace" - }, - "#messagecounters.ekgview": { - "subtrace": "NoTrace" - }, - "#messagecounters.katip": { - "subtrace": "NoTrace" - }, - "#messagecounters.monitoring": { - "subtrace": "NoTrace" - }, - "#messagecounters.switchboard": { - "subtrace": "NoTrace" - }, - "benchmark": { - "contents": [ - "GhcRtsStats", - "MonotonicClock" - ], - "subtrace": "ObservableTrace" - }, - "cardano.epoch-validation.utxo-stats": { - "subtrace": "NoTrace" - } - } - }, - "rotation": { - "rpKeepFilesNum": 10, - "rpLogLimitBytes": 5000000, - "rpMaxAgeHours": 24 - }, - "setupBackends": [ - "AggregationBK", - "KatipBK" - ], - "setupScribes": [ - { - "scFormat": "ScText", - "scKind": "StdoutSK", - "scName": "stdout", - "scRotation": null - } - ], - "insert_options": { - "tx_out": { - "value": "prune", - "force_tx_in": true - } - } -}