diff --git a/.gitignore b/.gitignore index f8fd82235..dc56fa03c 100644 --- a/.gitignore +++ b/.gitignore @@ -9,4 +9,5 @@ cabal.project.local gen/ /.vscode -cardano-chain-gen/test/testfiles/temp/ \ No newline at end of file +cardano-chain-gen/test/testfiles/temp/ +cardano-chain-gen/bench/benchfiles/temp/ diff --git a/cabal.project b/cabal.project index 8a5adf0ba..819b0495d 100644 --- a/cabal.project +++ b/cabal.project @@ -258,3 +258,11 @@ source-repository-package tag: 297cd9db5074339a2fb2e5ae7d0780debb670c63 --sha256: 1zcwry3y5rmd9lgxy89wsb3k4kpffqji35dc7ghzbz603y1gy24g +source-repository-package + type: git + location: https://github.com/input-output-hk/criterion-2 + --sha256: 189brk8lpmjgsy32yin6ps0v34wvs971bkw92d5w8r4jsi7wwndc + tag: 4a99389084cba4eabd3149f37adee2a394d065a9 + subdir: + . + criterion-measurement diff --git a/cardano-chain-gen/bench/Cardano/Db/Bench.hs b/cardano-chain-gen/bench/Cardano/Db/Bench.hs new file mode 100644 index 000000000..1bed5ecaa --- /dev/null +++ b/cardano-chain-gen/bench/Cardano/Db/Bench.hs @@ -0,0 +1,307 @@ +module Cardano.Db.Bench where + +import Control.DeepSeq +import Control.Monad +import Control.Monad.Class.MonadSTM.Strict +import qualified Data.Text.Encoding as Text +import Data.List.Split +import qualified Data.Map as Map +import Data.Text (Text) + +import Ouroboros.Network.Block (Point (..)) + +import Cardano.Slotting.Slot + +import Cardano.Ledger.Address +import Cardano.Ledger.BaseTypes +import Cardano.Ledger.Credential +import Cardano.Ledger.Mary.Value +import Cardano.Ledger.Shelley.TxBody + +import Cardano.Mock.ChainSync.Server +import Cardano.Mock.Db.Config hiding (withFullConfig) +import qualified Cardano.Mock.Db.Config as Config +import Cardano.Mock.Db.Validate +import Cardano.Mock.Forging.Interpreter +import qualified Cardano.Mock.Forging.Tx.Alonzo as Alonzo +import Cardano.Mock.Forging.Tx.Generic +import Cardano.Mock.Forging.Types + +import Criterion + +benchmark :: IOManager -> [(Text, Text)] -> Benchmark +benchmark iom knownMigrations = + bgroup "bench" + [ bgroup "empty blocks" + [ bnch 3 "10 blocks" $ emptyBlocks 10 + , bnch 3 "50 blocks" $ emptyBlocks 50 + , bnch 3 "100 blocks" $ emptyBlocks 100 + , longBnch "500 blocks" $ emptyBlocks 500 + , longBnch "5000 blocks" $ emptyBlocks 5000 + , longBnch "10000 blocks" $ emptyBlocks 10000 + ] + , bgroup "register addresses 1000 per block" + [ bnch 3 "1 block" $ registerAddressess 1 + , bnch 3 "10 blocks" $ registerAddressess 10 + , bnch 3 "100 blocks" $ registerAddressess 100 + , bnch 3 "200 blocks" $ registerAddressess 200 + ] + , bgroup "create UTxO. 200 per block" + [ bnch 3 "1 block" $ createUTXO 1 + , bnch 3 "10 blocks" $ createUTXO 10 + , longBnch "100 blocks" $ createUTXO 100 + , longBnch "100 blocks" $ createUTXO 1000 + ] + , bgroup "create UTxO. 1000 per block" + [ bnch 3 "1 block" $ createUTXO' 1 + , bnch 3 "10 blocks" $ createUTXO' 10 + , longBnch "100 blocks" $ createUTXO' 100 + , longBnch "1000 blocks" $ createUTXO' 1000 + ] + , bgroup "create multiasssets." + [ bnch 3 "1 block" $ createMaTxOut 1 + , bnch 3 "10 blocks" $ createMaTxOut 10 + , longBnch "100 blocks" $ createMaTxOut 100 + , longBnch "500 blocks" $ createMaTxOut 500 + ] + , bgroup "delegate and send funds" + [ bnch 3 "3 block" $ delegateAndSend 1 + , bnch 3 "30 blocks" $ delegateAndSend 10 + , longBnch "300 blocks" $ delegateAndSend 100 + , longBnch "1200 blocks" $ delegateAndSend 400 + ] + , bgroup "rollback multiassets" + [ bnch 3 "1 block" $ rollbackMaTxOut 1 + , bnch 3 "10 blocks" $ rollbackMaTxOut 10 + , longBnch "100 blocks" $ rollbackMaTxOut 100 + , longBnch "500 blocks" $ rollbackMaTxOut 500 + ] + bgroup "rollback delegate and send funds" + [ bnch 3 "3 blocks" $ rollbackDelegateAndSend 1 + , bnch 3 "30 blocks" $ rollbackDelegateAndSend 10 + , longBnch "300 blocks" $ rollbackDelegateAndSend 100 + , longBnch "1200 blocks" $ rollbackDelegateAndSend 400 + ] + ] + where + _bnch' :: String -> (IOManager -> [(Text, Text)] -> Benchmarkable) -> Benchmark + _bnch' str action = bench str (action iom knownMigrations) + + bnch :: Int -> String -> (IOManager -> [(Text, Text)] -> Benchmarkable) -> Benchmark + bnch n str action = bench str (fixIterations n $ action iom knownMigrations) + + longBnch :: String -> (IOManager -> [(Text, Text)] -> Benchmarkable) -> Benchmark + longBnch str = bnch 1 str + +data BenchEnv = BenchEnv Interpreter (ServerHandle IO CardanoBlock) DBSyncEnv [CardanoBlock] + +instance NFData BenchEnv where + -- We don't really use many feautures of criterion. 'NFData' is not one of them. + rnf _ = () + +defaultConfigDir :: FilePath +defaultConfigDir = "config" + +rootTestDir :: FilePath +rootTestDir = "bench/benchfiles" + +withFullConfig :: FilePath -> FilePath + -> (Interpreter -> ServerHandle IO CardanoBlock -> DBSyncEnv -> IO ()) + -> IOManager -> [(Text, Text)] -> IO () +withFullConfig = Config.withFullConfig rootTestDir + +benchmarkSyncing :: FilePath -> FilePath -> FilePath + -> (Interpreter -> IO [CardanoBlock]) + -> IOManager -> [(Text, Text)] + -> Benchmarkable +benchmarkSyncing rootDir config testLabel mkBlocks iom mig = + perRunEnvWithCleanup createEnv cleanupEnv runBench + where + createEnv :: IO BenchEnv + createEnv = do + (interpreter, mockServer, dbSync) <- mkFullConfig rootDir config testLabel iom mig + -- first block server and then start db-sync during env creation, so that + -- schema migrations doesn't affect benchmarking results.\ + atomically $ blockServing mockServer + startDBSync dbSync + blks <- mkBlocks interpreter + forM_ blks $ atomically . addBlock mockServer + -- This is here to wait for all migration to run before running the benchmark + assertBlocksCount dbSync 2 + pure $ BenchEnv interpreter mockServer dbSync blks + + cleanupEnv (BenchEnv interpreter mockServer dbSync _blks) = do + cleanFullConfig (interpreter, mockServer, dbSync) + + runBench (BenchEnv _interpreter mockServer dbSync blks) = do + -- unblock the server and wait for the blocks in db. + atomically $ unBlockServing mockServer + assertBlockNo dbSync (Just $ length blks - 1) [1,1..] + + +benchmarkRollback :: FilePath -> FilePath -> FilePath + -> (Interpreter -> IO [CardanoBlock]) + -> IOManager -> [(Text, Text)] + -> Benchmarkable +benchmarkRollback rootDir config testLabel mkBlocks iom mig = + perRunEnvWithCleanup createEnv cleanupEnv runBench + where + createEnv :: IO BenchEnv + createEnv = do + (interpreter, mockServer, dbSync) <- mkFullConfig rootDir config testLabel iom mig + startDBSync dbSync + blks <- mkBlocks interpreter + forM_ blks $ atomically . addBlock mockServer + -- Sync all blocks in db-sync + assertBlockNo dbSync (Just $ length blks - 1) [1,1..] + pure $ BenchEnv interpreter mockServer dbSync blks + + cleanupEnv (BenchEnv interpreter mockServer dbSync _blks) = do + cleanFullConfig (interpreter, mockServer, dbSync) + + runBench (BenchEnv _interpreter mockServer dbSync _blks) = do + -- unblock the server and wait for the blocks in db. + atomically $ rollback mockServer (Point Origin) + assertBlockNo dbSync Nothing [1,1..] + + +emptyBlocks :: Int -> IOManager -> [(Text, Text)] -> Benchmarkable +emptyBlocks n = + benchmarkSyncing rootTestDir defaultConfigDir testLabel $ \interpreter -> + replicateM n $ forgeNextFindLeader interpreter [] + where + testLabel = "emptyBlock_" <> show n + +registerAddressess :: Int -> IOManager -> [(Text, Text)] -> Benchmarkable +registerAddressess n = + benchmarkSyncing rootTestDir defaultConfigDir testLabel $ + registerAddressesBlocks n + where + testLabel = "registerAddressess_" <> show n + +registerAddressesBlocks :: Int -> Interpreter -> IO [CardanoBlock] +registerAddressesBlocks n interpreter = do + forM (chunksOf 1000 creds) $ \blockCreds -> do + blockTxs <- withAlonzoLedgerState interpreter $ \_st -> + forM (chunksOf 10 blockCreds) $ \txCreds -> -- 10 per tx + Alonzo.mkDCertTx (fmap (DCertDeleg . RegKey) txCreds) (Wdrl mempty) + forgeNextFindLeader interpreter (TxAlonzo <$> blockTxs) + where + creds = createStakeCredentials (1000 * n) + +createUTXO :: Int -> IOManager -> [(Text, Text)] -> Benchmarkable +createUTXO n = + benchmarkSyncing rootTestDir defaultConfigDir testLabel $ + createUTXOBlocks n + where + testLabel = "createUTXO_" <> show n + +-- 200 txs per block. 1 outputs per tx +createUTXOBlocks :: Int -> Interpreter -> IO [CardanoBlock] +createUTXOBlocks n interpreter = do + addr <- withAlonzoLedgerState interpreter $ resolveAddress (UTxOIndex 0) + -- we use the change output to create the next transaction. + let utxoIndex = UTxOAddress addr + forM (chunksOf 200 addresses) $ \blockAddresses -> do + blockTxs <- withAlonzoLedgerState interpreter $ \st -> + forM blockAddresses $ \sendAddr -> + Alonzo.mkPaymentTx utxoIndex (UTxOAddress sendAddr) 1 0 st + forgeNextFindLeader interpreter (TxAlonzo <$> blockTxs) + where + addresses = fmap (\addr -> Addr Testnet addr StakeRefNull) (createPaymentCredentials (200 * n)) + +createUTXO' :: Int -> IOManager -> [(Text, Text)] -> Benchmarkable +createUTXO' n = + benchmarkSyncing rootTestDir defaultConfigDir testLabel $ + createUTXOBlocks' n + where + testLabel = "createUTXO'_" <> show n + +-- 100 txs per block. 10 outputs per tx +createUTXOBlocks' :: Int -> Interpreter -> IO [CardanoBlock] +createUTXOBlocks' n interpreter = do + addrFrom <- withAlonzoLedgerState interpreter $ resolveAddress (UTxOIndex 0) + -- we use the change output to create the next transaction. + let utxoIndex = UTxOAddress addrFrom + forM (chunksOf 1000 addresses) $ \blockAddresses -> do + blockTxs <- withAlonzoLedgerState interpreter $ \st -> + forM (chunksOf 10 blockAddresses) $ \txAddresses -> + Alonzo.mkPaymentTx' utxoIndex (fmap (\addr -> (UTxOAddress addr, Value 1 mempty)) txAddresses) st + forgeNextFindLeader interpreter (TxAlonzo <$> blockTxs) + where + addresses = fmap (\addr -> Addr Testnet addr StakeRefNull) (createPaymentCredentials (1000 * n)) + +createMaTxOut :: Int -> IOManager -> [(Text, Text)] -> Benchmarkable +createMaTxOut n = + benchmarkSyncing rootTestDir defaultConfigDir testLabel $ + createMaTxOutBlocks n + where + testLabel = "createMaTxOut_" <> show n + +rollbackMaTxOut :: Int -> IOManager -> [(Text, Text)] -> Benchmarkable +rollbackMaTxOut n = + benchmarkRollback rootTestDir defaultConfigDir testLabel $ + createMaTxOutBlocks n + where + testLabel = "rollbackMaTxOut_" <> show n + +createMaTxOutBlocks :: Int -> Interpreter -> IO [CardanoBlock] +createMaTxOutBlocks n interpreter = do + addrFrom <- withAlonzoLedgerState interpreter $ resolveAddress (UTxOIndex 0) + -- we use the change output to create the next transaction. + let utxoIndex = UTxOAddress addrFrom + forM (zip [1..n] $ chunksOf 1000 addresses) $ \(_blockId, blockAddresses) -> do + blockTxs <- withAlonzoLedgerState interpreter $ \st -> + forM (zip [1..100] $ chunksOf 10 blockAddresses) $ \(txId, txAddresses) -> + let maMap = Map.fromList $ flip fmap [0..9] $ \maIndex -> + let assets = Map.fromList $ flip fmap [0..9] $ \assetIx -> + (AssetName $ Text.encodeUtf8 $ textShow (100 * assetIx + maIndex), 1) + in (PolicyID (mkDummyScriptHash $ 10 * maIndex + txId `mod` 10), assets) + in Alonzo.mkPaymentTx' utxoIndex (fmap (\addr -> (UTxOAddress addr, Value 1 maMap)) txAddresses) st + forgeNextFindLeader interpreter (TxAlonzo <$> blockTxs) + where + addresses = fmap (\addr -> Addr Testnet addr StakeRefNull) (createPaymentCredentials (1000 * n)) + +delegateAndSend :: Int -> IOManager -> [(Text, Text)] -> Benchmarkable +delegateAndSend n = + benchmarkSyncing rootTestDir defaultConfigDir testLabel $ + delegateAndSendBlocks n + where + testLabel = "delegateAndSend_" <> show n + +rollbackDelegateAndSend :: Int -> IOManager -> [(Text, Text)] -> Benchmarkable +rollbackDelegateAndSend n = + benchmarkRollback rootTestDir defaultConfigDir testLabel $ + delegateAndSendBlocks n + where + testLabel = "rollbackDelegateAndSend_" <> show n + +delegateAndSendBlocks :: Int -> Interpreter -> IO [CardanoBlock] +delegateAndSendBlocks n interpreter = do + addrFrom <- withAlonzoLedgerState interpreter $ resolveAddress (UTxOIndex 0) + registerBlocks <- forM (chunksOf 1000 creds) $ \blockCreds -> do + blockTxs <- withAlonzoLedgerState interpreter $ \_st -> + forM (chunksOf 10 blockCreds) $ \txCreds -> -- 10 per tx + Alonzo.mkDCertTx (fmap (DCertDeleg . RegKey) txCreds) (Wdrl mempty) + forgeNextFindLeader interpreter (TxAlonzo <$> blockTxs) + + delegateBlocks <- forM (chunksOf 1000 creds) $ \blockCreds -> do + blockTxs <- withAlonzoLedgerState interpreter $ \st -> + forM (chunksOf 10 blockCreds) $ \txCreds -> --do -- 10 per tx + Alonzo.mkDCertTx + (fmap (\ (poolIx, cred) -> DCertDeleg $ Delegate $ Delegation cred (resolvePool (PoolIndex poolIx) st)) + (zip (cycle [0,1,2]) txCreds)) + (Wdrl mempty) + forgeNextFindLeader interpreter (TxAlonzo <$> blockTxs) + + let utxoIndex = UTxOAddress addrFrom + sendBlocks <- forM (chunksOf 1000 addresses) $ \blockAddresses -> do + blockTxs <- withAlonzoLedgerState interpreter $ \st -> + forM (chunksOf 10 blockAddresses) $ \txAddresses -> + Alonzo.mkPaymentTx' utxoIndex (fmap (\addr -> (UTxOAddress addr, Value 1 mempty)) txAddresses) st + forgeNextFindLeader interpreter (TxAlonzo <$> blockTxs) + pure $ registerBlocks <> delegateBlocks <> sendBlocks + where + creds = createStakeCredentials (1000 * n) + pcreds = createPaymentCredentials (1000 * n) + addresses = fmap (\(pcred, cred) -> Addr Testnet pcred (StakeRefBase cred)) (zip pcreds creds) diff --git a/cardano-chain-gen/bench/Main.hs b/cardano-chain-gen/bench/Main.hs new file mode 100644 index 000000000..7fe07e9ea --- /dev/null +++ b/cardano-chain-gen/bench/Main.hs @@ -0,0 +1,48 @@ +import Cardano.Prelude (Text) + +import Prelude + +import Control.Monad (when, (>=>)) +import Data.Maybe (isNothing) + +import System.Directory (getCurrentDirectory) +import System.Environment (lookupEnv, setEnv) +import System.FilePath (()) + +import MigrationValidations (KnownMigration (..), knownMigrations) + +import Cardano.Mock.ChainSync.Server + +import Criterion.Main + +import qualified Cardano.Db.Bench as Bench + +main :: IO () +main = do + -- If the env is not set, set it to default. + mPgPassFile <- lookupEnv "PGPASSFILE" + when (isNothing mPgPassFile) $ do + currentDir <- getCurrentDirectory + setEnv "PGPASSFILE" (currentDir "bench/benchfiles/pgpass-bench") + withIOManager $ + benchmarks >=> defaultMain + where +-- config = defaultConfig +-- { resamples = 1 +-- , reportFile = Just "report.html" +-- , csvFile = Just "report.csv" +-- , jsonFile = Just "reprt.json" +-- , junitFile = Just "report.junit" +-- } + +benchmarks :: IOManager -> IO [Benchmark] +benchmarks iom = do + pure $ + [ bgroup + "cardano-chain" + [ Bench.benchmark iom knownMigrationsPlain + ] + ] + where + knownMigrationsPlain :: [(Text, Text)] + knownMigrationsPlain = (\x -> (hash x, filepath x)) <$> knownMigrations diff --git a/cardano-chain-gen/bench/benchfiles/config/genesis.alonzo.json b/cardano-chain-gen/bench/benchfiles/config/genesis.alonzo.json new file mode 100644 index 000000000..bcc2d3176 --- /dev/null +++ b/cardano-chain-gen/bench/benchfiles/config/genesis.alonzo.json @@ -0,0 +1,188 @@ +{ + "collateralPercentage": 1, + "maxBlockExUnits": { + "exUnitsMem": 500000000000, + "exUnitsSteps": 500000000000 + }, + "maxCollateralInputs": 5, + "maxValueSize": 4000, + "costModels": { + "PlutusV1": { + "sha2_256-memory-arguments": 4, + "equalsString-cpu-arguments-constant": 1000, + "cekDelayCost-exBudgetMemory": 100, + "lessThanEqualsByteString-cpu-arguments-intercept": 103599, + "divideInteger-memory-arguments-minimum": 1, + "appendByteString-cpu-arguments-slope": 621, + "blake2b-cpu-arguments-slope": 29175, + "iData-cpu-arguments": 150000, + "encodeUtf8-cpu-arguments-slope": 1000, + "unBData-cpu-arguments": 150000, + "multiplyInteger-cpu-arguments-intercept": 61516, + "cekConstCost-exBudgetMemory": 100, + "nullList-cpu-arguments": 150000, + "equalsString-cpu-arguments-intercept": 150000, + "trace-cpu-arguments": 150000, + "mkNilData-memory-arguments": 32, + "lengthOfByteString-cpu-arguments": 150000, + "cekBuiltinCost-exBudgetCPU": 29773, + "bData-cpu-arguments": 150000, + "subtractInteger-cpu-arguments-slope": 0, + "unIData-cpu-arguments": 150000, + "consByteString-memory-arguments-intercept": 0, + "divideInteger-memory-arguments-slope": 1, + "divideInteger-cpu-arguments-model-arguments-slope": 118, + "listData-cpu-arguments": 150000, + "headList-cpu-arguments": 150000, + "chooseData-memory-arguments": 32, + "equalsInteger-cpu-arguments-intercept": 136542, + "sha3_256-cpu-arguments-slope": 82363, + "sliceByteString-cpu-arguments-slope": 5000, + "unMapData-cpu-arguments": 150000, + "lessThanInteger-cpu-arguments-intercept": 179690, + "mkCons-cpu-arguments": 150000, + "appendString-memory-arguments-intercept": 0, + "modInteger-cpu-arguments-model-arguments-slope": 118, + "ifThenElse-cpu-arguments": 1, + "mkNilPairData-cpu-arguments": 150000, + "lessThanEqualsInteger-cpu-arguments-intercept": 145276, + "addInteger-memory-arguments-slope": 1, + "chooseList-memory-arguments": 32, + "constrData-memory-arguments": 32, + "decodeUtf8-cpu-arguments-intercept": 150000, + "equalsData-memory-arguments": 1, + "subtractInteger-memory-arguments-slope": 1, + "appendByteString-memory-arguments-intercept": 0, + "lengthOfByteString-memory-arguments": 4, + "headList-memory-arguments": 32, + "listData-memory-arguments": 32, + "consByteString-cpu-arguments-intercept": 150000, + "unIData-memory-arguments": 32, + "remainderInteger-memory-arguments-minimum": 1, + "bData-memory-arguments": 32, + "lessThanByteString-cpu-arguments-slope": 248, + "encodeUtf8-memory-arguments-intercept": 0, + "cekStartupCost-exBudgetCPU": 100, + "multiplyInteger-memory-arguments-intercept": 0, + "unListData-memory-arguments": 32, + "remainderInteger-cpu-arguments-model-arguments-slope": 118, + "cekVarCost-exBudgetCPU": 29773, + "remainderInteger-memory-arguments-slope": 1, + "cekForceCost-exBudgetCPU": 29773, + "sha2_256-cpu-arguments-slope": 29175, + "equalsInteger-memory-arguments": 1, + "indexByteString-memory-arguments": 1, + "addInteger-memory-arguments-intercept": 1, + "chooseUnit-cpu-arguments": 150000, + "sndPair-cpu-arguments": 150000, + "cekLamCost-exBudgetCPU": 29773, + "fstPair-cpu-arguments": 150000, + "quotientInteger-memory-arguments-minimum": 1, + "decodeUtf8-cpu-arguments-slope": 1000, + "lessThanInteger-memory-arguments": 1, + "lessThanEqualsInteger-cpu-arguments-slope": 1366, + "fstPair-memory-arguments": 32, + "modInteger-memory-arguments-intercept": 0, + "unConstrData-cpu-arguments": 150000, + "lessThanEqualsInteger-memory-arguments": 1, + "chooseUnit-memory-arguments": 32, + "sndPair-memory-arguments": 32, + "addInteger-cpu-arguments-intercept": 197209, + "decodeUtf8-memory-arguments-slope": 8, + "equalsData-cpu-arguments-intercept": 150000, + "mapData-cpu-arguments": 150000, + "mkPairData-cpu-arguments": 150000, + "quotientInteger-cpu-arguments-constant": 148000, + "consByteString-memory-arguments-slope": 1, + "cekVarCost-exBudgetMemory": 100, + "indexByteString-cpu-arguments": 150000, + "unListData-cpu-arguments": 150000, + "equalsInteger-cpu-arguments-slope": 1326, + "cekStartupCost-exBudgetMemory": 100, + "subtractInteger-cpu-arguments-intercept": 197209, + "divideInteger-cpu-arguments-model-arguments-intercept": 425507, + "divideInteger-memory-arguments-intercept": 0, + "cekForceCost-exBudgetMemory": 100, + "blake2b-cpu-arguments-intercept": 2477736, + "remainderInteger-cpu-arguments-constant": 148000, + "tailList-cpu-arguments": 150000, + "encodeUtf8-cpu-arguments-intercept": 150000, + "equalsString-cpu-arguments-slope": 1000, + "lessThanByteString-memory-arguments": 1, + "multiplyInteger-cpu-arguments-slope": 11218, + "appendByteString-cpu-arguments-intercept": 396231, + "lessThanEqualsByteString-cpu-arguments-slope": 248, + "modInteger-memory-arguments-slope": 1, + "addInteger-cpu-arguments-slope": 0, + "equalsData-cpu-arguments-slope": 10000, + "decodeUtf8-memory-arguments-intercept": 0, + "chooseList-cpu-arguments": 150000, + "constrData-cpu-arguments": 150000, + "equalsByteString-memory-arguments": 1, + "cekApplyCost-exBudgetCPU": 29773, + "quotientInteger-memory-arguments-slope": 1, + "verifySignature-cpu-arguments-intercept": 3345831, + "unMapData-memory-arguments": 32, + "mkCons-memory-arguments": 32, + "sliceByteString-memory-arguments-slope": 1, + "sha3_256-memory-arguments": 4, + "ifThenElse-memory-arguments": 1, + "mkNilPairData-memory-arguments": 32, + "equalsByteString-cpu-arguments-slope": 247, + "appendString-cpu-arguments-intercept": 150000, + "quotientInteger-cpu-arguments-model-arguments-slope": 118, + "cekApplyCost-exBudgetMemory": 100, + "equalsString-memory-arguments": 1, + "multiplyInteger-memory-arguments-slope": 1, + "cekBuiltinCost-exBudgetMemory": 100, + "remainderInteger-memory-arguments-intercept": 0, + "sha2_256-cpu-arguments-intercept": 2477736, + "remainderInteger-cpu-arguments-model-arguments-intercept": 425507, + "lessThanEqualsByteString-memory-arguments": 1, + "tailList-memory-arguments": 32, + "mkNilData-cpu-arguments": 150000, + "chooseData-cpu-arguments": 150000, + "unBData-memory-arguments": 32, + "blake2b-memory-arguments": 4, + "iData-memory-arguments": 32, + "nullList-memory-arguments": 32, + "cekDelayCost-exBudgetCPU": 29773, + "subtractInteger-memory-arguments-intercept": 1, + "lessThanByteString-cpu-arguments-intercept": 103599, + "consByteString-cpu-arguments-slope": 1000, + "appendByteString-memory-arguments-slope": 1, + "trace-memory-arguments": 32, + "divideInteger-cpu-arguments-constant": 148000, + "cekConstCost-exBudgetCPU": 29773, + "encodeUtf8-memory-arguments-slope": 8, + "quotientInteger-cpu-arguments-model-arguments-intercept": 425507, + "mapData-memory-arguments": 32, + "appendString-cpu-arguments-slope": 1000, + "modInteger-cpu-arguments-constant": 148000, + "verifySignature-cpu-arguments-slope": 1, + "unConstrData-memory-arguments": 32, + "quotientInteger-memory-arguments-intercept": 0, + "equalsByteString-cpu-arguments-constant": 150000, + "sliceByteString-memory-arguments-intercept": 0, + "mkPairData-memory-arguments": 32, + "equalsByteString-cpu-arguments-intercept": 112536, + "appendString-memory-arguments-slope": 1, + "lessThanInteger-cpu-arguments-slope": 497, + "modInteger-cpu-arguments-model-arguments-intercept": 425507, + "modInteger-memory-arguments-minimum": 1, + "sha3_256-cpu-arguments-intercept": 0, + "verifySignature-memory-arguments": 1, + "cekLamCost-exBudgetMemory": 100, + "sliceByteString-cpu-arguments-intercept": 150000 + } + }, + "executionPrices": { + "prMem": 0.1, + "prSteps": 0.1 + }, + "lovelacePerUTxOWord": 1, + "maxTxExUnits": { + "exUnitsMem": 500000000000, + "exUnitsSteps": 500000000000 + } +} \ No newline at end of file diff --git a/cardano-chain-gen/bench/benchfiles/config/genesis.byron.json b/cardano-chain-gen/bench/benchfiles/config/genesis.byron.json new file mode 100644 index 000000000..cf088f937 --- /dev/null +++ b/cardano-chain-gen/bench/benchfiles/config/genesis.byron.json @@ -0,0 +1,31 @@ +{ "bootStakeholders": + { "1a3e49767796fd99b057ad54db3310fd640806fcb0927399bbca7b43": 1 } +, "heavyDelegation": + { } +, "startTime": 1637266922 +, "nonAvvmBalances": + { } +, "blockVersionData": + { "scriptVersion": 0 + , "slotDuration": "20000" + , "maxBlockSize": "2000000" + , "maxHeaderSize": "2000000" + , "maxTxSize": "4096" + , "maxProposalSize": "700" + , "mpcThd": "20000000000000" + , "heavyDelThd": "300000000000" + , "updateVoteThd": "1000000000000" + , "updateProposalThd": "100000000000000" + , "updateImplicit": "10000" + , "softforkRule": + { "initThd": "900000000000000" + , "minThd": "600000000000000" + , "thdDecrement": "50000000000000" + } + , "txFeePolicy": + { "summand": "155381000000000" , "multiplier": "43946000000" } + , "unlockStakeEpoch": "18446744073709551615" + } +, "protocolConsts": { "k": 216 , "protocolMagic": 42 } +, "avvmDistr": {} +} diff --git a/cardano-chain-gen/bench/benchfiles/config/genesis.json b/cardano-chain-gen/bench/benchfiles/config/genesis.json new file mode 100644 index 000000000..4a73b7c9e --- /dev/null +++ b/cardano-chain-gen/bench/benchfiles/config/genesis.json @@ -0,0 +1,109 @@ +{ + "maxLovelaceSupply": 60000000, + "securityParam": 216, + "slotsPerKESPeriod": 129600, + "updateQuorum": 5, + "activeSlotsCoeff": 0.2, + "protocolParams": { + "minUTxOValue": 0, + "eMax": 18, + "extraEntropy": { + "tag": "NeutralNonce" + }, + "minFeeB": 0, + "tau": 0.0, + "maxBlockBodySize": 65536, + "maxTxSize": 16384, + "minPoolCost": 0, + "minFeeA": 1, + "nOpt": 3, + "maxBlockHeaderSize": 1100, + "keyDeposit": 0, + "poolDeposit": 0, + "protocolVersion": { + "minor": 0, + "major": 6 + }, + "a0": 0.3, + "rho": 0.0, + "decentralisationParam": 0 + }, + "networkMagic": 42, + "initialFunds": { + "00ae51de0c8e130f9ec51755f163258fe661e95e2648080f8e5c9583571b9b85d81adacab01fd7ee2f6e1619a0ca67b619a849bbb069ef0e42": 900000, + "005fdb717fabe97938da294e151d96b4af375bea38d176021edb9975b8921c25093b263793a1baf36166b819543f5822c62f725715a4136b39": 900000, + "60b13227c296440956c2a014359d6d83e9a854deec46471b57bd2ed2b6": 900000, + "60959e277d0f9213ac343e7841dc247089879585c9b6f49e8e0a0e8ce7": 900000, + "607903a7c2c29c52a963f40cf58357cb5bae37e2d57e2463b51e747efb": 900000, + "00c34b6acfb276a6ec529b3ab56d56988dcd8968647ceeebc28be28751ed15a48df4d479feca6e418ad433041bce1e94cc58d0e104455189bf": 900000, + "005fdb717fabe97938da294e151d96b4af375bea38d176021ed1111111921c25093b263793a1baf36166b819543f5822c62f72571111111111": 900000, + "005fdb717fabe97938da294e151d96b4af375bea38d176021ed222222295be61304693df94ba89ff989e6542f174bb10d5ff49e8e8b1292519": 900000, + "005fdb717fabe97938da294e151d96b4af375bea38d176021ed3333333921c25093b263793a1baf36166b819543f5822c62f72573333333333": 900000, + "005fdb717fabe97938da294e151d96b4af375bea38d176021ed1231231b09771da66c23a23450a53420f25b609cfa3b776068da27bee2371e1": 900000 + }, + "networkId": "Testnet", + "maxKESEvolutions": 60, + "genDelegs": { }, + "slotLength": 1, + "systemStart": "2021-11-18T20:22:02Z", + "epochLength": 43200, + "staking": { + "pools": { + "9f1b441b9b781b3c3abb43b25679dc17dbaaf116dddca1ad09dc1de0": { + "publicKey": "9f1b441b9b781b3c3abb43b25679dc17dbaaf116dddca1ad09dc1de0", + "cost": 5, + "metadata": null, + "owners": [], + "vrf": "a78358019b160775d7b04f7c5e06462e1469823cead9b005c941ecefcc386c51", + "pledge": 0, + "margin": 0.01, + "rewardAccount": { + "network": "Testnet", + "credential": { + "key hash": "addfa484e8095ff53f45b25cf337923cf79abe6ec192fdf288d621f9" + } + }, + "relays": [] + }, + "5af582399de8c226391bfd21424f34d0b053419c4d93975802b7d107": { + "publicKey": "5af582399de8c226391bfd21424f34d0b053419c4d93975802b7d107", + "cost": 5, + "metadata": null, + "owners": ["95be61304693df94ba89ff989e6542f174bb10d5ff49e8e8b1292519"], + "vrf": "71833bb9a56532e952bdb30f5f2773ec375d0e02e81a5374246485979012b02a", + "pledge": 0, + "margin": 0.01, + "rewardAccount": { + "network": "Testnet", + "credential": { + "key hash": "95be61304693df94ba89ff989e6542f174bb10d5ff49e8e8b1292519" + } + }, + "relays": [] + }, + "58eef2925db2789f76ea057c51069e52c5e0a44550f853c6cdf620f8": { + "publicKey": "58eef2925db2789f76ea057c51069e52c5e0a44550f853c6cdf620f8", + "cost": 100, + "metadata": null, + "owners": ["921c25093b263793a1baf36166b819543f5822c62f72573333333333"], + "vrf": "8ce25eb830d7f4f7b79e65de7392dab4a156e0298446df022b6175fcaf7aba27", + "pledge": 0, + "margin": 0.01, + "rewardAccount": { + "network": "Testnet", + "credential": { + "key hash": "b09771da66c23a23450a53420f25b609cfa3b776068da27bee2371e1" + } + }, + "relays": [] + } + }, + "stake": { + "921c25093b263793a1baf36166b819543f5822c62f725715a4136b39": "58eef2925db2789f76ea057c51069e52c5e0a44550f853c6cdf620f8", + "ed15a48df4d479feca6e418ad433041bce1e94cc58d0e104455189bf": "5af582399de8c226391bfd21424f34d0b053419c4d93975802b7d107", + "1b9b85d81adacab01fd7ee2f6e1619a0ca67b619a849bbb069ef0e42": "9f1b441b9b781b3c3abb43b25679dc17dbaaf116dddca1ad09dc1de0", + "b09771da66c23a23450a53420f25b609cfa3b776068da27bee2371e1": "58eef2925db2789f76ea057c51069e52c5e0a44550f853c6cdf620f8", + "95be61304693df94ba89ff989e6542f174bb10d5ff49e8e8b1292519": "9f1b441b9b781b3c3abb43b25679dc17dbaaf116dddca1ad09dc1de0" + } + } +} \ No newline at end of file diff --git a/cardano-chain-gen/bench/benchfiles/config/genesis.spec.json b/cardano-chain-gen/bench/benchfiles/config/genesis.spec.json new file mode 100644 index 000000000..b43b36f56 --- /dev/null +++ b/cardano-chain-gen/bench/benchfiles/config/genesis.spec.json @@ -0,0 +1,43 @@ +{ + "maxLovelaceSupply": 0, + "securityParam": 2160, + "slotsPerKESPeriod": 129600, + "updateQuorum": 5, + "activeSlotsCoeff": 5.0e-2, + "protocolParams": { + "minUTxOValue": 0, + "eMax": 18, + "extraEntropy": { + "tag": "NeutralNonce" + }, + "minFeeB": 0, + "tau": 0.0, + "maxBlockBodySize": 65536, + "maxTxSize": 16384, + "minPoolCost": 0, + "minFeeA": 1, + "nOpt": 100, + "maxBlockHeaderSize": 1100, + "keyDeposit": 0, + "poolDeposit": 0, + "protocolVersion": { + "minor": 0, + "major": 0 + }, + "a0": 0.0, + "rho": 0.0, + "decentralisationParam": 1.0 + }, + "networkMagic": 42, + "initialFunds": {}, + "networkId": "Testnet", + "maxKESEvolutions": 60, + "genDelegs": {}, + "slotLength": 1, + "systemStart": "1970-01-01T00:00:00Z", + "epochLength": 432000, + "staking": { + "pools": {}, + "stake": {} + } +} \ No newline at end of file diff --git a/cardano-chain-gen/bench/benchfiles/config/pools/bulk1.creds b/cardano-chain-gen/bench/benchfiles/config/pools/bulk1.creds new file mode 100644 index 000000000..f0216586b --- /dev/null +++ b/cardano-chain-gen/bench/benchfiles/config/pools/bulk1.creds @@ -0,0 +1 @@ +[[{"cborHex":"8284582091bb7c5b3b409250d63addeaa4f41123c78b703d2612516a3c059f7c2b1e15310000584071ce22482933f85ffddf9cb90778cb0248ebe441b2697d413f9225b01ce786e2a120c227ec96ca8d713157758cf0ea45cc7723d2d9f3f9adad219500b3c6c80e582057ed87e13cbdc2fec8a4ebc6242b76d6c71fa483d3813799a2cb3eb710d1f577","description":"","type":"NodeOperationalCertificate"},{"cborHex":"58403467216a6c6555397c57c79830c9723ddc8668fc9c44c50386193a2ea559887bf8f07e0ad5c29d6080333329fa971867061ffeba0c30f2672fe5809f461b6ecb","description":"VRF Signing Key","type":"VrfSigningKey_PraosVRF"},{"cborHex":"590260d4ea8d759ab61e5dce8b6dfea931cd9e3918ea61d2870152a6146553c323bb7de6713109f8b9ac327796747cc3c85a48678d89cb3f09901b1c57dd2bd1dbc8a8e0f5fd64ce2c5c994e3382320a97ee17341bba737c92bfff4f1e213b5f606f32f91989d2a1b255cb8620abb8667ef3831eb752953052925412aea10b5a2b8649c3aadb079a19dee0387404d161804028f42984c44d6c90ce6366535acf6d712c973068222b6bd646cf037fa0b2aec7ab924a0a6668aebfb53282f6dd1baedd349909d3150dfd06068bd35efcd4db9cca6d9f43ec25864fbc2ee781ac7f9f0bd566544eb374e4663fbe18b513ac13a15c0c2b9dd5607d43c09afbf66ca70651cfc980562e4d69bb7d986f8203cd6c723463b0603e45a3be8ec288b40435d6c4c763122657892f5a558d7a1b52f435b2ae0727d3ef8ae37dee24cc1091002d33b2c9a46ffad59ead9c39e285a65b4911e7579b67550426765eff92d0bb47dd66c452df274d42aacb03ed094b698e2e5d2e188dbed041ae7bf2ee57d3fe7934d038c3a6920347d646eca70d6f403f2b5db5a37ecb1d39e593c1ed19838e2b6dc26228f03bc56f73495e17bc4b78b0ea16f7ef6eaef6ba11dd63d0807720cafd80c978b76c42b86bffc4b32710cba203656afb69fb266934869d2be758f33787f2365f5d65fe19a6a9c546c165cff0ff805fef2281b0b24706be9750c0401467aab795dfc931f3d8e943b7fe877c09816100a4bb1667cfe9753d9cf2477275e4eaef45aee37fa658cab049f8645b32447a0358df23f82f96f624bb0432486b9e755e179faef04387cb15210a2d17d147cbd693a3d56e1b899e3a66bd4d3dc1d4634d","description":"KES Signing Key","type":"KesSigningKey_ed25519_kes_2^6"}],[{"cborHex":"82845820970179a0f36e39aa8bb4095dc4fb219e8382d0ba20ec9b235c458e636d1e596f0000584098aad60b0bfbfda4981ba5f92b07a6b09990e7364191bf6d34558f15f39b51a04a07c852c4255a484353c5a0f325e79c448099fb3d859c12216029bd97f6090c5820d478654ee2c301f78446db60537377f69875ffcba2781a81c0e2bf3c77209410","description":"","type":"NodeOperationalCertificate"},{"cborHex":"58409da4aabcc214be4a6f7dd3efe77b1809c969edf867f3e592b6a84fd3ce2f33134f50bf8a1710b0854ba79a9a7e90c5b6a3082d4608d057e5ab432c933f293767","description":"VRF Signing Key","type":"VrfSigningKey_PraosVRF"},{"cborHex":"590260a65014be8d192af8cd1be12ed2e3aff1744f92bfea2406948344f4a6f07f5d92cfc2561ac2d8c8a52e3001c6b4d52c04dcedacc0bbf3e48a43dd230c5a6cbc2803922803a9c2245f0634e96d50b395644609794811b7d07f69fb8642af58a3fd51566a15976f198dd61ac47812d021c298038cca5af7f69d9be3b280c4d50e2f75c21a414cbecaf4ed3229563ca26934906df54d7e10a5d7e579cb34ce6d1932ac015fbd8c34610d7b63e42ac208fe5cee7c78938a61c57d7f5c917d70dfd7dfc456ffcd745b64d3aa282368e71dd22f2631eec3df03f6c482724936a3b687dc6c9f4f332cf1e185eceef8d8de538948aec9d0e1dcb9cc252db3eb722af488a3adcef9ecb560c737cfe736d5d89ea2cd0e38d5ddffb5a5f8645ce9acc1ece25ba1cac3c1e0b43d22d4479d4daa703b0cc95ec6954d90c7a5d4feae748417c01db58f6dc1f0e256bf0e886ec1268d7bd3ef603c999cdc3e431a3d823d2ae70353504baff71b1e308f410f3c6eea3f4fc3390771cca3625bde1afe4b1bce88c60e3472719fe716a5fe34e6adc94c9407c31e3837df08c2206e8f6462b7889c00c5a1b2e129abdc312131b2591affcce31ef301f136cc91a2453d11fe0bd03885284d8622c3b48fc1209fd1f802caa1028f8efd72f7b180eae644eb0134429ddd7f6035c8b1d696e33deff624faceec6fe1092f837ddb96ba5e5cf9ea145ec1d56527945ef3e0bb80245643dc1766bc0fcce58dcfdd718c3b84334def83d41f5ed693dfab9ce3f9ac2509929f4beef897dee36940c9f8a26ce577707d4a3125c08c6807a00f88d040da929cefb6f6b76494358e07f2e278bb5e7c6ee8a83d997205","description":"KES Signing Key","type":"KesSigningKey_ed25519_kes_2^6"}],[{"cborHex":"82845820112b314dfe4d619bb215c52c4973b51ac269f161370ea57aed3f334811f2923300005840c1715a7c12b52bca14e33d8b8d23e2c9b139e2be0beded4426bc401d3f8f16a5a6660f78f192329de7566c3b2d1fe5e9a2bb5476573689a03660a18b7f20850258200ba394a87622c06c4d67af4e3fa2314824c5d8db428f8200c6eb49033c7e27ec","description":"","type":"NodeOperationalCertificate"},{"cborHex":"58400def24a9256e667363b8a9529d6d8d4893c932a40c02eecd2777a55940254fffab6800ebfb93be0b69dbe2f9ef6dfe39fc0117304c6370485e48b11dc709d59c","description":"VRF Signing Key","type":"VrfSigningKey_PraosVRF"},{"cborHex":"5902605f91217f9ae5ea1ce6dd6b42eafdc5e95c4361e98be395dbf9fc87285eaf6171fd737c7d240941941555484ffdb6f01704a938e58a65ec522a9041df131ebb69fd876eaa1c3621a549c3c5e22eef483e267c2282d02f5a1a60d00786e6951f4ac4c9a8536a8333f02d5ccef2b3093851d10b903694ebc5f6b97039e0a5a48e385838b6db8143362c324e90ffdad680e6c18c7280495c2d4fc28600f93e48091eb0d92aed0ec63312a03d9d89d44ac5b71aa1c1ea289b31ef88a0ca7c0508e944af118730f5443ac68fdc227620234f663c8dfa75796935a14955fbb9f1f216984504b3fc391d6ca2275a4f202029981c4ca5d06cff3dec78c2b28aee2dd4594e5ef286705932e989e619030f5c54a47bf767b883b19eca6d0663008385c807a2da97e2a0d99810ade35e71254eb667cac8261f2990a903ef658942c19ef5109fe33539224b5fb98281c4f90757b7fc0dc3d7239f77b4d1905bed3083773daebfbe15e791b33a8d051325af9dbfe2b1451b7fddc8ae5b7454ba68a219d9b186686a02c57bccae68bc9bdf3c05a9008cf78adc0e5e464537769646b8cc0f6fa71b555d7426aa15f06635fbbdf48c2d3eba56f23ad26799cb5253b456e2b30eb7013775390278c761d35ddd129b0a07b686dad1ab09cd9416dcd7e476648d9d2e6dc7addc8a1b842b7c3a59bdbd803bec78fcb058c64251886ff7a3106387150c651edba78d20f890d2c3d208bc37eb2d449487d6b11160913af836ff4877153893179e739c3e483c75e7b26e8c06e35ed50d3e805879fdd8bb6281581fecee6b30a1343b0dd696103072f2afc35c90677706231c8daa754c401b49e47719cc219d","description":"KES Signing Key","type":"KesSigningKey_ed25519_kes_2^6"}]] \ No newline at end of file diff --git a/cardano-chain-gen/bench/benchfiles/config/pools/bulk1.creds.0cert b/cardano-chain-gen/bench/benchfiles/config/pools/bulk1.creds.0cert new file mode 100644 index 000000000..dce469c3e --- /dev/null +++ b/cardano-chain-gen/bench/benchfiles/config/pools/bulk1.creds.0cert @@ -0,0 +1,5 @@ +{ + "type": "NodeOperationalCertificate", + "description": "", + "cborHex": "8284582091bb7c5b3b409250d63addeaa4f41123c78b703d2612516a3c059f7c2b1e15310000584071ce22482933f85ffddf9cb90778cb0248ebe441b2697d413f9225b01ce786e2a120c227ec96ca8d713157758cf0ea45cc7723d2d9f3f9adad219500b3c6c80e582057ed87e13cbdc2fec8a4ebc6242b76d6c71fa483d3813799a2cb3eb710d1f577" +} diff --git a/cardano-chain-gen/bench/benchfiles/config/pools/bulk1.creds.0kes b/cardano-chain-gen/bench/benchfiles/config/pools/bulk1.creds.0kes new file mode 100644 index 000000000..b2796a623 --- /dev/null +++ b/cardano-chain-gen/bench/benchfiles/config/pools/bulk1.creds.0kes @@ -0,0 +1,5 @@ +{ + "type": "KesSigningKey_ed25519_kes_2^6", + "description": "KES Signing Key", + "cborHex": "590260d4ea8d759ab61e5dce8b6dfea931cd9e3918ea61d2870152a6146553c323bb7de6713109f8b9ac327796747cc3c85a48678d89cb3f09901b1c57dd2bd1dbc8a8e0f5fd64ce2c5c994e3382320a97ee17341bba737c92bfff4f1e213b5f606f32f91989d2a1b255cb8620abb8667ef3831eb752953052925412aea10b5a2b8649c3aadb079a19dee0387404d161804028f42984c44d6c90ce6366535acf6d712c973068222b6bd646cf037fa0b2aec7ab924a0a6668aebfb53282f6dd1baedd349909d3150dfd06068bd35efcd4db9cca6d9f43ec25864fbc2ee781ac7f9f0bd566544eb374e4663fbe18b513ac13a15c0c2b9dd5607d43c09afbf66ca70651cfc980562e4d69bb7d986f8203cd6c723463b0603e45a3be8ec288b40435d6c4c763122657892f5a558d7a1b52f435b2ae0727d3ef8ae37dee24cc1091002d33b2c9a46ffad59ead9c39e285a65b4911e7579b67550426765eff92d0bb47dd66c452df274d42aacb03ed094b698e2e5d2e188dbed041ae7bf2ee57d3fe7934d038c3a6920347d646eca70d6f403f2b5db5a37ecb1d39e593c1ed19838e2b6dc26228f03bc56f73495e17bc4b78b0ea16f7ef6eaef6ba11dd63d0807720cafd80c978b76c42b86bffc4b32710cba203656afb69fb266934869d2be758f33787f2365f5d65fe19a6a9c546c165cff0ff805fef2281b0b24706be9750c0401467aab795dfc931f3d8e943b7fe877c09816100a4bb1667cfe9753d9cf2477275e4eaef45aee37fa658cab049f8645b32447a0358df23f82f96f624bb0432486b9e755e179faef04387cb15210a2d17d147cbd693a3d56e1b899e3a66bd4d3dc1d4634d" +} diff --git a/cardano-chain-gen/bench/benchfiles/config/pools/bulk1.creds.1cert b/cardano-chain-gen/bench/benchfiles/config/pools/bulk1.creds.1cert new file mode 100644 index 000000000..e6e85ee5d --- /dev/null +++ b/cardano-chain-gen/bench/benchfiles/config/pools/bulk1.creds.1cert @@ -0,0 +1,5 @@ +{ + "type": "NodeOperationalCertificate", + "description": "", + "cborHex": "82845820970179a0f36e39aa8bb4095dc4fb219e8382d0ba20ec9b235c458e636d1e596f0000584098aad60b0bfbfda4981ba5f92b07a6b09990e7364191bf6d34558f15f39b51a04a07c852c4255a484353c5a0f325e79c448099fb3d859c12216029bd97f6090c5820d478654ee2c301f78446db60537377f69875ffcba2781a81c0e2bf3c77209410" +} diff --git a/cardano-chain-gen/bench/benchfiles/config/pools/bulk1.creds.1kes b/cardano-chain-gen/bench/benchfiles/config/pools/bulk1.creds.1kes new file mode 100644 index 000000000..110e71607 --- /dev/null +++ b/cardano-chain-gen/bench/benchfiles/config/pools/bulk1.creds.1kes @@ -0,0 +1,5 @@ +{ + "type": "KesSigningKey_ed25519_kes_2^6", + "description": "KES Signing Key", + "cborHex": "590260a65014be8d192af8cd1be12ed2e3aff1744f92bfea2406948344f4a6f07f5d92cfc2561ac2d8c8a52e3001c6b4d52c04dcedacc0bbf3e48a43dd230c5a6cbc2803922803a9c2245f0634e96d50b395644609794811b7d07f69fb8642af58a3fd51566a15976f198dd61ac47812d021c298038cca5af7f69d9be3b280c4d50e2f75c21a414cbecaf4ed3229563ca26934906df54d7e10a5d7e579cb34ce6d1932ac015fbd8c34610d7b63e42ac208fe5cee7c78938a61c57d7f5c917d70dfd7dfc456ffcd745b64d3aa282368e71dd22f2631eec3df03f6c482724936a3b687dc6c9f4f332cf1e185eceef8d8de538948aec9d0e1dcb9cc252db3eb722af488a3adcef9ecb560c737cfe736d5d89ea2cd0e38d5ddffb5a5f8645ce9acc1ece25ba1cac3c1e0b43d22d4479d4daa703b0cc95ec6954d90c7a5d4feae748417c01db58f6dc1f0e256bf0e886ec1268d7bd3ef603c999cdc3e431a3d823d2ae70353504baff71b1e308f410f3c6eea3f4fc3390771cca3625bde1afe4b1bce88c60e3472719fe716a5fe34e6adc94c9407c31e3837df08c2206e8f6462b7889c00c5a1b2e129abdc312131b2591affcce31ef301f136cc91a2453d11fe0bd03885284d8622c3b48fc1209fd1f802caa1028f8efd72f7b180eae644eb0134429ddd7f6035c8b1d696e33deff624faceec6fe1092f837ddb96ba5e5cf9ea145ec1d56527945ef3e0bb80245643dc1766bc0fcce58dcfdd718c3b84334def83d41f5ed693dfab9ce3f9ac2509929f4beef897dee36940c9f8a26ce577707d4a3125c08c6807a00f88d040da929cefb6f6b76494358e07f2e278bb5e7c6ee8a83d997205" +} diff --git a/cardano-chain-gen/bench/benchfiles/config/pools/bulk1.creds.2cert b/cardano-chain-gen/bench/benchfiles/config/pools/bulk1.creds.2cert new file mode 100644 index 000000000..dd1066050 --- /dev/null +++ b/cardano-chain-gen/bench/benchfiles/config/pools/bulk1.creds.2cert @@ -0,0 +1,5 @@ +{ + "type": "NodeOperationalCertificate", + "description": "", + "cborHex": "82845820112b314dfe4d619bb215c52c4973b51ac269f161370ea57aed3f334811f2923300005840c1715a7c12b52bca14e33d8b8d23e2c9b139e2be0beded4426bc401d3f8f16a5a6660f78f192329de7566c3b2d1fe5e9a2bb5476573689a03660a18b7f20850258200ba394a87622c06c4d67af4e3fa2314824c5d8db428f8200c6eb49033c7e27ec" +} diff --git a/cardano-chain-gen/bench/benchfiles/config/pools/bulk1.creds.2kes b/cardano-chain-gen/bench/benchfiles/config/pools/bulk1.creds.2kes new file mode 100644 index 000000000..154783577 --- /dev/null +++ b/cardano-chain-gen/bench/benchfiles/config/pools/bulk1.creds.2kes @@ -0,0 +1,5 @@ +{ + "type": "KesSigningKey_ed25519_kes_2^6", + "description": "KES Signing Key", + "cborHex": "5902605f91217f9ae5ea1ce6dd6b42eafdc5e95c4361e98be395dbf9fc87285eaf6171fd737c7d240941941555484ffdb6f01704a938e58a65ec522a9041df131ebb69fd876eaa1c3621a549c3c5e22eef483e267c2282d02f5a1a60d00786e6951f4ac4c9a8536a8333f02d5ccef2b3093851d10b903694ebc5f6b97039e0a5a48e385838b6db8143362c324e90ffdad680e6c18c7280495c2d4fc28600f93e48091eb0d92aed0ec63312a03d9d89d44ac5b71aa1c1ea289b31ef88a0ca7c0508e944af118730f5443ac68fdc227620234f663c8dfa75796935a14955fbb9f1f216984504b3fc391d6ca2275a4f202029981c4ca5d06cff3dec78c2b28aee2dd4594e5ef286705932e989e619030f5c54a47bf767b883b19eca6d0663008385c807a2da97e2a0d99810ade35e71254eb667cac8261f2990a903ef658942c19ef5109fe33539224b5fb98281c4f90757b7fc0dc3d7239f77b4d1905bed3083773daebfbe15e791b33a8d051325af9dbfe2b1451b7fddc8ae5b7454ba68a219d9b186686a02c57bccae68bc9bdf3c05a9008cf78adc0e5e464537769646b8cc0f6fa71b555d7426aa15f06635fbbdf48c2d3eba56f23ad26799cb5253b456e2b30eb7013775390278c761d35ddd129b0a07b686dad1ab09cd9416dcd7e476648d9d2e6dc7addc8a1b842b7c3a59bdbd803bec78fcb058c64251886ff7a3106387150c651edba78d20f890d2c3d208bc37eb2d449487d6b11160913af836ff4877153893179e739c3e483c75e7b26e8c06e35ed50d3e805879fdd8bb6281581fecee6b30a1343b0dd696103072f2afc35c90677706231c8daa754c401b49e47719cc219d" +} diff --git a/cardano-chain-gen/bench/benchfiles/config/test-config.json b/cardano-chain-gen/bench/benchfiles/config/test-config.json new file mode 100644 index 000000000..60a3306d4 --- /dev/null +++ b/cardano-chain-gen/bench/benchfiles/config/test-config.json @@ -0,0 +1,108 @@ +{ + "AlonzoGenesisFile": "genesis.alonzo.json", + "AlonzoGenesisHash": "7e94a15f55d1e82d10f09203fa1d40f8eede58fd8066542cf6566008068ed874", + "ApplicationName": "cardano-sl", + "ApplicationVersion": 0, + "ByronGenesisFile": "genesis.byron.json", + "ByronGenesisHash": "462bb9869a5a6e4325cc294ca659d68607e8a6f37b5be96ea663fdedfe2b5949", + "LastKnownBlockVersion-Alt": 0, + "LastKnownBlockVersion-Major": 5, + "LastKnownBlockVersion-Minor": 1, + "MaxKnownMajorProtocolVersion": 5, + "PBftSignatureThreshold": 1.1, + "Protocol": "Cardano", + "RequiresNetworkMagic": "RequiresMagic", + "ShelleyGenesisFile": "genesis.json", + "ShelleyGenesisHash": "733960b0b305cbfedcca13d2fea87b077f17501d257d4d2844d1f1e3d9dea0b7", + "TestAllegraHardForkAtEpoch": 0, + "TestAlonzoHardForkAtEpoch": 0, + "TestEnableDevelopmentHardForkEras": false, + "TestEnableDevelopmentNetworkProtocols": false, + "TestMaryHardForkAtEpoch": 0, + "TestShelleyHardForkAtEpoch": 0, + "TraceAcceptPolicy": true, + "TraceBlockFetchClient": false, + "TraceBlockFetchDecisions": false, + "TraceBlockFetchProtocol": false, + "TraceBlockFetchProtocolSerialised": false, + "TraceBlockFetchServer": false, + "TraceChainDb": true, + "TraceChainSyncBlockServer": false, + "TraceChainSyncClient": false, + "TraceChainSyncHeaderServer": false, + "TraceChainSyncProtocol": false, + "TraceConnectionManager": true, + "TraceDNSResolver": true, + "TraceDNSSubscription": true, + "TraceDiffusionInitialization": true, + "TraceErrorPolicy": true, + "TraceForge": true, + "TraceHandshake": false, + "TraceInboundGovernor": true, + "TraceIpSubscription": true, + "TraceLedgerPeers": true, + "TraceLocalChainSyncProtocol": false, + "TraceLocalErrorPolicy": true, + "TraceLocalHandshake": false, + "TraceLocalRootPeers": true, + "TraceLocalTxSubmissionProtocol": false, + "TraceLocalTxSubmissionServer": false, + "TraceMempool": true, + "TraceMux": false, + "TracePeerSelection": true, + "TracePeerSelectionActions": true, + "TracePublicRootPeers": true, + "TraceServer": true, + "TraceTxInbound": false, + "TraceTxOutbound": false, + "TraceTxSubmissionProtocol": false, + "TracingVerbosity": "NormalVerbosity", + "TurnOnLogMetrics": true, + "TurnOnLogging": true, + "defaultBackends": [ + "KatipBK" + ], + "defaultScribes": [ + [ + "StdoutSK", + "stdout" + ] + ], + "hasEKG": 12788, + "hasPrometheus": [ + "127.0.0.1", + 12798 + ], + "minSeverity": "Debug", + "options": { + "mapBackends": { + "cardano.node.metrics": [ + "EKGViewBK" + ], + "cardano.node.resources": [ + "EKGViewBK" + ] + }, + "mapSubtrace": { + "cardano.node.metrics": { + "subtrace": "Neutral" + } + } + }, + "rotation": { + "rpKeepFilesNum": 10, + "rpLogLimitBytes": 5000000, + "rpMaxAgeHours": 24 + }, + "setupBackends": [ + "KatipBK" + ], + "setupScribes": [ + { + "scFormat": "ScText", + "scKind": "StdoutSK", + "scName": "stdout", + "scRotation": null + } + ] +} diff --git a/cardano-chain-gen/bench/benchfiles/config/test-db-sync-config.json b/cardano-chain-gen/bench/benchfiles/config/test-db-sync-config.json new file mode 100644 index 000000000..a99805bd3 --- /dev/null +++ b/cardano-chain-gen/bench/benchfiles/config/test-db-sync-config.json @@ -0,0 +1,114 @@ +{ + "EnableLogMetrics": false, + "EnableLogging": true, + "NetworkName": "testing", + "NodeConfigFile": "test-config.json", + "PrometheusPort": 8080, + "RequiresNetworkMagic": "RequiresMagic", + "defaultBackends": [ + "KatipBK" + ], + "defaultScribes": [ + [ + "StdoutSK", + "stdout" + ] + ], + "minSeverity": "Warning", + "options": { + "cfokey": { + "value": "Release-1.0.0" + }, + "mapBackends": {}, + "mapSeverity": { + "db-sync-node": "Error", + "db-sync-node.Mux": "Error", + "db-sync-node.Subscription": "Error" + }, + "mapSubtrace": { + "#ekgview": { + "contents": [ + [ + { + "contents": "cardano.epoch-validation.benchmark", + "tag": "Contains" + }, + [ + { + "contents": ".monoclock.basic.", + "tag": "Contains" + } + ] + ], + [ + { + "contents": "cardano.epoch-validation.benchmark", + "tag": "Contains" + }, + [ + { + "contents": "diff.RTS.cpuNs.timed.", + "tag": "Contains" + } + ] + ], + [ + { + "contents": "#ekgview.#aggregation.cardano.epoch-validation.benchmark", + "tag": "StartsWith" + }, + [ + { + "contents": "diff.RTS.gcNum.timed.", + "tag": "Contains" + } + ] + ] + ], + "subtrace": "FilterTrace" + }, + "#messagecounters.aggregation": { + "subtrace": "NoTrace" + }, + "#messagecounters.ekgview": { + "subtrace": "NoTrace" + }, + "#messagecounters.katip": { + "subtrace": "NoTrace" + }, + "#messagecounters.monitoring": { + "subtrace": "NoTrace" + }, + "#messagecounters.switchboard": { + "subtrace": "NoTrace" + }, + "benchmark": { + "contents": [ + "GhcRtsStats", + "MonotonicClock" + ], + "subtrace": "ObservableTrace" + }, + "cardano.epoch-validation.utxo-stats": { + "subtrace": "NoTrace" + } + } + }, + "rotation": { + "rpKeepFilesNum": 10, + "rpLogLimitBytes": 5000000, + "rpMaxAgeHours": 24 + }, + "setupBackends": [ + "AggregationBK", + "KatipBK" + ], + "setupScribes": [ + { + "scFormat": "ScText", + "scKind": "StdoutSK", + "scName": "stdout", + "scRotation": null + } + ] +} diff --git a/cardano-chain-gen/bench/benchfiles/fingerprint/createMaTxOut_1 b/cardano-chain-gen/bench/benchfiles/fingerprint/createMaTxOut_1 new file mode 100644 index 000000000..6e7ea636e --- /dev/null +++ b/cardano-chain-gen/bench/benchfiles/fingerprint/createMaTxOut_1 @@ -0,0 +1 @@ +[0] \ No newline at end of file diff --git a/cardano-chain-gen/bench/benchfiles/fingerprint/createMaTxOut_10 b/cardano-chain-gen/bench/benchfiles/fingerprint/createMaTxOut_10 new file mode 100644 index 000000000..57041f55f --- /dev/null +++ b/cardano-chain-gen/bench/benchfiles/fingerprint/createMaTxOut_10 @@ -0,0 +1 @@ +[0,1,9,14,23,28,29,31,34,69] \ No newline at end of file diff --git a/cardano-chain-gen/bench/benchfiles/fingerprint/createMaTxOut_100 b/cardano-chain-gen/bench/benchfiles/fingerprint/createMaTxOut_100 new file mode 100644 index 000000000..8b6e0e180 --- /dev/null +++ b/cardano-chain-gen/bench/benchfiles/fingerprint/createMaTxOut_100 @@ -0,0 +1 @@ +[0,1,9,14,23,28,29,31,34,69,74,75,80,82,84,88,95,98,104,106,108,113,115,127,129,144,146,147,151,153,161,163,171,176,177,178,179,186,189,195,197,198,204,207,210,211,212,213,219,222,226,233,241,252,265,266,274,290,291,294,295,298,304,305,309,312,314,317,326,328,329,332,333,336,346,351,352,357,365,367,385,387,391,400,401,404,411,413,414,424,427,430,436,444,449,455,458,460,461,462] \ No newline at end of file diff --git a/cardano-chain-gen/bench/benchfiles/fingerprint/createMaTxOut_500 b/cardano-chain-gen/bench/benchfiles/fingerprint/createMaTxOut_500 new file mode 100644 index 000000000..ba054d4ce --- /dev/null +++ b/cardano-chain-gen/bench/benchfiles/fingerprint/createMaTxOut_500 @@ -0,0 +1 @@ +[0,1,9,14,23,28,29,31,34,69,74,75,80,82,84,88,95,98,104,106,108,113,115,127,129,144,146,147,151,153,161,163,171,176,177,178,179,186,189,195,197,198,204,207,210,211,212,213,219,222,226,233,241,252,265,266,274,290,291,294,295,298,304,305,309,312,314,317,326,328,329,332,333,336,346,351,352,357,365,367,385,387,391,400,401,404,411,413,414,424,427,430,436,444,449,455,458,460,461,462,473,474,476,477,482,491,497,498,499,502,506,507,514,521,547,563,566,575,578,581,594,599,602,607,614,623,631,638,639,641,649,652,653,654,665,666,670,672,673,682,683,688,692,696,700,701,708,710,714,725,735,737,746,750,763,772,776,783,793,795,797,802,804,817,818,822,824,826,827,832,834,836,841,847,851,855,861,868,870,873,876,877,882,883,891,894,905,908,913,915,925,934,942,943,949,956,960,967,968,974,980,987,998,1002,1004,1005,1012,1016,1019,1022,1023,1035,1036,1037,1039,1040,1051,1057,1058,1061,1064,1067,1074,1089,1091,1094,1096,1099,1104,1105,1107,1109,1121,1125,1133,1140,1145,1147,1148,1150,1153,1155,1159,1160,1172,1179,1185,1187,1194,1195,1201,1202,1211,1212,1216,1217,1221,1223,1233,1234,1235,1240,1241,1243,1250,1253,1259,1272,1273,1278,1280,1286,1289,1295,1298,1304,1310,1313,1320,1325,1328,1331,1332,1361,1379,1380,1382,1398,1402,1408,1411,1433,1436,1438,1449,1453,1454,1464,1468,1469,1480,1481,1482,1485,1492,1502,1504,1506,1512,1519,1524,1534,1537,1544,1545,1553,1559,1564,1565,1571,1578,1580,1583,1586,1587,1594,1597,1599,1605,1606,1609,1611,1613,1617,1623,1627,1630,1633,1634,1635,1640,1650,1655,1664,1666,1668,1670,1674,1682,1683,1684,1687,1697,1702,1710,1711,1712,1715,1718,1729,1739,1745,1750,1754,1757,1762,1775,1781,1794,1797,1801,1803,1808,1809,1812,1814,1820,1824,1825,1827,1832,1836,1854,1858,1865,1869,1872,1888,1890,1891,1892,1895,1905,1911,1917,1920,1921,1922,1928,1933,1943,1944,1962,1987,1992,1994,1998,2003,2008,2034,2037,2041,2043,2048,2051,2063,2065,2068,2070,2086,2099,2109,2122,2124,2127,2128,2129,2149,2152,2154,2160,2161,2162,2163,2168,2171,2175,2176,2180,2187,2191,2194,2201,2202,2203,2205,2206,2208,2218,2222,2229,2236,2238,2258,2266,2285,2289,2290,2293,2295,2299,2302,2308,2309,2311,2317,2325,2332,2333,2335,2337,2339,2341,2351,2357,2360,2361,2364,2366,2380,2383,2384,2386,2396,2397,2423,2429,2435,2438,2442,2448,2449,2458,2459,2463,2465,2470,2474,2477,2479] \ No newline at end of file diff --git a/cardano-chain-gen/bench/benchfiles/fingerprint/createUTXO'_1 b/cardano-chain-gen/bench/benchfiles/fingerprint/createUTXO'_1 new file mode 100644 index 000000000..6e7ea636e --- /dev/null +++ b/cardano-chain-gen/bench/benchfiles/fingerprint/createUTXO'_1 @@ -0,0 +1 @@ +[0] \ No newline at end of file diff --git a/cardano-chain-gen/bench/benchfiles/fingerprint/createUTXO'_10 b/cardano-chain-gen/bench/benchfiles/fingerprint/createUTXO'_10 new file mode 100644 index 000000000..57041f55f --- /dev/null +++ b/cardano-chain-gen/bench/benchfiles/fingerprint/createUTXO'_10 @@ -0,0 +1 @@ +[0,1,9,14,23,28,29,31,34,69] \ No newline at end of file diff --git a/cardano-chain-gen/bench/benchfiles/fingerprint/createUTXO'_100 b/cardano-chain-gen/bench/benchfiles/fingerprint/createUTXO'_100 new file mode 100644 index 000000000..8b6e0e180 --- /dev/null +++ b/cardano-chain-gen/bench/benchfiles/fingerprint/createUTXO'_100 @@ -0,0 +1 @@ +[0,1,9,14,23,28,29,31,34,69,74,75,80,82,84,88,95,98,104,106,108,113,115,127,129,144,146,147,151,153,161,163,171,176,177,178,179,186,189,195,197,198,204,207,210,211,212,213,219,222,226,233,241,252,265,266,274,290,291,294,295,298,304,305,309,312,314,317,326,328,329,332,333,336,346,351,352,357,365,367,385,387,391,400,401,404,411,413,414,424,427,430,436,444,449,455,458,460,461,462] \ No newline at end of file diff --git a/cardano-chain-gen/bench/benchfiles/fingerprint/createUTXO'_1000 b/cardano-chain-gen/bench/benchfiles/fingerprint/createUTXO'_1000 new file mode 100644 index 000000000..8cb901246 --- /dev/null +++ b/cardano-chain-gen/bench/benchfiles/fingerprint/createUTXO'_1000 @@ -0,0 +1 @@ +[0,1,9,14,23,28,29,31,34,69,74,75,80,82,84,88,95,98,104,106,108,113,115,127,129,144,146,147,151,153,161,163,171,176,177,178,179,186,189,195,197,198,204,207,210,211,212,213,219,222,226,233,241,252,265,266,274,290,291,294,295,298,304,305,309,312,314,317,326,328,329,332,333,336,346,351,352,357,365,367,385,387,391,400,401,404,411,413,414,424,427,430,436,444,449,455,458,460,461,462,473,474,476,477,482,491,497,498,499,502,506,507,514,521,547,563,566,575,578,581,594,599,602,607,614,623,631,638,639,641,649,652,653,654,665,666,670,672,673,682,683,688,692,696,700,701,708,710,714,725,735,737,746,750,763,772,776,783,793,795,797,802,804,817,818,822,824,826,827,832,834,836,841,847,851,855,861,868,870,873,876,877,882,883,891,894,905,908,913,915,925,934,942,943,949,956,960,967,968,974,980,987,998,1002,1004,1005,1012,1016,1019,1022,1023,1035,1036,1037,1039,1040,1051,1057,1058,1061,1064,1067,1074,1089,1091,1094,1096,1099,1104,1105,1107,1109,1121,1125,1133,1140,1145,1147,1148,1150,1153,1155,1159,1160,1172,1179,1185,1187,1194,1195,1201,1202,1211,1212,1216,1217,1221,1223,1233,1234,1235,1240,1241,1243,1250,1253,1259,1272,1273,1278,1280,1286,1289,1295,1298,1304,1310,1313,1320,1325,1328,1331,1332,1361,1379,1380,1382,1398,1402,1408,1411,1433,1436,1438,1449,1453,1454,1464,1468,1469,1480,1481,1482,1485,1492,1502,1504,1506,1512,1519,1524,1534,1537,1544,1545,1553,1559,1564,1565,1571,1578,1580,1583,1586,1587,1594,1597,1599,1605,1606,1609,1611,1613,1617,1623,1627,1630,1633,1634,1635,1640,1650,1655,1664,1666,1668,1670,1674,1682,1683,1684,1687,1697,1702,1710,1711,1712,1715,1718,1729,1739,1745,1750,1754,1757,1762,1775,1781,1794,1797,1801,1803,1808,1809,1812,1814,1820,1824,1825,1827,1832,1836,1854,1858,1865,1869,1872,1888,1890,1891,1892,1895,1905,1911,1917,1920,1921,1922,1928,1933,1943,1944,1962,1987,1992,1994,1998,2003,2008,2034,2037,2041,2043,2048,2051,2063,2065,2068,2070,2086,2099,2109,2122,2124,2127,2128,2129,2149,2152,2154,2160,2161,2162,2163,2168,2171,2175,2176,2180,2187,2191,2194,2201,2202,2203,2205,2206,2208,2218,2222,2229,2236,2238,2258,2266,2285,2289,2290,2293,2295,2299,2302,2308,2309,2311,2317,2325,2332,2333,2335,2337,2339,2341,2351,2357,2360,2361,2364,2366,2380,2383,2384,2386,2396,2397,2423,2429,2435,2438,2442,2448,2449,2458,2459,2463,2465,2470,2474,2477,2479,2491,2494,2496,2497,2499,2500,2505,2506,2509,2512,2519,2523,2540,2544,2546,2556,2558,2561,2562,2563,2566,2568,2569,2574,2580,2582,2600,2601,2605,2608,2620,2629,2633,2634,2637,2642,2654,2659,2660,2666,2673,2675,2683,2691,2693,2695,2697,2698,2699,2703,2705,2706,2709,2716,2717,2725,2726,2727,2731,2748,2758,2761,2767,2768,2777,2780,2787,2807,2811,2816,2818,2826,2830,2834,2835,2837,2842,2843,2846,2847,2849,2850,2854,2856,2857,2858,2860,2864,2867,2869,2872,2874,2879,2881,2887,2891,2898,2901,2903,2907,2909,2910,2933,2937,2941,2945,2947,2961,2969,2974,2975,2977,2980,2984,2990,3014,3023,3027,3036,3040,3042,3043,3050,3059,3063,3064,3068,3071,3073,3074,3087,3100,3103,3104,3111,3114,3123,3127,3131,3140,3143,3144,3150,3155,3157,3163,3169,3172,3179,3180,3193,3197,3200,3206,3211,3218,3220,3222,3232,3233,3234,3238,3249,3255,3256,3260,3280,3289,3291,3294,3299,3300,3301,3303,3308,3314,3322,3330,3333,3338,3343,3346,3352,3356,3357,3362,3365,3371,3379,3381,3383,3396,3398,3411,3413,3427,3440,3446,3457,3459,3461,3466,3471,3488,3490,3495,3496,3500,3506,3507,3509,3524,3539,3548,3555,3559,3569,3571,3575,3576,3578,3589,3595,3599,3600,3606,3608,3610,3611,3612,3616,3625,3628,3636,3649,3651,3657,3670,3673,3677,3688,3702,3706,3707,3709,3718,3736,3768,3776,3778,3785,3786,3787,3794,3802,3803,3810,3812,3819,3821,3822,3834,3844,3847,3848,3854,3856,3862,3863,3867,3869,3873,3876,3878,3879,3880,3881,3886,3888,3889,3891,3893,3903,3906,3912,3913,3916,3918,3920,3925,3926,3929,3938,3946,3956,3957,3964,3969,3980,3987,3990,3991,3997,4004,4005,4013,4014,4015,4019,4020,4023,4035,4039,4041,4048,4055,4057,4066,4071,4072,4083,4084,4090,4091,4092,4096,4125,4128,4137,4143,4145,4150,4151,4152,4158,4159,4166,4169,4174,4175,4183,4185,4189,4190,4194,4195,4196,4198,4201,4203,4210,4211,4217,4221,4222,4225,4228,4233,4240,4253,4256,4258,4261,4263,4265,4283,4287,4303,4306,4312,4314,4318,4323,4326,4333,4334,4335,4343,4345,4347,4350,4366,4374,4382,4401,4402,4405,4406,4419,4423,4425,4430,4432,4436,4440,4444,4446,4462,4467,4468,4472,4474,4484,4490,4497,4500,4502,4509,4510,4514,4516,4517,4519,4523,4534,4536,4544,4548,4556,4560,4572,4581,4584,4585,4602,4604,4607,4609,4612,4616,4620,4623,4625,4629,4631,4636,4638,4656,4664,4665,4666,4667,4669,4671,4673,4677,4679,4682,4688,4693,4698,4704,4715,4725,4727,4729,4733,4736,4743,4746,4747,4748,4752,4753,4757,4758,4760,4761,4767,4779,4785,4790,4793,4794,4795,4800,4804,4816,4820,4830,4835,4842,4843,4848,4851,4852,4853,4861,4864,4868,4873,4893,4900,4904,4905,4913,4914,4922,4934,4942] \ No newline at end of file diff --git a/cardano-chain-gen/bench/benchfiles/fingerprint/createUTXO_1 b/cardano-chain-gen/bench/benchfiles/fingerprint/createUTXO_1 new file mode 100644 index 000000000..6e7ea636e --- /dev/null +++ b/cardano-chain-gen/bench/benchfiles/fingerprint/createUTXO_1 @@ -0,0 +1 @@ +[0] \ No newline at end of file diff --git a/cardano-chain-gen/bench/benchfiles/fingerprint/createUTXO_10 b/cardano-chain-gen/bench/benchfiles/fingerprint/createUTXO_10 new file mode 100644 index 000000000..57041f55f --- /dev/null +++ b/cardano-chain-gen/bench/benchfiles/fingerprint/createUTXO_10 @@ -0,0 +1 @@ +[0,1,9,14,23,28,29,31,34,69] \ No newline at end of file diff --git a/cardano-chain-gen/bench/benchfiles/fingerprint/createUTXO_100 b/cardano-chain-gen/bench/benchfiles/fingerprint/createUTXO_100 new file mode 100644 index 000000000..8b6e0e180 --- /dev/null +++ b/cardano-chain-gen/bench/benchfiles/fingerprint/createUTXO_100 @@ -0,0 +1 @@ +[0,1,9,14,23,28,29,31,34,69,74,75,80,82,84,88,95,98,104,106,108,113,115,127,129,144,146,147,151,153,161,163,171,176,177,178,179,186,189,195,197,198,204,207,210,211,212,213,219,222,226,233,241,252,265,266,274,290,291,294,295,298,304,305,309,312,314,317,326,328,329,332,333,336,346,351,352,357,365,367,385,387,391,400,401,404,411,413,414,424,427,430,436,444,449,455,458,460,461,462] \ No newline at end of file diff --git a/cardano-chain-gen/bench/benchfiles/fingerprint/createUTXO_1000 b/cardano-chain-gen/bench/benchfiles/fingerprint/createUTXO_1000 new file mode 100644 index 000000000..8cb901246 --- /dev/null +++ b/cardano-chain-gen/bench/benchfiles/fingerprint/createUTXO_1000 @@ -0,0 +1 @@ +[0,1,9,14,23,28,29,31,34,69,74,75,80,82,84,88,95,98,104,106,108,113,115,127,129,144,146,147,151,153,161,163,171,176,177,178,179,186,189,195,197,198,204,207,210,211,212,213,219,222,226,233,241,252,265,266,274,290,291,294,295,298,304,305,309,312,314,317,326,328,329,332,333,336,346,351,352,357,365,367,385,387,391,400,401,404,411,413,414,424,427,430,436,444,449,455,458,460,461,462,473,474,476,477,482,491,497,498,499,502,506,507,514,521,547,563,566,575,578,581,594,599,602,607,614,623,631,638,639,641,649,652,653,654,665,666,670,672,673,682,683,688,692,696,700,701,708,710,714,725,735,737,746,750,763,772,776,783,793,795,797,802,804,817,818,822,824,826,827,832,834,836,841,847,851,855,861,868,870,873,876,877,882,883,891,894,905,908,913,915,925,934,942,943,949,956,960,967,968,974,980,987,998,1002,1004,1005,1012,1016,1019,1022,1023,1035,1036,1037,1039,1040,1051,1057,1058,1061,1064,1067,1074,1089,1091,1094,1096,1099,1104,1105,1107,1109,1121,1125,1133,1140,1145,1147,1148,1150,1153,1155,1159,1160,1172,1179,1185,1187,1194,1195,1201,1202,1211,1212,1216,1217,1221,1223,1233,1234,1235,1240,1241,1243,1250,1253,1259,1272,1273,1278,1280,1286,1289,1295,1298,1304,1310,1313,1320,1325,1328,1331,1332,1361,1379,1380,1382,1398,1402,1408,1411,1433,1436,1438,1449,1453,1454,1464,1468,1469,1480,1481,1482,1485,1492,1502,1504,1506,1512,1519,1524,1534,1537,1544,1545,1553,1559,1564,1565,1571,1578,1580,1583,1586,1587,1594,1597,1599,1605,1606,1609,1611,1613,1617,1623,1627,1630,1633,1634,1635,1640,1650,1655,1664,1666,1668,1670,1674,1682,1683,1684,1687,1697,1702,1710,1711,1712,1715,1718,1729,1739,1745,1750,1754,1757,1762,1775,1781,1794,1797,1801,1803,1808,1809,1812,1814,1820,1824,1825,1827,1832,1836,1854,1858,1865,1869,1872,1888,1890,1891,1892,1895,1905,1911,1917,1920,1921,1922,1928,1933,1943,1944,1962,1987,1992,1994,1998,2003,2008,2034,2037,2041,2043,2048,2051,2063,2065,2068,2070,2086,2099,2109,2122,2124,2127,2128,2129,2149,2152,2154,2160,2161,2162,2163,2168,2171,2175,2176,2180,2187,2191,2194,2201,2202,2203,2205,2206,2208,2218,2222,2229,2236,2238,2258,2266,2285,2289,2290,2293,2295,2299,2302,2308,2309,2311,2317,2325,2332,2333,2335,2337,2339,2341,2351,2357,2360,2361,2364,2366,2380,2383,2384,2386,2396,2397,2423,2429,2435,2438,2442,2448,2449,2458,2459,2463,2465,2470,2474,2477,2479,2491,2494,2496,2497,2499,2500,2505,2506,2509,2512,2519,2523,2540,2544,2546,2556,2558,2561,2562,2563,2566,2568,2569,2574,2580,2582,2600,2601,2605,2608,2620,2629,2633,2634,2637,2642,2654,2659,2660,2666,2673,2675,2683,2691,2693,2695,2697,2698,2699,2703,2705,2706,2709,2716,2717,2725,2726,2727,2731,2748,2758,2761,2767,2768,2777,2780,2787,2807,2811,2816,2818,2826,2830,2834,2835,2837,2842,2843,2846,2847,2849,2850,2854,2856,2857,2858,2860,2864,2867,2869,2872,2874,2879,2881,2887,2891,2898,2901,2903,2907,2909,2910,2933,2937,2941,2945,2947,2961,2969,2974,2975,2977,2980,2984,2990,3014,3023,3027,3036,3040,3042,3043,3050,3059,3063,3064,3068,3071,3073,3074,3087,3100,3103,3104,3111,3114,3123,3127,3131,3140,3143,3144,3150,3155,3157,3163,3169,3172,3179,3180,3193,3197,3200,3206,3211,3218,3220,3222,3232,3233,3234,3238,3249,3255,3256,3260,3280,3289,3291,3294,3299,3300,3301,3303,3308,3314,3322,3330,3333,3338,3343,3346,3352,3356,3357,3362,3365,3371,3379,3381,3383,3396,3398,3411,3413,3427,3440,3446,3457,3459,3461,3466,3471,3488,3490,3495,3496,3500,3506,3507,3509,3524,3539,3548,3555,3559,3569,3571,3575,3576,3578,3589,3595,3599,3600,3606,3608,3610,3611,3612,3616,3625,3628,3636,3649,3651,3657,3670,3673,3677,3688,3702,3706,3707,3709,3718,3736,3768,3776,3778,3785,3786,3787,3794,3802,3803,3810,3812,3819,3821,3822,3834,3844,3847,3848,3854,3856,3862,3863,3867,3869,3873,3876,3878,3879,3880,3881,3886,3888,3889,3891,3893,3903,3906,3912,3913,3916,3918,3920,3925,3926,3929,3938,3946,3956,3957,3964,3969,3980,3987,3990,3991,3997,4004,4005,4013,4014,4015,4019,4020,4023,4035,4039,4041,4048,4055,4057,4066,4071,4072,4083,4084,4090,4091,4092,4096,4125,4128,4137,4143,4145,4150,4151,4152,4158,4159,4166,4169,4174,4175,4183,4185,4189,4190,4194,4195,4196,4198,4201,4203,4210,4211,4217,4221,4222,4225,4228,4233,4240,4253,4256,4258,4261,4263,4265,4283,4287,4303,4306,4312,4314,4318,4323,4326,4333,4334,4335,4343,4345,4347,4350,4366,4374,4382,4401,4402,4405,4406,4419,4423,4425,4430,4432,4436,4440,4444,4446,4462,4467,4468,4472,4474,4484,4490,4497,4500,4502,4509,4510,4514,4516,4517,4519,4523,4534,4536,4544,4548,4556,4560,4572,4581,4584,4585,4602,4604,4607,4609,4612,4616,4620,4623,4625,4629,4631,4636,4638,4656,4664,4665,4666,4667,4669,4671,4673,4677,4679,4682,4688,4693,4698,4704,4715,4725,4727,4729,4733,4736,4743,4746,4747,4748,4752,4753,4757,4758,4760,4761,4767,4779,4785,4790,4793,4794,4795,4800,4804,4816,4820,4830,4835,4842,4843,4848,4851,4852,4853,4861,4864,4868,4873,4893,4900,4904,4905,4913,4914,4922,4934,4942] \ No newline at end of file diff --git a/cardano-chain-gen/bench/benchfiles/fingerprint/delegateAndSend_1 b/cardano-chain-gen/bench/benchfiles/fingerprint/delegateAndSend_1 new file mode 100644 index 000000000..df965face --- /dev/null +++ b/cardano-chain-gen/bench/benchfiles/fingerprint/delegateAndSend_1 @@ -0,0 +1 @@ +[0,1,9] \ No newline at end of file diff --git a/cardano-chain-gen/bench/benchfiles/fingerprint/delegateAndSend_10 b/cardano-chain-gen/bench/benchfiles/fingerprint/delegateAndSend_10 new file mode 100644 index 000000000..495236454 --- /dev/null +++ b/cardano-chain-gen/bench/benchfiles/fingerprint/delegateAndSend_10 @@ -0,0 +1 @@ +[0,1,9,14,23,28,29,31,34,69,74,75,80,82,84,88,95,98,104,106,108,113,115,127,129,144,146,147,151,153] \ No newline at end of file diff --git a/cardano-chain-gen/bench/benchfiles/fingerprint/delegateAndSend_100 b/cardano-chain-gen/bench/benchfiles/fingerprint/delegateAndSend_100 new file mode 100644 index 000000000..cecab0676 --- /dev/null +++ b/cardano-chain-gen/bench/benchfiles/fingerprint/delegateAndSend_100 @@ -0,0 +1 @@ +[0,1,9,14,23,28,29,31,34,69,74,75,80,82,84,88,95,98,104,106,108,113,115,127,129,144,146,147,151,153,161,163,171,176,177,178,179,186,189,195,197,198,204,207,210,211,212,213,219,222,226,233,241,252,265,266,274,290,291,294,295,298,304,305,309,312,314,317,326,328,329,332,333,336,346,351,352,357,365,367,385,387,391,400,401,404,411,413,414,424,427,430,436,444,449,455,458,460,461,462,473,474,476,477,482,491,497,498,499,502,506,507,514,521,547,563,566,575,578,581,594,599,602,607,614,623,631,638,639,641,649,652,653,654,665,666,670,672,673,682,683,688,692,696,700,701,708,710,714,725,735,737,746,750,763,772,776,783,793,795,797,802,804,817,818,822,824,826,827,832,834,836,841,847,851,855,861,868,870,873,876,877,882,883,891,894,905,908,913,915,925,934,942,943,949,956,960,967,968,974,980,987,998,1002,1004,1005,1012,1016,1019,1022,1023,1035,1036,1037,1039,1040,1051,1057,1058,1061,1064,1067,1074,1089,1091,1094,1096,1099,1104,1105,1107,1109,1121,1125,1133,1140,1145,1147,1148,1150,1153,1155,1159,1160,1172,1179,1185,1187,1194,1195,1201,1202,1211,1212,1216,1217,1221,1223,1233,1234,1235,1240,1241,1243,1250,1253,1259,1272,1273,1278,1280,1286,1289,1295,1298,1304,1310,1313,1320,1325,1328,1331,1332,1361,1379,1380,1382,1398,1402,1408,1411,1433,1436,1438,1449,1453,1454,1464,1468,1469] \ No newline at end of file diff --git a/cardano-chain-gen/bench/benchfiles/fingerprint/delegateAndSend_400 b/cardano-chain-gen/bench/benchfiles/fingerprint/delegateAndSend_400 new file mode 100644 index 000000000..518717669 --- /dev/null +++ b/cardano-chain-gen/bench/benchfiles/fingerprint/delegateAndSend_400 @@ -0,0 +1 @@ +[0,1,9,14,23,28,29,31,34,69,74,75,80,82,84,88,95,98,104,106,108,113,115,127,129,144,146,147,151,153,161,163,171,176,177,178,179,186,189,195,197,198,204,207,210,211,212,213,219,222,226,233,241,252,265,266,274,290,291,294,295,298,304,305,309,312,314,317,326,328,329,332,333,336,346,351,352,357,365,367,385,387,391,400,401,404,411,413,414,424,427,430,436,444,449,455,458,460,461,462,473,474,476,477,482,491,497,498,499,502,506,507,514,521,547,563,566,575,578,581,594,599,602,607,614,623,631,638,639,641,649,652,653,654,665,666,670,672,673,682,683,688,692,696,700,701,708,710,714,725,735,737,746,750,763,772,776,783,793,795,797,802,804,817,818,822,824,826,827,832,834,836,841,847,851,855,861,868,870,873,876,877,882,883,891,894,905,908,913,915,925,934,942,943,949,956,960,967,968,974,980,987,998,1002,1004,1005,1012,1016,1019,1022,1023,1035,1036,1037,1039,1040,1051,1057,1058,1061,1064,1067,1074,1089,1091,1094,1096,1099,1104,1105,1107,1109,1121,1125,1133,1140,1145,1147,1148,1150,1153,1155,1159,1160,1172,1179,1185,1187,1194,1195,1201,1202,1211,1212,1216,1217,1221,1223,1233,1234,1235,1240,1241,1243,1250,1253,1259,1272,1273,1278,1280,1286,1289,1295,1298,1304,1310,1313,1320,1325,1328,1331,1332,1361,1379,1380,1382,1398,1402,1408,1411,1433,1436,1438,1449,1453,1454,1464,1468,1469,1480,1481,1482,1485,1492,1502,1504,1506,1512,1519,1524,1534,1537,1544,1545,1553,1559,1564,1565,1571,1578,1580,1583,1586,1587,1594,1597,1599,1605,1606,1609,1611,1613,1617,1623,1627,1630,1633,1634,1635,1640,1650,1655,1664,1666,1668,1670,1674,1682,1683,1684,1687,1697,1702,1710,1711,1712,1715,1718,1729,1739,1745,1750,1754,1757,1762,1775,1781,1794,1797,1801,1803,1808,1809,1812,1814,1820,1824,1825,1827,1832,1836,1854,1858,1865,1869,1872,1888,1890,1891,1892,1895,1905,1911,1917,1920,1921,1922,1928,1933,1943,1944,1962,1987,1992,1994,1998,2003,2008,2034,2037,2041,2043,2048,2051,2063,2065,2068,2070,2086,2099,2109,2122,2124,2127,2128,2129,2149,2152,2154,2160,2161,2162,2163,2168,2171,2175,2176,2180,2187,2191,2194,2201,2202,2203,2205,2206,2208,2218,2222,2229,2236,2238,2258,2266,2285,2289,2290,2293,2295,2299,2302,2308,2309,2311,2317,2325,2332,2333,2335,2337,2339,2341,2351,2357,2360,2361,2364,2366,2380,2383,2384,2386,2396,2397,2423,2429,2435,2438,2442,2448,2449,2458,2459,2463,2465,2470,2474,2477,2479,2491,2494,2496,2497,2499,2500,2505,2506,2509,2512,2519,2523,2540,2544,2546,2556,2558,2561,2562,2563,2566,2568,2569,2574,2580,2582,2600,2601,2605,2608,2620,2629,2633,2634,2637,2642,2654,2659,2660,2666,2673,2675,2683,2691,2693,2695,2697,2698,2699,2703,2705,2706,2709,2716,2717,2725,2726,2727,2731,2748,2758,2761,2767,2768,2777,2780,2787,2807,2811,2816,2818,2826,2830,2834,2835,2837,2842,2843,2846,2847,2849,2850,2854,2856,2857,2858,2860,2864,2867,2869,2872,2874,2879,2881,2887,2891,2898,2901,2903,2907,2909,2910,2933,2937,2941,2945,2947,2961,2969,2974,2975,2977,2980,2984,2990,3014,3023,3027,3036,3040,3042,3043,3050,3059,3063,3064,3068,3071,3073,3074,3087,3100,3103,3104,3111,3114,3123,3127,3131,3140,3143,3144,3150,3155,3157,3163,3169,3172,3179,3180,3193,3197,3200,3206,3211,3218,3220,3222,3232,3233,3234,3238,3249,3255,3256,3260,3280,3289,3291,3294,3299,3300,3301,3303,3308,3314,3322,3330,3333,3338,3343,3346,3352,3356,3357,3362,3365,3371,3379,3381,3383,3396,3398,3411,3413,3427,3440,3446,3457,3459,3461,3466,3471,3488,3490,3495,3496,3500,3506,3507,3509,3524,3539,3548,3555,3559,3569,3571,3575,3576,3578,3589,3595,3599,3600,3606,3608,3610,3611,3612,3616,3625,3628,3636,3649,3651,3657,3670,3673,3677,3688,3702,3706,3707,3709,3718,3736,3768,3776,3778,3785,3786,3787,3794,3802,3803,3810,3812,3819,3821,3822,3834,3844,3847,3848,3854,3856,3862,3863,3867,3869,3873,3876,3878,3879,3880,3881,3886,3888,3889,3891,3893,3903,3906,3912,3913,3916,3918,3920,3925,3926,3929,3938,3946,3956,3957,3964,3969,3980,3987,3990,3991,3997,4004,4005,4013,4014,4015,4019,4020,4023,4035,4039,4041,4048,4055,4057,4066,4071,4072,4083,4084,4090,4091,4092,4096,4125,4128,4137,4143,4145,4150,4151,4152,4158,4159,4166,4169,4174,4175,4183,4185,4189,4190,4194,4195,4196,4198,4201,4203,4210,4211,4217,4221,4222,4225,4228,4233,4240,4253,4256,4258,4261,4263,4265,4283,4287,4303,4306,4312,4314,4318,4323,4326,4333,4334,4335,4343,4345,4347,4350,4366,4374,4382,4401,4402,4405,4406,4419,4423,4425,4430,4432,4436,4440,4444,4446,4462,4467,4468,4472,4474,4484,4490,4497,4500,4502,4509,4510,4514,4516,4517,4519,4523,4534,4536,4544,4548,4556,4560,4572,4581,4584,4585,4602,4604,4607,4609,4612,4616,4620,4623,4625,4629,4631,4636,4638,4656,4664,4665,4666,4667,4669,4671,4673,4677,4679,4682,4688,4693,4698,4704,4715,4725,4727,4729,4733,4736,4743,4746,4747,4748,4752,4753,4757,4758,4760,4761,4767,4779,4785,4790,4793,4794,4795,4800,4804,4816,4820,4830,4835,4842,4843,4848,4851,4852,4853,4861,4864,4868,4873,4893,4900,4904,4905,4913,4914,4922,4934,4942,4945,4955,4959,4960,4978,4979,4986,4989,4996,5009,5016,5025,5028,5031,5035,5036,5040,5043,5047,5050,5053,5061,5063,5064,5068,5070,5073,5077,5095,5104,5107,5114,5117,5118,5120,5127,5132,5134,5148,5149,5159,5163,5164,5166,5171,5174,5175,5178,5185,5187,5200,5202,5212,5221,5224,5225,5229,5237,5242,5268,5276,5283,5287,5290,5299,5300,5301,5307,5318,5321,5322,5323,5361,5365,5366,5382,5389,5394,5398,5409,5410,5414,5417,5418,5431,5441,5443,5453,5456,5465,5468,5470,5480,5494,5500,5510,5519,5523,5532,5534,5535,5539,5543,5544,5546,5555,5558,5560,5562,5567,5568,5583,5585,5594,5600,5602,5606,5608,5611,5612,5615,5616,5617,5636,5639,5641,5650,5659,5664,5670,5672,5676,5679,5680,5688,5689,5692,5693,5694,5706,5709,5714,5715,5728,5729,5730,5734,5735,5739,5752,5755,5759,5776,5782,5783,5784,5792,5796,5799,5800,5803,5808,5810,5815,5818,5821,5824,5830,5835,5845,5847,5849,5861,5863,5867,5869,5874,5893,5897,5899,5900,5902,5903,5904,5906,5911,5924,5934,5939,5943,5947,5951,5963,5966,5968,5980,5985,5987,5992,5994] \ No newline at end of file diff --git a/cardano-chain-gen/bench/benchfiles/fingerprint/emptyBlock_10 b/cardano-chain-gen/bench/benchfiles/fingerprint/emptyBlock_10 new file mode 100644 index 000000000..57041f55f --- /dev/null +++ b/cardano-chain-gen/bench/benchfiles/fingerprint/emptyBlock_10 @@ -0,0 +1 @@ +[0,1,9,14,23,28,29,31,34,69] \ No newline at end of file diff --git a/cardano-chain-gen/bench/benchfiles/fingerprint/emptyBlock_100 b/cardano-chain-gen/bench/benchfiles/fingerprint/emptyBlock_100 new file mode 100644 index 000000000..8b6e0e180 --- /dev/null +++ b/cardano-chain-gen/bench/benchfiles/fingerprint/emptyBlock_100 @@ -0,0 +1 @@ +[0,1,9,14,23,28,29,31,34,69,74,75,80,82,84,88,95,98,104,106,108,113,115,127,129,144,146,147,151,153,161,163,171,176,177,178,179,186,189,195,197,198,204,207,210,211,212,213,219,222,226,233,241,252,265,266,274,290,291,294,295,298,304,305,309,312,314,317,326,328,329,332,333,336,346,351,352,357,365,367,385,387,391,400,401,404,411,413,414,424,427,430,436,444,449,455,458,460,461,462] \ No newline at end of file diff --git a/cardano-chain-gen/bench/benchfiles/fingerprint/emptyBlock_10000 b/cardano-chain-gen/bench/benchfiles/fingerprint/emptyBlock_10000 new file mode 100644 index 000000000..261c516b1 --- /dev/null +++ b/cardano-chain-gen/bench/benchfiles/fingerprint/emptyBlock_10000 @@ -0,0 +1 @@ +[0,1,9,14,23,28,29,31,34,69,74,75,80,82,84,88,95,98,104,106,108,113,115,127,129,144,146,147,151,153,161,163,171,176,177,178,179,186,189,195,197,198,204,207,210,211,212,213,219,222,226,233,241,252,265,266,274,290,291,294,295,298,304,305,309,312,314,317,326,328,329,332,333,336,346,351,352,357,365,367,385,387,391,400,401,404,411,413,414,424,427,430,436,444,449,455,458,460,461,462,473,474,476,477,482,491,497,498,499,502,506,507,514,521,547,563,566,575,578,581,594,599,602,607,614,623,631,638,639,641,649,652,653,654,665,666,670,672,673,682,683,688,692,696,700,701,708,710,714,725,735,737,746,750,763,772,776,783,793,795,797,802,804,817,818,822,824,826,827,832,834,836,841,847,851,855,861,868,870,873,876,877,882,883,891,894,905,908,913,915,925,934,942,943,949,956,960,967,968,974,980,987,998,1002,1004,1005,1012,1016,1019,1022,1023,1035,1036,1037,1039,1040,1051,1057,1058,1061,1064,1067,1074,1089,1091,1094,1096,1099,1104,1105,1107,1109,1121,1125,1133,1140,1145,1147,1148,1150,1153,1155,1159,1160,1172,1179,1185,1187,1194,1195,1201,1202,1211,1212,1216,1217,1221,1223,1233,1234,1235,1240,1241,1243,1250,1253,1259,1272,1273,1278,1280,1286,1289,1295,1298,1304,1310,1313,1320,1325,1328,1331,1332,1361,1379,1380,1382,1398,1402,1408,1411,1433,1436,1438,1449,1453,1454,1464,1468,1469,1480,1481,1482,1485,1492,1502,1504,1506,1512,1519,1524,1534,1537,1544,1545,1553,1559,1564,1565,1571,1578,1580,1583,1586,1587,1594,1597,1599,1605,1606,1609,1611,1613,1617,1623,1627,1630,1633,1634,1635,1640,1650,1655,1664,1666,1668,1670,1674,1682,1683,1684,1687,1697,1702,1710,1711,1712,1715,1718,1729,1739,1745,1750,1754,1757,1762,1775,1781,1794,1797,1801,1803,1808,1809,1812,1814,1820,1824,1825,1827,1832,1836,1854,1858,1865,1869,1872,1888,1890,1891,1892,1895,1905,1911,1917,1920,1921,1922,1928,1933,1943,1944,1962,1987,1992,1994,1998,2003,2008,2034,2037,2041,2043,2048,2051,2063,2065,2068,2070,2086,2099,2109,2122,2124,2127,2128,2129,2149,2152,2154,2160,2161,2162,2163,2168,2171,2175,2176,2180,2187,2191,2194,2201,2202,2203,2205,2206,2208,2218,2222,2229,2236,2238,2258,2266,2285,2289,2290,2293,2295,2299,2302,2308,2309,2311,2317,2325,2332,2333,2335,2337,2339,2341,2351,2357,2360,2361,2364,2366,2380,2383,2384,2386,2396,2397,2423,2429,2435,2438,2442,2448,2449,2458,2459,2463,2465,2470,2474,2477,2479,2491,2494,2496,2497,2499,2500,2505,2506,2509,2512,2519,2523,2540,2544,2546,2556,2558,2561,2562,2563,2566,2568,2569,2574,2580,2582,2600,2601,2605,2608,2620,2629,2633,2634,2637,2642,2654,2659,2660,2666,2673,2675,2683,2691,2693,2695,2697,2698,2699,2703,2705,2706,2709,2716,2717,2725,2726,2727,2731,2748,2758,2761,2767,2768,2777,2780,2787,2807,2811,2816,2818,2826,2830,2834,2835,2837,2842,2843,2846,2847,2849,2850,2854,2856,2857,2858,2860,2864,2867,2869,2872,2874,2879,2881,2887,2891,2898,2901,2903,2907,2909,2910,2933,2937,2941,2945,2947,2961,2969,2974,2975,2977,2980,2984,2990,3014,3023,3027,3036,3040,3042,3043,3050,3059,3063,3064,3068,3071,3073,3074,3087,3100,3103,3104,3111,3114,3123,3127,3131,3140,3143,3144,3150,3155,3157,3163,3169,3172,3179,3180,3193,3197,3200,3206,3211,3218,3220,3222,3232,3233,3234,3238,3249,3255,3256,3260,3280,3289,3291,3294,3299,3300,3301,3303,3308,3314,3322,3330,3333,3338,3343,3346,3352,3356,3357,3362,3365,3371,3379,3381,3383,3396,3398,3411,3413,3427,3440,3446,3457,3459,3461,3466,3471,3488,3490,3495,3496,3500,3506,3507,3509,3524,3539,3548,3555,3559,3569,3571,3575,3576,3578,3589,3595,3599,3600,3606,3608,3610,3611,3612,3616,3625,3628,3636,3649,3651,3657,3670,3673,3677,3688,3702,3706,3707,3709,3718,3736,3768,3776,3778,3785,3786,3787,3794,3802,3803,3810,3812,3819,3821,3822,3834,3844,3847,3848,3854,3856,3862,3863,3867,3869,3873,3876,3878,3879,3880,3881,3886,3888,3889,3891,3893,3903,3906,3912,3913,3916,3918,3920,3925,3926,3929,3938,3946,3956,3957,3964,3969,3980,3987,3990,3991,3997,4004,4005,4013,4014,4015,4019,4020,4023,4035,4039,4041,4048,4055,4057,4066,4071,4072,4083,4084,4090,4091,4092,4096,4125,4128,4137,4143,4145,4150,4151,4152,4158,4159,4166,4169,4174,4175,4183,4185,4189,4190,4194,4195,4196,4198,4201,4203,4210,4211,4217,4221,4222,4225,4228,4233,4240,4253,4256,4258,4261,4263,4265,4283,4287,4303,4306,4312,4314,4318,4323,4326,4333,4334,4335,4343,4345,4347,4350,4366,4374,4382,4401,4402,4405,4406,4419,4423,4425,4430,4432,4436,4440,4444,4446,4462,4467,4468,4472,4474,4484,4490,4497,4500,4502,4509,4510,4514,4516,4517,4519,4523,4534,4536,4544,4548,4556,4560,4572,4581,4584,4585,4602,4604,4607,4609,4612,4616,4620,4623,4625,4629,4631,4636,4638,4656,4664,4665,4666,4667,4669,4671,4673,4677,4679,4682,4688,4693,4698,4704,4715,4725,4727,4729,4733,4736,4743,4746,4747,4748,4752,4753,4757,4758,4760,4761,4767,4779,4785,4790,4793,4794,4795,4800,4804,4816,4820,4830,4835,4842,4843,4848,4851,4852,4853,4861,4864,4868,4873,4893,4900,4904,4905,4913,4914,4922,4934,4942,4945,4955,4959,4960,4978,4979,4986,4989,4996,5009,5016,5025,5028,5031,5035,5036,5040,5043,5047,5050,5053,5061,5063,5064,5068,5070,5073,5077,5095,5104,5107,5114,5117,5118,5120,5127,5132,5134,5148,5149,5159,5163,5164,5166,5171,5174,5175,5178,5185,5187,5200,5202,5212,5221,5224,5225,5229,5237,5242,5268,5276,5283,5287,5290,5299,5300,5301,5307,5318,5321,5322,5323,5361,5365,5366,5382,5389,5394,5398,5409,5410,5414,5417,5418,5431,5441,5443,5453,5456,5465,5468,5470,5480,5494,5500,5510,5519,5523,5532,5534,5535,5539,5543,5544,5546,5555,5558,5560,5562,5567,5568,5583,5585,5594,5600,5602,5606,5608,5611,5612,5615,5616,5617,5636,5639,5641,5650,5659,5664,5670,5672,5676,5679,5680,5688,5689,5692,5693,5694,5706,5709,5714,5715,5728,5729,5730,5734,5735,5739,5752,5755,5759,5776,5782,5783,5784,5792,5796,5799,5800,5803,5808,5810,5815,5818,5821,5824,5830,5835,5845,5847,5849,5861,5863,5867,5869,5874,5893,5897,5899,5900,5902,5903,5904,5906,5911,5924,5934,5939,5943,5947,5951,5963,5966,5968,5980,5985,5987,5992,5994,5999,6001,6018,6020,6027,6039,6046,6047,6053,6057,6059,6064,6070,6085,6089,6101,6103,6112,6123,6135,6140,6143,6148,6153,6156,6157,6158,6159,6160,6161,6165,6167,6168,6171,6177,6180,6184,6193,6206,6212,6220,6221,6230,6236,6240,6248,6255,6262,6266,6272,6273,6275,6280,6281,6283,6288,6289,6290,6292,6293,6303,6306,6317,6321,6329,6334,6336,6344,6347,6354,6356,6358,6360,6366,6375,6377,6378,6385,6390,6393,6400,6408,6413,6416,6419,6422,6423,6426,6427,6428,6432,6434,6438,6442,6445,6452,6454,6465,6466,6467,6470,6471,6481,6482,6483,6484,6491,6495,6497,6500,6503,6515,6516,6517,6522,6525,6527,6536,6551,6563,6564,6566,6574,6578,6579,6580,6582,6585,6594,6602,6608,6610,6613,6616,6625,6629,6635,6639,6645,6648,6651,6663,6665,6668,6669,6672,6687,6690,6694,6704,6705,6707,6708,6711,6713,6715,6718,6719,6727,6731,6737,6741,6746,6749,6750,6758,6760,6765,6771,6772,6773,6777,6783,6786,6788,6790,6791,6797,6800,6801,6802,6810,6811,6815,6825,6829,6832,6842,6847,6857,6869,6871,6878,6883,6887,6890,6893,6895,6896,6898,6901,6920,6924,6928,6931,6934,6942,6944,6963,6964,6987,6988,6994,6996,7000,7001,7002,7004,7005,7007,7015,7016,7022,7023,7036,7044,7045,7047,7052,7057,7060,7062,7067,7077,7080,7083,7084,7087,7090,7093,7095,7096,7100,7107,7114,7115,7118,7119,7120,7123,7124,7127,7135,7141,7163,7170,7176,7178,7187,7188,7198,7205,7213,7214,7215,7225,7226,7253,7274,7277,7278,7283,7286,7287,7289,7298,7307,7309,7310,7315,7317,7318,7322,7334,7337,7340,7341,7344,7346,7351,7357,7358,7376,7377,7385,7386,7390,7392,7394,7396,7398,7407,7412,7419,7428,7436,7443,7454,7455,7457,7458,7463,7472,7485,7496,7505,7511,7512,7517,7522,7524,7525,7528,7533,7539,7541,7543,7547,7548,7557,7561,7580,7587,7592,7601,7602,7604,7609,7610,7613,7616,7621,7627,7636,7638,7639,7641,7648,7651,7656,7659,7662,7676,7678,7682,7687,7688,7692,7696,7699,7701,7702,7704,7707,7711,7721,7727,7730,7733,7735,7743,7747,7748,7749,7757,7758,7762,7768,7769,7777,7786,7791,7798,7809,7810,7813,7819,7835,7837,7839,7841,7844,7847,7849,7850,7855,7858,7865,7868,7871,7876,7883,7885,7894,7898,7903,7906,7908,7913,7917,7918,7921,7922,7927,7931,7942,7947,7950,7953,7956,7957,7959,7963,7964,7973,7977,7978,7980,7982,7985,7986,7989,7993,7999,8003,8007,8013,8015,8034,8057,8062,8073,8088,8091,8096,8097,8103,8105,8107,8112,8118,8121,8127,8129,8132,8136,8137,8138,8145,8152,8153,8154,8159,8168,8187,8188,8189,8200,8203,8211,8234,8236,8237,8239,8250,8254,8263,8268,8269,8276,8280,8284,8291,8294,8295,8300,8301,8313,8315,8329,8330,8331,8335,8337,8345,8351,8352,8360,8362,8365,8366,8368,8370,8372,8374,8377,8380,8383,8387,8388,8406,8416,8418,8421,8422,8428,8432,8434,8443,8447,8459,8461,8467,8468,8489,8494,8497,8502,8503,8506,8508,8512,8514,8523,8525,8537,8539,8542,8543,8548,8555,8563,8566,8567,8570,8572,8574,8586,8598,8612,8620,8623,8624,8630,8634,8635,8642,8647,8653,8658,8659,8663,8668,8672,8673,8679,8682,8690,8701,8706,8711,8714,8722,8726,8737,8739,8742,8743,8744,8748,8751,8754,8757,8759,8766,8772,8780,8789,8792,8797,8815,8817,8819,8822,8828,8840,8852,8857,8858,8859,8865,8866,8867,8876,8882,8890,8892,8897,8905,8906,8907,8911,8915,8918,8922,8923,8958,8965,8970,8972,8978,8980,8982,8984,8985,8990,9000,9003,9007,9016,9020,9026,9030,9040,9048,9049,9050,9058,9062,9064,9066,9068,9071,9082,9085,9086,9095,9097,9099,9111,9114,9117,9127,9130,9134,9142,9149,9151,9155,9156,9165,9166,9169,9187,9199,9202,9206,9233,9234,9244,9246,9248,9255,9259,9262,9266,9278,9281,9286,9289,9290,9293,9295,9296,9302,9307,9308,9313,9314,9318,9330,9332,9343,9349,9352,9361,9362,9363,9373,9378,9382,9385,9386,9396,9397,9401,9403,9411,9412,9415,9419,9422,9425,9427,9433,9435,9444,9448,9454,9458,9462,9463,9470,9471,9472,9480,9489,9503,9515,9521,9523,9525,9528,9531,9541,9549,9550,9552,9555,9563,9565,9566,9567,9571,9577,9580,9584,9597,9600,9608,9615,9618,9625,9628,9629,9636,9637,9639,9642,9648,9658,9664,9666,9668,9678,9683,9697,9700,9701,9705,9707,9708,9714,9718,9719,9736,9738,9749,9755,9758,9759,9772,9774,9777,9779,9782,9791,9811,9812,9813,9822,9829,9837,9842,9848,9851,9859,9864,9879,9888,9894,9895,9899,9903,9904,9913,9919,9920,9922,9931,9939,9941,9944,9949,9960,9969,9970,9973,9976,9977,9979,9982,9983,9984,9987,9989,9992,9999,10000,10009,10013,10014,10030,10032,10044,10048,10049,10067,10075,10079,10081,10083,10084,10097,10107,10109,10118,10119,10120,10121,10125,10128,10131,10132,10135,10147,10151,10160,10164,10165,10172,10181,10188,10189,10194,10198,10200,10201,10207,10208,10211,10227,10228,10231,10232,10233,10236,10237,10245,10248,10255,10266,10273,10281,10283,10287,10288,10296,10297,10301,10307,10311,10320,10325,10328,10335,10345,10346,10349,10353,10359,10367,10372,10373,10376,10380,10394,10396,10399,10402,10403,10405,10410,10424,10427,10436,10437,10444,10445,10455,10460,10462,10469,10476,10477,10478,10480,10481,10498,10500,10501,10503,10509,10517,10527,10531,10532,10534,10540,10541,10542,10550,10555,10564,10566,10570,10576,10578,10582,10583,10586,10590,10592,10604,10605,10606,10611,10616,10617,10626,10629,10636,10637,10644,10655,10659,10664,10667,10668,10674,10686,10696,10706,10715,10725,10730,10732,10734,10738,10749,10750,10757,10759,10773,10774,10775,10776,10785,10794,10796,10801,10804,10812,10820,10825,10827,10833,10834,10835,10841,10851,10854,10855,10859,10868,10869,10876,10881,10886,10892,10900,10902,10903,10915,10922,10925,10927,10931,10938,10943,10945,10946,10958,10963,10964,10981,10996,10998,11001,11008,11010,11014,11020,11027,11035,11037,11050,11054,11057,11058,11061,11069,11070,11072,11073,11077,11078,11079,11082,11085,11086,11088,11090,11093,11095,11097,11104,11105,11120,11129,11142,11152,11154,11159,11166,11175,11180,11181,11186,11189,11191,11192,11194,11198,11209,11210,11212,11214,11223,11225,11226,11228,11230,11234,11236,11246,11256,11258,11263,11281,11284,11290,11291,11305,11312,11318,11319,11326,11328,11330,11354,11358,11361,11366,11374,11376,11379,11380,11383,11386,11391,11407,11415,11438,11445,11450,11457,11458,11459,11460,11465,11467,11468,11471,11473,11482,11496,11506,11507,11511,11515,11532,11533,11534,11536,11537,11538,11542,11543,11546,11552,11555,11565,11567,11572,11573,11576,11577,11579,11586,11593,11596,11597,11612,11614,11630,11631,11632,11634,11639,11641,11670,11671,11672,11673,11675,11679,11680,11682,11695,11699,11700,11709,11713,11716,11722,11735,11743,11751,11752,11758,11771,11774,11777,11789,11800,11803,11809,11827,11833,11835,11836,11841,11843,11847,11862,11869,11872,11885,11894,11897,11901,11904,11907,11911,11917,11919,11924,11937,11939,11941,11947,11964,11971,11973,11979,11988,11994,11996,12000,12002,12011,12012,12013,12014,12037,12041,12045,12060,12062,12072,12086,12094,12109,12110,12115,12118,12120,12141,12142,12146,12152,12174,12175,12176,12181,12195,12201,12212,12220,12225,12226,12231,12250,12252,12269,12272,12274,12279,12284,12286,12288,12295,12302,12306,12308,12311,12317,12328,12329,12338,12343,12345,12347,12355,12368,12371,12377,12382,12383,12386,12390,12400,12403,12404,12405,12412,12419,12422,12423,12428,12449,12452,12455,12462,12463,12466,12491,12494,12505,12508,12509,12512,12515,12516,12518,12536,12548,12549,12551,12557,12559,12560,12566,12568,12573,12577,12580,12581,12583,12586,12588,12589,12591,12593,12596,12599,12601,12604,12605,12611,12613,12623,12627,12629,12634,12635,12640,12643,12646,12652,12653,12655,12658,12662,12664,12665,12666,12670,12672,12674,12677,12681,12689,12692,12693,12695,12713,12715,12717,12718,12720,12729,12736,12738,12742,12745,12748,12757,12759,12760,12763,12767,12774,12793,12796,12800,12801,12804,12808,12813,12815,12821,12824,12826,12828,12829,12830,12833,12849,12865,12868,12871,12884,12888,12889,12892,12896,12904,12909,12911,12926,12933,12935,12942,12956,12957,12958,12966,12972,12975,12980,12982,12987,12988,12997,13006,13007,13008,13012,13013,13015,13016,13029,13031,13040,13046,13060,13068,13070,13076,13080,13085,13096,13097,13098,13105,13113,13116,13117,13120,13122,13130,13133,13137,13138,13148,13149,13171,13174,13175,13178,13182,13183,13184,13187,13189,13194,13196,13197,13215,13217,13219,13220,13227,13237,13238,13239,13247,13253,13261,13270,13278,13286,13287,13289,13291,13299,13302,13306,13314,13326,13348,13349,13350,13351,13354,13356,13357,13363,13367,13370,13392,13398,13402,13403,13407,13415,13417,13424,13425,13431,13433,13438,13445,13448,13465,13470,13477,13479,13484,13491,13505,13507,13523,13524,13527,13530,13531,13533,13536,13541,13544,13546,13553,13563,13568,13574,13581,13587,13596,13599,13605,13613,13618,13622,13629,13630,13633,13634,13639,13640,13643,13646,13661,13662,13669,13671,13675,13694,13703,13704,13706,13713,13720,13727,13731,13733,13764,13767,13775,13779,13785,13794,13795,13803,13805,13812,13820,13829,13843,13845,13852,13854,13859,13875,13876,13882,13883,13889,13894,13901,13903,13917,13925,13933,13937,13942,13951,13955,13961,13969,13970,13971,13976,13983,13986,13989,13994,14004,14007,14011,14022,14027,14044,14047,14051,14059,14061,14064,14066,14071,14072,14076,14082,14084,14088,14095,14097,14105,14112,14113,14114,14116,14117,14118,14122,14130,14135,14149,14150,14155,14156,14169,14177,14181,14188,14190,14191,14226,14232,14237,14238,14239,14246,14250,14253,14256,14262,14263,14267,14270,14272,14275,14283,14287,14290,14294,14302,14305,14308,14310,14315,14316,14319,14326,14344,14350,14353,14354,14368,14370,14377,14381,14382,14384,14387,14392,14403,14404,14411,14412,14418,14421,14426,14434,14437,14438,14440,14442,14444,14452,14459,14469,14473,14477,14486,14487,14489,14501,14514,14516,14518,14534,14539,14549,14555,14556,14570,14574,14587,14595,14604,14631,14638,14640,14641,14645,14652,14654,14658,14667,14668,14685,14688,14699,14700,14704,14706,14714,14726,14728,14732,14748,14750,14759,14766,14776,14777,14778,14790,14792,14793,14796,14800,14804,14805,14813,14814,14816,14822,14829,14837,14839,14846,14853,14861,14862,14871,14873,14887,14888,14890,14902,14909,14911,14921,14928,14934,14937,14944,14945,14956,14959,14977,14989,15000,15009,15014,15031,15034,15035,15037,15042,15050,15055,15064,15067,15068,15076,15078,15079,15092,15093,15094,15102,15105,15107,15115,15123,15128,15140,15141,15145,15152,15154,15162,15165,15167,15174,15182,15188,15190,15200,15205,15206,15208,15212,15216,15217,15218,15224,15228,15233,15236,15239,15256,15260,15263,15271,15283,15289,15294,15296,15301,15303,15312,15313,15344,15345,15346,15349,15353,15359,15365,15368,15369,15374,15386,15398,15422,15427,15429,15430,15433,15436,15440,15446,15451,15453,15454,15461,15463,15465,15466,15467,15468,15473,15475,15478,15489,15496,15514,15519,15520,15522,15529,15535,15542,15544,15546,15557,15558,15565,15567,15574,15584,15585,15592,15595,15621,15622,15625,15636,15639,15640,15642,15644,15645,15662,15672,15676,15678,15683,15685,15689,15690,15691,15692,15696,15700,15705,15712,15714,15728,15729,15741,15746,15747,15752,15755,15766,15767,15769,15771,15778,15782,15789,15794,15800,15809,15810,15814,15816,15820,15835,15839,15840,15846,15853,15858,15869,15884,15886,15889,15890,15902,15914,15919,15933,15934,15941,15945,15947,15949,15960,15963,15972,15979,16007,16011,16023,16024,16032,16036,16040,16046,16055,16056,16060,16067,16070,16075,16076,16082,16087,16094,16105,16119,16123,16124,16127,16132,16143,16153,16160,16165,16171,16172,16173,16181,16182,16186,16187,16192,16196,16203,16211,16212,16213,16214,16224,16232,16233,16235,16238,16241,16245,16247,16249,16251,16254,16260,16274,16277,16286,16288,16295,16299,16300,16307,16308,16311,16312,16326,16328,16330,16337,16342,16354,16361,16374,16376,16383,16384,16392,16395,16400,16401,16403,16411,16422,16431,16433,16435,16437,16442,16452,16457,16462,16463,16464,16472,16481,16485,16490,16497,16502,16507,16508,16513,16519,16521,16524,16525,16533,16544,16546,16548,16561,16562,16568,16577,16580,16582,16597,16599,16604,16607,16612,16616,16617,16619,16621,16631,16656,16660,16662,16663,16664,16666,16670,16673,16674,16678,16679,16683,16685,16704,16705,16706,16733,16734,16742,16751,16760,16766,16774,16786,16789,16801,16807,16810,16816,16821,16830,16832,16839,16849,16853,16859,16861,16867,16878,16890,16891,16898,16901,16903,16912,16920,16922,16927,16928,16931,16936,16939,16947,16949,16954,16958,16959,16965,16966,16969,16970,16973,16980,16985,16989,16998,17001,17005,17009,17015,17016,17018,17019,17027,17037,17054,17072,17075,17094,17096,17097,17100,17101,17106,17110,17113,17117,17127,17129,17134,17146,17162,17164,17165,17174,17175,17183,17184,17186,17189,17195,17196,17198,17205,17214,17217,17219,17222,17233,17235,17236,17242,17256,17268,17269,17270,17271,17279,17284,17294,17299,17302,17313,17321,17323,17324,17326,17328,17337,17340,17341,17347,17349,17351,17355,17357,17359,17361,17363,17374,17375,17383,17385,17386,17390,17395,17397,17404,17408,17432,17443,17444,17462,17463,17465,17472,17473,17479,17483,17490,17501,17509,17522,17546,17549,17551,17554,17560,17563,17565,17567,17570,17573,17575,17594,17595,17598,17606,17632,17633,17635,17642,17652,17653,17657,17664,17665,17667,17668,17669,17676,17678,17689,17691,17695,17697,17702,17711,17723,17731,17735,17736,17740,17743,17745,17749,17754,17761,17771,17778,17780,17784,17789,17796,17799,17800,17806,17823,17828,17834,17835,17843,17847,17853,17858,17862,17864,17865,17869,17871,17876,17880,17881,17890,17891,17897,17898,17907,17910,17920,17921,17929,17939,17943,17945,17951,17952,17958,17962,17966,17968,17972,17976,17980,17981,17986,17989,17991,17992,17994,18000,18001,18009,18010,18017,18027,18036,18042,18047,18064,18082,18091,18092,18106,18108,18115,18129,18131,18134,18140,18141,18144,18146,18150,18155,18160,18161,18163,18170,18175,18178,18187,18189,18190,18191,18193,18194,18214,18217,18220,18227,18233,18238,18241,18245,18256,18265,18273,18283,18286,18288,18289,18291,18299,18305,18308,18314,18319,18330,18331,18335,18357,18361,18367,18372,18373,18375,18376,18388,18389,18390,18399,18407,18408,18412,18423,18425,18433,18442,18446,18449,18452,18468,18469,18470,18480,18483,18490,18498,18502,18503,18504,18512,18529,18531,18532,18533,18542,18545,18554,18558,18560,18564,18581,18582,18585,18593,18596,18601,18605,18610,18612,18616,18618,18624,18625,18637,18638,18639,18644,18645,18649,18650,18653,18654,18665,18670,18671,18677,18680,18684,18685,18707,18714,18716,18722,18724,18732,18733,18739,18752,18758,18766,18769,18770,18786,18788,18795,18799,18806,18810,18811,18813,18818,18819,18827,18828,18839,18841,18855,18864,18866,18871,18872,18873,18879,18885,18897,18900,18901,18909,18911,18912,18921,18923,18943,18945,18949,18953,18965,18968,18971,18973,18978,18988,18989,18991,18993,18995,18997,19004,19009,19017,19029,19032,19033,19034,19038,19044,19053,19056,19075,19079,19086,19093,19095,19103,19109,19111,19113,19116,19119,19122,19123,19136,19137,19138,19140,19147,19150,19154,19155,19160,19169,19170,19172,19174,19180,19188,19189,19192,19196,19198,19200,19204,19214,19225,19234,19237,19248,19253,19262,19272,19273,19277,19282,19283,19289,19290,19296,19304,19306,19309,19310,19311,19316,19323,19327,19331,19332,19333,19334,19346,19347,19348,19350,19355,19358,19363,19364,19374,19376,19383,19385,19388,19395,19396,19404,19413,19414,19416,19417,19423,19425,19427,19428,19431,19433,19435,19436,19438,19444,19449,19455,19456,19462,19465,19466,19467,19475,19480,19488,19500,19505,19508,19513,19516,19519,19521,19524,19532,19533,19535,19542,19543,19548,19554,19556,19558,19566,19568,19571,19572,19581,19583,19585,19588,19597,19599,19604,19608,19610,19619,19625,19632,19635,19639,19645,19650,19652,19655,19662,19664,19667,19680,19682,19688,19691,19692,19704,19706,19707,19713,19719,19722,19726,19727,19728,19736,19754,19763,19766,19776,19783,19788,19789,19790,19792,19794,19797,19798,19807,19812,19813,19826,19827,19828,19830,19832,19833,19835,19836,19843,19846,19849,19851,19861,19866,19869,19871,19872,19873,19876,19883,19884,19888,19897,19911,19917,19920,19923,19928,19930,19932,19940,19945,19955,19956,19972,19983,19986,19998,20006,20010,20015,20022,20028,20030,20033,20036,20038,20045,20053,20084,20086,20087,20095,20098,20100,20101,20102,20111,20115,20118,20126,20138,20141,20142,20146,20147,20150,20153,20159,20183,20185,20189,20197,20203,20204,20211,20212,20213,20216,20220,20222,20225,20239,20250,20253,20259,20274,20284,20286,20293,20298,20308,20312,20324,20334,20356,20368,20385,20388,20393,20398,20401,20402,20404,20405,20409,20410,20413,20417,20426,20428,20431,20438,20440,20446,20449,20451,20457,20460,20461,20466,20470,20475,20477,20479,20482,20483,20484,20488,20489,20495,20497,20499,20500,20503,20528,20531,20532,20533,20538,20543,20547,20548,20549,20565,20567,20569,20574,20584,20587,20602,20607,20609,20617,20621,20625,20626,20637,20639,20646,20647,20651,20652,20653,20654,20656,20664,20665,20674,20678,20679,20684,20685,20690,20710,20717,20718,20726,20733,20735,20740,20758,20764,20776,20781,20788,20792,20800,20811,20815,20824,20826,20835,20845,20850,20852,20853,20854,20857,20861,20869,20870,20874,20877,20884,20903,20904,20905,20910,20928,20930,20931,20932,20936,20937,20940,20943,20947,20948,20953,20960,20962,20964,20968,20969,20984,20985,20989,20994,21006,21008,21010,21011,21021,21024,21037,21039,21041,21043,21051,21057,21063,21067,21070,21073,21077,21085,21091,21100,21107,21128,21132,21135,21136,21142,21147,21148,21155,21156,21159,21161,21163,21167,21170,21172,21175,21177,21187,21188,21192,21198,21206,21209,21212,21216,21231,21235,21243,21247,21251,21255,21259,21264,21266,21271,21276,21279,21294,21299,21300,21306,21311,21314,21316,21318,21320,21329,21337,21340,21354,21357,21372,21381,21385,21387,21391,21398,21400,21407,21408,21409,21423,21426,21436,21437,21441,21452,21453,21456,21457,21463,21467,21475,21478,21490,21498,21506,21510,21536,21540,21542,21545,21552,21557,21567,21569,21582,21588,21590,21595,21601,21607,21612,21620,21622,21624,21636,21637,21640,21646,21650,21651,21655,21665,21666,21672,21674,21692,21699,21706,21710,21712,21724,21733,21734,21737,21739,21741,21745,21747,21754,21758,21759,21760,21763,21765,21767,21772,21773,21780,21782,21784,21785,21798,21800,21806,21812,21813,21818,21820,21827,21829,21832,21836,21839,21851,21856,21862,21864,21870,21887,21897,21904,21907,21912,21920,21922,21923,21925,21931,21932,21936,21938,21939,21943,21947,21949,21951,21957,21960,21964,21967,21971,21976,21978,21979,21984,21998,22008,22009,22020,22021,22032,22033,22039,22046,22048,22054,22056,22062,22063,22065,22074,22078,22082,22086,22088,22093,22094,22098,22099,22100,22117,22121,22123,22124,22128,22138,22141,22151,22154,22162,22163,22170,22172,22174,22176,22195,22207,22208,22210,22211,22213,22217,22218,22226,22227,22241,22243,22244,22246,22266,22268,22272,22281,22285,22292,22297,22299,22300,22303,22306,22312,22313,22320,22326,22338,22342,22347,22360,22365,22367,22371,22375,22379,22381,22382,22383,22385,22386,22388,22392,22395,22400,22403,22414,22419,22421,22422,22425,22441,22443,22445,22465,22466,22471,22475,22476,22478,22481,22482,22486,22489,22500,22503,22505,22511,22515,22520,22524,22528,22530,22533,22537,22538,22548,22554,22558,22559,22564,22566,22570,22572,22574,22575,22589,22591,22592,22593,22596,22597,22603,22604,22606,22608,22619,22631,22639,22642,22643,22655,22662,22664,22665,22668,22673,22680,22682,22685,22693,22696,22697,22700,22701,22703,22713,22722,22730,22733,22736,22737,22749,22757,22760,22761,22765,22776,22782,22791,22810,22817,22834,22841,22848,22849,22852,22853,22859,22864,22877,22881,22885,22886,22887,22888,22891,22892,22899,22902,22903,22905,22916,22922,22937,22940,22960,22967,22971,22990,22991,22993,22994,23006,23021,23022,23029,23031,23032,23034,23035,23039,23055,23085,23086,23093,23102,23105,23107,23110,23114,23125,23144,23148,23150,23156,23169,23170,23186,23195,23207,23208,23210,23221,23231,23233,23234,23240,23241,23248,23258,23268,23269,23271,23273,23275,23277,23284,23285,23292,23295,23297,23302,23327,23330,23331,23333,23350,23351,23356,23359,23363,23369,23370,23372,23377,23383,23384,23385,23386,23394,23413,23425,23427,23433,23435,23436,23437,23438,23439,23444,23451,23467,23474,23475,23477,23478,23481,23484,23490,23491,23492,23499,23504,23509,23511,23514,23527,23528,23530,23546,23547,23548,23556,23558,23564,23566,23567,23569,23570,23571,23578,23579,23582,23592,23596,23607,23608,23611,23613,23617,23619,23620,23623,23626,23641,23653,23654,23666,23671,23673,23685,23688,23691,23695,23700,23701,23705,23708,23712,23714,23717,23721,23724,23731,23732,23736,23738,23739,23741,23744,23749,23752,23763,23768,23774,23778,23779,23781,23782,23785,23787,23790,23792,23808,23809,23811,23814,23815,23816,23818,23820,23832,23839,23842,23843,23847,23848,23854,23855,23859,23861,23863,23865,23866,23867,23870,23874,23885,23889,23890,23892,23895,23896,23905,23907,23909,23913,23922,23924,23926,23930,23936,23940,23942,23947,23952,23970,23983,23985,23994,23999,24004,24006,24017,24018,24032,24034,24036,24053,24054,24058,24063,24070,24075,24084,24085,24089,24091,24092,24108,24114,24123,24126,24128,24131,24136,24143,24149,24151,24153,24163,24167,24175,24181,24185,24190,24191,24192,24203,24204,24205,24208,24209,24217,24218,24223,24225,24226,24242,24246,24249,24256,24257,24262,24267,24282,24290,24291,24293,24295,24300,24301,24313,24314,24318,24320,24327,24328,24329,24330,24338,24344,24360,24368,24387,24395,24399,24400,24408,24414,24426,24429,24430,24432,24448,24456,24457,24463,24468,24470,24473,24476,24478,24487,24489,24492,24499,24504,24507,24509,24512,24517,24518,24522,24524,24526,24533,24547,24559,24560,24561,24563,24568,24572,24576,24577,24578,24580,24583,24586,24596,24604,24606,24607,24617,24625,24636,24649,24653,24657,24662,24678,24679,24683,24690,24691,24692,24696,24698,24700,24709,24711,24713,24715,24722,24728,24732,24734,24743,24746,24754,24763,24764,24769,24770,24772,24775,24777,24783,24788,24790,24793,24796,24817,24818,24829,24830,24834,24842,24859,24865,24867,24874,24879,24888,24889,24894,24901,24903,24904,24906,24921,24922,24943,24951,24952,24953,24955,24957,24959,24963,24964,24968,24971,24981,24982,24988,24998,25004,25006,25007,25018,25024,25027,25030,25033,25035,25051,25057,25058,25059,25061,25067,25075,25076,25077,25080,25084,25091,25115,25118,25124,25131,25134,25135,25139,25142,25157,25169,25170,25178,25180,25185,25188,25189,25196,25205,25210,25216,25219,25221,25237,25243,25244,25245,25257,25269,25271,25274,25283,25284,25289,25290,25299,25302,25305,25309,25311,25313,25321,25322,25324,25327,25331,25339,25351,25353,25354,25355,25357,25360,25362,25365,25373,25382,25388,25392,25401,25402,25405,25408,25414,25415,25422,25424,25425,25426,25429,25437,25440,25441,25447,25452,25455,25456,25464,25479,25484,25489,25494,25497,25499,25500,25501,25506,25512,25525,25527,25531,25533,25547,25558,25561,25563,25570,25583,25584,25592,25597,25599,25601,25602,25603,25605,25606,25617,25621,25625,25632,25637,25639,25642,25646,25647,25648,25653,25664,25673,25676,25677,25682,25686,25687,25688,25691,25694,25696,25709,25716,25717,25718,25721,25729,25730,25732,25733,25741,25757,25769,25779,25780,25785,25792,25801,25804,25806,25807,25810,25814,25816,25821,25828,25835,25842,25846,25847,25850,25852,25860,25862,25863,25867,25868,25874,25890,25893,25894,25896,25897,25907,25910,25912,25916,25920,25921,25926,25928,25946,25949,25953,25954,25960,25964,25971,25981,25983,25995,26000,26010,26013,26021,26031,26034,26036,26038,26055,26056,26058,26060,26061,26066,26067,26068,26075,26079,26084,26086,26088,26095,26096,26100,26103,26110,26115,26116,26118,26120,26130,26148,26150,26152,26169,26172,26176,26179,26183,26185,26190,26191,26193,26202,26204,26221,26231,26232,26234,26235,26237,26255,26258,26266,26272,26273,26274,26276,26278,26286,26291,26301,26307,26311,26314,26315,26317,26321,26328,26331,26333,26346,26347,26348,26356,26361,26368,26370,26374,26377,26380,26388,26392,26397,26400,26402,26406,26408,26412,26418,26435,26440,26445,26447,26454,26457,26463,26464,26467,26468,26475,26480,26485,26491,26493,26500,26501,26502,26503,26508,26523,26524,26526,26527,26531,26539,26540,26541,26543,26544,26546,26547,26560,26565,26579,26582,26588,26589,26590,26597,26602,26606,26617,26622,26626,26627,26652,26653,26654,26657,26661,26674,26676,26688,26700,26701,26702,26715,26716,26733,26739,26761,26764,26768,26775,26783,26784,26785,26786,26795,26799,26811,26812,26814,26816,26830,26832,26842,26845,26864,26872,26875,26882,26888,26890,26892,26893,26894,26897,26901,26904,26906,26907,26908,26910,26911,26912,26918,26919,26923,26929,26952,26954,26972,26975,26977,26980,26981,26986,26987,26991,26993,26996,27000,27009,27016,27025,27028,27030,27039,27048,27059,27061,27062,27066,27070,27071,27079,27093,27094,27102,27106,27113,27117,27126,27130,27132,27136,27147,27149,27150,27151,27152,27156,27163,27165,27166,27170,27179,27184,27188,27190,27192,27193,27194,27195,27200,27211,27220,27223,27224,27229,27234,27242,27249,27254,27258,27261,27262,27265,27270,27274,27293,27302,27308,27312,27314,27318,27326,27327,27330,27345,27352,27356,27363,27364,27367,27369,27371,27379,27392,27395,27398,27402,27418,27434,27437,27440,27441,27444,27449,27458,27459,27467,27471,27476,27478,27479,27491,27492,27496,27500,27501,27502,27504,27512,27514,27523,27527,27556,27567,27568,27571,27572,27573,27585,27591,27593,27594,27598,27599,27615,27616,27619,27622,27624,27626,27632,27638,27641,27644,27645,27647,27652,27658,27662,27664,27665,27669,27673,27674,27680,27682,27683,27687,27691,27695,27701,27703,27708,27714,27716,27720,27725,27726,27727,27729,27737,27741,27743,27745,27757,27767,27769,27776,27779,27791,27793,27798,27799,27802,27806,27807,27809,27818,27819,27821,27844,27860,27862,27871,27873,27875,27880,27884,27885,27898,27907,27908,27915,27919,27920,27926,27935,27937,27941,27958,27962,27965,27974,27982,27987,27990,27992,27993,27994,27995,28002,28007,28013,28019,28030,28031,28033,28034,28036,28038,28039,28042,28045,28046,28047,28048,28052,28074,28082,28091,28101,28104,28110,28111,28119,28124,28142,28144,28159,28160,28163,28168,28173,28175,28183,28184,28186,28188,28190,28191,28193,28200,28205,28220,28223,28226,28231,28232,28241,28244,28247,28259,28260,28265,28281,28284,28286,28293,28295,28296,28299,28300,28308,28314,28324,28327,28328,28330,28333,28337,28347,28367,28368,28369,28372,28373,28374,28378,28383,28386,28388,28399,28407,28414,28425,28426,28429,28431,28437,28439,28447,28454,28462,28467,28469,28473,28476,28480,28487,28489,28494,28497,28504,28511,28521,28529,28540,28542,28546,28551,28553,28559,28560,28562,28567,28574,28579,28594,28605,28606,28608,28609,28619,28622,28624,28626,28636,28644,28650,28652,28654,28655,28657,28662,28668,28671,28674,28676,28684,28696,28697,28699,28700,28702,28703,28704,28705,28706,28707,28722,28727,28730,28740,28742,28744,28753,28759,28767,28773,28777,28778,28790,28794,28795,28800,28805,28807,28812,28815,28817,28818,28824,28828,28829,28830,28836,28840,28841,28842,28843,28847,28848,28862,28875,28878,28879,28880,28882,28885,28886,28895,28907,28911,28912,28922,28925,28927,28935,28936,28940,28967,28968,28973,28979,28989,29003,29006,29011,29018,29023,29024,29026,29028,29046,29050,29051,29054,29064,29066,29078,29081,29086,29091,29097,29098,29102,29106,29111,29113,29114,29119,29124,29126,29139,29144,29154,29157,29162,29164,29169,29170,29179,29187,29188,29205,29207,29209,29220,29225,29228,29229,29231,29245,29247,29248,29255,29256,29270,29272,29278,29283,29288,29290,29295,29297,29298,29303,29308,29312,29317,29318,29321,29322,29327,29329,29330,29332,29338,29347,29358,29360,29380,29383,29389,29390,29392,29395,29404,29405,29406,29407,29408,29409,29410,29413,29417,29419,29422,29430,29431,29436,29437,29443,29448,29453,29458,29461,29474,29485,29491,29495,29496,29497,29507,29508,29510,29520,29522,29532,29536,29544,29546,29548,29566,29583,29587,29595,29597,29607,29612,29617,29619,29620,29624,29625,29626,29631,29640,29649,29656,29659,29662,29665,29668,29670,29671,29678,29679,29680,29701,29702,29709,29714,29720,29726,29730,29733,29736,29737,29739,29740,29747,29751,29758,29759,29779,29787,29791,29792,29795,29801,29804,29808,29813,29814,29819,29823,29830,29832,29835,29836,29839,29840,29845,29846,29847,29848,29849,29851,29852,29856,29858,29861,29868,29871,29877,29878,29886,29889,29892,29912,29913,29925,29932,29937,29938,29939,29943,29944,29945,29949,29958,29960,29965,29976,29984,29985,29986,29988,29989,29994,29997,29998,30003,30009,30013,30016,30020,30022,30035,30036,30040,30041,30047,30051,30052,30056,30060,30065,30066,30081,30086,30096,30103,30107,30112,30114,30123,30128,30131,30132,30134,30136,30140,30142,30143,30147,30154,30156,30165,30173,30177,30191,30195,30210,30211,30220,30223,30228,30229,30238,30239,30253,30258,30262,30265,30266,30289,30291,30302,30303,30315,30317,30318,30326,30328,30331,30344,30345,30348,30351,30361,30367,30372,30374,30378,30383,30393,30398,30404,30411,30412,30414,30416,30419,30420,30426,30432,30435,30438,30439,30458,30459,30462,30464,30466,30467,30475,30494,30498,30502,30515,30516,30520,30526,30531,30538,30541,30547,30548,30551,30558,30561,30573,30582,30589,30598,30599,30605,30610,30611,30616,30623,30628,30636,30654,30661,30663,30665,30668,30671,30673,30674,30677,30678,30680,30689,30702,30703,30706,30710,30720,30726,30731,30733,30735,30741,30748,30750,30751,30754,30755,30756,30759,30762,30763,30767,30768,30770,30771,30774,30776,30782,30786,30793,30800,30802,30816,30819,30821,30822,30823,30824,30829,30830,30838,30841,30842,30844,30847,30854,30855,30858,30861,30862,30865,30869,30886,30901,30904,30906,30910,30912,30913,30914,30915,30916,30918,30923,30926,30930,30940,30946,30961,30962,30964,30973,30976,30977,30982,30987,30990,30992,30993,30994,30999,31000,31003,31013,31017,31019,31030,31031,31032,31044,31048,31050,31051,31054,31060,31068,31084,31091,31102,31115,31125,31128,31144,31153,31155,31158,31167,31171,31181,31191,31200,31207,31209,31216,31217,31230,31236,31240,31247,31249,31257,31258,31268,31269,31276,31279,31283,31291,31297,31298,31304,31305,31310,31313,31317,31321,31324,31326,31333,31337,31338,31351,31352,31357,31364,31365,31368,31388,31393,31394,31395,31409,31418,31420,31427,31436,31438,31440,31445,31458,31467,31472,31476,31482,31487,31489,31498,31515,31522,31524,31528,31533,31536,31537,31543,31544,31545,31556,31568,31582,31588,31592,31604,31608,31609,31610,31613,31626,31630,31633,31645,31653,31659,31660,31663,31670,31695,31697,31698,31702,31705,31707,31708,31711,31716,31720,31731,31734,31738,31747,31749,31754,31760,31765,31777,31783,31788,31793,31796,31810,31811,31814,31815,31819,31829,31830,31831,31832,31842,31843,31853,31854,31857,31859,31864,31867,31868,31871,31877,31879,31883,31894,31900,31902,31910,31913,31920,31922,31925,31926,31929,31937,31943,31948,31957,31959,31965,31971,31972,31976,31982,31987,31989,31990,31999,32001,32002,32003,32012,32013,32026,32027,32030,32034,32040,32047,32051,32053,32054,32055,32065,32068,32069,32070,32073,32082,32085,32095,32100,32118,32121,32124,32129,32130,32132,32134,32140,32150,32153,32158,32162,32163,32170,32176,32185,32188,32198,32200,32202,32203,32206,32207,32208,32210,32217,32220,32227,32228,32237,32240,32243,32249,32256,32257,32258,32259,32261,32272,32278,32280,32283,32284,32287,32290,32296,32299,32300,32301,32302,32304,32309,32314,32320,32322,32323,32329,32337,32339,32347,32351,32360,32362,32370,32373,32382,32386,32390,32392,32400,32401,32402,32406,32409,32417,32418,32419,32420,32423,32431,32437,32439,32444,32447,32449,32452,32453,32454,32456,32462,32464,32466,32467,32471,32473,32483,32484,32497,32508,32513,32516,32522,32526,32541,32547,32551,32554,32556,32557,32561,32562,32563,32571,32574,32576,32581,32585,32591,32599,32604,32609,32622,32623,32629,32632,32634,32640,32648,32649,32652,32654,32656,32663,32666,32674,32677,32678,32682,32687,32696,32697,32699,32717,32725,32730,32733,32734,32741,32746,32750,32752,32758,32759,32765,32766,32770,32781,32791,32797,32799,32804,32811,32822,32823,32842,32845,32852,32860,32867,32870,32872,32878,32890,32891,32893,32894,32904,32905,32906,32908,32912,32929,32931,32946,32953,32956,32957,32964,32968,32974,32979,32980,32987,33004,33009,33019,33022,33026,33028,33030,33033,33043,33044,33050,33076,33078,33079,33080,33084,33085,33096,33103,33108,33113,33115,33120,33121,33127,33129,33137,33144,33148,33167,33172,33177,33178,33181,33185,33193,33198,33201,33208,33214,33219,33221,33222,33227,33230,33234,33236,33237,33239,33249,33253,33261,33262,33266,33269,33271,33272,33273,33274,33282,33294,33296,33298,33305,33315,33328,33331,33334,33337,33351,33352,33358,33360,33371,33381,33384,33388,33389,33390,33400,33403,33406,33407,33409,33410,33412,33426,33429,33430,33431,33446,33448,33464,33467,33472,33474,33475,33477,33484,33487,33491,33492,33495,33500,33505,33508,33510,33511,33517,33523,33530,33531,33534,33544,33547,33555,33559,33567,33574,33576,33586,33590,33593,33609,33614,33616,33625,33647,33651,33652,33653,33654,33671,33672,33674,33675,33681,33684,33686,33695,33705,33706,33708,33709,33710,33716,33728,33730,33738,33746,33770,33776,33788,33791,33793,33794,33795,33801,33803,33807,33808,33827,33831,33833,33837,33840,33842,33844,33845,33854,33855,33857,33865,33867,33869,33872,33873,33878,33879,33884,33898,33900,33901,33907,33910,33926,33928,33934,33936,33937,33943,33951,33952,33954,33955,33956,33961,33968,33976,33988,33998,34001,34006,34008,34011,34018,34027,34028,34032,34034,34042,34050,34059,34070,34071,34075,34080,34081,34082,34085,34089,34095,34104,34111,34118,34120,34122,34124,34129,34130,34135,34137,34138,34139,34146,34148,34154,34158,34160,34172,34174,34182,34187,34188,34189,34191,34192,34204,34211,34212,34219,34220,34221,34225,34226,34228,34231,34236,34246,34249,34251,34256,34270,34274,34289,34292,34294,34295,34301,34304,34306,34316,34324,34331,34337,34347,34350,34354,34358,34362,34363,34378,34386,34389,34392,34405,34412,34416,34417,34418,34421,34423,34432,34434,34437,34446,34454,34456,34458,34463,34464,34476,34482,34487,34492,34493,34497,34499,34502,34505,34506,34508,34514,34516,34528,34543,34544,34548,34567,34568,34571,34572,34580,34582,34583,34587,34592,34594,34618,34621,34625,34626,34630,34633,34636,34644,34661,34668,34678,34683,34684,34686,34691,34702,34706,34708,34709,34710,34712,34713,34714,34715,34717,34721,34724,34725,34730,34735,34749,34755,34758,34764,34768,34781,34783,34798,34799,34804,34808,34815,34818,34824,34827,34833,34848,34851,34857,34864,34867,34885,34890,34897,34916,34919,34920,34926,34935,34940,34942,34949,34950,34952,34953,34954,34957,34965,34971,34981,34993,34994,34995,34997,34998,35000,35004,35013,35024,35030,35033,35040,35042,35044,35048,35056,35064,35074,35083,35086,35087,35090,35097,35101,35103,35104,35113,35116,35127,35135,35138,35139,35144,35155,35162,35164,35165,35180,35188,35191,35192,35198,35202,35206,35211,35215,35223,35225,35232,35239,35250,35259,35260,35262,35269,35281,35283,35284,35292,35295,35298,35304,35306,35311,35314,35322,35326,35328,35330,35343,35353,35364,35365,35378,35392,35393,35398,35401,35402,35417,35425,35431,35433,35439,35450,35455,35457,35463,35464,35467,35472,35475,35478,35500,35507,35514,35515,35520,35532,35534,35545,35552,35558,35559,35560,35565,35572,35573,35583,35593,35600,35611,35613,35616,35623,35627,35642,35646,35647,35654,35655,35663,35664,35665,35666,35667,35671,35677,35679,35681,35695,35697,35700,35721,35727,35731,35732,35733,35738,35752,35758,35776,35777,35779,35785,35786,35789,35794,35800,35810,35814,35828,35831,35832,35837,35840,35841,35849,35851,35854,35861,35877,35880,35884,35885,35891,35900,35901,35905,35909,35910,35913,35918,35924,35938,35942,35948,35951,35973,35974,35976,35978,35980,36001,36002,36008,36009,36013,36016,36017,36020,36022,36027,36028,36031,36037,36044,36048,36049,36050,36051,36052,36059,36063,36080,36086,36090,36093,36094,36095,36097,36101,36103,36108,36109,36110,36115,36116,36121,36122,36123,36124,36131,36136,36139,36147,36155,36167,36168,36175,36187,36190,36193,36195,36196,36197,36204,36208,36211,36224,36232,36234,36235,36242,36253,36257,36264,36273,36280,36281,36284,36300,36303,36306,36307,36308,36311,36318,36320,36321,36322,36323,36326,36329,36330,36335,36336,36339,36347,36353,36358,36360,36361,36371,36378,36391,36398,36400,36406,36407,36412,36420,36423,36427,36431,36432,36436,36439,36446,36457,36461,36468,36480,36493,36511,36516,36519,36530,36534,36535,36536,36539,36544,36545,36548,36564,36565,36569,36573,36576,36579,36580,36611,36617,36625,36628,36638,36644,36646,36659,36660,36666,36667,36668,36671,36672,36685,36689,36690,36698,36699,36704,36706,36709,36717,36722,36724,36727,36729,36743,36751,36754,36764,36766,36768,36773,36774,36777,36789,36790,36792,36797,36798,36802,36804,36805,36806,36809,36810,36848,36855,36856,36860,36863,36864,36865,36869,36870,36873,36876,36879,36880,36884,36891,36900,36901,36910,36916,36922,36932,36933,36936,36953,36955,36957,36958,36959,36960,36968,36973,36976,36977,36986,36988,36992,36995,36996,36998,37000,37002,37005,37013,37029,37037,37038,37044,37052,37054,37065,37074,37076,37078,37080,37086,37089,37091,37095,37109,37111,37114,37116,37128,37130,37131,37138,37146,37148,37160,37163,37164,37165,37171,37174,37176,37185,37200,37201,37202,37206,37216,37244,37251,37260,37269,37273,37279,37283,37285,37286,37287,37290,37294,37306,37307,37308,37313,37318,37332,37345,37346,37350,37352,37353,37358,37360,37376,37377,37379,37386,37394,37402,37414,37417,37421,37435,37447,37452,37455,37458,37459,37460,37467,37468,37473,37475,37486,37487,37497,37509,37511,37512,37520,37529,37544,37545,37554,37558,37564,37568,37571,37575,37584,37588,37589,37598,37602,37608,37616,37632,37635,37644,37648,37654,37677,37681,37686,37687,37695,37696,37697,37704,37711,37717,37719,37721,37722,37723,37727,37732,37734,37737,37743,37750,37755,37756,37763,37765,37766,37768,37772,37776,37781,37797,37803,37814,37815,37829,37841,37863,37870,37881,37887,37898,37899,37906,37908,37910,37912,37914,37919,37927,37932,37936,37942,37956,37958,37979,37982,37985,37990,37996,38000,38009,38010,38021,38030,38037,38038,38042,38060,38061,38062,38064,38070,38071,38075,38092,38094,38099,38100,38101,38106,38112,38132,38135,38136,38137,38141,38146,38148,38152,38159,38160,38161,38163,38174,38176,38179,38182,38186,38187,38192,38206,38209,38210,38240,38243,38244,38247,38248,38254,38260,38264,38267,38269,38270,38272,38276,38282,38287,38288,38292,38294,38296,38297,38299,38305,38314,38315,38316,38318,38325,38332,38335,38336,38337,38340,38342,38349,38356,38358,38364,38370,38371,38372,38375,38392,38396,38398,38401,38407,38421,38422,38425,38431,38433,38436,38437,38447,38451,38457,38465,38469,38471,38474,38479,38480,38483,38493,38496,38501,38510,38513,38526,38538,38541,38544,38545,38546,38550,38555,38569,38570,38578,38582,38589,38596,38597,38600,38601,38604,38606,38617,38621,38623,38624,38628,38631,38638,38643,38644,38646,38648,38654,38657,38676,38692,38697,38705,38709,38712,38714,38716,38728,38729,38731,38735,38740,38742,38743,38744,38749,38752,38758,38760,38761,38767,38785,38791,38792,38796,38797,38798,38800,38801,38803,38804,38817,38827,38830,38846,38852,38853,38867,38873,38904,38909,38912,38914,38917,38919,38920,38927,38930,38934,38936,38940,38949,38967,38977,38979,38980,38982,38986,38992,38993,39003,39012,39014,39019,39020,39021,39029,39038,39041,39064,39068,39074,39094,39105,39109,39113,39114,39116,39119,39120,39121,39126,39128,39132,39133,39138,39140,39143,39146,39152,39155,39156,39157,39159,39162,39165,39167,39176,39182,39184,39198,39209,39211,39213,39214,39217,39218,39224,39228,39230,39237,39240,39242,39245,39250,39253,39257,39260,39262,39264,39269,39273,39286,39294,39297,39299,39302,39303,39305,39310,39316,39318,39319,39322,39325,39327,39329,39334,39336,39339,39340,39341,39342,39349,39351,39366,39368,39370,39380,39388,39393,39397,39399,39401,39406,39407,39413,39416,39420,39425,39433,39435,39444,39446,39448,39453,39460,39461,39462,39463,39466,39468,39473,39477,39478,39489,39490,39494,39508,39510,39512,39514,39515,39517,39532,39535,39537,39538,39542,39543,39544,39553,39554,39555,39557,39562,39564,39565,39572,39575,39578,39582,39593,39601,39608,39619,39622,39625,39629,39630,39634,39636,39638,39646,39647,39650,39652,39655,39656,39661,39668,39670,39671,39675,39679,39682,39686,39688,39690,39691,39701,39702,39703,39712,39715,39719,39728,39748,39754,39755,39759,39766,39767,39779,39780,39784,39792,39794,39798,39801,39804,39809,39810,39820,39821,39826,39828,39829,39831,39832,39835,39836,39853,39854,39857,39865,39867,39873,39874,39876,39877,39882,39883,39897,39899,39901,39918,39926,39932,39945,39957,39967,39969,39975,39978,39985,39989,39993,39994,39997,39999,40000,40002,40007,40013,40017,40025,40027,40028,40031,40032,40042,40061,40069,40072,40075,40076,40079,40081,40083,40084,40085,40088,40092,40097,40099,40100,40101,40106,40111,40123,40125,40127,40133,40135,40148,40150,40155,40158,40159,40162,40170,40180,40185,40189,40191,40194,40199,40201,40202,40207,40212,40217,40228,40237,40238,40247,40256,40257,40260,40263,40265,40269,40272,40273,40280,40281,40289,40291,40296,40299,40300,40301,40303,40313,40324,40332,40335,40339,40342,40353,40354,40355,40365,40366,40367,40372,40390,40393,40402,40403,40419,40426,40428,40433,40442,40444,40458,40461,40467,40477,40489,40495,40512,40513,40514,40519,40521,40524,40529,40530,40541,40542,40548,40550,40555,40560,40567,40569,40570,40571,40575,40580,40588,40591,40594,40595,40604,40606,40610,40613,40614,40626,40627,40634,40636,40638,40643,40646,40647,40652,40660,40665,40673,40674,40679,40686,40688,40689,40693,40695,40698,40700,40702,40705,40708,40715,40718,40727,40737,40747,40753,40754,40755,40757,40760,40772,40776,40779,40781,40789,40797,40802,40803,40810,40813,40823,40831,40837,40847,40848,40856,40859,40861,40863,40871,40874,40884,40893,40894,40902,40911,40913,40915,40916,40924,40926,40932,40935,40936,40940,40942,40951,40952,40958,40959,40961,40978,40984,40991,40999,41000,41005,41007,41011,41018,41027,41028,41035,41036,41038,41043,41052,41061,41071,41072,41081,41082,41084,41085,41088,41089,41092,41103,41106,41107,41110,41118,41123,41128,41143,41147,41148,41150,41152,41167,41172,41173,41175,41183,41197,41199,41208,41211,41213,41228,41234,41238,41262,41269,41271,41280,41282,41283,41290,41307,41316,41317,41318,41323,41327,41330,41335,41337,41338,41340,41343,41350,41357,41363,41372,41380,41384,41398,41399,41400,41410,41436,41442,41445,41448,41455,41458,41476,41484,41488,41499,41502,41506,41507,41509,41511,41512,41513,41516,41521,41525,41527,41534,41535,41547,41551,41555,41561,41562,41567,41568,41570,41573,41578,41579,41597,41598,41601,41603,41608,41609,41616,41621,41630,41632,41633,41649,41658,41681,41687,41688,41689,41692,41694,41697,41710,41711,41715,41718,41721,41723,41735,41736,41738,41744,41747,41748,41757,41761,41763,41765,41774,41780,41782,41783,41804,41812,41815,41817,41822,41827,41831,41835,41836,41844,41850,41856,41860,41862,41863,41865,41867,41873,41875,41876,41878,41881,41883,41888,41907,41911,41916,41922,41928,41939,41946,41952,41955,41964,41966,41970,41982,41990,41994,41996,41999,42004,42006,42016,42020,42021,42034,42046,42047,42055,42058,42060,42070,42074,42080,42084,42085,42089,42091,42092,42105,42117,42120,42128,42136,42151,42157,42159,42164,42175,42190,42191,42194,42198,42204,42210,42211,42217,42221,42235,42238,42240,42242,42247,42251,42252,42260,42261,42267,42269,42272,42279,42284,42289,42295,42309,42314,42318,42321,42328,42329,42332,42333,42338,42340,42343,42346,42360,42361,42378,42379,42380,42394,42396,42397,42407,42410,42411,42417,42421,42434,42435,42436,42458,42461,42463,42469,42473,42474,42480,42482,42483,42485,42495,42518,42521,42522,42527,42528,42533,42537,42544,42546,42553,42555,42562,42564,42568,42575,42577,42578,42587,42590,42596,42601,42603,42609,42611,42616,42619,42620,42626,42635,42636,42640,42642,42652,42658,42659,42673,42680,42685,42688,42691,42696,42701,42708,42710,42712,42714,42716,42741,42742,42744,42754,42760,42762,42766,42767,42772,42776,42783,42785,42787,42790,42792,42795,42801,42804,42812,42816,42819,42821,42827,42828,42829,42830,42832,42838,42841,42842,42844,42854,42856,42857,42863,42867,42871,42874,42880,42881,42885,42887,42897,42911,42915,42919,42923,42930,42938,42940,42950,42970,42973,42978,42983,42993,42994,43002,43003,43005,43015,43017,43021,43026,43031,43045,43049,43050,43053,43055,43056,43062,43066,43068,43070,43073,43076,43077,43081,43088,43098,43107,43109,43130,43131,43132,43136,43140,43142,43146,43155,43167,43177,43189,43191,43197,43198,43200,43203,43205,43210,43216,43218,43220,43224,43235,43239,43241,43246,43255,43257,43264,43274,43276,43278,43281,43285,43291,43293,43294,43313,43317,43318,43320,43322,43323,43332,43334,43338,43343,43352,43353,43363,43369,43371,43373,43378,43380,43383,43385,43396,43397,43403,43423,43428,43429,43436,43446,43458,43469,43470,43478,43482,43483,43485,43494,43499,43514,43538,43540,43543,43548,43551,43553,43562,43569,43572,43583,43585,43588,43589,43591,43593,43594,43600,43620,43621,43625,43628,43630,43631,43632,43635,43637,43638,43643,43647,43648,43649,43656,43658,43659,43667,43668,43673,43686,43694,43695,43706,43707,43733,43736,43737,43738,43743,43747,43751,43754,43765,43766,43770,43774,43778,43782,43785,43786,43787,43791,43795,43799,43802,43804,43806,43807,43812,43819,43823,43824,43827,43829,43831,43839,43845,43851,43852,43862,43873,43876,43882,43886,43888,43892,43911,43923,43929,43934,43936,43938,43942,43948,43965,43966,43971,43973,43975,43993,43996,44001,44002,44004,44007,44012,44013,44018,44022,44025,44027,44028,44033,44037,44043,44049,44050,44068,44082,44091,44092,44095,44097,44101,44104,44112,44117,44119,44121,44123,44126,44132,44141,44144,44156,44179,44182,44191,44195,44196,44202,44205,44209,44213,44218,44222,44223,44238,44256,44259,44261,44262,44271,44283,44287,44289,44291,44292,44293,44299,44301,44309,44311,44327,44330,44331,44333,44334,44341,44359,44364,44373,44374,44379,44380,44390,44392,44396,44399,44403,44416,44419,44429,44434,44435,44437,44446,44454,44457,44461,44463,44464,44474,44479,44480,44481,44482,44492,44503,44511,44513,44520,44521,44547,44552,44555,44558,44568,44578,44584,44592,44594,44599,44606,44608,44612,44622,44624,44626,44632,44639,44641,44642,44643,44648,44657,44658,44674,44676,44679,44684,44687,44691,44692,44693,44709,44711,44714,44718,44720,44726,44730,44739,44748,44754,44760,44776,44777,44781,44786,44787,44791,44796,44799,44800,44802,44803,44805,44808,44813,44815,44818,44822,44825,44831,44834,44836,44838,44844,44848,44856,44861,44867,44876,44880,44881,44912,44917,44926,44934,44940,44941,44947,44961,44962,44963,44972,44981,44983,44990,44993,44996,45001,45003,45006,45011,45012,45017,45024,45031,45041,45044,45047,45051,45054,45058,45060,45069,45071,45073,45083,45090,45095,45099,45113,45123,45131,45133,45138,45143,45145,45146,45152,45164,45167,45172,45173,45174,45176,45182,45186,45200,45201,45203,45205,45210,45212,45227,45229,45232,45237,45243,45249,45253,45255,45279,45280,45282,45284,45285,45287,45295,45300,45303,45305,45323,45329,45331,45332,45336,45338,45339,45343,45347,45352,45354,45356,45361,45364,45365,45368,45372,45373,45377,45380,45385,45387,45403,45409,45415,45423,45429,45432,45448,45449,45453,45455,45457,45460,45464,45469,45471,45476,45477,45486,45489,45493,45504,45508,45517,45519,45530,45533,45534,45537,45539,45545,45550,45553,45558,45560,45569,45576,45578,45581,45595,45596,45600,45603,45605,45606,45608,45627,45642,45647,45649,45651,45656,45665,45668,45669,45676,45692,45718,45720,45721,45730,45731,45737,45741,45747,45749,45758,45768,45783,45784,45786,45787,45797,45798,45802,45805,45807,45829,45830,45832,45835,45838,45844,45848,45853,45855,45857,45860,45872,45874,45893,45894,45897,45903,45909,45912,45916,45922,45929,45934,45941,45944,45955,45956,45963,45966,45969,45977,45981,45984,45987,45988,45995,45996,45997,45998,46009,46016,46020,46023,46028,46032,46033,46046,46050,46053,46058,46061,46065,46068,46071,46082,46090,46098,46099,46104,46117,46118,46121,46122,46124,46131,46134,46138,46147,46155,46156,46161,46165,46167,46172,46179,46187,46191,46192,46193,46196,46198,46204,46213,46222,46224,46226,46229,46233,46238,46244,46245,46246,46253,46254,46257,46285,46286,46287,46293,46295,46297,46299,46303,46305,46307,46308,46311,46325,46327,46335,46350,46356,46364,46367,46368,46370,46378,46388,46391,46398,46403,46410,46412,46415,46421,46424,46425,46428,46433,46437,46439,46444,46451,46453,46460,46462,46464,46466,46470,46471,46481,46486,46495,46498,46500,46507,46517,46532,46534,46540,46563,46564,46565,46573,46577,46580,46593,46594,46610,46616,46618,46626,46630,46634,46651,46688,46690,46692,46693,46695,46697,46701,46704,46731,46734,46742,46745,46766,46773,46776,46777,46784,46789,46795,46804,46819,46824,46829,46831,46839,46847,46850,46852,46855,46856,46866,46879,46885,46890,46894,46895,46902,46911,46915,46918,46924,46928,46934,46935,46937,46941,46942,46946,46955,46956,46958,46963,46964,46967,46970,46973,47004,47007,47022,47026,47029,47039,47040,47042,47046,47048,47070,47106,47109,47110,47116,47120,47123,47126,47129,47141,47142,47148,47149,47152,47157,47163,47169,47174,47190,47193,47194,47207,47217,47219,47221,47225,47238,47247,47248,47251,47256,47260,47261,47262,47274,47286,47289,47294,47296,47297,47304,47305,47318,47329,47330,47335,47340,47347,47361,47367,47368,47373,47376,47378,47381,47390,47401,47407,47409,47412,47413,47427,47434,47435,47436,47439,47445,47452,47457,47461,47462,47465,47466,47468,47476,47480,47481,47494,47498,47501,47502,47506,47508,47509,47510,47511,47513,47514,47516,47525,47545,47549,47556,47565,47567,47568,47570,47572,47589,47595,47597,47604,47607,47615,47628,47637,47638,47645,47647,47651,47654,47664,47667,47668,47671,47678,47680,47682,47689,47691,47692,47701,47707,47725,47734,47736,47737,47745,47746,47754,47771,47773,47776,47779,47785,47791,47794,47798,47804,47808,47811,47815,47818,47820,47829,47831,47838,47845,47852,47853,47861,47864,47868,47869,47870,47874,47878,47881,47887,47890,47901,47902,47912,47915,47918,47929,47933,47934,47936,47946,47952,47954,47971,47977,47980,47997,48003,48008,48017,48018,48020,48024,48034,48043,48049,48053,48056,48066,48067,48068,48073,48078,48080,48083,48091,48092,48095,48097,48099,48110,48113,48119,48122,48126,48127,48137,48145,48147,48156,48157,48196,48213,48215,48216,48222,48229,48234,48237,48239,48242,48243,48261,48264,48267,48273,48274,48275,48281,48295,48306,48312,48315,48318,48326,48328,48334,48337,48345,48351,48354,48355,48359,48367,48370,48372,48374,48380,48392,48394,48396,48413,48417,48424,48426,48436,48438,48440,48447,48451,48457,48463,48466,48470,48472,48482,48509,48520,48521,48524,48527,48528,48537,48538,48545,48546,48547,48551,48557,48561,48569,48584,48598,48604,48607,48611,48612,48618,48620,48621,48624,48627,48645,48660,48661,48668,48676,48678,48688,48689,48690,48708,48714,48717,48721,48723,48730,48745,48746,48747,48756,48757,48763,48766,48774,48775,48781,48788,48790,48799,48804,48809,48810,48812,48820,48821,48836,48837,48841,48843,48844,48849,48859,48862,48863,48865,48888,48889,48890,48907,48921,48933,48935,48939,48949,48953,48966,48972,48975,48978,48982,48983,48985,48992,48993,48998,49000,49003,49006,49015,49023,49025,49029,49037,49045,49049,49056,49065,49067,49073,49083,49084,49094,49102,49126,49127,49130,49131,49135,49138,49142,49146,49161,49163,49165,49170,49186,49189,49192,49196,49202,49205,49215,49221,49224,49225,49229,49230,49251,49252,49253,49260,49268,49270,49274,49279,49285,49287,49295,49296,49308,49309,49315,49327,49330,49337,49347,49362,49364,49370,49373,49378,49398,49401,49407,49411,49413,49418,49425,49431,49439,49442,49443,49449,49456,49466,49467,49477,49479,49485,49486,49487,49488,49492,49493,49495,49497,49498,49503,49505,49508,49513,49519,49526,49528,49533,49534,49539,49544,49547,49549,49551,49559,49561,49565,49566,49570,49583,49586,49595,49603,49605,49619,49620,49622,49626,49635,49636,49646,49650,49663,49664,49668,49670,49671,49685,49686,49697,49698,49708,49709,49725,49731,49735,49744,49747,49750,49755,49760,49763,49765,49766,49767,49780,49781,49793,49794,49795,49798,49800,49807,49818,49821,49824,49831,49834,49845,49862,49867,49879,49888,49890,49897,49899,49904,49905,49906,49910,49911,49919,49920,49923,49933,49934,49936,49951,49962,49972,49976,49979,49981,49983,49987,49996,50008,50021,50024,50025,50026,50033,50034,50036,50039,50053,50054,50056,50059,50062,50063,50070,50078,50080,50083,50086,50088,50094,50095,50106,50107,50109,50111,50126,50128,50138,50141,50153,50154,50158,50161,50163,50166,50174,50175,50201,50217,50223,50230,50234,50242,50248,50253,50259,50260,50261,50264,50271,50272,50273,50281,50293,50296,50310,50316,50322,50326] \ No newline at end of file diff --git a/cardano-chain-gen/bench/benchfiles/fingerprint/emptyBlock_50 b/cardano-chain-gen/bench/benchfiles/fingerprint/emptyBlock_50 new file mode 100644 index 000000000..fb966492b --- /dev/null +++ b/cardano-chain-gen/bench/benchfiles/fingerprint/emptyBlock_50 @@ -0,0 +1 @@ +[0,1,9,14,23,28,29,31,34,69,74,75,80,82,84,88,95,98,104,106,108,113,115,127,129,144,146,147,151,153,161,163,171,176,177,178,179,186,189,195,197,198,204,207,210,211,212,213,219,222] \ No newline at end of file diff --git a/cardano-chain-gen/bench/benchfiles/fingerprint/emptyBlock_500 b/cardano-chain-gen/bench/benchfiles/fingerprint/emptyBlock_500 new file mode 100644 index 000000000..ba054d4ce --- /dev/null +++ b/cardano-chain-gen/bench/benchfiles/fingerprint/emptyBlock_500 @@ -0,0 +1 @@ +[0,1,9,14,23,28,29,31,34,69,74,75,80,82,84,88,95,98,104,106,108,113,115,127,129,144,146,147,151,153,161,163,171,176,177,178,179,186,189,195,197,198,204,207,210,211,212,213,219,222,226,233,241,252,265,266,274,290,291,294,295,298,304,305,309,312,314,317,326,328,329,332,333,336,346,351,352,357,365,367,385,387,391,400,401,404,411,413,414,424,427,430,436,444,449,455,458,460,461,462,473,474,476,477,482,491,497,498,499,502,506,507,514,521,547,563,566,575,578,581,594,599,602,607,614,623,631,638,639,641,649,652,653,654,665,666,670,672,673,682,683,688,692,696,700,701,708,710,714,725,735,737,746,750,763,772,776,783,793,795,797,802,804,817,818,822,824,826,827,832,834,836,841,847,851,855,861,868,870,873,876,877,882,883,891,894,905,908,913,915,925,934,942,943,949,956,960,967,968,974,980,987,998,1002,1004,1005,1012,1016,1019,1022,1023,1035,1036,1037,1039,1040,1051,1057,1058,1061,1064,1067,1074,1089,1091,1094,1096,1099,1104,1105,1107,1109,1121,1125,1133,1140,1145,1147,1148,1150,1153,1155,1159,1160,1172,1179,1185,1187,1194,1195,1201,1202,1211,1212,1216,1217,1221,1223,1233,1234,1235,1240,1241,1243,1250,1253,1259,1272,1273,1278,1280,1286,1289,1295,1298,1304,1310,1313,1320,1325,1328,1331,1332,1361,1379,1380,1382,1398,1402,1408,1411,1433,1436,1438,1449,1453,1454,1464,1468,1469,1480,1481,1482,1485,1492,1502,1504,1506,1512,1519,1524,1534,1537,1544,1545,1553,1559,1564,1565,1571,1578,1580,1583,1586,1587,1594,1597,1599,1605,1606,1609,1611,1613,1617,1623,1627,1630,1633,1634,1635,1640,1650,1655,1664,1666,1668,1670,1674,1682,1683,1684,1687,1697,1702,1710,1711,1712,1715,1718,1729,1739,1745,1750,1754,1757,1762,1775,1781,1794,1797,1801,1803,1808,1809,1812,1814,1820,1824,1825,1827,1832,1836,1854,1858,1865,1869,1872,1888,1890,1891,1892,1895,1905,1911,1917,1920,1921,1922,1928,1933,1943,1944,1962,1987,1992,1994,1998,2003,2008,2034,2037,2041,2043,2048,2051,2063,2065,2068,2070,2086,2099,2109,2122,2124,2127,2128,2129,2149,2152,2154,2160,2161,2162,2163,2168,2171,2175,2176,2180,2187,2191,2194,2201,2202,2203,2205,2206,2208,2218,2222,2229,2236,2238,2258,2266,2285,2289,2290,2293,2295,2299,2302,2308,2309,2311,2317,2325,2332,2333,2335,2337,2339,2341,2351,2357,2360,2361,2364,2366,2380,2383,2384,2386,2396,2397,2423,2429,2435,2438,2442,2448,2449,2458,2459,2463,2465,2470,2474,2477,2479] \ No newline at end of file diff --git a/cardano-chain-gen/bench/benchfiles/fingerprint/emptyBlock_5000 b/cardano-chain-gen/bench/benchfiles/fingerprint/emptyBlock_5000 new file mode 100644 index 000000000..6506f2ea9 --- /dev/null +++ b/cardano-chain-gen/bench/benchfiles/fingerprint/emptyBlock_5000 @@ -0,0 +1 @@ +[0,1,9,14,23,28,29,31,34,69,74,75,80,82,84,88,95,98,104,106,108,113,115,127,129,144,146,147,151,153,161,163,171,176,177,178,179,186,189,195,197,198,204,207,210,211,212,213,219,222,226,233,241,252,265,266,274,290,291,294,295,298,304,305,309,312,314,317,326,328,329,332,333,336,346,351,352,357,365,367,385,387,391,400,401,404,411,413,414,424,427,430,436,444,449,455,458,460,461,462,473,474,476,477,482,491,497,498,499,502,506,507,514,521,547,563,566,575,578,581,594,599,602,607,614,623,631,638,639,641,649,652,653,654,665,666,670,672,673,682,683,688,692,696,700,701,708,710,714,725,735,737,746,750,763,772,776,783,793,795,797,802,804,817,818,822,824,826,827,832,834,836,841,847,851,855,861,868,870,873,876,877,882,883,891,894,905,908,913,915,925,934,942,943,949,956,960,967,968,974,980,987,998,1002,1004,1005,1012,1016,1019,1022,1023,1035,1036,1037,1039,1040,1051,1057,1058,1061,1064,1067,1074,1089,1091,1094,1096,1099,1104,1105,1107,1109,1121,1125,1133,1140,1145,1147,1148,1150,1153,1155,1159,1160,1172,1179,1185,1187,1194,1195,1201,1202,1211,1212,1216,1217,1221,1223,1233,1234,1235,1240,1241,1243,1250,1253,1259,1272,1273,1278,1280,1286,1289,1295,1298,1304,1310,1313,1320,1325,1328,1331,1332,1361,1379,1380,1382,1398,1402,1408,1411,1433,1436,1438,1449,1453,1454,1464,1468,1469,1480,1481,1482,1485,1492,1502,1504,1506,1512,1519,1524,1534,1537,1544,1545,1553,1559,1564,1565,1571,1578,1580,1583,1586,1587,1594,1597,1599,1605,1606,1609,1611,1613,1617,1623,1627,1630,1633,1634,1635,1640,1650,1655,1664,1666,1668,1670,1674,1682,1683,1684,1687,1697,1702,1710,1711,1712,1715,1718,1729,1739,1745,1750,1754,1757,1762,1775,1781,1794,1797,1801,1803,1808,1809,1812,1814,1820,1824,1825,1827,1832,1836,1854,1858,1865,1869,1872,1888,1890,1891,1892,1895,1905,1911,1917,1920,1921,1922,1928,1933,1943,1944,1962,1987,1992,1994,1998,2003,2008,2034,2037,2041,2043,2048,2051,2063,2065,2068,2070,2086,2099,2109,2122,2124,2127,2128,2129,2149,2152,2154,2160,2161,2162,2163,2168,2171,2175,2176,2180,2187,2191,2194,2201,2202,2203,2205,2206,2208,2218,2222,2229,2236,2238,2258,2266,2285,2289,2290,2293,2295,2299,2302,2308,2309,2311,2317,2325,2332,2333,2335,2337,2339,2341,2351,2357,2360,2361,2364,2366,2380,2383,2384,2386,2396,2397,2423,2429,2435,2438,2442,2448,2449,2458,2459,2463,2465,2470,2474,2477,2479,2491,2494,2496,2497,2499,2500,2505,2506,2509,2512,2519,2523,2540,2544,2546,2556,2558,2561,2562,2563,2566,2568,2569,2574,2580,2582,2600,2601,2605,2608,2620,2629,2633,2634,2637,2642,2654,2659,2660,2666,2673,2675,2683,2691,2693,2695,2697,2698,2699,2703,2705,2706,2709,2716,2717,2725,2726,2727,2731,2748,2758,2761,2767,2768,2777,2780,2787,2807,2811,2816,2818,2826,2830,2834,2835,2837,2842,2843,2846,2847,2849,2850,2854,2856,2857,2858,2860,2864,2867,2869,2872,2874,2879,2881,2887,2891,2898,2901,2903,2907,2909,2910,2933,2937,2941,2945,2947,2961,2969,2974,2975,2977,2980,2984,2990,3014,3023,3027,3036,3040,3042,3043,3050,3059,3063,3064,3068,3071,3073,3074,3087,3100,3103,3104,3111,3114,3123,3127,3131,3140,3143,3144,3150,3155,3157,3163,3169,3172,3179,3180,3193,3197,3200,3206,3211,3218,3220,3222,3232,3233,3234,3238,3249,3255,3256,3260,3280,3289,3291,3294,3299,3300,3301,3303,3308,3314,3322,3330,3333,3338,3343,3346,3352,3356,3357,3362,3365,3371,3379,3381,3383,3396,3398,3411,3413,3427,3440,3446,3457,3459,3461,3466,3471,3488,3490,3495,3496,3500,3506,3507,3509,3524,3539,3548,3555,3559,3569,3571,3575,3576,3578,3589,3595,3599,3600,3606,3608,3610,3611,3612,3616,3625,3628,3636,3649,3651,3657,3670,3673,3677,3688,3702,3706,3707,3709,3718,3736,3768,3776,3778,3785,3786,3787,3794,3802,3803,3810,3812,3819,3821,3822,3834,3844,3847,3848,3854,3856,3862,3863,3867,3869,3873,3876,3878,3879,3880,3881,3886,3888,3889,3891,3893,3903,3906,3912,3913,3916,3918,3920,3925,3926,3929,3938,3946,3956,3957,3964,3969,3980,3987,3990,3991,3997,4004,4005,4013,4014,4015,4019,4020,4023,4035,4039,4041,4048,4055,4057,4066,4071,4072,4083,4084,4090,4091,4092,4096,4125,4128,4137,4143,4145,4150,4151,4152,4158,4159,4166,4169,4174,4175,4183,4185,4189,4190,4194,4195,4196,4198,4201,4203,4210,4211,4217,4221,4222,4225,4228,4233,4240,4253,4256,4258,4261,4263,4265,4283,4287,4303,4306,4312,4314,4318,4323,4326,4333,4334,4335,4343,4345,4347,4350,4366,4374,4382,4401,4402,4405,4406,4419,4423,4425,4430,4432,4436,4440,4444,4446,4462,4467,4468,4472,4474,4484,4490,4497,4500,4502,4509,4510,4514,4516,4517,4519,4523,4534,4536,4544,4548,4556,4560,4572,4581,4584,4585,4602,4604,4607,4609,4612,4616,4620,4623,4625,4629,4631,4636,4638,4656,4664,4665,4666,4667,4669,4671,4673,4677,4679,4682,4688,4693,4698,4704,4715,4725,4727,4729,4733,4736,4743,4746,4747,4748,4752,4753,4757,4758,4760,4761,4767,4779,4785,4790,4793,4794,4795,4800,4804,4816,4820,4830,4835,4842,4843,4848,4851,4852,4853,4861,4864,4868,4873,4893,4900,4904,4905,4913,4914,4922,4934,4942,4945,4955,4959,4960,4978,4979,4986,4989,4996,5009,5016,5025,5028,5031,5035,5036,5040,5043,5047,5050,5053,5061,5063,5064,5068,5070,5073,5077,5095,5104,5107,5114,5117,5118,5120,5127,5132,5134,5148,5149,5159,5163,5164,5166,5171,5174,5175,5178,5185,5187,5200,5202,5212,5221,5224,5225,5229,5237,5242,5268,5276,5283,5287,5290,5299,5300,5301,5307,5318,5321,5322,5323,5361,5365,5366,5382,5389,5394,5398,5409,5410,5414,5417,5418,5431,5441,5443,5453,5456,5465,5468,5470,5480,5494,5500,5510,5519,5523,5532,5534,5535,5539,5543,5544,5546,5555,5558,5560,5562,5567,5568,5583,5585,5594,5600,5602,5606,5608,5611,5612,5615,5616,5617,5636,5639,5641,5650,5659,5664,5670,5672,5676,5679,5680,5688,5689,5692,5693,5694,5706,5709,5714,5715,5728,5729,5730,5734,5735,5739,5752,5755,5759,5776,5782,5783,5784,5792,5796,5799,5800,5803,5808,5810,5815,5818,5821,5824,5830,5835,5845,5847,5849,5861,5863,5867,5869,5874,5893,5897,5899,5900,5902,5903,5904,5906,5911,5924,5934,5939,5943,5947,5951,5963,5966,5968,5980,5985,5987,5992,5994,5999,6001,6018,6020,6027,6039,6046,6047,6053,6057,6059,6064,6070,6085,6089,6101,6103,6112,6123,6135,6140,6143,6148,6153,6156,6157,6158,6159,6160,6161,6165,6167,6168,6171,6177,6180,6184,6193,6206,6212,6220,6221,6230,6236,6240,6248,6255,6262,6266,6272,6273,6275,6280,6281,6283,6288,6289,6290,6292,6293,6303,6306,6317,6321,6329,6334,6336,6344,6347,6354,6356,6358,6360,6366,6375,6377,6378,6385,6390,6393,6400,6408,6413,6416,6419,6422,6423,6426,6427,6428,6432,6434,6438,6442,6445,6452,6454,6465,6466,6467,6470,6471,6481,6482,6483,6484,6491,6495,6497,6500,6503,6515,6516,6517,6522,6525,6527,6536,6551,6563,6564,6566,6574,6578,6579,6580,6582,6585,6594,6602,6608,6610,6613,6616,6625,6629,6635,6639,6645,6648,6651,6663,6665,6668,6669,6672,6687,6690,6694,6704,6705,6707,6708,6711,6713,6715,6718,6719,6727,6731,6737,6741,6746,6749,6750,6758,6760,6765,6771,6772,6773,6777,6783,6786,6788,6790,6791,6797,6800,6801,6802,6810,6811,6815,6825,6829,6832,6842,6847,6857,6869,6871,6878,6883,6887,6890,6893,6895,6896,6898,6901,6920,6924,6928,6931,6934,6942,6944,6963,6964,6987,6988,6994,6996,7000,7001,7002,7004,7005,7007,7015,7016,7022,7023,7036,7044,7045,7047,7052,7057,7060,7062,7067,7077,7080,7083,7084,7087,7090,7093,7095,7096,7100,7107,7114,7115,7118,7119,7120,7123,7124,7127,7135,7141,7163,7170,7176,7178,7187,7188,7198,7205,7213,7214,7215,7225,7226,7253,7274,7277,7278,7283,7286,7287,7289,7298,7307,7309,7310,7315,7317,7318,7322,7334,7337,7340,7341,7344,7346,7351,7357,7358,7376,7377,7385,7386,7390,7392,7394,7396,7398,7407,7412,7419,7428,7436,7443,7454,7455,7457,7458,7463,7472,7485,7496,7505,7511,7512,7517,7522,7524,7525,7528,7533,7539,7541,7543,7547,7548,7557,7561,7580,7587,7592,7601,7602,7604,7609,7610,7613,7616,7621,7627,7636,7638,7639,7641,7648,7651,7656,7659,7662,7676,7678,7682,7687,7688,7692,7696,7699,7701,7702,7704,7707,7711,7721,7727,7730,7733,7735,7743,7747,7748,7749,7757,7758,7762,7768,7769,7777,7786,7791,7798,7809,7810,7813,7819,7835,7837,7839,7841,7844,7847,7849,7850,7855,7858,7865,7868,7871,7876,7883,7885,7894,7898,7903,7906,7908,7913,7917,7918,7921,7922,7927,7931,7942,7947,7950,7953,7956,7957,7959,7963,7964,7973,7977,7978,7980,7982,7985,7986,7989,7993,7999,8003,8007,8013,8015,8034,8057,8062,8073,8088,8091,8096,8097,8103,8105,8107,8112,8118,8121,8127,8129,8132,8136,8137,8138,8145,8152,8153,8154,8159,8168,8187,8188,8189,8200,8203,8211,8234,8236,8237,8239,8250,8254,8263,8268,8269,8276,8280,8284,8291,8294,8295,8300,8301,8313,8315,8329,8330,8331,8335,8337,8345,8351,8352,8360,8362,8365,8366,8368,8370,8372,8374,8377,8380,8383,8387,8388,8406,8416,8418,8421,8422,8428,8432,8434,8443,8447,8459,8461,8467,8468,8489,8494,8497,8502,8503,8506,8508,8512,8514,8523,8525,8537,8539,8542,8543,8548,8555,8563,8566,8567,8570,8572,8574,8586,8598,8612,8620,8623,8624,8630,8634,8635,8642,8647,8653,8658,8659,8663,8668,8672,8673,8679,8682,8690,8701,8706,8711,8714,8722,8726,8737,8739,8742,8743,8744,8748,8751,8754,8757,8759,8766,8772,8780,8789,8792,8797,8815,8817,8819,8822,8828,8840,8852,8857,8858,8859,8865,8866,8867,8876,8882,8890,8892,8897,8905,8906,8907,8911,8915,8918,8922,8923,8958,8965,8970,8972,8978,8980,8982,8984,8985,8990,9000,9003,9007,9016,9020,9026,9030,9040,9048,9049,9050,9058,9062,9064,9066,9068,9071,9082,9085,9086,9095,9097,9099,9111,9114,9117,9127,9130,9134,9142,9149,9151,9155,9156,9165,9166,9169,9187,9199,9202,9206,9233,9234,9244,9246,9248,9255,9259,9262,9266,9278,9281,9286,9289,9290,9293,9295,9296,9302,9307,9308,9313,9314,9318,9330,9332,9343,9349,9352,9361,9362,9363,9373,9378,9382,9385,9386,9396,9397,9401,9403,9411,9412,9415,9419,9422,9425,9427,9433,9435,9444,9448,9454,9458,9462,9463,9470,9471,9472,9480,9489,9503,9515,9521,9523,9525,9528,9531,9541,9549,9550,9552,9555,9563,9565,9566,9567,9571,9577,9580,9584,9597,9600,9608,9615,9618,9625,9628,9629,9636,9637,9639,9642,9648,9658,9664,9666,9668,9678,9683,9697,9700,9701,9705,9707,9708,9714,9718,9719,9736,9738,9749,9755,9758,9759,9772,9774,9777,9779,9782,9791,9811,9812,9813,9822,9829,9837,9842,9848,9851,9859,9864,9879,9888,9894,9895,9899,9903,9904,9913,9919,9920,9922,9931,9939,9941,9944,9949,9960,9969,9970,9973,9976,9977,9979,9982,9983,9984,9987,9989,9992,9999,10000,10009,10013,10014,10030,10032,10044,10048,10049,10067,10075,10079,10081,10083,10084,10097,10107,10109,10118,10119,10120,10121,10125,10128,10131,10132,10135,10147,10151,10160,10164,10165,10172,10181,10188,10189,10194,10198,10200,10201,10207,10208,10211,10227,10228,10231,10232,10233,10236,10237,10245,10248,10255,10266,10273,10281,10283,10287,10288,10296,10297,10301,10307,10311,10320,10325,10328,10335,10345,10346,10349,10353,10359,10367,10372,10373,10376,10380,10394,10396,10399,10402,10403,10405,10410,10424,10427,10436,10437,10444,10445,10455,10460,10462,10469,10476,10477,10478,10480,10481,10498,10500,10501,10503,10509,10517,10527,10531,10532,10534,10540,10541,10542,10550,10555,10564,10566,10570,10576,10578,10582,10583,10586,10590,10592,10604,10605,10606,10611,10616,10617,10626,10629,10636,10637,10644,10655,10659,10664,10667,10668,10674,10686,10696,10706,10715,10725,10730,10732,10734,10738,10749,10750,10757,10759,10773,10774,10775,10776,10785,10794,10796,10801,10804,10812,10820,10825,10827,10833,10834,10835,10841,10851,10854,10855,10859,10868,10869,10876,10881,10886,10892,10900,10902,10903,10915,10922,10925,10927,10931,10938,10943,10945,10946,10958,10963,10964,10981,10996,10998,11001,11008,11010,11014,11020,11027,11035,11037,11050,11054,11057,11058,11061,11069,11070,11072,11073,11077,11078,11079,11082,11085,11086,11088,11090,11093,11095,11097,11104,11105,11120,11129,11142,11152,11154,11159,11166,11175,11180,11181,11186,11189,11191,11192,11194,11198,11209,11210,11212,11214,11223,11225,11226,11228,11230,11234,11236,11246,11256,11258,11263,11281,11284,11290,11291,11305,11312,11318,11319,11326,11328,11330,11354,11358,11361,11366,11374,11376,11379,11380,11383,11386,11391,11407,11415,11438,11445,11450,11457,11458,11459,11460,11465,11467,11468,11471,11473,11482,11496,11506,11507,11511,11515,11532,11533,11534,11536,11537,11538,11542,11543,11546,11552,11555,11565,11567,11572,11573,11576,11577,11579,11586,11593,11596,11597,11612,11614,11630,11631,11632,11634,11639,11641,11670,11671,11672,11673,11675,11679,11680,11682,11695,11699,11700,11709,11713,11716,11722,11735,11743,11751,11752,11758,11771,11774,11777,11789,11800,11803,11809,11827,11833,11835,11836,11841,11843,11847,11862,11869,11872,11885,11894,11897,11901,11904,11907,11911,11917,11919,11924,11937,11939,11941,11947,11964,11971,11973,11979,11988,11994,11996,12000,12002,12011,12012,12013,12014,12037,12041,12045,12060,12062,12072,12086,12094,12109,12110,12115,12118,12120,12141,12142,12146,12152,12174,12175,12176,12181,12195,12201,12212,12220,12225,12226,12231,12250,12252,12269,12272,12274,12279,12284,12286,12288,12295,12302,12306,12308,12311,12317,12328,12329,12338,12343,12345,12347,12355,12368,12371,12377,12382,12383,12386,12390,12400,12403,12404,12405,12412,12419,12422,12423,12428,12449,12452,12455,12462,12463,12466,12491,12494,12505,12508,12509,12512,12515,12516,12518,12536,12548,12549,12551,12557,12559,12560,12566,12568,12573,12577,12580,12581,12583,12586,12588,12589,12591,12593,12596,12599,12601,12604,12605,12611,12613,12623,12627,12629,12634,12635,12640,12643,12646,12652,12653,12655,12658,12662,12664,12665,12666,12670,12672,12674,12677,12681,12689,12692,12693,12695,12713,12715,12717,12718,12720,12729,12736,12738,12742,12745,12748,12757,12759,12760,12763,12767,12774,12793,12796,12800,12801,12804,12808,12813,12815,12821,12824,12826,12828,12829,12830,12833,12849,12865,12868,12871,12884,12888,12889,12892,12896,12904,12909,12911,12926,12933,12935,12942,12956,12957,12958,12966,12972,12975,12980,12982,12987,12988,12997,13006,13007,13008,13012,13013,13015,13016,13029,13031,13040,13046,13060,13068,13070,13076,13080,13085,13096,13097,13098,13105,13113,13116,13117,13120,13122,13130,13133,13137,13138,13148,13149,13171,13174,13175,13178,13182,13183,13184,13187,13189,13194,13196,13197,13215,13217,13219,13220,13227,13237,13238,13239,13247,13253,13261,13270,13278,13286,13287,13289,13291,13299,13302,13306,13314,13326,13348,13349,13350,13351,13354,13356,13357,13363,13367,13370,13392,13398,13402,13403,13407,13415,13417,13424,13425,13431,13433,13438,13445,13448,13465,13470,13477,13479,13484,13491,13505,13507,13523,13524,13527,13530,13531,13533,13536,13541,13544,13546,13553,13563,13568,13574,13581,13587,13596,13599,13605,13613,13618,13622,13629,13630,13633,13634,13639,13640,13643,13646,13661,13662,13669,13671,13675,13694,13703,13704,13706,13713,13720,13727,13731,13733,13764,13767,13775,13779,13785,13794,13795,13803,13805,13812,13820,13829,13843,13845,13852,13854,13859,13875,13876,13882,13883,13889,13894,13901,13903,13917,13925,13933,13937,13942,13951,13955,13961,13969,13970,13971,13976,13983,13986,13989,13994,14004,14007,14011,14022,14027,14044,14047,14051,14059,14061,14064,14066,14071,14072,14076,14082,14084,14088,14095,14097,14105,14112,14113,14114,14116,14117,14118,14122,14130,14135,14149,14150,14155,14156,14169,14177,14181,14188,14190,14191,14226,14232,14237,14238,14239,14246,14250,14253,14256,14262,14263,14267,14270,14272,14275,14283,14287,14290,14294,14302,14305,14308,14310,14315,14316,14319,14326,14344,14350,14353,14354,14368,14370,14377,14381,14382,14384,14387,14392,14403,14404,14411,14412,14418,14421,14426,14434,14437,14438,14440,14442,14444,14452,14459,14469,14473,14477,14486,14487,14489,14501,14514,14516,14518,14534,14539,14549,14555,14556,14570,14574,14587,14595,14604,14631,14638,14640,14641,14645,14652,14654,14658,14667,14668,14685,14688,14699,14700,14704,14706,14714,14726,14728,14732,14748,14750,14759,14766,14776,14777,14778,14790,14792,14793,14796,14800,14804,14805,14813,14814,14816,14822,14829,14837,14839,14846,14853,14861,14862,14871,14873,14887,14888,14890,14902,14909,14911,14921,14928,14934,14937,14944,14945,14956,14959,14977,14989,15000,15009,15014,15031,15034,15035,15037,15042,15050,15055,15064,15067,15068,15076,15078,15079,15092,15093,15094,15102,15105,15107,15115,15123,15128,15140,15141,15145,15152,15154,15162,15165,15167,15174,15182,15188,15190,15200,15205,15206,15208,15212,15216,15217,15218,15224,15228,15233,15236,15239,15256,15260,15263,15271,15283,15289,15294,15296,15301,15303,15312,15313,15344,15345,15346,15349,15353,15359,15365,15368,15369,15374,15386,15398,15422,15427,15429,15430,15433,15436,15440,15446,15451,15453,15454,15461,15463,15465,15466,15467,15468,15473,15475,15478,15489,15496,15514,15519,15520,15522,15529,15535,15542,15544,15546,15557,15558,15565,15567,15574,15584,15585,15592,15595,15621,15622,15625,15636,15639,15640,15642,15644,15645,15662,15672,15676,15678,15683,15685,15689,15690,15691,15692,15696,15700,15705,15712,15714,15728,15729,15741,15746,15747,15752,15755,15766,15767,15769,15771,15778,15782,15789,15794,15800,15809,15810,15814,15816,15820,15835,15839,15840,15846,15853,15858,15869,15884,15886,15889,15890,15902,15914,15919,15933,15934,15941,15945,15947,15949,15960,15963,15972,15979,16007,16011,16023,16024,16032,16036,16040,16046,16055,16056,16060,16067,16070,16075,16076,16082,16087,16094,16105,16119,16123,16124,16127,16132,16143,16153,16160,16165,16171,16172,16173,16181,16182,16186,16187,16192,16196,16203,16211,16212,16213,16214,16224,16232,16233,16235,16238,16241,16245,16247,16249,16251,16254,16260,16274,16277,16286,16288,16295,16299,16300,16307,16308,16311,16312,16326,16328,16330,16337,16342,16354,16361,16374,16376,16383,16384,16392,16395,16400,16401,16403,16411,16422,16431,16433,16435,16437,16442,16452,16457,16462,16463,16464,16472,16481,16485,16490,16497,16502,16507,16508,16513,16519,16521,16524,16525,16533,16544,16546,16548,16561,16562,16568,16577,16580,16582,16597,16599,16604,16607,16612,16616,16617,16619,16621,16631,16656,16660,16662,16663,16664,16666,16670,16673,16674,16678,16679,16683,16685,16704,16705,16706,16733,16734,16742,16751,16760,16766,16774,16786,16789,16801,16807,16810,16816,16821,16830,16832,16839,16849,16853,16859,16861,16867,16878,16890,16891,16898,16901,16903,16912,16920,16922,16927,16928,16931,16936,16939,16947,16949,16954,16958,16959,16965,16966,16969,16970,16973,16980,16985,16989,16998,17001,17005,17009,17015,17016,17018,17019,17027,17037,17054,17072,17075,17094,17096,17097,17100,17101,17106,17110,17113,17117,17127,17129,17134,17146,17162,17164,17165,17174,17175,17183,17184,17186,17189,17195,17196,17198,17205,17214,17217,17219,17222,17233,17235,17236,17242,17256,17268,17269,17270,17271,17279,17284,17294,17299,17302,17313,17321,17323,17324,17326,17328,17337,17340,17341,17347,17349,17351,17355,17357,17359,17361,17363,17374,17375,17383,17385,17386,17390,17395,17397,17404,17408,17432,17443,17444,17462,17463,17465,17472,17473,17479,17483,17490,17501,17509,17522,17546,17549,17551,17554,17560,17563,17565,17567,17570,17573,17575,17594,17595,17598,17606,17632,17633,17635,17642,17652,17653,17657,17664,17665,17667,17668,17669,17676,17678,17689,17691,17695,17697,17702,17711,17723,17731,17735,17736,17740,17743,17745,17749,17754,17761,17771,17778,17780,17784,17789,17796,17799,17800,17806,17823,17828,17834,17835,17843,17847,17853,17858,17862,17864,17865,17869,17871,17876,17880,17881,17890,17891,17897,17898,17907,17910,17920,17921,17929,17939,17943,17945,17951,17952,17958,17962,17966,17968,17972,17976,17980,17981,17986,17989,17991,17992,17994,18000,18001,18009,18010,18017,18027,18036,18042,18047,18064,18082,18091,18092,18106,18108,18115,18129,18131,18134,18140,18141,18144,18146,18150,18155,18160,18161,18163,18170,18175,18178,18187,18189,18190,18191,18193,18194,18214,18217,18220,18227,18233,18238,18241,18245,18256,18265,18273,18283,18286,18288,18289,18291,18299,18305,18308,18314,18319,18330,18331,18335,18357,18361,18367,18372,18373,18375,18376,18388,18389,18390,18399,18407,18408,18412,18423,18425,18433,18442,18446,18449,18452,18468,18469,18470,18480,18483,18490,18498,18502,18503,18504,18512,18529,18531,18532,18533,18542,18545,18554,18558,18560,18564,18581,18582,18585,18593,18596,18601,18605,18610,18612,18616,18618,18624,18625,18637,18638,18639,18644,18645,18649,18650,18653,18654,18665,18670,18671,18677,18680,18684,18685,18707,18714,18716,18722,18724,18732,18733,18739,18752,18758,18766,18769,18770,18786,18788,18795,18799,18806,18810,18811,18813,18818,18819,18827,18828,18839,18841,18855,18864,18866,18871,18872,18873,18879,18885,18897,18900,18901,18909,18911,18912,18921,18923,18943,18945,18949,18953,18965,18968,18971,18973,18978,18988,18989,18991,18993,18995,18997,19004,19009,19017,19029,19032,19033,19034,19038,19044,19053,19056,19075,19079,19086,19093,19095,19103,19109,19111,19113,19116,19119,19122,19123,19136,19137,19138,19140,19147,19150,19154,19155,19160,19169,19170,19172,19174,19180,19188,19189,19192,19196,19198,19200,19204,19214,19225,19234,19237,19248,19253,19262,19272,19273,19277,19282,19283,19289,19290,19296,19304,19306,19309,19310,19311,19316,19323,19327,19331,19332,19333,19334,19346,19347,19348,19350,19355,19358,19363,19364,19374,19376,19383,19385,19388,19395,19396,19404,19413,19414,19416,19417,19423,19425,19427,19428,19431,19433,19435,19436,19438,19444,19449,19455,19456,19462,19465,19466,19467,19475,19480,19488,19500,19505,19508,19513,19516,19519,19521,19524,19532,19533,19535,19542,19543,19548,19554,19556,19558,19566,19568,19571,19572,19581,19583,19585,19588,19597,19599,19604,19608,19610,19619,19625,19632,19635,19639,19645,19650,19652,19655,19662,19664,19667,19680,19682,19688,19691,19692,19704,19706,19707,19713,19719,19722,19726,19727,19728,19736,19754,19763,19766,19776,19783,19788,19789,19790,19792,19794,19797,19798,19807,19812,19813,19826,19827,19828,19830,19832,19833,19835,19836,19843,19846,19849,19851,19861,19866,19869,19871,19872,19873,19876,19883,19884,19888,19897,19911,19917,19920,19923,19928,19930,19932,19940,19945,19955,19956,19972,19983,19986,19998,20006,20010,20015,20022,20028,20030,20033,20036,20038,20045,20053,20084,20086,20087,20095,20098,20100,20101,20102,20111,20115,20118,20126,20138,20141,20142,20146,20147,20150,20153,20159,20183,20185,20189,20197,20203,20204,20211,20212,20213,20216,20220,20222,20225,20239,20250,20253,20259,20274,20284,20286,20293,20298,20308,20312,20324,20334,20356,20368,20385,20388,20393,20398,20401,20402,20404,20405,20409,20410,20413,20417,20426,20428,20431,20438,20440,20446,20449,20451,20457,20460,20461,20466,20470,20475,20477,20479,20482,20483,20484,20488,20489,20495,20497,20499,20500,20503,20528,20531,20532,20533,20538,20543,20547,20548,20549,20565,20567,20569,20574,20584,20587,20602,20607,20609,20617,20621,20625,20626,20637,20639,20646,20647,20651,20652,20653,20654,20656,20664,20665,20674,20678,20679,20684,20685,20690,20710,20717,20718,20726,20733,20735,20740,20758,20764,20776,20781,20788,20792,20800,20811,20815,20824,20826,20835,20845,20850,20852,20853,20854,20857,20861,20869,20870,20874,20877,20884,20903,20904,20905,20910,20928,20930,20931,20932,20936,20937,20940,20943,20947,20948,20953,20960,20962,20964,20968,20969,20984,20985,20989,20994,21006,21008,21010,21011,21021,21024,21037,21039,21041,21043,21051,21057,21063,21067,21070,21073,21077,21085,21091,21100,21107,21128,21132,21135,21136,21142,21147,21148,21155,21156,21159,21161,21163,21167,21170,21172,21175,21177,21187,21188,21192,21198,21206,21209,21212,21216,21231,21235,21243,21247,21251,21255,21259,21264,21266,21271,21276,21279,21294,21299,21300,21306,21311,21314,21316,21318,21320,21329,21337,21340,21354,21357,21372,21381,21385,21387,21391,21398,21400,21407,21408,21409,21423,21426,21436,21437,21441,21452,21453,21456,21457,21463,21467,21475,21478,21490,21498,21506,21510,21536,21540,21542,21545,21552,21557,21567,21569,21582,21588,21590,21595,21601,21607,21612,21620,21622,21624,21636,21637,21640,21646,21650,21651,21655,21665,21666,21672,21674,21692,21699,21706,21710,21712,21724,21733,21734,21737,21739,21741,21745,21747,21754,21758,21759,21760,21763,21765,21767,21772,21773,21780,21782,21784,21785,21798,21800,21806,21812,21813,21818,21820,21827,21829,21832,21836,21839,21851,21856,21862,21864,21870,21887,21897,21904,21907,21912,21920,21922,21923,21925,21931,21932,21936,21938,21939,21943,21947,21949,21951,21957,21960,21964,21967,21971,21976,21978,21979,21984,21998,22008,22009,22020,22021,22032,22033,22039,22046,22048,22054,22056,22062,22063,22065,22074,22078,22082,22086,22088,22093,22094,22098,22099,22100,22117,22121,22123,22124,22128,22138,22141,22151,22154,22162,22163,22170,22172,22174,22176,22195,22207,22208,22210,22211,22213,22217,22218,22226,22227,22241,22243,22244,22246,22266,22268,22272,22281,22285,22292,22297,22299,22300,22303,22306,22312,22313,22320,22326,22338,22342,22347,22360,22365,22367,22371,22375,22379,22381,22382,22383,22385,22386,22388,22392,22395,22400,22403,22414,22419,22421,22422,22425,22441,22443,22445,22465,22466,22471,22475,22476,22478,22481,22482,22486,22489,22500,22503,22505,22511,22515,22520,22524,22528,22530,22533,22537,22538,22548,22554,22558,22559,22564,22566,22570,22572,22574,22575,22589,22591,22592,22593,22596,22597,22603,22604,22606,22608,22619,22631,22639,22642,22643,22655,22662,22664,22665,22668,22673,22680,22682,22685,22693,22696,22697,22700,22701,22703,22713,22722,22730,22733,22736,22737,22749,22757,22760,22761,22765,22776,22782,22791,22810,22817,22834,22841,22848,22849,22852,22853,22859,22864,22877,22881,22885,22886,22887,22888,22891,22892,22899,22902,22903,22905,22916,22922,22937,22940,22960,22967,22971,22990,22991,22993,22994,23006,23021,23022,23029,23031,23032,23034,23035,23039,23055,23085,23086,23093,23102,23105,23107,23110,23114,23125,23144,23148,23150,23156,23169,23170,23186,23195,23207,23208,23210,23221,23231,23233,23234,23240,23241,23248,23258,23268,23269,23271,23273,23275,23277,23284,23285,23292,23295,23297,23302,23327,23330,23331,23333,23350,23351,23356,23359,23363,23369,23370,23372,23377,23383,23384,23385,23386,23394,23413,23425,23427,23433,23435,23436,23437,23438,23439,23444,23451,23467,23474,23475,23477,23478,23481,23484,23490,23491,23492,23499,23504,23509,23511,23514,23527,23528,23530,23546,23547,23548,23556,23558,23564,23566,23567,23569,23570,23571,23578,23579,23582,23592,23596,23607,23608,23611,23613,23617,23619,23620,23623,23626,23641,23653,23654,23666,23671,23673,23685,23688,23691,23695,23700,23701,23705,23708,23712,23714,23717,23721,23724,23731,23732,23736,23738,23739,23741,23744,23749,23752,23763,23768,23774,23778,23779,23781,23782,23785,23787,23790,23792,23808,23809,23811,23814,23815,23816,23818,23820,23832,23839,23842,23843,23847,23848,23854,23855,23859,23861,23863,23865,23866,23867,23870,23874,23885,23889,23890,23892,23895,23896,23905,23907,23909,23913,23922,23924,23926,23930,23936,23940,23942,23947,23952,23970,23983,23985,23994,23999,24004,24006,24017,24018,24032,24034,24036,24053,24054,24058,24063,24070,24075,24084,24085,24089,24091,24092,24108,24114,24123,24126,24128,24131,24136,24143,24149,24151,24153,24163,24167,24175,24181,24185,24190,24191,24192,24203,24204,24205,24208,24209,24217,24218,24223,24225,24226,24242,24246,24249,24256,24257,24262,24267,24282,24290,24291,24293,24295,24300,24301,24313,24314,24318,24320,24327,24328,24329,24330,24338,24344,24360,24368,24387,24395,24399,24400,24408,24414,24426,24429,24430,24432,24448,24456,24457,24463,24468,24470,24473,24476,24478,24487,24489,24492,24499,24504,24507,24509,24512,24517,24518,24522,24524,24526,24533,24547,24559,24560,24561,24563,24568,24572,24576,24577,24578,24580,24583,24586,24596,24604,24606,24607,24617,24625,24636,24649,24653,24657,24662,24678,24679,24683,24690,24691,24692,24696,24698,24700,24709,24711,24713,24715,24722,24728,24732,24734,24743,24746,24754,24763,24764,24769,24770,24772,24775,24777,24783,24788,24790,24793,24796,24817,24818,24829,24830,24834,24842,24859,24865,24867,24874,24879,24888,24889,24894,24901,24903,24904,24906,24921,24922,24943,24951,24952,24953,24955,24957,24959,24963,24964,24968,24971,24981,24982,24988,24998,25004,25006,25007,25018,25024,25027,25030,25033,25035,25051,25057,25058,25059,25061,25067,25075,25076,25077,25080,25084,25091,25115,25118,25124,25131,25134,25135,25139,25142,25157,25169,25170,25178,25180,25185,25188,25189,25196,25205,25210,25216,25219,25221] \ No newline at end of file diff --git a/cardano-chain-gen/bench/benchfiles/fingerprint/registerAddressess_1 b/cardano-chain-gen/bench/benchfiles/fingerprint/registerAddressess_1 new file mode 100644 index 000000000..6e7ea636e --- /dev/null +++ b/cardano-chain-gen/bench/benchfiles/fingerprint/registerAddressess_1 @@ -0,0 +1 @@ +[0] \ No newline at end of file diff --git a/cardano-chain-gen/bench/benchfiles/fingerprint/registerAddressess_10 b/cardano-chain-gen/bench/benchfiles/fingerprint/registerAddressess_10 new file mode 100644 index 000000000..57041f55f --- /dev/null +++ b/cardano-chain-gen/bench/benchfiles/fingerprint/registerAddressess_10 @@ -0,0 +1 @@ +[0,1,9,14,23,28,29,31,34,69] \ No newline at end of file diff --git a/cardano-chain-gen/bench/benchfiles/fingerprint/registerAddressess_100 b/cardano-chain-gen/bench/benchfiles/fingerprint/registerAddressess_100 new file mode 100644 index 000000000..8b6e0e180 --- /dev/null +++ b/cardano-chain-gen/bench/benchfiles/fingerprint/registerAddressess_100 @@ -0,0 +1 @@ +[0,1,9,14,23,28,29,31,34,69,74,75,80,82,84,88,95,98,104,106,108,113,115,127,129,144,146,147,151,153,161,163,171,176,177,178,179,186,189,195,197,198,204,207,210,211,212,213,219,222,226,233,241,252,265,266,274,290,291,294,295,298,304,305,309,312,314,317,326,328,329,332,333,336,346,351,352,357,365,367,385,387,391,400,401,404,411,413,414,424,427,430,436,444,449,455,458,460,461,462] \ No newline at end of file diff --git a/cardano-chain-gen/bench/benchfiles/fingerprint/registerAddressess_200 b/cardano-chain-gen/bench/benchfiles/fingerprint/registerAddressess_200 new file mode 100644 index 000000000..ec6e5d49a --- /dev/null +++ b/cardano-chain-gen/bench/benchfiles/fingerprint/registerAddressess_200 @@ -0,0 +1 @@ +[0,1,9,14,23,28,29,31,34,69,74,75,80,82,84,88,95,98,104,106,108,113,115,127,129,144,146,147,151,153,161,163,171,176,177,178,179,186,189,195,197,198,204,207,210,211,212,213,219,222,226,233,241,252,265,266,274,290,291,294,295,298,304,305,309,312,314,317,326,328,329,332,333,336,346,351,352,357,365,367,385,387,391,400,401,404,411,413,414,424,427,430,436,444,449,455,458,460,461,462,473,474,476,477,482,491,497,498,499,502,506,507,514,521,547,563,566,575,578,581,594,599,602,607,614,623,631,638,639,641,649,652,653,654,665,666,670,672,673,682,683,688,692,696,700,701,708,710,714,725,735,737,746,750,763,772,776,783,793,795,797,802,804,817,818,822,824,826,827,832,834,836,841,847,851,855,861,868,870,873,876,877,882,883,891,894,905,908,913,915,925,934,942,943,949,956,960,967,968,974] \ No newline at end of file diff --git a/cardano-chain-gen/bench/benchfiles/fingerprint/rollbackDelegateAndSend_1 b/cardano-chain-gen/bench/benchfiles/fingerprint/rollbackDelegateAndSend_1 new file mode 100644 index 000000000..df965face --- /dev/null +++ b/cardano-chain-gen/bench/benchfiles/fingerprint/rollbackDelegateAndSend_1 @@ -0,0 +1 @@ +[0,1,9] \ No newline at end of file diff --git a/cardano-chain-gen/bench/benchfiles/fingerprint/rollbackDelegateAndSend_10 b/cardano-chain-gen/bench/benchfiles/fingerprint/rollbackDelegateAndSend_10 new file mode 100644 index 000000000..495236454 --- /dev/null +++ b/cardano-chain-gen/bench/benchfiles/fingerprint/rollbackDelegateAndSend_10 @@ -0,0 +1 @@ +[0,1,9,14,23,28,29,31,34,69,74,75,80,82,84,88,95,98,104,106,108,113,115,127,129,144,146,147,151,153] \ No newline at end of file diff --git a/cardano-chain-gen/bench/benchfiles/fingerprint/rollbackDelegateAndSend_100 b/cardano-chain-gen/bench/benchfiles/fingerprint/rollbackDelegateAndSend_100 new file mode 100644 index 000000000..cecab0676 --- /dev/null +++ b/cardano-chain-gen/bench/benchfiles/fingerprint/rollbackDelegateAndSend_100 @@ -0,0 +1 @@ +[0,1,9,14,23,28,29,31,34,69,74,75,80,82,84,88,95,98,104,106,108,113,115,127,129,144,146,147,151,153,161,163,171,176,177,178,179,186,189,195,197,198,204,207,210,211,212,213,219,222,226,233,241,252,265,266,274,290,291,294,295,298,304,305,309,312,314,317,326,328,329,332,333,336,346,351,352,357,365,367,385,387,391,400,401,404,411,413,414,424,427,430,436,444,449,455,458,460,461,462,473,474,476,477,482,491,497,498,499,502,506,507,514,521,547,563,566,575,578,581,594,599,602,607,614,623,631,638,639,641,649,652,653,654,665,666,670,672,673,682,683,688,692,696,700,701,708,710,714,725,735,737,746,750,763,772,776,783,793,795,797,802,804,817,818,822,824,826,827,832,834,836,841,847,851,855,861,868,870,873,876,877,882,883,891,894,905,908,913,915,925,934,942,943,949,956,960,967,968,974,980,987,998,1002,1004,1005,1012,1016,1019,1022,1023,1035,1036,1037,1039,1040,1051,1057,1058,1061,1064,1067,1074,1089,1091,1094,1096,1099,1104,1105,1107,1109,1121,1125,1133,1140,1145,1147,1148,1150,1153,1155,1159,1160,1172,1179,1185,1187,1194,1195,1201,1202,1211,1212,1216,1217,1221,1223,1233,1234,1235,1240,1241,1243,1250,1253,1259,1272,1273,1278,1280,1286,1289,1295,1298,1304,1310,1313,1320,1325,1328,1331,1332,1361,1379,1380,1382,1398,1402,1408,1411,1433,1436,1438,1449,1453,1454,1464,1468,1469] \ No newline at end of file diff --git a/cardano-chain-gen/bench/benchfiles/fingerprint/rollbackDelegateAndSend_400 b/cardano-chain-gen/bench/benchfiles/fingerprint/rollbackDelegateAndSend_400 new file mode 100644 index 000000000..518717669 --- /dev/null +++ b/cardano-chain-gen/bench/benchfiles/fingerprint/rollbackDelegateAndSend_400 @@ -0,0 +1 @@ +[0,1,9,14,23,28,29,31,34,69,74,75,80,82,84,88,95,98,104,106,108,113,115,127,129,144,146,147,151,153,161,163,171,176,177,178,179,186,189,195,197,198,204,207,210,211,212,213,219,222,226,233,241,252,265,266,274,290,291,294,295,298,304,305,309,312,314,317,326,328,329,332,333,336,346,351,352,357,365,367,385,387,391,400,401,404,411,413,414,424,427,430,436,444,449,455,458,460,461,462,473,474,476,477,482,491,497,498,499,502,506,507,514,521,547,563,566,575,578,581,594,599,602,607,614,623,631,638,639,641,649,652,653,654,665,666,670,672,673,682,683,688,692,696,700,701,708,710,714,725,735,737,746,750,763,772,776,783,793,795,797,802,804,817,818,822,824,826,827,832,834,836,841,847,851,855,861,868,870,873,876,877,882,883,891,894,905,908,913,915,925,934,942,943,949,956,960,967,968,974,980,987,998,1002,1004,1005,1012,1016,1019,1022,1023,1035,1036,1037,1039,1040,1051,1057,1058,1061,1064,1067,1074,1089,1091,1094,1096,1099,1104,1105,1107,1109,1121,1125,1133,1140,1145,1147,1148,1150,1153,1155,1159,1160,1172,1179,1185,1187,1194,1195,1201,1202,1211,1212,1216,1217,1221,1223,1233,1234,1235,1240,1241,1243,1250,1253,1259,1272,1273,1278,1280,1286,1289,1295,1298,1304,1310,1313,1320,1325,1328,1331,1332,1361,1379,1380,1382,1398,1402,1408,1411,1433,1436,1438,1449,1453,1454,1464,1468,1469,1480,1481,1482,1485,1492,1502,1504,1506,1512,1519,1524,1534,1537,1544,1545,1553,1559,1564,1565,1571,1578,1580,1583,1586,1587,1594,1597,1599,1605,1606,1609,1611,1613,1617,1623,1627,1630,1633,1634,1635,1640,1650,1655,1664,1666,1668,1670,1674,1682,1683,1684,1687,1697,1702,1710,1711,1712,1715,1718,1729,1739,1745,1750,1754,1757,1762,1775,1781,1794,1797,1801,1803,1808,1809,1812,1814,1820,1824,1825,1827,1832,1836,1854,1858,1865,1869,1872,1888,1890,1891,1892,1895,1905,1911,1917,1920,1921,1922,1928,1933,1943,1944,1962,1987,1992,1994,1998,2003,2008,2034,2037,2041,2043,2048,2051,2063,2065,2068,2070,2086,2099,2109,2122,2124,2127,2128,2129,2149,2152,2154,2160,2161,2162,2163,2168,2171,2175,2176,2180,2187,2191,2194,2201,2202,2203,2205,2206,2208,2218,2222,2229,2236,2238,2258,2266,2285,2289,2290,2293,2295,2299,2302,2308,2309,2311,2317,2325,2332,2333,2335,2337,2339,2341,2351,2357,2360,2361,2364,2366,2380,2383,2384,2386,2396,2397,2423,2429,2435,2438,2442,2448,2449,2458,2459,2463,2465,2470,2474,2477,2479,2491,2494,2496,2497,2499,2500,2505,2506,2509,2512,2519,2523,2540,2544,2546,2556,2558,2561,2562,2563,2566,2568,2569,2574,2580,2582,2600,2601,2605,2608,2620,2629,2633,2634,2637,2642,2654,2659,2660,2666,2673,2675,2683,2691,2693,2695,2697,2698,2699,2703,2705,2706,2709,2716,2717,2725,2726,2727,2731,2748,2758,2761,2767,2768,2777,2780,2787,2807,2811,2816,2818,2826,2830,2834,2835,2837,2842,2843,2846,2847,2849,2850,2854,2856,2857,2858,2860,2864,2867,2869,2872,2874,2879,2881,2887,2891,2898,2901,2903,2907,2909,2910,2933,2937,2941,2945,2947,2961,2969,2974,2975,2977,2980,2984,2990,3014,3023,3027,3036,3040,3042,3043,3050,3059,3063,3064,3068,3071,3073,3074,3087,3100,3103,3104,3111,3114,3123,3127,3131,3140,3143,3144,3150,3155,3157,3163,3169,3172,3179,3180,3193,3197,3200,3206,3211,3218,3220,3222,3232,3233,3234,3238,3249,3255,3256,3260,3280,3289,3291,3294,3299,3300,3301,3303,3308,3314,3322,3330,3333,3338,3343,3346,3352,3356,3357,3362,3365,3371,3379,3381,3383,3396,3398,3411,3413,3427,3440,3446,3457,3459,3461,3466,3471,3488,3490,3495,3496,3500,3506,3507,3509,3524,3539,3548,3555,3559,3569,3571,3575,3576,3578,3589,3595,3599,3600,3606,3608,3610,3611,3612,3616,3625,3628,3636,3649,3651,3657,3670,3673,3677,3688,3702,3706,3707,3709,3718,3736,3768,3776,3778,3785,3786,3787,3794,3802,3803,3810,3812,3819,3821,3822,3834,3844,3847,3848,3854,3856,3862,3863,3867,3869,3873,3876,3878,3879,3880,3881,3886,3888,3889,3891,3893,3903,3906,3912,3913,3916,3918,3920,3925,3926,3929,3938,3946,3956,3957,3964,3969,3980,3987,3990,3991,3997,4004,4005,4013,4014,4015,4019,4020,4023,4035,4039,4041,4048,4055,4057,4066,4071,4072,4083,4084,4090,4091,4092,4096,4125,4128,4137,4143,4145,4150,4151,4152,4158,4159,4166,4169,4174,4175,4183,4185,4189,4190,4194,4195,4196,4198,4201,4203,4210,4211,4217,4221,4222,4225,4228,4233,4240,4253,4256,4258,4261,4263,4265,4283,4287,4303,4306,4312,4314,4318,4323,4326,4333,4334,4335,4343,4345,4347,4350,4366,4374,4382,4401,4402,4405,4406,4419,4423,4425,4430,4432,4436,4440,4444,4446,4462,4467,4468,4472,4474,4484,4490,4497,4500,4502,4509,4510,4514,4516,4517,4519,4523,4534,4536,4544,4548,4556,4560,4572,4581,4584,4585,4602,4604,4607,4609,4612,4616,4620,4623,4625,4629,4631,4636,4638,4656,4664,4665,4666,4667,4669,4671,4673,4677,4679,4682,4688,4693,4698,4704,4715,4725,4727,4729,4733,4736,4743,4746,4747,4748,4752,4753,4757,4758,4760,4761,4767,4779,4785,4790,4793,4794,4795,4800,4804,4816,4820,4830,4835,4842,4843,4848,4851,4852,4853,4861,4864,4868,4873,4893,4900,4904,4905,4913,4914,4922,4934,4942,4945,4955,4959,4960,4978,4979,4986,4989,4996,5009,5016,5025,5028,5031,5035,5036,5040,5043,5047,5050,5053,5061,5063,5064,5068,5070,5073,5077,5095,5104,5107,5114,5117,5118,5120,5127,5132,5134,5148,5149,5159,5163,5164,5166,5171,5174,5175,5178,5185,5187,5200,5202,5212,5221,5224,5225,5229,5237,5242,5268,5276,5283,5287,5290,5299,5300,5301,5307,5318,5321,5322,5323,5361,5365,5366,5382,5389,5394,5398,5409,5410,5414,5417,5418,5431,5441,5443,5453,5456,5465,5468,5470,5480,5494,5500,5510,5519,5523,5532,5534,5535,5539,5543,5544,5546,5555,5558,5560,5562,5567,5568,5583,5585,5594,5600,5602,5606,5608,5611,5612,5615,5616,5617,5636,5639,5641,5650,5659,5664,5670,5672,5676,5679,5680,5688,5689,5692,5693,5694,5706,5709,5714,5715,5728,5729,5730,5734,5735,5739,5752,5755,5759,5776,5782,5783,5784,5792,5796,5799,5800,5803,5808,5810,5815,5818,5821,5824,5830,5835,5845,5847,5849,5861,5863,5867,5869,5874,5893,5897,5899,5900,5902,5903,5904,5906,5911,5924,5934,5939,5943,5947,5951,5963,5966,5968,5980,5985,5987,5992,5994] \ No newline at end of file diff --git a/cardano-chain-gen/bench/benchfiles/fingerprint/rollbackMaTxOut_1 b/cardano-chain-gen/bench/benchfiles/fingerprint/rollbackMaTxOut_1 new file mode 100644 index 000000000..6e7ea636e --- /dev/null +++ b/cardano-chain-gen/bench/benchfiles/fingerprint/rollbackMaTxOut_1 @@ -0,0 +1 @@ +[0] \ No newline at end of file diff --git a/cardano-chain-gen/bench/benchfiles/fingerprint/rollbackMaTxOut_10 b/cardano-chain-gen/bench/benchfiles/fingerprint/rollbackMaTxOut_10 new file mode 100644 index 000000000..57041f55f --- /dev/null +++ b/cardano-chain-gen/bench/benchfiles/fingerprint/rollbackMaTxOut_10 @@ -0,0 +1 @@ +[0,1,9,14,23,28,29,31,34,69] \ No newline at end of file diff --git a/cardano-chain-gen/bench/benchfiles/fingerprint/rollbackMaTxOut_100 b/cardano-chain-gen/bench/benchfiles/fingerprint/rollbackMaTxOut_100 new file mode 100644 index 000000000..8b6e0e180 --- /dev/null +++ b/cardano-chain-gen/bench/benchfiles/fingerprint/rollbackMaTxOut_100 @@ -0,0 +1 @@ +[0,1,9,14,23,28,29,31,34,69,74,75,80,82,84,88,95,98,104,106,108,113,115,127,129,144,146,147,151,153,161,163,171,176,177,178,179,186,189,195,197,198,204,207,210,211,212,213,219,222,226,233,241,252,265,266,274,290,291,294,295,298,304,305,309,312,314,317,326,328,329,332,333,336,346,351,352,357,365,367,385,387,391,400,401,404,411,413,414,424,427,430,436,444,449,455,458,460,461,462] \ No newline at end of file diff --git a/cardano-chain-gen/bench/benchfiles/fingerprint/rollbackMaTxOut_500 b/cardano-chain-gen/bench/benchfiles/fingerprint/rollbackMaTxOut_500 new file mode 100644 index 000000000..ba054d4ce --- /dev/null +++ b/cardano-chain-gen/bench/benchfiles/fingerprint/rollbackMaTxOut_500 @@ -0,0 +1 @@ +[0,1,9,14,23,28,29,31,34,69,74,75,80,82,84,88,95,98,104,106,108,113,115,127,129,144,146,147,151,153,161,163,171,176,177,178,179,186,189,195,197,198,204,207,210,211,212,213,219,222,226,233,241,252,265,266,274,290,291,294,295,298,304,305,309,312,314,317,326,328,329,332,333,336,346,351,352,357,365,367,385,387,391,400,401,404,411,413,414,424,427,430,436,444,449,455,458,460,461,462,473,474,476,477,482,491,497,498,499,502,506,507,514,521,547,563,566,575,578,581,594,599,602,607,614,623,631,638,639,641,649,652,653,654,665,666,670,672,673,682,683,688,692,696,700,701,708,710,714,725,735,737,746,750,763,772,776,783,793,795,797,802,804,817,818,822,824,826,827,832,834,836,841,847,851,855,861,868,870,873,876,877,882,883,891,894,905,908,913,915,925,934,942,943,949,956,960,967,968,974,980,987,998,1002,1004,1005,1012,1016,1019,1022,1023,1035,1036,1037,1039,1040,1051,1057,1058,1061,1064,1067,1074,1089,1091,1094,1096,1099,1104,1105,1107,1109,1121,1125,1133,1140,1145,1147,1148,1150,1153,1155,1159,1160,1172,1179,1185,1187,1194,1195,1201,1202,1211,1212,1216,1217,1221,1223,1233,1234,1235,1240,1241,1243,1250,1253,1259,1272,1273,1278,1280,1286,1289,1295,1298,1304,1310,1313,1320,1325,1328,1331,1332,1361,1379,1380,1382,1398,1402,1408,1411,1433,1436,1438,1449,1453,1454,1464,1468,1469,1480,1481,1482,1485,1492,1502,1504,1506,1512,1519,1524,1534,1537,1544,1545,1553,1559,1564,1565,1571,1578,1580,1583,1586,1587,1594,1597,1599,1605,1606,1609,1611,1613,1617,1623,1627,1630,1633,1634,1635,1640,1650,1655,1664,1666,1668,1670,1674,1682,1683,1684,1687,1697,1702,1710,1711,1712,1715,1718,1729,1739,1745,1750,1754,1757,1762,1775,1781,1794,1797,1801,1803,1808,1809,1812,1814,1820,1824,1825,1827,1832,1836,1854,1858,1865,1869,1872,1888,1890,1891,1892,1895,1905,1911,1917,1920,1921,1922,1928,1933,1943,1944,1962,1987,1992,1994,1998,2003,2008,2034,2037,2041,2043,2048,2051,2063,2065,2068,2070,2086,2099,2109,2122,2124,2127,2128,2129,2149,2152,2154,2160,2161,2162,2163,2168,2171,2175,2176,2180,2187,2191,2194,2201,2202,2203,2205,2206,2208,2218,2222,2229,2236,2238,2258,2266,2285,2289,2290,2293,2295,2299,2302,2308,2309,2311,2317,2325,2332,2333,2335,2337,2339,2341,2351,2357,2360,2361,2364,2366,2380,2383,2384,2386,2396,2397,2423,2429,2435,2438,2442,2448,2449,2458,2459,2463,2465,2470,2474,2477,2479] \ No newline at end of file diff --git a/cardano-chain-gen/bench/benchfiles/pgpass-bench b/cardano-chain-gen/bench/benchfiles/pgpass-bench new file mode 100644 index 000000000..e42d64610 --- /dev/null +++ b/cardano-chain-gen/bench/benchfiles/pgpass-bench @@ -0,0 +1 @@ +/var/run/postgresql:5432:bench:*:* diff --git a/cardano-chain-gen/cardano-chain-gen.cabal b/cardano-chain-gen/cardano-chain-gen.cabal index 286fe6468..9f95dbb2e 100644 --- a/cardano-chain-gen/cardano-chain-gen.cabal +++ b/cardano-chain-gen/cardano-chain-gen.cabal @@ -44,12 +44,16 @@ library Cardano.Mock.ChainDB Cardano.Mock.ChainSync.Server Cardano.Mock.ChainSync.State + Cardano.Mock.Db.Config + Cardano.Mock.Db.Validate + Cardano.Mock.Forging.Examples Cardano.Mock.Forging.Interpreter Cardano.Mock.Forging.Tx.Alonzo Cardano.Mock.Forging.Tx.Alonzo.ScriptsExamples Cardano.Mock.Forging.Tx.Generic Cardano.Mock.Forging.Tx.Shelley Cardano.Mock.Forging.Types + Cardano.Mock.UnifiedApi build-depends: base >= 4.14 && < 4.16 , async @@ -63,6 +67,10 @@ library , cardano-crypto-class , cardano-crypto-praos , cardano-crypto-wrapper + , cardano-cli + , cardano-db + , cardano-db-sync + , cardano-smash-server , cardano-ledger-alonzo , cardano-ledger-byron , cardano-ledger-core @@ -90,6 +98,7 @@ library , memory , mtl , monad-control + , monad-logger , network-mux , nothunks , ouroboros-consensus @@ -102,11 +111,13 @@ library , persistent-postgresql , plutus-core , plutus-example + , postgresql-simple , pretty-show , prometheus , random-shuffle , serialise , set-algebra + , silently , small-steps , split , stm @@ -114,6 +125,7 @@ library , strict-containers , strict-stm , swagger2 + , tasty-hunit , text , text-ansi , time @@ -146,11 +158,8 @@ test-suite cardano-chain-gen other-modules: Paths_cardano_chain_gen MigrationValidations - other-modules: Test.Cardano.Db.Mock.Config - Test.Cardano.Db.Mock.Examples + other-modules: Test.Cardano.Db.Mock.Examples Test.Cardano.Db.Mock.Unit - Test.Cardano.Db.Mock.UnifiedApi - Test.Cardano.Db.Mock.Validate build-depends: async , base >= 4.12 && < 4.15 @@ -200,3 +209,55 @@ test-suite cardano-chain-gen , persistent , plutus-example , postgresql-simple + +benchmark cardano-chain + type: exitcode-stdio-1.0 + default-language: Haskell2010 + main-is: Main.hs + hs-source-dirs: gen + hs-source-dirs: bench + + ghc-options: -Wall + -Wcompat + -fwarn-redundant-constraints + -fwarn-incomplete-patterns + -fwarn-unused-imports + -Wincomplete-record-updates + -Wincomplete-uni-patterns + -Wno-unsafe + -threaded + -rtsopts + -with-rtsopts=-N4 + + autogen-modules: Paths_cardano_chain_gen + MigrationValidations + other-modules: Paths_cardano_chain_gen + MigrationValidations + + other-modules: Cardano.Db.Bench + build-depends: async + , base >= 4.12 + , bytestring + , containers + , criterion + , deepseq + , directory + , filepath + , split + , strict-stm + , tasty + , tasty-hunit + , text + , cardano-prelude + , cardano-chain-gen + , cardano-db + , cardano-db-sync + , cardano-crypto-class + , cardano-ledger-alonzo + , cardano-ledger-core + , cardano-ledger-shelley + , cardano-ledger-shelley-ma + , cardano-slotting + , io-classes + , ouroboros-consensus-cardano + , ouroboros-network diff --git a/cardano-chain-gen/src/Cardano/Mock/ChainSync/Server.hs b/cardano-chain-gen/src/Cardano/Mock/ChainSync/Server.hs index bc72c1eed..a47b8d8f9 100644 --- a/cardano-chain-gen/src/Cardano/Mock/ChainSync/Server.hs +++ b/cardano-chain-gen/src/Cardano/Mock/ChainSync/Server.hs @@ -22,6 +22,8 @@ module Cardano.Mock.ChainSync.Server , addBlock , rollback , readChain + , blockServing + , unBlockServing , withIOManager ) where @@ -32,8 +34,9 @@ import Control.Concurrent (threadDelay) import Control.Concurrent.Async import Control.Exception (bracket) import Control.Monad (forever) -import Control.Monad.Class.MonadSTM.Strict (MonadSTM (atomically), STM, StrictTVar, - modifyTVar, newTVarIO, readTVar, retry, writeTVar) +import Control.Monad.Class.MonadSTM.Strict (MonadSTM (atomically), STM, StrictTMVar, + StrictTVar, modifyTVar, newTMVarIO, newTVarIO, putTMVar, readTMVar, readTVar, retry, + takeTMVar, writeTVar) import Control.Tracer (nullTracer) import Data.ByteString.Lazy.Char8 (ByteString) import qualified Data.Map.Strict as Map @@ -88,6 +91,7 @@ import Cardano.Mock.ChainSync.State data ServerHandle m blk = ServerHandle { chainProducerState :: StrictTVar m (ChainProducerState blk) , threadHandle :: Async () + , blocking :: StrictTMVar m () } replaceGenesis :: MonadSTM m => ServerHandle m blk -> State blk -> STM m () @@ -114,6 +118,13 @@ rollback handle point = stopServer :: ServerHandle m blk -> IO () stopServer = cancel . threadHandle +blockServing :: MonadSTM m => ServerHandle m blk -> STM m () +blockServing handle = + takeTMVar (blocking handle) + +unBlockServing :: MonadSTM m => ServerHandle m blk -> STM m () +unBlockServing handle = putTMVar (blocking handle) () + type MockServerConstraint blk = ( SerialiseNodeToClientConstraints blk , ShowQuery (BlockQuery blk) @@ -138,8 +149,9 @@ forkServerThread -> IO (ServerHandle IO blk) forkServerThread iom config initSt networkMagic path = do chainSt <- newTVarIO $ initChainProducerState config initSt - thread <- async $ runLocalServer iom (configCodec config) networkMagic path chainSt - pure $ ServerHandle chainSt thread + lock <- newTMVarIO () + thread <- async $ runLocalServer iom (configCodec config) networkMagic path chainSt lock + pure $ ServerHandle chainSt thread lock withServerHandle :: forall blk a. MockServerConstraint blk @@ -161,8 +173,9 @@ runLocalServer -> NetworkMagic -> FilePath -> StrictTVar IO (ChainProducerState blk) + -> StrictTMVar IO () -> IO () -runLocalServer iom codecConfig networkMagic localDomainSock chainProducerState = +runLocalServer iom codecConfig networkMagic localDomainSock chainProducerState lockServing = withSnocket iom localDomainSock $ \ localSocket localSnocket -> do networkState <- NodeToClient.newNetworkMutableState _ <- NodeToClient.withServer @@ -170,27 +183,26 @@ runLocalServer iom codecConfig networkMagic localDomainSock chainProducerState = NodeToClient.nullNetworkServerTracers -- debuggingNetworkServerTracers networkState localSocket - (versions chainProducerState) + versions NodeToClient.networkErrorPolicies pure () where - versions :: StrictTVar IO (ChainProducerState blk) - -> Versions NodeToClientVersion + versions :: Versions NodeToClientVersion NodeToClientVersionData (OuroborosApplication 'ResponderMode LocalAddress ByteString IO Void ()) - versions state = + versions = let version = fromJust $ snd $ latestReleasedNodeVersion (Proxy @blk) allVersions = supportedNodeToClientVersions (Proxy @blk) blockVersion = fromJust $ Map.lookup version allVersions in simpleSingletonVersions version (NodeToClientVersionData networkMagic) - (NTC.responder version $ mkApps state version blockVersion (NTC.defaultCodecs codecConfig blockVersion version)) + (NTC.responder version $ mkApps version blockVersion (NTC.defaultCodecs codecConfig blockVersion version)) - mkApps :: StrictTVar IO (ChainProducerState blk) -> NodeToClientVersion -> BlockNodeToClientVersion blk -> DefaultCodecs blk IO + mkApps :: NodeToClientVersion -> BlockNodeToClientVersion blk -> DefaultCodecs blk IO -> NTC.Apps IO localPeer ByteString ByteString ByteString ByteString () - mkApps state _version blockVersion Codecs {..} = + mkApps _version blockVersion Codecs {..} = Apps { aChainSyncServer = chainSyncServer' , aTxSubmissionServer = txSubmitServer @@ -208,7 +220,7 @@ runLocalServer iom codecConfig networkMagic localDomainSock chainProducerState = cChainSyncCodec channel $ chainSyncServerPeer - $ chainSyncServer state codecConfig blockVersion + $ chainSyncServer chainProducerState lockServing codecConfig blockVersion txSubmitServer :: localPeer @@ -250,10 +262,11 @@ chainSyncServer , EncodeDisk blk blk ) => StrictTVar m (ChainProducerState blk) + -> StrictTMVar m () -> CodecConfig blk -> BlockNodeToClientVersion blk -> ChainSyncServer (Serialised blk) (Point blk) (Tip blk) m () -chainSyncServer state codec _blockVersion = +chainSyncServer state lockServing codec _blockVersion = ChainSyncServer $ idle <$> newFollower where idle :: FollowerId -> ServerStIdle (Serialised blk) (Point blk) (Tip blk) m () @@ -271,6 +284,7 @@ chainSyncServer state codec _blockVersion = -> m (Either (ServerStNext (Serialised blk) (Point blk) (Tip blk) m ()) (m (ServerStNext (Serialised blk) (Point blk) (Tip blk) m ()))) handleRequestNext r = do + atomically $ readTMVar lockServing mupdate <- tryReadChainUpdate r case mupdate of Just update -> pure (Left (sendNext r update)) diff --git a/cardano-chain-gen/test/Test/Cardano/Db/Mock/Config.hs b/cardano-chain-gen/src/Cardano/Mock/Db/Config.hs similarity index 75% rename from cardano-chain-gen/test/Test/Cardano/Db/Mock/Config.hs rename to cardano-chain-gen/src/Cardano/Mock/Db/Config.hs index 8b528dc5b..efd841083 100644 --- a/cardano-chain-gen/test/Test/Cardano/Db/Mock/Config.hs +++ b/cardano-chain-gen/src/Cardano/Mock/Db/Config.hs @@ -2,7 +2,7 @@ {-# LANGUAGE ScopedTypeVariables #-} {-# LANGUAGE TypeApplications #-} -module Test.Cardano.Db.Mock.Config where +module Cardano.Mock.Db.Config where import Cardano.Prelude (ReaderT, panic, stderr) @@ -50,20 +50,17 @@ import Cardano.SMASH.Server.PoolDataLayer import Cardano.Mock.ChainSync.Server import Cardano.Mock.Forging.Interpreter hiding (CardanoBlock) -rootTestDir :: FilePath -rootTestDir = "test/testfiles" +mkMutableDir :: FilePath -> FilePath -> FilePath +mkMutableDir rootTestDir testLabel = rootTestDir "temp" testLabel -mkMutableDir :: FilePath -> FilePath -mkMutableDir testLabel = rootTestDir "temp" testLabel +mkConfigDir :: FilePath -> FilePath -> FilePath +mkConfigDir rootTestDir config = rootTestDir config -mkConfigDir :: FilePath -> FilePath -mkConfigDir config = rootTestDir config +fingerprintRoot :: FilePath -> FilePath +fingerprintRoot rootTestDir = rootTestDir "fingerprint" -fingerprintRoot :: FilePath -fingerprintRoot = rootTestDir "fingerprint" - -mkFingerPrint :: FilePath -> FilePath -mkFingerPrint testLabel = fingerprintRoot testLabel +mkFingerPrint :: FilePath -> FilePath -> FilePath +mkFingerPrint rootTestDir testLabel = fingerprintRoot rootTestDir testLabel data Config = Config { topLevelConfig :: TopLevelConfig CardanoBlock @@ -192,17 +189,17 @@ emptyMetricsSetters = MetricSetters , metricsSetDbSlotHeight = \_ -> pure () } -withFullConfig :: FilePath -> FilePath +withFullConfig :: FilePath -> FilePath -> FilePath -> (Interpreter -> ServerHandle IO CardanoBlock -> DBSyncEnv -> IO ()) -> IOManager -> [(Text, Text)] -> IO () -withFullConfig config testLabel action iom migr = do +withFullConfig rootTestDir config testLabel action iom migr = do recreateDir mutableDir cfg <- mkConfig configDir mutableDir - fingerFile <- prepareFingerprintFile testLabel + fingerFile <- prepareFingerprintFile rootTestDir testLabel let dbsyncParams = syncNodeParams cfg - let trce = nullTracer + -- let trce = nullTracer -- Replace with this for better debugging of tests - -- trce <- configureLogging dbsyncParams "db-sync-node" + trce <- configureLogging dbsyncParams "db-sync-node" let dbsyncRun = runDbSync emptyMetricsSetters migr iom trce dbsyncParams True 35 35 let initSt = Consensus.pInfoInitLedger $ protocolInfo cfg withInterpreter (protocolInfoForging cfg) nullTracer fingerFile $ \interpreter -> do @@ -215,15 +212,47 @@ withFullConfig config testLabel action iom migr = do _ <- hSilence [stderr] $ Db.recreateDB (getDBSyncPGPass dbSync) action interpreter mockServer dbSync where - configDir = mkConfigDir config - mutableDir = mkMutableDir testLabel - -prepareFingerprintFile :: FilePath -> IO FilePath -prepareFingerprintFile testLabel = do - createDirectoryIfMissing True fingerprintRoot + configDir = mkConfigDir rootTestDir config + mutableDir = mkMutableDir rootTestDir testLabel + +-- Same as 'withFullConfig' but doesn't use the bracket style. Can be used with +-- 'cleanFullConfig' to cleanup the env. +mkFullConfig :: FilePath -> FilePath -> FilePath + -> IOManager -> [(Text, Text)] + -> IO (Interpreter, ServerHandle IO CardanoBlock, DBSyncEnv) +mkFullConfig rootTestDir config testLabel iom migr = do + recreateDir mutableDir + cfg <- mkConfig configDir mutableDir + fingerFile <- prepareFingerprintFile rootTestDir testLabel + let dbsyncParams = syncNodeParams cfg + let trce = nullTracer + -- Replace with this for better debugging of tests + -- trce <- configureLogging dbsyncParams "db-sync-node" + let dbsyncRun = runDbSync emptyMetricsSetters migr iom trce dbsyncParams True 35 35 + let initSt = Consensus.pInfoInitLedger $ protocolInfo cfg + interpreter <- initInterpreter (protocolInfoForging cfg) nullTracer fingerFile + serverHandle <- forkServerThread @CardanoBlock iom (topLevelConfig cfg) initSt (NetworkMagic 42) + (unSocketPath (enpSocketPath $ syncNodeParams cfg)) + dbSync <- mkDBSyncEnv dbsyncParams dbsyncRun + _ <- hSilence [stderr] $ Db.recreateDB (getDBSyncPGPass dbSync) + pure (interpreter, serverHandle, dbSync) + where + configDir = mkConfigDir rootTestDir config + mutableDir = mkMutableDir rootTestDir testLabel + +cleanFullConfig :: (Interpreter, ServerHandle IO CardanoBlock, DBSyncEnv) + -> IO () +cleanFullConfig (interpreter, serverHandle, dbSync) = do + stopDBSyncIfRunning dbSync + stopServer serverHandle + finalizeFingerprint interpreter + +prepareFingerprintFile :: FilePath -> FilePath -> IO FilePath +prepareFingerprintFile rootTestDir testLabel = do + createDirectoryIfMissing True (fingerprintRoot rootTestDir) pure fingerprintFile where - fingerprintFile = mkFingerPrint testLabel + fingerprintFile = mkFingerPrint rootTestDir testLabel recreateDir :: FilePath -> IO () recreateDir path = do diff --git a/cardano-chain-gen/test/Test/Cardano/Db/Mock/Validate.hs b/cardano-chain-gen/src/Cardano/Mock/Db/Validate.hs similarity index 91% rename from cardano-chain-gen/test/Test/Cardano/Db/Mock/Validate.hs rename to cardano-chain-gen/src/Cardano/Mock/Db/Validate.hs index 5ba17b016..cec4bfb90 100644 --- a/cardano-chain-gen/test/Test/Cardano/Db/Mock/Validate.hs +++ b/cardano-chain-gen/src/Cardano/Mock/Db/Validate.hs @@ -5,7 +5,7 @@ {-# LANGUAGE OverloadedStrings #-} {-# LANGUAGE ScopedTypeVariables #-} -module Test.Cardano.Db.Mock.Validate where +module Cardano.Mock.Db.Validate where import Cardano.Db import Control.Concurrent @@ -25,7 +25,7 @@ import Data.Word (Word64) import GHC.Records (HasField (..)) import Database.Esqueleto.Legacy (InnerJoin (..), SqlExpr, countRows, from, on, select, - unValue, (==.), (^.)) + unValue, val, where_, (==.), (^.)) import Database.Persist.Sql (Entity, SqlBackend, entityVal) import Database.PostgreSQL.Simple (SqlError (..)) @@ -42,10 +42,10 @@ import Cardano.SMASH.Server.Types import Ouroboros.Consensus.Cardano.Block import Ouroboros.Consensus.Shelley.Ledger (ShelleyBlock) +import Cardano.Mock.Db.Config import Cardano.Mock.Forging.Tx.Generic import Cardano.Mock.Forging.Types -import Test.Cardano.Db.Mock.Config import Test.Tasty.HUnit @@ -65,9 +65,16 @@ assertRewardCount :: DBSyncEnv -> Word64 -> IO () assertRewardCount env n = assertEqBackoff env queryRewardCount n defaultDelays "Unexpected rewards count" +assertBlockNo :: DBSyncEnv -> Maybe Int -> [Int] -> IO () +assertBlockNo env mBlockNo delays = + assertEqBackoff env queryBlockHeight (fromIntegral <$> mBlockNo) delays "Unexpected BlockNo" + assertBlockNoBackoff :: DBSyncEnv -> Int -> IO () -assertBlockNoBackoff env blockNo = - assertEqBackoff env queryBlockHeight (Just $ fromIntegral blockNo) defaultDelays "Unexpected BlockNo" +assertBlockNoBackoff = assertBlockNoBackoffTimes defaultDelays + +assertBlockNoBackoffTimes :: [Int] -> DBSyncEnv -> Int -> IO () +assertBlockNoBackoffTimes times env blockNo = + assertEqBackoff env queryBlockHeight (Just $ fromIntegral blockNo) times "Unexpected BlockNo" defaultDelays :: [Int] defaultDelays = [1,2,4,8,16,32,64,128] @@ -201,6 +208,24 @@ assertRewardCounts env st filterAddr expected = do pure (reward, stake_addr ^. StakeAddressHashRaw) pure $ fmap (bimap entityVal unValue) res +assertEpochStake :: DBSyncEnv -> Word64 -> IO () +assertEpochStake env expected = + assertEqBackoff env q expected defaultDelays "Unexpected epoch stake counts" + where + q = + maybe 0 unValue . listToMaybe <$> + (select . from $ \(_a :: SqlExpr (Entity EpochStake)) -> pure countRows) + +assertEpochStakeEpoch :: DBSyncEnv -> Word64 -> Word64 -> IO () +assertEpochStakeEpoch env e expected = + assertEqBackoff env q expected defaultDelays "Unexpected epoch stake counts" + where + q = + maybe 0 unValue . listToMaybe <$> + (select . from $ \(a :: SqlExpr (Entity EpochStake)) -> do + where_ (a ^. EpochStakeEpochNo ==. val e) + pure countRows + ) assertAlonzoCounts :: DBSyncEnv -> (Word64, Word64, Word64, Word64, Word64, Word64, Word64, Word64) -> IO () assertAlonzoCounts env expected = diff --git a/cardano-chain-gen/src/Cardano/Mock/Forging/Examples.hs b/cardano-chain-gen/src/Cardano/Mock/Forging/Examples.hs new file mode 100644 index 000000000..f20a6e11e --- /dev/null +++ b/cardano-chain-gen/src/Cardano/Mock/Forging/Examples.hs @@ -0,0 +1,42 @@ +module Cardano.Mock.Forging.Examples where + +import Cardano.Prelude hiding (length, (.)) + +import Data.List.Extra + +import Cardano.Ledger.Mary.Value +import Cardano.Ledger.Shelley.API +import Cardano.Mock.Forging.Interpreter +import qualified Cardano.Mock.Forging.Tx.Alonzo as Alonzo +import Cardano.Mock.Forging.Tx.Generic +import Cardano.Mock.Forging.Types + +delegateAndSendBlocks :: Int -> Interpreter -> IO [CardanoBlock] +delegateAndSendBlocks n interpreter = do + addrFrom <- withAlonzoLedgerState interpreter $ resolveAddress (UTxOIndex 0) + registerBlocks <- forM (chunksOf 500 creds) $ \blockCreds -> do + blockTxs <- withAlonzoLedgerState interpreter $ \_st -> + forM (chunksOf 10 blockCreds) $ \txCreds -> -- 10 per tx + Alonzo.mkDCertTx (fmap (DCertDeleg . RegKey) txCreds) (Wdrl mempty) + forgeNextFindLeader interpreter (TxAlonzo <$> blockTxs) + + delegateBlocks <- forM (chunksOf 500 creds) $ \blockCreds -> do + blockTxs <- withAlonzoLedgerState interpreter $ \st -> + forM (chunksOf 10 blockCreds) $ \txCreds -> --do -- 10 per tx + Alonzo.mkDCertTx + (fmap (\ (poolIx, cred) -> DCertDeleg $ Delegate $ Delegation cred (resolvePool (PoolIndex poolIx) st)) + (zip (cycle [0,1,2]) txCreds)) + (Wdrl mempty) + forgeNextFindLeader interpreter (TxAlonzo <$> blockTxs) + + let utxoIndex = UTxOAddress addrFrom + sendBlocks <- forM (chunksOf 500 addresses) $ \blockAddresses -> do + blockTxs <- withAlonzoLedgerState interpreter $ \st -> + forM (chunksOf 10 blockAddresses) $ \txAddresses -> + Alonzo.mkPaymentTx' utxoIndex (fmap (\addr -> (UTxOAddress addr, Value 1 mempty)) txAddresses) st + forgeNextFindLeader interpreter (TxAlonzo <$> blockTxs) + pure $ registerBlocks <> delegateBlocks <> sendBlocks + where + creds = createStakeCredentials n + pcreds = createPaymentCredentials n + addresses = fmap (\(pcred, cred) -> Addr Testnet pcred (StakeRefBase cred)) (zip pcreds creds) diff --git a/cardano-chain-gen/src/Cardano/Mock/Forging/Interpreter.hs b/cardano-chain-gen/src/Cardano/Mock/Forging/Interpreter.hs index a8c584541..35f7aee32 100644 --- a/cardano-chain-gen/src/Cardano/Mock/Forging/Interpreter.hs +++ b/cardano-chain-gen/src/Cardano/Mock/Forging/Interpreter.hs @@ -18,6 +18,7 @@ module Cardano.Mock.Forging.Interpreter , NodeId (..) , initInterpreter , withInterpreter + , finalizeFingerprint , forgeNextFindLeader , forgeNext , forgeNextAfter diff --git a/cardano-chain-gen/src/Cardano/Mock/Forging/Tx/Alonzo.hs b/cardano-chain-gen/src/Cardano/Mock/Forging/Tx/Alonzo.hs index 55d7e4afb..665687452 100644 --- a/cardano-chain-gen/src/Cardano/Mock/Forging/Tx/Alonzo.hs +++ b/cardano-chain-gen/src/Cardano/Mock/Forging/Tx/Alonzo.hs @@ -8,7 +8,7 @@ module Cardano.Mock.Forging.Tx.Alonzo where -import Cardano.Prelude hiding ((.)) +import Cardano.Prelude hiding (sum, (.)) import qualified Data.Map.Strict as Map import Data.Maybe (fromJust) @@ -109,6 +109,24 @@ mkPaymentTx inputIndex outputIndex amount fees sta = do change = TxOut addr' (valueFromList (fromIntegral $ fromIntegral inputValue - amount - fees) []) Strict.SNothing Right $ mkSimpleTx True $ consPaymentTxBody input mempty (StrictSeq.fromList [output, change]) (Coin fees) mempty +mkPaymentTx' :: AlonzoUTxOIndex + -> [(AlonzoUTxOIndex, Value StandardCrypto)] + -> AlonzoLedgerState + -> Either ForgingError (ValidatedTx (AlonzoEra StandardCrypto)) +mkPaymentTx' inputIndex outputIndex sta = do + inputPair <- fst <$> resolveUTxOIndex inputIndex sta + outps <- mapM mkOuts outputIndex + + let inps = Set.singleton $ fst inputPair + TxOut addr' (Value inputValue _) _ = snd inputPair + outValue = sum ((\ (Value vl _) -> vl) . snd <$> outputIndex) + change = TxOut addr' (valueFromList (fromIntegral $ fromIntegral inputValue - outValue) []) Strict.SNothing + Right $ mkSimpleTx True $ consPaymentTxBody inps mempty (StrictSeq.fromList $ outps ++ [change]) (Coin 0) mempty + where + mkOuts (outIx, vl) = do + addr <- resolveAddress outIx sta + Right $ TxOut addr vl Strict.SNothing + mkLockByScriptTx :: AlonzoUTxOIndex -> [Bool] -> Integer -> Integer -> AlonzoLedgerState -> Either ForgingError (ValidatedTx (AlonzoEra StandardCrypto)) diff --git a/cardano-chain-gen/src/Cardano/Mock/Forging/Tx/Generic.hs b/cardano-chain-gen/src/Cardano/Mock/Forging/Tx/Generic.hs index fcc1d5148..810d5843e 100644 --- a/cardano-chain-gen/src/Cardano/Mock/Forging/Tx/Generic.hs +++ b/cardano-chain-gen/src/Cardano/Mock/Forging/Tx/Generic.hs @@ -11,6 +11,9 @@ module Cardano.Mock.Forging.Tx.Generic , resolveUTxOIndex , resolveStakeCreds , resolvePool + , createStakeCredentials + , createPaymentCredentials + , mkDummyScriptHash ) where import Cardano.Prelude hiding (length, (.)) @@ -24,7 +27,9 @@ import Cardano.Ledger.Address import Cardano.Ledger.BaseTypes import qualified Cardano.Ledger.Core as Core import Cardano.Ledger.Credential +import Cardano.Ledger.Crypto (ADDRHASH) import Cardano.Ledger.Era (Crypto) +import Cardano.Ledger.Hashes import Cardano.Ledger.Keys import Cardano.Ledger.Shelley.LedgerState hiding (LedgerState) import Cardano.Ledger.Shelley.TxBody @@ -39,6 +44,8 @@ import qualified Ouroboros.Consensus.Shelley.Ledger.Ledger as Consensus import Cardano.Mock.Forging.Tx.Alonzo.ScriptsExamples import Cardano.Mock.Forging.Types +import Test.Cardano.Ledger.Shelley.Examples.Consensus + resolveAddress :: forall era. (Crypto era ~ StandardCrypto, HasField "address" (Core.TxOut era) (Addr (Crypto era))) => UTxOIndex era -> LedgerState (ShelleyBlock era) -> Either ForgingError (Addr (Crypto era)) @@ -161,3 +168,14 @@ unregisteredPools = , KeyHash "222462543264795t3298745680239746523897456238974563298348" , KeyHash "33323876542397465497834256329487563428975634827956348975" ] + +createStakeCredentials :: Int -> [StakeCredential StandardCrypto] +createStakeCredentials n = + fmap (KeyHashObj . KeyHash . mkDummyHash (Proxy @(ADDRHASH StandardCrypto))) [1..n] + +createPaymentCredentials :: Int -> [PaymentCredential StandardCrypto] +createPaymentCredentials n = + fmap (KeyHashObj . KeyHash . mkDummyHash (Proxy @(ADDRHASH StandardCrypto))) [1..n] + +mkDummyScriptHash :: Int -> ScriptHash StandardCrypto +mkDummyScriptHash n = ScriptHash $ mkDummyHash (Proxy @(ADDRHASH StandardCrypto)) n diff --git a/cardano-chain-gen/test/Test/Cardano/Db/Mock/UnifiedApi.hs b/cardano-chain-gen/src/Cardano/Mock/UnifiedApi.hs similarity index 93% rename from cardano-chain-gen/test/Test/Cardano/Db/Mock/UnifiedApi.hs rename to cardano-chain-gen/src/Cardano/Mock/UnifiedApi.hs index afaf817fb..f58490e50 100644 --- a/cardano-chain-gen/test/Test/Cardano/Db/Mock/UnifiedApi.hs +++ b/cardano-chain-gen/src/Cardano/Mock/UnifiedApi.hs @@ -1,6 +1,7 @@ -module Test.Cardano.Db.Mock.UnifiedApi where +module Cardano.Mock.UnifiedApi where import Control.Monad.Class.MonadSTM.Strict +import Data.Word (Word64) import Cardano.Slotting.Slot (SlotNo (..)) @@ -28,6 +29,12 @@ forgeNextFindLeaderAndSubmit interpreter mockServer txs' = do atomically $ addBlock mockServer blk pure blk +forgeNextSkipSlotsFindLeaderAndSubmit :: Interpreter -> ServerHandle IO CardanoBlock -> Word64 -> [TxEra] -> IO CardanoBlock +forgeNextSkipSlotsFindLeaderAndSubmit interpreter mockServer skipSlots txs' = do + blk <- forgeNextAfter interpreter skipSlots txs' + atomically $ addBlock mockServer blk + pure blk + forgeAndSubmitBlocks :: Interpreter -> ServerHandle IO CardanoBlock -> Int -> IO [CardanoBlock] forgeAndSubmitBlocks interpreter mockServer blocksToCreate = do forM [1..blocksToCreate] $ \_ -> forgeNextFindLeaderAndSubmit interpreter mockServer [] diff --git a/cardano-chain-gen/test/Test/Cardano/Db/Mock/Unit.hs b/cardano-chain-gen/test/Test/Cardano/Db/Mock/Unit.hs index 6dfbc3cfe..8153e3e34 100644 --- a/cardano-chain-gen/test/Test/Cardano/Db/Mock/Unit.hs +++ b/cardano-chain-gen/test/Test/Cardano/Db/Mock/Unit.hs @@ -36,20 +36,22 @@ import Cardano.SMASH.Server.PoolDataLayer import Cardano.SMASH.Server.Types import Cardano.Mock.ChainSync.Server +import Cardano.Mock.Db.Validate +import Cardano.Mock.Db.Config hiding (withFullConfig) +import qualified Cardano.Mock.Db.Config as Config +import Cardano.Mock.Forging.Examples import Cardano.Mock.Forging.Interpreter import qualified Cardano.Mock.Forging.Tx.Alonzo as Alonzo import Cardano.Mock.Forging.Tx.Alonzo.ScriptsExamples import Cardano.Mock.Forging.Tx.Generic import qualified Cardano.Mock.Forging.Tx.Shelley as Shelley import Cardano.Mock.Forging.Types +import Cardano.Mock.UnifiedApi import Test.Tasty (TestTree, testGroup) import Test.Tasty.HUnit (Assertion, assertBool, assertEqual, assertFailure, testCase) -import Test.Cardano.Db.Mock.Config import Test.Cardano.Db.Mock.Examples -import Test.Cardano.Db.Mock.UnifiedApi -import Test.Cardano.Db.Mock.Validate unitTests :: IOManager -> [(Text, Text)] -> TestTree unitTests iom knownMigrations = @@ -95,6 +97,14 @@ unitTests iom knownMigrations = , test "rollback on epoch boundary" rollbackBoundary , test "single MIR Cert multiple outputs" singleMIRCertMultiOut ] + , testGroup "stake distribution" + [ test "stake distribution from genesis" stakeDistGenesis + , test "2000 delegations" delegations2000 + , test "2001 delegations" delegations2001 + , test "8000 delegations" delegations8000 + , test "many delegations" delegationsMany + , test "many delegations, not dense chain" delegationsManyNotDense + ] , testGroup "plutus spend scripts" [ test "simple script lock" simpleScript , test "unlock script in same block" unlockScriptSameBlock @@ -133,6 +143,14 @@ unitTests iom knownMigrations = defaultConfigDir :: FilePath defaultConfigDir = "config" +rootTestDir :: FilePath +rootTestDir = "test/testfiles" + +withFullConfig :: FilePath -> FilePath + -> (Interpreter -> ServerHandle IO CardanoBlock -> DBSyncEnv -> IO ()) + -> IOManager -> [(Text, Text)] -> IO () +withFullConfig = Config.withFullConfig rootTestDir + forgeBlocks :: IOManager -> [(Text, Text)] -> Assertion forgeBlocks = do withFullConfig defaultConfigDir testLabel $ \interpreter _mockServer _dbSync -> do @@ -842,6 +860,129 @@ singleMIRCertMultiOut = where testLabel = "singleMIRCertMultiOut" +stakeDistGenesis :: IOManager -> [(Text, Text)] -> Assertion +stakeDistGenesis = + withFullConfig "config" testLabel $ \interpreter mockServer dbSync -> do + startDBSync dbSync + a <- fillUntilNextEpoch interpreter mockServer + assertBlockNoBackoff dbSync (fromIntegral $ length a - 1) + -- There are 5 delegations in genesis + assertEpochStake dbSync 5 + where + testLabel = "stakeDistGenesis" + +delegations2000 :: IOManager -> [(Text, Text)] -> Assertion +delegations2000 = + withFullConfig "config" testLabel $ \interpreter mockServer dbSync -> do + startDBSync dbSync + a <- delegateAndSendBlocks 1995 interpreter + forM_ a $ atomically . addBlock mockServer + b <- fillUntilNextEpoch interpreter mockServer + c <- fillUntilNextEpoch interpreter mockServer + + assertBlockNoBackoff dbSync (fromIntegral $ length a + length b + length c - 1) + -- There are exactly 2000 entries on the second epoch, 5 from genesis and 1995 manually added + assertEpochStakeEpoch dbSync 2 2000 + + _ <- forgeNextFindLeaderAndSubmit interpreter mockServer [] + assertBlockNoBackoff dbSync (fromIntegral $ length a + length b + length c) + assertEpochStakeEpoch dbSync 2 2000 + where + testLabel = "delegations2000" + +delegations2001 :: IOManager -> [(Text, Text)] -> Assertion +delegations2001 = + withFullConfig "config" testLabel $ \interpreter mockServer dbSync -> do + startDBSync dbSync + a <- delegateAndSendBlocks 1996 interpreter + forM_ a $ atomically . addBlock mockServer + b <- fillUntilNextEpoch interpreter mockServer + c <- fillUntilNextEpoch interpreter mockServer + + assertBlockNoBackoff dbSync (fromIntegral $ length a + length b + length c - 1) + -- The first block of epoch inserts 2000 out of 2001 epoch distribution. + assertEpochStakeEpoch dbSync 2 2000 + -- The remaining entry is inserted on the next block. + _ <- forgeNextFindLeaderAndSubmit interpreter mockServer [] + assertBlockNoBackoff dbSync (fromIntegral $ length a + length b + length c) + assertEpochStakeEpoch dbSync 2 2001 + where + testLabel = "delegations2001" + +delegations8000 :: IOManager -> [(Text, Text)] -> Assertion +delegations8000 = + withFullConfig "config" testLabel $ \interpreter mockServer dbSync -> do + startDBSync dbSync + a <- delegateAndSendBlocks 7995 interpreter + forM_ a $ atomically . addBlock mockServer + b <- fillEpochs interpreter mockServer 3 + + assertBlockNoBackoff dbSync (fromIntegral $ length a + length b - 1) + assertEpochStakeEpoch dbSync 3 2000 + + _ <- forgeNextFindLeaderAndSubmit interpreter mockServer [] + assertEpochStakeEpoch dbSync 3 4000 + + _ <- forgeNextFindLeaderAndSubmit interpreter mockServer [] + assertEpochStakeEpoch dbSync 3 6000 + + _ <- forgeNextFindLeaderAndSubmit interpreter mockServer [] + assertEpochStakeEpoch dbSync 3 8000 + + _ <- forgeNextFindLeaderAndSubmit interpreter mockServer [] + assertEpochStakeEpoch dbSync 3 8000 + where + testLabel = "delegations8000" + +delegationsMany :: IOManager -> [(Text, Text)] -> Assertion +delegationsMany = + withFullConfig "config" testLabel $ \interpreter mockServer dbSync -> do + startDBSync dbSync + a <- delegateAndSendBlocks 40000 interpreter + forM_ a $ atomically . addBlock mockServer + b <- fillEpochs interpreter mockServer 5 + + -- too long. We cannot use default delays + assertBlockNoBackoffTimes (repeat 10) dbSync (fromIntegral $ length a + length b - 1) + -- The slice size here is + -- 1 + div (delegationsLen * 5) expectedBlocks = 2001 + -- instead of 2000, because there are many delegations + assertEpochStakeEpoch dbSync 7 2001 + + _ <- forgeNextFindLeaderAndSubmit interpreter mockServer [] + assertEpochStakeEpoch dbSync 7 4002 + + _ <- forgeNextFindLeaderAndSubmit interpreter mockServer [] + assertEpochStakeEpoch dbSync 7 6003 + where + testLabel = "delegationsMany" + +delegationsManyNotDense :: IOManager -> [(Text, Text)] -> Assertion +delegationsManyNotDense = + withFullConfig "config" testLabel $ \interpreter mockServer dbSync -> do + startDBSync dbSync + a <- delegateAndSendBlocks 40000 interpreter + forM_ a $ atomically . addBlock mockServer + b <- fillEpochs interpreter mockServer 5 + + -- too long. We cannot use default delays + assertBlockNoBackoffTimes (repeat 10) dbSync (fromIntegral $ length a + length b - 1) + -- The slice size here is + -- 1 + div (delegationsLen * 5) expectedBlocks = 2001 + -- instead of 2000, because there are many delegations + assertEpochStakeEpoch dbSync 7 2001 + + -- Blocks come on average every 5 slots. If we skip 15 slots before each block, + -- we are expected to get only 1/4 of the expected blocks. The adjusted slices + -- should still be long enough to cover everything. + replicateM_ 40 $ + forgeNextSkipSlotsFindLeaderAndSubmit interpreter mockServer 15 [] + + -- Even if the chain is not dense, all distributions are inserted. + assertEpochStakeEpoch dbSync 7 40005 + where + testLabel = "delegationsManyNotDense" + simpleScript :: IOManager -> [(Text, Text)] -> Assertion simpleScript = withFullConfig "config" testLabel $ \interpreter mockServer dbSync -> do diff --git a/cardano-chain-gen/test/testfiles/config/genesis.byron.json b/cardano-chain-gen/test/testfiles/config/genesis.byron.json index cf088f937..25ced6be5 100644 --- a/cardano-chain-gen/test/testfiles/config/genesis.byron.json +++ b/cardano-chain-gen/test/testfiles/config/genesis.byron.json @@ -26,6 +26,6 @@ { "summand": "155381000000000" , "multiplier": "43946000000" } , "unlockStakeEpoch": "18446744073709551615" } -, "protocolConsts": { "k": 216 , "protocolMagic": 42 } +, "protocolConsts": { "k": 10 , "protocolMagic": 42 } , "avvmDistr": {} } diff --git a/cardano-chain-gen/test/testfiles/config/test-config.json b/cardano-chain-gen/test/testfiles/config/test-config.json index 60a3306d4..64e59bf85 100644 --- a/cardano-chain-gen/test/testfiles/config/test-config.json +++ b/cardano-chain-gen/test/testfiles/config/test-config.json @@ -4,7 +4,7 @@ "ApplicationName": "cardano-sl", "ApplicationVersion": 0, "ByronGenesisFile": "genesis.byron.json", - "ByronGenesisHash": "462bb9869a5a6e4325cc294ca659d68607e8a6f37b5be96ea663fdedfe2b5949", + "ByronGenesisHash": "865a9da19944fc00cefe5a0cdcb6dc9d3964a74681d9488ab79967f13a6400b3", "LastKnownBlockVersion-Alt": 0, "LastKnownBlockVersion-Major": 5, "LastKnownBlockVersion-Minor": 1, diff --git a/cardano-chain-gen/test/testfiles/fingerprint/delegations2000 b/cardano-chain-gen/test/testfiles/fingerprint/delegations2000 new file mode 100644 index 000000000..969f76da4 --- /dev/null +++ b/cardano-chain-gen/test/testfiles/fingerprint/delegations2000 @@ -0,0 +1 @@ +[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,1002,1003] \ No newline at end of file diff --git a/cardano-chain-gen/test/testfiles/fingerprint/delegations2001 b/cardano-chain-gen/test/testfiles/fingerprint/delegations2001 new file mode 100644 index 000000000..51e5c28f8 --- /dev/null +++ b/cardano-chain-gen/test/testfiles/fingerprint/delegations2001 @@ -0,0 +1 @@ +[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,1006,1011] \ No newline at end of file diff --git a/cardano-chain-gen/test/testfiles/fingerprint/delegations8000 b/cardano-chain-gen/test/testfiles/fingerprint/delegations8000 new file mode 100644 index 000000000..f0a18e6c0 --- /dev/null +++ b/cardano-chain-gen/test/testfiles/fingerprint/delegations8000 @@ -0,0 +1 @@ +[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,1002,1007,1012,1014,1021,1022,1025,1026,1028,1038,1041,1058,1059,1060,1062,1063,1064,1069,1070,1079,1084,1092,1093,1109,1110,1111,1119,1120,1132,1134,1135,1148,1149,1167,1173,1178,1189,1192,1194,1195,1196,1202,1203,1209,1221,1223,1232,1233,1240,1246,1257,1263,1267,1268,1271,1273,1277,1280,1282,1285,1297,1299,1306,1313,1318,1319,1323,1325,1328,1333,1336,1341,1344,1348,1350,1352,1359,1362,1371,1372,1378,1379,1383,1393,1397,1399,1414,1417,1420,1421,1433,1434,1435,1460,1466,1467,1472,1474,1476,1479,1481,1482,1485,1497,1499,1503,1506,1515,1517,1521] \ No newline at end of file diff --git a/cardano-chain-gen/test/testfiles/fingerprint/delegationsMany b/cardano-chain-gen/test/testfiles/fingerprint/delegationsMany new file mode 100644 index 000000000..9de734b61 --- /dev/null +++ b/cardano-chain-gen/test/testfiles/fingerprint/delegationsMany @@ -0,0 +1 @@ +[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,1004,1010,1013,1019,1031,1034,1038,1041,1052,1060,1061,1069,1076,1082,1090,1105,1107,1113,1116,1126,1128,1130,1134,1136,1149,1154,1156,1157,1158,1160,1169,1176,1177,1185,1186,1190,1200,1202,1205,1207,1208,1209,1214,1215,1222,1227,1230,1234,1235,1239,1257,1259,1264,1272,1275,1278,1283,1285,1288,1290,1293,1304,1308,1321,1325,1326,1331,1334,1337,1340,1344,1348,1349,1350,1362,1364,1367,1369,1372,1373,1376,1384,1385,1388,1391,1397,1403,1406,1408,1415,1417,1427,1431,1432,1435,1436,1437,1438,1465,1466,1470,1472,1474,1491,1499,1500,1518,1529,1545,1546,1559,1560,1562,1573,1574,1576,1579,1586,1606,1610,1613,1614,1620,1621,1629,1634,1642,1646,1648,1653,1660,1665,1668,1674,1683,1686,1699,1703,1715,1716,1718,1719,1731,1745,1752,1761,1764,1766,1769,1777,1784,1786,1791,1792,1799,1804,1814,1821,1836,1839,1841,1851,1852,1869,1879,1880,1882,1888,1891,1905,1906,1907,1908,1915,1925,1926,1929,1933,1939,1946,1955,1956,1959,1967,1974,1978,1981,1985,1988,1991,1997,2001,2002,2011,2015,2016,2017,2022,2030,2031,2033,2037,2042,2050,2056,2060,2064,2070,2077,2079,2088,2090,2095,2096,2104,2105,2111,2112,2116,2123,2130,2132,2135,2137,2138,2140,2147,2149,2154,2167,2174,2177,2182,2185,2189,2192,2194,2206,2218,2224,2228,2232,2234,2257,2268,2269,2270,2271,2273,2278,2279,2287,2289,2290,2292,2306,2311,2313,2315,2319,2327,2330,2351,2352,2356,2362,2364,2369,2377,2383,2386,2395,2400,2404,2405,2406,2413,2415,2423,2424,2431,2432,2437,2438,2449,2464,2468,2469,2477,2486,2503,2504,2511,2517,2519,2522,2526,2527,2529,2544,2549,2551,2553,2559,2567,2569,2570,2571,2579,2581,2587,2588,2592,2594,2595,2607,2609,2610,2614,2617,2620,2622,2632,2636,2638,2644,2645,2646,2647,2649,2652,2655,2656,2658,2662,2666,2668,2674,2675,2676,2692,2698,2701,2713,2717,2727,2728,2730,2735,2738,2740,2742,2743,2763,2774,2785,2786,2788,2791,2802,2805,2809,2814,2816,2819,2833,2836,2839,2844,2845,2846,2858,2863,2867,2869,2871,2872,2874,2880,2882,2883,2893,2894,2895,2900,2909,2925,2929,2958,2960,2962,2965,2966,2973,2974,2979,2985,2987,3000,3001,3005,3008,3020,3028,3030,3031,3033,3036,3044,3046,3050,3061,3064,3066,3071,3076,3082,3088,3091,3106,3108,3117,3122,3123,3129,3130,3132,3135,3136,3144,3172,3174,3177,3178,3182,3190,3193,3200,3204,3210,3212,3214,3215,3216,3218,3219,3229,3230,3234,3241,3245,3248,3254,3263,3264,3268,3278,3280,3286,3289,3292,3295,3305,3306,3309,3317,3319,3320,3328,3333,3334,3336,3346,3356,3359,3360,3363,3364,3365,3368,3370,3373,3379,3384,3387,3389,3390,3395,3399,3409,3422,3425,3435,3438,3447,3450,3452,3461,3463,3467,3472,3477,3481,3485,3488,3491,3493,3495,3496,3498,3500,3502,3504] \ No newline at end of file diff --git a/cardano-chain-gen/test/testfiles/fingerprint/delegationsManyNotDense b/cardano-chain-gen/test/testfiles/fingerprint/delegationsManyNotDense new file mode 100644 index 000000000..c51ffeda4 --- /dev/null +++ b/cardano-chain-gen/test/testfiles/fingerprint/delegationsManyNotDense @@ -0,0 +1 @@ +[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,1004,1010,1013,1019,1031,1034,1038,1041,1052,1060,1061,1069,1076,1082,1090,1105,1107,1113,1116,1126,1128,1130,1134,1136,1149,1154,1156,1157,1158,1160,1169,1176,1177,1185,1186,1190,1200,1202,1205,1207,1208,1209,1214,1215,1222,1227,1230,1234,1235,1239,1257,1259,1264,1272,1275,1278,1283,1285,1288,1290,1293,1304,1308,1321,1325,1326,1331,1334,1337,1340,1344,1348,1349,1350,1362,1364,1367,1369,1372,1373,1376,1384,1385,1388,1391,1397,1403,1406,1408,1415,1417,1427,1431,1432,1435,1436,1437,1438,1465,1466,1470,1472,1474,1491,1499,1500,1518,1529,1545,1546,1559,1560,1562,1573,1574,1576,1579,1586,1606,1610,1613,1614,1620,1621,1629,1634,1642,1646,1648,1653,1660,1665,1668,1674,1683,1686,1699,1703,1715,1716,1718,1719,1731,1745,1752,1761,1764,1766,1769,1777,1784,1786,1791,1792,1799,1804,1814,1821,1836,1839,1841,1851,1852,1869,1879,1880,1882,1888,1891,1905,1906,1907,1908,1915,1925,1926,1929,1933,1939,1946,1955,1956,1959,1967,1974,1978,1981,1985,1988,1991,1997,2001,2002,2011,2015,2016,2017,2022,2030,2031,2033,2037,2042,2050,2056,2060,2064,2070,2077,2079,2088,2090,2095,2096,2104,2105,2111,2112,2116,2123,2130,2132,2135,2137,2138,2140,2147,2149,2154,2167,2174,2177,2182,2185,2189,2192,2194,2206,2218,2224,2228,2232,2234,2257,2268,2269,2270,2271,2273,2278,2279,2287,2289,2290,2292,2306,2311,2313,2315,2319,2327,2330,2351,2352,2356,2362,2364,2369,2377,2383,2386,2395,2400,2404,2405,2406,2413,2415,2423,2424,2431,2432,2437,2438,2449,2464,2468,2469,2477,2486,2503,2504,2511,2517,2519,2522,2526,2527,2529,2544,2549,2551,2553,2559,2567,2569,2570,2571,2579,2581,2587,2588,2592,2594,2595,2607,2609,2610,2614,2617,2620,2622,2632,2636,2638,2644,2645,2646,2647,2649,2652,2655,2656,2658,2662,2666,2668,2674,2675,2676,2692,2698,2701,2713,2717,2727,2728,2730,2735,2738,2740,2742,2743,2763,2774,2785,2786,2788,2791,2802,2805,2809,2814,2816,2819,2833,2836,2839,2844,2845,2846,2858,2863,2867,2869,2871,2872,2874,2880,2882,2883,2893,2894,2895,2900,2909,2925,2929,2958,2960,2962,2965,2966,2973,2974,2979,2985,2987,3000,3001,3005,3008,3020,3028,3030,3031,3033,3036,3044,3046,3050,3061,3064,3066,3071,3076,3082,3088,3091,3106,3108,3117,3122,3123,3129,3130,3132,3135,3136,3144,3172,3174,3177,3178,3182,3190,3193,3200,3204,3210,3212,3214,3215,3216,3218,3219,3229,3230,3234,3241,3245,3248,3254,3263,3264,3268,3278,3280,3286,3289,3292,3295,3305,3306,3309,3317,3319,3320,3328,3333,3334,3336,3346,3356,3359,3360,3363,3364,3365,3368,3370,3373,3379,3384,3387,3389,3390,3395,3399,3409,3422,3425,3435,3438,3447,3450,3452,3461,3463,3467,3472,3477,3481,3485,3488,3491,3493,3495,3496,3498,3500,3521,3543,3560,3576,3603,3624,3641,3657,3676,3694,3716,3732,3759,3787,3807,3826,3845,3862,3883,3903,3924,3948,3966,3983,4003,4019,4046,4062,4082,4101,4118,4136,4157,4173,4192,4210,4226,4246,4262,4284] \ No newline at end of file diff --git a/cardano-chain-gen/test/testfiles/fingerprint/stakeDistGenesis b/cardano-chain-gen/test/testfiles/fingerprint/stakeDistGenesis new file mode 100644 index 000000000..42445c6bb --- /dev/null +++ b/cardano-chain-gen/test/testfiles/fingerprint/stakeDistGenesis @@ -0,0 +1 @@ +[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] \ No newline at end of file diff --git a/cardano-db-sync/src/Cardano/DbSync/Default.hs b/cardano-db-sync/src/Cardano/DbSync/Default.hs index 6405d8308..4416d908d 100644 --- a/cardano-db-sync/src/Cardano/DbSync/Default.hs +++ b/cardano-db-sync/src/Cardano/DbSync/Default.hs @@ -23,7 +23,7 @@ import Cardano.DbSync.Era.Shelley.Adjust (adjustEpochRewards) import qualified Cardano.DbSync.Era.Shelley.Generic as Generic import Cardano.DbSync.Era.Shelley.Insert (insertShelleyBlock) import Cardano.DbSync.Era.Shelley.Insert.Epoch (finalizeEpochBulkOps, forceInsertRewards, - insertPoolDepositRefunds, isEmptyEpochBulkOps, postEpochRewards, postEpochStake) + insertPoolDepositRefunds, isEmptyEpochBulkOps, postEpochRewards) import Cardano.DbSync.Era.Shelley.Validate (validateEpochRewards) import Cardano.DbSync.Error import Cardano.DbSync.LedgerState (LedgerEvent (..), LedgerStateSnapshot (..), applyBlock, @@ -153,12 +153,6 @@ handleLedgerEvents tracer lenv point = , show (unEpochNo $ Generic.rwdEpoch rwds), " ", renderPoint point ] postEpochRewards lenv rwds point - LedgerStakeDist sdist -> do - liftIO . logInfo tracer $ mconcat - [ "Handling ", show (Map.size (Generic.sdistStakeMap sdist)), " stakes for epoch " - , show (unEpochNo $ Generic.sdistEpochNo sdist), " ", renderPoint point - ] - postEpochStake lenv sdist point LedgerRewardDist rwd -> lift $ stashPoolRewards tracer lenv rwd LedgerMirDist md -> diff --git a/cardano-db-sync/src/Cardano/DbSync/Era/Byron/Insert.hs b/cardano-db-sync/src/Cardano/DbSync/Era/Byron/Insert.hs index 972d847ef..bd659a89c 100644 --- a/cardano-db-sync/src/Cardano/DbSync/Era/Byron/Insert.hs +++ b/cardano-db-sync/src/Cardano/DbSync/Era/Byron/Insert.hs @@ -78,10 +78,7 @@ insertABOBBoundary -> ExceptT SyncNodeError (ReaderT SqlBackend m) () insertABOBBoundary tracer blk details = do -- Will not get called in the OBFT part of the Byron era. - let prevHash = case Byron.boundaryPrevHash (Byron.boundaryHeader blk) of - Left gh -> Byron.genesisToHeaderHash gh - Right hh -> Byron.unHeaderHash hh - pbid <- liftLookupFail "insertABOBBoundary" $ DB.queryBlockId prevHash + pbid <- liftLookupFail "insertABOBBoundary" $ DB.queryBlockId (Byron.ebbPrevHash blk) slid <- lift . DB.insertSlotLeader $ DB.SlotLeader { DB.slotLeaderHash = BS.replicate 28 '\0' @@ -123,7 +120,7 @@ insertABlock => Trace IO Text -> Bool -> Byron.ABlock ByteString -> SlotDetails -> ExceptT SyncNodeError (ReaderT SqlBackend m) () insertABlock tracer firstBlockOfEpoch blk details = do - pbid <- liftLookupFail "insertABlock" $ DB.queryBlockId (Byron.unHeaderHash $ Byron.blockPreviousHash blk) + pbid <- liftLookupFail "insertABlock" $ DB.queryBlockId (Byron.blockPreviousHash blk) slid <- lift . DB.insertSlotLeader $ Byron.mkSlotLeader blk blkId <- lift . DB.insertBlock $ DB.Block diff --git a/cardano-db-sync/src/Cardano/DbSync/Era/Byron/Util.hs b/cardano-db-sync/src/Cardano/DbSync/Era/Byron/Util.hs index 40919702f..336609000 100644 --- a/cardano-db-sync/src/Cardano/DbSync/Era/Byron/Util.hs +++ b/cardano-db-sync/src/Cardano/DbSync/Era/Byron/Util.hs @@ -15,6 +15,8 @@ module Cardano.DbSync.Era.Byron.Util , blockNumber , blockPayload , blockPreviousHash + , ebbPrevHash + , prevHash , epochNumber , genesisToHeaderHash , protocolVersion @@ -40,6 +42,7 @@ import qualified Cardano.Chain.Slotting as Byron import qualified Cardano.Chain.UTxO as Byron import qualified Cardano.Chain.Update as Byron +import qualified Ouroboros.Consensus.Byron.Ledger.Block as Byron import qualified Cardano.Db as DB @@ -91,8 +94,19 @@ blockPayload :: Byron.ABlock a -> [Byron.TxAux] blockPayload = Byron.unTxPayload . Byron.bodyTxPayload . Byron.blockBody -blockPreviousHash :: Byron.ABlock a -> Byron.HeaderHash -blockPreviousHash = Byron.headerPrevHash . Byron.blockHeader +blockPreviousHash :: Byron.ABlock a -> ByteString +blockPreviousHash = unHeaderHash . Byron.headerPrevHash . Byron.blockHeader + +ebbPrevHash :: Byron.ABoundaryBlock a -> ByteString +ebbPrevHash bblock = + case Byron.boundaryPrevHash (Byron.boundaryHeader bblock) of + Left gh -> genesisToHeaderHash gh + Right hh -> unHeaderHash hh + +prevHash :: Byron.ByronBlock -> ByteString +prevHash blk = case Byron.byronBlockRaw blk of + Byron.ABOBBlock ablk -> blockPreviousHash ablk + Byron.ABOBBoundary abblk -> ebbPrevHash abblk epochNumber :: Byron.ABlock ByteString -> Word64 -> Word64 epochNumber blk slotsPerEpoch = diff --git a/cardano-db-sync/src/Cardano/DbSync/Era/Shelley/Generic/Block.hs b/cardano-db-sync/src/Cardano/DbSync/Era/Shelley/Generic/Block.hs index d1ecd7517..5dc31454a 100644 --- a/cardano-db-sync/src/Cardano/DbSync/Era/Shelley/Generic/Block.hs +++ b/cardano-db-sync/src/Cardano/DbSync/Era/Shelley/Generic/Block.hs @@ -14,6 +14,7 @@ module Cardano.DbSync.Era.Shelley.Generic.Block , blockHash , slotLeaderHash + , blockPrevHash ) where import qualified Cardano.Api.Shelley as Api diff --git a/cardano-db-sync/src/Cardano/DbSync/Era/Shelley/Generic/StakeDist.hs b/cardano-db-sync/src/Cardano/DbSync/Era/Shelley/Generic/StakeDist.hs index a2e30bff8..0b3f0ce0a 100644 --- a/cardano-db-sync/src/Cardano/DbSync/Era/Shelley/Generic/StakeDist.hs +++ b/cardano-db-sync/src/Cardano/DbSync/Era/Shelley/Generic/StakeDist.hs @@ -1,14 +1,21 @@ {-# LANGUAGE DataKinds #-} +{-# LANGUAGE FlexibleContexts #-} +{-# LANGUAGE GADTs #-} {-# LANGUAGE NoImplicitPrelude #-} {-# LANGUAGE ScopedTypeVariables #-} +{-# LANGUAGE TupleSections #-} + module Cardano.DbSync.Era.Shelley.Generic.StakeDist - ( StakeDist (..) - , epochStakeDist + ( StakeSliceRes (..) + , StakeSlice (..) , stakeDistPoolHashKeys , stakeDistStakeCreds + , getSecurityParameter + , getStakeSlice ) where import Cardano.Prelude +import Prelude (id) import Cardano.Crypto.Hash (hashToBytes) @@ -21,82 +28,135 @@ import Cardano.Ledger.Keys (KeyHash (..), KeyRole (..)) import qualified Cardano.Ledger.Shelley.EpochBoundary as Shelley import qualified Cardano.Ledger.Shelley.LedgerState as Shelley hiding (_delegations) -import Cardano.Slotting.Slot (EpochNo (..)) - import Cardano.DbSync.Era.Shelley.Generic.StakeCred import Cardano.DbSync.Era.Shelley.Generic.StakePoolKeyHash import Cardano.DbSync.Types +import Data.Compact.VMap (VB, VMap (..), VP) import qualified Data.Compact.VMap as VMap import qualified Data.Map.Strict as Map import qualified Data.Set as Set +import qualified Data.Vector.Generic as VG +import Ouroboros.Consensus.Block import Ouroboros.Consensus.Cardano.Block (LedgerState (..)) - +import Ouroboros.Consensus.Config +import Ouroboros.Consensus.HardFork.Combinator import Ouroboros.Consensus.Ledger.Extended (ExtLedgerState (..)) -import Ouroboros.Consensus.Shelley.Ledger.Block (ShelleyBlock) +import Ouroboros.Consensus.Node.ProtocolInfo +import Ouroboros.Consensus.Protocol.Abstract +import Ouroboros.Consensus.Shelley.Ledger import qualified Ouroboros.Consensus.Shelley.Ledger.Ledger as Consensus +data StakeSliceRes = + Slice StakeSlice Bool -- True if this is the final slice for this epoch. Can be used for logging. + | NoSlices -data StakeDist = StakeDist - { sdistEpochNo :: !EpochNo - , sdistStakeMap :: !(Map StakeCred (Coin, StakePoolKeyHash)) +data StakeSlice = StakeSlice + { sliceEpochNo :: !EpochNo + , sliceDistr :: !(Map StakeCred (Coin, StakePoolKeyHash)) } deriving Eq -epochStakeDist :: Ledger.Network -> EpochNo -> ExtLedgerState CardanoBlock -> Maybe StakeDist -epochStakeDist network epoch els = +emptySlice :: EpochNo -> StakeSlice +emptySlice epoch = StakeSlice epoch Map.empty + +getSecurityParameter :: ConsensusProtocol (BlockProtocol blk) + => ProtocolInfo IO blk -> Word64 +getSecurityParameter = maxRollbacks . configSecurityParam . pInfoConfig + +-- 'sliceIndex' can match the epochBlockNo for every block. +-- +-- 'minSliceSize' has to be constant or it could cause missing data. +-- If this value is too small it will be adjusted to a 'defaultEpochSliceSize' +-- which is big enough to cover all delegations. +-- On mainnet, for a value minSliceSize = 2000, it will be used as the actual size of slices +-- until the size of delegations grows up to 8.6M, in which case, the size of slices +-- will be adjusted. +getStakeSlice :: ConsensusProtocol (BlockProtocol blk) + => ProtocolInfo IO blk -> Ledger.Network + -> EpochNo -> Word64 -> Word64 -> ExtLedgerState CardanoBlock -> StakeSliceRes +getStakeSlice pInfo network epoch sliceIndex minSliceSize els = case ledgerState els of - LedgerStateByron _ -> Nothing - LedgerStateShelley sls -> Just $ genericStakeDist network epoch sls - LedgerStateAllegra als -> Just $ genericStakeDist network epoch als - LedgerStateMary mls -> Just $ genericStakeDist network epoch mls - LedgerStateAlonzo als -> Just $ genericStakeDist network epoch als - --- Use Set because they guarantee unique elements. -stakeDistPoolHashKeys :: StakeDist -> Set StakePoolKeyHash -stakeDistPoolHashKeys = Set.fromList . map snd . Map.elems . sdistStakeMap - -stakeDistStakeCreds :: StakeDist -> Set StakeCred -stakeDistStakeCreds = Map.keysSet . sdistStakeMap - --- ------------------------------------------------------------------------------------------------- - -genericStakeDist :: forall era. Ledger.Network -> EpochNo -> LedgerState (ShelleyBlock era) -> StakeDist -genericStakeDist network epoch lstate = - StakeDist - { sdistEpochNo = epoch - , sdistStakeMap = stakeMap - } + LedgerStateByron _ -> NoSlices + LedgerStateShelley sls -> genericStakeSlice pInfo network epoch sliceIndex minSliceSize sls + LedgerStateAllegra als -> genericStakeSlice pInfo network epoch sliceIndex minSliceSize als + LedgerStateMary mls -> genericStakeSlice pInfo network epoch sliceIndex minSliceSize mls + LedgerStateAlonzo als -> genericStakeSlice pInfo network epoch sliceIndex minSliceSize als + +genericStakeSlice :: forall era c blk. (c ~ Crypto era, ConsensusProtocol (BlockProtocol blk)) + => ProtocolInfo IO blk -> Ledger.Network -> EpochNo -> Word64 -> Word64 + -> LedgerState (ShelleyBlock era) -> StakeSliceRes +genericStakeSlice pInfo network epoch sliceIndex minSliceSize lstate + | index > delegationsLen = NoSlices + | index == delegationsLen = Slice (emptySlice epoch) True + | index + epochSliceSize > delegationsLen = Slice (mkSlice (delegationsLen - index)) True + | otherwise = Slice (mkSlice epochSliceSize) False where - stakeMap :: Map StakeCred (Coin, StakePoolKeyHash) - stakeMap = Map.intersectionWith (,) stakeCoinMap stakePoolMap - - stakeCoinMap :: Map StakeCred Coin - stakeCoinMap = mapBimap (toStakeCred network) Ledger.fromCompact stMap - - stMap :: Map (Credential 'Staking (Crypto era)) (Ledger.CompactForm Coin) - stMap = VMap.toMap . Shelley.unStake $ Shelley._stake stakeSet - - stakePoolMap :: Map StakeCred StakePoolKeyHash - stakePoolMap = mapBimap (toStakeCred network) convertStakePoolkeyHash delMap - - delMap :: Map (Credential 'Staking (Crypto era)) (KeyHash 'StakePool (Crypto era)) - delMap = VMap.toMap $ Shelley._delegations stakeSet - -- We use '_pstakeSet' here instead of '_pstateMark' because the stake addresses for the -- later may not have been added to the database yet. That means that when these values -- are added to the database, the epoch number where they become active is the current -- epoch plus one. - stakeSet :: Shelley.SnapShot (Crypto era) - stakeSet = Shelley._pstakeSet . Shelley.esSnapshots . Shelley.nesEs + stakeSnapshot :: Shelley.SnapShot c + stakeSnapshot = Shelley._pstakeSet . Shelley.esSnapshots . Shelley.nesEs $ Consensus.shelleyLedgerState lstate - convertStakePoolkeyHash :: KeyHash 'StakePool (Crypto era) -> StakePoolKeyHash + delegations :: VMap.KVVector VB VB (Credential 'Staking c, KeyHash 'StakePool c) + delegations = VMap.unVMap $ Shelley._delegations stakeSnapshot + + delegationsLen :: Word64 + delegationsLen = fromIntegral $ VG.length delegations + + stakes :: VMap VB VP (Credential 'Staking c) (Ledger.CompactForm Coin) + stakes = Shelley.unStake $ Shelley._stake stakeSnapshot + + lookupStake :: Credential 'Staking c -> Maybe Coin + lookupStake cred = Ledger.fromCompact <$> VMap.lookup cred stakes + + -- This is deterministic for the whole epoch and is the constant size of slices + -- until the data are over. This means the last slice could be of smaller size and slices + -- after that will be empty. + epochSliceSize :: Word64 + epochSliceSize = + max minSliceSize defaultEpochSliceSize + where + -- On mainnet this is 2160 + k :: Word64 + k = getSecurityParameter pInfo + + -- On mainnet this is 21600 + expectedBlocks :: Word64 + expectedBlocks = 10 * k + + -- This size of slices is enough to cover the whole list, even if only + -- the 20% of the expected blocks appear in an epoch. + defaultEpochSliceSize :: Word64 + defaultEpochSliceSize = 1 + div (delegationsLen * 5) expectedBlocks + + -- The starting index of the data in the delegation vector. + index :: Word64 + index = sliceIndex * epochSliceSize + + mkSlice :: Word64 -> StakeSlice + mkSlice size = + StakeSlice + { sliceEpochNo = epoch + , sliceDistr = distribution + } + where + delegationsSliced :: VMap VB VB (Credential 'Staking c) (KeyHash 'StakePool c) + delegationsSliced = VMap $ VG.slice (fromIntegral index) (fromIntegral size) delegations + + distribution :: Map StakeCred (Coin, StakePoolKeyHash) + distribution = Map.mapKeys (toStakeCred network) $ VMap.toMap $ + VMap.mapMaybe id $ VMap.mapWithKey (\k p -> (, convertStakePoolkeyHash p) <$> lookupStake k) delegationsSliced + + convertStakePoolkeyHash :: KeyHash 'StakePool c -> StakePoolKeyHash convertStakePoolkeyHash (KeyHash h) = StakePoolKeyHash $ hashToBytes h --- Is there a better way to do this? -mapBimap :: Ord k2 => (k1 -> k2) -> (a1 -> a2) -> Map k1 a1 -> Map k2 a2 -mapBimap fk fa = Map.fromAscList . map (bimap fk fa) . Map.toAscList - +-- Use Set because they guarantee unique elements. +stakeDistPoolHashKeys :: StakeSlice -> Set StakePoolKeyHash +stakeDistPoolHashKeys = Set.fromList . map snd . Map.elems . sliceDistr +stakeDistStakeCreds :: StakeSlice -> Set StakeCred +stakeDistStakeCreds = Map.keysSet . sliceDistr diff --git a/cardano-db-sync/src/Cardano/DbSync/Era/Shelley/Insert.hs b/cardano-db-sync/src/Cardano/DbSync/Era/Shelley/Insert.hs index 009d499be..8c143263d 100644 --- a/cardano-db-sync/src/Cardano/DbSync/Era/Shelley/Insert.hs +++ b/cardano-db-sync/src/Cardano/DbSync/Era/Shelley/Insert.hs @@ -10,7 +10,6 @@ module Cardano.DbSync.Era.Shelley.Insert ( insertShelleyBlock , postEpochRewards - , postEpochStake -- These are exported for data in Shelley Genesis , insertPoolRegister @@ -137,6 +136,8 @@ insertShelleyBlock tracer lenv firstBlockOfEpoch blk lStateSnap details = do whenJust (lssNewEpoch lStateSnap) $ \ newEpoch -> do insertOnNewEpoch tracer blkId (Generic.blkSlotNo blk) (sdEpochNo details) newEpoch + insertStakeSlice tracer (leIndexCache lenv) (lssStakeSlice lStateSnap) + mbop <- liftIO . atomically $ tryReadTBQueue (leBulkOpQueue lenv) whenJust (maybeToStrict mbop) $ \ bop -> insertEpochInterleaved tracer bop diff --git a/cardano-db-sync/src/Cardano/DbSync/Era/Shelley/Insert/Epoch.hs b/cardano-db-sync/src/Cardano/DbSync/Era/Shelley/Insert/Epoch.hs index 347e70ec5..dd76c0c8a 100644 --- a/cardano-db-sync/src/Cardano/DbSync/Era/Shelley/Insert/Epoch.hs +++ b/cardano-db-sync/src/Cardano/DbSync/Era/Shelley/Insert/Epoch.hs @@ -15,7 +15,7 @@ module Cardano.DbSync.Era.Shelley.Insert.Epoch , insertEpochInterleaved , insertPoolDepositRefunds , postEpochRewards - , postEpochStake + , insertStakeSlice ) where import Cardano.Prelude @@ -36,8 +36,8 @@ import Cardano.DbSync.Util import Cardano.Slotting.Slot (EpochNo (..)) -import Control.Monad.Class.MonadSTM.Strict (flushTBQueue, isEmptyTBQueue, readTVar, - writeTBQueue, writeTVar) +import Control.Monad.Class.MonadSTM.Strict (StrictTVar, flushTBQueue, isEmptyTBQueue, + readTVar, readTVarIO, writeTBQueue, writeTVar) import Control.Monad.Extra (mapMaybeM) import Control.Monad.Trans.Control (MonadBaseControl) import Control.Monad.Trans.Except.Extra (hoistEither) @@ -93,19 +93,7 @@ insertEpochInterleaved tracer bop = BulkRewardReport epochNo _ rewardCount total -> do liftIO $ reportRewards epochNo rewardCount lift $ insertEpochRewardTotalReceived epochNo total - BulkStakeDistChunk epochNo _ icache sDistChunk -> - insertEpochStake tracer icache epochNo sDistChunk - BulkStakeDistReport epochNo _ count -> - liftIO $ reportStakeDist epochNo count where - reportStakeDist :: EpochNo -> Int -> IO () - reportStakeDist epochNo count = - logInfo tracer $ - mconcat - [ "insertEpochInterleaved: Epoch ", textShow (unEpochNo epochNo) - , ", ", textShow count, " stake addresses" - ] - reportRewards :: EpochNo -> Int -> IO () reportRewards epochNo rewardCount = logInfo tracer $ @@ -127,18 +115,6 @@ postEpochRewards lenv rwds point = do writeTBQueue (leBulkOpQueue lenv) $ BulkRewardReport epochNo point (length $ Generic.rwdRewards rwds) (sumRewardTotal $ Generic.rwdRewards rwds) -postEpochStake - :: (MonadBaseControl IO m, MonadIO m) - => LedgerEnv -> Generic.StakeDist -> CardanoPoint - -> ExceptT SyncNodeError (ReaderT SqlBackend m) () -postEpochStake lenv smap point = do - icache <- lift $ updateIndexCache lenv (Generic.stakeDistStakeCreds smap) (Generic.stakeDistPoolHashKeys smap) - liftIO . atomically $ do - let epochNo = Generic.sdistEpochNo smap - forM_ (chunksOf 1000 $ Map.toList (Generic.sdistStakeMap smap)) $ \stakeChunk -> - writeTBQueue (leBulkOpQueue lenv) $ BulkStakeDistChunk epochNo point icache stakeChunk - writeTBQueue (leBulkOpQueue lenv) $ BulkStakeDistReport epochNo point (length $ Generic.sdistStakeMap smap) - isEmptyEpochBulkOps :: MonadIO m => LedgerEnv @@ -159,12 +135,26 @@ insertEpochRewardTotalReceived epochNo total = , DB.epochRewardTotalReceivedAmount = Generic.coinToDbLovelace total } +insertStakeSlice + :: (MonadBaseControl IO m, MonadIO m) + => Trace IO Text -> StrictTVar IO IndexCache -> Generic.StakeSliceRes + -> ExceptT SyncNodeError (ReaderT SqlBackend m) () +insertStakeSlice _ _ Generic.NoSlices = pure () +insertStakeSlice tracer cacheVar (Generic.Slice slice finalSlice) = do + cache <- liftIO $ readTVarIO cacheVar + -- cache TVar is not updated. We just use a slice here. + cacheSlice <- lift $ modifyCache (Generic.stakeDistStakeCreds slice) (Generic.stakeDistPoolHashKeys slice) cache + insertEpochStake cacheSlice (Generic.sliceEpochNo slice) (Map.toList $ Generic.sliceDistr slice) + when finalSlice $ do + size <- lift $ DB.queryEpochStakeCount (unEpochNo $ Generic.sliceEpochNo slice) + liftIO . logInfo tracer $ mconcat ["Inserted ", show size, " EpochStake for ", show (Generic.sliceEpochNo slice)] + insertEpochStake :: (MonadBaseControl IO m, MonadIO m) - => Trace IO Text -> IndexCache -> EpochNo + => IndexCache -> EpochNo -> [(Generic.StakeCred, (Shelley.Coin, Generic.StakePoolKeyHash))] -> ExceptT SyncNodeError (ReaderT SqlBackend m) () -insertEpochStake _tracer icache epochNo stakeChunk = do +insertEpochStake icache epochNo stakeChunk = do dbStakes <- mapM mkStake stakeChunk lift $ DB.insertManyEpochStakes dbStakes where @@ -292,21 +282,22 @@ updateIndexCache -> ReaderT SqlBackend m IndexCache updateIndexCache lenv screds pkhs = do oldCache <- liftIO . atomically $ readTVar (leIndexCache lenv) - newIndexCache <- createNewCache oldCache + newIndexCache <- modifyCache screds pkhs oldCache liftIO . atomically $ writeTVar (leIndexCache lenv) newIndexCache pure newIndexCache - where - createNewCache - :: (MonadBaseControl IO m, MonadIO m) - => IndexCache -> ReaderT SqlBackend m IndexCache - createNewCache oldCache = do - newAddresses <- newAddressCache (icAddressCache oldCache) - newPools <- newPoolCache (icPoolCache oldCache) - pure $ IndexCache - { icAddressCache = newAddresses - , icPoolCache = newPools - } +modifyCache + :: (MonadBaseControl IO m, MonadIO m) + => Set Generic.StakeCred -> Set Generic.StakePoolKeyHash + -> IndexCache -> ReaderT SqlBackend m IndexCache +modifyCache screds pkhs oldCache = do + newAddresses <- newAddressCache (icAddressCache oldCache) + newPools <- newPoolCache (icPoolCache oldCache) + pure $ IndexCache + { icAddressCache = newAddresses + , icPoolCache = newPools + } + where newAddressCache :: (MonadBaseControl IO m, MonadIO m) => Map Generic.StakeCred DB.StakeAddressId diff --git a/cardano-db-sync/src/Cardano/DbSync/LedgerEvent.hs b/cardano-db-sync/src/Cardano/DbSync/LedgerEvent.hs index 9a1ea817a..63597c3fd 100644 --- a/cardano-db-sync/src/Cardano/DbSync/LedgerEvent.hs +++ b/cardano-db-sync/src/Cardano/DbSync/LedgerEvent.hs @@ -54,7 +54,6 @@ data LedgerEvent = LedgerNewEpoch !EpochNo !SyncState | LedgerStartAtEpoch !EpochNo | LedgerRewards !SlotDetails !Generic.Rewards - | LedgerStakeDist !Generic.StakeDist | LedgerRewardDist !Generic.Rewards | LedgerMirDist !Generic.Rewards diff --git a/cardano-db-sync/src/Cardano/DbSync/LedgerState.hs b/cardano-db-sync/src/Cardano/DbSync/LedgerState.hs index ce6487589..ce81f64de 100644 --- a/cardano-db-sync/src/Cardano/DbSync/LedgerState.hs +++ b/cardano-db-sync/src/Cardano/DbSync/LedgerState.hs @@ -4,6 +4,7 @@ {-# LANGUAGE MultiParamTypeClasses #-} {-# LANGUAGE NoImplicitPrelude #-} {-# LANGUAGE OverloadedStrings #-} +{-# LANGUAGE RankNTypes #-} {-# LANGUAGE ScopedTypeVariables #-} {-# LANGUAGE TypeApplications #-} {-# LANGUAGE TypeFamilies #-} @@ -32,11 +33,11 @@ module Cardano.DbSync.LedgerState , getAlonzoPParams ) where -import Prelude (String, id) +import Prelude (String, fail, id) import Cardano.BM.Trace (Trace, logInfo, logWarning) -import Cardano.Binary (DecoderError) +import Cardano.Binary (Decoder, DecoderError, Encoding, FromCBOR (..), ToCBOR (..)) import qualified Cardano.Binary as Serialize import qualified Cardano.Db as DB @@ -130,8 +131,6 @@ import System.Mem (performMajorGC) data BulkOperation = BulkRewardChunk !EpochNo !CardanoPoint !IndexCache ![(StakeCred, Set Generic.Reward)] | BulkRewardReport !EpochNo !CardanoPoint !Int !Coin - | BulkStakeDistChunk !EpochNo !CardanoPoint !IndexCache ![(StakeCred, (Coin, StakePoolKeyHash))] - | BulkStakeDistReport !EpochNo !CardanoPoint !Int data IndexCache = IndexCache { icAddressCache :: !(Map StakeCred DB.StakeAddressId) @@ -161,21 +160,54 @@ data LedgerEnv = LedgerEnv , leStableEpochSlot :: !EpochSlot } +-- TODO this is unstable in terms of restarts and we should try to remove it. data LedgerEventState = LedgerEventState { lesInitialized :: !Bool , lesEpochNo :: !(Maybe EpochNo) , lesLastRewardsEpoch :: !(Maybe EpochNo) - , lesLastStateDistEpoch :: !(Maybe EpochNo) , lesLastAdded :: !CardanoPoint } topLevelConfig :: LedgerEnv -> TopLevelConfig CardanoBlock topLevelConfig = Consensus.pInfoConfig . leProtocolInfo -newtype CardanoLedgerState = CardanoLedgerState +data CardanoLedgerState = CardanoLedgerState { clsState :: ExtLedgerState CardanoBlock + , clsEpochBlockNo :: EpochBlockNo } +-- The height of the block in the current Epoch. We maintain this +-- data next to the ledger state and store it in the same blob file. +data EpochBlockNo = GenesisEpochBlockNo | EBBEpochBlockNo | EpochBlockNo Word64 + +instance ToCBOR EpochBlockNo where + toCBOR GenesisEpochBlockNo = toCBOR (0 :: Word8) + toCBOR EBBEpochBlockNo = toCBOR (1 :: Word8) + toCBOR (EpochBlockNo n) = + toCBOR (2 :: Word8) <> toCBOR n + +instance FromCBOR EpochBlockNo where + fromCBOR = do + tag :: Word8 <- fromCBOR + case tag of + 0 -> pure GenesisEpochBlockNo + 1 -> pure EBBEpochBlockNo + 2 -> EpochBlockNo <$> fromCBOR + n -> fail $ "unexpected EpochBlockNo value " <> show n + +encodeCardanoLedgerState :: (ExtLedgerState CardanoBlock -> Encoding) + -> CardanoLedgerState -> Encoding +encodeCardanoLedgerState encodeExt cls = mconcat + [ encodeExt (clsState cls) + , toCBOR (clsEpochBlockNo cls) + ] + +decodeCardanoLedgerState :: (forall s. Decoder s (ExtLedgerState CardanoBlock)) + -> (forall s. Decoder s CardanoLedgerState) +decodeCardanoLedgerState decodeExt = do + ldgrState <- decodeExt + CardanoLedgerState ldgrState <$> fromCBOR + data LedgerStateFile = LedgerStateFile { lsfSlotNo :: !SlotNo , lsfHash :: !ByteString @@ -189,6 +221,7 @@ data LedgerStateSnapshot = LedgerStateSnapshot , lssNewEpoch :: !(Strict.Maybe Generic.NewEpoch) -- Only Just for a single block at the epoch boundary , lssSlotDetails :: !SlotDetails , lssPoint :: !CardanoPoint + , lssStakeSlice :: !Generic.StakeSliceRes , lssEvents :: ![LedgerEvent] } @@ -259,7 +292,6 @@ mkLedgerEnv trce protocolInfo dir nw stableEpochSlot systemStart aop = do { lesInitialized = False , lesEpochNo = Nothing , lesLastRewardsEpoch = Nothing - , lesLastStateDistEpoch = Nothing , lesLastAdded = GenesisPoint } @@ -267,6 +299,7 @@ mkLedgerEnv trce protocolInfo dir nw stableEpochSlot systemStart aop = do initCardanoLedgerState :: Consensus.ProtocolInfo IO CardanoBlock -> CardanoLedgerState initCardanoLedgerState pInfo = CardanoLedgerState { clsState = Consensus.pInfoInitLedger pInfo + , clsEpochBlockNo = GenesisEpochBlockNo } -- TODO make this type safe. We make the assumption here that the first message of @@ -291,18 +324,22 @@ applyBlock env blk = do ledgerDB <- readStateUnsafe env let oldState = ledgerDbCurrent ledgerDB let !result = applyBlk (ExtLedgerCfg (topLevelConfig env)) blk (clsState oldState) - let !newState = oldState { clsState = lrResult result } - details <- getSlotDetails env (ledgerState $ clsState newState) time (cardanoBlockSlotNo blk) + let !newLedgerState = lrResult result + details <- getSlotDetails env (ledgerState newLedgerState) time (cardanoBlockSlotNo blk) + let !newEpoch = mkNewEpoch (clsState oldState) newLedgerState + let !newEpochBlockNo = applyToEpochBlockNo (isJust $ blockIsEBB blk) (isJust newEpoch) (clsEpochBlockNo oldState) + let !newState = CardanoLedgerState newLedgerState newEpochBlockNo let !ledgerDB' = pushLedgerDB ledgerDB newState writeTVar (leStateVar env) (Just ledgerDB') oldEventState <- readTVar (leEventState env) - events <- generateEvents env oldEventState details newState (blockPoint blk) + events <- generateEvents env oldEventState details newState (blockPoint blk) pure $ LedgerStateSnapshot { lssState = newState , lssOldState = oldState - , lssNewEpoch = maybeToStrict $ mkNewEpoch oldState newState + , lssNewEpoch = maybeToStrict newEpoch , lssSlotDetails = details , lssPoint = blockPoint blk + , lssStakeSlice = stakeSlice newState details , lssEvents = events ++ mapMaybe (convertAuxLedgerEvent (leNetwork env)) (lrEvents result) } where @@ -315,7 +352,7 @@ applyBlock env blk = do Left err -> panic err Right result -> result - mkNewEpoch :: CardanoLedgerState -> CardanoLedgerState -> Maybe Generic.NewEpoch + mkNewEpoch :: ExtLedgerState CardanoBlock -> ExtLedgerState CardanoBlock -> Maybe Generic.NewEpoch mkNewEpoch oldState newState = if ledgerEpochNo env newState /= ledgerEpochNo env oldState + 1 then Nothing @@ -325,16 +362,36 @@ applyBlock env blk = do { Generic.neEpoch = ledgerEpochNo env newState , Generic.neIsEBB = isJust $ blockIsEBB blk , Generic.neAdaPots = maybeToStrict $ getAdaPots newState - , Generic.neEpochUpdate = Generic.epochUpdate (clsState newState) + , Generic.neEpochUpdate = Generic.epochUpdate newState } + applyToEpochBlockNo :: Bool -> Bool -> EpochBlockNo -> EpochBlockNo + applyToEpochBlockNo True _ _ = EBBEpochBlockNo + applyToEpochBlockNo _ True _ = EpochBlockNo 0 + applyToEpochBlockNo _ _ (EpochBlockNo n) = EpochBlockNo (n + 1) + applyToEpochBlockNo _ _ GenesisEpochBlockNo = EpochBlockNo 0 + applyToEpochBlockNo _ _ EBBEpochBlockNo = EpochBlockNo 0 + + stakeSliceMinSize :: Word64 + stakeSliceMinSize = 2000 + + stakeSlice :: CardanoLedgerState -> SlotDetails -> Generic.StakeSliceRes + stakeSlice cls details = case clsEpochBlockNo cls of + EpochBlockNo n -> Generic.getStakeSlice + (leProtocolInfo env) + (leNetwork env) + (sdEpochNo details) + n + stakeSliceMinSize + (clsState cls) + _ -> Generic.NoSlices + generateEvents :: LedgerEnv -> LedgerEventState -> SlotDetails -> CardanoLedgerState -> CardanoPoint -> STM [LedgerEvent] generateEvents env oldEventState details cls pnt = do writeTVar (leEventState env) newEventState pure $ catMaybes [ newEpochEvent , LedgerRewards details <$> rewards - , LedgerStakeDist <$> stakeDist ] where currentEpochNo :: EpochNo @@ -359,22 +416,9 @@ generateEvents env oldEventState details cls pnt = do then mkRewards else Nothing - mkRewards :: Maybe Generic.Rewards mkRewards = Generic.epochRewards (leNetwork env) (sdEpochNo details) (clsState cls) - stakeDist :: Maybe Generic.StakeDist - stakeDist = - case lesLastStateDistEpoch oldEventState of - Nothing -> mkStakeDist - Just oldStakeEpoch -> - if oldStakeEpoch < currentEpochNo - then mkStakeDist - else Nothing - - mkStakeDist :: Maybe Generic.StakeDist - mkStakeDist = Generic.epochStakeDist (leNetwork env) (sdEpochNo details) (clsState cls) - newEventState :: LedgerEventState newEventState = LedgerEventState @@ -384,19 +428,15 @@ generateEvents env oldEventState details cls pnt = do if isJust rewards then Just currentEpochNo else lesLastRewardsEpoch oldEventState - , lesLastStateDistEpoch = - if isJust stakeDist - then Just currentEpochNo - else lesLastStateDistEpoch oldEventState , lesLastAdded = - if isNothing rewards && isNothing stakeDist + if isNothing rewards then lesLastAdded oldEventState else pnt } -saveCurrentLedgerState :: LedgerEnv -> ExtLedgerState CardanoBlock -> Maybe EpochNo -> IO () +saveCurrentLedgerState :: LedgerEnv -> CardanoLedgerState -> Maybe EpochNo -> IO () saveCurrentLedgerState env ledger mEpochNo = do - case mkLedgerStateFilename (leDir env) ledger mEpochNo of + case mkLedgerStateFilename (leDir env) (clsState ledger) mEpochNo of Origin -> pure () -- we don't store genesis At file -> do exists <- doesFileExist file @@ -406,11 +446,12 @@ saveCurrentLedgerState env ledger mEpochNo = do else do LBS.writeFile file $ Serialize.serializeEncoding $ - Consensus.encodeExtLedgerState - (encodeDisk codecConfig) - (encodeDisk codecConfig) - (encodeDisk codecConfig) - ledger + encodeCardanoLedgerState + (Consensus.encodeExtLedgerState + (encodeDisk codecConfig) + (encodeDisk codecConfig) + (encodeDisk codecConfig)) + ledger logInfo (leTrace env) $ mconcat ["Took a ledger snapshot at ", Text.pack file] where codecConfig :: CodecConfig CardanoBlock @@ -423,7 +464,7 @@ mkLedgerStateFilename dir ledger mEpochNo = lsfFilePath . dbPointToFileName dir saveCleanupState :: LedgerEnv -> CardanoLedgerState -> Maybe EpochNo -> IO () saveCleanupState env ledger mEpochNo = do let st = clsState ledger - saveCurrentLedgerState env st mEpochNo + saveCurrentLedgerState env ledger mEpochNo cleanupLedgerStateFiles env $ fromWithOrigin (SlotNo 0) (ledgerTipSlot $ ledgerState st) @@ -639,9 +680,9 @@ loadLedgerStateFromFile config delete lsf = do mst <- safeReadFile (lsfFilePath lsf) case mst of Left err -> when delete (safeRemoveFile $ lsfFilePath lsf) >> pure (Left err) - Right st -> pure . Right $ CardanoLedgerState { clsState = st } + Right st -> pure $ Right st where - safeReadFile :: FilePath -> IO (Either Text (ExtLedgerState CardanoBlock)) + safeReadFile :: FilePath -> IO (Either Text CardanoLedgerState) safeReadFile fp = do mbs <- Exception.try $ BS.readFile fp case mbs of @@ -654,16 +695,21 @@ loadLedgerStateFromFile config delete lsf = do codecConfig :: CodecConfig CardanoBlock codecConfig = configCodec config - decode :: ByteString -> Either DecoderError (ExtLedgerState CardanoBlock) - decode = + decode :: ByteString -> Either DecoderError CardanoLedgerState + decode = do Serialize.decodeFullDecoder "Ledger state file" - (Consensus.decodeExtLedgerState - (decodeDisk codecConfig) - (decodeDisk codecConfig) - (decodeDisk codecConfig)) + decodeState . LBS.fromStrict + decodeState :: (forall s. Decoder s CardanoLedgerState) + decodeState = + decodeCardanoLedgerState $ + Consensus.decodeExtLedgerState + (decodeDisk codecConfig) + (decodeDisk codecConfig) + (decodeDisk codecConfig) + -- Get a list of the ledger state files order most recent listLedgerStateFilesOrdered :: LedgerStateDir -> IO [LedgerStateFile] listLedgerStateFilesOrdered dir = do @@ -702,18 +748,18 @@ getPoolParamsShelley lState = -- We only compute 'AdaPots' for later eras. This is a time consuming -- function and we only want to run it on epoch boundaries. -getAdaPots :: CardanoLedgerState -> Maybe Shelley.AdaPots +getAdaPots :: ExtLedgerState CardanoBlock -> Maybe Shelley.AdaPots getAdaPots st = - case ledgerState $ clsState st of + case ledgerState st of LedgerStateByron _ -> Nothing LedgerStateShelley sts -> Just $ totalAdaPots sts LedgerStateAllegra sta -> Just $ totalAdaPots sta LedgerStateMary stm -> Just $ totalAdaPots stm LedgerStateAlonzo sta -> Just $ totalAdaPots sta -ledgerEpochNo :: LedgerEnv -> CardanoLedgerState -> EpochNo +ledgerEpochNo :: LedgerEnv -> ExtLedgerState CardanoBlock -> EpochNo ledgerEpochNo env cls = - case ledgerTipSlot (ledgerState (clsState cls)) of + case ledgerTipSlot (ledgerState cls) of Origin -> 0 -- An empty chain is in epoch 0 NotOrigin slot -> case runExcept $ epochInfoEpoch epochInfo slot of @@ -721,7 +767,7 @@ ledgerEpochNo env cls = Right en -> en where epochInfo :: EpochInfo (Except Consensus.PastHorizonException) - epochInfo = epochInfoLedger (configLedger $ topLevelConfig env) (hardForkLedgerStatePerEra . ledgerState $ clsState cls) + epochInfo = epochInfoLedger (configLedger $ topLevelConfig env) (hardForkLedgerStatePerEra $ ledgerState cls) -- Like 'Consensus.tickThenReapply' but also checks that the previous hash from the block matches -- the head hash of the ledger state. diff --git a/cardano-db/src/Cardano/Db/Insert.hs b/cardano-db/src/Cardano/Db/Insert.hs index c68e55a6e..4cf89e223 100644 --- a/cardano-db/src/Cardano/Db/Insert.hs +++ b/cardano-db/src/Cardano/Db/Insert.hs @@ -19,7 +19,6 @@ module Cardano.Db.Insert , insertManyRewards , insertManyTxIn , insertMaTxMint - , insertMaTxOut , insertManyMaTxOut , insertMeta , insertMultiAsset @@ -73,7 +72,7 @@ import Data.Proxy (Proxy (..)) import Data.Text (Text) import qualified Data.Text as Text -import Database.Persist.Class (AtLeastOneUniqueKey, PersistEntityBackend, checkUnique, +import Database.Persist.Class (AtLeastOneUniqueKey, PersistEntityBackend, PersistEntity, checkUnique, insert, insertBy, replaceUnique) import Database.Persist.EntityDef.Internal (entityDB, entityUniques) import Database.Persist.Sql (OnlyOneUniqueKey, PersistRecordBackend, SqlBackend, @@ -146,9 +145,6 @@ insertManyTxIn = insertManyUncheckedUnique "Many TxIn" insertMaTxMint :: (MonadBaseControl IO m, MonadIO m) => MaTxMint -> ReaderT SqlBackend m MaTxMintId insertMaTxMint = insertCheckUnique "insertMaTxMint" -insertMaTxOut :: (MonadBaseControl IO m, MonadIO m) => MaTxOut -> ReaderT SqlBackend m MaTxOutId -insertMaTxOut = insertCheckUnique "insertMaTxOut" - insertManyMaTxOut :: (MonadBaseControl IO m, MonadIO m) => [MaTxOut] -> ReaderT SqlBackend m () insertManyMaTxOut = insertManyUncheckedUnique "Many MaTxOut" @@ -276,6 +272,40 @@ insertMany' vtype records = handle exceptHandler (insertMany records) exceptHandler e = liftIO $ throwIO (DbInsertException vtype e) +-- Used to benchmark tables without unique keys. +_insertManyNoUnique + :: forall m record. + ( MonadBaseControl IO m + , MonadIO m + , PersistEntity record + ) + => String -> [record] -> ReaderT SqlBackend m () +_insertManyNoUnique vtype records = + unless (null records) $ + handle exceptHandler (rawExecute query values) + where + query :: Text + query = + Text.concat + [ "INSERT INTO " + , unEntityNameDB (entityDB . entityDef $ records) + , " (", Util.commaSeparated fieldNames + , ") VALUES " + , Util.commaSeparated . replicate (length records) + . Util.parenWrapped . Util.commaSeparated $ placeholders + ] + + values :: [PersistValue] + values = concatMap (map toPersistValue . toPersistFields) records + + fieldNames, placeholders :: [Text] + (fieldNames, placeholders) = + unzip (Util.mkInsertPlaceholders (entityDef (Proxy @record)) escapeFieldName) + + exceptHandler :: SqlError -> ReaderT SqlBackend m a + exceptHandler e = + liftIO $ throwIO (DbInsertException vtype e) + insertManyUncheckedUnique :: forall m record. ( MonadBaseControl IO m diff --git a/cardano-db/src/Cardano/Db/Query.hs b/cardano-db/src/Cardano/Db/Query.hs index 32044ae25..146f84424 100644 --- a/cardano-db/src/Cardano/Db/Query.hs +++ b/cardano-db/src/Cardano/Db/Query.hs @@ -57,6 +57,7 @@ module Cardano.Db.Query , queryTxOutCount , queryTxOutValue , queryTxOutCredentials + , queryEpochStakeCount , queryUtxoAtBlockNo , queryUtxoAtSlotNo , queryWithdrawalsUpToBlockNo @@ -742,6 +743,13 @@ queryUtxoAtBlockId blkid = do (out, Value (Just hash')) -> Just (entityVal out, hash') (_, Value Nothing) -> Nothing +queryEpochStakeCount :: MonadIO m => Word64 -> ReaderT SqlBackend m Word64 +queryEpochStakeCount epoch = do + res <- select $ do + epochStake <- from $ table @ EpochStake + where_ (epochStake ^. EpochStakeEpochNo ==. val epoch) + pure countRows + pure $ maybe 0 unValue (listToMaybe res) queryUtxoAtBlockNo :: MonadIO m => Word64 -> ReaderT SqlBackend m [(TxOut, ByteString)] queryUtxoAtBlockNo blkNo = do diff --git a/schema/migration-2-0011-20220318.sql b/schema/migration-2-0011-20220318.sql new file mode 100644 index 000000000..fd5791fab --- /dev/null +++ b/schema/migration-2-0011-20220318.sql @@ -0,0 +1,21 @@ +-- Persistent generated migration. + +CREATE FUNCTION migrate() RETURNS void AS $$ +DECLARE + next_version int ; +BEGIN + SELECT stage_two + 1 INTO next_version FROM schema_version ; + IF next_version = 11 THEN + EXECUTE 'ALTER TABLE "block" ALTER COLUMN "slot_no" TYPE word63type' ; + EXECUTE 'ALTER TABLE "ada_pots" ALTER COLUMN "slot_no" TYPE word63type' ; + EXECUTE 'ALTER TABLE "delegation" ALTER COLUMN "slot_no" TYPE word63type' ; + -- Hand written SQL statements can be added here. + UPDATE schema_version SET stage_two = next_version ; + RAISE NOTICE 'DB has been migrated to stage_two version %', next_version ; + END IF ; +END ; +$$ LANGUAGE plpgsql ; + +SELECT migrate() ; + +DROP FUNCTION migrate() ;