{-# LANGUAGE DataKinds #-}
{-# LANGUAGE FlexibleContexts #-}
{-# LANGUAGE GADTs #-}
{-# LANGUAGE ScopedTypeVariables #-}
{-# LANGUAGE TypeApplications #-}
module Cardano.CLI.Legacy.Option
(
parseLegacyCmds
, module Cardano.CLI.Legacy.Command
, parseTxIn
, pKeyRegistDeposit
, pStakePoolVerificationKeyOrHashOrFile
)
where
import Cardano.Api hiding (QueryInShelleyBasedEra (..))
import Cardano.CLI.Environment
import Cardano.CLI.EraBased.Common.Option
import Cardano.CLI.Legacy.Command
import Cardano.CLI.Legacy.Genesis.Command
import Cardano.CLI.Parser
import Cardano.CLI.Type.Common
import Cardano.Ledger.BaseTypes (NonZero, knownNonZeroBounded)
import Data.Char (toLower)
import Data.Foldable
import Data.Maybe
import Data.Word (Word64)
import Options.Applicative hiding (help, str)
import Options.Applicative qualified as Opt
parseLegacyCmds :: EnvCli -> Parser LegacyCmds
parseLegacyCmds :: EnvCli -> Parser LegacyCmds
parseLegacyCmds EnvCli
envCli =
Mod CommandFields LegacyCmds -> Parser LegacyCmds
forall a. Mod CommandFields a -> Parser a
Opt.hsubparser (Mod CommandFields LegacyCmds -> Parser LegacyCmds)
-> Mod CommandFields LegacyCmds -> Parser LegacyCmds
forall a b. (a -> b) -> a -> b
$
[Mod CommandFields LegacyCmds] -> Mod CommandFields LegacyCmds
forall a. Monoid a => [a] -> a
mconcat
[ String -> Mod CommandFields LegacyCmds
forall (f :: * -> *) a. HasMetavar f => String -> Mod f a
Opt.metavar String
"COMMAND"
, String -> ParserInfo LegacyCmds -> Mod CommandFields LegacyCmds
forall a. String -> ParserInfo a -> Mod CommandFields a
Opt.command String
"genesis" (ParserInfo LegacyCmds -> Mod CommandFields LegacyCmds)
-> ParserInfo LegacyCmds -> Mod CommandFields LegacyCmds
forall a b. (a -> b) -> a -> b
$
Parser LegacyCmds -> InfoMod LegacyCmds -> ParserInfo LegacyCmds
forall a. Parser a -> InfoMod a -> ParserInfo a
Opt.info (LegacyGenesisCmds -> LegacyCmds
LegacyGenesisCmds (LegacyGenesisCmds -> LegacyCmds)
-> Parser LegacyGenesisCmds -> Parser LegacyCmds
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> EnvCli -> Parser LegacyGenesisCmds
pGenesisCmds EnvCli
envCli) (InfoMod LegacyCmds -> ParserInfo LegacyCmds)
-> InfoMod LegacyCmds -> ParserInfo LegacyCmds
forall a b. (a -> b) -> a -> b
$
String -> InfoMod LegacyCmds
forall a. String -> InfoMod a
Opt.progDesc String
"Genesis block commands"
]
pGenesisCmds :: EnvCli -> Parser LegacyGenesisCmds
pGenesisCmds :: EnvCli -> Parser LegacyGenesisCmds
pGenesisCmds EnvCli
envCli =
[Parser LegacyGenesisCmds] -> Parser LegacyGenesisCmds
forall (t :: * -> *) (f :: * -> *) a.
(Foldable t, Alternative f) =>
t (f a) -> f a
asum
[ Mod CommandFields LegacyGenesisCmds -> Parser LegacyGenesisCmds
forall a. Mod CommandFields a -> Parser a
Opt.hsubparser (Mod CommandFields LegacyGenesisCmds -> Parser LegacyGenesisCmds)
-> Mod CommandFields LegacyGenesisCmds -> Parser LegacyGenesisCmds
forall a b. (a -> b) -> a -> b
$
String
-> ParserInfo LegacyGenesisCmds
-> Mod CommandFields LegacyGenesisCmds
forall a. String -> ParserInfo a -> Mod CommandFields a
commandWithMetavar String
"key-gen-genesis" (ParserInfo LegacyGenesisCmds
-> Mod CommandFields LegacyGenesisCmds)
-> ParserInfo LegacyGenesisCmds
-> Mod CommandFields LegacyGenesisCmds
forall a b. (a -> b) -> a -> b
$
Parser LegacyGenesisCmds
-> InfoMod LegacyGenesisCmds -> ParserInfo LegacyGenesisCmds
forall a. Parser a -> InfoMod a -> ParserInfo a
Opt.info Parser LegacyGenesisCmds
pGenesisKeyGen (InfoMod LegacyGenesisCmds -> ParserInfo LegacyGenesisCmds)
-> InfoMod LegacyGenesisCmds -> ParserInfo LegacyGenesisCmds
forall a b. (a -> b) -> a -> b
$
String -> InfoMod LegacyGenesisCmds
forall a. String -> InfoMod a
Opt.progDesc String
"Create a Shelley genesis key pair"
, Mod CommandFields LegacyGenesisCmds -> Parser LegacyGenesisCmds
forall a. Mod CommandFields a -> Parser a
Opt.hsubparser (Mod CommandFields LegacyGenesisCmds -> Parser LegacyGenesisCmds)
-> Mod CommandFields LegacyGenesisCmds -> Parser LegacyGenesisCmds
forall a b. (a -> b) -> a -> b
$
String
-> ParserInfo LegacyGenesisCmds
-> Mod CommandFields LegacyGenesisCmds
forall a. String -> ParserInfo a -> Mod CommandFields a
commandWithMetavar String
"key-gen-delegate" (ParserInfo LegacyGenesisCmds
-> Mod CommandFields LegacyGenesisCmds)
-> ParserInfo LegacyGenesisCmds
-> Mod CommandFields LegacyGenesisCmds
forall a b. (a -> b) -> a -> b
$
Parser LegacyGenesisCmds
-> InfoMod LegacyGenesisCmds -> ParserInfo LegacyGenesisCmds
forall a. Parser a -> InfoMod a -> ParserInfo a
Opt.info Parser LegacyGenesisCmds
pGenesisDelegateKeyGen (InfoMod LegacyGenesisCmds -> ParserInfo LegacyGenesisCmds)
-> InfoMod LegacyGenesisCmds -> ParserInfo LegacyGenesisCmds
forall a b. (a -> b) -> a -> b
$
String -> InfoMod LegacyGenesisCmds
forall a. String -> InfoMod a
Opt.progDesc String
"Create a Shelley genesis delegate key pair"
, Mod CommandFields LegacyGenesisCmds -> Parser LegacyGenesisCmds
forall a. Mod CommandFields a -> Parser a
Opt.hsubparser (Mod CommandFields LegacyGenesisCmds -> Parser LegacyGenesisCmds)
-> Mod CommandFields LegacyGenesisCmds -> Parser LegacyGenesisCmds
forall a b. (a -> b) -> a -> b
$
String
-> ParserInfo LegacyGenesisCmds
-> Mod CommandFields LegacyGenesisCmds
forall a. String -> ParserInfo a -> Mod CommandFields a
commandWithMetavar String
"key-gen-utxo" (ParserInfo LegacyGenesisCmds
-> Mod CommandFields LegacyGenesisCmds)
-> ParserInfo LegacyGenesisCmds
-> Mod CommandFields LegacyGenesisCmds
forall a b. (a -> b) -> a -> b
$
Parser LegacyGenesisCmds
-> InfoMod LegacyGenesisCmds -> ParserInfo LegacyGenesisCmds
forall a. Parser a -> InfoMod a -> ParserInfo a
Opt.info Parser LegacyGenesisCmds
pGenesisUTxOKeyGen (InfoMod LegacyGenesisCmds -> ParserInfo LegacyGenesisCmds)
-> InfoMod LegacyGenesisCmds -> ParserInfo LegacyGenesisCmds
forall a b. (a -> b) -> a -> b
$
String -> InfoMod LegacyGenesisCmds
forall a. String -> InfoMod a
Opt.progDesc String
"Create a Shelley genesis UTxO key pair"
, Mod CommandFields LegacyGenesisCmds -> Parser LegacyGenesisCmds
forall a. Mod CommandFields a -> Parser a
Opt.hsubparser (Mod CommandFields LegacyGenesisCmds -> Parser LegacyGenesisCmds)
-> Mod CommandFields LegacyGenesisCmds -> Parser LegacyGenesisCmds
forall a b. (a -> b) -> a -> b
$
String
-> ParserInfo LegacyGenesisCmds
-> Mod CommandFields LegacyGenesisCmds
forall a. String -> ParserInfo a -> Mod CommandFields a
commandWithMetavar String
"key-hash" (ParserInfo LegacyGenesisCmds
-> Mod CommandFields LegacyGenesisCmds)
-> ParserInfo LegacyGenesisCmds
-> Mod CommandFields LegacyGenesisCmds
forall a b. (a -> b) -> a -> b
$
Parser LegacyGenesisCmds
-> InfoMod LegacyGenesisCmds -> ParserInfo LegacyGenesisCmds
forall a. Parser a -> InfoMod a -> ParserInfo a
Opt.info Parser LegacyGenesisCmds
pGenesisKeyHash (InfoMod LegacyGenesisCmds -> ParserInfo LegacyGenesisCmds)
-> InfoMod LegacyGenesisCmds -> ParserInfo LegacyGenesisCmds
forall a b. (a -> b) -> a -> b
$
String -> InfoMod LegacyGenesisCmds
forall a. String -> InfoMod a
Opt.progDesc String
"Print the identifier (hash) of a public key"
, Mod CommandFields LegacyGenesisCmds -> Parser LegacyGenesisCmds
forall a. Mod CommandFields a -> Parser a
Opt.hsubparser (Mod CommandFields LegacyGenesisCmds -> Parser LegacyGenesisCmds)
-> Mod CommandFields LegacyGenesisCmds -> Parser LegacyGenesisCmds
forall a b. (a -> b) -> a -> b
$
String
-> ParserInfo LegacyGenesisCmds
-> Mod CommandFields LegacyGenesisCmds
forall a. String -> ParserInfo a -> Mod CommandFields a
commandWithMetavar String
"get-ver-key" (ParserInfo LegacyGenesisCmds
-> Mod CommandFields LegacyGenesisCmds)
-> ParserInfo LegacyGenesisCmds
-> Mod CommandFields LegacyGenesisCmds
forall a b. (a -> b) -> a -> b
$
Parser LegacyGenesisCmds
-> InfoMod LegacyGenesisCmds -> ParserInfo LegacyGenesisCmds
forall a. Parser a -> InfoMod a -> ParserInfo a
Opt.info Parser LegacyGenesisCmds
pGenesisVerKey (InfoMod LegacyGenesisCmds -> ParserInfo LegacyGenesisCmds)
-> InfoMod LegacyGenesisCmds -> ParserInfo LegacyGenesisCmds
forall a b. (a -> b) -> a -> b
$
String -> InfoMod LegacyGenesisCmds
forall a. String -> InfoMod a
Opt.progDesc String
"Derive the verification key from a signing key"
, Mod CommandFields LegacyGenesisCmds -> Parser LegacyGenesisCmds
forall a. Mod CommandFields a -> Parser a
Opt.hsubparser (Mod CommandFields LegacyGenesisCmds -> Parser LegacyGenesisCmds)
-> Mod CommandFields LegacyGenesisCmds -> Parser LegacyGenesisCmds
forall a b. (a -> b) -> a -> b
$
String
-> ParserInfo LegacyGenesisCmds
-> Mod CommandFields LegacyGenesisCmds
forall a. String -> ParserInfo a -> Mod CommandFields a
commandWithMetavar String
"initial-addr" (ParserInfo LegacyGenesisCmds
-> Mod CommandFields LegacyGenesisCmds)
-> ParserInfo LegacyGenesisCmds
-> Mod CommandFields LegacyGenesisCmds
forall a b. (a -> b) -> a -> b
$
Parser LegacyGenesisCmds
-> InfoMod LegacyGenesisCmds -> ParserInfo LegacyGenesisCmds
forall a. Parser a -> InfoMod a -> ParserInfo a
Opt.info Parser LegacyGenesisCmds
pGenesisAddr (InfoMod LegacyGenesisCmds -> ParserInfo LegacyGenesisCmds)
-> InfoMod LegacyGenesisCmds -> ParserInfo LegacyGenesisCmds
forall a b. (a -> b) -> a -> b
$
String -> InfoMod LegacyGenesisCmds
forall a. String -> InfoMod a
Opt.progDesc String
"Get the address for an initial UTxO based on the verification key"
, Mod CommandFields LegacyGenesisCmds -> Parser LegacyGenesisCmds
forall a. Mod CommandFields a -> Parser a
Opt.hsubparser (Mod CommandFields LegacyGenesisCmds -> Parser LegacyGenesisCmds)
-> Mod CommandFields LegacyGenesisCmds -> Parser LegacyGenesisCmds
forall a b. (a -> b) -> a -> b
$
String
-> ParserInfo LegacyGenesisCmds
-> Mod CommandFields LegacyGenesisCmds
forall a. String -> ParserInfo a -> Mod CommandFields a
commandWithMetavar String
"initial-txin" (ParserInfo LegacyGenesisCmds
-> Mod CommandFields LegacyGenesisCmds)
-> ParserInfo LegacyGenesisCmds
-> Mod CommandFields LegacyGenesisCmds
forall a b. (a -> b) -> a -> b
$
Parser LegacyGenesisCmds
-> InfoMod LegacyGenesisCmds -> ParserInfo LegacyGenesisCmds
forall a. Parser a -> InfoMod a -> ParserInfo a
Opt.info Parser LegacyGenesisCmds
pGenesisTxIn (InfoMod LegacyGenesisCmds -> ParserInfo LegacyGenesisCmds)
-> InfoMod LegacyGenesisCmds -> ParserInfo LegacyGenesisCmds
forall a b. (a -> b) -> a -> b
$
String -> InfoMod LegacyGenesisCmds
forall a. String -> InfoMod a
Opt.progDesc String
"Get the TxIn for an initial UTxO based on the verification key"
, Mod CommandFields LegacyGenesisCmds -> Parser LegacyGenesisCmds
forall a. Mod CommandFields a -> Parser a
Opt.hsubparser (Mod CommandFields LegacyGenesisCmds -> Parser LegacyGenesisCmds)
-> Mod CommandFields LegacyGenesisCmds -> Parser LegacyGenesisCmds
forall a b. (a -> b) -> a -> b
$
String
-> ParserInfo LegacyGenesisCmds
-> Mod CommandFields LegacyGenesisCmds
forall a. String -> ParserInfo a -> Mod CommandFields a
commandWithMetavar String
"create-cardano" (ParserInfo LegacyGenesisCmds
-> Mod CommandFields LegacyGenesisCmds)
-> ParserInfo LegacyGenesisCmds
-> Mod CommandFields LegacyGenesisCmds
forall a b. (a -> b) -> a -> b
$
Parser LegacyGenesisCmds
-> InfoMod LegacyGenesisCmds -> ParserInfo LegacyGenesisCmds
forall a. Parser a -> InfoMod a -> ParserInfo a
Opt.info Parser LegacyGenesisCmds
pGenesisCreateCardano (InfoMod LegacyGenesisCmds -> ParserInfo LegacyGenesisCmds)
-> InfoMod LegacyGenesisCmds -> ParserInfo LegacyGenesisCmds
forall a b. (a -> b) -> a -> b
$
String -> InfoMod LegacyGenesisCmds
forall a. String -> InfoMod a
Opt.progDesc (String -> InfoMod LegacyGenesisCmds)
-> String -> InfoMod LegacyGenesisCmds
forall a b. (a -> b) -> a -> b
$
[String] -> String
forall a. Monoid a => [a] -> a
mconcat
[ String
"Create a Byron and Shelley genesis file from a genesis "
, String
"template and genesis/delegation/spending keys."
]
, Mod CommandFields LegacyGenesisCmds -> Parser LegacyGenesisCmds
forall a. Mod CommandFields a -> Parser a
Opt.hsubparser (Mod CommandFields LegacyGenesisCmds -> Parser LegacyGenesisCmds)
-> Mod CommandFields LegacyGenesisCmds -> Parser LegacyGenesisCmds
forall a b. (a -> b) -> a -> b
$
String
-> ParserInfo LegacyGenesisCmds
-> Mod CommandFields LegacyGenesisCmds
forall a. String -> ParserInfo a -> Mod CommandFields a
commandWithMetavar String
"create" (ParserInfo LegacyGenesisCmds
-> Mod CommandFields LegacyGenesisCmds)
-> ParserInfo LegacyGenesisCmds
-> Mod CommandFields LegacyGenesisCmds
forall a b. (a -> b) -> a -> b
$
Parser LegacyGenesisCmds
-> InfoMod LegacyGenesisCmds -> ParserInfo LegacyGenesisCmds
forall a. Parser a -> InfoMod a -> ParserInfo a
Opt.info Parser LegacyGenesisCmds
pGenesisCreate (InfoMod LegacyGenesisCmds -> ParserInfo LegacyGenesisCmds)
-> InfoMod LegacyGenesisCmds -> ParserInfo LegacyGenesisCmds
forall a b. (a -> b) -> a -> b
$
String -> InfoMod LegacyGenesisCmds
forall a. String -> InfoMod a
Opt.progDesc (String -> InfoMod LegacyGenesisCmds)
-> String -> InfoMod LegacyGenesisCmds
forall a b. (a -> b) -> a -> b
$
[String] -> String
forall a. Monoid a => [a] -> a
mconcat
[ String
"Create a Shelley genesis file from a genesis "
, String
"template and genesis/delegation/spending keys."
]
, Mod CommandFields LegacyGenesisCmds -> Parser LegacyGenesisCmds
forall a. Mod CommandFields a -> Parser a
Opt.hsubparser (Mod CommandFields LegacyGenesisCmds -> Parser LegacyGenesisCmds)
-> Mod CommandFields LegacyGenesisCmds -> Parser LegacyGenesisCmds
forall a b. (a -> b) -> a -> b
$
String
-> ParserInfo LegacyGenesisCmds
-> Mod CommandFields LegacyGenesisCmds
forall a. String -> ParserInfo a -> Mod CommandFields a
commandWithMetavar String
"create-staked" (ParserInfo LegacyGenesisCmds
-> Mod CommandFields LegacyGenesisCmds)
-> ParserInfo LegacyGenesisCmds
-> Mod CommandFields LegacyGenesisCmds
forall a b. (a -> b) -> a -> b
$
Parser LegacyGenesisCmds
-> InfoMod LegacyGenesisCmds -> ParserInfo LegacyGenesisCmds
forall a. Parser a -> InfoMod a -> ParserInfo a
Opt.info Parser LegacyGenesisCmds
pGenesisCreateStaked (InfoMod LegacyGenesisCmds -> ParserInfo LegacyGenesisCmds)
-> InfoMod LegacyGenesisCmds -> ParserInfo LegacyGenesisCmds
forall a b. (a -> b) -> a -> b
$
String -> InfoMod LegacyGenesisCmds
forall a. String -> InfoMod a
Opt.progDesc (String -> InfoMod LegacyGenesisCmds)
-> String -> InfoMod LegacyGenesisCmds
forall a b. (a -> b) -> a -> b
$
[String] -> String
forall a. Monoid a => [a] -> a
mconcat
[ String
"Create a staked Shelley genesis file from a genesis "
, String
"template and genesis/delegation/spending keys."
]
, Mod CommandFields LegacyGenesisCmds -> Parser LegacyGenesisCmds
forall a. Mod CommandFields a -> Parser a
Opt.hsubparser (Mod CommandFields LegacyGenesisCmds -> Parser LegacyGenesisCmds)
-> Mod CommandFields LegacyGenesisCmds -> Parser LegacyGenesisCmds
forall a b. (a -> b) -> a -> b
$
String
-> ParserInfo LegacyGenesisCmds
-> Mod CommandFields LegacyGenesisCmds
forall a. String -> ParserInfo a -> Mod CommandFields a
commandWithMetavar String
"hash" (ParserInfo LegacyGenesisCmds
-> Mod CommandFields LegacyGenesisCmds)
-> ParserInfo LegacyGenesisCmds
-> Mod CommandFields LegacyGenesisCmds
forall a b. (a -> b) -> a -> b
$
Parser LegacyGenesisCmds
-> InfoMod LegacyGenesisCmds -> ParserInfo LegacyGenesisCmds
forall a. Parser a -> InfoMod a -> ParserInfo a
Opt.info Parser LegacyGenesisCmds
pGenesisHash (InfoMod LegacyGenesisCmds -> ParserInfo LegacyGenesisCmds)
-> InfoMod LegacyGenesisCmds -> ParserInfo LegacyGenesisCmds
forall a b. (a -> b) -> a -> b
$
String -> InfoMod LegacyGenesisCmds
forall a. String -> InfoMod a
Opt.progDesc (String -> InfoMod LegacyGenesisCmds)
-> String -> InfoMod LegacyGenesisCmds
forall a b. (a -> b) -> a -> b
$
[String] -> String
unlines
[ String
"DEPRECATION WARNING! This command is deprecated and will be "
, String
"removed in a future release. Please use hash genesis-file "
, String
"instead. "
, String
"Compute the hash of a genesis file."
]
]
where
pGenesisKeyGen :: Parser LegacyGenesisCmds
pGenesisKeyGen :: Parser LegacyGenesisCmds
pGenesisKeyGen =
VerificationKeyFile 'Out
-> SigningKeyFile 'Out -> LegacyGenesisCmds
GenesisKeyGenGenesis
(VerificationKeyFile 'Out
-> SigningKeyFile 'Out -> LegacyGenesisCmds)
-> Parser (VerificationKeyFile 'Out)
-> Parser (SigningKeyFile 'Out -> LegacyGenesisCmds)
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> Parser (VerificationKeyFile 'Out)
forall keyrole. Parser (File (VerificationKey keyrole) 'Out)
pVerificationKeyFileOut
Parser (SigningKeyFile 'Out -> LegacyGenesisCmds)
-> Parser (SigningKeyFile 'Out) -> Parser LegacyGenesisCmds
forall a b. Parser (a -> b) -> Parser a -> Parser b
forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
<*> Parser (SigningKeyFile 'Out)
forall keyrole. Parser (File (SigningKey keyrole) 'Out)
pSigningKeyFileOut
pGenesisDelegateKeyGen :: Parser LegacyGenesisCmds
pGenesisDelegateKeyGen :: Parser LegacyGenesisCmds
pGenesisDelegateKeyGen =
VerificationKeyFile 'Out
-> SigningKeyFile 'Out
-> OpCertCounterFile 'Out
-> LegacyGenesisCmds
GenesisKeyGenDelegate
(VerificationKeyFile 'Out
-> SigningKeyFile 'Out
-> OpCertCounterFile 'Out
-> LegacyGenesisCmds)
-> Parser (VerificationKeyFile 'Out)
-> Parser
(SigningKeyFile 'Out
-> OpCertCounterFile 'Out -> LegacyGenesisCmds)
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> Parser (VerificationKeyFile 'Out)
forall keyrole. Parser (File (VerificationKey keyrole) 'Out)
pVerificationKeyFileOut
Parser
(SigningKeyFile 'Out
-> OpCertCounterFile 'Out -> LegacyGenesisCmds)
-> Parser (SigningKeyFile 'Out)
-> Parser (OpCertCounterFile 'Out -> LegacyGenesisCmds)
forall a b. Parser (a -> b) -> Parser a -> Parser b
forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
<*> Parser (SigningKeyFile 'Out)
forall keyrole. Parser (File (SigningKey keyrole) 'Out)
pSigningKeyFileOut
Parser (OpCertCounterFile 'Out -> LegacyGenesisCmds)
-> Parser (OpCertCounterFile 'Out) -> Parser LegacyGenesisCmds
forall a b. Parser (a -> b) -> Parser a -> Parser b
forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
<*> Parser (OpCertCounterFile 'Out)
forall (direction :: FileDirection).
Parser (File OpCertCounter direction)
pOperatorCertIssueCounterFile
pGenesisUTxOKeyGen :: Parser LegacyGenesisCmds
pGenesisUTxOKeyGen :: Parser LegacyGenesisCmds
pGenesisUTxOKeyGen =
VerificationKeyFile 'Out
-> SigningKeyFile 'Out -> LegacyGenesisCmds
GenesisKeyGenUTxO
(VerificationKeyFile 'Out
-> SigningKeyFile 'Out -> LegacyGenesisCmds)
-> Parser (VerificationKeyFile 'Out)
-> Parser (SigningKeyFile 'Out -> LegacyGenesisCmds)
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> Parser (VerificationKeyFile 'Out)
forall keyrole. Parser (File (VerificationKey keyrole) 'Out)
pVerificationKeyFileOut
Parser (SigningKeyFile 'Out -> LegacyGenesisCmds)
-> Parser (SigningKeyFile 'Out) -> Parser LegacyGenesisCmds
forall a b. Parser (a -> b) -> Parser a -> Parser b
forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
<*> Parser (SigningKeyFile 'Out)
forall keyrole. Parser (File (SigningKey keyrole) 'Out)
pSigningKeyFileOut
pGenesisKeyHash :: Parser LegacyGenesisCmds
pGenesisKeyHash :: Parser LegacyGenesisCmds
pGenesisKeyHash =
VerificationKeyFile 'In -> LegacyGenesisCmds
GenesisCmdKeyHash
(VerificationKeyFile 'In -> LegacyGenesisCmds)
-> Parser (VerificationKeyFile 'In) -> Parser LegacyGenesisCmds
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> Parser (VerificationKeyFile 'In)
pVerificationKeyFileIn
pGenesisVerKey :: Parser LegacyGenesisCmds
pGenesisVerKey :: Parser LegacyGenesisCmds
pGenesisVerKey =
VerificationKeyFile 'Out -> SigningKeyFile 'In -> LegacyGenesisCmds
GenesisVerKey
(VerificationKeyFile 'Out
-> SigningKeyFile 'In -> LegacyGenesisCmds)
-> Parser (VerificationKeyFile 'Out)
-> Parser (SigningKeyFile 'In -> LegacyGenesisCmds)
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> Parser (VerificationKeyFile 'Out)
forall keyrole. Parser (File (VerificationKey keyrole) 'Out)
pVerificationKeyFileOut
Parser (SigningKeyFile 'In -> LegacyGenesisCmds)
-> Parser (SigningKeyFile 'In) -> Parser LegacyGenesisCmds
forall a b. Parser (a -> b) -> Parser a -> Parser b
forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
<*> Parser (SigningKeyFile 'In)
pSigningKeyFileIn
pGenesisAddr :: Parser LegacyGenesisCmds
pGenesisAddr :: Parser LegacyGenesisCmds
pGenesisAddr =
VerificationKeyFile 'In
-> NetworkId -> Maybe (File () 'Out) -> LegacyGenesisCmds
GenesisAddr
(VerificationKeyFile 'In
-> NetworkId -> Maybe (File () 'Out) -> LegacyGenesisCmds)
-> Parser (VerificationKeyFile 'In)
-> Parser (NetworkId -> Maybe (File () 'Out) -> LegacyGenesisCmds)
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> Parser (VerificationKeyFile 'In)
pVerificationKeyFileIn
Parser (NetworkId -> Maybe (File () 'Out) -> LegacyGenesisCmds)
-> Parser NetworkId
-> Parser (Maybe (File () 'Out) -> LegacyGenesisCmds)
forall a b. Parser (a -> b) -> Parser a -> Parser b
forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
<*> EnvCli -> Parser NetworkId
pNetworkId EnvCli
envCli
Parser (Maybe (File () 'Out) -> LegacyGenesisCmds)
-> Parser (Maybe (File () 'Out)) -> Parser LegacyGenesisCmds
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 (File () 'Out))
forall content. Parser (Maybe (File content 'Out))
pMaybeOutputFile
pGenesisTxIn :: Parser LegacyGenesisCmds
pGenesisTxIn :: Parser LegacyGenesisCmds
pGenesisTxIn =
VerificationKeyFile 'In
-> NetworkId -> Maybe (File () 'Out) -> LegacyGenesisCmds
GenesisTxIn
(VerificationKeyFile 'In
-> NetworkId -> Maybe (File () 'Out) -> LegacyGenesisCmds)
-> Parser (VerificationKeyFile 'In)
-> Parser (NetworkId -> Maybe (File () 'Out) -> LegacyGenesisCmds)
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> Parser (VerificationKeyFile 'In)
pVerificationKeyFileIn
Parser (NetworkId -> Maybe (File () 'Out) -> LegacyGenesisCmds)
-> Parser NetworkId
-> Parser (Maybe (File () 'Out) -> LegacyGenesisCmds)
forall a b. Parser (a -> b) -> Parser a -> Parser b
forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
<*> EnvCli -> Parser NetworkId
pNetworkId EnvCli
envCli
Parser (Maybe (File () 'Out) -> LegacyGenesisCmds)
-> Parser (Maybe (File () 'Out)) -> Parser LegacyGenesisCmds
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 (File () 'Out))
forall content. Parser (Maybe (File content 'Out))
pMaybeOutputFile
pGenesisCreateCardano :: Parser LegacyGenesisCmds
pGenesisCreateCardano :: Parser LegacyGenesisCmds
pGenesisCreateCardano =
Era ConwayEra
-> GenesisDir
-> Word
-> Word
-> Maybe SystemStart
-> Maybe Coin
-> NonZero Word64
-> Word
-> Rational
-> NetworkId
-> String
-> String
-> String
-> String
-> Maybe String
-> LegacyGenesisCmds
forall era.
Era era
-> GenesisDir
-> Word
-> Word
-> Maybe SystemStart
-> Maybe Coin
-> NonZero Word64
-> Word
-> Rational
-> NetworkId
-> String
-> String
-> String
-> String
-> Maybe String
-> LegacyGenesisCmds
GenesisCreateCardano
(Era ConwayEra
-> GenesisDir
-> Word
-> Word
-> Maybe SystemStart
-> Maybe Coin
-> NonZero Word64
-> Word
-> Rational
-> NetworkId
-> String
-> String
-> String
-> String
-> Maybe String
-> LegacyGenesisCmds)
-> Parser (Era ConwayEra)
-> Parser
(GenesisDir
-> Word
-> Word
-> Maybe SystemStart
-> Maybe Coin
-> NonZero Word64
-> Word
-> Rational
-> NetworkId
-> String
-> String
-> String
-> String
-> Maybe String
-> LegacyGenesisCmds)
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> EnvCli -> Parser (Era ConwayEra)
pConwayEra EnvCli
envCli
Parser
(GenesisDir
-> Word
-> Word
-> Maybe SystemStart
-> Maybe Coin
-> NonZero Word64
-> Word
-> Rational
-> NetworkId
-> String
-> String
-> String
-> String
-> Maybe String
-> LegacyGenesisCmds)
-> Parser GenesisDir
-> Parser
(Word
-> Word
-> Maybe SystemStart
-> Maybe Coin
-> NonZero Word64
-> Word
-> Rational
-> NetworkId
-> String
-> String
-> String
-> String
-> Maybe String
-> LegacyGenesisCmds)
forall a b. Parser (a -> b) -> Parser a -> Parser b
forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
<*> Parser GenesisDir
pGenesisDir
Parser
(Word
-> Word
-> Maybe SystemStart
-> Maybe Coin
-> NonZero Word64
-> Word
-> Rational
-> NetworkId
-> String
-> String
-> String
-> String
-> Maybe String
-> LegacyGenesisCmds)
-> Parser Word
-> Parser
(Word
-> Maybe SystemStart
-> Maybe Coin
-> NonZero Word64
-> Word
-> Rational
-> NetworkId
-> String
-> String
-> String
-> String
-> Maybe String
-> LegacyGenesisCmds)
forall a b. Parser (a -> b) -> Parser a -> Parser b
forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
<*> Parser Word
pGenesisNumGenesisKeys
Parser
(Word
-> Maybe SystemStart
-> Maybe Coin
-> NonZero Word64
-> Word
-> Rational
-> NetworkId
-> String
-> String
-> String
-> String
-> Maybe String
-> LegacyGenesisCmds)
-> Parser Word
-> Parser
(Maybe SystemStart
-> Maybe Coin
-> NonZero Word64
-> Word
-> Rational
-> NetworkId
-> String
-> String
-> String
-> String
-> Maybe String
-> LegacyGenesisCmds)
forall a b. Parser (a -> b) -> Parser a -> Parser b
forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
<*> Parser Word
pGenesisNumUTxOKeys
Parser
(Maybe SystemStart
-> Maybe Coin
-> NonZero Word64
-> Word
-> Rational
-> NetworkId
-> String
-> String
-> String
-> String
-> Maybe String
-> LegacyGenesisCmds)
-> Parser (Maybe SystemStart)
-> Parser
(Maybe Coin
-> NonZero Word64
-> Word
-> Rational
-> NetworkId
-> String
-> String
-> String
-> String
-> Maybe String
-> LegacyGenesisCmds)
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 SystemStart)
pMaybeSystemStart
Parser
(Maybe Coin
-> NonZero Word64
-> Word
-> Rational
-> NetworkId
-> String
-> String
-> String
-> String
-> Maybe String
-> LegacyGenesisCmds)
-> Parser (Maybe Coin)
-> Parser
(NonZero Word64
-> Word
-> Rational
-> NetworkId
-> String
-> String
-> String
-> String
-> Maybe String
-> LegacyGenesisCmds)
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 Coin)
pInitialSupplyNonDelegated
Parser
(NonZero Word64
-> Word
-> Rational
-> NetworkId
-> String
-> String
-> String
-> String
-> Maybe String
-> LegacyGenesisCmds)
-> Parser (NonZero Word64)
-> Parser
(Word
-> Rational
-> NetworkId
-> String
-> String
-> String
-> String
-> Maybe String
-> LegacyGenesisCmds)
forall a b. Parser (a -> b) -> Parser a -> Parser b
forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
<*> Parser (NonZero Word64)
pSecurityParam
Parser
(Word
-> Rational
-> NetworkId
-> String
-> String
-> String
-> String
-> Maybe String
-> LegacyGenesisCmds)
-> Parser Word
-> Parser
(Rational
-> NetworkId
-> String
-> String
-> String
-> String
-> Maybe String
-> LegacyGenesisCmds)
forall a b. Parser (a -> b) -> Parser a -> Parser b
forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
<*> Parser Word
pSlotLength
Parser
(Rational
-> NetworkId
-> String
-> String
-> String
-> String
-> Maybe String
-> LegacyGenesisCmds)
-> Parser Rational
-> Parser
(NetworkId
-> String
-> String
-> String
-> String
-> Maybe String
-> LegacyGenesisCmds)
forall a b. Parser (a -> b) -> Parser a -> Parser b
forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
<*> Parser Rational
pSlotCoefficient
Parser
(NetworkId
-> String
-> String
-> String
-> String
-> Maybe String
-> LegacyGenesisCmds)
-> Parser NetworkId
-> Parser
(String
-> String -> String -> String -> Maybe String -> LegacyGenesisCmds)
forall a b. Parser (a -> b) -> Parser a -> Parser b
forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
<*> EnvCli -> Parser NetworkId
pNetworkId EnvCli
envCli
Parser
(String
-> String -> String -> String -> Maybe String -> LegacyGenesisCmds)
-> Parser String
-> Parser
(String -> String -> String -> Maybe String -> LegacyGenesisCmds)
forall a b. Parser (a -> b) -> Parser a -> Parser b
forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
<*> String -> String -> Parser String
parseFilePath
String
"byron-template"
String
"JSON file with genesis defaults for each byron."
Parser
(String -> String -> String -> Maybe String -> LegacyGenesisCmds)
-> Parser String
-> Parser (String -> String -> Maybe String -> LegacyGenesisCmds)
forall a b. Parser (a -> b) -> Parser a -> Parser b
forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
<*> String -> String -> Parser String
parseFilePath
String
"shelley-template"
String
"JSON file with genesis defaults for each shelley."
Parser (String -> String -> Maybe String -> LegacyGenesisCmds)
-> Parser String
-> Parser (String -> Maybe String -> LegacyGenesisCmds)
forall a b. Parser (a -> b) -> Parser a -> Parser b
forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
<*> String -> String -> Parser String
parseFilePath
String
"alonzo-template"
String
"JSON file with genesis defaults for alonzo."
Parser (String -> Maybe String -> LegacyGenesisCmds)
-> Parser String -> Parser (Maybe String -> LegacyGenesisCmds)
forall a b. Parser (a -> b) -> Parser a -> Parser b
forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
<*> String -> String -> Parser String
parseFilePath
String
"conway-template"
String
"JSON file with genesis defaults for conway."
Parser (Maybe String -> LegacyGenesisCmds)
-> Parser (Maybe String) -> Parser LegacyGenesisCmds
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 String)
pNodeConfigTemplate
pGenesisCreate :: Parser LegacyGenesisCmds
pGenesisCreate :: Parser LegacyGenesisCmds
pGenesisCreate =
AnyShelleyBasedEra
-> Vary '[FormatBech32, FormatTextEnvelope]
-> GenesisDir
-> Word
-> Word
-> Maybe SystemStart
-> Maybe Coin
-> NetworkId
-> LegacyGenesisCmds
GenesisCreate
(AnyShelleyBasedEra
-> Vary '[FormatBech32, FormatTextEnvelope]
-> GenesisDir
-> Word
-> Word
-> Maybe SystemStart
-> Maybe Coin
-> NetworkId
-> LegacyGenesisCmds)
-> Parser AnyShelleyBasedEra
-> Parser
(Vary '[FormatBech32, FormatTextEnvelope]
-> GenesisDir
-> Word
-> Word
-> Maybe SystemStart
-> Maybe Coin
-> NetworkId
-> LegacyGenesisCmds)
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> EnvCli -> Parser AnyShelleyBasedEra
pShelleyBasedEra EnvCli
envCli
Parser
(Vary '[FormatBech32, FormatTextEnvelope]
-> GenesisDir
-> Word
-> Word
-> Maybe SystemStart
-> Maybe Coin
-> NetworkId
-> LegacyGenesisCmds)
-> Parser (Vary '[FormatBech32, FormatTextEnvelope])
-> Parser
(GenesisDir
-> Word
-> Word
-> Maybe SystemStart
-> Maybe Coin
-> NetworkId
-> LegacyGenesisCmds)
forall a b. Parser (a -> b) -> Parser a -> Parser b
forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
<*> Parser (Vary '[FormatBech32, FormatTextEnvelope])
pKeyOutputFormat
Parser
(GenesisDir
-> Word
-> Word
-> Maybe SystemStart
-> Maybe Coin
-> NetworkId
-> LegacyGenesisCmds)
-> Parser GenesisDir
-> Parser
(Word
-> Word
-> Maybe SystemStart
-> Maybe Coin
-> NetworkId
-> LegacyGenesisCmds)
forall a b. Parser (a -> b) -> Parser a -> Parser b
forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
<*> Parser GenesisDir
pGenesisDir
Parser
(Word
-> Word
-> Maybe SystemStart
-> Maybe Coin
-> NetworkId
-> LegacyGenesisCmds)
-> Parser Word
-> Parser
(Word
-> Maybe SystemStart
-> Maybe Coin
-> NetworkId
-> LegacyGenesisCmds)
forall a b. Parser (a -> b) -> Parser a -> Parser b
forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
<*> Parser Word
pGenesisNumGenesisKeys
Parser
(Word
-> Maybe SystemStart
-> Maybe Coin
-> NetworkId
-> LegacyGenesisCmds)
-> Parser Word
-> Parser
(Maybe SystemStart -> Maybe Coin -> NetworkId -> LegacyGenesisCmds)
forall a b. Parser (a -> b) -> Parser a -> Parser b
forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
<*> Parser Word
pGenesisNumUTxOKeys
Parser
(Maybe SystemStart -> Maybe Coin -> NetworkId -> LegacyGenesisCmds)
-> Parser (Maybe SystemStart)
-> Parser (Maybe Coin -> NetworkId -> LegacyGenesisCmds)
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 SystemStart)
pMaybeSystemStart
Parser (Maybe Coin -> NetworkId -> LegacyGenesisCmds)
-> Parser (Maybe Coin) -> Parser (NetworkId -> LegacyGenesisCmds)
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 Coin)
pInitialSupplyNonDelegated
Parser (NetworkId -> LegacyGenesisCmds)
-> Parser NetworkId -> Parser LegacyGenesisCmds
forall a b. Parser (a -> b) -> Parser a -> Parser b
forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
<*> EnvCli -> Parser NetworkId
pNetworkId EnvCli
envCli
pGenesisCreateStaked :: Parser LegacyGenesisCmds
pGenesisCreateStaked :: Parser LegacyGenesisCmds
pGenesisCreateStaked =
Era ConwayEra
-> Vary '[FormatBech32, FormatTextEnvelope]
-> GenesisDir
-> Word
-> Word
-> Word
-> Word
-> Maybe SystemStart
-> Maybe Coin
-> Coin
-> NetworkId
-> Word
-> Word
-> Word
-> Maybe String
-> LegacyGenesisCmds
forall era.
Era era
-> Vary '[FormatBech32, FormatTextEnvelope]
-> GenesisDir
-> Word
-> Word
-> Word
-> Word
-> Maybe SystemStart
-> Maybe Coin
-> Coin
-> NetworkId
-> Word
-> Word
-> Word
-> Maybe String
-> LegacyGenesisCmds
GenesisCreateStaked
(Era ConwayEra
-> Vary '[FormatBech32, FormatTextEnvelope]
-> GenesisDir
-> Word
-> Word
-> Word
-> Word
-> Maybe SystemStart
-> Maybe Coin
-> Coin
-> NetworkId
-> Word
-> Word
-> Word
-> Maybe String
-> LegacyGenesisCmds)
-> Parser (Era ConwayEra)
-> Parser
(Vary '[FormatBech32, FormatTextEnvelope]
-> GenesisDir
-> Word
-> Word
-> Word
-> Word
-> Maybe SystemStart
-> Maybe Coin
-> Coin
-> NetworkId
-> Word
-> Word
-> Word
-> Maybe String
-> LegacyGenesisCmds)
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> EnvCli -> Parser (Era ConwayEra)
pConwayEra EnvCli
envCli
Parser
(Vary '[FormatBech32, FormatTextEnvelope]
-> GenesisDir
-> Word
-> Word
-> Word
-> Word
-> Maybe SystemStart
-> Maybe Coin
-> Coin
-> NetworkId
-> Word
-> Word
-> Word
-> Maybe String
-> LegacyGenesisCmds)
-> Parser (Vary '[FormatBech32, FormatTextEnvelope])
-> Parser
(GenesisDir
-> Word
-> Word
-> Word
-> Word
-> Maybe SystemStart
-> Maybe Coin
-> Coin
-> NetworkId
-> Word
-> Word
-> Word
-> Maybe String
-> LegacyGenesisCmds)
forall a b. Parser (a -> b) -> Parser a -> Parser b
forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
<*> Parser (Vary '[FormatBech32, FormatTextEnvelope])
pKeyOutputFormat
Parser
(GenesisDir
-> Word
-> Word
-> Word
-> Word
-> Maybe SystemStart
-> Maybe Coin
-> Coin
-> NetworkId
-> Word
-> Word
-> Word
-> Maybe String
-> LegacyGenesisCmds)
-> Parser GenesisDir
-> Parser
(Word
-> Word
-> Word
-> Word
-> Maybe SystemStart
-> Maybe Coin
-> Coin
-> NetworkId
-> Word
-> Word
-> Word
-> Maybe String
-> LegacyGenesisCmds)
forall a b. Parser (a -> b) -> Parser a -> Parser b
forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
<*> Parser GenesisDir
pGenesisDir
Parser
(Word
-> Word
-> Word
-> Word
-> Maybe SystemStart
-> Maybe Coin
-> Coin
-> NetworkId
-> Word
-> Word
-> Word
-> Maybe String
-> LegacyGenesisCmds)
-> Parser Word
-> Parser
(Word
-> Word
-> Word
-> Maybe SystemStart
-> Maybe Coin
-> Coin
-> NetworkId
-> Word
-> Word
-> Word
-> Maybe String
-> LegacyGenesisCmds)
forall a b. Parser (a -> b) -> Parser a -> Parser b
forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
<*> Parser Word
pGenesisNumGenesisKeys
Parser
(Word
-> Word
-> Word
-> Maybe SystemStart
-> Maybe Coin
-> Coin
-> NetworkId
-> Word
-> Word
-> Word
-> Maybe String
-> LegacyGenesisCmds)
-> Parser Word
-> Parser
(Word
-> Word
-> Maybe SystemStart
-> Maybe Coin
-> Coin
-> NetworkId
-> Word
-> Word
-> Word
-> Maybe String
-> LegacyGenesisCmds)
forall a b. Parser (a -> b) -> Parser a -> Parser b
forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
<*> Parser Word
pGenesisNumUTxOKeys
Parser
(Word
-> Word
-> Maybe SystemStart
-> Maybe Coin
-> Coin
-> NetworkId
-> Word
-> Word
-> Word
-> Maybe String
-> LegacyGenesisCmds)
-> Parser Word
-> Parser
(Word
-> Maybe SystemStart
-> Maybe Coin
-> Coin
-> NetworkId
-> Word
-> Word
-> Word
-> Maybe String
-> LegacyGenesisCmds)
forall a b. Parser (a -> b) -> Parser a -> Parser b
forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
<*> Parser Word
pGenesisNumPools
Parser
(Word
-> Maybe SystemStart
-> Maybe Coin
-> Coin
-> NetworkId
-> Word
-> Word
-> Word
-> Maybe String
-> LegacyGenesisCmds)
-> Parser Word
-> Parser
(Maybe SystemStart
-> Maybe Coin
-> Coin
-> NetworkId
-> Word
-> Word
-> Word
-> Maybe String
-> LegacyGenesisCmds)
forall a b. Parser (a -> b) -> Parser a -> Parser b
forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
<*> Parser Word
pGenesisNumStDelegs
Parser
(Maybe SystemStart
-> Maybe Coin
-> Coin
-> NetworkId
-> Word
-> Word
-> Word
-> Maybe String
-> LegacyGenesisCmds)
-> Parser (Maybe SystemStart)
-> Parser
(Maybe Coin
-> Coin
-> NetworkId
-> Word
-> Word
-> Word
-> Maybe String
-> LegacyGenesisCmds)
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 SystemStart)
pMaybeSystemStart
Parser
(Maybe Coin
-> Coin
-> NetworkId
-> Word
-> Word
-> Word
-> Maybe String
-> LegacyGenesisCmds)
-> Parser (Maybe Coin)
-> Parser
(Coin
-> NetworkId
-> Word
-> Word
-> Word
-> Maybe String
-> LegacyGenesisCmds)
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 Coin)
pInitialSupplyNonDelegated
Parser
(Coin
-> NetworkId
-> Word
-> Word
-> Word
-> Maybe String
-> LegacyGenesisCmds)
-> Parser Coin
-> Parser
(NetworkId
-> Word -> Word -> Word -> Maybe String -> LegacyGenesisCmds)
forall a b. Parser (a -> b) -> Parser a -> Parser b
forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
<*> Parser Coin
pInitialSupplyDelegated
Parser
(NetworkId
-> Word -> Word -> Word -> Maybe String -> LegacyGenesisCmds)
-> Parser NetworkId
-> Parser
(Word -> Word -> Word -> Maybe String -> LegacyGenesisCmds)
forall a b. Parser (a -> b) -> Parser a -> Parser b
forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
<*> EnvCli -> Parser NetworkId
pNetworkId EnvCli
envCli
Parser (Word -> Word -> Word -> Maybe String -> LegacyGenesisCmds)
-> Parser Word
-> Parser (Word -> Word -> Maybe String -> LegacyGenesisCmds)
forall a b. Parser (a -> b) -> Parser a -> Parser b
forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
<*> Parser Word
pBulkPoolCredFiles
Parser (Word -> Word -> Maybe String -> LegacyGenesisCmds)
-> Parser Word
-> Parser (Word -> Maybe String -> LegacyGenesisCmds)
forall a b. Parser (a -> b) -> Parser a -> Parser b
forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
<*> Parser Word
pBulkPoolsPerFile
Parser (Word -> Maybe String -> LegacyGenesisCmds)
-> Parser Word -> Parser (Maybe String -> LegacyGenesisCmds)
forall a b. Parser (a -> b) -> Parser a -> Parser b
forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
<*> Parser Word
pStuffedUtxoCount
Parser (Maybe String -> LegacyGenesisCmds)
-> Parser (Maybe String) -> Parser LegacyGenesisCmds
forall a b. Parser (a -> b) -> Parser a -> Parser b
forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
<*> Parser String -> Parser (Maybe String)
forall (f :: * -> *) a. Alternative f => f a -> f (Maybe a)
Opt.optional Parser String
pRelayJsonFp
pGenesisHash :: Parser LegacyGenesisCmds
pGenesisHash :: Parser LegacyGenesisCmds
pGenesisHash =
GenesisFile -> LegacyGenesisCmds
GenesisHashFile (GenesisFile -> LegacyGenesisCmds)
-> Parser GenesisFile -> Parser LegacyGenesisCmds
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> String -> Parser GenesisFile
pGenesisFile String
"The genesis file."
pGenesisDir :: Parser GenesisDir
pGenesisDir :: Parser GenesisDir
pGenesisDir =
(String -> GenesisDir) -> Parser String -> Parser GenesisDir
forall a b. (a -> b) -> Parser a -> Parser b
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
fmap String -> GenesisDir
GenesisDir (Parser String -> Parser GenesisDir)
-> Parser String -> Parser GenesisDir
forall a b. (a -> b) -> a -> b
$
Mod OptionFields String -> Parser String
forall s. IsString s => Mod OptionFields s -> Parser s
Opt.strOption (Mod OptionFields String -> Parser String)
-> Mod OptionFields String -> Parser String
forall a b. (a -> b) -> a -> b
$
[Mod OptionFields String] -> Mod OptionFields String
forall a. Monoid a => [a] -> a
mconcat
[ String -> Mod OptionFields String
forall (f :: * -> *) a. HasName f => String -> Mod f a
Opt.long String
"genesis-dir"
, String -> Mod OptionFields String
forall (f :: * -> *) a. HasMetavar f => String -> Mod f a
Opt.metavar String
"DIR"
, String -> Mod OptionFields String
forall (f :: * -> *) a. String -> Mod f a
Opt.help
String
"The genesis directory containing the genesis template and required genesis/delegation/spending keys."
]
pMaybeSystemStart :: Parser (Maybe SystemStart)
pMaybeSystemStart :: Parser (Maybe SystemStart)
pMaybeSystemStart =
Parser SystemStart -> Parser (Maybe SystemStart)
forall (f :: * -> *) a. Alternative f => f a -> f (Maybe a)
Opt.optional (Parser SystemStart -> Parser (Maybe SystemStart))
-> Parser SystemStart -> Parser (Maybe SystemStart)
forall a b. (a -> b) -> a -> b
$
(String -> SystemStart) -> Parser String -> Parser SystemStart
forall a b. (a -> b) -> Parser a -> Parser b
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
fmap (UTCTime -> SystemStart
SystemStart (UTCTime -> SystemStart)
-> (String -> UTCTime) -> String -> SystemStart
forall b c a. (b -> c) -> (a -> b) -> a -> c
. String -> UTCTime
convertTime) (Parser String -> Parser SystemStart)
-> Parser String -> Parser SystemStart
forall a b. (a -> b) -> a -> b
$
Mod OptionFields String -> Parser String
forall s. IsString s => Mod OptionFields s -> Parser s
Opt.strOption (Mod OptionFields String -> Parser String)
-> Mod OptionFields String -> Parser String
forall a b. (a -> b) -> a -> b
$
[Mod OptionFields String] -> Mod OptionFields String
forall a. Monoid a => [a] -> a
mconcat
[ String -> Mod OptionFields String
forall (f :: * -> *) a. HasName f => String -> Mod f a
Opt.long String
"start-time"
, String -> Mod OptionFields String
forall (f :: * -> *) a. HasMetavar f => String -> Mod f a
Opt.metavar String
"UTC_TIME"
, String -> Mod OptionFields String
forall (f :: * -> *) a. String -> Mod f a
Opt.help
String
"The genesis start time in YYYY-MM-DDThh:mm:ssZ format. If unspecified, will be the current time +30 seconds."
]
pGenesisNumGenesisKeys :: Parser Word
pGenesisNumGenesisKeys :: Parser Word
pGenesisNumGenesisKeys =
ReadM Word -> Mod OptionFields Word -> Parser Word
forall a. ReadM a -> Mod OptionFields a -> Parser a
Opt.option ReadM Word
forall a. (Typeable a, Integral a, Bits a) => ReadM a
integralReader (Mod OptionFields Word -> Parser Word)
-> Mod OptionFields Word -> Parser Word
forall a b. (a -> b) -> a -> b
$
[Mod OptionFields Word] -> Mod OptionFields Word
forall a. Monoid a => [a] -> a
mconcat
[ String -> Mod OptionFields Word
forall (f :: * -> *) a. HasName f => String -> Mod f a
Opt.long String
"gen-genesis-keys"
, String -> Mod OptionFields Word
forall (f :: * -> *) a. HasMetavar f => String -> Mod f a
Opt.metavar String
"INT"
, String -> Mod OptionFields Word
forall (f :: * -> *) a. String -> Mod f a
Opt.help String
"The number of genesis keys to make [default is 3]."
, Word -> Mod OptionFields Word
forall (f :: * -> *) a. HasValue f => a -> Mod f a
Opt.value Word
3
]
pNodeConfigTemplate :: Parser (Maybe FilePath)
pNodeConfigTemplate :: Parser (Maybe String)
pNodeConfigTemplate = Parser String -> Parser (Maybe String)
forall (f :: * -> *) a. Alternative f => f a -> f (Maybe a)
optional (Parser String -> Parser (Maybe String))
-> Parser String -> Parser (Maybe String)
forall a b. (a -> b) -> a -> b
$ String -> String -> Parser String
parseFilePath String
"node-config-template" String
"the node config template"
pGenesisNumUTxOKeys :: Parser Word
pGenesisNumUTxOKeys :: Parser Word
pGenesisNumUTxOKeys =
ReadM Word -> Mod OptionFields Word -> Parser Word
forall a. ReadM a -> Mod OptionFields a -> Parser a
Opt.option ReadM Word
forall a. (Typeable a, Integral a, Bits a) => ReadM a
integralReader (Mod OptionFields Word -> Parser Word)
-> Mod OptionFields Word -> Parser Word
forall a b. (a -> b) -> a -> b
$
[Mod OptionFields Word] -> Mod OptionFields Word
forall a. Monoid a => [a] -> a
mconcat
[ String -> Mod OptionFields Word
forall (f :: * -> *) a. HasName f => String -> Mod f a
Opt.long String
"gen-utxo-keys"
, String -> Mod OptionFields Word
forall (f :: * -> *) a. HasMetavar f => String -> Mod f a
Opt.metavar String
"INT"
, String -> Mod OptionFields Word
forall (f :: * -> *) a. String -> Mod f a
Opt.help String
"The number of UTxO keys to make [default is 0]."
, Word -> Mod OptionFields Word
forall (f :: * -> *) a. HasValue f => a -> Mod f a
Opt.value Word
0
]
pGenesisNumPools :: Parser Word
pGenesisNumPools :: Parser Word
pGenesisNumPools =
ReadM Word -> Mod OptionFields Word -> Parser Word
forall a. ReadM a -> Mod OptionFields a -> Parser a
Opt.option ReadM Word
forall a. (Typeable a, Integral a, Bits a) => ReadM a
integralReader (Mod OptionFields Word -> Parser Word)
-> Mod OptionFields Word -> Parser Word
forall a b. (a -> b) -> a -> b
$
[Mod OptionFields Word] -> Mod OptionFields Word
forall a. Monoid a => [a] -> a
mconcat
[ String -> Mod OptionFields Word
forall (f :: * -> *) a. HasName f => String -> Mod f a
Opt.long String
"gen-pools"
, String -> Mod OptionFields Word
forall (f :: * -> *) a. HasMetavar f => String -> Mod f a
Opt.metavar String
"INT"
, String -> Mod OptionFields Word
forall (f :: * -> *) a. String -> Mod f a
Opt.help String
"The number of stake pool credential sets to make [default is 0]."
, Word -> Mod OptionFields Word
forall (f :: * -> *) a. HasValue f => a -> Mod f a
Opt.value Word
0
]
pGenesisNumStDelegs :: Parser Word
pGenesisNumStDelegs :: Parser Word
pGenesisNumStDelegs =
ReadM Word -> Mod OptionFields Word -> Parser Word
forall a. ReadM a -> Mod OptionFields a -> Parser a
Opt.option ReadM Word
forall a. (Typeable a, Integral a, Bits a) => ReadM a
integralReader (Mod OptionFields Word -> Parser Word)
-> Mod OptionFields Word -> Parser Word
forall a b. (a -> b) -> a -> b
$
[Mod OptionFields Word] -> Mod OptionFields Word
forall a. Monoid a => [a] -> a
mconcat
[ String -> Mod OptionFields Word
forall (f :: * -> *) a. HasName f => String -> Mod f a
Opt.long String
"gen-stake-delegs"
, String -> Mod OptionFields Word
forall (f :: * -> *) a. HasMetavar f => String -> Mod f a
Opt.metavar String
"INT"
, String -> Mod OptionFields Word
forall (f :: * -> *) a. String -> Mod f a
Opt.help String
"The number of stake delegator credential sets to make [default is 0]."
, Word -> Mod OptionFields Word
forall (f :: * -> *) a. HasValue f => a -> Mod f a
Opt.value Word
0
]
pStuffedUtxoCount :: Parser Word
pStuffedUtxoCount :: Parser Word
pStuffedUtxoCount =
ReadM Word -> Mod OptionFields Word -> Parser Word
forall a. ReadM a -> Mod OptionFields a -> Parser a
Opt.option ReadM Word
forall a. (Typeable a, Integral a, Bits a) => ReadM a
integralReader (Mod OptionFields Word -> Parser Word)
-> Mod OptionFields Word -> Parser Word
forall a b. (a -> b) -> a -> b
$
[Mod OptionFields Word] -> Mod OptionFields Word
forall a. Monoid a => [a] -> a
mconcat
[ String -> Mod OptionFields Word
forall (f :: * -> *) a. HasName f => String -> Mod f a
Opt.long String
"num-stuffed-utxo"
, String -> Mod OptionFields Word
forall (f :: * -> *) a. HasMetavar f => String -> Mod f a
Opt.metavar String
"INT"
, String -> Mod OptionFields Word
forall (f :: * -> *) a. String -> Mod f a
Opt.help String
"The number of fake UTxO entries to generate [default is 0]."
, Word -> Mod OptionFields Word
forall (f :: * -> *) a. HasValue f => a -> Mod f a
Opt.value Word
0
]
pRelayJsonFp :: Parser FilePath
pRelayJsonFp :: Parser String
pRelayJsonFp =
String -> String -> Parser String
parseFilePath String
"relay-specification-file" String
"JSON file specified the relays of each stake pool."
pInitialSupplyNonDelegated :: Parser (Maybe Coin)
pInitialSupplyNonDelegated :: Parser (Maybe Coin)
pInitialSupplyNonDelegated =
Parser Coin -> Parser (Maybe Coin)
forall (f :: * -> *) a. Alternative f => f a -> f (Maybe a)
Opt.optional (Parser Coin -> Parser (Maybe Coin))
-> Parser Coin -> Parser (Maybe Coin)
forall a b. (a -> b) -> a -> b
$
(Integer -> Coin) -> Parser Integer -> Parser Coin
forall a b. (a -> b) -> Parser a -> Parser b
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
fmap Integer -> Coin
Coin (Parser Integer -> Parser Coin) -> Parser Integer -> Parser Coin
forall a b. (a -> b) -> a -> b
$
ReadM Integer -> Mod OptionFields Integer -> Parser Integer
forall a. ReadM a -> Mod OptionFields a -> Parser a
Opt.option ReadM Integer
forall a. (Typeable a, Integral a, Bits a) => ReadM a
integralReader (Mod OptionFields Integer -> Parser Integer)
-> Mod OptionFields Integer -> Parser Integer
forall a b. (a -> b) -> a -> b
$
[Mod OptionFields Integer] -> Mod OptionFields Integer
forall a. Monoid a => [a] -> a
mconcat
[ String -> Mod OptionFields Integer
forall (f :: * -> *) a. HasName f => String -> Mod f a
Opt.long String
"supply"
, String -> Mod OptionFields Integer
forall (f :: * -> *) a. HasMetavar f => String -> Mod f a
Opt.metavar String
"LOVELACE"
, String -> Mod OptionFields Integer
forall (f :: * -> *) a. String -> Mod f a
Opt.help
String
"The initial coin supply in Lovelace which will be evenly distributed across initial, non-delegating stake holders."
]
pInitialSupplyDelegated :: Parser Coin
pInitialSupplyDelegated :: Parser Coin
pInitialSupplyDelegated =
(Maybe Integer -> Coin) -> Parser (Maybe Integer) -> Parser Coin
forall a b. (a -> b) -> Parser a -> Parser b
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
fmap (Integer -> Coin
Coin (Integer -> Coin)
-> (Maybe Integer -> Integer) -> Maybe Integer -> Coin
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Integer -> Maybe Integer -> Integer
forall a. a -> Maybe a -> a
fromMaybe Integer
0) (Parser (Maybe Integer) -> Parser Coin)
-> Parser (Maybe Integer) -> Parser Coin
forall a b. (a -> b) -> a -> b
$
Parser Integer -> Parser (Maybe Integer)
forall (f :: * -> *) a. Alternative f => f a -> f (Maybe a)
Opt.optional (Parser Integer -> Parser (Maybe Integer))
-> Parser Integer -> Parser (Maybe Integer)
forall a b. (a -> b) -> a -> b
$
ReadM Integer -> Mod OptionFields Integer -> Parser Integer
forall a. ReadM a -> Mod OptionFields a -> Parser a
Opt.option ReadM Integer
forall a. (Typeable a, Integral a, Bits a) => ReadM a
integralReader (Mod OptionFields Integer -> Parser Integer)
-> Mod OptionFields Integer -> Parser Integer
forall a b. (a -> b) -> a -> b
$
[Mod OptionFields Integer] -> Mod OptionFields Integer
forall a. Monoid a => [a] -> a
mconcat
[ String -> Mod OptionFields Integer
forall (f :: * -> *) a. HasName f => String -> Mod f a
Opt.long String
"supply-delegated"
, String -> Mod OptionFields Integer
forall (f :: * -> *) a. HasMetavar f => String -> Mod f a
Opt.metavar String
"LOVELACE"
, String -> Mod OptionFields Integer
forall (f :: * -> *) a. String -> Mod f a
Opt.help
String
"The initial coin supply in Lovelace which will be evenly distributed across initial, delegating stake holders."
, Integer -> Mod OptionFields Integer
forall (f :: * -> *) a. HasValue f => a -> Mod f a
Opt.value Integer
0
]
pSecurityParam :: Parser (NonZero Word64)
pSecurityParam :: Parser (NonZero Word64)
pSecurityParam =
ReadM (NonZero Word64)
-> Mod OptionFields (NonZero Word64) -> Parser (NonZero Word64)
forall a. ReadM a -> Mod OptionFields a -> Parser a
Opt.option ReadM (NonZero Word64)
nonZeroReader (Mod OptionFields (NonZero Word64) -> Parser (NonZero Word64))
-> Mod OptionFields (NonZero Word64) -> Parser (NonZero Word64)
forall a b. (a -> b) -> a -> b
$
[Mod OptionFields (NonZero Word64)]
-> Mod OptionFields (NonZero Word64)
forall a. Monoid a => [a] -> a
mconcat
[ String -> Mod OptionFields (NonZero Word64)
forall (f :: * -> *) a. HasName f => String -> Mod f a
Opt.long String
"security-param"
, String -> Mod OptionFields (NonZero Word64)
forall (f :: * -> *) a. HasMetavar f => String -> Mod f a
Opt.metavar String
"INT"
, String -> Mod OptionFields (NonZero Word64)
forall (f :: * -> *) a. String -> Mod f a
Opt.help String
"Security parameter for genesis file [default is 108]."
, NonZero Word64 -> Mod OptionFields (NonZero Word64)
forall (f :: * -> *) a. HasValue f => a -> Mod f a
Opt.value (NonZero Word64 -> Mod OptionFields (NonZero Word64))
-> NonZero Word64 -> Mod OptionFields (NonZero Word64)
forall a b. (a -> b) -> a -> b
$ forall (n :: Natural) a.
(KnownNat n, 1 <= n, WithinBounds n a, Num a) =>
NonZero a
knownNonZeroBounded @108
]
pSlotLength :: Parser Word
pSlotLength :: Parser Word
pSlotLength =
ReadM Word -> Mod OptionFields Word -> Parser Word
forall a. ReadM a -> Mod OptionFields a -> Parser a
Opt.option ReadM Word
forall a. (Typeable a, Integral a, Bits a) => ReadM a
integralReader (Mod OptionFields Word -> Parser Word)
-> Mod OptionFields Word -> Parser Word
forall a b. (a -> b) -> a -> b
$
[Mod OptionFields Word] -> Mod OptionFields Word
forall a. Monoid a => [a] -> a
mconcat
[ String -> Mod OptionFields Word
forall (f :: * -> *) a. HasName f => String -> Mod f a
Opt.long String
"slot-length"
, String -> Mod OptionFields Word
forall (f :: * -> *) a. HasMetavar f => String -> Mod f a
Opt.metavar String
"INT"
, String -> Mod OptionFields Word
forall (f :: * -> *) a. String -> Mod f a
Opt.help String
"slot length (ms) parameter for genesis file [default is 1000]."
, Word -> Mod OptionFields Word
forall (f :: * -> *) a. HasValue f => a -> Mod f a
Opt.value Word
1000
]
pSlotCoefficient :: Parser Rational
pSlotCoefficient :: Parser Rational
pSlotCoefficient =
ReadM Rational -> Mod OptionFields Rational -> Parser Rational
forall a. ReadM a -> Mod OptionFields a -> Parser a
Opt.option ReadM Rational
readRationalUnitInterval (Mod OptionFields Rational -> Parser Rational)
-> Mod OptionFields Rational -> Parser Rational
forall a b. (a -> b) -> a -> b
$
[Mod OptionFields Rational] -> Mod OptionFields Rational
forall a. Monoid a => [a] -> a
mconcat
[ String -> Mod OptionFields Rational
forall (f :: * -> *) a. HasName f => String -> Mod f a
Opt.long String
"slot-coefficient"
, String -> Mod OptionFields Rational
forall (f :: * -> *) a. HasMetavar f => String -> Mod f a
Opt.metavar String
"RATIONAL"
, String -> Mod OptionFields Rational
forall (f :: * -> *) a. String -> Mod f a
Opt.help String
"Slot Coefficient for genesis file [default is .05]."
, Rational -> Mod OptionFields Rational
forall (f :: * -> *) a. HasValue f => a -> Mod f a
Opt.value Rational
0.05
]
pBulkPoolCredFiles :: Parser Word
pBulkPoolCredFiles :: Parser Word
pBulkPoolCredFiles =
ReadM Word -> Mod OptionFields Word -> Parser Word
forall a. ReadM a -> Mod OptionFields a -> Parser a
Opt.option ReadM Word
forall a. (Typeable a, Integral a, Bits a) => ReadM a
integralReader (Mod OptionFields Word -> Parser Word)
-> Mod OptionFields Word -> Parser Word
forall a b. (a -> b) -> a -> b
$
[Mod OptionFields Word] -> Mod OptionFields Word
forall a. Monoid a => [a] -> a
mconcat
[ String -> Mod OptionFields Word
forall (f :: * -> *) a. HasName f => String -> Mod f a
Opt.long String
"bulk-pool-cred-files"
, String -> Mod OptionFields Word
forall (f :: * -> *) a. HasMetavar f => String -> Mod f a
Opt.metavar String
"INT"
, String -> Mod OptionFields Word
forall (f :: * -> *) a. String -> Mod f a
Opt.help String
"Generate bulk pool credential files [default is 0]."
, Word -> Mod OptionFields Word
forall (f :: * -> *) a. HasValue f => a -> Mod f a
Opt.value Word
0
]
pBulkPoolsPerFile :: Parser Word
pBulkPoolsPerFile :: Parser Word
pBulkPoolsPerFile =
ReadM Word -> Mod OptionFields Word -> Parser Word
forall a. ReadM a -> Mod OptionFields a -> Parser a
Opt.option ReadM Word
forall a. (Typeable a, Integral a, Bits a) => ReadM a
integralReader (Mod OptionFields Word -> Parser Word)
-> Mod OptionFields Word -> Parser Word
forall a b. (a -> b) -> a -> b
$
[Mod OptionFields Word] -> Mod OptionFields Word
forall a. Monoid a => [a] -> a
mconcat
[ String -> Mod OptionFields Word
forall (f :: * -> *) a. HasName f => String -> Mod f a
Opt.long String
"bulk-pools-per-file"
, String -> Mod OptionFields Word
forall (f :: * -> *) a. HasMetavar f => String -> Mod f a
Opt.metavar String
"INT"
, String -> Mod OptionFields Word
forall (f :: * -> *) a. String -> Mod f a
Opt.help String
"Each bulk pool to contain this many pool credential sets [default is 0]."
, Word -> Mod OptionFields Word
forall (f :: * -> *) a. HasValue f => a -> Mod f a
Opt.value Word
0
]
pShelleyBasedEra :: EnvCli -> Parser AnyShelleyBasedEra
pShelleyBasedEra :: EnvCli -> Parser AnyShelleyBasedEra
pShelleyBasedEra EnvCli
envCli =
[Parser AnyShelleyBasedEra] -> Parser AnyShelleyBasedEra
forall (t :: * -> *) (f :: * -> *) a.
(Foldable t, Alternative f) =>
t (f a) -> f a
asum ([Parser AnyShelleyBasedEra] -> Parser AnyShelleyBasedEra)
-> [Parser AnyShelleyBasedEra] -> Parser AnyShelleyBasedEra
forall a b. (a -> b) -> a -> b
$
[ AnyShelleyBasedEra -> Parser AnyShelleyBasedEra
shelleyBasedEraFlag AnyShelleyBasedEra
era
| AnyShelleyBasedEra
era <- AnyShelleyBasedEra -> [AnyShelleyBasedEra]
forall a. Enum a => a -> [a]
enumFrom AnyShelleyBasedEra
forall a. Bounded a => a
minBound
]
[Parser AnyShelleyBasedEra]
-> [Parser AnyShelleyBasedEra] -> [Parser AnyShelleyBasedEra]
forall a. [a] -> [a] -> [a]
++ (AnyShelleyBasedEra -> Parser AnyShelleyBasedEra
forall a. a -> Parser a
forall (f :: * -> *) a. Applicative f => a -> f a
pure (AnyShelleyBasedEra -> Parser AnyShelleyBasedEra)
-> [AnyShelleyBasedEra] -> [Parser AnyShelleyBasedEra]
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> Maybe AnyShelleyBasedEra -> [AnyShelleyBasedEra]
forall a. Maybe a -> [a]
maybeToList (EnvCli -> Maybe AnyShelleyBasedEra
envCliShelleyBasedEra EnvCli
envCli))
where
shelleyBasedEraFlag :: AnyShelleyBasedEra -> Parser AnyShelleyBasedEra
shelleyBasedEraFlag :: AnyShelleyBasedEra -> Parser AnyShelleyBasedEra
shelleyBasedEraFlag era :: AnyShelleyBasedEra
era@(AnyShelleyBasedEra ShelleyBasedEra era
sbe) =
let eraName :: String
eraName = Doc Any -> String
forall a. Show a => a -> String
show (Doc Any -> String)
-> (CardanoEra era -> Doc Any) -> CardanoEra era -> String
forall b c a. (b -> c) -> (a -> b) -> a -> c
. CardanoEra era -> Doc Any
forall a ann. Pretty a => a -> Doc ann
forall ann. CardanoEra era -> Doc ann
pretty (CardanoEra era -> String) -> CardanoEra era -> String
forall a b. (a -> b) -> a -> b
$ ShelleyBasedEra era -> CardanoEra era
forall era. ShelleyBasedEra era -> CardanoEra era
forall (eon :: * -> *) era.
ToCardanoEra eon =>
eon era -> CardanoEra era
toCardanoEra ShelleyBasedEra era
sbe
in AnyShelleyBasedEra
-> Mod FlagFields AnyShelleyBasedEra -> Parser AnyShelleyBasedEra
forall a. a -> Mod FlagFields a -> Parser a
flag' AnyShelleyBasedEra
era (Mod FlagFields AnyShelleyBasedEra -> Parser AnyShelleyBasedEra)
-> Mod FlagFields AnyShelleyBasedEra -> Parser AnyShelleyBasedEra
forall a b. (a -> b) -> a -> b
$
[Mod FlagFields AnyShelleyBasedEra]
-> Mod FlagFields AnyShelleyBasedEra
forall a. Monoid a => [a] -> a
mconcat
[ String -> Mod FlagFields AnyShelleyBasedEra
forall (f :: * -> *) a. HasName f => String -> Mod f a
long (String -> Mod FlagFields AnyShelleyBasedEra)
-> String -> Mod FlagFields AnyShelleyBasedEra
forall a b. (a -> b) -> a -> b
$ (Char -> Char) -> String -> String
forall a b. (a -> b) -> [a] -> [b]
map Char -> Char
toLower String
eraName
, String -> Mod FlagFields AnyShelleyBasedEra
forall (f :: * -> *) a. String -> Mod f a
Opt.help (String -> Mod FlagFields AnyShelleyBasedEra)
-> String -> Mod FlagFields AnyShelleyBasedEra
forall a b. (a -> b) -> a -> b
$ String
"Specify the " String -> String -> String
forall a. Semigroup a => a -> a -> a
<> String
eraName String -> String -> String
forall a. Semigroup a => a -> a -> a
<> String
" era"
]
envCliShelleyBasedEra :: EnvCli -> Maybe AnyShelleyBasedEra
envCliShelleyBasedEra :: EnvCli -> Maybe AnyShelleyBasedEra
envCliShelleyBasedEra EnvCli
envCli = do
AnyCardanoEra CardanoEra era
era <- EnvCli -> Maybe AnyCardanoEra
envCliAnyCardanoEra EnvCli
envCli
ShelleyBasedEra era -> AnyShelleyBasedEra
forall era.
Typeable era =>
ShelleyBasedEra era -> AnyShelleyBasedEra
AnyShelleyBasedEra (ShelleyBasedEra era -> AnyShelleyBasedEra)
-> Maybe (ShelleyBasedEra era) -> Maybe AnyShelleyBasedEra
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> CardanoEra era -> Maybe (ShelleyBasedEra era)
forall (eon :: * -> *) era.
Eon eon =>
CardanoEra era -> Maybe (eon era)
forEraMaybeEon CardanoEra era
era