diff --git a/cardano-chain-gen/src/Cardano/Mock/ChainSync/Server.hs b/cardano-chain-gen/src/Cardano/Mock/ChainSync/Server.hs index 7a2aef256..179fdce88 100644 --- a/cardano-chain-gen/src/Cardano/Mock/ChainSync/Server.hs +++ b/cardano-chain-gen/src/Cardano/Mock/ChainSync/Server.hs @@ -369,8 +369,10 @@ chainSyncServer state codec _blockVersion = atomically $ do cps <- readTVar state let chain = chainDB cps + chainTip = headTip chain case findFirstPoint (map castPoint points) chain of - Nothing -> pure (Nothing, castTip (headTip chain)) + Nothing -> + pure (Nothing, castTip chainTip) Just ipoint -> do let !cps' = updateFollower rid ipoint cps writeTVar state cps' 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 6de19b682..116d74bf8 100644 --- a/cardano-chain-gen/test/Test/Cardano/Db/Mock/Config.hs +++ b/cardano-chain-gen/test/Test/Cardano/Db/Mock/Config.hs @@ -57,6 +57,7 @@ module Test.Cardano.Db.Mock.Config ( withFullConfig, withFullConfigDropDB, withFullConfigDropDBLog, + withFullConfigDropDBNoFingerprint, withFullConfigLog, withCustomConfigDropDBLog, withCustomConfig, @@ -470,6 +471,27 @@ withFullConfigDropDBLog = initCommandLineArgs Nothing +-- For tests that rollback and restart, fingerprints create divergent chains +withFullConfigDropDBNoFingerprint :: + -- | config filepath + FilePath -> + -- | test label + FilePath -> + (Interpreter -> ServerHandle IO CardanoBlock -> DBSyncEnv -> IO a) -> + IOManager -> + [(Text, Text)] -> + IO a +withFullConfigDropDBNoFingerprint = + withFullConfig' + ( WithConfigArgs + { hasFingerprint = False + , shouldLog = False + , shouldDropDB = True + } + ) + initCommandLineArgs + Nothing + withFullConfigLog :: -- | config filepath FilePath -> diff --git a/cardano-chain-gen/test/Test/Cardano/Db/Mock/Property/Property.hs b/cardano-chain-gen/test/Test/Cardano/Db/Mock/Property/Property.hs index aa75b72be..63a089788 100644 --- a/cardano-chain-gen/test/Test/Cardano/Db/Mock/Property/Property.hs +++ b/cardano-chain-gen/test/Test/Cardano/Db/Mock/Property/Property.hs @@ -21,6 +21,7 @@ import Cardano.Mock.Forging.Interpreter import Cardano.Mock.Forging.Tx.Babbage import Cardano.Mock.Forging.Types import Control.Concurrent.Class.MonadSTM.Strict (MonadSTM (atomically)) +import Control.Monad (void) import Data.Foldable import Data.Maybe (isJust) import Data.Text (Text) @@ -129,7 +130,8 @@ transition m cmd resp = case (cmd, resp) of , dbSyncMaxBlockNo = dbSyncMaxBlockNo' } (RollBack blkNo, _) -> - m {serverChain = rollbackChain blkNo (serverChain m)} + -- rollbackTo now forges an empty block after rollback + m {serverChain = rollbackChain blkNo (serverChain m) ++ [0]} (StopDBSync, _) | dbSynsIsOn m -> m {dbSynsIsOn = False} @@ -178,12 +180,12 @@ postcondition _ _ resp = case resp of semantics :: Interpreter -> ServerHandle IO CardanoBlock -> DBSyncEnv -> Command Concrete -> IO (Response Concrete) semantics interpreter mockServer dbSync cmd = case cmd of RollForward n -> NewBlockAdded . reference . Opaque <$> createBlock n interpreter mockServer - RollBack Nothing -> Unit <$> rollbackTo interpreter mockServer GenesisPoint + RollBack Nothing -> Unit <$> void (rollbackTo interpreter mockServer GenesisPoint) RollBack (Just blkNo) -> do chain <- atomically $ readChain mockServer case findFirstPointByBlockNo chain blkNo of Nothing -> pure $ Error $ "Failed to find point for " <> show blkNo - Just pnt -> Unit <$> rollbackTo interpreter mockServer pnt + Just pnt -> Unit <$> void (rollbackTo interpreter mockServer pnt) StopDBSync -> Unit <$> stopDBSync dbSync StartDBSync -> Unit <$> startDBSync dbSync RestartNode -> Unit <$> restartServer mockServer diff --git a/cardano-chain-gen/test/Test/Cardano/Db/Mock/UnifiedApi.hs b/cardano-chain-gen/test/Test/Cardano/Db/Mock/UnifiedApi.hs index 9decefaf3..90b2a57d3 100644 --- a/cardano-chain-gen/test/Test/Cardano/Db/Mock/UnifiedApi.hs +++ b/cardano-chain-gen/test/Test/Cardano/Db/Mock/UnifiedApi.hs @@ -200,10 +200,15 @@ fillEpochPercentage interpreter mockServer percentage = do let blocksToCreate = div (percentage * blocksPerEpoch) 100 replicateM blocksToCreate $ forgeNextFindLeaderAndSubmit interpreter mockServer [] -rollbackTo :: Interpreter -> ServerHandle IO CardanoBlock -> CardanoPoint -> IO () +rollbackTo :: Interpreter -> ServerHandle IO CardanoBlock -> CardanoPoint -> IO [CardanoBlock] rollbackTo interpreter mockServer point = do rollbackInterpreter interpreter point atomically $ rollback mockServer point + -- Forge an empty block to establish a new thread after rollback. + -- This ensures DBSync recognizes the rollback and deletes data. + blk <- forgeNextFindLeader interpreter [] + atomically $ addBlock mockServer blk + pure [blk] registerAllStakeCreds :: Interpreter -> ServerHandle IO CardanoBlock -> IO CardanoBlock registerAllStakeCreds interpreter mockServer = do diff --git a/cardano-chain-gen/test/Test/Cardano/Db/Mock/Unit/Babbage/Plutus.hs b/cardano-chain-gen/test/Test/Cardano/Db/Mock/Unit/Babbage/Plutus.hs index 6ec790247..88c7dc3ec 100644 --- a/cardano-chain-gen/test/Test/Cardano/Db/Mock/Unit/Babbage/Plutus.hs +++ b/cardano-chain-gen/test/Test/Cardano/Db/Mock/Unit/Babbage/Plutus.hs @@ -241,7 +241,7 @@ multipleScriptsRollback = assertBlockNoBackoff dbSync 2 assertAlonzoCounts dbSync (1, 2, 1, 1, 3, 2, 0, 0) - rollbackTo interpreter mockServer genesisPoint + void $ rollbackTo interpreter mockServer genesisPoint void $ forgeNextFindLeaderAndSubmit interpreter mockServer [] void $ forgeNextAndSubmit interpreter mockServer $ MockBlock [TxBabbage tx0] (NodeId 1) diff --git a/cardano-chain-gen/test/Test/Cardano/Db/Mock/Unit/Babbage/Reward.hs b/cardano-chain-gen/test/Test/Cardano/Db/Mock/Unit/Babbage/Reward.hs index 79b679759..ace7cfa36 100644 --- a/cardano-chain-gen/test/Test/Cardano/Db/Mock/Unit/Babbage/Reward.hs +++ b/cardano-chain-gen/test/Test/Cardano/Db/Mock/Unit/Babbage/Reward.hs @@ -17,7 +17,7 @@ import Cardano.Ledger.Shelley.TxBody ( Withdrawals (..), ) import Cardano.Ledger.Shelley.TxCert -import Cardano.Mock.ChainSync.Server (IOManager, addBlock, rollback) +import Cardano.Mock.ChainSync.Server (IOManager, addBlock) import Cardano.Mock.Forging.Interpreter (withShelleyLedgerState) import qualified Cardano.Mock.Forging.Tx.Babbage as Babbage import Cardano.Mock.Forging.Tx.Babbage.Scenarios (delegateAndSendBlocks) @@ -314,7 +314,7 @@ _mirRewardRollback = assertBlockNoBackoff dbSync (fromIntegral $ 4 + length (a <> b <> c <> d)) assertRewardCounts dbSync st True Nothing [(StakeIndexNew 1, (0, 0, 0, 1, 0))] - rollbackTo interpreter mockServer (blockPoint $ last c) + void $ rollbackTo interpreter mockServer (blockPoint $ last c) void $ withBabbageFindLeaderAndSubmitTx interpreter mockServer $ \_ -> Babbage.mkDummyRegisterTx 1 1 d' <- fillUntilNextEpoch interpreter mockServer @@ -491,13 +491,13 @@ rollbackBoundary = blks' <- fillUntilNextEpoch interpreter mockServer assertRewardCount dbSync 3 - atomically $ rollback mockServer (blockPoint $ last blks) - assertBlockNoBackoff dbSync (2 + length a + length blks + length blks') + rbBlocks <- rollbackTo interpreter mockServer (blockPoint $ last blks) + assertBlockNoBackoff dbSync (length (a <> blks <> blks' <> rbBlocks) + 1) forM_ blks' $ atomically . addBlock mockServer - assertBlockNoBackoff dbSync (2 + length a + length blks + length blks') + assertBlockNoBackoff dbSync (length (a <> blks <> rbBlocks <> blks') + 1) assertRewardCount dbSync 3 blks'' <- fillUntilNextEpoch interpreter mockServer - assertBlockNoBackoff dbSync (2 + length a + length blks + length blks' + length blks'') + assertBlockNoBackoff dbSync (length (a <> blks <> rbBlocks <> blks'') + 2) where testLabel = "rollbackBoundary" diff --git a/cardano-chain-gen/test/Test/Cardano/Db/Mock/Unit/Conway.hs b/cardano-chain-gen/test/Test/Cardano/Db/Mock/Unit/Conway.hs index 0f7ce78ee..d9b633f20 100644 --- a/cardano-chain-gen/test/Test/Cardano/Db/Mock/Unit/Conway.hs +++ b/cardano-chain-gen/test/Test/Cardano/Db/Mock/Unit/Conway.hs @@ -121,6 +121,7 @@ unitTests iom knownMigrations = , test "drepDistr rollback" Rollback.drepDistrRollback , test "sync bigger chain" Rollback.bigChain , test "rollback while db-sync is off" Rollback.restartAndRollback + , test "large rollback while db-sync is off" Rollback.restartAndRollbackLarge , test "big rollback executed lazily" Rollback.lazyRollback , test "lazy rollback on restart" Rollback.lazyRollbackRestart , test "rollback while rollbacking" Rollback.doubleRollback 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 4a657aa05..2210f8420 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 @@ -126,9 +126,9 @@ performPruneWithSimpleRollback useTxOutAddress = assertUnspentTx dbSync -- Rollback - rollbackTo interpreter mockServer (blockPoint blk1) + rbBlocks <- rollbackTo interpreter mockServer (blockPoint blk1) assertEqQuery dbSync (DB.queryTxOutConsumedCount txOutVariantType) 0 "Unexpected TxOutConsumedByTxId count after rollback" - assertBlockNoBackoff dbSync (fullBlockSize blks) + assertBlockNoBackoff dbSync (2 + length rbBlocks) where cmdLineArgs = initCommandLineArgs testLabel = "conwayConfigPruneSimpleRollback" @@ -160,7 +160,7 @@ performPruneWithFullTxRollback useTxOutAddress = assertEqQuery dbSync (DB.queryTxOutCount txOutVariantType) 14 "new epoch didn't prune tx_out column that are null" -- Rollback - rollbackTo interpreter mockServer $ blockPoint blk0 + rbBlocks <- rollbackTo interpreter mockServer $ blockPoint blk0 -- Add more transactions void $ withConwayFindLeaderAndSubmit interpreter mockServer $ \st -> do tx0 <- Conway.mkFullTx 0 100 st @@ -169,7 +169,7 @@ performPruneWithFullTxRollback useTxOutAddress = pure [tx1, tx2, tx0] -- Verify tx_out was pruned again - assertBlockNoBackoff dbSync 2 + assertBlockNoBackoff dbSync (2 + length rbBlocks) assertTxCount dbSync 14 assertEqQuery dbSync (DB.queryTxOutCount txOutVariantType) 16 "new epoch didn't prune tx_out column that are null" assertUnspentTx dbSync @@ -244,18 +244,16 @@ performPruneAndRollBackOneBlock useTxOutAddress = assertBlockNoBackoff dbSync 101 assertEqQuery dbSync (DB.queryTxOutConsumedCount txOutVariantType) 2 "Unexpected TxOutConsumedByTxId count before rollback" - rollbackTo interpreter mockServer (blockPoint blk100) + rbBlocks <- rollbackTo interpreter mockServer (blockPoint blk100) - -- Add an empty block - void $ forgeNextFindLeaderAndSubmit interpreter mockServer [] - -- Verify the transactions were removed in the rollback - assertBlockNoBackoff dbSync 101 + -- Verify the transactions were removed in the rollback (100 is max block number at blk100) + assertBlockNoBackoff dbSync (100 + length rbBlocks) assertEqQuery dbSync (DB.queryTxOutConsumedCount txOutVariantType) 1 "Unexpected TxOutConsumedByTxId count after rollback" -- Trigger a prune void $ forgeAndSubmitBlocks interpreter mockServer 102 -- Verify everything was pruned - assertBlockNoBackoff dbSync 203 + assertBlockNoBackoff dbSync (100 + length rbBlocks + 102) assertEqQuery dbSync (DB.queryTxOutConsumedCount txOutVariantType) 0 "Unexpected TxOutConsumedByTxId count after rollback" where cmdLineArgs = initCommandLineArgs @@ -290,18 +288,16 @@ performNoPruneAndRollBack useTxOutAddress = assertBlockNoBackoff dbSync 101 assertEqQuery dbSync (DB.queryTxOutConsumedCount txOutVariantType) 2 "Unexpected TxOutConsumedByTxId count before rollback" - rollbackTo interpreter mockServer (blockPoint blk100) + rbBlocks <- rollbackTo interpreter mockServer (blockPoint blk100) - -- Add an empty block - void $ forgeNextFindLeaderAndSubmit interpreter mockServer [] - -- Verify transactions were removed - assertBlockNoBackoff dbSync 101 + -- Verify transactions were removed (100 is max block number at blk100) + assertBlockNoBackoff dbSync (100 + length rbBlocks) assertEqQuery dbSync (DB.queryTxOutConsumedCount txOutVariantType) 1 "Unexpected TxOutConsumedByTxId count after rollback" -- Add some more blocks void $ forgeAndSubmitBlocks interpreter mockServer 102 -- Verify nothing has been pruned - assertBlockNoBackoff dbSync 203 + assertBlockNoBackoff dbSync (100 + length rbBlocks + 102) assertEqQuery dbSync (DB.queryTxOutConsumedCount txOutVariantType) 1 "Unexpected TxOutConsumedByTxId count after rollback" where cmdLineArgs = initCommandLineArgs @@ -338,12 +334,11 @@ performPruneSameBlock useTxOutAddress = assertBlockNoBackoff dbSync 100 assertEqQuery dbSync (DB.queryTxOutConsumedCount txOutVariantType) 0 "Unexpected TxOutConsumedByTxId after prune" - rollbackTo interpreter mockServer (blockPoint blk77) + rbBlocks <- rollbackTo interpreter mockServer (blockPoint blk77) + let rbBlocksLength = length rbBlocks - -- Add an empty block - void $ forgeNextFindLeaderAndSubmit interpreter mockServer [] - -- Verify the transactions were pruned again - assertBlockNoBackoff dbSync 78 + -- Verify the transactions were pruned again (77 is max block number at blk77, + rbBlocks) + assertBlockNoBackoff dbSync (77 + rbBlocksLength) assertTxInCount dbSync 0 assertEqQuery dbSync (DB.queryTxOutConsumedCount txOutVariantType) 0 "Unexpected TxOutConsumedByTxId after rollback" where @@ -375,14 +370,14 @@ performNoPruneSameBlock useTxOutAddress = -- Verify the blocks exist assertBlockNoBackoff dbSync 100 - rollbackTo interpreter mockServer (blockPoint blk97) + rbBlocks <- rollbackTo interpreter mockServer (blockPoint blk97) -- Verify we haven't pruned anything yet assertBlockNoBackoff dbSync 100 -- Add an empty block void $ forgeNextFindLeaderAndSubmit interpreter mockServer [] -- Verify everything was pruned - assertBlockNoBackoff dbSync 98 + assertBlockNoBackoff dbSync (98 + length rbBlocks) assertEqQuery dbSync (DB.queryTxOutConsumedCount $ txOutVariantTypeFromConfig dbSync) 0 "Unexpected TxOutConsumedByTxId after rollback" where cmdLineArgs = initCommandLineArgs diff --git a/cardano-chain-gen/test/Test/Cardano/Db/Mock/Unit/Conway/Governance.hs b/cardano-chain-gen/test/Test/Cardano/Db/Mock/Unit/Conway/Governance.hs index 00eb46920..0de76f2f8 100644 --- a/cardano-chain-gen/test/Test/Cardano/Db/Mock/Unit/Conway/Governance.hs +++ b/cardano-chain-gen/test/Test/Cardano/Db/Mock/Unit/Conway/Governance.hs @@ -122,8 +122,8 @@ rollbackNewCommittee = (1, 1, 0, 0) "Unexpected governance action counts" - -- Rollback the last 2 blocks - epoch1' <- rollbackBlocks interpreter server 2 epoch3 + -- Rollback the last 4 blocks + epoch1' <- rollbackBlocks interpreter server 4 epoch3 -- Wait for it to sync assertBlockNoBackoff dbSync (length $ epoch1 <> epoch1') -- Should not have a new committee member @@ -277,13 +277,13 @@ rollbackBlocks interpreter server n blocks = do [] -> assertFailure $ "Expected at least " <> show n <> " blocks" -- Rollback to the previous epoch - Api.rollbackTo interpreter server rollbackPoint + rbBlocks <- Api.rollbackTo interpreter server rollbackPoint -- Create a fork newBlock <- Api.withConwayFindLeaderAndSubmitTx interpreter server $ Conway.mkSimpleDCertTx [(StakeIndexNew 1, Conway.mkRegTxCert SNothing)] - pure $ reverse (newBlock : blocks') + pure $ reverse ([newBlock] <> rbBlocks <> blocks') updateConstitution :: IOManager -> [(Text, Text)] -> Assertion updateConstitution = @@ -507,8 +507,8 @@ rollbackHardFork = (Just 11) "Unexpected governance action counts" - -- Rollback the last 2 blocks - epoch2 <- rollbackBlocks interpreter server 2 epoch3 + -- Rollback the last 4 blocks + epoch2 <- rollbackBlocks interpreter server 4 epoch3 -- Wait for it to sync assertBlockNoBackoff dbSync (length $ epoch1 <> epoch2) -- Should not have a new committee member diff --git a/cardano-chain-gen/test/Test/Cardano/Db/Mock/Unit/Conway/InlineAndReference.hs b/cardano-chain-gen/test/Test/Cardano/Db/Mock/Unit/Conway/InlineAndReference.hs index 06731f3d2..dedda2729 100644 --- a/cardano-chain-gen/test/Test/Cardano/Db/Mock/Unit/Conway/InlineAndReference.hs +++ b/cardano-chain-gen/test/Test/Cardano/Db/Mock/Unit/Conway/InlineAndReference.hs @@ -324,10 +324,8 @@ spendCollateralOutputRollback = -- Create and spend collateral mkSpendCollOutput interpreter mockServer dbSync 0 - -- Rollback past action above - Api.rollbackTo interpreter mockServer (blockPoint blk) - -- Forge and submit another block - void $ Api.forgeNextFindLeaderAndSubmit interpreter mockServer [] + -- Rollback past action above (forges a block to establish new thread) + void $ Api.rollbackTo interpreter mockServer (blockPoint blk) -- Create and spend collateral mkSpendCollOutput interpreter mockServer dbSync 1 where diff --git a/cardano-chain-gen/test/Test/Cardano/Db/Mock/Unit/Conway/Other.hs b/cardano-chain-gen/test/Test/Cardano/Db/Mock/Unit/Conway/Other.hs index ae7c76d4e..d04dcb4fe 100644 --- a/cardano-chain-gen/test/Test/Cardano/Db/Mock/Unit/Conway/Other.hs +++ b/cardano-chain-gen/test/Test/Cardano/Db/Mock/Unit/Conway/Other.hs @@ -30,7 +30,7 @@ import Cardano.Ledger.Conway.TxCert (ConwayTxCert (..)) import Cardano.Ledger.Core (PoolCert (..)) import Cardano.Ledger.Credential (StakeCredential) import Cardano.Ledger.Keys (KeyHash, KeyRole (..)) -import Cardano.Mock.ChainSync.Server (IOManager (), addBlock, rollback) +import Cardano.Mock.ChainSync.Server (IOManager (), addBlock) import Cardano.Mock.Forging.Interpreter (forgeNext, getCurrentEpoch) import qualified Cardano.Mock.Forging.Tx.Babbage as Babbage import qualified Cardano.Mock.Forging.Tx.Conway as Conway @@ -430,14 +430,14 @@ rollbackFork = Conway.mkPaymentTx (UTxOIndex 0) (UTxOIndex 1) 10_000 500 0 -- Wait for it to sync - assertBlockNoBackoff dbSync $ 2 + length (epoch0 <> epoch1 <> epoch1') + assertBlockNoBackoff dbSync $ 1 + length (epoch0 <> epoch1 <> epoch1' <> [blk]) -- Rollback - atomically $ rollback mockServer (blockPoint $ last epoch1) + rollbackBlocks <- Api.rollbackTo interpreter mockServer (blockPoint $ last epoch1) -- Replay remaining blocks forM_ (epoch1' <> [blk]) (atomically . addBlock mockServer) -- Verify block count - assertBlockNoBackoff dbSync $ 2 + length (epoch0 <> epoch1 <> epoch1') + assertBlockNoBackoff dbSync $ length (epoch0 <> epoch1 <> rollbackBlocks <> epoch1' <> [blk]) where configDir = "config-conway-hf-epoch1" testLabel = "conwayRollbackFork" 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 852701be5..8dc305fad 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 @@ -376,9 +376,7 @@ multipleScriptsRollback = assertAlonzoCounts dbSync (1, 2, 1, 1, 3, 2, 0, 0) -- Roll back to genesis - Api.rollbackTo interpreter mockServer genesisPoint - -- Forge another block - void $ Api.forgeNextFindLeaderAndSubmit interpreter mockServer [] + void $ Api.rollbackTo interpreter mockServer genesisPoint -- Submit the txs again void $ @@ -388,7 +386,7 @@ multipleScriptsRollback = Api.forgeNextAndSubmit interpreter mockServer $ MockBlock [TxConway tx1] (NodeId 1) - -- Verify tx counts + -- Verify tx counts (rollbackTo forges 1 block, then we forge 2 more) assertBlockNoBackoff dbSync 3 assertAlonzoCounts dbSync (1, 2, 1, 1, 3, 2, 0, 0) where diff --git a/cardano-chain-gen/test/Test/Cardano/Db/Mock/Unit/Conway/Reward.hs b/cardano-chain-gen/test/Test/Cardano/Db/Mock/Unit/Conway/Reward.hs index abd943934..c1d61a961 100644 --- a/cardano-chain-gen/test/Test/Cardano/Db/Mock/Unit/Conway/Reward.hs +++ b/cardano-chain-gen/test/Test/Cardano/Db/Mock/Unit/Conway/Reward.hs @@ -8,7 +8,7 @@ module Test.Cardano.Db.Mock.Unit.Conway.Reward ( ) where import Cardano.Ledger.Keys (KeyHash (..)) -import Cardano.Mock.ChainSync.Server (IOManager (), addBlock, rollback) +import Cardano.Mock.ChainSync.Server (IOManager (), addBlock) import qualified Cardano.Mock.Forging.Tx.Conway as Conway import Cardano.Mock.Forging.Types (PoolIndex (..), StakeIndex (..), UTxOIndex (..)) import Cardano.Prelude @@ -104,17 +104,17 @@ rollbackBoundary = assertRewardCount dbSync 3 -- Rollback - atomically $ rollback mockServer (blockPoint $ last blks) + rbBlocks <- Api.rollbackTo interpreter mockServer (blockPoint $ last blks) -- Rollback effects are delayed - assertBlockNoBackoff dbSync (2 + length (epochs <> blks <> epochs')) + assertBlockNoBackoff dbSync (1 + length (epochs <> blks <> rbBlocks <> epochs')) -- Add the blocks again forM_ epochs' $ atomically . addBlock mockServer -- Should have the same amount of rewards - assertBlockNoBackoff dbSync (2 + length (epochs <> blks <> epochs')) + assertBlockNoBackoff dbSync (1 + length (epochs <> blks <> rbBlocks <> epochs')) assertRewardCount dbSync 3 -- Add some more blocks and verify epochs'' <- Api.fillUntilNextEpoch interpreter mockServer - assertBlockNoBackoff dbSync (2 + length (epochs <> blks <> epochs' <> epochs'')) + assertBlockNoBackoff dbSync (2 + length (epochs <> blks <> rbBlocks <> epochs'')) where testLabel = "conwayRollbackBoundary" diff --git a/cardano-chain-gen/test/Test/Cardano/Db/Mock/Unit/Conway/Rollback.hs b/cardano-chain-gen/test/Test/Cardano/Db/Mock/Unit/Conway/Rollback.hs index 06bfb5362..839a4d20a 100644 --- a/cardano-chain-gen/test/Test/Cardano/Db/Mock/Unit/Conway/Rollback.hs +++ b/cardano-chain-gen/test/Test/Cardano/Db/Mock/Unit/Conway/Rollback.hs @@ -9,6 +9,7 @@ module Test.Cardano.Db.Mock.Unit.Conway.Rollback ( simpleRollback, bigChain, restartAndRollback, + restartAndRollbackLarge, lazyRollback, lazyRollbackRestart, doubleRollback, @@ -26,7 +27,7 @@ import qualified Cardano.Db as DB import Cardano.DbSync.Era.Shelley.Generic (unCredentialHash) import Cardano.Ledger.Coin (Coin (..)) import Cardano.Ledger.Conway.TxCert (ConwayDelegCert (..), Delegatee (..)) -import Cardano.Mock.ChainSync.Server (IOManager (), addBlock, rollback) +import Cardano.Mock.ChainSync.Server (IOManager (), addBlock) import Cardano.Mock.Forging.Interpreter (forgeNext) import qualified Cardano.Mock.Forging.Tx.Conway as Conway import Cardano.Mock.Forging.Tx.Generic (resolvePool) @@ -35,7 +36,7 @@ import Cardano.Mock.Forging.Types (PoolIndex (..), StakeIndex (..), UTxOIndex (. import Cardano.Prelude import Data.Maybe.Strict (StrictMaybe (..)) import Ouroboros.Network.Block (blockPoint) -import Test.Cardano.Db.Mock.Config (claFullMode, configPoolStats, conwayConfigDir, initCommandLineArgs, queryDBSync, startDBSync, stopDBSync, withCustomConfigDropDB, withFullConfigDropDB) +import Test.Cardano.Db.Mock.Config (claFullMode, configPoolStats, conwayConfigDir, initCommandLineArgs, queryDBSync, startDBSync, stopDBSync, withCustomConfigDropDB, withFullConfigDropDB, withFullConfigDropDBNoFingerprint) import Test.Cardano.Db.Mock.Examples import Test.Cardano.Db.Mock.UnifiedApi import Test.Cardano.Db.Mock.Validate (assertBlockNoBackoff, assertEqQuery, assertTxCount) @@ -60,9 +61,9 @@ simpleRollback = -- Wait for them to sync assertBlockNoBackoff dbSync 3 - -- Rollback - atomically $ rollback mockServer (blockPoint blk1) - assertBlockNoBackoff dbSync 3 -- Rollback effects are now delayed + -- Rollback (removes blk2, keeps blk0 and blk1, then forges new block) + rbBlock <- rollbackTo interpreter mockServer (blockPoint blk1) + assertBlockNoBackoff dbSync (2 + length rbBlock) where testLabel = "conwaySimpleRollback" @@ -87,14 +88,14 @@ bigChain = assertBlockNoBackoff dbSync 206 -- Rollback - atomically $ rollback mockServer (blockPoint $ last blks') - assertBlockNoBackoff dbSync 206 -- Rollback effects are now delayed + rbBlock <- rollbackTo interpreter mockServer (blockPoint $ last blks') + assertBlockNoBackoff dbSync (201 + length rbBlock) where testLabel = "conwayBigChain" restartAndRollback :: IOManager -> [(Text, Text)] -> Assertion restartAndRollback = - withFullConfigDropDB conwayConfigDir testLabel $ \interpreter mockServer dbSync -> do + withFullConfigDropDBNoFingerprint conwayConfigDir testLabel $ \interpreter mockServer dbSync -> do -- Forge some blocks forM_ (replicate 101 mockBlock0) (forgeNextAndSubmit interpreter mockServer) @@ -107,19 +108,49 @@ restartAndRollback = -- Wait for it to sync assertBlockNoBackoff dbSync 201 - -- Forge some more blocks - forM_ (replicate 5 mockBlock2) (forgeNextAndSubmit interpreter mockServer) + -- Forge some more blocks (using mockBlock0 so the new block after rollback will have a different forger) + forM_ (replicate 5 mockBlock0) (forgeNextAndSubmit interpreter mockServer) assertBlockNoBackoff dbSync 206 -- Rollback and restart stopDBSync dbSync - atomically $ rollback mockServer (blockPoint $ last blks) + void $ rollbackTo interpreter mockServer (blockPoint $ last blks) startDBSync dbSync - assertBlockNoBackoff dbSync 206 -- Rollback effects are now delayed + -- rollbackTo forges an empty block after rollback, so we expect 202 blocks + -- (rollback point at 201 + the new empty block) + assertBlockNoBackoff dbSync 202 where testLabel = "conwayRestartAndRollback" +restartAndRollbackLarge :: IOManager -> [(Text, Text)] -> Assertion +restartAndRollbackLarge = + withFullConfigDropDBNoFingerprint conwayConfigDir testLabel $ \interpreter mockServer dbSync -> do + -- Forge initial blocks + forM_ (replicate 101 mockBlock0) (forgeNextAndSubmit interpreter mockServer) + + startDBSync dbSync + assertBlockNoBackoff dbSync 101 + + -- First batch: blocks to rollback to + blks1 <- forM (replicate 100 mockBlock0) (forgeNextAndSubmit interpreter mockServer) + assertBlockNoBackoff dbSync 201 + + -- Second batch: blocks that will be rolled back + forM_ (replicate 100 mockBlock0) (forgeNextAndSubmit interpreter mockServer) + assertBlockNoBackoff dbSync 301 + + -- Rollback and restart - rolling back 100 blocks + stopDBSync dbSync + void $ rollbackTo interpreter mockServer (blockPoint $ last blks1) + startDBSync dbSync + + -- rollbackTo forges an empty block after rollback, so we expect 202 blocks + -- (rollback point at 201 + the new empty block) + assertBlockNoBackoff dbSync 202 + where + testLabel = "conwayRestartAndRollbackLarge" + lazyRollback :: IOManager -> [(Text, Text)] -> Assertion lazyRollback = withFullConfigDropDB conwayConfigDir testLabel $ \interpreter mockServer dbSync -> do @@ -132,7 +163,7 @@ lazyRollback = -- Wait for them to sync assertBlockNoBackoff dbSync 270 - rollbackTo interpreter mockServer (blockPoint lastBlk) + rbBlock <- rollbackTo interpreter mockServer (blockPoint lastBlk) -- Here we create the fork void $ @@ -141,7 +172,7 @@ lazyRollback = -- Add some more blocks void $ forgeAndSubmitBlocks interpreter mockServer 40 -- Verify the new block count - assertBlockNoBackoff dbSync 241 + assertBlockNoBackoff dbSync (241 + length rbBlock) where testLabel = "conwayLazyRollback" @@ -159,7 +190,7 @@ lazyRollbackRestart = -- Rollback and restart stopDBSync dbSync - rollbackTo interpreter mockServer (blockPoint lastBlk) + rbBlock <- rollbackTo interpreter mockServer (blockPoint lastBlk) startDBSync dbSync -- Here we create the fork @@ -169,7 +200,7 @@ lazyRollbackRestart = -- Add some more blocks void $ forgeAndSubmitBlocks interpreter mockServer 30 -- Verify the new block count - assertBlockNoBackoff dbSync 251 + assertBlockNoBackoff dbSync (251 + length rbBlock) where testLabel = "conwayLazyRollbackRestart" @@ -187,7 +218,7 @@ doubleRollback = assertBlockNoBackoff dbSync 350 -- Rollback to second block point - rollbackTo interpreter mockServer (blockPoint lastBlk2) + void $ rollbackTo interpreter mockServer (blockPoint lastBlk2) -- Here we create a fork void $ withConwayFindLeaderAndSubmitTx interpreter mockServer $ @@ -196,15 +227,15 @@ doubleRollback = void $ forgeAndSubmitBlocks interpreter mockServer 50 -- Rollback to first block point - rollbackTo interpreter mockServer (blockPoint lastBlk1) + rbBlock2 <- rollbackTo interpreter mockServer (blockPoint lastBlk1) -- Create another fork void $ withConwayFindLeaderAndSubmitTx interpreter mockServer $ Conway.mkSimpleDCertTx [(StakeIndexNew 0, Conway.mkRegTxCert $ SJust (Coin 100))] -- Add some more blocks void $ forgeAndSubmitBlocks interpreter mockServer 50 - -- Wait for it to sync - assertBlockNoBackoff dbSync 201 + -- Wait for it to sync (150 + rbBlock2 + fork + 50 blocks = 202) + assertBlockNoBackoff dbSync (150 + length rbBlock2 + 1 + 50) where testLabel = "conwayDoubleRollback" @@ -228,17 +259,17 @@ stakeAddressRollback = -- Wait for it to sync assertBlockNoBackoff dbSync 2 - rollbackTo interpreter mockServer (blockPoint blk) + rbBlock <- rollbackTo interpreter mockServer (blockPoint blk) -- Create a fork void $ withConwayFindLeaderAndSubmitTx interpreter mockServer $ \_ -> Conway.mkDummyRegisterTx 1 2 -- Wait for it to sync - assertBlockNoBackoff dbSync 2 + assertBlockNoBackoff dbSync (2 + length rbBlock) -- Add another block void $ forgeNextFindLeaderAndSubmit interpreter mockServer [] -- Verify the new block count - assertBlockNoBackoff dbSync 3 + assertBlockNoBackoff dbSync (3 + length rbBlock) where testLabel = "conwayStakeAddressRollback" @@ -262,13 +293,13 @@ rollbackChangeTxOrder = assertBlockNoBackoff dbSync 2 assertTxCount dbSync 13 - rollbackTo interpreter mockServer (blockPoint blk0) + rbBlock <- rollbackTo interpreter mockServer (blockPoint blk0) -- Submit the transactions again, in a different order void $ withConwayFindLeaderAndSubmit interpreter mockServer $ \_ -> sequence [tx1, tx0, tx2] -- Verify the new transaction counts - assertBlockNoBackoff dbSync 2 + assertBlockNoBackoff dbSync (2 + length rbBlock) assertTxCount dbSync 14 where testLabel = "conwayRollbackChangeTxOrder" @@ -290,7 +321,7 @@ rollbackFullTx = assertBlockNoBackoff dbSync 2 assertTxCount dbSync 13 - rollbackTo interpreter mockServer (blockPoint blk0) + rbBlock <- rollbackTo interpreter mockServer (blockPoint blk0) -- Add some more blocks void $ withConwayFindLeaderAndSubmit interpreter mockServer $ \state' -> @@ -300,7 +331,7 @@ rollbackFullTx = , Conway.mkFullTx 2 200 state' ] -- Verify the new transaction counts - assertBlockNoBackoff dbSync 2 + assertBlockNoBackoff dbSync (2 + length rbBlock) assertTxCount dbSync 14 where testLabel = "conwayRollbackFullTx" @@ -351,7 +382,7 @@ drepDistrRollback = assertBlockNoBackoff dbSync (2 + length epoch0 + length epoch1 + length blksAfter) -- Rollback to the epoch 2 boundary (first block of epoch 2) - rollbackTo interpreter mockServer rollbackPoint + rbBlock <- rollbackTo interpreter mockServer rollbackPoint -- Create fork - replay through the epoch 2 boundary -- This will re-insert DrepDistr for epoch 2 @@ -367,7 +398,7 @@ drepDistrRollback = "DrepDistr for epoch 1 should still exist after rollback" -- Verify final state - assertBlockNoBackoff dbSync (2 + length epoch0 + length epoch1 + length blksFork) + assertBlockNoBackoff dbSync (2 + (length (epoch0 <> epoch1 <> rbBlock <> blksFork))) -- Verify DrepDistr for both epochs exist after replay assertEqQuery @@ -422,12 +453,12 @@ poolStatRollbackNoDuplicates = assertBlockNoBackoff dbSync 351 -- Rollback (following exact pattern from bigChain test) - atomically $ rollback mockServer (blockPoint $ last rollbackBlks) - assertBlockNoBackoff dbSync 351 -- Delayed rollbackExpand commentComment on line R345ResolvedCode has comments. Press enter to view. + void $ rollbackTo interpreter mockServer (blockPoint $ last rollbackBlks) + assertBlockNoBackoff dbSync 351 -- Delayed rollbackExpand -- Re-sync some blocks void $ forgeAndSubmitBlocks interpreter mockServer 100 - assertBlockNoBackoff dbSync 351 -- Should stay same due to rollbackExpand commentComment on line R349ResolvedCode has comments. Press enter to view. + assertBlockNoBackoff dbSync 352 -- Should stay same due to rollback -- The main test: no duplicates after rollback + re-sync duplicateCount <- queryDBSync dbSync DB.queryPoolStatDuplicates @@ -464,15 +495,15 @@ poolStatRollbackGeneral = assertBool "Pool stats should have increased" (afterCount > initialCount) -- Rollback to previous point - rollbackTo interpreter mockServer (blockPoint $ last rollbackBlks) + rbBlocks <- rollbackTo interpreter mockServer (blockPoint $ last rollbackBlks) _ <- withConwayFindLeaderAndSubmitTx interpreter mockServer $ Conway.mkSimpleDCertTx [(StakeIndexNew 1, Conway.mkRegTxCert SNothing)] - assertBlockNoBackoff dbSync $ totalBeforeRollback + 1 + assertBlockNoBackoff dbSync $ totalBeforeRollback + 1 + (length rbBlocks) -- +1 from tx -- Re-sync the same blocks - should not create duplicates epochBlks3 <- fillEpochs interpreter mockServer 1 - let finalTotal = totalBeforeRollback + 1 + length epochBlks3 + let finalTotal = totalBeforeRollback + 2 + length epochBlks3 -- +1 from rollbackTo, +1 from tx assertBlockNoBackoff dbSync finalTotal finalCount <- queryDBSync dbSync DB.queryPoolStatCount @@ -500,17 +531,17 @@ adaPots = assertEqual "Ada pots don't match" [(1, 60_000_000), (2, 60_000_000), (3, 60_000_000), (4, 60_000_000)] potsPerEpoch0 -- Rollback to previous point - rollbackTo interpreter mockServer (blockPoint $ last blks1) + rbBlock <- rollbackTo interpreter mockServer (blockPoint $ last blks1) + let rbBlockLength = length rbBlock void $ withConwayFindLeaderAndSubmitTx interpreter mockServer $ \_ -> Right $ Conway.mkDonationTx (Coin 500) - assertBlockNoBackoff dbSync $ length blks0 + 70 + 1 - + assertBlockNoBackoff dbSync $ (length blks0) + 70 + rbBlockLength + 1 -- +1 from tx potsPerEpoch1 <- queryDBSync dbSync DB.queryAdaPotsAll assertEqual "Ada pots don't match" [(1, 60_000_000), (2, 60_000_000), (3, 60_000_000)] potsPerEpoch1 blks3 <- fillEpochs interpreter mockServer 1 - assertBlockNoBackoff dbSync $ length blks0 + 70 + 1 + length blks3 + assertBlockNoBackoff dbSync $ length blks0 + 70 + 1 + rbBlockLength + length blks3 -- +1 from tx potsPerEpoch2 <- queryDBSync dbSync DB.queryAdaPotsAll assertEqual "Ada pots don't match" [(1, 60_000_000), (2, 60_000_000), (3, 60_000_000), (4, 60_000_000)] potsPerEpoch2 where diff --git a/cardano-chain-gen/test/testfiles/fingerprint/configNoPruneSameBlock b/cardano-chain-gen/test/testfiles/fingerprint/configNoPruneSameBlock deleted file mode 100644 index 3961e46fb..000000000 --- a/cardano-chain-gen/test/testfiles/fingerprint/configNoPruneSameBlock +++ /dev/null @@ -1 +0,0 @@ -[5,11,15,21,22,23,28,33,34,36,42,43,48,52,62,82,88,92,102,106,109,111,116,133,134,143,151,153,157,161,162,171,182,183,193,195,196,197,200,206,208,216,219,222,238,245,250,262,271,272,275,282,286,296,301,310,311,314,325,340,347,354,355,365,376,379,382,384,389,390,391,392,393,398,404,407,414,418,419,422,424,446,448,450,457,465,476,478,485,486,488,499,503,506,509,512,515,518,524,526,518] \ No newline at end of file diff --git a/cardano-chain-gen/test/testfiles/fingerprint/configPruneAndRollBack b/cardano-chain-gen/test/testfiles/fingerprint/configPruneAndRollBack deleted file mode 100644 index 7aa05f9e3..000000000 --- a/cardano-chain-gen/test/testfiles/fingerprint/configPruneAndRollBack +++ /dev/null @@ -1 +0,0 @@ -[5,11,15,21,22,23,28,33,34,36,42,43,48,52,62,82,88,92,102,106,109,111,116,133,134,143,151,153,157,161,162,171,182,183,193,195,196,197,200,206,208,216,219,222,238,245,250,262,271,272,275,282,286,296,301,310,311,314,325,340,347,354,355,365,376,379,382,384,389,390,391,392,393,398,404,407,414,418,419,422,424,446,448,450,457,465,476,478,485,486,488,499,503,506,509,512,515,518,524,526,527,527,530,541,542,549,556,561,570,576,578,579,583,589,596,597,609,611,615,620,621,627,633,634,644,650,651,654,661,671,675,680,682,687,694,698,703,705,711,716,718,726,728,730,739,748,749,757,761,782,784,785,791,796,798,815,818,823,837,845,846,847,858,862,865,877,879,881,882,884,885,888,890,892,893,895,898,900,904,908,916,921,922,923,929,930,932,934,936,950,956,957,968,969,985,992,993,994,1009,1011,1022,1025,1027,1033] \ No newline at end of file diff --git a/cardano-chain-gen/test/testfiles/fingerprint/configPruneOnFullRollback b/cardano-chain-gen/test/testfiles/fingerprint/configPruneOnFullRollback deleted file mode 100644 index b1ccb125b..000000000 --- a/cardano-chain-gen/test/testfiles/fingerprint/configPruneOnFullRollback +++ /dev/null @@ -1 +0,0 @@ -[5,11,11] \ No newline at end of file diff --git a/cardano-chain-gen/test/testfiles/fingerprint/configPruneSameBlock b/cardano-chain-gen/test/testfiles/fingerprint/configPruneSameBlock deleted file mode 100644 index d4c70e765..000000000 --- a/cardano-chain-gen/test/testfiles/fingerprint/configPruneSameBlock +++ /dev/null @@ -1 +0,0 @@ -[5,11,15,21,22,23,28,33,34,36,42,43,48,52,62,82,88,92,102,106,109,111,116,133,134,143,151,153,157,161,162,171,182,183,193,195,196,197,200,206,208,216,219,222,238,245,250,262,271,272,275,282,286,296,301,310,311,314,325,340,347,354,355,365,376,379,382,384,389,390,391,392,393,398,404,407,414,418,419,422,424,446,448,450,457,465,476,478,485,486,488,499,503,506,509,512,515,518,524,526,418] \ No newline at end of file diff --git a/cardano-chain-gen/test/testfiles/fingerprint/configPruneSimpleRollback b/cardano-chain-gen/test/testfiles/fingerprint/configPruneSimpleRollback deleted file mode 100644 index 93fe0e31a..000000000 --- a/cardano-chain-gen/test/testfiles/fingerprint/configPruneSimpleRollback +++ /dev/null @@ -1 +0,0 @@ -[28,33,34,36,42,43,48,52,62,82,88,92,102,106,109,111,116,133,134,143,151,153,157,161,162,171,182,183,193,195,196,197,200,206,208,216,219,222,238,245,250,262,271,272,275,282,286,296,301,310,311,314,325,340,347,354,355,365,376,379,382,384,389,390,391,392,393,398,404,407,414,418,419,422,424,446,448,450,457,465,476,478,485,486,488,499,503,510,513,514,519,521,522,523,529,533,536,539,545,549] \ No newline at end of file diff --git a/cardano-chain-gen/test/testfiles/fingerprint/conwayBigChain b/cardano-chain-gen/test/testfiles/fingerprint/conwayBigChain index 7e9daac6a..011737dfc 100644 --- a/cardano-chain-gen/test/testfiles/fingerprint/conwayBigChain +++ b/cardano-chain-gen/test/testfiles/fingerprint/conwayBigChain @@ -1 +1 @@ -[18,32,33,40,41,60,80,84,106,110,111,112,154,168,178,183,194,198,200,202,223,224,239,242,261,288,303,313,315,331,344,364,369,394,407,418,425,439,450,453,467,492,499,516,517,526,538,544,562,574,580,594,602,603,632,640,641,653,659,684,703,792,808,810,812,816,819,822,844,867,868,921,930,938,939,951,961,970,971,974,993,1009,1025,1052,1070,1093,1110,1111,1114,1126,1161,1170,1171,1174,1191,1207,1217,1218,1244,1275,1299,1313,1343,1357,1361,1363,1380,1382,1387,1402,1405,1433,1469,1495,1498,1517,1572,1579,1658,1667,1699,1720,1762,1802,1806,1808,1816,1849,1861,1905,1950,1977,1987,2023,2027,2028,2030,2042,2043,2045,2058,2064,2068,2120,2170,2183,2233,2256,2284,2290,2291,2318,2335,2336,2363,2378,2382,2397,2399,2404,2446,2464,2479,2487,2489,2500,2503,2519,2532,2559,2584,2651,2681,2690,2710,2711,2716,2718,2739,2758,2777,2815,2835,2849,2950,2977,2988,2991,3010,3030,3046,3092,3122,3123,3183,3186,3199,3212,3214,3240,3268,3273,3279,3301,3308,3323] \ No newline at end of file +[18,32,33,40,41,60,80,84,106,110,111,112,154,168,178,183,194,198,200,202,223,224,239,242,261,288,303,313,315,331,344,364,369,394,407,418,425,439,450,453,467,492,499,516,517,526,538,544,562,574,580,594,602,603,632,640,641,653,659,684,703,792,808,810,812,816,819,822,844,867,868,921,930,938,939,951,961,970,971,974,993,1009,1025,1052,1070,1093,1110,1111,1114,1126,1161,1170,1171,1174,1191,1207,1217,1218,1244,1275,1299,1313,1343,1357,1361,1363,1380,1382,1387,1402,1405,1433,1469,1495,1498,1517,1572,1579,1658,1667,1699,1720,1762,1802,1806,1808,1816,1849,1861,1905,1950,1977,1987,2023,2027,2028,2030,2042,2043,2045,2058,2064,2068,2120,2170,2183,2233,2256,2284,2290,2291,2318,2335,2336,2363,2378,2382,2397,2399,2404,2446,2464,2479,2487,2489,2500,2503,2519,2532,2559,2584,2651,2681,2690,2710,2711,2716,2718,2739,2758,2777,2815,2835,2849,2950,2977,2988,2991,3010,3030,3046,3092,3122,3123,3183,3186,3199,3212,3214,3240,3268,3273,3279,3301,3308,3323,3271] \ No newline at end of file diff --git a/cardano-chain-gen/test/testfiles/fingerprint/conwayConfigNoPruneAndRollBack b/cardano-chain-gen/test/testfiles/fingerprint/conwayConfigNoPruneAndRollBack index f35e568ad..39d174280 100644 --- a/cardano-chain-gen/test/testfiles/fingerprint/conwayConfigNoPruneAndRollBack +++ b/cardano-chain-gen/test/testfiles/fingerprint/conwayConfigNoPruneAndRollBack @@ -1 +1 @@ -[12,16,18,21,24,30,31,32,33,40,41,42,43,47,52,60,62,70,80,84,86,92,98,100,106,109,110,111,112,127,134,138,146,149,154,166,168,178,183,188,193,194,198,200,202,220,222,223,224,225,231,239,242,247,261,282,283,288,289,301,302,303,308,313,315,316,320,331,334,344,345,363,364,368,369,375,377,381,389,394,407,418,422,425,430,437,438,439,440,447,450,453,454,456,458,461,467,492,499,507,516,516,524,538,541,544,546,550,567,573,576,577,579,580,586,589,595,597,603,605,609,616,618,619,623,624,634,636,643,644,659,664,665,672,678,692,705,711,712,719,726,730,739,740,743,747,749,751,754,759,762,763,765,767,773,777,786,788,789,794,801,806,807,829,830,832,849,851,853,869,871,874,875,878,882,888,893,895,896,898,899,903,906,908,911,912,913,922,930,932,938,941,944,950,960,963,966,968,972,977,985,986,988,990] \ No newline at end of file +[12,16,18,21,24,30,31,32,33,40,41,42,43,47,52,60,62,70,80,84,86,92,98,100,106,109,110,111,112,127,134,138,146,149,154,166,168,178,183,188,193,194,198,200,202,220,222,223,224,225,231,239,242,247,261,282,283,288,289,301,302,303,308,313,315,316,320,331,334,344,345,363,364,368,369,375,377,381,389,394,407,418,422,425,430,437,438,439,440,447,450,453,454,456,458,461,467,492,499,507,516,516,524,538,541,544,546,550,567,573,576,577,579,580,586,589,595,597,603,605,609,616,618,619,623,624,634,636,643,644,659,664,665,672,678,692,705,711,712,719,726,730,739,740,743,747,749,751,754,759,762,763,765,767,773,777,786,788,789,794,801,806,807,829,830,832,849,851,853,869,871,874,875,878,882,888,893,895,896,898,899,903,906,908,911,912,913,922,930,932,938,941,944,950,960,963,966,968,972,977,985,986,988,990,991] \ No newline at end of file diff --git a/cardano-chain-gen/test/testfiles/fingerprint/conwayConfigNoPruneSameBlock b/cardano-chain-gen/test/testfiles/fingerprint/conwayConfigNoPruneSameBlock index 4bf3d7cea..8727f1bb8 100644 --- a/cardano-chain-gen/test/testfiles/fingerprint/conwayConfigNoPruneSameBlock +++ b/cardano-chain-gen/test/testfiles/fingerprint/conwayConfigNoPruneSameBlock @@ -1 +1 @@ -[12,16,18,21,24,30,31,32,33,40,41,42,43,47,52,60,62,70,80,84,86,92,98,100,106,109,110,111,112,127,134,138,146,149,154,166,168,178,183,188,193,194,198,200,202,220,222,223,224,225,231,239,242,247,261,282,283,288,289,301,302,303,308,313,315,316,320,331,334,344,345,363,364,368,369,375,377,381,389,394,407,418,422,425,430,437,438,439,440,447,450,453,454,456,458,461,467,492,499,507,492] \ No newline at end of file +[12,16,18,21,24,30,31,32,33,40,41,42,43,47,52,60,62,70,80,84,86,92,98,100,106,109,110,111,112,127,134,138,146,149,154,166,168,178,183,188,193,194,198,200,202,220,222,223,224,225,231,239,242,247,261,282,283,288,289,301,302,303,308,313,315,316,320,331,334,344,345,363,364,368,369,375,377,381,389,394,407,418,422,425,430,437,438,439,440,447,450,453,454,456,458,461,467,492,499,507,492,499] \ No newline at end of file diff --git a/cardano-chain-gen/test/testfiles/fingerprint/conwayConfigPruneAndRollBack b/cardano-chain-gen/test/testfiles/fingerprint/conwayConfigPruneAndRollBack index f35e568ad..39d174280 100644 --- a/cardano-chain-gen/test/testfiles/fingerprint/conwayConfigPruneAndRollBack +++ b/cardano-chain-gen/test/testfiles/fingerprint/conwayConfigPruneAndRollBack @@ -1 +1 @@ -[12,16,18,21,24,30,31,32,33,40,41,42,43,47,52,60,62,70,80,84,86,92,98,100,106,109,110,111,112,127,134,138,146,149,154,166,168,178,183,188,193,194,198,200,202,220,222,223,224,225,231,239,242,247,261,282,283,288,289,301,302,303,308,313,315,316,320,331,334,344,345,363,364,368,369,375,377,381,389,394,407,418,422,425,430,437,438,439,440,447,450,453,454,456,458,461,467,492,499,507,516,516,524,538,541,544,546,550,567,573,576,577,579,580,586,589,595,597,603,605,609,616,618,619,623,624,634,636,643,644,659,664,665,672,678,692,705,711,712,719,726,730,739,740,743,747,749,751,754,759,762,763,765,767,773,777,786,788,789,794,801,806,807,829,830,832,849,851,853,869,871,874,875,878,882,888,893,895,896,898,899,903,906,908,911,912,913,922,930,932,938,941,944,950,960,963,966,968,972,977,985,986,988,990] \ No newline at end of file +[12,16,18,21,24,30,31,32,33,40,41,42,43,47,52,60,62,70,80,84,86,92,98,100,106,109,110,111,112,127,134,138,146,149,154,166,168,178,183,188,193,194,198,200,202,220,222,223,224,225,231,239,242,247,261,282,283,288,289,301,302,303,308,313,315,316,320,331,334,344,345,363,364,368,369,375,377,381,389,394,407,418,422,425,430,437,438,439,440,447,450,453,454,456,458,461,467,492,499,507,516,516,524,538,541,544,546,550,567,573,576,577,579,580,586,589,595,597,603,605,609,616,618,619,623,624,634,636,643,644,659,664,665,672,678,692,705,711,712,719,726,730,739,740,743,747,749,751,754,759,762,763,765,767,773,777,786,788,789,794,801,806,807,829,830,832,849,851,853,869,871,874,875,878,882,888,893,895,896,898,899,903,906,908,911,912,913,922,930,932,938,941,944,950,960,963,966,968,972,977,985,986,988,990,991] \ No newline at end of file diff --git a/cardano-chain-gen/test/testfiles/fingerprint/conwayConfigPruneOnFullRollback b/cardano-chain-gen/test/testfiles/fingerprint/conwayConfigPruneOnFullRollback index bf2d8e7a5..7840b4489 100644 --- a/cardano-chain-gen/test/testfiles/fingerprint/conwayConfigPruneOnFullRollback +++ b/cardano-chain-gen/test/testfiles/fingerprint/conwayConfigPruneOnFullRollback @@ -1 +1 @@ -[12,16,16] \ No newline at end of file +[12,16,16,18] \ No newline at end of file diff --git a/cardano-chain-gen/test/testfiles/fingerprint/conwayConfigPruneSimpleRollback b/cardano-chain-gen/test/testfiles/fingerprint/conwayConfigPruneSimpleRollback index 31c929e8b..19a6646e9 100644 --- a/cardano-chain-gen/test/testfiles/fingerprint/conwayConfigPruneSimpleRollback +++ b/cardano-chain-gen/test/testfiles/fingerprint/conwayConfigPruneSimpleRollback @@ -1 +1 @@ -[18,21,24,30,31,32,33,40,41,42,43,47,52,60,62,70,80,84,86,92,98,100,106,109,110,111,112,127,134,138,146,149,154,166,168,178,183,188,193,194,198,200,202,220,222,223,224,225,231,239,242,247,261,282,283,288,289,301,302,303,308,313,315,316,320,331,334,344,345,363,364,368,369,375,377,381,389,394,407,418,422,425,430,437,438,439,440,447,450,453,454,456,458,461,467,492,499,509,511,526] \ No newline at end of file +[18,21,24,30,31,32,33,40,41,42,43,47,52,60,62,70,80,84,86,92,98,100,106,109,110,111,112,127,134,138,146,149,154,166,168,178,183,188,193,194,198,200,202,220,222,223,224,225,231,239,242,247,261,282,283,288,289,301,302,303,308,313,315,316,320,331,334,344,345,363,364,368,369,375,377,381,389,394,407,418,422,425,430,437,438,439,440,447,450,453,454,456,458,461,467,492,499,509,511,526,24] \ No newline at end of file diff --git a/cardano-chain-gen/test/testfiles/fingerprint/conwayDoubleRollback b/cardano-chain-gen/test/testfiles/fingerprint/conwayDoubleRollback index b9e370073..c95896e25 100644 --- a/cardano-chain-gen/test/testfiles/fingerprint/conwayDoubleRollback +++ b/cardano-chain-gen/test/testfiles/fingerprint/conwayDoubleRollback @@ -1 +1 @@ -[12,16,18,21,24,30,31,32,33,40,41,42,43,47,52,60,62,70,80,84,86,92,98,100,106,109,110,111,112,127,134,138,146,149,154,166,168,178,183,188,193,194,198,200,202,220,222,223,224,225,231,239,242,247,261,282,283,288,289,301,302,303,308,313,315,316,320,331,334,344,345,363,364,368,369,375,377,381,389,394,407,418,422,425,430,437,438,439,440,447,450,453,454,456,458,461,467,492,499,507,516,524,538,541,544,546,550,567,573,576,577,579,580,586,589,595,597,603,605,609,616,618,619,623,624,634,636,643,644,659,664,665,672,678,692,705,711,712,719,726,730,739,740,743,747,749,751,754,759,762,763,765,767,773,777,786,788,789,794,801,806,807,829,830,832,849,851,853,869,871,874,875,878,882,888,893,895,896,898,899,903,906,908,911,912,913,922,930,932,938,941,944,950,960,963,966,968,972,977,985,986,988,990,991,994,997,1005,1010,1012,1015,1038,1042,1046,1048,1049,1054,1055,1061,1067,1072,1073,1092,1097,1103,1106,1109,1125,1134,1143,1151,1154,1174,1175,1190,1191,1194,1200,1204,1212,1216,1225,1228,1231,1236,1241,1250,1252,1257,1258,1259,1262,1268,1278,1284,1290,1291,1294,1298,1300,1302,1308,1318,1331,1333,1339,1348,1349,1359,1368,1373,1385,1391,1400,1408,1410,1412,1424,1428,1430,1433,1434,1439,1446,1456,1459,1461,1462,1482,1484,1486,1487,1496,1511,1517,1530,1532,1538,1547,1549,1562,1574,1578,1585,1586,1587,1603,1604,1610,1628,1636,1643,1658,1671,1677,1678,1679,1682,1683,1686,1687,1689,1692,1699,1702,1706,1741,1742,1749,1752,1755,1760,1766,1771,1781,1789,1792,1793,1803,1811,1815,1817,1819,1822,1824,1827,1831,1837,1847,1854,1855,1262,1268,1278,1284,1290,1291,1294,1298,1300,1302,1308,1318,1331,1333,1339,1348,1349,1359,1368,1373,1385,1391,1400,1408,1410,1412,1424,1428,1430,1433,1434,1439,1446,1456,1459,1461,1462,1482,1484,1486,1487,1496,1511,1517,1530,1532,1538,1547,1549,1562,1574,763,765,767,773,777,786,788,789,794,801,806,807,829,830,832,849,851,853,869,871,874,875,878,882,888,893,895,896,898,899,903,906,908,911,912,913,922,930,932,938,941,944,950,960,963,966,968,972,977,985,986] \ No newline at end of file +[12,16,18,21,24,30,31,32,33,40,41,42,43,47,52,60,62,70,80,84,86,92,98,100,106,109,110,111,112,127,134,138,146,149,154,166,168,178,183,188,193,194,198,200,202,220,222,223,224,225,231,239,242,247,261,282,283,288,289,301,302,303,308,313,315,316,320,331,334,344,345,363,364,368,369,375,377,381,389,394,407,418,422,425,430,437,438,439,440,447,450,453,454,456,458,461,467,492,499,507,516,524,538,541,544,546,550,567,573,576,577,579,580,586,589,595,597,603,605,609,616,618,619,623,624,634,636,643,644,659,664,665,672,678,692,705,711,712,719,726,730,739,740,743,747,749,751,754,759,762,763,765,767,773,777,786,788,789,794,801,806,807,829,830,832,849,851,853,869,871,874,875,878,882,888,893,895,896,898,899,903,906,908,911,912,913,922,930,932,938,941,944,950,960,963,966,968,972,977,985,986,988,990,991,994,997,1005,1010,1012,1015,1038,1042,1046,1048,1049,1054,1055,1061,1067,1072,1073,1092,1097,1103,1106,1109,1125,1134,1143,1151,1154,1174,1175,1190,1191,1194,1200,1204,1212,1216,1225,1228,1231,1236,1241,1250,1252,1257,1258,1259,1262,1268,1278,1284,1290,1291,1294,1298,1300,1302,1308,1318,1331,1333,1339,1348,1349,1359,1368,1373,1385,1391,1400,1408,1410,1412,1424,1428,1430,1433,1434,1439,1446,1456,1459,1461,1462,1482,1484,1486,1487,1496,1511,1517,1530,1532,1538,1547,1549,1562,1574,1578,1585,1586,1587,1603,1604,1610,1628,1636,1643,1658,1671,1677,1678,1679,1682,1683,1686,1687,1689,1692,1699,1702,1706,1741,1742,1749,1752,1755,1760,1766,1771,1781,1789,1792,1793,1803,1811,1815,1817,1819,1822,1824,1827,1831,1837,1847,1854,1855,1262,1268,1278,1284,1290,1291,1294,1298,1300,1302,1308,1318,1331,1333,1339,1348,1349,1359,1368,1373,1385,1391,1400,1408,1410,1412,1424,1428,1430,1433,1434,1439,1446,1456,1459,1461,1462,1482,1484,1486,1487,1496,1511,1517,1530,1532,1538,1547,1549,1562,1574,1578,763,765,767,773,777,786,788,789,794,801,806,807,829,830,832,849,851,853,869,871,874,875,878,882,888,893,895,896,898,899,903,906,908,911,912,913,922,930,932,938,941,944,950,960,963,966,968,972,977,985,986,988] \ No newline at end of file diff --git a/cardano-chain-gen/test/testfiles/fingerprint/conwayDrepDistrRollback b/cardano-chain-gen/test/testfiles/fingerprint/conwayDrepDistrRollback index 371bbfa1c..7f5ed0055 100644 --- a/cardano-chain-gen/test/testfiles/fingerprint/conwayDrepDistrRollback +++ b/cardano-chain-gen/test/testfiles/fingerprint/conwayDrepDistrRollback @@ -1 +1 @@ -[12,16,18,21,24,30,31,32,33,40,41,42,43,47,52,60,62,70,80,84,86,92,98,100,106,109,110,111,112,127,134,138,146,149,154,166,168,178,183,188,193,194,198,200,202,220,222,223,224,225,231,239,242,247,261,282,283,288,289,301,302,303,308,313,315,316,320,331,334,344,345,363,364,368,369,375,377,381,389,394,407,418,422,425,430,437,438,439,440,447,450,453,454,456,458,461,467,492,499,507,516,524,538,541,544,546,550,567,573,576,577,579,580,586,589,595,597,603,605,609,616,618,619,623,624,634,636,643,644,659,664,665,672,678,692,705,711,712,719,726,730,739,740,743,747,749,751,754,759,762,763,765,767,773,777,786,788,789,794,801,806,807,829,830,832,849,851,853,869,871,874,875,878,882,888,893,895,896,898,899,903,906,908,911,912,913,922,930,932,938,941,944,950,960,963,966,968,972,977,985,986,988,990,991,994,997,1001,1005,1014,1019,1005,1014,1019,1020,1026] \ No newline at end of file +[12,16,18,21,24,30,31,32,33,40,41,42,43,47,52,60,62,70,80,84,86,92,98,100,106,109,110,111,112,127,134,138,146,149,154,166,168,178,183,188,193,194,198,200,202,220,222,223,224,225,231,239,242,247,261,282,283,288,289,301,302,303,308,313,315,316,320,331,334,344,345,363,364,368,369,375,377,381,389,394,407,418,422,425,430,437,438,439,440,447,450,453,454,456,458,461,467,492,499,507,516,524,538,541,544,546,550,567,573,576,577,579,580,586,589,595,597,603,605,609,616,618,619,623,624,634,636,643,644,659,664,665,672,678,692,705,711,712,719,726,730,739,740,743,747,749,751,754,759,762,763,765,767,773,777,786,788,789,794,801,806,807,829,830,832,849,851,853,869,871,874,875,878,882,888,893,895,896,898,899,903,906,908,911,912,913,922,930,932,938,941,944,950,960,963,966,968,972,977,985,986,988,990,991,994,997,1001,1005,1014,1019,1005,1014,1019,1020,1026,1027] \ No newline at end of file diff --git a/cardano-chain-gen/test/testfiles/fingerprint/conwayLazyRollback b/cardano-chain-gen/test/testfiles/fingerprint/conwayLazyRollback index 04fdf6865..2dbece535 100644 --- a/cardano-chain-gen/test/testfiles/fingerprint/conwayLazyRollback +++ b/cardano-chain-gen/test/testfiles/fingerprint/conwayLazyRollback @@ -1 +1 @@ -[12,16,18,21,24,30,31,32,33,40,41,42,43,47,52,60,62,70,80,84,86,92,98,100,106,109,110,111,112,127,134,138,146,149,154,166,168,178,183,188,193,194,198,200,202,220,222,223,224,225,231,239,242,247,261,282,283,288,289,301,302,303,308,313,315,316,320,331,334,344,345,363,364,368,369,375,377,381,389,394,407,418,422,425,430,437,438,439,440,447,450,453,454,456,458,461,467,492,499,507,516,524,538,541,544,546,550,567,573,576,577,579,580,586,589,595,597,603,605,609,616,618,619,623,624,634,636,643,644,659,664,665,672,678,692,705,711,712,719,726,730,739,740,743,747,749,751,754,759,762,763,765,767,773,777,786,788,789,794,801,806,807,829,830,832,849,851,853,869,871,874,875,878,882,888,893,895,896,898,899,903,906,908,911,912,913,922,930,932,938,941,944,950,960,963,966,968,972,977,985,986,988,990,991,994,997,1005,1010,1012,1015,1038,1042,1046,1048,1049,1054,1055,1061,1067,1072,1073,1092,1097,1103,1106,1109,1125,1134,1143,1151,1154,1174,1175,1190,1191,1194,1200,1204,1212,1216,1225,1228,1231,1236,1241,1250,1252,1257,1258,1259,1262,1268,1278,1284,1290,1291,1294,1298,1300,1302,1308,1318,1331,1333,1339,1348,1349,1359,1368,1373,986,988,990,991,994,997,1005,1010,1012,1015,1038,1042,1046,1048,1049,1054,1055,1061,1067,1072,1073,1092,1097,1103,1106,1109,1125,1134,1143,1151,1154,1174,1175,1190,1191,1194,1200,1204,1212,1216,1225] \ No newline at end of file +[12,16,18,21,24,30,31,32,33,40,41,42,43,47,52,60,62,70,80,84,86,92,98,100,106,109,110,111,112,127,134,138,146,149,154,166,168,178,183,188,193,194,198,200,202,220,222,223,224,225,231,239,242,247,261,282,283,288,289,301,302,303,308,313,315,316,320,331,334,344,345,363,364,368,369,375,377,381,389,394,407,418,422,425,430,437,438,439,440,447,450,453,454,456,458,461,467,492,499,507,516,524,538,541,544,546,550,567,573,576,577,579,580,586,589,595,597,603,605,609,616,618,619,623,624,634,636,643,644,659,664,665,672,678,692,705,711,712,719,726,730,739,740,743,747,749,751,754,759,762,763,765,767,773,777,786,788,789,794,801,806,807,829,830,832,849,851,853,869,871,874,875,878,882,888,893,895,896,898,899,903,906,908,911,912,913,922,930,932,938,941,944,950,960,963,966,968,972,977,985,986,988,990,991,994,997,1005,1010,1012,1015,1038,1042,1046,1048,1049,1054,1055,1061,1067,1072,1073,1092,1097,1103,1106,1109,1125,1134,1143,1151,1154,1174,1175,1190,1191,1194,1200,1204,1212,1216,1225,1228,1231,1236,1241,1250,1252,1257,1258,1259,1262,1268,1278,1284,1290,1291,1294,1298,1300,1302,1308,1318,1331,1333,1339,1348,1349,1359,1368,1373,986,988,990,991,994,997,1005,1010,1012,1015,1038,1042,1046,1048,1049,1054,1055,1061,1067,1072,1073,1092,1097,1103,1106,1109,1125,1134,1143,1151,1154,1174,1175,1190,1191,1194,1200,1204,1212,1216,1225,1228] \ No newline at end of file diff --git a/cardano-chain-gen/test/testfiles/fingerprint/conwayLazyRollbackRestart b/cardano-chain-gen/test/testfiles/fingerprint/conwayLazyRollbackRestart index 4c5ddd9cc..acb59ce04 100644 --- a/cardano-chain-gen/test/testfiles/fingerprint/conwayLazyRollbackRestart +++ b/cardano-chain-gen/test/testfiles/fingerprint/conwayLazyRollbackRestart @@ -1 +1 @@ -[12,16,18,21,24,30,31,32,33,40,41,42,43,47,52,60,62,70,80,84,86,92,98,100,106,109,110,111,112,127,134,138,146,149,154,166,168,178,183,188,193,194,198,200,202,220,222,223,224,225,231,239,242,247,261,282,283,288,289,301,302,303,308,313,315,316,320,331,334,344,345,363,364,368,369,375,377,381,389,394,407,418,422,425,430,437,438,439,440,447,450,453,454,456,458,461,467,492,499,507,516,524,538,541,544,546,550,567,573,576,577,579,580,586,589,595,597,603,605,609,616,618,619,623,624,634,636,643,644,659,664,665,672,678,692,705,711,712,719,726,730,739,740,743,747,749,751,754,759,762,763,765,767,773,777,786,788,789,794,801,806,807,829,830,832,849,851,853,869,871,874,875,878,882,888,893,895,896,898,899,903,906,908,911,912,913,922,930,932,938,941,944,950,960,963,966,968,972,977,985,986,988,990,991,994,997,1005,1010,1012,1015,1038,1042,1046,1048,1049,1054,1055,1061,1067,1072,1073,1092,1097,1103,1106,1109,1125,1134,1143,1151,1154,1174,1175,1190,1191,1194,1200,1204,1212,1216,1225,1228,1231,1236,1241,1250,1252,1257,1258,1259,1262,1268,1278,1284,1290,1291,1294,1298,1300,1302,1308,1318,1331,1333,1339,1348,1349,1359,1368,1373,1385,1391,1400,1408,1410,1412,1424,1428,1430,1433,1073,1092,1097,1103,1106,1109,1125,1134,1143,1151,1154,1174,1175,1190,1191,1194,1200,1204,1212,1216,1225,1228,1231,1236,1241,1250,1252,1257,1258,1259,1262] \ No newline at end of file +[12,16,18,21,24,30,31,32,33,40,41,42,43,47,52,60,62,70,80,84,86,92,98,100,106,109,110,111,112,127,134,138,146,149,154,166,168,178,183,188,193,194,198,200,202,220,222,223,224,225,231,239,242,247,261,282,283,288,289,301,302,303,308,313,315,316,320,331,334,344,345,363,364,368,369,375,377,381,389,394,407,418,422,425,430,437,438,439,440,447,450,453,454,456,458,461,467,492,499,507,516,524,538,541,544,546,550,567,573,576,577,579,580,586,589,595,597,603,605,609,616,618,619,623,624,634,636,643,644,659,664,665,672,678,692,705,711,712,719,726,730,739,740,743,747,749,751,754,759,762,763,765,767,773,777,786,788,789,794,801,806,807,829,830,832,849,851,853,869,871,874,875,878,882,888,893,895,896,898,899,903,906,908,911,912,913,922,930,932,938,941,944,950,960,963,966,968,972,977,985,986,988,990,991,994,997,1005,1010,1012,1015,1038,1042,1046,1048,1049,1054,1055,1061,1067,1072,1073,1092,1097,1103,1106,1109,1125,1134,1143,1151,1154,1174,1175,1190,1191,1194,1200,1204,1212,1216,1225,1228,1231,1236,1241,1250,1252,1257,1258,1259,1262,1268,1278,1284,1290,1291,1294,1298,1300,1302,1308,1318,1331,1333,1339,1348,1349,1359,1368,1373,1385,1391,1400,1408,1410,1412,1424,1428,1430,1433,1073,1092,1097,1103,1106,1109,1125,1134,1143,1151,1154,1174,1175,1190,1191,1194,1200,1204,1212,1216,1225,1228,1231,1236,1241,1250,1252,1257,1258,1259,1262,1268] \ No newline at end of file diff --git a/cardano-chain-gen/test/testfiles/fingerprint/conwayPoolStatRollbackNoDuplicates b/cardano-chain-gen/test/testfiles/fingerprint/conwayPoolStatRollbackNoDuplicates index 9754d2b01..d69ef2f0c 100644 --- a/cardano-chain-gen/test/testfiles/fingerprint/conwayPoolStatRollbackNoDuplicates +++ b/cardano-chain-gen/test/testfiles/fingerprint/conwayPoolStatRollbackNoDuplicates @@ -1 +1 @@ -[12,16,18,21,24,30,31,32,33,40,41,42,43,47,52,60,62,70,80,84,86,92,98,100,106,109,110,111,112,127,134,138,146,149,154,166,168,178,183,188,193,194,198,200,202,220,222,223,224,225,231,239,242,247,261,282,283,288,289,301,302,303,308,313,315,316,320,331,334,344,345,363,364,368,369,375,377,381,389,394,407,418,422,425,430,437,438,439,440,447,450,453,454,456,458,461,467,492,499,507,516,524,538,541,544,546,550,567,573,576,577,579,580,586,589,595,597,603,605,609,616,618,619,623,624,634,636,643,644,659,664,665,672,678,692,705,711,712,719,726,730,739,740,743,747,749,751,754,759,762,763,765,767,773,777,786,788,789,794,801,806,807,829,830,832,849,851,853,869,871,874,875,878,882,888,893,895,896,898,899,903,906,908,911,912,913,922,930,932,938,941,944,950,960,963,966,968,972,977,985,986,988,990,991,994,997,1001,1002,1034,1035,1036,1039,1041,1051,1059,1061,1068,1076,1081,1082,1102,1104,1106,1123,1126,1138,1143,1144,1149,1162,1167,1172,1177,1181,1184,1185,1188,1190,1213,1214,1221,1233,1234,1245,1250,1251,1261,1265,1266,1267,1281,1289,1291,1294,1300,1304,1307,1308,1310,1313,1315,1319,1325,1334,1353,1359,1361,1362,1370,1371,1373,1375,1381,1383,1397,1399,1404,1415,1416,1420,1422,1426,1436,1437,1441,1444,1448,1462,1467,1470,1486,1489,1494,1496,1497,1500,1501,1504,1505,1512,1514,1524,1531,1532,1537,1539,1541,1544,1546,1561,1592,1598,1599,1601,1605,1621,1623,1624,1626,1627,1633,1638,1640,1644,1649,1664,1680,1684,1685,1687,1694,1701,1703,1706,1712,1714,1720,1722,1724,1730,1738,1740,1743,1744,1753,1754,1755,1761,1762,1763,1768,1802,1804,1806,1807,1826,1841,1842,1846,1850,1858,1867,1874,1880,1885,1887,1890,1891,1896,1897,1900,1901,1904,1909,1918,1919,1920,1926,1927,1934,1943,1949,1951,1952,1961,1964,1973,1980,1983,1987,1996,2000,2001,2006,2007,2013,2019,2020,2023,2029,2031,2036,2037,2042,2055,2061,2068,2075,2082,2085,2090,2093,2100,2104,2114,2115,2116,2117,2118,2119,2120,2124,2130,2133,2136,2142,2153,2161,2165,2170,2172,2174,2176,2185,2189,2191,2195,2202,2204,2210,2213,2214,2215,2226,2227,2231,2234,2235,2237,2244,2252] \ No newline at end of file +[12,16,18,21,24,30,31,32,33,40,41,42,43,47,52,60,62,70,80,84,86,92,98,100,106,109,110,111,112,127,134,138,146,149,154,166,168,178,183,188,193,194,198,200,202,220,222,223,224,225,231,239,242,247,261,282,283,288,289,301,302,303,308,313,315,316,320,331,334,344,345,363,364,368,369,375,377,381,389,394,407,418,422,425,430,437,438,439,440,447,450,453,454,456,458,461,467,492,499,507,516,524,538,541,544,546,550,567,573,576,577,579,580,586,589,595,597,603,605,609,616,618,619,623,624,634,636,643,644,659,664,665,672,678,692,705,711,712,719,726,730,739,740,743,747,749,751,754,759,762,763,765,767,773,777,786,788,789,794,801,806,807,829,830,832,849,851,853,869,871,874,875,878,882,888,893,895,896,898,899,903,906,908,911,912,913,922,930,932,938,941,944,950,960,963,966,968,972,977,985,986,988,990,991,994,997,1001,1002,1034,1035,1036,1039,1041,1051,1059,1061,1068,1076,1081,1082,1102,1104,1106,1123,1126,1138,1143,1144,1149,1162,1167,1172,1177,1181,1184,1185,1188,1190,1213,1214,1221,1233,1234,1245,1250,1251,1261,1265,1266,1267,1281,1289,1291,1294,1300,1304,1307,1308,1310,1313,1315,1319,1325,1334,1353,1359,1361,1362,1370,1371,1373,1375,1381,1383,1397,1399,1404,1415,1416,1420,1422,1426,1436,1437,1441,1444,1448,1462,1467,1470,1486,1489,1494,1496,1497,1500,1501,1504,1505,1512,1514,1524,1531,1532,1537,1539,1541,1544,1546,1561,1592,1598,1599,1601,1605,1621,1623,1624,1626,1627,1633,1638,1640,1644,1649,1664,1680,1684,1685,1687,1694,1701,1703,1706,1712,1714,1720,1722,1724,1730,1738,1740,1743,1744,1753,1754,1755,1761,1762,1763,1768,1289,1291,1294,1300,1304,1307,1308,1310,1313,1315,1319,1325,1334,1353,1359,1361,1362,1370,1371,1373,1375,1381,1383,1397,1399,1404,1415,1416,1420,1422,1426,1436,1437,1441,1444,1448,1462,1467,1470,1486,1489,1494,1496,1497,1500,1501,1504,1505,1512,1514,1524,1531,1532,1537,1539,1541,1544,1546,1561,1592,1598,1599,1601,1605,1621,1623,1624,1626,1627,1633,1638,1640,1644,1649,1664,1680,1684,1685,1687,1694,1701,1703,1706,1712,1714,1720,1722,1724,1730,1738,1740,1743,1744,1753,1754,1755,1761,1762,1763,1768,1802] \ No newline at end of file diff --git a/cardano-chain-gen/test/testfiles/fingerprint/conwayRestartAndRollback b/cardano-chain-gen/test/testfiles/fingerprint/conwayRestartAndRollback index 3ccd50fb3..e0cbad055 100644 --- a/cardano-chain-gen/test/testfiles/fingerprint/conwayRestartAndRollback +++ b/cardano-chain-gen/test/testfiles/fingerprint/conwayRestartAndRollback @@ -1 +1 @@ -[18,32,33,40,41,60,80,84,106,110,111,112,154,168,178,183,194,198,200,202,223,224,239,242,261,288,303,313,315,331,344,364,369,394,407,418,425,439,450,453,467,492,499,516,517,526,538,544,562,574,580,594,602,603,632,640,641,653,659,684,703,792,808,810,812,816,819,822,844,867,868,921,930,938,939,951,961,970,971,974,993,1009,1025,1052,1070,1093,1110,1111,1114,1126,1161,1170,1171,1174,1191,1207,1217,1218,1244,1275,1299,1304,1307,1314,1331,1338,1398,1413,1414,1416,1426,1441,1458,1460,1471,1486,1489,1490,1493,1505,1513,1518,1525,1542,1550,1578,1580,1602,1605,1617,1628,1635,1643,1644,1646,1661,1672,1683,1686,1694,1709,1716,1724,1731,1736,1746,1749,1778,1791,1793,1807,1816,1846,1852,1853,1882,1894,1897,1908,1932,1933,1940,1955,1961,1965,1971,1994,2002,2018,2036,2038,2052,2053,2068,2086,2093,2095,2103,2108,2124,2141,2144,2149,2168,2175,2179,2186,2193,2197,2198,2225,2232,2242,2253,2257,2262,2272,2277,2303,2315,2320,2322,2342,2354,2355,2365] \ No newline at end of file +[18,32,33,40,41,60,80,84,106,110,111,112,154,168,178,183,194,198,200,202,223,224,239,242,261,288,303,313,315,331,344,364,369,394,407,418,425,439,450,453,467,492,499,516,517,526,538,544,562,574,580,594,602,603,632,640,641,653,659,684,703,792,808,810,812,816,819,822,844,867,868,921,930,938,939,951,961,970,971,974,993,1009,1025,1052,1070,1093,1110,1111,1114,1126,1161,1170,1171,1174,1191,1207,1217,1218,1244,1275,1299,1304,1307,1314,1331,1338,1398,1413,1414,1416,1426,1441,1458,1460,1471,1486,1489,1490,1493,1505,1513,1518,1525,1542,1550,1578,1580,1602,1605,1617,1628,1635,1643,1644,1646,1661,1672,1683,1686,1694,1709,1716,1724,1731,1736,1746,1749,1778,1791,1793,1807,1816,1846,1852,1853,1882,1894,1897,1908,1932,1933,1940,1955,1961,1965,1971,1994,2002,2018,2036,2038,2052,2053,2068,2086,2093,2095,2103,2108,2124,2141,2144,2149,2168,2175,2179,2186,2193,2197,2198,2225,2232,2242,2253,2257,2262,2272,2277,2303,2315,2320,2322,2342,2354,2355,2365,2322] \ No newline at end of file diff --git a/cardano-chain-gen/test/testfiles/fingerprint/conwayRollbackBoundary b/cardano-chain-gen/test/testfiles/fingerprint/conwayRollbackBoundary index ad9d03fa1..98b38e720 100644 --- a/cardano-chain-gen/test/testfiles/fingerprint/conwayRollbackBoundary +++ b/cardano-chain-gen/test/testfiles/fingerprint/conwayRollbackBoundary @@ -1 +1 @@ -[12,16,18,21,24,30,31,32,33,40,41,42,43,47,52,60,62,70,80,84,86,92,98,100,106,109,110,111,112,127,134,138,146,149,154,166,168,178,183,188,193,194,198,200,202,220,222,223,224,225,231,239,242,247,261,282,283,288,289,301,302,303,308,313,315,316,320,331,334,344,345,363,364,368,369,375,377,381,389,394,407,418,422,425,430,437,438,439,440,447,450,453,454,456,458,461,467,492,499,507,516,524,538,541,544,546,550,567,573,576,577,579,580,586,589,595,597,603,605,609,616,618,619,623,624,634,636,643,644,659,664,665,672,678,692,705,711,712,719,726,730,739,740,743,747,749,751,754,759,762,763,765,767,773,777,786,788,789,794,801,806,807,829,830,832,849,851,853,869,871,874,875,878,882,888,893,895,896,898,899,903,906,908,911,912,913,922,930,932,938,941,944,950,960,963,966,968,972,977,985,986,988,990,991,994,997,1001,1002,1034,1035,1036,1039,1041,1051,1059,1061,1068,1076,1081,1082,1102,1104,1106,1123,1126,1138,1143,1144,1149,1162,1167,1172,1177,1181,1184,1185,1188,1190,1213,1214,1221,1233,1234,1245,1250,1251,1261,1265,1266,1267,1281,1289,1291,1294,1300,1304,1307,1308,1310,1313,1315,1319,1325,1334,1353,1359,1361,1362,1370,1371,1373,1375,1381,1383,1397,1399,1404,1415,1416,1420,1422,1426,1436,1437,1441,1444,1448,1462,1467,1470,1486,1489,1494,1496,1497,1500,1501,1504,1505,1512,1514,1524,1531,1532,1537,1539,1541,1544,1546,1561,1592,1598,1599,1601,1605,1621,1623,1624,1626,1627,1633,1638,1640,1644,1649,1664,1680,1684,1685,1687,1694,1701,1703,1706,1712,1714,1720,1722,1724,1730,1738,1740,1743,1744,1753,1754,1755,1761,1762,1763,1768,1802,1804,1806,1807,1826,1841,1842,1846,1850,1858,1867,1874,1880,1885,1887,1890,1891,1896,1897,1900,1901,1904,1909,1918,1919,1920,1926,1927,1934,1943,1949,1951,1952,1961,1964,1973,1980,1983,1987,1996,2000] \ No newline at end of file +[12,16,18,21,24,30,31,32,33,40,41,42,43,47,52,60,62,70,80,84,86,92,98,100,106,109,110,111,112,127,134,138,146,149,154,166,168,178,183,188,193,194,198,200,202,220,222,223,224,225,231,239,242,247,261,282,283,288,289,301,302,303,308,313,315,316,320,331,334,344,345,363,364,368,369,375,377,381,389,394,407,418,422,425,430,437,438,439,440,447,450,453,454,456,458,461,467,492,499,507,516,524,538,541,544,546,550,567,573,576,577,579,580,586,589,595,597,603,605,609,616,618,619,623,624,634,636,643,644,659,664,665,672,678,692,705,711,712,719,726,730,739,740,743,747,749,751,754,759,762,763,765,767,773,777,786,788,789,794,801,806,807,829,830,832,849,851,853,869,871,874,875,878,882,888,893,895,896,898,899,903,906,908,911,912,913,922,930,932,938,941,944,950,960,963,966,968,972,977,985,986,988,990,991,994,997,1001,1002,1034,1035,1036,1039,1041,1051,1059,1061,1068,1076,1081,1082,1102,1104,1106,1123,1126,1138,1143,1144,1149,1162,1167,1172,1177,1181,1184,1185,1188,1190,1213,1214,1221,1233,1234,1245,1250,1251,1261,1265,1266,1267,1281,1289,1291,1294,1300,1304,1307,1308,1310,1313,1315,1319,1325,1334,1353,1359,1361,1362,1370,1371,1373,1375,1381,1383,1397,1399,1404,1415,1416,1420,1422,1426,1436,1437,1441,1444,1448,1462,1467,1470,1486,1489,1494,1496,1497,1500,1310,1313,1315,1319,1325,1334,1353,1359,1361,1362,1370,1371,1373,1375,1381,1383,1397,1399,1404,1415,1416,1420,1422,1426,1436,1437,1441,1444,1448,1462,1467,1470,1486,1489,1494,1496,1497,1500] \ No newline at end of file diff --git a/cardano-chain-gen/test/testfiles/fingerprint/conwayRollbackChangeTxOrder b/cardano-chain-gen/test/testfiles/fingerprint/conwayRollbackChangeTxOrder index bf2d8e7a5..7840b4489 100644 --- a/cardano-chain-gen/test/testfiles/fingerprint/conwayRollbackChangeTxOrder +++ b/cardano-chain-gen/test/testfiles/fingerprint/conwayRollbackChangeTxOrder @@ -1 +1 @@ -[12,16,16] \ No newline at end of file +[12,16,16,18] \ No newline at end of file diff --git a/cardano-chain-gen/test/testfiles/fingerprint/conwayRollbackFork b/cardano-chain-gen/test/testfiles/fingerprint/conwayRollbackFork index 9fdd9e2c4..abe61dffb 100644 --- a/cardano-chain-gen/test/testfiles/fingerprint/conwayRollbackFork +++ b/cardano-chain-gen/test/testfiles/fingerprint/conwayRollbackFork @@ -1 +1 @@ -[1,3,4,7,8,9,10,11,14,30,31,33,34,35,40,42,44,61,62,74,76,82,85,88,89,93,95,102,104,106,111,114,120,123,141,143,146,149,158,170,171,178,186,190,198,201,207,209,210,221,223,227,245,249,250,259,260,265,272,276,283,284,294,296,301,305,306,311,312,317,318,321,322,325,331,333,337,339,345,347,348,350,365,375,377,379,382,391,394,401,407,411,413,415,424,428,445,453,467,469,471,474,487,489,490,492,497,498,515,519,520,524,528,529,530,531,554,557,567,568,575,576,597,603,615,616,631,637,640,641,643,650,654,656,657,662,668,676,678,688,694,695,698,700,701,702,703,716,725,727,729,730,732,733,738,747,750,771,774,777,778,780,785,796,798,799,805,808,819,821,822,827,831,833,835,838,841,844,847,848,858,859,860,863,864,872,875,889,906,912,913,914,917,942,943,945,948,950,952,954,955,959,967,971,980,981,983,993,997,1002,1003] \ No newline at end of file +[1,3,4,7,8,9,10,11,14,30,31,33,34,35,40,42,44,61,62,74,76,82,85,88,89,93,95,102,104,106,111,114,120,123,141,143,146,149,158,170,171,178,186,190,198,201,207,209,210,221,223,227,245,249,250,259,260,265,272,276,283,284,294,296,301,305,306,311,312,317,318,321,322,325,331,333,337,339,345,347,348,350,365,375,377,379,382,391,394,401,407,411,413,415,424,428,445,453,467,469,471,474,487,489,490,492,497,498,515,519,520,524,528,529,530,531,554,557,567,568,575,576,597,603,615,616,631,637,640,641,643,650,654,656,657,662,668,676,678,688,694,695,698,700,701,702,703,716,725,727,729,730,732,733,738,747,750,771,774,777,778,780,785,796,798,799,805,808,819,821,822,827,831,833,835,838,841,844,847,848,858,859,860,863,864,872,875,889,906,912,913,914,917,942,943,945,948,950,952,954,955,959,967,971,980,981,983,993,997,1002,1003,943] \ No newline at end of file diff --git a/cardano-chain-gen/test/testfiles/fingerprint/conwayRollbackFullTx b/cardano-chain-gen/test/testfiles/fingerprint/conwayRollbackFullTx index bf2d8e7a5..7840b4489 100644 --- a/cardano-chain-gen/test/testfiles/fingerprint/conwayRollbackFullTx +++ b/cardano-chain-gen/test/testfiles/fingerprint/conwayRollbackFullTx @@ -1 +1 @@ -[12,16,16] \ No newline at end of file +[12,16,16,18] \ No newline at end of file diff --git a/cardano-chain-gen/test/testfiles/fingerprint/conwayRollbackHardFork b/cardano-chain-gen/test/testfiles/fingerprint/conwayRollbackHardFork index f7a881706..ecb173b2e 100644 --- a/cardano-chain-gen/test/testfiles/fingerprint/conwayRollbackHardFork +++ b/cardano-chain-gen/test/testfiles/fingerprint/conwayRollbackHardFork @@ -1 +1 @@ -[12,16,18,21,24,30,31,32,33,40,41,42,43,47,52,60,62,70,80,84,86,92,98,100,106,109,110,111,112,127,134,138,146,149,154,166,168,178,183,188,193,194,198,200,202,220,222,223,224,225,231,239,242,247,261,282,283,288,289,301,302,303,308,313,315,316,320,331,334,344,345,363,364,368,369,375,377,381,389,394,407,418,422,425,430,437,438,439,440,447,450,453,454,456,458,461,467,492,499,507,516,524,538,541,544,546,550,567,573,576,577,579,580,586,589,595,597,603,605,609,616,618,619,623,624,634,636,643,644,659,664,665,672,678,692,705,711,712,719,726,730,739,740,743,747,749,751,754,759,762,763,765,767,773,777,786,788,789,794,801,806,807,829,830,832,849,851,853,869,871,874,875,878,882,888,893,895,896,898,899,903,906,908,911,912,913,922,930,932,938,941,944,950,960,963,966,968,972,977,985,986,988,990,991,994,997,1001,1005,1014,1019,1020,1026,1027,1031,1032,1033,1036,1037,1050,1057,1062,1067,1068,1070,1074,1083,1094,1102,1104,1107,1111,1115,1118,1120,1125,1137,1149,1151,1155,1161,1164,1167,1174,1187,1200,1201,1218,1221,1237,1242,1248,1263,1266,1272,1277,1283,1299,1304,1309,1313,1317,1336,1338,1343,1356,1366,1376,1377,1379,1390,1397,1401,1408,1410,1412,1418,1424,1429,1432,1435,1439,1442,1444,1449,1453,1462,1470,1473,1474,1481,1484,1486,1519,1486,1519] \ No newline at end of file +[12,16,18,21,24,30,31,32,33,40,41,42,43,47,52,60,62,70,80,84,86,92,98,100,106,109,110,111,112,127,134,138,146,149,154,166,168,178,183,188,193,194,198,200,202,220,222,223,224,225,231,239,242,247,261,282,283,288,289,301,302,303,308,313,315,316,320,331,334,344,345,363,364,368,369,375,377,381,389,394,407,418,422,425,430,437,438,439,440,447,450,453,454,456,458,461,467,492,499,507,516,524,538,541,544,546,550,567,573,576,577,579,580,586,589,595,597,603,605,609,616,618,619,623,624,634,636,643,644,659,664,665,672,678,692,705,711,712,719,726,730,739,740,743,747,749,751,754,759,762,763,765,767,773,777,786,788,789,794,801,806,807,829,830,832,849,851,853,869,871,874,875,878,882,888,893,895,896,898,899,903,906,908,911,912,913,922,930,932,938,941,944,950,960,963,966,968,972,977,985,986,988,990,991,994,997,1001,1005,1014,1019,1020,1026,1027,1031,1032,1033,1036,1037,1050,1057,1062,1067,1068,1070,1074,1083,1094,1102,1104,1107,1111,1115,1118,1120,1125,1137,1149,1151,1155,1161,1164,1167,1174,1187,1200,1201,1218,1221,1237,1242,1248,1263,1266,1272,1277,1283,1299,1304,1309,1313,1317,1336,1338,1343,1356,1366,1376,1377,1379,1390,1397,1401,1408,1410,1412,1418,1424,1429,1432,1435,1439,1442,1444,1449,1453,1462,1470,1473,1474,1481,1484,1486,1519,1481,1484,1486,1519] \ No newline at end of file diff --git a/cardano-chain-gen/test/testfiles/fingerprint/conwayRollbackNewCommittee b/cardano-chain-gen/test/testfiles/fingerprint/conwayRollbackNewCommittee index 398e2618c..40f4380e3 100644 --- a/cardano-chain-gen/test/testfiles/fingerprint/conwayRollbackNewCommittee +++ b/cardano-chain-gen/test/testfiles/fingerprint/conwayRollbackNewCommittee @@ -1 +1 @@ -[12,16,18,21,24,30,31,32,33,40,41,42,43,47,52,60,62,70,80,84,86,92,98,100,106,109,110,111,112,127,134,138,146,149,154,166,168,178,183,188,193,194,198,200,202,220,222,223,224,225,231,239,242,247,261,282,283,288,289,301,302,303,308,313,315,316,320,331,334,344,345,363,364,368,369,375,377,381,389,394,407,418,422,425,430,437,438,439,440,447,450,453,454,456,458,461,467,492,499,507,516,524,538,541,544,546,550,567,573,576,577,579,580,586,589,595,597,603,605,609,616,618,619,623,624,634,636,643,644,659,664,665,672,678,692,705,711,712,719,726,730,739,740,743,747,749,751,754,759,762,763,765,767,773,777,786,788,789,794,801,806,807,829,830,832,849,851,853,869,871,874,875,878,882,888,893,895,896,898,899,903,906,908,911,912,913,922,930,932,938,941,944,950,960,963,966,968,972,977,985,986,988,990,991,994,997,1001,1005,1014,1019,1020,1026,1027,1031,1032,1033,1036,1037,1050,1057,1062,1067,1068,1070,1074,1083,1094,1102,1104,1107,1111,1115,1118,1120,1125,1137,1149,1151,1155,1161,1164,1167,1174,1187,1200,1201,1218,1221,1237,1242,1248,1263,1266,1272,1277,1283,1299,1304,1309,1313,1317,1336,1338,1343,1356,1366,1376,1377,1379,1390,1397,1401,1408,1410,1412,1418,1424,1429,1432,1435,1439,1442,1444,1449,1453,1462,1470,1473,1474,1481,1484,1486,1518,1486,1518] \ No newline at end of file +[12,16,18,21,24,30,31,32,33,40,41,42,43,47,52,60,62,70,80,84,86,92,98,100,106,109,110,111,112,127,134,138,146,149,154,166,168,178,183,188,193,194,198,200,202,220,222,223,224,225,231,239,242,247,261,282,283,288,289,301,302,303,308,313,315,316,320,331,334,344,345,363,364,368,369,375,377,381,389,394,407,418,422,425,430,437,438,439,440,447,450,453,454,456,458,461,467,492,499,507,516,524,538,541,544,546,550,567,573,576,577,579,580,586,589,595,597,603,605,609,616,618,619,623,624,634,636,643,644,659,664,665,672,678,692,705,711,712,719,726,730,739,740,743,747,749,751,754,759,762,763,765,767,773,777,786,788,789,794,801,806,807,829,830,832,849,851,853,869,871,874,875,878,882,888,893,895,896,898,899,903,906,908,911,912,913,922,930,932,938,941,944,950,960,963,966,968,972,977,985,986,988,990,991,994,997,1001,1005,1014,1019,1020,1026,1027,1031,1032,1033,1036,1037,1050,1057,1062,1067,1068,1070,1074,1083,1094,1102,1104,1107,1111,1115,1118,1120,1125,1137,1149,1151,1155,1161,1164,1167,1174,1187,1200,1201,1218,1221,1237,1242,1248,1263,1266,1272,1277,1283,1299,1304,1309,1313,1317,1336,1338,1343,1356,1366,1376,1377,1379,1390,1397,1401,1408,1410,1412,1418,1424,1429,1432,1435,1439,1442,1444,1449,1453,1462,1470,1473,1474,1481,1484,1486,1518,1481,1484,1486,1518] \ No newline at end of file diff --git a/cardano-chain-gen/test/testfiles/fingerprint/conwayRollbackNewCommitteeProposal b/cardano-chain-gen/test/testfiles/fingerprint/conwayRollbackNewCommitteeProposal index 26c5e85a8..2ebf6a7b7 100644 --- a/cardano-chain-gen/test/testfiles/fingerprint/conwayRollbackNewCommitteeProposal +++ b/cardano-chain-gen/test/testfiles/fingerprint/conwayRollbackNewCommitteeProposal @@ -1 +1 @@ -[12,16,18,21,24,30,31,32,33,40,41,42,43,47,52,60,62,70,80,84,86,92,98,100,106,109,110,111,112,127,134,138,146,149,154,166,168,178,183,188,193,194,198,200,202,220,222,223,224,225,231,239,242,247,261,282,283,288,289,301,302,303,308,313,315,316,320,331,334,344,345,363,364,368,369,375,377,381,389,394,407,418,422,425,430,437,438,439,440,447,450,453,454,456,458,461,467,492,499,507,516,524,516] \ No newline at end of file +[12,16,18,21,24,30,31,32,33,40,41,42,43,47,52,60,62,70,80,84,86,92,98,100,106,109,110,111,112,127,134,138,146,149,154,166,168,178,183,188,193,194,198,200,202,220,222,223,224,225,231,239,242,247,261,282,283,288,289,301,302,303,308,313,315,316,320,331,334,344,345,363,364,368,369,375,377,381,389,394,407,418,422,425,430,437,438,439,440,447,450,453,454,456,458,461,467,492,499,507,516,524,516,524] \ No newline at end of file diff --git a/cardano-chain-gen/test/testfiles/fingerprint/conwaySimpleRollback b/cardano-chain-gen/test/testfiles/fingerprint/conwaySimpleRollback index a27a0b600..6a9a9ac17 100644 --- a/cardano-chain-gen/test/testfiles/fingerprint/conwaySimpleRollback +++ b/cardano-chain-gen/test/testfiles/fingerprint/conwaySimpleRollback @@ -1 +1 @@ -[18,21,24] \ No newline at end of file +[18,21,24,24] \ No newline at end of file diff --git a/cardano-chain-gen/test/testfiles/fingerprint/conwayStakeAddressRollback b/cardano-chain-gen/test/testfiles/fingerprint/conwayStakeAddressRollback index 7840b4489..0a5fe0d73 100644 --- a/cardano-chain-gen/test/testfiles/fingerprint/conwayStakeAddressRollback +++ b/cardano-chain-gen/test/testfiles/fingerprint/conwayStakeAddressRollback @@ -1 +1 @@ -[12,16,16,18] \ No newline at end of file +[12,16,16,18,21] \ No newline at end of file diff --git a/cardano-chain-gen/test/testfiles/fingerprint/doubleRollback b/cardano-chain-gen/test/testfiles/fingerprint/doubleRollback deleted file mode 100644 index cc522d75d..000000000 --- a/cardano-chain-gen/test/testfiles/fingerprint/doubleRollback +++ /dev/null @@ -1 +0,0 @@ -[5,11,15,21,22,23,28,33,34,36,42,43,48,52,62,82,88,92,102,106,109,111,116,133,134,143,151,153,157,161,162,171,182,183,193,195,196,197,200,206,208,216,219,222,238,245,250,262,271,272,275,282,286,296,301,310,311,314,325,340,347,354,355,365,376,379,382,384,389,390,391,392,393,398,404,407,414,418,419,422,424,446,448,450,457,465,476,478,485,486,488,499,503,506,509,512,515,518,524,526,527,530,541,542,549,556,561,570,576,578,579,583,589,596,597,609,611,615,620,621,627,633,634,644,650,651,654,661,671,675,680,682,687,694,698,703,705,711,716,718,726,728,730,739,748,749,757,761,782,784,785,791,796,798,815,818,823,837,845,846,847,858,862,865,877,879,881,882,884,885,888,890,892,893,895,898,900,904,908,916,921,922,923,929,930,932,934,936,950,956,957,968,969,985,992,993,994,1009,1011,1022,1025,1027,1033,1035,1036,1037,1042,1043,1045,1052,1065,1077,1082,1088,1102,1103,1105,1106,1109,1128,1137,1143,1156,1167,1169,1172,1177,1178,1180,1189,1193,1197,1198,1201,1208,1212,1214,1217,1218,1223,1225,1229,1232,1233,1246,1248,1253,1256,1267,1278,1284,1289,1290,1305,1307,1308,1312,1316,1326,1329,1334,1349,1361,1366,1368,1369,1372,1377,1382,1383,1386,1387,1390,1392,1401,1406,1409,1412,1413,1416,1419,1421,1423,1431,1433,1438,1442,1453,1466,1479,1485,1491,1493,1495,1502,1507,1510,1522,1524,1528,1537,1540,1542,1556,1561,1563,1568,1573,1575,1580,1588,1591,1595,1600,1622,1623,1625,1629,1633,1634,1637,1639,1640,1647,1651,1653,1659,1660,1671,1672,1675,1682,1698,1702,1707,1713,1714,1724,1728,1732,1736,1740,1741,1744,1751,1753,1754,1757,1760,1765,1284,1289,1290,1305,1307,1308,1312,1316,1326,1329,1334,1349,1361,1366,1368,1369,1372,1377,1382,1383,1386,1387,1390,1392,1401,1406,1409,1412,1413,1416,1419,1421,1423,1431,1433,1438,1442,1453,1466,1479,1485,1491,1493,1495,1502,1507,1510,1522,1524,1528,1537,785,791,796,798,815,818,823,837,845,846,847,858,862,865,877,879,881,882,884,885,888,890,892,893,895,898,900,904,908,916,921,922,923,929,930,932,934,936,950,956,957,968,969,985,992,993,994,1009,1011,1022,1025] \ No newline at end of file diff --git a/cardano-chain-gen/test/testfiles/fingerprint/lazyRollback b/cardano-chain-gen/test/testfiles/fingerprint/lazyRollback deleted file mode 100644 index 89ed79c70..000000000 --- a/cardano-chain-gen/test/testfiles/fingerprint/lazyRollback +++ /dev/null @@ -1 +0,0 @@ -[5,11,15,21,22,23,28,33,34,36,42,43,48,52,62,82,88,92,102,106,109,111,116,133,134,143,151,153,157,161,162,171,182,183,193,195,196,197,200,206,208,216,219,222,238,245,250,262,271,272,275,282,286,296,301,310,311,314,325,340,347,354,355,365,376,379,382,384,389,390,391,392,393,398,404,407,414,418,419,422,424,446,448,450,457,465,476,478,485,486,488,499,503,506,509,512,515,518,524,526,527,530,541,542,549,556,561,570,576,578,579,583,589,596,597,609,611,615,620,621,627,633,634,644,650,651,654,661,671,675,680,682,687,694,698,703,705,711,716,718,726,728,730,739,748,749,757,761,782,784,785,791,796,798,815,818,823,837,845,846,847,858,862,865,877,879,881,882,884,885,888,890,892,893,895,898,900,904,908,916,921,922,923,929,930,932,934,936,950,956,957,968,969,985,992,993,994,1009,1011,1022,1025,1027,1033,1035,1036,1037,1042,1043,1045,1052,1065,1077,1082,1088,1102,1103,1105,1106,1109,1128,1137,1143,1156,1167,1169,1172,1177,1178,1180,1189,1193,1197,1198,1201,1208,1212,1214,1217,1218,1223,1225,1229,1232,1233,1246,1248,1253,1256,1267,1278,1284,1289,1290,1305,1307,1308,1312,1316,1326,1329,1334,1349,1361,1366,1368,1369,1372,1377,1382,1383,1025,1027,1033,1035,1036,1037,1042,1043,1045,1052,1065,1077,1082,1088,1102,1103,1105,1106,1109,1128,1137,1143,1156,1167,1169,1172,1177,1178,1180,1189,1193,1197,1198,1201,1208,1212,1214,1217,1218,1223,1225] \ No newline at end of file diff --git a/cardano-chain-gen/test/testfiles/fingerprint/lazyRollbackRestart b/cardano-chain-gen/test/testfiles/fingerprint/lazyRollbackRestart deleted file mode 100644 index e2f3c1d26..000000000 --- a/cardano-chain-gen/test/testfiles/fingerprint/lazyRollbackRestart +++ /dev/null @@ -1 +0,0 @@ -[5,11,15,21,22,23,28,33,34,36,42,43,48,52,62,82,88,92,102,106,109,111,116,133,134,143,151,153,157,161,162,171,182,183,193,195,196,197,200,206,208,216,219,222,238,245,250,262,271,272,275,282,286,296,301,310,311,314,325,340,347,354,355,365,376,379,382,384,389,390,391,392,393,398,404,407,414,418,419,422,424,446,448,450,457,465,476,478,485,486,488,499,503,506,509,512,515,518,524,526,527,530,541,542,549,556,561,570,576,578,579,583,589,596,597,609,611,615,620,621,627,633,634,644,650,651,654,661,671,675,680,682,687,694,698,703,705,711,716,718,726,728,730,739,748,749,757,761,782,784,785,791,796,798,815,818,823,837,845,846,847,858,862,865,877,879,881,882,884,885,888,890,892,893,895,898,900,904,908,916,921,922,923,929,930,932,934,936,950,956,957,968,969,985,992,993,994,1009,1011,1022,1025,1027,1033,1035,1036,1037,1042,1043,1045,1052,1065,1077,1082,1088,1102,1103,1105,1106,1109,1128,1137,1143,1156,1167,1169,1172,1177,1178,1180,1189,1193,1197,1198,1201,1208,1212,1214,1217,1218,1223,1225,1229,1232,1233,1246,1248,1253,1256,1267,1278,1284,1289,1290,1305,1307,1308,1312,1316,1326,1329,1334,1349,1361,1366,1368,1369,1372,1377,1382,1383,1386,1387,1390,1392,1401,1406,1409,1412,1413,1416,1137,1143,1156,1167,1169,1172,1177,1178,1180,1189,1193,1197,1198,1201,1208,1212,1214,1217,1218,1223,1225,1229,1232,1233,1246,1248,1253,1256,1267,1278,1284] \ No newline at end of file diff --git a/cardano-chain-gen/test/testfiles/fingerprint/mirRewardRollback-alonzo b/cardano-chain-gen/test/testfiles/fingerprint/mirRewardRollback-alonzo deleted file mode 100644 index a1938babc..000000000 --- a/cardano-chain-gen/test/testfiles/fingerprint/mirRewardRollback-alonzo +++ /dev/null @@ -1 +0,0 @@ -[3,4,6,13,22,31,43,46,52,54,56,64,69,73,76,78,79,90,98,99,104,105,106,109,111,113,114,120,122,124,132,142,143,144,152,158,163,167,199,201,209,210,216,219,235,237,254,261,268,273,275,279,280,285,303,304,306,309,310,313,322,325,327,329,330,331,335,340,346,348,353,361,366,372,373,376,377,378,383,388,391,392,393,397,406,408,409,413,420,422,430,438,440,444,452,454,456,460,461,468,469,471,478,483,488,503,507,511,513,514,529,530,536,547,550,554,556,558,561,562,565,566,577,591,594,595,596,599,605,606,611,620,625,627,629,643,644,655,658,667,676,684,690,695,701,704,711,715,720,723,730,732,737,739,741,748,752,755,758,765,772,776,779,780,781,785,790,806,810,816,818,820,822,835,843,846,852,854,855,858,864,865,866,875,878,880,883,888,891,900,904,905,906,907,911,914,917,920,925,934,939,945,951,953,959,962,968,971,975,979,983,988,992,993,996,1008,1009,1013,1014,1028,1029] \ No newline at end of file diff --git a/cardano-chain-gen/test/testfiles/fingerprint/multipleScriptsRollback b/cardano-chain-gen/test/testfiles/fingerprint/multipleScriptsRollback deleted file mode 100644 index 9a1a79291..000000000 --- a/cardano-chain-gen/test/testfiles/fingerprint/multipleScriptsRollback +++ /dev/null @@ -1 +0,0 @@ -[15,23,5,15,23] \ No newline at end of file diff --git a/cardano-chain-gen/test/testfiles/fingerprint/restartAndRollback b/cardano-chain-gen/test/testfiles/fingerprint/restartAndRollback deleted file mode 100644 index 20a5c59ac..000000000 --- a/cardano-chain-gen/test/testfiles/fingerprint/restartAndRollback +++ /dev/null @@ -1 +0,0 @@ -[28,42,43,52,62,82,92,106,109,133,161,162,171,195,196,197,206,208,216,222,272,275,282,347,382,392,393,398,414,424,446,448,465,478,485,499,500,506,508,509,513,514,515,518,539,548,566,577,584,589,602,613,626,644,661,664,668,677,725,729,736,746,749,757,773,774,784,810,813,819,828,849,852,866,876,880,886,895,900,924,930,952,964,971,981,987,989,1001,1005,1012,1025,1026,1041,1046,1060,1071,1076,1079,1101,1119,1140,1159,1160,1168,1173,1175,1207,1221,1258,1268,1283,1287,1343,1346,1363,1366,1369,1371,1372,1373,1379,1390,1394,1402,1419,1423,1447,1451,1464,1466,1475,1485,1491,1493,1499,1516,1521,1538,1544,1560,1561,1568,1569,1573,1588,1596,1607,1666,1672,1682,1697,1734,1751,1764,1766,1767,1798,1809,1837,1842,1863,1870,1872,1875,1887,1888,1892,1905,1925,1931,1933,1934,1939,1944,1946,1947,1948,1962,1973,1975,1977,1978,1984,1990,1995,2026,2039,2063,2072,2074,2085,2086,2093,2120,2133,2164,2182,2185,2203,2206,2242,2245,2253,2271,2288,2291] \ No newline at end of file diff --git a/cardano-chain-gen/test/testfiles/fingerprint/rollbackBoundary b/cardano-chain-gen/test/testfiles/fingerprint/rollbackBoundary index 1d8dff2f0..27282f677 100644 --- a/cardano-chain-gen/test/testfiles/fingerprint/rollbackBoundary +++ b/cardano-chain-gen/test/testfiles/fingerprint/rollbackBoundary @@ -1 +1 @@ -[5,11,15,21,22,23,28,33,34,36,42,43,48,52,62,82,88,92,102,106,109,111,116,133,134,143,151,153,157,161,162,171,182,183,193,195,196,197,200,206,208,216,219,222,238,245,250,262,271,272,275,282,286,296,301,310,311,314,325,340,347,354,355,365,376,379,382,384,389,390,391,392,393,398,404,407,414,418,419,422,424,446,448,450,457,465,476,478,485,486,488,499,503,506,509,512,515,518,524,526,527,530,541,542,549,556,561,570,576,578,579,583,589,596,597,609,611,615,620,621,627,633,634,644,650,651,654,661,671,675,680,682,687,694,698,703,705,711,716,718,726,728,730,739,748,749,757,761,782,784,785,791,796,798,815,818,823,837,845,846,847,858,862,865,877,879,881,882,884,885,888,890,892,893,895,898,900,904,908,916,921,922,923,929,930,932,934,936,950,956,957,968,969,985,992,993,994,1001,1003,1006,1012,1014,1032,1033,1034,1036,1038,1046,1047,1054,1068,1073,1074,1078,1084,1088,1096,1098,1100,1111,1115,1120,1130,1131,1142,1144,1149,1151,1158,1160,1163,1167,1170,1176,1180,1187,1197,1198,1199,1204,1209,1214,1222,1224,1230,1239,1247,1248,1259,1268,1275,1278,1281,1289,1293,1300,1302,1303,1307,1310,1312,1313,1317,1324,1334,1336,1338,1347,1356,1361,1377,1379,1387,1392,1398,1401,1404,1410,1418,1419,1423,1426,1434,1437,1443,1447,1449,1454,1460,1461,1466,1467,1473,1484,1485,1489,1490,1495,1496,1500,1505,1506,1510,1517,1521,1527,1529,1533,1558,1563,1565,1566,1571,1579,1584,1588,1591,1598,1600,1605,1612,1626,1629,1639,1650,1656,1664,1666,1667,1672,1677,1678,1684,1689,1701,1705,1706,1716,1718,1727,1733,1755,1760,1766,1792,1795,1798,1800,1803,1809,1816,1819,1825,1829,1831,1835,1839,1842,1843,1851,1857,1860,1862,1867,1872,1874,1886,1888,1894,1897,1905,1906,1913,1914,1915,1917,1919,1920,1923,1940,1942,1944,1955,1957,1966,1978,1981,1990,1995,2006] \ No newline at end of file +[5,11,15,21,22,23,28,33,34,36,42,43,48,52,62,82,88,92,102,106,109,111,116,133,134,143,151,153,157,161,162,171,182,183,193,195,196,197,200,206,208,216,219,222,238,245,250,262,271,272,275,282,286,296,301,310,311,314,325,340,347,354,355,365,376,379,382,384,389,390,391,392,393,398,404,407,414,418,419,422,424,446,448,450,457,465,476,478,485,486,488,499,503,506,509,512,515,518,524,526,527,530,541,542,549,556,561,570,576,578,579,583,589,596,597,609,611,615,620,621,627,633,634,644,650,651,654,661,671,675,680,682,687,694,698,703,705,711,716,718,726,728,730,739,748,749,757,761,782,784,785,791,796,798,815,818,823,837,845,846,847,858,862,865,877,879,881,882,884,885,888,890,892,893,895,898,900,904,908,916,921,922,923,929,930,932,934,936,950,956,957,968,969,985,992,993,994,1001,1003,1006,1012,1014,1032,1033,1034,1036,1038,1046,1047,1054,1068,1073,1074,1078,1084,1088,1096,1098,1100,1111,1115,1120,1130,1131,1142,1144,1149,1151,1158,1160,1163,1167,1170,1176,1180,1187,1197,1198,1199,1204,1209,1214,1222,1224,1230,1239,1247,1248,1259,1268,1275,1278,1281,1289,1293,1300,1302,1303,1307,1310,1312,1313,1317,1324,1334,1336,1338,1347,1356,1361,1377,1379,1387,1392,1398,1401,1404,1410,1418,1419,1423,1426,1434,1437,1443,1447,1449,1454,1460,1461,1466,1467,1473,1484,1485,1489,1490,1495,1496,1500,1268,1275,1278,1281,1289,1293,1300,1302,1303,1307,1310,1312,1313,1317,1324,1334,1336,1338,1347,1356,1361,1377,1379,1387,1392,1398,1401,1404,1410,1418,1419,1423,1426,1434,1437,1443,1447,1449,1454,1460,1461,1466,1467,1473,1484,1485,1489,1490,1495,1496,1500] \ No newline at end of file diff --git a/cardano-chain-gen/test/testfiles/fingerprint/rollbackBoundary-alonzo b/cardano-chain-gen/test/testfiles/fingerprint/rollbackBoundary-alonzo deleted file mode 100644 index 5a4a2eabd..000000000 --- a/cardano-chain-gen/test/testfiles/fingerprint/rollbackBoundary-alonzo +++ /dev/null @@ -1 +0,0 @@ -[3,4,6,13,22,31,43,46,52,54,56,64,69,73,76,78,79,90,98,99,104,105,106,109,111,113,114,120,122,124,132,142,143,144,152,158,163,167,199,201,209,210,216,219,235,237,254,261,268,273,275,279,280,285,303,304,306,309,310,313,322,325,327,329,330,331,335,340,346,348,353,361,366,372,373,376,377,378,383,388,391,392,393,397,406,408,409,413,420,422,430,438,440,444,452,454,456,460,461,468,469,471,478,483,488,503,507,511,513,514,529,530,536,547,550,554,556,558,561,562,565,566,577,591,594,595,596,599,605,606,611,620,625,627,629,643,644,655,658,667,676,684,690,695,701,704,711,715,720,723,730,732,737,739,741,748,752,755,758,765,772,776,779,780,781,785,790,806,810,816,818,820,822,835,843,846,852,854,855,858,864,865,866,875,878,880,883,888,891,900,904,905,906,907,911,914,917,920,925,934,939,945,951,953,959,962,968,971,975,979,983,988,992,993,996,1008,1010,1013,1020,1022,1024,1025,1028,1036,1053,1059,1066,1067,1077,1082,1084,1089,1091,1092,1094,1105,1111,1115,1118,1120,1122,1124,1126,1135,1136,1140,1143,1144,1146,1149,1150,1163,1165,1169,1173,1174,1180,1194,1196,1198,1226,1232,1234,1238,1239,1246,1248,1254,1258,1262,1276,1281,1282,1285,1290,1300,1304,1311,1315,1319,1320,1325,1327,1328,1338,1339,1343,1346,1352,1362,1364,1365,1384,1392,1395,1407,1420,1428,1440,1443,1455,1456,1459,1460,1464,1467,1469,1475,1479,1480,1483,1484,1488,1492,1496,1500,1505,1506,1508,1515,1519,1523,1524,1533,1538,1539,1541,1543,1546,1550,1551,1557,1559,1563,1567,1570,1572,1577,1579,1581,1599,1601,1602,1606,1616,1629,1634,1635,1639,1651,1656,1670,1678,1679,1682,1683,1687,1693,1702,1709,1710,1718,1719,1737,1740,1742,1743,1750,1754,1759,1761,1785,1788,1789,1792,1794,1797,1801,1805,1807,1808,1810,1815,1816,1817,1829,1830,1834,1843,1849,1850,1851,1854,1856,1858,1875,1890,1896,1905,1907,1915,1917,1918,1919,1923,1931,1934,1940,1942,1945,1949,1951,1957,1961,1970,1981,1988,2010] \ No newline at end of file diff --git a/cardano-chain-gen/test/testfiles/fingerprint/rollbackChangeTxOrder b/cardano-chain-gen/test/testfiles/fingerprint/rollbackChangeTxOrder deleted file mode 100644 index b1ccb125b..000000000 --- a/cardano-chain-gen/test/testfiles/fingerprint/rollbackChangeTxOrder +++ /dev/null @@ -1 +0,0 @@ -[5,11,11] \ No newline at end of file diff --git a/cardano-chain-gen/test/testfiles/fingerprint/rollbackFork b/cardano-chain-gen/test/testfiles/fingerprint/rollbackFork deleted file mode 100644 index 6bfd9c678..000000000 --- a/cardano-chain-gen/test/testfiles/fingerprint/rollbackFork +++ /dev/null @@ -1 +0,0 @@ -[3,4,6,13,22,31,43,46,52,54,56,64,69,73,76,78,79,90,98,99,104,105,106,109,111,113,114,120,122,124,132,142,143,144,152,158,163,167,199,201,209,210,216,219,235,237,254,261,268,273,275,279,280,285,303,304,306,309,310,313,322,325,327,329,330,331,335,340,346,348,353,361,366,372,373,376,377,378,383,388,391,392,393,397,406,408,409,413,420,422,430,438,440,444,452,454,456,460,461,468,469,471,478,483,488,503,507,511,513,514,529,530,536,547,550,554,556,558,561,562,565,566,577,591,594,595,596,599,605,606,611,620,625,627,629,643,644,655,658,667,676,684,690,695,701,704,711,715,720,723,730,732,737,739,741,748,752,755,758,765,772,776,779,780,781,785,790,806,810,816,818,820,822,835,843,846,852,854,855,858,864,865,866,875,878,880,883,888,891,900,904,905,906,907,911,914,917,920,925,934,939,945,951,953,959,962,968,971,975,979,983,988,992,993,996,1013,1018] \ No newline at end of file diff --git a/cardano-chain-gen/test/testfiles/fingerprint/rollbackFullTx b/cardano-chain-gen/test/testfiles/fingerprint/rollbackFullTx deleted file mode 100644 index b1ccb125b..000000000 --- a/cardano-chain-gen/test/testfiles/fingerprint/rollbackFullTx +++ /dev/null @@ -1 +0,0 @@ -[5,11,11] \ No newline at end of file diff --git a/cardano-chain-gen/test/testfiles/fingerprint/simpleRollback b/cardano-chain-gen/test/testfiles/fingerprint/simpleRollback deleted file mode 100644 index ee475e707..000000000 --- a/cardano-chain-gen/test/testfiles/fingerprint/simpleRollback +++ /dev/null @@ -1 +0,0 @@ -[28,33,34] \ No newline at end of file diff --git a/cardano-chain-gen/test/testfiles/fingerprint/spendCollateralOutputRollback b/cardano-chain-gen/test/testfiles/fingerprint/spendCollateralOutputRollback deleted file mode 100644 index fb668b604..000000000 --- a/cardano-chain-gen/test/testfiles/fingerprint/spendCollateralOutputRollback +++ /dev/null @@ -1 +0,0 @@ -[5,11,15,21,11,15,21,22] \ No newline at end of file diff --git a/cardano-chain-gen/test/testfiles/fingerprint/stakeAddressRollback b/cardano-chain-gen/test/testfiles/fingerprint/stakeAddressRollback deleted file mode 100644 index 7e384d74c..000000000 --- a/cardano-chain-gen/test/testfiles/fingerprint/stakeAddressRollback +++ /dev/null @@ -1 +0,0 @@ -[5,11,11,15] \ No newline at end of file diff --git a/cardano-db-sync/src/Cardano/DbSync/Api.hs b/cardano-db-sync/src/Cardano/DbSync/Api.hs index 4298fb805..4cc7adbf2 100644 --- a/cardano-db-sync/src/Cardano/DbSync/Api.hs +++ b/cardano-db-sync/src/Cardano/DbSync/Api.hs @@ -448,7 +448,14 @@ getLatestPoints env = do case envLedgerEnv env of HasLedger hasLedgerEnv -> do snapshotPoints <- listKnownSnapshots hasLedgerEnv - verifySnapshotPoint env snapshotPoints + if null snapshotPoints + then do + -- Fallback: When no snapshots available (e.g., after restart), + -- query database for recent blocks to use as intersection points + lastPoints <- DB.runDbDirectSilent (envDbEnv env) DB.queryLatestPoints + pure $ mapMaybe convert lastPoints + else + verifySnapshotPoint env snapshotPoints NoLedger _ -> do -- Brings the 5 latest. lastPoints <- DB.runDbDirectSilent (envDbEnv env) DB.queryLatestPoints diff --git a/cardano-db-sync/src/Cardano/DbSync/Sync.hs b/cardano-db-sync/src/Cardano/DbSync/Sync.hs index fca7c8a43..3bc7a6719 100644 --- a/cardano-db-sync/src/Cardano/DbSync/Sync.hs +++ b/cardano-db-sync/src/Cardano/DbSync/Sync.hs @@ -318,7 +318,11 @@ chainSyncClient metricsSetters trce latestPoints currentTip tc = do ClientPipelinedStIdle n CardanoBlock (Point CardanoBlock) (Tip CardanoBlock) IO () go mkPipelineDecision n clientTip serverTip mPoint = case (mPoint, n, runPipelineDecision mkPipelineDecision n clientTip serverTip) of - (Just points, _, _) -> drainThePipe n $ clientPipelinedStIdle clientTip points + (Just points, _, _) -> + -- When re-intersecting after rollback failure, reset clientTip to Origin + -- if falling back to genesis, otherwise keep current clientTip + let newClientTip = if points == [genesisPoint] then Origin else clientTip + in drainThePipe n $ clientPipelinedStIdle newClientTip points (_, _Zero, (Request, mkPipelineDecision')) -> SendMsgRequestNext (pure ()) clientStNext where