Skip to content
Open
Show file tree
Hide file tree
Changes from all commits
Commits
File filter

Filter by extension

Filter by extension

Conversations
Failed to load comments.
Loading
Jump to
Jump to file
Failed to load files.
Loading
Diff view
Diff view
4 changes: 3 additions & 1 deletion cardano-chain-gen/src/Cardano/Mock/ChainSync/Server.hs
Original file line number Diff line number Diff line change
Expand Up @@ -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'
Expand Down
22 changes: 22 additions & 0 deletions cardano-chain-gen/test/Test/Cardano/Db/Mock/Config.hs
Original file line number Diff line number Diff line change
Expand Up @@ -57,6 +57,7 @@ module Test.Cardano.Db.Mock.Config (
withFullConfig,
withFullConfigDropDB,
withFullConfigDropDBLog,
withFullConfigDropDBNoFingerprint,
withFullConfigLog,
withCustomConfigDropDBLog,
withCustomConfig,
Expand Down Expand Up @@ -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 ->
Expand Down
Original file line number Diff line number Diff line change
Expand Up @@ -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)
Expand Down Expand Up @@ -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}
Expand Down Expand Up @@ -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
Expand Down
7 changes: 6 additions & 1 deletion cardano-chain-gen/test/Test/Cardano/Db/Mock/UnifiedApi.hs
Original file line number Diff line number Diff line change
Expand Up @@ -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
Expand Down
Original file line number Diff line number Diff line change
Expand Up @@ -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)
Expand Down
Original file line number Diff line number Diff line change
Expand Up @@ -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)
Expand Down Expand Up @@ -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
Expand Down Expand Up @@ -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"

Expand Down
Original file line number Diff line number Diff line change
Expand Up @@ -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
Expand Down
Original file line number Diff line number Diff line change
Expand Up @@ -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"
Expand Down Expand Up @@ -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
Expand All @@ -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
Expand Down Expand Up @@ -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
Expand Down Expand Up @@ -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
Expand Down Expand Up @@ -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
Expand Down Expand Up @@ -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
Expand Down
Original file line number Diff line number Diff line change
Expand Up @@ -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
Expand Down Expand Up @@ -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 =
Expand Down Expand Up @@ -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
Expand Down
Original file line number Diff line number Diff line change
Expand Up @@ -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
Expand Down
Original file line number Diff line number Diff line change
Expand Up @@ -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
Expand Down Expand Up @@ -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"
Expand Down
Original file line number Diff line number Diff line change
Expand Up @@ -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 $
Expand All @@ -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
Expand Down
Original file line number Diff line number Diff line change
Expand Up @@ -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
Expand Down Expand Up @@ -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"
Loading
Loading