module Hydra.Cluster.Options where

import Data.ByteString.Char8 qualified as BSC
import Hydra.Cardano.Api (AsType (AsTxId), TxId, deserialiseFromRawBytesHex)
import Hydra.Cluster.Fixture (KnownNetwork (..))
import Hydra.Prelude
import Options.Applicative (Parser, eitherReader, flag, flag', help, long, metavar, strOption)
import Options.Applicative.Builder (option)

data Options = Options
  { Options -> Maybe KnownNetwork
knownNetwork :: Maybe KnownNetwork
  , Options -> Maybe FilePath
stateDirectory :: Maybe FilePath
  , Options -> PublishOrReuse
publishHydraScripts :: PublishOrReuse
  , Options -> UseMithril
useMithril :: UseMithril
  }
  deriving stock (Int -> Options -> ShowS
[Options] -> ShowS
Options -> FilePath
(Int -> Options -> ShowS)
-> (Options -> FilePath) -> ([Options] -> ShowS) -> Show Options
forall a.
(Int -> a -> ShowS) -> (a -> FilePath) -> ([a] -> ShowS) -> Show a
$cshowsPrec :: Int -> Options -> ShowS
showsPrec :: Int -> Options -> ShowS
$cshow :: Options -> FilePath
show :: Options -> FilePath
$cshowList :: [Options] -> ShowS
showList :: [Options] -> ShowS
Show, Options -> Options -> Bool
(Options -> Options -> Bool)
-> (Options -> Options -> Bool) -> Eq Options
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
$c== :: Options -> Options -> Bool
== :: Options -> Options -> Bool
$c/= :: Options -> Options -> Bool
/= :: Options -> Options -> Bool
Eq, (forall x. Options -> Rep Options x)
-> (forall x. Rep Options x -> Options) -> Generic Options
forall x. Rep Options x -> Options
forall x. Options -> Rep Options x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cfrom :: forall x. Options -> Rep Options x
from :: forall x. Options -> Rep Options x
$cto :: forall x. Rep Options x -> Options
to :: forall x. Rep Options x -> Options
Generic)
  deriving anyclass ([Options] -> Value
[Options] -> Encoding
Options -> Bool
Options -> Value
Options -> Encoding
(Options -> Value)
-> (Options -> Encoding)
-> ([Options] -> Value)
-> ([Options] -> Encoding)
-> (Options -> Bool)
-> ToJSON Options
forall a.
(a -> Value)
-> (a -> Encoding)
-> ([a] -> Value)
-> ([a] -> Encoding)
-> (a -> Bool)
-> ToJSON a
$ctoJSON :: Options -> Value
toJSON :: Options -> Value
$ctoEncoding :: Options -> Encoding
toEncoding :: Options -> Encoding
$ctoJSONList :: [Options] -> Value
toJSONList :: [Options] -> Value
$ctoEncodingList :: [Options] -> Encoding
toEncodingList :: [Options] -> Encoding
$comitField :: Options -> Bool
omitField :: Options -> Bool
ToJSON, Maybe Options
Value -> Parser [Options]
Value -> Parser Options
(Value -> Parser Options)
-> (Value -> Parser [Options]) -> Maybe Options -> FromJSON Options
forall a.
(Value -> Parser a)
-> (Value -> Parser [a]) -> Maybe a -> FromJSON a
$cparseJSON :: Value -> Parser Options
parseJSON :: Value -> Parser Options
$cparseJSONList :: Value -> Parser [Options]
parseJSONList :: Value -> Parser [Options]
$comittedField :: Maybe Options
omittedField :: Maybe Options
FromJSON)

data PublishOrReuse = Publish | Reuse TxId
  deriving stock (Int -> PublishOrReuse -> ShowS
[PublishOrReuse] -> ShowS
PublishOrReuse -> FilePath
(Int -> PublishOrReuse -> ShowS)
-> (PublishOrReuse -> FilePath)
-> ([PublishOrReuse] -> ShowS)
-> Show PublishOrReuse
forall a.
(Int -> a -> ShowS) -> (a -> FilePath) -> ([a] -> ShowS) -> Show a
$cshowsPrec :: Int -> PublishOrReuse -> ShowS
showsPrec :: Int -> PublishOrReuse -> ShowS
$cshow :: PublishOrReuse -> FilePath
show :: PublishOrReuse -> FilePath
$cshowList :: [PublishOrReuse] -> ShowS
showList :: [PublishOrReuse] -> ShowS
Show, PublishOrReuse -> PublishOrReuse -> Bool
(PublishOrReuse -> PublishOrReuse -> Bool)
-> (PublishOrReuse -> PublishOrReuse -> Bool) -> Eq PublishOrReuse
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
$c== :: PublishOrReuse -> PublishOrReuse -> Bool
== :: PublishOrReuse -> PublishOrReuse -> Bool
$c/= :: PublishOrReuse -> PublishOrReuse -> Bool
/= :: PublishOrReuse -> PublishOrReuse -> Bool
Eq, (forall x. PublishOrReuse -> Rep PublishOrReuse x)
-> (forall x. Rep PublishOrReuse x -> PublishOrReuse)
-> Generic PublishOrReuse
forall x. Rep PublishOrReuse x -> PublishOrReuse
forall x. PublishOrReuse -> Rep PublishOrReuse x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cfrom :: forall x. PublishOrReuse -> Rep PublishOrReuse x
from :: forall x. PublishOrReuse -> Rep PublishOrReuse x
$cto :: forall x. Rep PublishOrReuse x -> PublishOrReuse
to :: forall x. Rep PublishOrReuse x -> PublishOrReuse
Generic)
  deriving anyclass ([PublishOrReuse] -> Value
[PublishOrReuse] -> Encoding
PublishOrReuse -> Bool
PublishOrReuse -> Value
PublishOrReuse -> Encoding
(PublishOrReuse -> Value)
-> (PublishOrReuse -> Encoding)
-> ([PublishOrReuse] -> Value)
-> ([PublishOrReuse] -> Encoding)
-> (PublishOrReuse -> Bool)
-> ToJSON PublishOrReuse
forall a.
(a -> Value)
-> (a -> Encoding)
-> ([a] -> Value)
-> ([a] -> Encoding)
-> (a -> Bool)
-> ToJSON a
$ctoJSON :: PublishOrReuse -> Value
toJSON :: PublishOrReuse -> Value
$ctoEncoding :: PublishOrReuse -> Encoding
toEncoding :: PublishOrReuse -> Encoding
$ctoJSONList :: [PublishOrReuse] -> Value
toJSONList :: [PublishOrReuse] -> Value
$ctoEncodingList :: [PublishOrReuse] -> Encoding
toEncodingList :: [PublishOrReuse] -> Encoding
$comitField :: PublishOrReuse -> Bool
omitField :: PublishOrReuse -> Bool
ToJSON, Maybe PublishOrReuse
Value -> Parser [PublishOrReuse]
Value -> Parser PublishOrReuse
(Value -> Parser PublishOrReuse)
-> (Value -> Parser [PublishOrReuse])
-> Maybe PublishOrReuse
-> FromJSON PublishOrReuse
forall a.
(Value -> Parser a)
-> (Value -> Parser [a]) -> Maybe a -> FromJSON a
$cparseJSON :: Value -> Parser PublishOrReuse
parseJSON :: Value -> Parser PublishOrReuse
$cparseJSONList :: Value -> Parser [PublishOrReuse]
parseJSONList :: Value -> Parser [PublishOrReuse]
$comittedField :: Maybe PublishOrReuse
omittedField :: Maybe PublishOrReuse
FromJSON)

data UseMithril = NotUseMithril | UseMithril
  deriving stock (Int -> UseMithril -> ShowS
[UseMithril] -> ShowS
UseMithril -> FilePath
(Int -> UseMithril -> ShowS)
-> (UseMithril -> FilePath)
-> ([UseMithril] -> ShowS)
-> Show UseMithril
forall a.
(Int -> a -> ShowS) -> (a -> FilePath) -> ([a] -> ShowS) -> Show a
$cshowsPrec :: Int -> UseMithril -> ShowS
showsPrec :: Int -> UseMithril -> ShowS
$cshow :: UseMithril -> FilePath
show :: UseMithril -> FilePath
$cshowList :: [UseMithril] -> ShowS
showList :: [UseMithril] -> ShowS
Show, UseMithril -> UseMithril -> Bool
(UseMithril -> UseMithril -> Bool)
-> (UseMithril -> UseMithril -> Bool) -> Eq UseMithril
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
$c== :: UseMithril -> UseMithril -> Bool
== :: UseMithril -> UseMithril -> Bool
$c/= :: UseMithril -> UseMithril -> Bool
/= :: UseMithril -> UseMithril -> Bool
Eq, (forall x. UseMithril -> Rep UseMithril x)
-> (forall x. Rep UseMithril x -> UseMithril) -> Generic UseMithril
forall x. Rep UseMithril x -> UseMithril
forall x. UseMithril -> Rep UseMithril x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cfrom :: forall x. UseMithril -> Rep UseMithril x
from :: forall x. UseMithril -> Rep UseMithril x
$cto :: forall x. Rep UseMithril x -> UseMithril
to :: forall x. Rep UseMithril x -> UseMithril
Generic)
  deriving anyclass ([UseMithril] -> Value
[UseMithril] -> Encoding
UseMithril -> Bool
UseMithril -> Value
UseMithril -> Encoding
(UseMithril -> Value)
-> (UseMithril -> Encoding)
-> ([UseMithril] -> Value)
-> ([UseMithril] -> Encoding)
-> (UseMithril -> Bool)
-> ToJSON UseMithril
forall a.
(a -> Value)
-> (a -> Encoding)
-> ([a] -> Value)
-> ([a] -> Encoding)
-> (a -> Bool)
-> ToJSON a
$ctoJSON :: UseMithril -> Value
toJSON :: UseMithril -> Value
$ctoEncoding :: UseMithril -> Encoding
toEncoding :: UseMithril -> Encoding
$ctoJSONList :: [UseMithril] -> Value
toJSONList :: [UseMithril] -> Value
$ctoEncodingList :: [UseMithril] -> Encoding
toEncodingList :: [UseMithril] -> Encoding
$comitField :: UseMithril -> Bool
omitField :: UseMithril -> Bool
ToJSON, Maybe UseMithril
Value -> Parser [UseMithril]
Value -> Parser UseMithril
(Value -> Parser UseMithril)
-> (Value -> Parser [UseMithril])
-> Maybe UseMithril
-> FromJSON UseMithril
forall a.
(Value -> Parser a)
-> (Value -> Parser [a]) -> Maybe a -> FromJSON a
$cparseJSON :: Value -> Parser UseMithril
parseJSON :: Value -> Parser UseMithril
$cparseJSONList :: Value -> Parser [UseMithril]
parseJSONList :: Value -> Parser [UseMithril]
$comittedField :: Maybe UseMithril
omittedField :: Maybe UseMithril
FromJSON)

parseOptions :: Parser Options
parseOptions :: Parser Options
parseOptions =
  Maybe KnownNetwork
-> Maybe FilePath -> PublishOrReuse -> UseMithril -> Options
Options
    (Maybe KnownNetwork
 -> Maybe FilePath -> PublishOrReuse -> UseMithril -> Options)
-> Parser (Maybe KnownNetwork)
-> Parser
     (Maybe FilePath -> PublishOrReuse -> UseMithril -> Options)
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> Parser (Maybe KnownNetwork)
parseKnownNetwork
    Parser (Maybe FilePath -> PublishOrReuse -> UseMithril -> Options)
-> Parser (Maybe FilePath)
-> Parser (PublishOrReuse -> UseMithril -> Options)
forall a b. Parser (a -> b) -> Parser a -> Parser b
forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
<*> Parser (Maybe FilePath)
parseStateDirectory
    Parser (PublishOrReuse -> UseMithril -> Options)
-> Parser PublishOrReuse -> Parser (UseMithril -> Options)
forall a b. Parser (a -> b) -> Parser a -> Parser b
forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
<*> Parser PublishOrReuse
parsePublishHydraScripts
    Parser (UseMithril -> Options)
-> Parser UseMithril -> Parser Options
forall a b. Parser (a -> b) -> Parser a -> Parser b
forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
<*> Parser UseMithril
parseUseMithril
 where
  parseKnownNetwork :: Parser (Maybe KnownNetwork)
parseKnownNetwork =
    Maybe KnownNetwork
-> Mod FlagFields (Maybe KnownNetwork)
-> Parser (Maybe KnownNetwork)
forall a. a -> Mod FlagFields a -> Parser a
flag' (KnownNetwork -> Maybe KnownNetwork
forall a. a -> Maybe a
Just KnownNetwork
Preview) (FilePath -> Mod FlagFields (Maybe KnownNetwork)
forall (f :: * -> *) a. HasName f => FilePath -> Mod f a
long FilePath
"preview" Mod FlagFields (Maybe KnownNetwork)
-> Mod FlagFields (Maybe KnownNetwork)
-> Mod FlagFields (Maybe KnownNetwork)
forall a. Semigroup a => a -> a -> a
<> FilePath -> Mod FlagFields (Maybe KnownNetwork)
forall (f :: * -> *) a. FilePath -> Mod f a
help FilePath
"The preview testnet")
      Parser (Maybe KnownNetwork)
-> Parser (Maybe KnownNetwork) -> Parser (Maybe KnownNetwork)
forall a. Parser a -> Parser a -> Parser a
forall (f :: * -> *) a. Alternative f => f a -> f a -> f a
<|> Maybe KnownNetwork
-> Mod FlagFields (Maybe KnownNetwork)
-> Parser (Maybe KnownNetwork)
forall a. a -> Mod FlagFields a -> Parser a
flag' (KnownNetwork -> Maybe KnownNetwork
forall a. a -> Maybe a
Just KnownNetwork
Preproduction) (FilePath -> Mod FlagFields (Maybe KnownNetwork)
forall (f :: * -> *) a. HasName f => FilePath -> Mod f a
long FilePath
"preprod" Mod FlagFields (Maybe KnownNetwork)
-> Mod FlagFields (Maybe KnownNetwork)
-> Mod FlagFields (Maybe KnownNetwork)
forall a. Semigroup a => a -> a -> a
<> FilePath -> Mod FlagFields (Maybe KnownNetwork)
forall (f :: * -> *) a. FilePath -> Mod f a
help FilePath
"The pre-production testnet")
      Parser (Maybe KnownNetwork)
-> Parser (Maybe KnownNetwork) -> Parser (Maybe KnownNetwork)
forall a. Parser a -> Parser a -> Parser a
forall (f :: * -> *) a. Alternative f => f a -> f a -> f a
<|> Maybe KnownNetwork
-> Mod FlagFields (Maybe KnownNetwork)
-> Parser (Maybe KnownNetwork)
forall a. a -> Mod FlagFields a -> Parser a
flag' (KnownNetwork -> Maybe KnownNetwork
forall a. a -> Maybe a
Just KnownNetwork
Mainnet) (FilePath -> Mod FlagFields (Maybe KnownNetwork)
forall (f :: * -> *) a. HasName f => FilePath -> Mod f a
long FilePath
"mainnet" Mod FlagFields (Maybe KnownNetwork)
-> Mod FlagFields (Maybe KnownNetwork)
-> Mod FlagFields (Maybe KnownNetwork)
forall a. Semigroup a => a -> a -> a
<> FilePath -> Mod FlagFields (Maybe KnownNetwork)
forall (f :: * -> *) a. FilePath -> Mod f a
help FilePath
"The mainnet")
      Parser (Maybe KnownNetwork)
-> Parser (Maybe KnownNetwork) -> Parser (Maybe KnownNetwork)
forall a. Parser a -> Parser a -> Parser a
forall (f :: * -> *) a. Alternative f => f a -> f a -> f a
<|> Maybe KnownNetwork
-> Mod FlagFields (Maybe KnownNetwork)
-> Parser (Maybe KnownNetwork)
forall a. a -> Mod FlagFields a -> Parser a
flag' (KnownNetwork -> Maybe KnownNetwork
forall a. a -> Maybe a
Just KnownNetwork
Sanchonet) (FilePath -> Mod FlagFields (Maybe KnownNetwork)
forall (f :: * -> *) a. HasName f => FilePath -> Mod f a
long FilePath
"sanchonet" Mod FlagFields (Maybe KnownNetwork)
-> Mod FlagFields (Maybe KnownNetwork)
-> Mod FlagFields (Maybe KnownNetwork)
forall a. Semigroup a => a -> a -> a
<> FilePath -> Mod FlagFields (Maybe KnownNetwork)
forall (f :: * -> *) a. FilePath -> Mod f a
help FilePath
"The sanchonet preview testnet")
      Parser (Maybe KnownNetwork)
-> Parser (Maybe KnownNetwork) -> Parser (Maybe KnownNetwork)
forall a. Parser a -> Parser a -> Parser a
forall (f :: * -> *) a. Alternative f => f a -> f a -> f a
<|> Maybe KnownNetwork
-> Mod FlagFields (Maybe KnownNetwork)
-> Parser (Maybe KnownNetwork)
forall a. a -> Mod FlagFields a -> Parser a
flag'
        Maybe KnownNetwork
forall a. Maybe a
Nothing
        ( FilePath -> Mod FlagFields (Maybe KnownNetwork)
forall (f :: * -> *) a. HasName f => FilePath -> Mod f a
long FilePath
"devnet"
            Mod FlagFields (Maybe KnownNetwork)
-> Mod FlagFields (Maybe KnownNetwork)
-> Mod FlagFields (Maybe KnownNetwork)
forall a. Semigroup a => a -> a -> a
<> FilePath -> Mod FlagFields (Maybe KnownNetwork)
forall (f :: * -> *) a. FilePath -> Mod f a
help
              FilePath
"Create a local cardano devnet by running a cardano-node, start a\
              \hydra-node and open a single-party head in it. Generates a wallet\
              \key pair and commits some ADA into the head using it. The head is\
              \also simulating some traffic on this UTxO by re-spending it to\
              \the same key constantly. The keys are available on the\
              \state-directory. This is useful as a sandbox for development and\
              \testing."
        )

  parseStateDirectory :: Parser (Maybe FilePath)
parseStateDirectory =
    Parser FilePath -> Parser (Maybe FilePath)
forall (f :: * -> *) a. Alternative f => f a -> f (Maybe a)
optional (Parser FilePath -> Parser (Maybe FilePath))
-> (Mod OptionFields FilePath -> Parser FilePath)
-> Mod OptionFields FilePath
-> Parser (Maybe FilePath)
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Mod OptionFields FilePath -> Parser FilePath
forall s. IsString s => Mod OptionFields s -> Parser s
strOption (Mod OptionFields FilePath -> Parser (Maybe FilePath))
-> Mod OptionFields FilePath -> Parser (Maybe FilePath)
forall a b. (a -> b) -> a -> b
$
      FilePath -> Mod OptionFields FilePath
forall (f :: * -> *) a. HasName f => FilePath -> Mod f a
long FilePath
"state-directory"
        Mod OptionFields FilePath
-> Mod OptionFields FilePath -> Mod OptionFields FilePath
forall a. Semigroup a => a -> a -> a
<> FilePath -> Mod OptionFields FilePath
forall (f :: * -> *) a. HasMetavar f => FilePath -> Mod f a
metavar FilePath
"DIR"
        Mod OptionFields FilePath
-> Mod OptionFields FilePath -> Mod OptionFields FilePath
forall a. Semigroup a => a -> a -> a
<> FilePath -> Mod OptionFields FilePath
forall (f :: * -> *) a. FilePath -> Mod f a
help
          FilePath
"Filepath to the state directory used. If not given a temporary \
          \one is used. Note that this directory will contain the \
          \cardano-node state of the network and is potentially quite \
          \large (> 13GB for testnet)!"

  parsePublishHydraScripts :: Parser PublishOrReuse
parsePublishHydraScripts =
    PublishOrReuse
-> Mod FlagFields PublishOrReuse -> Parser PublishOrReuse
forall a. a -> Mod FlagFields a -> Parser a
flag'
      PublishOrReuse
Publish
      ( FilePath -> Mod FlagFields PublishOrReuse
forall (f :: * -> *) a. HasName f => FilePath -> Mod f a
long FilePath
"publish-hydra-scripts"
          Mod FlagFields PublishOrReuse
-> Mod FlagFields PublishOrReuse -> Mod FlagFields PublishOrReuse
forall a. Semigroup a => a -> a -> a
<> FilePath -> Mod FlagFields PublishOrReuse
forall (f :: * -> *) a. FilePath -> Mod f a
help FilePath
"Publish hydra scripts before running the scenario."
      )
      Parser PublishOrReuse
-> Parser PublishOrReuse -> Parser PublishOrReuse
forall a. Parser a -> Parser a -> Parser a
forall (f :: * -> *) a. Alternative f => f a -> f a -> f a
<|> ReadM PublishOrReuse
-> Mod OptionFields PublishOrReuse -> Parser PublishOrReuse
forall a. ReadM a -> Mod OptionFields a -> Parser a
option
        ((FilePath -> Either FilePath PublishOrReuse)
-> ReadM PublishOrReuse
forall a. (FilePath -> Either FilePath a) -> ReadM a
eitherReader ((FilePath -> Either FilePath PublishOrReuse)
 -> ReadM PublishOrReuse)
-> (FilePath -> Either FilePath PublishOrReuse)
-> ReadM PublishOrReuse
forall a b. (a -> b) -> a -> b
$ (RawBytesHexError -> FilePath)
-> (TxId -> PublishOrReuse)
-> Either RawBytesHexError TxId
-> Either FilePath PublishOrReuse
forall a b c d. (a -> b) -> (c -> d) -> Either a c -> Either b d
forall (p :: * -> * -> *) a b c d.
Bifunctor p =>
(a -> b) -> (c -> d) -> p a c -> p b d
bimap RawBytesHexError -> FilePath
forall b a. (Show a, IsString b) => a -> b
show TxId -> PublishOrReuse
Reuse (Either RawBytesHexError TxId -> Either FilePath PublishOrReuse)
-> (FilePath -> Either RawBytesHexError TxId)
-> FilePath
-> Either FilePath PublishOrReuse
forall b c a. (b -> c) -> (a -> b) -> a -> c
. AsType TxId -> ByteString -> Either RawBytesHexError TxId
forall a.
SerialiseAsRawBytes a =>
AsType a -> ByteString -> Either RawBytesHexError a
deserialiseFromRawBytesHex AsType TxId
AsTxId (ByteString -> Either RawBytesHexError TxId)
-> (FilePath -> ByteString)
-> FilePath
-> Either RawBytesHexError TxId
forall b c a. (b -> c) -> (a -> b) -> a -> c
. FilePath -> ByteString
BSC.pack)
        ( FilePath -> Mod OptionFields PublishOrReuse
forall (f :: * -> *) a. HasName f => FilePath -> Mod f a
long FilePath
"hydra-scripts-tx-id"
            Mod OptionFields PublishOrReuse
-> Mod OptionFields PublishOrReuse
-> Mod OptionFields PublishOrReuse
forall a. Semigroup a => a -> a -> a
<> FilePath -> Mod OptionFields PublishOrReuse
forall (f :: * -> *) a. HasMetavar f => FilePath -> Mod f a
metavar FilePath
"TXID"
            Mod OptionFields PublishOrReuse
-> Mod OptionFields PublishOrReuse
-> Mod OptionFields PublishOrReuse
forall a. Semigroup a => a -> a -> a
<> FilePath -> Mod OptionFields PublishOrReuse
forall (f :: * -> *) a. FilePath -> Mod f a
help
              FilePath
"Use the hydra scripts already published in given transaction id. \
              \See --publish-hydra-scripts or hydra-node publish-scripts"
        )

  parseUseMithril :: Parser UseMithril
parseUseMithril =
    UseMithril
-> UseMithril -> Mod FlagFields UseMithril -> Parser UseMithril
forall a. a -> a -> Mod FlagFields a -> Parser a
flag
      UseMithril
NotUseMithril
      UseMithril
UseMithril
      ( FilePath -> Mod FlagFields UseMithril
forall (f :: * -> *) a. HasName f => FilePath -> Mod f a
long FilePath
"use-mithril"
          Mod FlagFields UseMithril
-> Mod FlagFields UseMithril -> Mod FlagFields UseMithril
forall a. Semigroup a => a -> a -> a
<> FilePath -> Mod FlagFields UseMithril
forall (f :: * -> *) a. FilePath -> Mod f a
help
            FilePath
"Use mithril-client to download and verify the latest network snapshot. \
            \When setting this, ensure that there is no db/ in --state-directory. \
            \If not set, the cardano-node will synchronize the network given the current \
            \cardano-node state in --state-directory."
      )