Skip to content

Commit e277843

Browse files
committed
Test for command line arguments
1 parent 542198e commit e277843

File tree

14 files changed

+188
-70
lines changed

14 files changed

+188
-70
lines changed

cardano-chain-gen/cardano-chain-gen.cabal

Lines changed: 3 additions & 1 deletion
Original file line numberDiff line numberDiff line change
@@ -165,7 +165,8 @@ test-suite cardano-chain-gen
165165
Test.Cardano.Db.Mock.Unit.Alonzo.Stake
166166
Test.Cardano.Db.Mock.Unit.Alonzo.Tx
167167
Test.Cardano.Db.Mock.Unit.Babbage
168-
Test.Cardano.Db.Mock.Unit.Babbage.Flag.ConsumedTxOut
168+
Test.Cardano.Db.Mock.Unit.Babbage.CommandLineArg.MigrateConsumedPruneTxOut
169+
Test.Cardano.Db.Mock.Unit.Babbage.CommandLineArg.ConfigFile
169170
Test.Cardano.Db.Mock.Unit.Babbage.InlineAndReference
170171
Test.Cardano.Db.Mock.Unit.Babbage.Other
171172
Test.Cardano.Db.Mock.Unit.Babbage.Plutus
@@ -209,6 +210,7 @@ test-suite cardano-chain-gen
209210
, stm
210211
, strict-stm
211212
, tasty
213+
, tasty-expected-failure
212214
, tasty-quickcheck
213215
, text
214216
, transformers

cardano-chain-gen/test/Test/Cardano/Db/Mock/Config.hs

Lines changed: 84 additions & 31 deletions
Original file line numberDiff line numberDiff line change
@@ -1,11 +1,14 @@
11
{-# LANGUAGE OverloadedStrings #-}
22
{-# LANGUAGE ScopedTypeVariables #-}
33
{-# LANGUAGE TypeApplications #-}
4+
{-# LANGUAGE RecordWildCards #-}
45

56
module Test.Cardano.Db.Mock.Config (
67
Config (..),
78
DBSyncEnv (..),
8-
TxOutParam(..),
9+
CommandLineArgs(..),
10+
TxOutParam (..),
11+
initCommandLineArgs,
912
babbageConfigDir,
1013
alonzoConfigDir,
1114
emptyMetricsSetters,
@@ -30,7 +33,8 @@ module Test.Cardano.Db.Mock.Config (
3033
startDBSync,
3134
withDBSyncEnv,
3235
withFullConfig,
33-
withTxOutParamConfig,
36+
withCustomConfig,
37+
withCustomConfigAndLogs,
3438
withFullConfig',
3539
) where
3640

@@ -48,7 +52,7 @@ import Cardano.Mock.ChainSync.Server
4852
import Cardano.Mock.Forging.Interpreter
4953
import Cardano.Node.Protocol.Shelley (readLeaderCredentials)
5054
import Cardano.Node.Types (ProtocolFilepaths (..))
51-
import Cardano.Prelude (ReaderT, panic, stderr)
55+
import Cardano.Prelude (ReaderT, panic, stderr, fromMaybe)
5256
import Cardano.SMASH.Server.PoolDataLayer
5357
import Control.Concurrent.Async (Async, async, cancel, poll)
5458
import Control.Concurrent.STM (atomically)
@@ -93,8 +97,26 @@ data DBSyncEnv = DBSyncEnv
9397

9498
-- used for testing of tx out pruning feature
9599
data TxOutParam = TxOutParam
96-
{ paramMigrateConsumed :: Bool,
97-
paramPruneTxOut :: Bool
100+
{ paramMigrateConsumed :: Bool
101+
, paramPruneTxOut :: Bool
102+
}
103+
104+
data CommandLineArgs = CommandLineArgs
105+
{ claHasConfigFile :: Bool
106+
, claExtended :: Bool
107+
, claHasCache :: Bool
108+
, claShouldUseLedger :: Bool
109+
, claSkipFix :: Bool
110+
, claOnlyFix :: Bool
111+
, claForceIndexes :: Bool
112+
, claHasMultiAssets :: Bool
113+
, claHasMetadata :: Bool
114+
, claHasPlutusExtra :: Bool
115+
, claHasOfflineData :: Bool
116+
, claTurboMode :: Bool
117+
, claFullMode :: Bool
118+
, claMigrateConsumed :: Bool
119+
, claPruneTxOut :: Bool
98120
}
99121

100122
babbageConfigDir :: FilePath
@@ -203,14 +225,14 @@ setupTestsDir dir = do
203225
0
204226
Nothing
205227

206-
mkConfig :: FilePath -> FilePath -> Maybe TxOutParam -> IO Config
207-
mkConfig staticDir mutableDir mTxOutParam = do
228+
mkConfig :: FilePath -> FilePath -> CommandLineArgs -> IO Config
229+
mkConfig staticDir mutableDir cmdLineArgs = do
208230
config <- readSyncNodeConfig $ ConfigFile (staticDir </> "test-db-sync-config.json")
209231
genCfg <- either (error . Text.unpack . renderSyncNodeError) id <$> runExceptT (readCardanoGenesisConfig config)
210232
let pInfoDbSync = mkProtocolInfoCardano genCfg []
211233
creds <- mkShelleyCredentials $ staticDir </> "pools" </> "bulk1.creds"
212234
let pInfoForger = mkProtocolInfoCardano genCfg creds
213-
syncPars <- mkSyncNodeParams staticDir mutableDir mTxOutParam
235+
syncPars <- mkSyncNodeParams staticDir mutableDir cmdLineArgs
214236
pure $ Config (Consensus.pInfoConfig pInfoDbSync) pInfoDbSync pInfoForger syncPars
215237

216238
mkShelleyCredentials :: FilePath -> IO [ShelleyLeaderCredentials StandardCrypto]
@@ -228,35 +250,55 @@ mkShelleyCredentials bulkFile = do
228250
}
229251

230252
-- | staticDir can be shared by tests running in parallel. mutableDir not.
231-
mkSyncNodeParams :: FilePath -> FilePath -> Maybe TxOutParam -> IO SyncNodeParams
232-
mkSyncNodeParams staticDir mutableDir mTxOutParam = do
253+
mkSyncNodeParams :: FilePath -> FilePath -> CommandLineArgs -> IO SyncNodeParams
254+
mkSyncNodeParams staticDir mutableDir CommandLineArgs{..} = do
233255
pgconfig <- orDie Db.renderPGPassError $ newExceptT Db.readPGPassDefault
234256
pure $
235257
SyncNodeParams
236-
{ enpConfigFile = ConfigFile $ staticDir </> "test-db-sync-config.json"
258+
{ enpConfigFile = ConfigFile $ staticDir </> (if claHasConfigFile then "test-db-sync-config.json" else "")
237259
, enpSocketPath = SocketPath $ mutableDir </> ".socket"
238260
, enpMaybeLedgerStateDir = Just $ LedgerStateDir $ mutableDir </> "ledger-states"
239261
, enpMigrationDir = MigrationDir "../schema"
240262
, enpPGPassSource = Db.PGPassCached pgconfig
241-
, enpExtended = True
242-
, enpHasCache = True
243-
, enpShouldUseLedger = True
244-
, enpSkipFix = True
245-
, enpOnlyFix = False
246-
, enpForceIndexes = False
247-
, enpHasMultiAssets = True
248-
, enpHasMetadata = True
263+
, enpExtended = claExtended
264+
, enpHasCache = claHasCache
265+
, enpShouldUseLedger = claShouldUseLedger
266+
, enpSkipFix = claSkipFix
267+
, enpOnlyFix = claOnlyFix
268+
, enpForceIndexes = claForceIndexes
269+
, enpHasMultiAssets = claHasMultiAssets
270+
, enpHasMetadata = claHasMetadata
249271
, enpHasPlutusExtra = True
250272
, enpHasOfflineData = True
251273
, enpTurboMode = False
252274
, enpFullMode = True
253-
, enpMigrateConsumed = maybe False paramMigrateConsumed mTxOutParam
254-
, enpPruneTxOut = maybe False paramPruneTxOut mTxOutParam
275+
, enpMigrateConsumed = claMigrateConsumed
276+
, enpPruneTxOut = claPruneTxOut
255277
, enpSnEveryFollowing = 35
256278
, enpSnEveryLagging = 35
257279
, enpMaybeRollback = Nothing
258280
}
259281

282+
initCommandLineArgs :: CommandLineArgs
283+
initCommandLineArgs =
284+
CommandLineArgs
285+
{ claHasConfigFile = True
286+
, claExtended = True
287+
, claHasCache = True
288+
, claShouldUseLedger = True
289+
, claSkipFix = True
290+
, claOnlyFix = False
291+
, claForceIndexes = False
292+
, claHasMultiAssets = True
293+
, claHasMetadata = True
294+
, claHasPlutusExtra = True
295+
, claHasOfflineData = True
296+
, claTurboMode = False
297+
, claFullMode = True
298+
, claMigrateConsumed = True
299+
, claPruneTxOut = True
300+
}
301+
260302
emptyMetricsSetters :: MetricSetters
261303
emptyMetricsSetters =
262304
MetricSetters
@@ -273,37 +315,48 @@ withFullConfig ::
273315
IOManager ->
274316
[(Text, Text)] ->
275317
IO a
276-
withFullConfig = withFullConfig' True Nothing
318+
withFullConfig = withFullConfig' True False initCommandLineArgs
319+
320+
withCustomConfig ::
321+
CommandLineArgs ->
322+
FilePath ->
323+
FilePath ->
324+
(Interpreter -> ServerHandle IO CardanoBlock -> DBSyncEnv -> IO a) ->
325+
IOManager ->
326+
[(Text, Text)] ->
327+
IO a
328+
withCustomConfig = withFullConfig' True False
277329

278-
withTxOutParamConfig ::
279-
TxOutParam ->
330+
withCustomConfigAndLogs ::
331+
CommandLineArgs ->
280332
FilePath ->
281333
FilePath ->
282334
(Interpreter -> ServerHandle IO CardanoBlock -> DBSyncEnv -> IO a) ->
283335
IOManager ->
284336
[(Text, Text)] ->
285337
IO a
286-
withTxOutParamConfig txOutParam = withFullConfig' True (Just txOutParam)
338+
withCustomConfigAndLogs = withFullConfig' True True
287339

288340
withFullConfig' ::
289341
Bool ->
290-
Maybe TxOutParam ->
342+
Bool ->
343+
CommandLineArgs ->
291344
FilePath ->
292345
FilePath ->
293346
(Interpreter -> ServerHandle IO CardanoBlock -> DBSyncEnv -> IO a) ->
294347
IOManager ->
295348
[(Text, Text)] ->
296349
IO a
297-
withFullConfig' hasFingerprint mTxOutParam config testLabel action iom migr = do
350+
withFullConfig' hasFingerprint shouldLog cmdLineArgs config testLabel action iom migr = do
298351
recreateDir mutableDir
299-
cfg <- mkConfig configDir mutableDir mTxOutParam
352+
cfg <- mkConfig configDir mutableDir cmdLineArgs
300353
fingerFile <- if hasFingerprint then Just <$> prepareFingerprintFile testLabel else pure Nothing
301354
let dbsyncParams = syncNodeParams cfg
302355
-- Set to True to disable logging, False to enable it.
303356
trce <-
304-
if True
305-
then pure nullTracer
306-
else configureLogging dbsyncParams "db-sync-node"
357+
if shouldLog
358+
then configureLogging dbsyncParams "db-sync-node"
359+
else pure nullTracer
307360
let dbsyncRun = runDbSync emptyMetricsSetters migr iom trce dbsyncParams True
308361
let initSt = Consensus.pInfoInitLedger $ protocolInfo cfg
309362
withInterpreter (protocolInfoForging cfg) nullTracer fingerFile $ \interpreter -> do

cardano-chain-gen/test/Test/Cardano/Db/Mock/Property/Property.hs

Lines changed: 1 addition & 1 deletion
Original file line numberDiff line numberDiff line change
@@ -273,4 +273,4 @@ prop_empty_blocks iom knownMigrations = withMaxSuccess 20 $ noShrinking $ forAll
273273
prettyCommands smSymbolic hist (checkCommandNames cmds (res === Ok))
274274
where
275275
smSymbolic = sm (error "inter") (error "mockServer") (error "dbSync")
276-
runAction action = withFullConfig' False Nothing "config" "qsm" action iom knownMigrations
276+
runAction action = withFullConfig' False False initCommandLineArgs "config" "qsm" action iom knownMigrations

cardano-chain-gen/test/Test/Cardano/Db/Mock/Unit/Babbage.hs

Lines changed: 18 additions & 12 deletions
Original file line numberDiff line numberDiff line change
@@ -10,8 +10,10 @@ import Cardano.Mock.ChainSync.Server (IOManager)
1010
import Data.Text (Text)
1111
import Test.Tasty (TestTree, testGroup)
1212
import Test.Tasty.HUnit (Assertion, testCase)
13+
import Test.Tasty.ExpectedFailure (expectFail)
1314

14-
import qualified Test.Cardano.Db.Mock.Unit.Babbage.Flag.ConsumedTxOut as FlagConsumedTxOut
15+
import qualified Test.Cardano.Db.Mock.Unit.Babbage.CommandLineArg.MigrateConsumedPruneTxOut as MigrateConsumedPruneTxOut
16+
import qualified Test.Cardano.Db.Mock.Unit.Babbage.CommandLineArg.ConfigFile as ConfigFile
1517
import qualified Test.Cardano.Db.Mock.Unit.Babbage.InlineAndReference as BabInlineRef
1618
import qualified Test.Cardano.Db.Mock.Unit.Babbage.Other as BabOther
1719
import qualified Test.Cardano.Db.Mock.Unit.Babbage.Plutus as BabPlutus
@@ -35,19 +37,23 @@ unitTests iom knownMigrations =
3537
, test "node restart boundary" BabSimple.nodeRestartBoundary
3638
]
3739
, testGroup
38-
"flags"
40+
"Command Line Arguements"
3941
[ testGroup
40-
"consumed-tx-out"
41-
[ test "flag check" FlagConsumedTxOut.flagCheck
42-
, test "basic prune" FlagConsumedTxOut.basicPrune
43-
, test "prune with simple rollback" FlagConsumedTxOut.pruneWithSimpleRollback
44-
, test "prune with full tx rollback" FlagConsumedTxOut.pruneWithFullTxRollback
45-
, test "pruning should keep some tx" FlagConsumedTxOut.pruningShouldKeepSomeTx
46-
, test "prune and rollback one block" FlagConsumedTxOut.pruneAndRollBackOneBlock
47-
, test "no pruning and rollback" FlagConsumedTxOut.noPruneAndRollBack
48-
, test "prune same block" FlagConsumedTxOut.pruneSameBlock
49-
, test "no pruning same block" FlagConsumedTxOut.noPruneSameBlock
42+
"MigrateConsumed - PruneTxOut"
43+
[ test "flag check" MigrateConsumedPruneTxOut.commandLineArgCheck
44+
, test "basic prune" MigrateConsumedPruneTxOut.basicPrune
45+
, test "prune with simple rollback" MigrateConsumedPruneTxOut.pruneWithSimpleRollback
46+
, test "prune with full tx rollback" MigrateConsumedPruneTxOut.pruneWithFullTxRollback
47+
, test "pruning should keep some tx" MigrateConsumedPruneTxOut.pruningShouldKeepSomeTx
48+
, test "prune and rollback one block" MigrateConsumedPruneTxOut.pruneAndRollBackOneBlock
49+
, test "no pruning and rollback" MigrateConsumedPruneTxOut.noPruneAndRollBack
50+
, test "prune same block" MigrateConsumedPruneTxOut.pruneSameBlock
51+
, test "no pruning same block" MigrateConsumedPruneTxOut.noPruneSameBlock
5052
]
53+
, testGroup
54+
"ConfigFile"
55+
[ expectFail $ test "fails if incorrect config file" ConfigFile.checkConfigFileArg
56+
]
5157
]
5258
, testGroup
5359
"rollbacks"
Lines changed: 37 additions & 0 deletions
Original file line numberDiff line numberDiff line change
@@ -0,0 +1,37 @@
1+
module Test.Cardano.Db.Mock.Unit.Babbage.CommandLineArg.ConfigFile (
2+
checkConfigFileArg,
3+
)
4+
where
5+
6+
import Cardano.Mock.ChainSync.Server (IOManager)
7+
import Data.Text (Text)
8+
import Test.Cardano.Db.Mock.Config (CommandLineArgs (..), babbageConfigDir, withCustomConfigAndLogs)
9+
import Test.Tasty.HUnit (Assertion)
10+
11+
mkCommandLineArgs :: Bool -> CommandLineArgs
12+
mkCommandLineArgs hasConfigFile =
13+
CommandLineArgs
14+
{ claHasConfigFile = hasConfigFile
15+
, claExtended = True
16+
, claHasCache = True
17+
, claShouldUseLedger = True
18+
, claSkipFix = True
19+
, claOnlyFix = False
20+
, claForceIndexes = False
21+
, claHasMultiAssets = True
22+
, claHasMetadata = True
23+
, claHasPlutusExtra = True
24+
, claHasOfflineData = True
25+
, claTurboMode = False
26+
, claFullMode = True
27+
, claMigrateConsumed = True
28+
, claPruneTxOut = True
29+
}
30+
31+
-- this test fails as incorrect configuration file given
32+
checkConfigFileArg :: IOManager -> [(Text, Text)] -> Assertion
33+
checkConfigFileArg =
34+
withCustomConfigAndLogs (mkCommandLineArgs False) babbageConfigDir testLabel $ \_ _ _ -> do
35+
pure ()
36+
where
37+
testLabel = "CLAcheckConfigFileArg"

0 commit comments

Comments
 (0)