Skip to content

Commit

Permalink
cardano-tools: styling; more explicit test case
Browse files Browse the repository at this point in the history
  • Loading branch information
mgmeier committed Aug 8, 2022
1 parent 76a43c8 commit a92ff11
Show file tree
Hide file tree
Showing 3 changed files with 50 additions and 47 deletions.
@@ -1,4 +1,4 @@
{-# LANGUAGE ApplicativeDo #-}
{-# LANGUAGE ApplicativeDo #-}

module DBAnalyser.Parsers (parseCmdLine) where

Expand Down
Expand Up @@ -11,53 +11,48 @@ import Ouroboros.Consensus.Shelley.Node (ShelleyGenesis)
import Cardano.Node.Types (ProtocolFilepaths)


data NodeConfigStub =
NodeConfigStub {
ncsNodeConfig :: !Aeson.Value
, ncsAlonzoGenesisFile :: !FilePath
, ncsShelleyGenesisFile :: !FilePath
, ncsByronGenesisFile :: !FilePath
}
deriving Show

data NodeFilePaths =
NodeFilePaths {
nfpConfig :: !FilePath
, nfpChainDB :: !FilePath
}
deriving Show

data NodeCredentials =
NodeCredentials {
credCertFile :: !(Maybe FilePath)
, credVRFFile :: !(Maybe FilePath)
, credKESFile :: !(Maybe FilePath)
, credBulkFile :: !(Maybe FilePath)
}
deriving Show
data NodeConfigStub = NodeConfigStub {
ncsNodeConfig :: !Aeson.Value
, ncsAlonzoGenesisFile :: !FilePath
, ncsShelleyGenesisFile :: !FilePath
, ncsByronGenesisFile :: !FilePath
}
deriving Show

data NodeFilePaths = NodeFilePaths {
nfpConfig :: !FilePath
, nfpChainDB :: !FilePath
}
deriving Show

data NodeCredentials = NodeCredentials {
credCertFile :: !(Maybe FilePath)
, credVRFFile :: !(Maybe FilePath)
, credKESFile :: !(Maybe FilePath)
, credBulkFile :: !(Maybe FilePath)
}
deriving Show

data ForgeLimit =
ForgeLimitBlock !Word64
| ForgeLimitSlot !SlotNo
| ForgeLimitEpoch !Word64
ForgeLimitBlock !Word64
| ForgeLimitSlot !SlotNo
| ForgeLimitEpoch !Word64
deriving (Eq, Show)

newtype ForgeResult = ForgeResult {resultForged :: Int}
deriving (Eq, Show)

data DBSynthesizerOptions =
DBSynthesizerOptions {
synthLimit :: !ForgeLimit
, synthForceDBRemoval :: !Bool
}
deriving Show

data DBSynthesizerConfig =
DBSynthesizerConfig {
confConfigStub :: NodeConfigStub
, confOptions :: DBSynthesizerOptions
, confProtocolCredentials :: ProtocolFilepaths
, confShelleyGenesis :: ShelleyGenesis StandardShelley
, confDbDir :: FilePath
data DBSynthesizerOptions = DBSynthesizerOptions {
synthLimit :: !ForgeLimit
, synthForceDBRemoval :: !Bool
}
deriving Show

data DBSynthesizerConfig = DBSynthesizerConfig {
confConfigStub :: NodeConfigStub
, confOptions :: DBSynthesizerOptions
, confProtocolCredentials :: ProtocolFilepaths
, confShelleyGenesis :: ShelleyGenesis StandardShelley
, confDbDir :: FilePath
}
deriving Show
18 changes: 13 additions & 5 deletions ouroboros-consensus-cardano-tools/test/Main.hs
Expand Up @@ -19,7 +19,7 @@ chainDB = "test/disk/chaindb"
testSynthOptions :: DBSynthesizerOptions
testSynthOptions =
DBSynthesizerOptions {
synthLimit = ForgeLimitEpoch 1
synthLimit = ForgeLimitSlot 8192
, synthForceDBRemoval = True
}

Expand Down Expand Up @@ -51,8 +51,14 @@ testAnalyserConfig =
, confLimit = Unlimited
}

multiStepTest :: (String -> IO ()) -> Assertion
multiStepTest logStep = do
-- | A multi-step test including synthesis and analaysis 'SomeConsensusProtocol' using the Cardano instance.
--
-- 1. step: synthesize a ChainDB and counts the amount of blocks forged in the proces.
-- 2. step: analyze the ChainDB from previous step and confirm the block count.

--
blockCountTest :: (String -> IO ()) -> Assertion
blockCountTest logStep = do
logStep "intializing synthesis"
(protocol, options) <- either assertFailure pure
=<< DBSynthesizer.initialize
Expand All @@ -70,12 +76,14 @@ multiStepTest logStep = do
CardanoBlock b -> DBAnalyser.analyse testAnalyserConfig b
_ -> assertFailure "expexcting test case for Cardano block type"

resultAnalysis == Just (ResultCountBlock blockCount) @? "wrong number of blocks counted during analysis"
resultAnalysis == Just (ResultCountBlock blockCount) @?
"wrong number of blocks encountered during analysis \
\ (counted: " ++ show resultAnalysis ++ "; expected: " ++ show blockCount ++ ")"

tests :: TestTree
tests =
testGroup "cardano-tools"
[ testCaseSteps "synthesize and analyse" multiStepTest
[ testCaseSteps "synthesize and analyse: blockCount" blockCountTest
]

main :: IO ()
Expand Down

0 comments on commit a92ff11

Please sign in to comment.