{-# LANGUAGE DataKinds #-} {-# LANGUAGE FlexibleContexts #-} {-# LANGUAGE GADTs #-} {-# LANGUAGE ScopedTypeVariables #-} module Cardano.CLI.Options.Address ( pAddressCmds ) where import Cardano.CLI.Commands.Address import Cardano.CLI.Environment (EnvCli (..)) import Cardano.CLI.EraBased.Options.Common import Cardano.CLI.Parser import Data.Foldable import Options.Applicative hiding (help, str) import qualified Options.Applicative as Opt pAddressCmds :: () => EnvCli -> Parser AddressCmds pAddressCmds :: EnvCli -> Parser AddressCmds pAddressCmds EnvCli envCli = let addressParsers :: Parser AddressCmds addressParsers = [Parser AddressCmds] -> Parser AddressCmds forall (t :: * -> *) (f :: * -> *) a. (Foldable t, Alternative f) => t (f a) -> f a asum [ String -> ParserInfo AddressCmds -> Parser AddressCmds forall a. String -> ParserInfo a -> Parser a subParser String "key-gen" (ParserInfo AddressCmds -> Parser AddressCmds) -> ParserInfo AddressCmds -> Parser AddressCmds forall a b. (a -> b) -> a -> b $ Parser AddressCmds -> InfoMod AddressCmds -> ParserInfo AddressCmds forall a. Parser a -> InfoMod a -> ParserInfo a Opt.info Parser AddressCmds pAddressKeyGen (InfoMod AddressCmds -> ParserInfo AddressCmds) -> InfoMod AddressCmds -> ParserInfo AddressCmds forall a b. (a -> b) -> a -> b $ String -> InfoMod AddressCmds forall a. String -> InfoMod a Opt.progDesc String "Create an address key pair." , String -> ParserInfo AddressCmds -> Parser AddressCmds forall a. String -> ParserInfo a -> Parser a subParser String "key-hash" (ParserInfo AddressCmds -> Parser AddressCmds) -> ParserInfo AddressCmds -> Parser AddressCmds forall a b. (a -> b) -> a -> b $ Parser AddressCmds -> InfoMod AddressCmds -> ParserInfo AddressCmds forall a. Parser a -> InfoMod a -> ParserInfo a Opt.info Parser AddressCmds pAddressKeyHash (InfoMod AddressCmds -> ParserInfo AddressCmds) -> InfoMod AddressCmds -> ParserInfo AddressCmds forall a b. (a -> b) -> a -> b $ String -> InfoMod AddressCmds forall a. String -> InfoMod a Opt.progDesc String "Print the hash of an address key." , String -> ParserInfo AddressCmds -> Parser AddressCmds forall a. String -> ParserInfo a -> Parser a subParser String "build" (ParserInfo AddressCmds -> Parser AddressCmds) -> ParserInfo AddressCmds -> Parser AddressCmds forall a b. (a -> b) -> a -> b $ Parser AddressCmds -> InfoMod AddressCmds -> ParserInfo AddressCmds forall a. Parser a -> InfoMod a -> ParserInfo a Opt.info (EnvCli -> Parser AddressCmds pAddressBuild EnvCli envCli) (InfoMod AddressCmds -> ParserInfo AddressCmds) -> InfoMod AddressCmds -> ParserInfo AddressCmds forall a b. (a -> b) -> a -> b $ String -> InfoMod AddressCmds forall a. String -> InfoMod a Opt.progDesc String "Build a Shelley payment address, with optional delegation to a stake address." , String -> ParserInfo AddressCmds -> Parser AddressCmds forall a. String -> ParserInfo a -> Parser a subParser String "info" (ParserInfo AddressCmds -> Parser AddressCmds) -> ParserInfo AddressCmds -> Parser AddressCmds forall a b. (a -> b) -> a -> b $ Parser AddressCmds -> InfoMod AddressCmds -> ParserInfo AddressCmds forall a. Parser a -> InfoMod a -> ParserInfo a Opt.info Parser AddressCmds pAddressInfo (InfoMod AddressCmds -> ParserInfo AddressCmds) -> InfoMod AddressCmds -> ParserInfo AddressCmds forall a b. (a -> b) -> a -> b $ String -> InfoMod AddressCmds forall a. String -> InfoMod a Opt.progDesc String "Print information about an address." ] in String -> ParserInfo AddressCmds -> Parser AddressCmds forall a. String -> ParserInfo a -> Parser a subParser String "address" (ParserInfo AddressCmds -> Parser AddressCmds) -> ParserInfo AddressCmds -> Parser AddressCmds forall a b. (a -> b) -> a -> b $ Parser AddressCmds -> InfoMod AddressCmds -> ParserInfo AddressCmds forall a. Parser a -> InfoMod a -> ParserInfo a Opt.info Parser AddressCmds addressParsers ( String -> InfoMod AddressCmds forall a. String -> InfoMod a Opt.progDesc (String -> InfoMod AddressCmds) -> String -> InfoMod AddressCmds forall a b. (a -> b) -> a -> b $ [String] -> String forall a. Monoid a => [a] -> a mconcat [ String "Payment address commands." ] ) pAddressKeyGen :: Parser AddressCmds pAddressKeyGen :: Parser AddressCmds pAddressKeyGen = KeyOutputFormat -> AddressKeyType -> VerificationKeyFile 'Out -> SigningKeyFile 'Out -> AddressCmds AddressKeyGen (KeyOutputFormat -> AddressKeyType -> VerificationKeyFile 'Out -> SigningKeyFile 'Out -> AddressCmds) -> Parser KeyOutputFormat -> Parser (AddressKeyType -> VerificationKeyFile 'Out -> SigningKeyFile 'Out -> AddressCmds) forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b <$> Parser KeyOutputFormat pKeyOutputFormat Parser (AddressKeyType -> VerificationKeyFile 'Out -> SigningKeyFile 'Out -> AddressCmds) -> Parser AddressKeyType -> Parser (VerificationKeyFile 'Out -> SigningKeyFile 'Out -> AddressCmds) forall a b. Parser (a -> b) -> Parser a -> Parser b forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b <*> Parser AddressKeyType pAddressKeyType Parser (VerificationKeyFile 'Out -> SigningKeyFile 'Out -> AddressCmds) -> Parser (VerificationKeyFile 'Out) -> Parser (SigningKeyFile 'Out -> AddressCmds) 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 Parser (SigningKeyFile 'Out -> AddressCmds) -> Parser (SigningKeyFile 'Out) -> Parser AddressCmds 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 pAddressKeyHash :: Parser AddressCmds pAddressKeyHash :: Parser AddressCmds pAddressKeyHash = VerificationKeyTextOrFile -> Maybe (File () 'Out) -> AddressCmds AddressKeyHash (VerificationKeyTextOrFile -> Maybe (File () 'Out) -> AddressCmds) -> Parser VerificationKeyTextOrFile -> Parser (Maybe (File () 'Out) -> AddressCmds) forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b <$> Parser VerificationKeyTextOrFile pPaymentVerificationKeyTextOrFile Parser (Maybe (File () 'Out) -> AddressCmds) -> Parser (Maybe (File () 'Out)) -> Parser AddressCmds 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 pAddressBuild :: EnvCli -> Parser AddressCmds pAddressBuild :: EnvCli -> Parser AddressCmds pAddressBuild EnvCli envCli = PaymentVerifier -> Maybe StakeIdentifier -> NetworkId -> Maybe (File () 'Out) -> AddressCmds AddressBuild (PaymentVerifier -> Maybe StakeIdentifier -> NetworkId -> Maybe (File () 'Out) -> AddressCmds) -> Parser PaymentVerifier -> Parser (Maybe StakeIdentifier -> NetworkId -> Maybe (File () 'Out) -> AddressCmds) forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b <$> Parser PaymentVerifier pPaymentVerifier Parser (Maybe StakeIdentifier -> NetworkId -> Maybe (File () 'Out) -> AddressCmds) -> Parser (Maybe StakeIdentifier) -> Parser (NetworkId -> Maybe (File () 'Out) -> AddressCmds) forall a b. Parser (a -> b) -> Parser a -> Parser b forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b <*> Parser StakeIdentifier -> Parser (Maybe StakeIdentifier) forall (f :: * -> *) a. Alternative f => f a -> f (Maybe a) Opt.optional (Maybe String -> Parser StakeIdentifier pStakeIdentifier Maybe String forall a. Maybe a Nothing) Parser (NetworkId -> Maybe (File () 'Out) -> AddressCmds) -> Parser NetworkId -> Parser (Maybe (File () 'Out) -> AddressCmds) 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) -> AddressCmds) -> Parser (Maybe (File () 'Out)) -> Parser AddressCmds 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 pAddressInfo :: Parser AddressCmds pAddressInfo :: Parser AddressCmds pAddressInfo = Text -> Maybe (File () 'Out) -> AddressCmds AddressInfo (Text -> Maybe (File () 'Out) -> AddressCmds) -> Parser Text -> Parser (Maybe (File () 'Out) -> AddressCmds) forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b <$> Parser Text pAddress Parser (Maybe (File () 'Out) -> AddressCmds) -> Parser (Maybe (File () 'Out)) -> Parser AddressCmds 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