1- {-# LANGUAGE BangPatterns #-}
2- {-# LANGUAGE BlockArguments #-}
3- {-# LANGUAGE DataKinds #-}
4- {-# LANGUAGE FlexibleContexts #-}
5- {-# LANGUAGE GADTs #-}
6- {-# LANGUAGE GeneralisedNewtypeDeriving #-}
7- {-# LANGUAGE LambdaCase #-}
8- {-# LANGUAGE NamedFieldPuns #-}
9- {-# LANGUAGE OverloadedStrings #-}
10- {-# LANGUAGE ScopedTypeVariables #-}
11- {-# LANGUAGE TupleSections #-}
12- {-# LANGUAGE TypeApplications #-}
13- {-# LANGUAGE TypeFamilies #-}
1+ {-# LANGUAGE BangPatterns #-}
2+ {-# LANGUAGE BlockArguments #-}
3+ {-# LANGUAGE DataKinds #-}
4+ {-# LANGUAGE FlexibleContexts #-}
5+ {-# LANGUAGE GADTs #-}
6+ {-# LANGUAGE LambdaCase #-}
7+ {-# LANGUAGE NamedFieldPuns #-}
8+ {-# LANGUAGE OverloadedStrings #-}
9+ {-# LANGUAGE ScopedTypeVariables #-}
10+ {-# LANGUAGE TupleSections #-}
11+ {-# LANGUAGE TypeApplications #-}
12+ {-# LANGUAGE TypeFamilies #-}
1413
1514module Cardano.Tools.DBAnalyser.Analysis (
1615 AnalysisEnv (.. )
@@ -33,6 +32,7 @@ import Cardano.Tools.DBAnalyser.CSV (computeAndWriteLine,
3332 writeHeaderLine )
3433import Cardano.Tools.DBAnalyser.HasAnalysis (HasAnalysis )
3534import qualified Cardano.Tools.DBAnalyser.HasAnalysis as HasAnalysis
35+ import Cardano.Tools.DBAnalyser.Types
3636import Codec.CBOR.Encoding (Encoding )
3737import Control.Monad (unless , void , when )
3838import Control.Monad.Except (runExcept )
@@ -83,39 +83,6 @@ import qualified System.IO as IO
8383 Run the requested analysis
8484-------------------------------------------------------------------------------}
8585
86- data AnalysisName =
87- ShowSlotBlockNo
88- | CountTxOutputs
89- | ShowBlockHeaderSize
90- | ShowBlockTxsSize
91- | ShowEBBs
92- | OnlyValidation
93- | StoreLedgerStateAt SlotNo LedgerApplicationMode
94- | CountBlocks
95- | CheckNoThunksEvery Word64
96- | TraceLedgerProcessing
97- | BenchmarkLedgerOps (Maybe FilePath )
98- | ReproMempoolAndForge Int
99- -- | Compute different block application metrics every 'NumberOfBlocks'.
100- --
101- -- The metrics will be written to the provided file path, or to
102- -- the standard output if no file path is specified.
103- | GetBlockApplicationMetrics NumberOfBlocks (Maybe FilePath )
104- deriving Show
105-
106- data AnalysisResult =
107- ResultCountBlock Int
108- | ResultMaxHeaderSize Word16
109- deriving (Eq , Show )
110-
111- newtype NumberOfBlocks = NumberOfBlocks { unNumberOfBlocks :: Word64 }
112- deriving (Eq , Show , Num , Read )
113-
114- -- | Whether to apply blocks to a ledger state via /reapplication/ (eg skipping
115- -- signature checks/Plutus scripts) or full /application/ (much slower).
116- data LedgerApplicationMode = LedgerReapply | LedgerApply
117- deriving (Eq , Show )
118-
11986runAnalysis ::
12087 forall blk .
12188 ( HasAnalysis blk
@@ -877,8 +844,6 @@ reproMempoolForge numBlks env = do
877844 Auxiliary: processing all blocks in the DB
878845-------------------------------------------------------------------------------}
879846
880- data Limit = Limit Int | Unlimited
881-
882847decreaseLimit :: Limit -> Maybe Limit
883848decreaseLimit Unlimited = Just Unlimited
884849decreaseLimit (Limit 0 ) = Nothing
0 commit comments