{-# LANGUAGE DataKinds #-} {-# LANGUAGE FlexibleContexts #-} {-# LANGUAGE GADTs #-} {-# LANGUAGE ScopedTypeVariables #-} module Cardano.CLI.Compatible.StakePool.Option ( pCompatibleStakePoolCmds ) where import Cardano.Api import Cardano.CLI.Compatible.StakePool.Command import Cardano.CLI.Environment (EnvCli (..)) import Cardano.CLI.EraBased.Common.Option import Cardano.CLI.Parser import Options.Applicative hiding (help, str) import Options.Applicative qualified as Opt pCompatibleStakePoolCmds :: () => ShelleyBasedEra era -> EnvCli -> Maybe (Parser (CompatibleStakePoolCmds era)) pCompatibleStakePoolCmds :: forall era. ShelleyBasedEra era -> EnvCli -> Maybe (Parser (CompatibleStakePoolCmds era)) pCompatibleStakePoolCmds ShelleyBasedEra era era EnvCli envCli = String -> InfoMod (CompatibleStakePoolCmds era) -> [Maybe (Parser (CompatibleStakePoolCmds era))] -> Maybe (Parser (CompatibleStakePoolCmds era)) forall a. String -> InfoMod a -> [Maybe (Parser a)] -> Maybe (Parser a) subInfoParser String "stake-pool" ( String -> InfoMod (CompatibleStakePoolCmds era) forall a. String -> InfoMod a Opt.progDesc (String -> InfoMod (CompatibleStakePoolCmds era)) -> String -> InfoMod (CompatibleStakePoolCmds era) forall a b. (a -> b) -> a -> b $ [String] -> String forall a. Monoid a => [a] -> a mconcat [ String "Stake pool commands." ] ) [ ShelleyBasedEra era -> EnvCli -> Maybe (Parser (CompatibleStakePoolCmds era)) forall era. ShelleyBasedEra era -> EnvCli -> Maybe (Parser (CompatibleStakePoolCmds era)) pCompatibleStakePoolRegistrationCertificateCmd ShelleyBasedEra era era EnvCli envCli ] pCompatibleStakePoolRegistrationCertificateCmd :: () => ShelleyBasedEra era -> EnvCli -> Maybe (Parser (CompatibleStakePoolCmds era)) pCompatibleStakePoolRegistrationCertificateCmd :: forall era. ShelleyBasedEra era -> EnvCli -> Maybe (Parser (CompatibleStakePoolCmds era)) pCompatibleStakePoolRegistrationCertificateCmd ShelleyBasedEra era era EnvCli envCli = do ShelleyBasedEra era w <- ShelleyBasedEra era -> Maybe (ShelleyBasedEra era) forall (eon :: * -> *) era. Eon eon => ShelleyBasedEra era -> Maybe (eon era) forShelleyBasedEraMaybeEon ShelleyBasedEra era era Parser (CompatibleStakePoolCmds era) -> Maybe (Parser (CompatibleStakePoolCmds era)) forall a. a -> Maybe a forall (f :: * -> *) a. Applicative f => a -> f a pure (Parser (CompatibleStakePoolCmds era) -> Maybe (Parser (CompatibleStakePoolCmds era))) -> Parser (CompatibleStakePoolCmds era) -> Maybe (Parser (CompatibleStakePoolCmds era)) forall a b. (a -> b) -> a -> b $ Mod CommandFields (CompatibleStakePoolCmds era) -> Parser (CompatibleStakePoolCmds era) forall a. Mod CommandFields a -> Parser a Opt.hsubparser (Mod CommandFields (CompatibleStakePoolCmds era) -> Parser (CompatibleStakePoolCmds era)) -> Mod CommandFields (CompatibleStakePoolCmds era) -> Parser (CompatibleStakePoolCmds era) forall a b. (a -> b) -> a -> b $ String -> ParserInfo (CompatibleStakePoolCmds era) -> Mod CommandFields (CompatibleStakePoolCmds era) forall a. String -> ParserInfo a -> Mod CommandFields a commandWithMetavar String "registration-certificate" (ParserInfo (CompatibleStakePoolCmds era) -> Mod CommandFields (CompatibleStakePoolCmds era)) -> ParserInfo (CompatibleStakePoolCmds era) -> Mod CommandFields (CompatibleStakePoolCmds era) forall a b. (a -> b) -> a -> b $ Parser (CompatibleStakePoolCmds era) -> InfoMod (CompatibleStakePoolCmds era) -> ParserInfo (CompatibleStakePoolCmds era) forall a. Parser a -> InfoMod a -> ParserInfo a Opt.info ( (CompatibleStakePoolRegistrationCertificateCmdArgs era -> CompatibleStakePoolCmds era) -> Parser (CompatibleStakePoolRegistrationCertificateCmdArgs era) -> Parser (CompatibleStakePoolCmds era) forall a b. (a -> b) -> Parser a -> Parser b forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b fmap CompatibleStakePoolRegistrationCertificateCmdArgs era -> CompatibleStakePoolCmds era forall era. CompatibleStakePoolRegistrationCertificateCmdArgs era -> CompatibleStakePoolCmds era CompatibleStakePoolRegistrationCertificateCmd (Parser (CompatibleStakePoolRegistrationCertificateCmdArgs era) -> Parser (CompatibleStakePoolCmds era)) -> Parser (CompatibleStakePoolRegistrationCertificateCmdArgs era) -> Parser (CompatibleStakePoolCmds era) forall a b. (a -> b) -> a -> b $ ShelleyBasedEra era -> VerificationKeyOrFile StakePoolKey -> VerificationKeyOrFile VrfKey -> Coin -> Coin -> Rational -> VerificationKeyOrFile StakeKey -> [VerificationKeyOrFile StakeKey] -> [StakePoolRelay] -> Maybe (PotentiallyCheckedAnchor StakePoolMetadataReference StakePoolMetadataReference) -> NetworkId -> File () 'Out -> CompatibleStakePoolRegistrationCertificateCmdArgs era forall era. ShelleyBasedEra era -> VerificationKeyOrFile StakePoolKey -> VerificationKeyOrFile VrfKey -> Coin -> Coin -> Rational -> VerificationKeyOrFile StakeKey -> [VerificationKeyOrFile StakeKey] -> [StakePoolRelay] -> Maybe (PotentiallyCheckedAnchor StakePoolMetadataReference StakePoolMetadataReference) -> NetworkId -> File () 'Out -> CompatibleStakePoolRegistrationCertificateCmdArgs era CompatibleStakePoolRegistrationCertificateCmdArgs ShelleyBasedEra era w (VerificationKeyOrFile StakePoolKey -> VerificationKeyOrFile VrfKey -> Coin -> Coin -> Rational -> VerificationKeyOrFile StakeKey -> [VerificationKeyOrFile StakeKey] -> [StakePoolRelay] -> Maybe (PotentiallyCheckedAnchor StakePoolMetadataReference StakePoolMetadataReference) -> NetworkId -> File () 'Out -> CompatibleStakePoolRegistrationCertificateCmdArgs era) -> Parser (VerificationKeyOrFile StakePoolKey) -> Parser (VerificationKeyOrFile VrfKey -> Coin -> Coin -> Rational -> VerificationKeyOrFile StakeKey -> [VerificationKeyOrFile StakeKey] -> [StakePoolRelay] -> Maybe (PotentiallyCheckedAnchor StakePoolMetadataReference StakePoolMetadataReference) -> NetworkId -> File () 'Out -> CompatibleStakePoolRegistrationCertificateCmdArgs era) forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b <$> Maybe String -> Parser (VerificationKeyOrFile StakePoolKey) pStakePoolVerificationKeyOrFile Maybe String forall a. Maybe a Nothing Parser (VerificationKeyOrFile VrfKey -> Coin -> Coin -> Rational -> VerificationKeyOrFile StakeKey -> [VerificationKeyOrFile StakeKey] -> [StakePoolRelay] -> Maybe (PotentiallyCheckedAnchor StakePoolMetadataReference StakePoolMetadataReference) -> NetworkId -> File () 'Out -> CompatibleStakePoolRegistrationCertificateCmdArgs era) -> Parser (VerificationKeyOrFile VrfKey) -> Parser (Coin -> Coin -> Rational -> VerificationKeyOrFile StakeKey -> [VerificationKeyOrFile StakeKey] -> [StakePoolRelay] -> Maybe (PotentiallyCheckedAnchor StakePoolMetadataReference StakePoolMetadataReference) -> NetworkId -> File () 'Out -> CompatibleStakePoolRegistrationCertificateCmdArgs era) forall a b. Parser (a -> b) -> Parser a -> Parser b forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b <*> Parser (VerificationKeyOrFile VrfKey) pVrfVerificationKeyOrFile Parser (Coin -> Coin -> Rational -> VerificationKeyOrFile StakeKey -> [VerificationKeyOrFile StakeKey] -> [StakePoolRelay] -> Maybe (PotentiallyCheckedAnchor StakePoolMetadataReference StakePoolMetadataReference) -> NetworkId -> File () 'Out -> CompatibleStakePoolRegistrationCertificateCmdArgs era) -> Parser Coin -> Parser (Coin -> Rational -> VerificationKeyOrFile StakeKey -> [VerificationKeyOrFile StakeKey] -> [StakePoolRelay] -> Maybe (PotentiallyCheckedAnchor StakePoolMetadataReference StakePoolMetadataReference) -> NetworkId -> File () 'Out -> CompatibleStakePoolRegistrationCertificateCmdArgs era) 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 pPoolPledge Parser (Coin -> Rational -> VerificationKeyOrFile StakeKey -> [VerificationKeyOrFile StakeKey] -> [StakePoolRelay] -> Maybe (PotentiallyCheckedAnchor StakePoolMetadataReference StakePoolMetadataReference) -> NetworkId -> File () 'Out -> CompatibleStakePoolRegistrationCertificateCmdArgs era) -> Parser Coin -> Parser (Rational -> VerificationKeyOrFile StakeKey -> [VerificationKeyOrFile StakeKey] -> [StakePoolRelay] -> Maybe (PotentiallyCheckedAnchor StakePoolMetadataReference StakePoolMetadataReference) -> NetworkId -> File () 'Out -> CompatibleStakePoolRegistrationCertificateCmdArgs era) 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 pPoolCost Parser (Rational -> VerificationKeyOrFile StakeKey -> [VerificationKeyOrFile StakeKey] -> [StakePoolRelay] -> Maybe (PotentiallyCheckedAnchor StakePoolMetadataReference StakePoolMetadataReference) -> NetworkId -> File () 'Out -> CompatibleStakePoolRegistrationCertificateCmdArgs era) -> Parser Rational -> Parser (VerificationKeyOrFile StakeKey -> [VerificationKeyOrFile StakeKey] -> [StakePoolRelay] -> Maybe (PotentiallyCheckedAnchor StakePoolMetadataReference StakePoolMetadataReference) -> NetworkId -> File () 'Out -> CompatibleStakePoolRegistrationCertificateCmdArgs era) 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 pPoolMargin Parser (VerificationKeyOrFile StakeKey -> [VerificationKeyOrFile StakeKey] -> [StakePoolRelay] -> Maybe (PotentiallyCheckedAnchor StakePoolMetadataReference StakePoolMetadataReference) -> NetworkId -> File () 'Out -> CompatibleStakePoolRegistrationCertificateCmdArgs era) -> Parser (VerificationKeyOrFile StakeKey) -> Parser ([VerificationKeyOrFile StakeKey] -> [StakePoolRelay] -> Maybe (PotentiallyCheckedAnchor StakePoolMetadataReference StakePoolMetadataReference) -> NetworkId -> File () 'Out -> CompatibleStakePoolRegistrationCertificateCmdArgs era) forall a b. Parser (a -> b) -> Parser a -> Parser b forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b <*> Parser (VerificationKeyOrFile StakeKey) pRewardAcctVerificationKeyOrFile Parser ([VerificationKeyOrFile StakeKey] -> [StakePoolRelay] -> Maybe (PotentiallyCheckedAnchor StakePoolMetadataReference StakePoolMetadataReference) -> NetworkId -> File () 'Out -> CompatibleStakePoolRegistrationCertificateCmdArgs era) -> Parser [VerificationKeyOrFile StakeKey] -> Parser ([StakePoolRelay] -> Maybe (PotentiallyCheckedAnchor StakePoolMetadataReference StakePoolMetadataReference) -> NetworkId -> File () 'Out -> CompatibleStakePoolRegistrationCertificateCmdArgs era) forall a b. Parser (a -> b) -> Parser a -> Parser b forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b <*> Parser (VerificationKeyOrFile StakeKey) -> Parser [VerificationKeyOrFile StakeKey] forall a. Parser a -> Parser [a] forall (f :: * -> *) a. Alternative f => f a -> f [a] some Parser (VerificationKeyOrFile StakeKey) pPoolOwnerVerificationKeyOrFile Parser ([StakePoolRelay] -> Maybe (PotentiallyCheckedAnchor StakePoolMetadataReference StakePoolMetadataReference) -> NetworkId -> File () 'Out -> CompatibleStakePoolRegistrationCertificateCmdArgs era) -> Parser [StakePoolRelay] -> Parser (Maybe (PotentiallyCheckedAnchor StakePoolMetadataReference StakePoolMetadataReference) -> NetworkId -> File () 'Out -> CompatibleStakePoolRegistrationCertificateCmdArgs era) forall a b. Parser (a -> b) -> Parser a -> Parser b forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b <*> Parser StakePoolRelay -> Parser [StakePoolRelay] forall a. Parser a -> Parser [a] forall (f :: * -> *) a. Alternative f => f a -> f [a] many Parser StakePoolRelay pPoolRelay Parser (Maybe (PotentiallyCheckedAnchor StakePoolMetadataReference StakePoolMetadataReference) -> NetworkId -> File () 'Out -> CompatibleStakePoolRegistrationCertificateCmdArgs era) -> Parser (Maybe (PotentiallyCheckedAnchor StakePoolMetadataReference StakePoolMetadataReference)) -> Parser (NetworkId -> File () 'Out -> CompatibleStakePoolRegistrationCertificateCmdArgs era) forall a b. Parser (a -> b) -> Parser a -> Parser b forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b <*> Parser (PotentiallyCheckedAnchor StakePoolMetadataReference StakePoolMetadataReference) -> Parser (Maybe (PotentiallyCheckedAnchor StakePoolMetadataReference StakePoolMetadataReference)) forall (f :: * -> *) a. Alternative f => f a -> f (Maybe a) optional ( Parser (MustCheckHash StakePoolMetadataReference) -> Parser StakePoolMetadataReference -> Parser (PotentiallyCheckedAnchor StakePoolMetadataReference StakePoolMetadataReference) forall anchorType anchor. Parser (MustCheckHash anchorType) -> Parser anchor -> Parser (PotentiallyCheckedAnchor anchorType anchor) pPotentiallyCheckedAnchorData Parser (MustCheckHash StakePoolMetadataReference) pMustCheckStakeMetadataHash Parser StakePoolMetadataReference pStakePoolMetadataReference ) Parser (NetworkId -> File () 'Out -> CompatibleStakePoolRegistrationCertificateCmdArgs era) -> Parser NetworkId -> Parser (File () 'Out -> CompatibleStakePoolRegistrationCertificateCmdArgs era) 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 (File () 'Out -> CompatibleStakePoolRegistrationCertificateCmdArgs era) -> Parser (File () 'Out) -> Parser (CompatibleStakePoolRegistrationCertificateCmdArgs era) 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 ) (InfoMod (CompatibleStakePoolCmds era) -> ParserInfo (CompatibleStakePoolCmds era)) -> InfoMod (CompatibleStakePoolCmds era) -> ParserInfo (CompatibleStakePoolCmds era) forall a b. (a -> b) -> a -> b $ String -> InfoMod (CompatibleStakePoolCmds era) forall a. String -> InfoMod a Opt.progDesc String "Create a stake pool registration certificate"