22{-# LANGUAGE LambdaCase #-}
33
44module DBAnalyser.Parsers
5- ( BlockType ( .. )
6- , blockTypeParser
7- , parseCmdLine
5+ ( parseCmdLine
6+ , parseCardanoArgs
7+ , CardanoBlockArgs
88 ) where
99
10- import Cardano.Crypto (RequiresNetworkMagic (.. ))
1110import Cardano.Tools.DBAnalyser.Analysis
12- import Cardano.Tools.DBAnalyser.Block.Byron
1311import Cardano.Tools.DBAnalyser.Block.Cardano
14- import Cardano.Tools.DBAnalyser.Block.Shelley
1512import Cardano.Tools.DBAnalyser.Types
1613import qualified Data.Foldable as Foldable
1714import Options.Applicative
1815import Ouroboros.Consensus.Block (SlotNo (.. ), WithOrigin (.. ))
1916import Ouroboros.Consensus.Byron.Node (PBftSignatureThreshold (.. ))
20- import Ouroboros.Consensus.Shelley.Node (Nonce (.. ))
2117
2218{- ------------------------------------------------------------------------------
2319 Parsing
2420-------------------------------------------------------------------------------}
2521
26- parseCmdLine :: Parser (DBAnalyserConfig , BlockType )
27- parseCmdLine = (,) <$> parseDBAnalyserConfig <*> blockTypeParser
22+ parseCmdLine :: Parser (DBAnalyserConfig , CardanoBlockArgs )
23+ parseCmdLine = (,) <$> parseDBAnalyserConfig <*> parseCardanoArgs
2824
2925parseDBAnalyserConfig :: Parser DBAnalyserConfig
3026parseDBAnalyserConfig =
@@ -259,65 +255,12 @@ pMaybeOutputFile =
259255 Parse BlockType-specific arguments
260256-------------------------------------------------------------------------------}
261257
262- data BlockType
263- = ByronBlock ByronBlockArgs
264- | ShelleyBlock ShelleyBlockArgs
265- | CardanoBlock CardanoBlockArgs
266-
267- blockTypeParser :: Parser BlockType
268- blockTypeParser =
269- subparser $
270- mconcat
271- [ command
272- " byron"
273- (info (parseByronType <**> helper) (progDesc " Analyse a Byron-only DB" ))
274- , command
275- " shelley"
276- (info (parseShelleyType <**> helper) (progDesc " Analyse a Shelley-only DB" ))
277- , command
278- " cardano"
279- (info (parseCardanoType <**> helper) (progDesc " Analyse a Cardano DB" ))
280- ]
281-
282- parseByronType :: Parser BlockType
283- parseByronType = ByronBlock <$> parseByronArgs
284-
285- parseShelleyType :: Parser BlockType
286- parseShelleyType = ShelleyBlock <$> parseShelleyArgs
287-
288- parseCardanoType :: Parser BlockType
289- parseCardanoType = CardanoBlock <$> parseCardanoArgs
290-
291258parseCardanoArgs :: Parser CardanoBlockArgs
292259parseCardanoArgs =
293260 CardanoBlockArgs
294261 <$> parseConfigFile
295262 <*> parsePBftSignatureThreshold
296263
297- parseShelleyArgs :: Parser ShelleyBlockArgs
298- parseShelleyArgs =
299- ShelleyBlockArgs
300- <$> strOption
301- ( mconcat
302- [ long " configShelley"
303- , help " Path to config file"
304- , metavar " PATH"
305- ]
306- )
307- <*> Foldable. asum
308- [ Nonce <$> parseNonce
309- , pure NeutralNonce
310- ]
311- where
312- parseNonce =
313- strOption
314- ( mconcat
315- [ long " nonce"
316- , help " Initial nonce, i.e., hash of the genesis config file"
317- , metavar " NONCE"
318- ]
319- )
320-
321264parseConfigFile :: Parser FilePath
322265parseConfigFile =
323266 strOption $
@@ -337,27 +280,3 @@ parsePBftSignatureThreshold =
337280 , help " PBftSignatureThreshold"
338281 , metavar " THRESHOLD"
339282 ]
340-
341- parseByronArgs :: Parser ByronBlockArgs
342- parseByronArgs =
343- ByronBlockArgs
344- <$> parseConfigFile
345- <*> flag
346- RequiresNoMagic
347- RequiresMagic
348- ( mconcat
349- [ long " requires-magic"
350- , help " The DB contains blocks from a testnet, requiring network magic, rather than mainnet"
351- ]
352- )
353- <*> optional
354- ( option
355- auto
356- ( mconcat
357- [ long " genesisHash"
358- , help " Expected genesis hash"
359- , metavar " HASH"
360- ]
361- )
362- )
363- <*> parsePBftSignatureThreshold
0 commit comments