{-# LANGUAGE DataKinds #-} {-# LANGUAGE FlexibleContexts #-} {-# LANGUAGE GADTs #-} {-# LANGUAGE LambdaCase #-} {-# LANGUAGE ScopedTypeVariables #-} module Cardano.CLI.EraIndependent.Key.Option ( pKeyCmds ) where import Cardano.Api hiding (QueryInShelleyBasedEra (..)) import Cardano.CLI.EraBased.Common.Option import Cardano.CLI.EraIndependent.Key.Command import Cardano.CLI.Parser import Cardano.CLI.Type.Common import Data.Foldable import Data.Text (Text) import GHC.Word (Word32) import Options.Applicative hiding (help, str) import Options.Applicative qualified as Opt import Options.Applicative.Types (readerAsk) pKeyCmds :: Parser KeyCmds pKeyCmds :: Parser KeyCmds pKeyCmds = let keyCmdParsers :: Parser KeyCmds keyCmdParsers = [Parser KeyCmds] -> Parser KeyCmds forall (t :: * -> *) (f :: * -> *) a. (Foldable t, Alternative f) => t (f a) -> f a asum [ Mod CommandFields KeyCmds -> Parser KeyCmds forall a. Mod CommandFields a -> Parser a Opt.hsubparser (Mod CommandFields KeyCmds -> Parser KeyCmds) -> Mod CommandFields KeyCmds -> Parser KeyCmds forall a b. (a -> b) -> a -> b $ String -> ParserInfo KeyCmds -> Mod CommandFields KeyCmds forall a. String -> ParserInfo a -> Mod CommandFields a commandWithMetavar String "verification-key" (ParserInfo KeyCmds -> Mod CommandFields KeyCmds) -> ParserInfo KeyCmds -> Mod CommandFields KeyCmds forall a b. (a -> b) -> a -> b $ Parser KeyCmds -> InfoMod KeyCmds -> ParserInfo KeyCmds forall a. Parser a -> InfoMod a -> ParserInfo a Opt.info Parser KeyCmds pKeyVerificationKeyCmd (InfoMod KeyCmds -> ParserInfo KeyCmds) -> InfoMod KeyCmds -> ParserInfo KeyCmds forall a b. (a -> b) -> a -> b $ String -> InfoMod KeyCmds forall a. String -> InfoMod a Opt.progDesc (String -> InfoMod KeyCmds) -> String -> InfoMod KeyCmds forall a b. (a -> b) -> a -> b $ [String] -> String forall a. Monoid a => [a] -> a mconcat [ String "Get a verification key from a signing key. This " , String " supports all key types." ] , Mod CommandFields KeyCmds -> Parser KeyCmds forall a. Mod CommandFields a -> Parser a Opt.hsubparser (Mod CommandFields KeyCmds -> Parser KeyCmds) -> Mod CommandFields KeyCmds -> Parser KeyCmds forall a b. (a -> b) -> a -> b $ String -> ParserInfo KeyCmds -> Mod CommandFields KeyCmds forall a. String -> ParserInfo a -> Mod CommandFields a commandWithMetavar String "non-extended-key" (ParserInfo KeyCmds -> Mod CommandFields KeyCmds) -> ParserInfo KeyCmds -> Mod CommandFields KeyCmds forall a b. (a -> b) -> a -> b $ Parser KeyCmds -> InfoMod KeyCmds -> ParserInfo KeyCmds forall a. Parser a -> InfoMod a -> ParserInfo a Opt.info Parser KeyCmds pKeyNonExtendedKeyCmd (InfoMod KeyCmds -> ParserInfo KeyCmds) -> InfoMod KeyCmds -> ParserInfo KeyCmds forall a b. (a -> b) -> a -> b $ String -> InfoMod KeyCmds forall a. String -> InfoMod a Opt.progDesc (String -> InfoMod KeyCmds) -> String -> InfoMod KeyCmds forall a b. (a -> b) -> a -> b $ [String] -> String forall a. Monoid a => [a] -> a mconcat [ String "Get a non-extended verification key from an " , String "extended verification key. This supports all " , String "extended key types." ] , Mod CommandFields KeyCmds -> Parser KeyCmds forall a. Mod CommandFields a -> Parser a Opt.hsubparser (Mod CommandFields KeyCmds -> Parser KeyCmds) -> Mod CommandFields KeyCmds -> Parser KeyCmds forall a b. (a -> b) -> a -> b $ String -> ParserInfo KeyCmds -> Mod CommandFields KeyCmds forall a. String -> ParserInfo a -> Mod CommandFields a commandWithMetavar String "generate-mnemonic" (ParserInfo KeyCmds -> Mod CommandFields KeyCmds) -> ParserInfo KeyCmds -> Mod CommandFields KeyCmds forall a b. (a -> b) -> a -> b $ Parser KeyCmds -> InfoMod KeyCmds -> ParserInfo KeyCmds forall a. Parser a -> InfoMod a -> ParserInfo a Opt.info Parser KeyCmds pKeyGenerateMnemonicCmd (InfoMod KeyCmds -> ParserInfo KeyCmds) -> InfoMod KeyCmds -> ParserInfo KeyCmds forall a b. (a -> b) -> a -> b $ String -> InfoMod KeyCmds forall a. String -> InfoMod a Opt.progDesc (String -> InfoMod KeyCmds) -> String -> InfoMod KeyCmds forall a b. (a -> b) -> a -> b $ [String] -> String forall a. Monoid a => [a] -> a mconcat [ String "Generate a mnemonic sentence that can be used " , String "for key derivation." ] , Mod CommandFields KeyCmds -> Parser KeyCmds forall a. Mod CommandFields a -> Parser a Opt.hsubparser (Mod CommandFields KeyCmds -> Parser KeyCmds) -> Mod CommandFields KeyCmds -> Parser KeyCmds forall a b. (a -> b) -> a -> b $ String -> ParserInfo KeyCmds -> Mod CommandFields KeyCmds forall a. String -> ParserInfo a -> Mod CommandFields a commandWithMetavar String "derive-from-mnemonic" (ParserInfo KeyCmds -> Mod CommandFields KeyCmds) -> ParserInfo KeyCmds -> Mod CommandFields KeyCmds forall a b. (a -> b) -> a -> b $ Parser KeyCmds -> InfoMod KeyCmds -> ParserInfo KeyCmds forall a. Parser a -> InfoMod a -> ParserInfo a Opt.info Parser KeyCmds pKeyExtendedSigningKeyFromMnemonicCmd (InfoMod KeyCmds -> ParserInfo KeyCmds) -> InfoMod KeyCmds -> ParserInfo KeyCmds forall a b. (a -> b) -> a -> b $ String -> InfoMod KeyCmds forall a. String -> InfoMod a Opt.progDesc (String -> InfoMod KeyCmds) -> String -> InfoMod KeyCmds forall a b. (a -> b) -> a -> b $ [String] -> String forall a. Monoid a => [a] -> a mconcat [ String "Derive an extended signing key from a mnemonic sentence. " , String "To ensure the safety of the mnemonic phrase, " , String "we recommend that key derivation is performed " , String "in an air-gapped environment." ] , Mod CommandFields KeyCmds -> Parser KeyCmds forall a. Mod CommandFields a -> Parser a Opt.hsubparser (Mod CommandFields KeyCmds -> Parser KeyCmds) -> Mod CommandFields KeyCmds -> Parser KeyCmds forall a b. (a -> b) -> a -> b $ String -> ParserInfo KeyCmds -> Mod CommandFields KeyCmds forall a. String -> ParserInfo a -> Mod CommandFields a commandWithMetavar String "convert-byron-key" (ParserInfo KeyCmds -> Mod CommandFields KeyCmds) -> ParserInfo KeyCmds -> Mod CommandFields KeyCmds forall a b. (a -> b) -> a -> b $ Parser KeyCmds -> InfoMod KeyCmds -> ParserInfo KeyCmds forall a. Parser a -> InfoMod a -> ParserInfo a Opt.info Parser KeyCmds pKeyConvertByronKeyCmd (InfoMod KeyCmds -> ParserInfo KeyCmds) -> InfoMod KeyCmds -> ParserInfo KeyCmds forall a b. (a -> b) -> a -> b $ String -> InfoMod KeyCmds forall a. String -> InfoMod a Opt.progDesc (String -> InfoMod KeyCmds) -> String -> InfoMod KeyCmds forall a b. (a -> b) -> a -> b $ [String] -> String forall a. Monoid a => [a] -> a mconcat [ String "Convert a Byron payment, genesis or genesis " , String "delegate key (signing or verification) to a " , String "corresponding Shelley-format key." ] , Mod CommandFields KeyCmds -> Parser KeyCmds forall a. Mod CommandFields a -> Parser a Opt.hsubparser (Mod CommandFields KeyCmds -> Parser KeyCmds) -> Mod CommandFields KeyCmds -> Parser KeyCmds forall a b. (a -> b) -> a -> b $ String -> ParserInfo KeyCmds -> Mod CommandFields KeyCmds forall a. String -> ParserInfo a -> Mod CommandFields a commandWithMetavar String "convert-byron-genesis-vkey" (ParserInfo KeyCmds -> Mod CommandFields KeyCmds) -> ParserInfo KeyCmds -> Mod CommandFields KeyCmds forall a b. (a -> b) -> a -> b $ Parser KeyCmds -> InfoMod KeyCmds -> ParserInfo KeyCmds forall a. Parser a -> InfoMod a -> ParserInfo a Opt.info Parser KeyCmds pKeyConvertByronGenesisKeyCmd (InfoMod KeyCmds -> ParserInfo KeyCmds) -> InfoMod KeyCmds -> ParserInfo KeyCmds forall a b. (a -> b) -> a -> b $ String -> InfoMod KeyCmds forall a. String -> InfoMod a Opt.progDesc (String -> InfoMod KeyCmds) -> String -> InfoMod KeyCmds forall a b. (a -> b) -> a -> b $ [String] -> String forall a. Monoid a => [a] -> a mconcat [ String "Convert a Base64-encoded Byron genesis " , String "verification key to a Shelley genesis " , String "verification key" ] , Mod CommandFields KeyCmds -> Parser KeyCmds forall a. Mod CommandFields a -> Parser a Opt.hsubparser (Mod CommandFields KeyCmds -> Parser KeyCmds) -> Mod CommandFields KeyCmds -> Parser KeyCmds forall a b. (a -> b) -> a -> b $ String -> ParserInfo KeyCmds -> Mod CommandFields KeyCmds forall a. String -> ParserInfo a -> Mod CommandFields a commandWithMetavar String "convert-itn-key" (ParserInfo KeyCmds -> Mod CommandFields KeyCmds) -> ParserInfo KeyCmds -> Mod CommandFields KeyCmds forall a b. (a -> b) -> a -> b $ Parser KeyCmds -> InfoMod KeyCmds -> ParserInfo KeyCmds forall a. Parser a -> InfoMod a -> ParserInfo a Opt.info Parser KeyCmds pKeyConvertITNKeyCmd (InfoMod KeyCmds -> ParserInfo KeyCmds) -> InfoMod KeyCmds -> ParserInfo KeyCmds forall a b. (a -> b) -> a -> b $ String -> InfoMod KeyCmds forall a. String -> InfoMod a Opt.progDesc (String -> InfoMod KeyCmds) -> String -> InfoMod KeyCmds forall a b. (a -> b) -> a -> b $ [String] -> String forall a. Monoid a => [a] -> a mconcat [ String "Convert an Incentivized Testnet (ITN) non-extended " , String "(Ed25519) signing or verification key to a " , String "corresponding Shelley stake key" ] , Mod CommandFields KeyCmds -> Parser KeyCmds forall a. Mod CommandFields a -> Parser a Opt.hsubparser (Mod CommandFields KeyCmds -> Parser KeyCmds) -> Mod CommandFields KeyCmds -> Parser KeyCmds forall a b. (a -> b) -> a -> b $ String -> ParserInfo KeyCmds -> Mod CommandFields KeyCmds forall a. String -> ParserInfo a -> Mod CommandFields a commandWithMetavar String "convert-itn-extended-key" (ParserInfo KeyCmds -> Mod CommandFields KeyCmds) -> ParserInfo KeyCmds -> Mod CommandFields KeyCmds forall a b. (a -> b) -> a -> b $ Parser KeyCmds -> InfoMod KeyCmds -> ParserInfo KeyCmds forall a. Parser a -> InfoMod a -> ParserInfo a Opt.info Parser KeyCmds pKeyConvertITNExtendedKeyCmd (InfoMod KeyCmds -> ParserInfo KeyCmds) -> InfoMod KeyCmds -> ParserInfo KeyCmds forall a b. (a -> b) -> a -> b $ String -> InfoMod KeyCmds forall a. String -> InfoMod a Opt.progDesc (String -> InfoMod KeyCmds) -> String -> InfoMod KeyCmds forall a b. (a -> b) -> a -> b $ [String] -> String forall a. Monoid a => [a] -> a mconcat [ String "Convert an Incentivized Testnet (ITN) extended " , String "(Ed25519Extended) signing key to a corresponding " , String "Shelley stake signing key" ] , Mod CommandFields KeyCmds -> Parser KeyCmds forall a. Mod CommandFields a -> Parser a Opt.hsubparser (Mod CommandFields KeyCmds -> Parser KeyCmds) -> Mod CommandFields KeyCmds -> Parser KeyCmds forall a b. (a -> b) -> a -> b $ String -> ParserInfo KeyCmds -> Mod CommandFields KeyCmds forall a. String -> ParserInfo a -> Mod CommandFields a commandWithMetavar String "convert-itn-bip32-key" (ParserInfo KeyCmds -> Mod CommandFields KeyCmds) -> ParserInfo KeyCmds -> Mod CommandFields KeyCmds forall a b. (a -> b) -> a -> b $ Parser KeyCmds -> InfoMod KeyCmds -> ParserInfo KeyCmds forall a. Parser a -> InfoMod a -> ParserInfo a Opt.info Parser KeyCmds pKeyConvertITNBip32KeyCmd (InfoMod KeyCmds -> ParserInfo KeyCmds) -> InfoMod KeyCmds -> ParserInfo KeyCmds forall a b. (a -> b) -> a -> b $ String -> InfoMod KeyCmds forall a. String -> InfoMod a Opt.progDesc (String -> InfoMod KeyCmds) -> String -> InfoMod KeyCmds forall a b. (a -> b) -> a -> b $ [String] -> String forall a. Monoid a => [a] -> a mconcat [ String "Convert an Incentivized Testnet (ITN) BIP32 " , String "(Ed25519Bip32) signing key to a corresponding " , String "Shelley stake signing key" ] , Mod CommandFields KeyCmds -> Parser KeyCmds forall a. Mod CommandFields a -> Parser a Opt.hsubparser (Mod CommandFields KeyCmds -> Parser KeyCmds) -> Mod CommandFields KeyCmds -> Parser KeyCmds forall a b. (a -> b) -> a -> b $ String -> ParserInfo KeyCmds -> Mod CommandFields KeyCmds forall a. String -> ParserInfo a -> Mod CommandFields a commandWithMetavar String "convert-cardano-address-key" (ParserInfo KeyCmds -> Mod CommandFields KeyCmds) -> ParserInfo KeyCmds -> Mod CommandFields KeyCmds forall a b. (a -> b) -> a -> b $ Parser KeyCmds -> InfoMod KeyCmds -> ParserInfo KeyCmds forall a. Parser a -> InfoMod a -> ParserInfo a Opt.info Parser KeyCmds pKeyConvertCardanoAddressKeyCmd (InfoMod KeyCmds -> ParserInfo KeyCmds) -> InfoMod KeyCmds -> ParserInfo KeyCmds forall a b. (a -> b) -> a -> b $ String -> InfoMod KeyCmds forall a. String -> InfoMod a Opt.progDesc (String -> InfoMod KeyCmds) -> String -> InfoMod KeyCmds forall a b. (a -> b) -> a -> b $ [String] -> String forall a. Monoid a => [a] -> a mconcat [ String "Convert a cardano-address extended signing key " , String "to a corresponding Shelley-format key." ] ] in Mod CommandFields KeyCmds -> Parser KeyCmds forall a. Mod CommandFields a -> Parser a Opt.hsubparser (Mod CommandFields KeyCmds -> Parser KeyCmds) -> Mod CommandFields KeyCmds -> Parser KeyCmds forall a b. (a -> b) -> a -> b $ String -> ParserInfo KeyCmds -> Mod CommandFields KeyCmds forall a. String -> ParserInfo a -> Mod CommandFields a commandWithMetavar String "key" (ParserInfo KeyCmds -> Mod CommandFields KeyCmds) -> ParserInfo KeyCmds -> Mod CommandFields KeyCmds forall a b. (a -> b) -> a -> b $ Parser KeyCmds -> InfoMod KeyCmds -> ParserInfo KeyCmds forall a. Parser a -> InfoMod a -> ParserInfo a Opt.info Parser KeyCmds keyCmdParsers (InfoMod KeyCmds -> ParserInfo KeyCmds) -> InfoMod KeyCmds -> ParserInfo KeyCmds forall a b. (a -> b) -> a -> b $ String -> InfoMod KeyCmds forall a. String -> InfoMod a Opt.progDesc (String -> InfoMod KeyCmds) -> String -> InfoMod KeyCmds forall a b. (a -> b) -> a -> b $ [String] -> String forall a. Monoid a => [a] -> a mconcat [ String "Key utility commands." ] pKeyVerificationKeyCmd :: Parser KeyCmds pKeyVerificationKeyCmd :: Parser KeyCmds pKeyVerificationKeyCmd = (KeyVerificationKeyCmdArgs -> KeyCmds) -> Parser KeyVerificationKeyCmdArgs -> Parser KeyCmds forall a b. (a -> b) -> Parser a -> Parser b forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b fmap KeyVerificationKeyCmdArgs -> KeyCmds KeyVerificationKeyCmd (Parser KeyVerificationKeyCmdArgs -> Parser KeyCmds) -> Parser KeyVerificationKeyCmdArgs -> Parser KeyCmds forall a b. (a -> b) -> a -> b $ SigningKeyFile 'In -> VerificationKeyFile 'Out -> KeyVerificationKeyCmdArgs KeyVerificationKeyCmdArgs (SigningKeyFile 'In -> VerificationKeyFile 'Out -> KeyVerificationKeyCmdArgs) -> Parser (SigningKeyFile 'In) -> Parser (VerificationKeyFile 'Out -> KeyVerificationKeyCmdArgs) forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b <$> Parser (SigningKeyFile 'In) pSigningKeyFileIn Parser (VerificationKeyFile 'Out -> KeyVerificationKeyCmdArgs) -> Parser (VerificationKeyFile 'Out) -> Parser KeyVerificationKeyCmdArgs forall a b. Parser (a -> b) -> Parser a -> Parser b forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b <*> Parser (VerificationKeyFile 'Out) forall keyrole. Parser (File (VerificationKey keyrole) 'Out) pVerificationKeyFileOut pKeyNonExtendedKeyCmd :: Parser KeyCmds pKeyNonExtendedKeyCmd :: Parser KeyCmds pKeyNonExtendedKeyCmd = (KeyNonExtendedKeyCmdArgs -> KeyCmds) -> Parser KeyNonExtendedKeyCmdArgs -> Parser KeyCmds forall a b. (a -> b) -> Parser a -> Parser b forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b fmap KeyNonExtendedKeyCmdArgs -> KeyCmds KeyNonExtendedKeyCmd (Parser KeyNonExtendedKeyCmdArgs -> Parser KeyCmds) -> Parser KeyNonExtendedKeyCmdArgs -> Parser KeyCmds forall a b. (a -> b) -> a -> b $ VerificationKeyFile 'In -> VerificationKeyFile 'Out -> KeyNonExtendedKeyCmdArgs KeyNonExtendedKeyCmdArgs (VerificationKeyFile 'In -> VerificationKeyFile 'Out -> KeyNonExtendedKeyCmdArgs) -> Parser (VerificationKeyFile 'In) -> Parser (VerificationKeyFile 'Out -> KeyNonExtendedKeyCmdArgs) forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b <$> Parser (VerificationKeyFile 'In) pExtendedVerificationKeyFileIn Parser (VerificationKeyFile 'Out -> KeyNonExtendedKeyCmdArgs) -> Parser (VerificationKeyFile 'Out) -> Parser KeyNonExtendedKeyCmdArgs forall a b. Parser (a -> b) -> Parser a -> Parser b forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b <*> Parser (VerificationKeyFile 'Out) forall keyrole. Parser (File (VerificationKey keyrole) 'Out) pVerificationKeyFileOut pKeyGenerateMnemonicCmd :: Parser KeyCmds pKeyGenerateMnemonicCmd :: Parser KeyCmds pKeyGenerateMnemonicCmd = (KeyGenerateMnemonicCmdArgs -> KeyCmds) -> Parser KeyGenerateMnemonicCmdArgs -> Parser KeyCmds forall a b. (a -> b) -> Parser a -> Parser b forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b fmap KeyGenerateMnemonicCmdArgs -> KeyCmds KeyGenerateMnemonicCmd (Parser KeyGenerateMnemonicCmdArgs -> Parser KeyCmds) -> Parser KeyGenerateMnemonicCmdArgs -> Parser KeyCmds forall a b. (a -> b) -> a -> b $ Maybe (File () 'Out) -> MnemonicSize -> KeyGenerateMnemonicCmdArgs KeyGenerateMnemonicCmdArgs (Maybe (File () 'Out) -> MnemonicSize -> KeyGenerateMnemonicCmdArgs) -> Parser (Maybe (File () 'Out)) -> Parser (MnemonicSize -> KeyGenerateMnemonicCmdArgs) forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b <$> Parser (File () 'Out) -> Parser (Maybe (File () 'Out)) forall (f :: * -> *) a. Alternative f => f a -> f (Maybe a) optional Parser (File () 'Out) forall content. Parser (File content 'Out) pOutputFile Parser (MnemonicSize -> KeyGenerateMnemonicCmdArgs) -> Parser MnemonicSize -> Parser KeyGenerateMnemonicCmdArgs forall a b. Parser (a -> b) -> Parser a -> Parser b forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b <*> Parser MnemonicSize pMnemonicSize pMnemonicSize :: Parser MnemonicSize pMnemonicSize :: Parser MnemonicSize pMnemonicSize = do ReadM MnemonicSize -> Mod OptionFields MnemonicSize -> Parser MnemonicSize forall a. ReadM a -> Mod OptionFields a -> Parser a option ReadM MnemonicSize parseSize ( String -> Mod OptionFields MnemonicSize forall (f :: * -> *) a. HasName f => String -> Mod f a long String "size" Mod OptionFields MnemonicSize -> Mod OptionFields MnemonicSize -> Mod OptionFields MnemonicSize forall a. Semigroup a => a -> a -> a <> String -> Mod OptionFields MnemonicSize forall (f :: * -> *) a. HasMetavar f => String -> Mod f a metavar String "WORD32" Mod OptionFields MnemonicSize -> Mod OptionFields MnemonicSize -> Mod OptionFields MnemonicSize forall a. Semigroup a => a -> a -> a <> String -> Mod OptionFields MnemonicSize forall (f :: * -> *) a. String -> Mod f a Opt.help ( [String] -> String forall a. Monoid a => [a] -> a mconcat [ String "Specify the desired number of words for the output" , String "mnemonic sentence (valid options are: 12, 15, 18, 21, and 24)" ] ) ) where parseSize :: ReadM MnemonicSize parseSize :: ReadM MnemonicSize parseSize = ReadM String readerAsk ReadM String -> (String -> ReadM MnemonicSize) -> ReadM MnemonicSize forall a b. ReadM a -> (a -> ReadM b) -> ReadM b forall (m :: * -> *) a b. Monad m => m a -> (a -> m b) -> m b >>= \case String "12" -> MnemonicSize -> ReadM MnemonicSize forall a. a -> ReadM a forall (m :: * -> *) a. Monad m => a -> m a return MnemonicSize MS12 String "15" -> MnemonicSize -> ReadM MnemonicSize forall a. a -> ReadM a forall (m :: * -> *) a. Monad m => a -> m a return MnemonicSize MS15 String "18" -> MnemonicSize -> ReadM MnemonicSize forall a. a -> ReadM a forall (m :: * -> *) a. Monad m => a -> m a return MnemonicSize MS18 String "21" -> MnemonicSize -> ReadM MnemonicSize forall a. a -> ReadM a forall (m :: * -> *) a. Monad m => a -> m a return MnemonicSize MS21 String "24" -> MnemonicSize -> ReadM MnemonicSize forall a. a -> ReadM a forall (m :: * -> *) a. Monad m => a -> m a return MnemonicSize MS24 String invalidSize -> String -> ReadM MnemonicSize forall a. String -> ReadM a readerError (String -> ReadM MnemonicSize) -> String -> ReadM MnemonicSize forall a b. (a -> b) -> a -> b $ String "Invalid mnemonic size " String -> String -> String forall a. Semigroup a => a -> a -> a <> String -> String forall a. Show a => a -> String show String invalidSize String -> String -> String forall a. Semigroup a => a -> a -> a <> String "! It must be one of: 12, 15, 18, 21, or 24." pKeyExtendedSigningKeyFromMnemonicCmd :: Parser KeyCmds pKeyExtendedSigningKeyFromMnemonicCmd :: Parser KeyCmds pKeyExtendedSigningKeyFromMnemonicCmd = (KeyExtendedSigningKeyFromMnemonicArgs -> KeyCmds) -> Parser KeyExtendedSigningKeyFromMnemonicArgs -> Parser KeyCmds forall a b. (a -> b) -> Parser a -> Parser b forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b fmap KeyExtendedSigningKeyFromMnemonicArgs -> KeyCmds KeyExtendedSigningKeyFromMnemonicCmd (Parser KeyExtendedSigningKeyFromMnemonicArgs -> Parser KeyCmds) -> Parser KeyExtendedSigningKeyFromMnemonicArgs -> Parser KeyCmds forall a b. (a -> b) -> a -> b $ Vary '[FormatBech32, FormatTextEnvelope] -> ExtendedSigningType -> Word32 -> MnemonicSource -> SigningKeyFile 'Out -> KeyExtendedSigningKeyFromMnemonicArgs KeyExtendedSigningKeyFromMnemonicArgs (Vary '[FormatBech32, FormatTextEnvelope] -> ExtendedSigningType -> Word32 -> MnemonicSource -> SigningKeyFile 'Out -> KeyExtendedSigningKeyFromMnemonicArgs) -> Parser (Vary '[FormatBech32, FormatTextEnvelope]) -> Parser (ExtendedSigningType -> Word32 -> MnemonicSource -> SigningKeyFile 'Out -> KeyExtendedSigningKeyFromMnemonicArgs) forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b <$> Parser (Vary '[FormatBech32, FormatTextEnvelope]) pKeyOutputFormat Parser (ExtendedSigningType -> Word32 -> MnemonicSource -> SigningKeyFile 'Out -> KeyExtendedSigningKeyFromMnemonicArgs) -> Parser ExtendedSigningType -> Parser (Word32 -> MnemonicSource -> SigningKeyFile 'Out -> KeyExtendedSigningKeyFromMnemonicArgs) forall a b. Parser (a -> b) -> Parser a -> Parser b forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b <*> Parser ExtendedSigningType pDerivedExtendedSigningKeyType Parser (Word32 -> MnemonicSource -> SigningKeyFile 'Out -> KeyExtendedSigningKeyFromMnemonicArgs) -> Parser Word32 -> Parser (MnemonicSource -> SigningKeyFile 'Out -> KeyExtendedSigningKeyFromMnemonicArgs) forall a b. Parser (a -> b) -> Parser a -> Parser b forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b <*> Parser Word32 pAccountNumber Parser (MnemonicSource -> SigningKeyFile 'Out -> KeyExtendedSigningKeyFromMnemonicArgs) -> Parser MnemonicSource -> Parser (SigningKeyFile 'Out -> KeyExtendedSigningKeyFromMnemonicArgs) forall a b. Parser (a -> b) -> Parser a -> Parser b forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b <*> Parser MnemonicSource pMnemonicSource Parser (SigningKeyFile 'Out -> KeyExtendedSigningKeyFromMnemonicArgs) -> Parser (SigningKeyFile 'Out) -> Parser KeyExtendedSigningKeyFromMnemonicArgs 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 pDerivedExtendedSigningKeyType :: Parser ExtendedSigningType pDerivedExtendedSigningKeyType :: Parser ExtendedSigningType pDerivedExtendedSigningKeyType = [Parser ExtendedSigningType] -> Parser ExtendedSigningType forall (t :: * -> *) (f :: * -> *) a. (Foldable t, Alternative f) => t (f a) -> f a asum [ ReadM ExtendedSigningType -> Mod OptionFields ExtendedSigningType -> Parser ExtendedSigningType forall a. ReadM a -> Mod OptionFields a -> Parser a Opt.option (Word32 -> ExtendedSigningType ExtendedSigningPaymentKey (Word32 -> ExtendedSigningType) -> ReadM Word32 -> ReadM ExtendedSigningType forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b <$> ReadM Word32 forall a. (Typeable a, Integral a, Bits a) => ReadM a integralReader) (Mod OptionFields ExtendedSigningType -> Parser ExtendedSigningType) -> Mod OptionFields ExtendedSigningType -> Parser ExtendedSigningType forall a b. (a -> b) -> a -> b $ [Mod OptionFields ExtendedSigningType] -> Mod OptionFields ExtendedSigningType forall a. Monoid a => [a] -> a mconcat [ String -> Mod OptionFields ExtendedSigningType forall (f :: * -> *) a. HasName f => String -> Mod f a Opt.long String "payment-key-with-number" , String -> Mod OptionFields ExtendedSigningType forall (f :: * -> *) a. HasMetavar f => String -> Mod f a Opt.metavar String "WORD32" , String -> Mod OptionFields ExtendedSigningType forall (f :: * -> *) a. String -> Mod f a Opt.help String "Derive an extended payment key with the given payment address number from the derivation path." ] , ReadM ExtendedSigningType -> Mod OptionFields ExtendedSigningType -> Parser ExtendedSigningType forall a. ReadM a -> Mod OptionFields a -> Parser a Opt.option (Word32 -> ExtendedSigningType ExtendedSigningStakeKey (Word32 -> ExtendedSigningType) -> ReadM Word32 -> ReadM ExtendedSigningType forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b <$> ReadM Word32 forall a. (Typeable a, Integral a, Bits a) => ReadM a integralReader) (Mod OptionFields ExtendedSigningType -> Parser ExtendedSigningType) -> Mod OptionFields ExtendedSigningType -> Parser ExtendedSigningType forall a b. (a -> b) -> a -> b $ [Mod OptionFields ExtendedSigningType] -> Mod OptionFields ExtendedSigningType forall a. Monoid a => [a] -> a mconcat [ String -> Mod OptionFields ExtendedSigningType forall (f :: * -> *) a. HasName f => String -> Mod f a Opt.long String "stake-key-with-number" , String -> Mod OptionFields ExtendedSigningType forall (f :: * -> *) a. HasMetavar f => String -> Mod f a Opt.metavar String "WORD32" , String -> Mod OptionFields ExtendedSigningType forall (f :: * -> *) a. String -> Mod f a Opt.help String "Derive an extended stake key with the given stake address number from the derivation path." ] , ExtendedSigningType -> Mod FlagFields ExtendedSigningType -> Parser ExtendedSigningType forall a. a -> Mod FlagFields a -> Parser a Opt.flag' ExtendedSigningType ExtendedSigningDRepKey (Mod FlagFields ExtendedSigningType -> Parser ExtendedSigningType) -> Mod FlagFields ExtendedSigningType -> Parser ExtendedSigningType forall a b. (a -> b) -> a -> b $ [Mod FlagFields ExtendedSigningType] -> Mod FlagFields ExtendedSigningType forall a. Monoid a => [a] -> a mconcat [ String -> Mod FlagFields ExtendedSigningType forall (f :: * -> *) a. HasName f => String -> Mod f a Opt.long String "drep-key" , String -> Mod FlagFields ExtendedSigningType forall (f :: * -> *) a. String -> Mod f a Opt.help String "Derive an extended DRep key." ] , ExtendedSigningType -> Mod FlagFields ExtendedSigningType -> Parser ExtendedSigningType forall a. a -> Mod FlagFields a -> Parser a Opt.flag' ExtendedSigningType ExtendedSigningCCColdKey (Mod FlagFields ExtendedSigningType -> Parser ExtendedSigningType) -> Mod FlagFields ExtendedSigningType -> Parser ExtendedSigningType forall a b. (a -> b) -> a -> b $ [Mod FlagFields ExtendedSigningType] -> Mod FlagFields ExtendedSigningType forall a. Monoid a => [a] -> a mconcat [ String -> Mod FlagFields ExtendedSigningType forall (f :: * -> *) a. HasName f => String -> Mod f a Opt.long String "cc-cold-key" , String -> Mod FlagFields ExtendedSigningType forall (f :: * -> *) a. String -> Mod f a Opt.help String "Derive an extended committee cold key." ] , ExtendedSigningType -> Mod FlagFields ExtendedSigningType -> Parser ExtendedSigningType forall a. a -> Mod FlagFields a -> Parser a Opt.flag' ExtendedSigningType ExtendedSigningCCHotKey (Mod FlagFields ExtendedSigningType -> Parser ExtendedSigningType) -> Mod FlagFields ExtendedSigningType -> Parser ExtendedSigningType forall a b. (a -> b) -> a -> b $ [Mod FlagFields ExtendedSigningType] -> Mod FlagFields ExtendedSigningType forall a. Monoid a => [a] -> a mconcat [ String -> Mod FlagFields ExtendedSigningType forall (f :: * -> *) a. HasName f => String -> Mod f a Opt.long String "cc-hot-key" , String -> Mod FlagFields ExtendedSigningType forall (f :: * -> *) a. String -> Mod f a Opt.help String "Derive an extended committee hot key." ] ] pMnemonicSource :: Parser MnemonicSource pMnemonicSource :: Parser MnemonicSource pMnemonicSource = [Parser MnemonicSource] -> Parser MnemonicSource forall (t :: * -> *) (f :: * -> *) a. (Foldable t, Alternative f) => t (f a) -> f a asum [ File () 'In -> MnemonicSource MnemonicFromFile (File () 'In -> MnemonicSource) -> (String -> File () 'In) -> String -> MnemonicSource forall b c a. (b -> c) -> (a -> b) -> a -> c . String -> File () 'In forall content (direction :: FileDirection). String -> File content direction File (String -> MnemonicSource) -> Parser String -> Parser MnemonicSource forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b <$> String -> String -> Parser String parseFilePath String "mnemonic-from-file" String "Input text file with the mnemonic." , MnemonicSource -> Mod FlagFields MnemonicSource -> Parser MnemonicSource forall a. a -> Mod FlagFields a -> Parser a Opt.flag' MnemonicSource MnemonicFromInteractivePrompt (Mod FlagFields MnemonicSource -> Parser MnemonicSource) -> Mod FlagFields MnemonicSource -> Parser MnemonicSource forall a b. (a -> b) -> a -> b $ [Mod FlagFields MnemonicSource] -> Mod FlagFields MnemonicSource forall a. Monoid a => [a] -> a mconcat [ String -> Mod FlagFields MnemonicSource forall (f :: * -> *) a. HasName f => String -> Mod f a Opt.long String "mnemonic-from-interactive-prompt" , String -> Mod FlagFields MnemonicSource forall (f :: * -> *) a. String -> Mod f a Opt.help (String -> Mod FlagFields MnemonicSource) -> String -> Mod FlagFields MnemonicSource forall a b. (a -> b) -> a -> b $ String "Input the mnemonic through an interactive prompt. " String -> String -> String forall a. Semigroup a => a -> a -> a <> String "This mode also accepts receiving the mnemonic through " String -> String -> String forall a. Semigroup a => a -> a -> a <> String "standard input directly, for example, by using a pipe." ] ] pAccountNumber :: Parser Word32 pAccountNumber :: Parser Word32 pAccountNumber = ReadM Word32 -> Mod OptionFields Word32 -> Parser Word32 forall a. ReadM a -> Mod OptionFields a -> Parser a Opt.option ReadM Word32 forall a. (Typeable a, Integral a, Bits a) => ReadM a integralReader (Mod OptionFields Word32 -> Parser Word32) -> Mod OptionFields Word32 -> Parser Word32 forall a b. (a -> b) -> a -> b $ [Mod OptionFields Word32] -> Mod OptionFields Word32 forall a. Monoid a => [a] -> a mconcat [ String -> Mod OptionFields Word32 forall (f :: * -> *) a. HasName f => String -> Mod f a Opt.long String "account-number" , String -> Mod OptionFields Word32 forall (f :: * -> *) a. HasMetavar f => String -> Mod f a Opt.metavar String "WORD32" , String -> Mod OptionFields Word32 forall (f :: * -> *) a. String -> Mod f a Opt.help String "Account number in the derivation path." ] pKeyConvertByronKeyCmd :: Parser KeyCmds pKeyConvertByronKeyCmd :: Parser KeyCmds pKeyConvertByronKeyCmd = (KeyConvertByronKeyCmdArgs -> KeyCmds) -> Parser KeyConvertByronKeyCmdArgs -> Parser KeyCmds forall a b. (a -> b) -> Parser a -> Parser b forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b fmap KeyConvertByronKeyCmdArgs -> KeyCmds KeyConvertByronKeyCmd (Parser KeyConvertByronKeyCmdArgs -> Parser KeyCmds) -> Parser KeyConvertByronKeyCmdArgs -> Parser KeyCmds forall a b. (a -> b) -> a -> b $ Maybe Text -> ByronKeyType -> SomeKeyFile 'In -> File () 'Out -> KeyConvertByronKeyCmdArgs KeyConvertByronKeyCmdArgs (Maybe Text -> ByronKeyType -> SomeKeyFile 'In -> File () 'Out -> KeyConvertByronKeyCmdArgs) -> Parser (Maybe Text) -> Parser (ByronKeyType -> SomeKeyFile 'In -> File () 'Out -> KeyConvertByronKeyCmdArgs) forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b <$> Parser Text -> Parser (Maybe Text) forall (f :: * -> *) a. Alternative f => f a -> f (Maybe a) optional Parser Text pPassword Parser (ByronKeyType -> SomeKeyFile 'In -> File () 'Out -> KeyConvertByronKeyCmdArgs) -> Parser ByronKeyType -> Parser (SomeKeyFile 'In -> File () 'Out -> KeyConvertByronKeyCmdArgs) forall a b. Parser (a -> b) -> Parser a -> Parser b forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b <*> Parser ByronKeyType pByronKeyType Parser (SomeKeyFile 'In -> File () 'Out -> KeyConvertByronKeyCmdArgs) -> Parser (SomeKeyFile 'In) -> Parser (File () 'Out -> KeyConvertByronKeyCmdArgs) forall a b. Parser (a -> b) -> Parser a -> Parser b forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b <*> Parser (SomeKeyFile 'In) pByronKeyFile Parser (File () 'Out -> KeyConvertByronKeyCmdArgs) -> Parser (File () 'Out) -> Parser KeyConvertByronKeyCmdArgs forall a b. Parser (a -> b) -> Parser a -> Parser b forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b <*> Parser (File () 'Out) forall content. Parser (File content 'Out) pOutputFile pPassword :: Parser Text pPassword :: Parser Text pPassword = Mod OptionFields Text -> Parser Text forall s. IsString s => Mod OptionFields s -> Parser s Opt.strOption (Mod OptionFields Text -> Parser Text) -> Mod OptionFields Text -> Parser Text forall a b. (a -> b) -> a -> b $ [Mod OptionFields Text] -> Mod OptionFields Text forall a. Monoid a => [a] -> a mconcat [ String -> Mod OptionFields Text forall (f :: * -> *) a. HasName f => String -> Mod f a Opt.long String "password" , String -> Mod OptionFields Text forall (f :: * -> *) a. HasMetavar f => String -> Mod f a Opt.metavar String "TEXT" , String -> Mod OptionFields Text forall (f :: * -> *) a. String -> Mod f a Opt.help String "Password for signing key (if applicable)." ] pByronKeyType :: Parser ByronKeyType pByronKeyType :: Parser ByronKeyType pByronKeyType = [Parser ByronKeyType] -> Parser ByronKeyType forall (t :: * -> *) (f :: * -> *) a. (Foldable t, Alternative f) => t (f a) -> f a asum [ ByronKeyType -> Mod FlagFields ByronKeyType -> Parser ByronKeyType forall a. a -> Mod FlagFields a -> Parser a Opt.flag' (ByronKeyFormat -> ByronKeyType ByronPaymentKey ByronKeyFormat NonLegacyByronKeyFormat) (Mod FlagFields ByronKeyType -> Parser ByronKeyType) -> Mod FlagFields ByronKeyType -> Parser ByronKeyType forall a b. (a -> b) -> a -> b $ [Mod FlagFields ByronKeyType] -> Mod FlagFields ByronKeyType forall a. Monoid a => [a] -> a mconcat [ String -> Mod FlagFields ByronKeyType forall (f :: * -> *) a. HasName f => String -> Mod f a Opt.long String "byron-payment-key-type" , String -> Mod FlagFields ByronKeyType forall (f :: * -> *) a. String -> Mod f a Opt.help String "Use a Byron-era payment key." ] , ByronKeyType -> Mod FlagFields ByronKeyType -> Parser ByronKeyType forall a. a -> Mod FlagFields a -> Parser a Opt.flag' (ByronKeyFormat -> ByronKeyType ByronPaymentKey ByronKeyFormat LegacyByronKeyFormat) (Mod FlagFields ByronKeyType -> Parser ByronKeyType) -> Mod FlagFields ByronKeyType -> Parser ByronKeyType forall a b. (a -> b) -> a -> b $ [Mod FlagFields ByronKeyType] -> Mod FlagFields ByronKeyType forall a. Monoid a => [a] -> a mconcat [ String -> Mod FlagFields ByronKeyType forall (f :: * -> *) a. HasName f => String -> Mod f a Opt.long String "legacy-byron-payment-key-type" , String -> Mod FlagFields ByronKeyType forall (f :: * -> *) a. String -> Mod f a Opt.help String "Use a Byron-era payment key, in legacy SL format." ] , ByronKeyType -> Mod FlagFields ByronKeyType -> Parser ByronKeyType forall a. a -> Mod FlagFields a -> Parser a Opt.flag' (ByronKeyFormat -> ByronKeyType ByronGenesisKey ByronKeyFormat NonLegacyByronKeyFormat) (Mod FlagFields ByronKeyType -> Parser ByronKeyType) -> Mod FlagFields ByronKeyType -> Parser ByronKeyType forall a b. (a -> b) -> a -> b $ [Mod FlagFields ByronKeyType] -> Mod FlagFields ByronKeyType forall a. Monoid a => [a] -> a mconcat [ String -> Mod FlagFields ByronKeyType forall (f :: * -> *) a. HasName f => String -> Mod f a Opt.long String "byron-genesis-key-type" , String -> Mod FlagFields ByronKeyType forall (f :: * -> *) a. String -> Mod f a Opt.help String "Use a Byron-era genesis key." ] , ByronKeyType -> Mod FlagFields ByronKeyType -> Parser ByronKeyType forall a. a -> Mod FlagFields a -> Parser a Opt.flag' (ByronKeyFormat -> ByronKeyType ByronGenesisKey ByronKeyFormat LegacyByronKeyFormat) (Mod FlagFields ByronKeyType -> Parser ByronKeyType) -> Mod FlagFields ByronKeyType -> Parser ByronKeyType forall a b. (a -> b) -> a -> b $ [Mod FlagFields ByronKeyType] -> Mod FlagFields ByronKeyType forall a. Monoid a => [a] -> a mconcat [ String -> Mod FlagFields ByronKeyType forall (f :: * -> *) a. HasName f => String -> Mod f a Opt.long String "legacy-byron-genesis-key-type" , String -> Mod FlagFields ByronKeyType forall (f :: * -> *) a. String -> Mod f a Opt.help String "Use a Byron-era genesis key, in legacy SL format." ] , ByronKeyType -> Mod FlagFields ByronKeyType -> Parser ByronKeyType forall a. a -> Mod FlagFields a -> Parser a Opt.flag' (ByronKeyFormat -> ByronKeyType ByronDelegateKey ByronKeyFormat NonLegacyByronKeyFormat) (Mod FlagFields ByronKeyType -> Parser ByronKeyType) -> Mod FlagFields ByronKeyType -> Parser ByronKeyType forall a b. (a -> b) -> a -> b $ [Mod FlagFields ByronKeyType] -> Mod FlagFields ByronKeyType forall a. Monoid a => [a] -> a mconcat [ String -> Mod FlagFields ByronKeyType forall (f :: * -> *) a. HasName f => String -> Mod f a Opt.long String "byron-genesis-delegate-key-type" , String -> Mod FlagFields ByronKeyType forall (f :: * -> *) a. String -> Mod f a Opt.help String "Use a Byron-era genesis delegate key." ] , ByronKeyType -> Mod FlagFields ByronKeyType -> Parser ByronKeyType forall a. a -> Mod FlagFields a -> Parser a Opt.flag' (ByronKeyFormat -> ByronKeyType ByronDelegateKey ByronKeyFormat LegacyByronKeyFormat) (Mod FlagFields ByronKeyType -> Parser ByronKeyType) -> Mod FlagFields ByronKeyType -> Parser ByronKeyType forall a b. (a -> b) -> a -> b $ [Mod FlagFields ByronKeyType] -> Mod FlagFields ByronKeyType forall a. Monoid a => [a] -> a mconcat [ String -> Mod FlagFields ByronKeyType forall (f :: * -> *) a. HasName f => String -> Mod f a Opt.long String "legacy-byron-genesis-delegate-key-type" , String -> Mod FlagFields ByronKeyType forall (f :: * -> *) a. String -> Mod f a Opt.help String "Use a Byron-era genesis delegate key, in legacy SL format." ] ] pByronKeyFile :: Parser (SomeKeyFile In) pByronKeyFile :: Parser (SomeKeyFile 'In) pByronKeyFile = [Parser (SomeKeyFile 'In)] -> Parser (SomeKeyFile 'In) forall (t :: * -> *) (f :: * -> *) a. (Foldable t, Alternative f) => t (f a) -> f a asum [ SigningKeyFile 'In -> SomeKeyFile 'In forall (direction :: FileDirection). SigningKeyFile direction -> SomeKeyFile direction ASigningKeyFile (SigningKeyFile 'In -> SomeKeyFile 'In) -> Parser (SigningKeyFile 'In) -> Parser (SomeKeyFile 'In) forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b <$> Parser (SigningKeyFile 'In) pByronSigningKeyFile , VerificationKeyFile 'In -> SomeKeyFile 'In forall (direction :: FileDirection). VerificationKeyFile direction -> SomeKeyFile direction AVerificationKeyFile (VerificationKeyFile 'In -> SomeKeyFile 'In) -> Parser (VerificationKeyFile 'In) -> Parser (SomeKeyFile 'In) forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b <$> Parser (VerificationKeyFile 'In) pByronVerificationKeyFile ] pByronSigningKeyFile :: Parser (SigningKeyFile In) pByronSigningKeyFile :: Parser (SigningKeyFile 'In) pByronSigningKeyFile = String -> SigningKeyFile 'In forall content (direction :: FileDirection). String -> File content direction File (String -> SigningKeyFile 'In) -> Parser String -> Parser (SigningKeyFile 'In) forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b <$> String -> String -> Parser String parseFilePath String "byron-signing-key-file" String "Input filepath of the Byron-format signing key." pByronVerificationKeyFile :: Parser (VerificationKeyFile In) pByronVerificationKeyFile :: Parser (VerificationKeyFile 'In) pByronVerificationKeyFile = String -> VerificationKeyFile 'In forall content (direction :: FileDirection). String -> File content direction File (String -> VerificationKeyFile 'In) -> Parser String -> Parser (VerificationKeyFile 'In) forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b <$> String -> String -> Parser String parseFilePath String "byron-verification-key-file" String "Input filepath of the Byron-format verification key." pKeyConvertByronGenesisKeyCmd :: Parser KeyCmds pKeyConvertByronGenesisKeyCmd :: Parser KeyCmds pKeyConvertByronGenesisKeyCmd = (KeyConvertByronGenesisVKeyCmdArgs -> KeyCmds) -> Parser KeyConvertByronGenesisVKeyCmdArgs -> Parser KeyCmds forall a b. (a -> b) -> Parser a -> Parser b forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b fmap KeyConvertByronGenesisVKeyCmdArgs -> KeyCmds KeyConvertByronGenesisVKeyCmd (Parser KeyConvertByronGenesisVKeyCmdArgs -> Parser KeyCmds) -> Parser KeyConvertByronGenesisVKeyCmdArgs -> Parser KeyCmds forall a b. (a -> b) -> a -> b $ VerificationKeyBase64 -> File () 'Out -> KeyConvertByronGenesisVKeyCmdArgs KeyConvertByronGenesisVKeyCmdArgs (VerificationKeyBase64 -> File () 'Out -> KeyConvertByronGenesisVKeyCmdArgs) -> Parser VerificationKeyBase64 -> Parser (File () 'Out -> KeyConvertByronGenesisVKeyCmdArgs) forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b <$> Parser VerificationKeyBase64 pByronGenesisVKeyBase64 Parser (File () 'Out -> KeyConvertByronGenesisVKeyCmdArgs) -> Parser (File () 'Out) -> Parser KeyConvertByronGenesisVKeyCmdArgs forall a b. Parser (a -> b) -> Parser a -> Parser b forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b <*> Parser (File () 'Out) forall content. Parser (File content 'Out) pOutputFile pByronGenesisVKeyBase64 :: Parser VerificationKeyBase64 pByronGenesisVKeyBase64 :: Parser VerificationKeyBase64 pByronGenesisVKeyBase64 = (String -> VerificationKeyBase64) -> Parser String -> Parser VerificationKeyBase64 forall a b. (a -> b) -> Parser a -> Parser b forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b fmap String -> VerificationKeyBase64 VerificationKeyBase64 (Parser String -> Parser VerificationKeyBase64) -> Parser String -> Parser VerificationKeyBase64 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 "byron-genesis-verification-key" , String -> Mod OptionFields String forall (f :: * -> *) a. HasMetavar f => String -> Mod f a Opt.metavar String "BASE64" , String -> Mod OptionFields String forall (f :: * -> *) a. String -> Mod f a Opt.help String "Base64 string for the Byron genesis verification key." ] pKeyConvertITNKeyCmd :: Parser KeyCmds pKeyConvertITNKeyCmd :: Parser KeyCmds pKeyConvertITNKeyCmd = (KeyConvertITNKeyCmdArgs -> KeyCmds) -> Parser KeyConvertITNKeyCmdArgs -> Parser KeyCmds forall a b. (a -> b) -> Parser a -> Parser b forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b fmap KeyConvertITNKeyCmdArgs -> KeyCmds KeyConvertITNKeyCmd (Parser KeyConvertITNKeyCmdArgs -> Parser KeyCmds) -> Parser KeyConvertITNKeyCmdArgs -> Parser KeyCmds forall a b. (a -> b) -> a -> b $ SomeKeyFile 'In -> File () 'Out -> KeyConvertITNKeyCmdArgs KeyConvertITNKeyCmdArgs (SomeKeyFile 'In -> File () 'Out -> KeyConvertITNKeyCmdArgs) -> Parser (SomeKeyFile 'In) -> Parser (File () 'Out -> KeyConvertITNKeyCmdArgs) forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b <$> Parser (SomeKeyFile 'In) forall (direction :: FileDirection). Parser (SomeKeyFile direction) pITNKeyFIle Parser (File () 'Out -> KeyConvertITNKeyCmdArgs) -> Parser (File () 'Out) -> Parser KeyConvertITNKeyCmdArgs forall a b. Parser (a -> b) -> Parser a -> Parser b forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b <*> Parser (File () 'Out) forall content. Parser (File content 'Out) pOutputFile pKeyConvertITNExtendedKeyCmd :: Parser KeyCmds pKeyConvertITNExtendedKeyCmd :: Parser KeyCmds pKeyConvertITNExtendedKeyCmd = (KeyConvertITNExtendedKeyCmdArgs -> KeyCmds) -> Parser KeyConvertITNExtendedKeyCmdArgs -> Parser KeyCmds forall a b. (a -> b) -> Parser a -> Parser b forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b fmap KeyConvertITNExtendedKeyCmdArgs -> KeyCmds KeyConvertITNExtendedKeyCmd (Parser KeyConvertITNExtendedKeyCmdArgs -> Parser KeyCmds) -> Parser KeyConvertITNExtendedKeyCmdArgs -> Parser KeyCmds forall a b. (a -> b) -> a -> b $ SomeKeyFile 'In -> File () 'Out -> KeyConvertITNExtendedKeyCmdArgs KeyConvertITNExtendedKeyCmdArgs (SomeKeyFile 'In -> File () 'Out -> KeyConvertITNExtendedKeyCmdArgs) -> Parser (SomeKeyFile 'In) -> Parser (File () 'Out -> KeyConvertITNExtendedKeyCmdArgs) forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b <$> Parser (SomeKeyFile 'In) forall (direction :: FileDirection). Parser (SomeKeyFile direction) pITNSigningKeyFile Parser (File () 'Out -> KeyConvertITNExtendedKeyCmdArgs) -> Parser (File () 'Out) -> Parser KeyConvertITNExtendedKeyCmdArgs forall a b. Parser (a -> b) -> Parser a -> Parser b forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b <*> Parser (File () 'Out) forall content. Parser (File content 'Out) pOutputFile pKeyConvertITNBip32KeyCmd :: Parser KeyCmds pKeyConvertITNBip32KeyCmd :: Parser KeyCmds pKeyConvertITNBip32KeyCmd = (KeyConvertITNBip32KeyCmdArgs -> KeyCmds) -> Parser KeyConvertITNBip32KeyCmdArgs -> Parser KeyCmds forall a b. (a -> b) -> Parser a -> Parser b forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b fmap KeyConvertITNBip32KeyCmdArgs -> KeyCmds KeyConvertITNBip32KeyCmd (Parser KeyConvertITNBip32KeyCmdArgs -> Parser KeyCmds) -> Parser KeyConvertITNBip32KeyCmdArgs -> Parser KeyCmds forall a b. (a -> b) -> a -> b $ SomeKeyFile 'In -> File () 'Out -> KeyConvertITNBip32KeyCmdArgs KeyConvertITNBip32KeyCmdArgs (SomeKeyFile 'In -> File () 'Out -> KeyConvertITNBip32KeyCmdArgs) -> Parser (SomeKeyFile 'In) -> Parser (File () 'Out -> KeyConvertITNBip32KeyCmdArgs) forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b <$> Parser (SomeKeyFile 'In) forall (direction :: FileDirection). Parser (SomeKeyFile direction) pITNSigningKeyFile Parser (File () 'Out -> KeyConvertITNBip32KeyCmdArgs) -> Parser (File () 'Out) -> Parser KeyConvertITNBip32KeyCmdArgs forall a b. Parser (a -> b) -> Parser a -> Parser b forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b <*> Parser (File () 'Out) forall content. Parser (File content 'Out) pOutputFile pITNKeyFIle :: Parser (SomeKeyFile direction) pITNKeyFIle :: forall (direction :: FileDirection). Parser (SomeKeyFile direction) pITNKeyFIle = [Parser (SomeKeyFile direction)] -> Parser (SomeKeyFile direction) forall (t :: * -> *) (f :: * -> *) a. (Foldable t, Alternative f) => t (f a) -> f a asum [ Parser (SomeKeyFile direction) forall (direction :: FileDirection). Parser (SomeKeyFile direction) pITNSigningKeyFile , Parser (SomeKeyFile direction) forall (direction :: FileDirection). Parser (SomeKeyFile direction) pITNVerificationKeyFile ] pITNSigningKeyFile :: Parser (SomeKeyFile direction) pITNSigningKeyFile :: forall (direction :: FileDirection). Parser (SomeKeyFile direction) pITNSigningKeyFile = SigningKeyFile direction -> SomeKeyFile direction forall (direction :: FileDirection). SigningKeyFile direction -> SomeKeyFile direction ASigningKeyFile (SigningKeyFile direction -> SomeKeyFile direction) -> (String -> SigningKeyFile direction) -> String -> SomeKeyFile direction forall b c a. (b -> c) -> (a -> b) -> a -> c . String -> SigningKeyFile direction forall content (direction :: FileDirection). String -> File content direction File (String -> SomeKeyFile direction) -> Parser String -> Parser (SomeKeyFile direction) forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b <$> String -> String -> Parser String parseFilePath String "itn-signing-key-file" String "Filepath of the ITN signing key." pITNVerificationKeyFile :: Parser (SomeKeyFile direction) pITNVerificationKeyFile :: forall (direction :: FileDirection). Parser (SomeKeyFile direction) pITNVerificationKeyFile = VerificationKeyFile direction -> SomeKeyFile direction forall (direction :: FileDirection). VerificationKeyFile direction -> SomeKeyFile direction AVerificationKeyFile (VerificationKeyFile direction -> SomeKeyFile direction) -> (String -> VerificationKeyFile direction) -> String -> SomeKeyFile direction forall b c a. (b -> c) -> (a -> b) -> a -> c . String -> VerificationKeyFile direction forall content (direction :: FileDirection). String -> File content direction File (String -> SomeKeyFile direction) -> Parser String -> Parser (SomeKeyFile direction) forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b <$> String -> String -> Parser String parseFilePath String "itn-verification-key-file" String "Filepath of the ITN verification key." pKeyConvertCardanoAddressKeyCmd :: Parser KeyCmds pKeyConvertCardanoAddressKeyCmd :: Parser KeyCmds pKeyConvertCardanoAddressKeyCmd = (KeyConvertCardanoAddressKeyCmdArgs -> KeyCmds) -> Parser KeyConvertCardanoAddressKeyCmdArgs -> Parser KeyCmds forall a b. (a -> b) -> Parser a -> Parser b forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b fmap KeyConvertCardanoAddressKeyCmdArgs -> KeyCmds KeyConvertCardanoAddressKeyCmd (Parser KeyConvertCardanoAddressKeyCmdArgs -> Parser KeyCmds) -> Parser KeyConvertCardanoAddressKeyCmdArgs -> Parser KeyCmds forall a b. (a -> b) -> a -> b $ CardanoAddressKeyType -> SigningKeyFile 'In -> File () 'Out -> KeyConvertCardanoAddressKeyCmdArgs KeyConvertCardanoAddressKeyCmdArgs (CardanoAddressKeyType -> SigningKeyFile 'In -> File () 'Out -> KeyConvertCardanoAddressKeyCmdArgs) -> Parser CardanoAddressKeyType -> Parser (SigningKeyFile 'In -> File () 'Out -> KeyConvertCardanoAddressKeyCmdArgs) forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b <$> Parser CardanoAddressKeyType pCardanoAddressKeyType Parser (SigningKeyFile 'In -> File () 'Out -> KeyConvertCardanoAddressKeyCmdArgs) -> Parser (SigningKeyFile 'In) -> Parser (File () 'Out -> KeyConvertCardanoAddressKeyCmdArgs) 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 Parser (File () 'Out -> KeyConvertCardanoAddressKeyCmdArgs) -> Parser (File () 'Out) -> Parser KeyConvertCardanoAddressKeyCmdArgs forall a b. Parser (a -> b) -> Parser a -> Parser b forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b <*> Parser (File () 'Out) forall content. Parser (File content 'Out) pOutputFile pCardanoAddressKeyType :: Parser CardanoAddressKeyType pCardanoAddressKeyType :: Parser CardanoAddressKeyType pCardanoAddressKeyType = [Parser CardanoAddressKeyType] -> Parser CardanoAddressKeyType forall (t :: * -> *) (f :: * -> *) a. (Foldable t, Alternative f) => t (f a) -> f a asum [ CardanoAddressKeyType -> Mod FlagFields CardanoAddressKeyType -> Parser CardanoAddressKeyType forall a. a -> Mod FlagFields a -> Parser a Opt.flag' CardanoAddressKeyType CardanoAddressCommitteeColdKey (Mod FlagFields CardanoAddressKeyType -> Parser CardanoAddressKeyType) -> Mod FlagFields CardanoAddressKeyType -> Parser CardanoAddressKeyType forall a b. (a -> b) -> a -> b $ [Mod FlagFields CardanoAddressKeyType] -> Mod FlagFields CardanoAddressKeyType forall a. Monoid a => [a] -> a mconcat [ String -> Mod FlagFields CardanoAddressKeyType forall (f :: * -> *) a. HasName f => String -> Mod f a Opt.long String "cc-cold-key" , String -> Mod FlagFields CardanoAddressKeyType forall (f :: * -> *) a. String -> Mod f a Opt.help String "Use a committee cold key." ] , CardanoAddressKeyType -> Mod FlagFields CardanoAddressKeyType -> Parser CardanoAddressKeyType forall a. a -> Mod FlagFields a -> Parser a Opt.flag' CardanoAddressKeyType CardanoAddressCommitteeHotKey (Mod FlagFields CardanoAddressKeyType -> Parser CardanoAddressKeyType) -> Mod FlagFields CardanoAddressKeyType -> Parser CardanoAddressKeyType forall a b. (a -> b) -> a -> b $ [Mod FlagFields CardanoAddressKeyType] -> Mod FlagFields CardanoAddressKeyType forall a. Monoid a => [a] -> a mconcat [ String -> Mod FlagFields CardanoAddressKeyType forall (f :: * -> *) a. HasName f => String -> Mod f a Opt.long String "cc-hot-key" , String -> Mod FlagFields CardanoAddressKeyType forall (f :: * -> *) a. String -> Mod f a Opt.help String "Use a committee hot key." ] , CardanoAddressKeyType -> Mod FlagFields CardanoAddressKeyType -> Parser CardanoAddressKeyType forall a. a -> Mod FlagFields a -> Parser a Opt.flag' CardanoAddressKeyType CardanoAddressDRepKey (Mod FlagFields CardanoAddressKeyType -> Parser CardanoAddressKeyType) -> Mod FlagFields CardanoAddressKeyType -> Parser CardanoAddressKeyType forall a b. (a -> b) -> a -> b $ [Mod FlagFields CardanoAddressKeyType] -> Mod FlagFields CardanoAddressKeyType forall a. Monoid a => [a] -> a mconcat [ String -> Mod FlagFields CardanoAddressKeyType forall (f :: * -> *) a. HasName f => String -> Mod f a Opt.long String "drep-key" , String -> Mod FlagFields CardanoAddressKeyType forall (f :: * -> *) a. String -> Mod f a Opt.help String "Use a DRep key." ] , CardanoAddressKeyType -> Mod FlagFields CardanoAddressKeyType -> Parser CardanoAddressKeyType forall a. a -> Mod FlagFields a -> Parser a Opt.flag' CardanoAddressKeyType CardanoAddressShelleyPaymentKey (Mod FlagFields CardanoAddressKeyType -> Parser CardanoAddressKeyType) -> Mod FlagFields CardanoAddressKeyType -> Parser CardanoAddressKeyType forall a b. (a -> b) -> a -> b $ [Mod FlagFields CardanoAddressKeyType] -> Mod FlagFields CardanoAddressKeyType forall a. Monoid a => [a] -> a mconcat [ String -> Mod FlagFields CardanoAddressKeyType forall (f :: * -> *) a. HasName f => String -> Mod f a Opt.long String "shelley-payment-key" , String -> Mod FlagFields CardanoAddressKeyType forall (f :: * -> *) a. String -> Mod f a Opt.help String "Use a Shelley-era extended payment key." ] , CardanoAddressKeyType -> Mod FlagFields CardanoAddressKeyType -> Parser CardanoAddressKeyType forall a. a -> Mod FlagFields a -> Parser a Opt.flag' CardanoAddressKeyType CardanoAddressShelleyStakeKey (Mod FlagFields CardanoAddressKeyType -> Parser CardanoAddressKeyType) -> Mod FlagFields CardanoAddressKeyType -> Parser CardanoAddressKeyType forall a b. (a -> b) -> a -> b $ [Mod FlagFields CardanoAddressKeyType] -> Mod FlagFields CardanoAddressKeyType forall a. Monoid a => [a] -> a mconcat [ String -> Mod FlagFields CardanoAddressKeyType forall (f :: * -> *) a. HasName f => String -> Mod f a Opt.long String "shelley-stake-key" , String -> Mod FlagFields CardanoAddressKeyType forall (f :: * -> *) a. String -> Mod f a Opt.help String "Use a Shelley-era extended stake key." ] , CardanoAddressKeyType -> Mod FlagFields CardanoAddressKeyType -> Parser CardanoAddressKeyType forall a. a -> Mod FlagFields a -> Parser a Opt.flag' CardanoAddressKeyType CardanoAddressIcarusPaymentKey (Mod FlagFields CardanoAddressKeyType -> Parser CardanoAddressKeyType) -> Mod FlagFields CardanoAddressKeyType -> Parser CardanoAddressKeyType forall a b. (a -> b) -> a -> b $ [Mod FlagFields CardanoAddressKeyType] -> Mod FlagFields CardanoAddressKeyType forall a. Monoid a => [a] -> a mconcat [ String -> Mod FlagFields CardanoAddressKeyType forall (f :: * -> *) a. HasName f => String -> Mod f a Opt.long String "icarus-payment-key" , String -> Mod FlagFields CardanoAddressKeyType forall (f :: * -> *) a. String -> Mod f a Opt.help String "Use a Byron-era extended payment key formatted in the Icarus style." ] , CardanoAddressKeyType -> Mod FlagFields CardanoAddressKeyType -> Parser CardanoAddressKeyType forall a. a -> Mod FlagFields a -> Parser a Opt.flag' CardanoAddressKeyType CardanoAddressByronPaymentKey (Mod FlagFields CardanoAddressKeyType -> Parser CardanoAddressKeyType) -> Mod FlagFields CardanoAddressKeyType -> Parser CardanoAddressKeyType forall a b. (a -> b) -> a -> b $ [Mod FlagFields CardanoAddressKeyType] -> Mod FlagFields CardanoAddressKeyType forall a. Monoid a => [a] -> a mconcat [ String -> Mod FlagFields CardanoAddressKeyType forall (f :: * -> *) a. HasName f => String -> Mod f a Opt.long String "byron-payment-key" , String -> Mod FlagFields CardanoAddressKeyType forall (f :: * -> *) a. String -> Mod f a Opt.help String "Use a Byron-era extended payment key formatted in the deprecated Byron style." ] ]