Skip to content

Commit

Permalink
add tests for using address table
Browse files Browse the repository at this point in the history
poop
  • Loading branch information
Cmdv committed Sep 24, 2024
1 parent d4a5d9b commit 1b5b4fa
Show file tree
Hide file tree
Showing 18 changed files with 511 additions and 200 deletions.
24 changes: 12 additions & 12 deletions cardano-chain-gen/test/Test/Cardano/Db/Mock/Config.hs
Original file line number Diff line number Diff line change
Expand Up @@ -302,21 +302,21 @@ mkConfigFile :: FilePath -> FilePath -> ConfigFile
mkConfigFile staticDir cliConfigFilename =
ConfigFile $ staticDir </> cliConfigFilename

configPruneForceTxIn :: SyncNodeConfig -> SyncNodeConfig
configPruneForceTxIn cfg = do
cfg {dncInsertOptions = (dncInsertOptions cfg) {sioTxOut = TxOutConsumedPrune (ForceTxIn True) (UseTxOutAddress False)}}
configPruneForceTxIn :: Bool -> SyncNodeConfig -> SyncNodeConfig
configPruneForceTxIn useTxOutAddress cfg = do
cfg {dncInsertOptions = (dncInsertOptions cfg) {sioTxOut = TxOutConsumedPrune (ForceTxIn True) (UseTxOutAddress useTxOutAddress)}}

configPrune :: SyncNodeConfig -> SyncNodeConfig
configPrune cfg = do
cfg {dncInsertOptions = (dncInsertOptions cfg) {sioTxOut = TxOutConsumedPrune (ForceTxIn False) (UseTxOutAddress False)}}
configPrune :: Bool -> SyncNodeConfig -> SyncNodeConfig
configPrune useTxOutAddress cfg = do
cfg {dncInsertOptions = (dncInsertOptions cfg) {sioTxOut = TxOutConsumedPrune (ForceTxIn False) (UseTxOutAddress useTxOutAddress)}}

configConsume :: SyncNodeConfig -> SyncNodeConfig
configConsume cfg = do
cfg {dncInsertOptions = (dncInsertOptions cfg) {sioTxOut = TxOutConsumed (ForceTxIn False) (UseTxOutAddress False)}}
configConsume :: Bool -> SyncNodeConfig -> SyncNodeConfig
configConsume useTxOutAddress cfg = do
cfg {dncInsertOptions = (dncInsertOptions cfg) {sioTxOut = TxOutConsumed (ForceTxIn False) (UseTxOutAddress useTxOutAddress)}}

configBootstrap :: SyncNodeConfig -> SyncNodeConfig
configBootstrap cfg = do
cfg {dncInsertOptions = (dncInsertOptions cfg) {sioTxOut = TxOutConsumedBootstrap (ForceTxIn False) (UseTxOutAddress False)}}
configBootstrap :: Bool -> SyncNodeConfig -> SyncNodeConfig
configBootstrap useTxOutAddress cfg = do
cfg {dncInsertOptions = (dncInsertOptions cfg) {sioTxOut = TxOutConsumedBootstrap (ForceTxIn False) (UseTxOutAddress useTxOutAddress)}}

configPlutusDisable :: SyncNodeConfig -> SyncNodeConfig
configPlutusDisable cfg = do
Expand Down
17 changes: 16 additions & 1 deletion cardano-chain-gen/test/Test/Cardano/Db/Mock/Unit/Babbage.hs
Original file line number Diff line number Diff line change
Expand Up @@ -34,8 +34,9 @@ unitTests iom knownMigrations =
[ testCase "default insert config" Config.defaultInsertConfig
, testCase "insert config" Config.insertConfig
, testGroup
"consumed-tx-out and prune-tx-out"
"tx-out"
[ test "basic prune" MigrateConsumedPruneTxOut.basicPrune
, test "basic prune with address table" MigrateConsumedPruneTxOut.basicPruneWithAddress
, test "prune with simple rollback" MigrateConsumedPruneTxOut.pruneWithSimpleRollback
, test "prune with full tx rollback" MigrateConsumedPruneTxOut.pruneWithFullTxRollback
, test "pruning should keep some tx" MigrateConsumedPruneTxOut.pruningShouldKeepSomeTx
Expand All @@ -47,6 +48,20 @@ unitTests iom knownMigrations =
, expectFailSilent "set prune flag, restart missing prune flag" $ MigrateConsumedPruneTxOut.pruneRestartMissingFlag iom knownMigrations
, expectFailSilent "set bootstrap flag, restart missing bootstrap flag" $ MigrateConsumedPruneTxOut.bootstrapRestartMissingFlag iom knownMigrations
]
, testGroup
"tx-out using Address table"
[ test "basic prune with address table" MigrateConsumedPruneTxOut.basicPruneWithAddress
, test "prune with simple rollback with address table" MigrateConsumedPruneTxOut.pruneWithSimpleRollbackWithAddress
, test "prune with full tx rollback with address table" MigrateConsumedPruneTxOut.pruneWithFullTxRollbackWithAddress
, test "pruning should keep some tx with address table" MigrateConsumedPruneTxOut.pruningShouldKeepSomeTxWithAddress
, test "prune and rollback one block with address table" MigrateConsumedPruneTxOut.pruneAndRollBackOneBlockWithAddress
, test "no pruning and rollback with address table" MigrateConsumedPruneTxOut.noPruneAndRollBackWithAddress
, test "prune same block with address table" MigrateConsumedPruneTxOut.pruneSameBlockWithAddress
, test "no pruning same block with address table" MigrateConsumedPruneTxOut.noPruneSameBlockWithAddress
, expectFailSilent "restart with new consumed set to false, with address table" $ MigrateConsumedPruneTxOut.migrateAndPruneRestartWithAddress iom knownMigrations
, expectFailSilent "set prune flag, restart missing prune flag, with address table" $ MigrateConsumedPruneTxOut.pruneRestartMissingFlagWithAddress iom knownMigrations
, expectFailSilent "set bootstrap flag, restart missing bootstrap flag, with address table" $ MigrateConsumedPruneTxOut.bootstrapRestartMissingFlagWithAddress iom knownMigrations
]
]
, testGroup
"simple"
Expand Down
Original file line number Diff line number Diff line change
Expand Up @@ -7,16 +7,27 @@

module Test.Cardano.Db.Mock.Unit.Babbage.Config.MigrateConsumedPruneTxOut (
basicPrune,
basicPruneWithAddress,
pruneWithSimpleRollback,
pruneWithSimpleRollbackWithAddress,
pruneWithFullTxRollback,
pruneWithFullTxRollbackWithAddress,
pruningShouldKeepSomeTx,
pruningShouldKeepSomeTxWithAddress,
pruneAndRollBackOneBlock,
pruneAndRollBackOneBlockWithAddress,
noPruneAndRollBack,
noPruneAndRollBackWithAddress,
pruneSameBlock,
pruneSameBlockWithAddress,
noPruneSameBlock,
noPruneSameBlockWithAddress,
migrateAndPruneRestart,
migrateAndPruneRestartWithAddress,
pruneRestartMissingFlag,
pruneRestartMissingFlagWithAddress,
bootstrapRestartMissingFlag,
bootstrapRestartMissingFlagWithAddress,
) where

import Cardano.Db (TxOutTableType (..))
Expand All @@ -41,7 +52,7 @@ import Test.Cardano.Db.Mock.Config (
startDBSync,
stopDBSync,
txOutTableTypeFromConfig,
withCustomConfig,
withCustomConfigAndDropDB,
)
import Test.Cardano.Db.Mock.Examples (mockBlock0, mockBlock1)
import Test.Cardano.Db.Mock.UnifiedApi (
Expand All @@ -59,8 +70,14 @@ import Test.Tasty.HUnit (Assertion)
-- Tests
------------------------------------------------------------------------------
basicPrune :: IOManager -> [(Text, Text)] -> Assertion
basicPrune = do
withCustomConfig cmdLineArgs (Just configPruneForceTxIn) babbageConfigDir testLabel $ \interpreter mockServer dbSyncEnv -> do
basicPrune = peformBasicPrune False

basicPruneWithAddress :: IOManager -> [(Text, Text)] -> Assertion
basicPruneWithAddress = peformBasicPrune True

peformBasicPrune :: Bool -> IOManager -> [(Text, Text)] -> Assertion
peformBasicPrune useTxOutAddress = do
withCustomConfigAndDropDB cmdLineArgs (Just $ configPruneForceTxIn useTxOutAddress) babbageConfigDir testLabel $ \interpreter mockServer dbSyncEnv -> do
let txOutTableType = txOutTableTypeFromConfig dbSyncEnv
startDBSync dbSyncEnv
-- add 50 block
Expand All @@ -84,8 +101,14 @@ basicPrune = do
testLabel = "configPrune"

pruneWithSimpleRollback :: IOManager -> [(Text, Text)] -> Assertion
pruneWithSimpleRollback = do
withCustomConfig cmdLineArgs (Just configPruneForceTxIn) babbageConfigDir testLabel $ \interpreter mockServer dbSyncEnv -> do
pruneWithSimpleRollback = peformPruneWithSimpleRollback False

pruneWithSimpleRollbackWithAddress :: IOManager -> [(Text, Text)] -> Assertion
pruneWithSimpleRollbackWithAddress = peformPruneWithSimpleRollback True

peformPruneWithSimpleRollback :: Bool -> IOManager -> [(Text, Text)] -> Assertion
peformPruneWithSimpleRollback useTxOutAddress = do
withCustomConfigAndDropDB cmdLineArgs (Just $ configPruneForceTxIn useTxOutAddress) babbageConfigDir testLabel $ \interpreter mockServer dbSyncEnv -> do
let txOutTableType = txOutTableTypeFromConfig dbSyncEnv
blk0 <- forgeNext interpreter mockBlock0
blk1 <- forgeNext interpreter mockBlock1
Expand All @@ -110,8 +133,14 @@ pruneWithSimpleRollback = do
testLabel = "configPruneSimpleRollback"

pruneWithFullTxRollback :: IOManager -> [(Text, Text)] -> Assertion
pruneWithFullTxRollback = do
withCustomConfig cmdLineArgs (Just configPruneForceTxIn) babbageConfigDir testLabel $ \interpreter mockServer dbSyncEnv -> do
pruneWithFullTxRollback = performPruneWithFullTxRollback False

pruneWithFullTxRollbackWithAddress :: IOManager -> [(Text, Text)] -> Assertion
pruneWithFullTxRollbackWithAddress = performPruneWithFullTxRollback True

performPruneWithFullTxRollback :: Bool -> IOManager -> [(Text, Text)] -> Assertion
performPruneWithFullTxRollback useTxOutAddress = do
withCustomConfigAndDropDB cmdLineArgs (Just $ configPruneForceTxIn useTxOutAddress) babbageConfigDir testLabel $ \interpreter mockServer dbSyncEnv -> do
let txOutTableType = txOutTableTypeFromConfig dbSyncEnv
startDBSync dbSyncEnv
blk0 <- forgeNextFindLeaderAndSubmit interpreter mockServer []
Expand Down Expand Up @@ -140,8 +169,14 @@ pruneWithFullTxRollback = do
-- 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 = do
withCustomConfig cmdLineArgs (Just configPrune) babbageConfigDir testLabel $ \interpreter mockServer dbSyncEnv -> do
pruningShouldKeepSomeTx = performPruningShouldKeepSomeTx False

pruningShouldKeepSomeTxWithAddress :: IOManager -> [(Text, Text)] -> Assertion
pruningShouldKeepSomeTxWithAddress = performPruningShouldKeepSomeTx True

performPruningShouldKeepSomeTx :: Bool -> IOManager -> [(Text, Text)] -> Assertion
performPruningShouldKeepSomeTx useTxOutAddress = do
withCustomConfigAndDropDB cmdLineArgs (Just $ configPrune useTxOutAddress) babbageConfigDir testLabel $ \interpreter mockServer dbSyncEnv -> do
startDBSync dbSyncEnv
let txOutTableType = txOutTableTypeFromConfig dbSyncEnv
b1 <- forgeAndSubmitBlocks interpreter mockServer 80
Expand All @@ -164,8 +199,14 @@ pruningShouldKeepSomeTx = do

-- prune with rollback
pruneAndRollBackOneBlock :: IOManager -> [(Text, Text)] -> Assertion
pruneAndRollBackOneBlock = do
withCustomConfig cmdLineArgs (Just configPruneForceTxIn) babbageConfigDir testLabel $ \interpreter mockServer dbSyncEnv -> do
pruneAndRollBackOneBlock = performPruneAndRollBackOneBlock False

pruneAndRollBackOneBlockWithAddress :: IOManager -> [(Text, Text)] -> Assertion
pruneAndRollBackOneBlockWithAddress = performPruneAndRollBackOneBlock True

performPruneAndRollBackOneBlock :: Bool -> IOManager -> [(Text, Text)] -> Assertion
performPruneAndRollBackOneBlock useTxOutAddress = do
withCustomConfigAndDropDB cmdLineArgs (Just $ configPruneForceTxIn useTxOutAddress) babbageConfigDir testLabel $ \interpreter mockServer dbSyncEnv -> do
startDBSync dbSyncEnv
let txOutTableType = txOutTableTypeFromConfig dbSyncEnv
void $ forgeAndSubmitBlocks interpreter mockServer 98
Expand Down Expand Up @@ -197,8 +238,14 @@ pruneAndRollBackOneBlock = do

-- consume with rollback
noPruneAndRollBack :: IOManager -> [(Text, Text)] -> Assertion
noPruneAndRollBack = do
withCustomConfig cmdLineArgs (Just configConsume) babbageConfigDir testLabel $ \interpreter mockServer dbSyncEnv -> do
noPruneAndRollBack = performNoPruneAndRollBack False

noPruneAndRollBackWithAddress :: IOManager -> [(Text, Text)] -> Assertion
noPruneAndRollBackWithAddress = performNoPruneAndRollBack True

performNoPruneAndRollBack :: Bool -> IOManager -> [(Text, Text)] -> Assertion
performNoPruneAndRollBack useTxOutAddress = do
withCustomConfigAndDropDB cmdLineArgs (Just $ configConsume useTxOutAddress) babbageConfigDir testLabel $ \interpreter mockServer dbSyncEnv -> do
startDBSync dbSyncEnv
let txOutTableType = txOutTableTypeFromConfig dbSyncEnv
void $ forgeAndSubmitBlocks interpreter mockServer 98
Expand Down Expand Up @@ -229,8 +276,14 @@ noPruneAndRollBack = do
testLabel = "configPruneAndRollBack"

pruneSameBlock :: IOManager -> [(Text, Text)] -> Assertion
pruneSameBlock =
withCustomConfig cmdLineArgs (Just configPruneForceTxIn) babbageConfigDir testLabel $ \interpreter mockServer dbSyncEnv -> do
pruneSameBlock = performPruneSameBlock False

pruneSameBlockWithAddress :: IOManager -> [(Text, Text)] -> Assertion
pruneSameBlockWithAddress = performPruneSameBlock True

performPruneSameBlock :: Bool -> IOManager -> [(Text, Text)] -> Assertion
performPruneSameBlock useTxOutAddress =
withCustomConfigAndDropDB cmdLineArgs (Just $ configPruneForceTxIn useTxOutAddress) babbageConfigDir testLabel $ \interpreter mockServer dbSyncEnv -> do
startDBSync dbSyncEnv
let txOutTableType = txOutTableTypeFromConfig dbSyncEnv
void $ forgeAndSubmitBlocks interpreter mockServer 76
Expand All @@ -255,8 +308,14 @@ pruneSameBlock =
testLabel = "configPruneSameBlock"

noPruneSameBlock :: IOManager -> [(Text, Text)] -> Assertion
noPruneSameBlock =
withCustomConfig cmdLineArgs (Just configConsume) babbageConfigDir testLabel $ \interpreter mockServer dbSyncEnv -> do
noPruneSameBlock = performNoPruneSameBlock False

noPruneSameBlockWithAddress :: IOManager -> [(Text, Text)] -> Assertion
noPruneSameBlockWithAddress = performNoPruneSameBlock True

performNoPruneSameBlock :: Bool -> IOManager -> [(Text, Text)] -> Assertion
performNoPruneSameBlock useTxOutAddress =
withCustomConfigAndDropDB cmdLineArgs (Just $ configConsume useTxOutAddress) babbageConfigDir testLabel $ \interpreter mockServer dbSyncEnv -> do
startDBSync dbSyncEnv
let txOutTableType = txOutTableTypeFromConfig dbSyncEnv
void $ forgeAndSubmitBlocks interpreter mockServer 96
Expand All @@ -278,8 +337,14 @@ noPruneSameBlock =
testLabel = "configNoPruneSameBlock"

migrateAndPruneRestart :: IOManager -> [(Text, Text)] -> Assertion
migrateAndPruneRestart = do
withCustomConfig cmdLineArgs (Just configConsume) babbageConfigDir testLabel $ \interpreter mockServer dbSyncEnv -> do
migrateAndPruneRestart = performMigrateAndPruneRestart False

migrateAndPruneRestartWithAddress :: IOManager -> [(Text, Text)] -> Assertion
migrateAndPruneRestartWithAddress = performMigrateAndPruneRestart True

performMigrateAndPruneRestart :: Bool -> IOManager -> [(Text, Text)] -> Assertion
performMigrateAndPruneRestart useTxOutAddress = do
withCustomConfigAndDropDB cmdLineArgs (Just $ configConsume useTxOutAddress) babbageConfigDir testLabel $ \interpreter mockServer dbSyncEnv -> do
startDBSync dbSyncEnv
void $ forgeAndSubmitBlocks interpreter mockServer 50
assertBlockNoBackoff dbSyncEnv 50
Expand All @@ -297,8 +362,14 @@ migrateAndPruneRestart = do
testLabel = "configMigrateAndPruneRestart"

pruneRestartMissingFlag :: IOManager -> [(Text, Text)] -> Assertion
pruneRestartMissingFlag = do
withCustomConfig cmdLineArgs (Just configPruneForceTxIn) babbageConfigDir testLabel $ \interpreter mockServer dbSyncEnv -> do
pruneRestartMissingFlag = performPruneRestartMissingFlag False

pruneRestartMissingFlagWithAddress :: IOManager -> [(Text, Text)] -> Assertion
pruneRestartMissingFlagWithAddress = performPruneRestartMissingFlag True

performPruneRestartMissingFlag :: Bool -> IOManager -> [(Text, Text)] -> Assertion
performPruneRestartMissingFlag useTxOutAddress = do
withCustomConfigAndDropDB cmdLineArgs (Just $ configPruneForceTxIn useTxOutAddress) babbageConfigDir testLabel $ \interpreter mockServer dbSyncEnv -> do
startDBSync dbSyncEnv
void $ forgeAndSubmitBlocks interpreter mockServer 50
assertBlockNoBackoff dbSyncEnv 50
Expand All @@ -316,8 +387,14 @@ pruneRestartMissingFlag = do
testLabel = "configPruneRestartMissingFlag"

bootstrapRestartMissingFlag :: IOManager -> [(Text, Text)] -> Assertion
bootstrapRestartMissingFlag = do
withCustomConfig cmdLineArgs (Just configBootstrap) babbageConfigDir testLabel $ \interpreter mockServer dbSyncEnv -> do
bootstrapRestartMissingFlag = performBootstrapRestartMissingFlag False

bootstrapRestartMissingFlagWithAddress :: IOManager -> [(Text, Text)] -> Assertion
bootstrapRestartMissingFlagWithAddress = performBootstrapRestartMissingFlag True

performBootstrapRestartMissingFlag :: Bool -> IOManager -> [(Text, Text)] -> Assertion
performBootstrapRestartMissingFlag useTxOutAddress = do
withCustomConfigAndDropDB cmdLineArgs (Just $ configBootstrap useTxOutAddress) babbageConfigDir testLabel $ \interpreter mockServer dbSyncEnv -> do
startDBSync dbSyncEnv
void $ forgeAndSubmitBlocks interpreter mockServer 50
assertBlockNoBackoff dbSyncEnv 50
Expand Down
23 changes: 23 additions & 0 deletions cardano-chain-gen/test/Test/Cardano/Db/Mock/Unit/Conway.hs
Original file line number Diff line number Diff line change
Expand Up @@ -62,6 +62,29 @@ unitTests iom knownMigrations =
"set bootstrap flag, restart missing bootstrap flag"
$ MigrateConsumedPruneTxOut.bootstrapRestartMissingFlag iom knownMigrations
]
, testGroup
"tx-out with use_address_table config"
[ test "basic prune, with use_address_table config" MigrateConsumedPruneTxOut.basicPruneWithAddress
, test "prune with simple rollback, with use_address_table config" MigrateConsumedPruneTxOut.pruneWithSimpleRollbackWithAddress
, test "prune with full tx rollback, with use_address_table config" MigrateConsumedPruneTxOut.pruneWithFullTxRollbackWithAddress
, test "pruning should keep some tx, with use_address_table config" MigrateConsumedPruneTxOut.pruningShouldKeepSomeTxWithAddress
, test "prune and rollback one block, with use_address_table config" MigrateConsumedPruneTxOut.pruneAndRollBackOneBlockWithAddress
, test "no pruning and rollback, with use_address_table config" MigrateConsumedPruneTxOut.noPruneAndRollBackWithAddress
, test "prune same block, with use_address_table config" MigrateConsumedPruneTxOut.pruneSameBlockWithAddress
, test "no pruning same block, with use_address_table config" MigrateConsumedPruneTxOut.noPruneSameBlockWithAddress
, expectFailSilent
"restart with new consumed set to false, with use_address_table config"
$ MigrateConsumedPruneTxOut.migrateAndPruneRestartWithAddress iom knownMigrations
, expectFailSilent
"set prune flag, restart missing prune flag, with use_address_table config"
$ MigrateConsumedPruneTxOut.pruneRestartMissingFlagWithAddress iom knownMigrations
, expectFailSilent
"set bootstrap flag, restart missing bootstrap flag, with use_address_table config"
$ MigrateConsumedPruneTxOut.bootstrapRestartMissingFlagWithAddress iom knownMigrations
, expectFailSilent
"populate db then reset with use_address_table config config active"
$ MigrateConsumedPruneTxOut.populateDbRestartWithAddressConfig iom knownMigrations
]
]
, testGroup
"simple"
Expand Down
Loading

0 comments on commit 1b5b4fa

Please sign in to comment.