{-# LANGUAGE DataKinds #-} {-# LANGUAGE TypeFamilies #-} module Cardano.CLI.EraBased.Options.Governance.Committee ( pGovernanceCommitteeCmds ) where import Cardano.Api import qualified Cardano.Api.Ledger as L import Cardano.CLI.EraBased.Commands.Governance.Committee import Cardano.CLI.EraBased.Options.Common hiding (pAnchorUrl) import Cardano.CLI.Parser import Cardano.CLI.Read import Cardano.CLI.Types.Key import Data.Foldable (asum) import Options.Applicative (Parser, optional) import qualified Options.Applicative as Opt pGovernanceCommitteeCmds :: () => ShelleyBasedEra era -> Maybe (Parser (GovernanceCommitteeCmds era)) pGovernanceCommitteeCmds :: forall era. ShelleyBasedEra era -> Maybe (Parser (GovernanceCommitteeCmds era)) pGovernanceCommitteeCmds ShelleyBasedEra era era = String -> InfoMod (GovernanceCommitteeCmds era) -> [Maybe (Parser (GovernanceCommitteeCmds era))] -> Maybe (Parser (GovernanceCommitteeCmds era)) forall a. String -> InfoMod a -> [Maybe (Parser a)] -> Maybe (Parser a) subInfoParser String "committee" ( String -> InfoMod (GovernanceCommitteeCmds era) forall a. String -> InfoMod a Opt.progDesc (String -> InfoMod (GovernanceCommitteeCmds era)) -> String -> InfoMod (GovernanceCommitteeCmds era) forall a b. (a -> b) -> a -> b $ [String] -> String forall a. Monoid a => [a] -> a mconcat [ String "Committee member commands." ] ) [ ShelleyBasedEra era -> Maybe (Parser (GovernanceCommitteeCmds era)) forall era. ShelleyBasedEra era -> Maybe (Parser (GovernanceCommitteeCmds era)) pGovernanceCommitteeKeyGenColdCmd ShelleyBasedEra era era , ShelleyBasedEra era -> Maybe (Parser (GovernanceCommitteeCmds era)) forall era. ShelleyBasedEra era -> Maybe (Parser (GovernanceCommitteeCmds era)) pGovernanceCommitteeKeyGenHotCmd ShelleyBasedEra era era , ShelleyBasedEra era -> Maybe (Parser (GovernanceCommitteeCmds era)) forall era. ShelleyBasedEra era -> Maybe (Parser (GovernanceCommitteeCmds era)) pGovernanceCommitteeKeyHashCmd ShelleyBasedEra era era , ShelleyBasedEra era -> Maybe (Parser (GovernanceCommitteeCmds era)) forall era. ShelleyBasedEra era -> Maybe (Parser (GovernanceCommitteeCmds era)) pGovernanceCommitteeCreateHotKeyAuthorizationCertificateCmd ShelleyBasedEra era era , ShelleyBasedEra era -> Maybe (Parser (GovernanceCommitteeCmds era)) forall era. ShelleyBasedEra era -> Maybe (Parser (GovernanceCommitteeCmds era)) pGovernanceCommitteeCreateColdKeyResignationCertificateCmd ShelleyBasedEra era era ] pGovernanceCommitteeKeyGenColdCmd :: () => ShelleyBasedEra era -> Maybe (Parser (GovernanceCommitteeCmds era)) pGovernanceCommitteeKeyGenColdCmd :: forall era. ShelleyBasedEra era -> Maybe (Parser (GovernanceCommitteeCmds era)) pGovernanceCommitteeKeyGenColdCmd ShelleyBasedEra era era = do ConwayEraOnwards era w <- ShelleyBasedEra era -> Maybe (ConwayEraOnwards era) forall (eon :: * -> *) era. Eon eon => ShelleyBasedEra era -> Maybe (eon era) forShelleyBasedEraMaybeEon ShelleyBasedEra era era Parser (GovernanceCommitteeCmds era) -> Maybe (Parser (GovernanceCommitteeCmds era)) forall a. a -> Maybe a forall (f :: * -> *) a. Applicative f => a -> f a pure (Parser (GovernanceCommitteeCmds era) -> Maybe (Parser (GovernanceCommitteeCmds era))) -> Parser (GovernanceCommitteeCmds era) -> Maybe (Parser (GovernanceCommitteeCmds era)) forall a b. (a -> b) -> a -> b $ String -> ParserInfo (GovernanceCommitteeCmds era) -> Parser (GovernanceCommitteeCmds era) forall a. String -> ParserInfo a -> Parser a subParser String "key-gen-cold" (ParserInfo (GovernanceCommitteeCmds era) -> Parser (GovernanceCommitteeCmds era)) -> ParserInfo (GovernanceCommitteeCmds era) -> Parser (GovernanceCommitteeCmds era) forall a b. (a -> b) -> a -> b $ Parser (GovernanceCommitteeCmds era) -> InfoMod (GovernanceCommitteeCmds era) -> ParserInfo (GovernanceCommitteeCmds era) forall a. Parser a -> InfoMod a -> ParserInfo a Opt.info (ConwayEraOnwards era -> Parser (GovernanceCommitteeCmds era) forall era. ConwayEraOnwards era -> Parser (GovernanceCommitteeCmds era) pCmd ConwayEraOnwards era w) (InfoMod (GovernanceCommitteeCmds era) -> ParserInfo (GovernanceCommitteeCmds era)) -> InfoMod (GovernanceCommitteeCmds era) -> ParserInfo (GovernanceCommitteeCmds era) forall a b. (a -> b) -> a -> b $ String -> InfoMod (GovernanceCommitteeCmds era) forall a. String -> InfoMod a Opt.progDesc (String -> InfoMod (GovernanceCommitteeCmds era)) -> String -> InfoMod (GovernanceCommitteeCmds era) forall a b. (a -> b) -> a -> b $ [String] -> String forall a. Monoid a => [a] -> a mconcat [ String "Create a cold key pair for a Constitutional Committee Member" ] where pCmd :: () => ConwayEraOnwards era -> Parser (GovernanceCommitteeCmds era) pCmd :: forall era. ConwayEraOnwards era -> Parser (GovernanceCommitteeCmds era) pCmd ConwayEraOnwards era w = (GovernanceCommitteeKeyGenColdCmdArgs era -> GovernanceCommitteeCmds era) -> Parser (GovernanceCommitteeKeyGenColdCmdArgs era) -> Parser (GovernanceCommitteeCmds era) forall a b. (a -> b) -> Parser a -> Parser b forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b fmap GovernanceCommitteeKeyGenColdCmdArgs era -> GovernanceCommitteeCmds era forall era. GovernanceCommitteeKeyGenColdCmdArgs era -> GovernanceCommitteeCmds era GovernanceCommitteeKeyGenColdCmd (Parser (GovernanceCommitteeKeyGenColdCmdArgs era) -> Parser (GovernanceCommitteeCmds era)) -> Parser (GovernanceCommitteeKeyGenColdCmdArgs era) -> Parser (GovernanceCommitteeCmds era) forall a b. (a -> b) -> a -> b $ ConwayEraOnwards era -> File (VerificationKey ()) 'Out -> File (SigningKey ()) 'Out -> GovernanceCommitteeKeyGenColdCmdArgs era forall era. ConwayEraOnwards era -> File (VerificationKey ()) 'Out -> File (SigningKey ()) 'Out -> GovernanceCommitteeKeyGenColdCmdArgs era GovernanceCommitteeKeyGenColdCmdArgs ConwayEraOnwards era w (File (VerificationKey ()) 'Out -> File (SigningKey ()) 'Out -> GovernanceCommitteeKeyGenColdCmdArgs era) -> Parser (File (VerificationKey ()) 'Out) -> Parser (File (SigningKey ()) 'Out -> GovernanceCommitteeKeyGenColdCmdArgs era) forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b <$> Parser (File (VerificationKey ()) 'Out) forall (direction :: FileDirection). Parser (VerificationKeyFile direction) pColdVerificationKeyFile Parser (File (SigningKey ()) 'Out -> GovernanceCommitteeKeyGenColdCmdArgs era) -> Parser (File (SigningKey ()) 'Out) -> Parser (GovernanceCommitteeKeyGenColdCmdArgs 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 (SigningKey ()) 'Out) forall keyrole (direction :: FileDirection). Parser (File (SigningKey keyrole) direction) pColdSigningKeyFile pGovernanceCommitteeKeyGenHotCmd :: () => ShelleyBasedEra era -> Maybe (Parser (GovernanceCommitteeCmds era)) pGovernanceCommitteeKeyGenHotCmd :: forall era. ShelleyBasedEra era -> Maybe (Parser (GovernanceCommitteeCmds era)) pGovernanceCommitteeKeyGenHotCmd ShelleyBasedEra era era = do ConwayEraOnwards era w <- ShelleyBasedEra era -> Maybe (ConwayEraOnwards era) forall (eon :: * -> *) era. Eon eon => ShelleyBasedEra era -> Maybe (eon era) forShelleyBasedEraMaybeEon ShelleyBasedEra era era Parser (GovernanceCommitteeCmds era) -> Maybe (Parser (GovernanceCommitteeCmds era)) forall a. a -> Maybe a forall (f :: * -> *) a. Applicative f => a -> f a pure (Parser (GovernanceCommitteeCmds era) -> Maybe (Parser (GovernanceCommitteeCmds era))) -> Parser (GovernanceCommitteeCmds era) -> Maybe (Parser (GovernanceCommitteeCmds era)) forall a b. (a -> b) -> a -> b $ String -> ParserInfo (GovernanceCommitteeCmds era) -> Parser (GovernanceCommitteeCmds era) forall a. String -> ParserInfo a -> Parser a subParser String "key-gen-hot" (ParserInfo (GovernanceCommitteeCmds era) -> Parser (GovernanceCommitteeCmds era)) -> ParserInfo (GovernanceCommitteeCmds era) -> Parser (GovernanceCommitteeCmds era) forall a b. (a -> b) -> a -> b $ Parser (GovernanceCommitteeCmds era) -> InfoMod (GovernanceCommitteeCmds era) -> ParserInfo (GovernanceCommitteeCmds era) forall a. Parser a -> InfoMod a -> ParserInfo a Opt.info (ConwayEraOnwards era -> Parser (GovernanceCommitteeCmds era) forall era. ConwayEraOnwards era -> Parser (GovernanceCommitteeCmds era) pCmd ConwayEraOnwards era w) (InfoMod (GovernanceCommitteeCmds era) -> ParserInfo (GovernanceCommitteeCmds era)) -> InfoMod (GovernanceCommitteeCmds era) -> ParserInfo (GovernanceCommitteeCmds era) forall a b. (a -> b) -> a -> b $ String -> InfoMod (GovernanceCommitteeCmds era) forall a. String -> InfoMod a Opt.progDesc (String -> InfoMod (GovernanceCommitteeCmds era)) -> String -> InfoMod (GovernanceCommitteeCmds era) forall a b. (a -> b) -> a -> b $ [String] -> String forall a. Monoid a => [a] -> a mconcat [ String "Create a hot key pair for a Constitutional Committee Member" ] where pCmd :: () => ConwayEraOnwards era -> Parser (GovernanceCommitteeCmds era) pCmd :: forall era. ConwayEraOnwards era -> Parser (GovernanceCommitteeCmds era) pCmd ConwayEraOnwards era w = (GovernanceCommitteeKeyGenHotCmdArgs era -> GovernanceCommitteeCmds era) -> Parser (GovernanceCommitteeKeyGenHotCmdArgs era) -> Parser (GovernanceCommitteeCmds era) forall a b. (a -> b) -> Parser a -> Parser b forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b fmap GovernanceCommitteeKeyGenHotCmdArgs era -> GovernanceCommitteeCmds era forall era. GovernanceCommitteeKeyGenHotCmdArgs era -> GovernanceCommitteeCmds era GovernanceCommitteeKeyGenHotCmd (Parser (GovernanceCommitteeKeyGenHotCmdArgs era) -> Parser (GovernanceCommitteeCmds era)) -> Parser (GovernanceCommitteeKeyGenHotCmdArgs era) -> Parser (GovernanceCommitteeCmds era) forall a b. (a -> b) -> a -> b $ ConwayEraOnwards era -> File (VerificationKey ()) 'Out -> File (SigningKey ()) 'Out -> GovernanceCommitteeKeyGenHotCmdArgs era forall era. ConwayEraOnwards era -> File (VerificationKey ()) 'Out -> File (SigningKey ()) 'Out -> GovernanceCommitteeKeyGenHotCmdArgs era GovernanceCommitteeKeyGenHotCmdArgs ConwayEraOnwards era w (File (VerificationKey ()) 'Out -> File (SigningKey ()) 'Out -> GovernanceCommitteeKeyGenHotCmdArgs era) -> Parser (File (VerificationKey ()) 'Out) -> Parser (File (SigningKey ()) 'Out -> GovernanceCommitteeKeyGenHotCmdArgs era) forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b <$> Parser (File (VerificationKey ()) 'Out) forall keyrole. Parser (File (VerificationKey keyrole) 'Out) pVerificationKeyFileOut Parser (File (SigningKey ()) 'Out -> GovernanceCommitteeKeyGenHotCmdArgs era) -> Parser (File (SigningKey ()) 'Out) -> Parser (GovernanceCommitteeKeyGenHotCmdArgs 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 (SigningKey ()) 'Out) forall keyrole. Parser (File (SigningKey keyrole) 'Out) pSigningKeyFileOut pGovernanceCommitteeKeyHashCmd :: () => ShelleyBasedEra era -> Maybe (Parser (GovernanceCommitteeCmds era)) pGovernanceCommitteeKeyHashCmd :: forall era. ShelleyBasedEra era -> Maybe (Parser (GovernanceCommitteeCmds era)) pGovernanceCommitteeKeyHashCmd ShelleyBasedEra era era = do ConwayEraOnwards era w <- ShelleyBasedEra era -> Maybe (ConwayEraOnwards era) forall (eon :: * -> *) era. Eon eon => ShelleyBasedEra era -> Maybe (eon era) forShelleyBasedEraMaybeEon ShelleyBasedEra era era Parser (GovernanceCommitteeCmds era) -> Maybe (Parser (GovernanceCommitteeCmds era)) forall a. a -> Maybe a forall (f :: * -> *) a. Applicative f => a -> f a pure (Parser (GovernanceCommitteeCmds era) -> Maybe (Parser (GovernanceCommitteeCmds era))) -> Parser (GovernanceCommitteeCmds era) -> Maybe (Parser (GovernanceCommitteeCmds era)) forall a b. (a -> b) -> a -> b $ String -> ParserInfo (GovernanceCommitteeCmds era) -> Parser (GovernanceCommitteeCmds era) forall a. String -> ParserInfo a -> Parser a subParser String "key-hash" (ParserInfo (GovernanceCommitteeCmds era) -> Parser (GovernanceCommitteeCmds era)) -> ParserInfo (GovernanceCommitteeCmds era) -> Parser (GovernanceCommitteeCmds era) forall a b. (a -> b) -> a -> b $ Parser (GovernanceCommitteeCmds era) -> InfoMod (GovernanceCommitteeCmds era) -> ParserInfo (GovernanceCommitteeCmds era) forall a. Parser a -> InfoMod a -> ParserInfo a Opt.info ( (GovernanceCommitteeKeyHashCmdArgs era -> GovernanceCommitteeCmds era) -> Parser (GovernanceCommitteeKeyHashCmdArgs era) -> Parser (GovernanceCommitteeCmds era) forall a b. (a -> b) -> Parser a -> Parser b forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b fmap GovernanceCommitteeKeyHashCmdArgs era -> GovernanceCommitteeCmds era forall era. GovernanceCommitteeKeyHashCmdArgs era -> GovernanceCommitteeCmds era GovernanceCommitteeKeyHashCmd (Parser (GovernanceCommitteeKeyHashCmdArgs era) -> Parser (GovernanceCommitteeCmds era)) -> Parser (GovernanceCommitteeKeyHashCmdArgs era) -> Parser (GovernanceCommitteeCmds era) forall a b. (a -> b) -> a -> b $ ConwayEraOnwards era -> AnyVerificationKeySource -> GovernanceCommitteeKeyHashCmdArgs era forall era. ConwayEraOnwards era -> AnyVerificationKeySource -> GovernanceCommitteeKeyHashCmdArgs era GovernanceCommitteeKeyHashCmdArgs ConwayEraOnwards era w (AnyVerificationKeySource -> GovernanceCommitteeKeyHashCmdArgs era) -> Parser AnyVerificationKeySource -> Parser (GovernanceCommitteeKeyHashCmdArgs era) forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b <$> String -> Parser AnyVerificationKeySource pAnyVerificationKeySource String "Constitutional Committee Member key (hot or cold)" ) (InfoMod (GovernanceCommitteeCmds era) -> ParserInfo (GovernanceCommitteeCmds era)) -> InfoMod (GovernanceCommitteeCmds era) -> ParserInfo (GovernanceCommitteeCmds era) forall a b. (a -> b) -> a -> b $ String -> InfoMod (GovernanceCommitteeCmds era) forall a. String -> InfoMod a Opt.progDesc (String -> InfoMod (GovernanceCommitteeCmds era)) -> String -> InfoMod (GovernanceCommitteeCmds era) forall a b. (a -> b) -> a -> b $ [String] -> String forall a. Monoid a => [a] -> a mconcat [ String "Print the identifier (hash) of a public key" ] pGovernanceCommitteeCreateHotKeyAuthorizationCertificateCmd :: () => ShelleyBasedEra era -> Maybe (Parser (GovernanceCommitteeCmds era)) pGovernanceCommitteeCreateHotKeyAuthorizationCertificateCmd :: forall era. ShelleyBasedEra era -> Maybe (Parser (GovernanceCommitteeCmds era)) pGovernanceCommitteeCreateHotKeyAuthorizationCertificateCmd ShelleyBasedEra era era = do ConwayEraOnwards era w <- ShelleyBasedEra era -> Maybe (ConwayEraOnwards era) forall (eon :: * -> *) era. Eon eon => ShelleyBasedEra era -> Maybe (eon era) forShelleyBasedEraMaybeEon ShelleyBasedEra era era Parser (GovernanceCommitteeCmds era) -> Maybe (Parser (GovernanceCommitteeCmds era)) forall a. a -> Maybe a forall (f :: * -> *) a. Applicative f => a -> f a pure (Parser (GovernanceCommitteeCmds era) -> Maybe (Parser (GovernanceCommitteeCmds era))) -> Parser (GovernanceCommitteeCmds era) -> Maybe (Parser (GovernanceCommitteeCmds era)) forall a b. (a -> b) -> a -> b $ String -> ParserInfo (GovernanceCommitteeCmds era) -> Parser (GovernanceCommitteeCmds era) forall a. String -> ParserInfo a -> Parser a subParser String "create-hot-key-authorization-certificate" (ParserInfo (GovernanceCommitteeCmds era) -> Parser (GovernanceCommitteeCmds era)) -> ParserInfo (GovernanceCommitteeCmds era) -> Parser (GovernanceCommitteeCmds era) forall a b. (a -> b) -> a -> b $ Parser (GovernanceCommitteeCmds era) -> InfoMod (GovernanceCommitteeCmds era) -> ParserInfo (GovernanceCommitteeCmds era) forall a. Parser a -> InfoMod a -> ParserInfo a Opt.info ( (GovernanceCommitteeCreateHotKeyAuthorizationCertificateCmdArgs era -> GovernanceCommitteeCmds era) -> Parser (GovernanceCommitteeCreateHotKeyAuthorizationCertificateCmdArgs era) -> Parser (GovernanceCommitteeCmds era) forall a b. (a -> b) -> Parser a -> Parser b forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b fmap GovernanceCommitteeCreateHotKeyAuthorizationCertificateCmdArgs era -> GovernanceCommitteeCmds era forall era. GovernanceCommitteeCreateHotKeyAuthorizationCertificateCmdArgs era -> GovernanceCommitteeCmds era GovernanceCommitteeCreateHotKeyAuthorizationCertificateCmd (Parser (GovernanceCommitteeCreateHotKeyAuthorizationCertificateCmdArgs era) -> Parser (GovernanceCommitteeCmds era)) -> Parser (GovernanceCommitteeCreateHotKeyAuthorizationCertificateCmdArgs era) -> Parser (GovernanceCommitteeCmds era) forall a b. (a -> b) -> a -> b $ ConwayEraOnwards era -> VerificationKeySource CommitteeColdKey -> VerificationKeySource CommitteeHotKey -> File () 'Out -> GovernanceCommitteeCreateHotKeyAuthorizationCertificateCmdArgs era forall era. ConwayEraOnwards era -> VerificationKeySource CommitteeColdKey -> VerificationKeySource CommitteeHotKey -> File () 'Out -> GovernanceCommitteeCreateHotKeyAuthorizationCertificateCmdArgs era GovernanceCommitteeCreateHotKeyAuthorizationCertificateCmdArgs ConwayEraOnwards era w (VerificationKeySource CommitteeColdKey -> VerificationKeySource CommitteeHotKey -> File () 'Out -> GovernanceCommitteeCreateHotKeyAuthorizationCertificateCmdArgs era) -> Parser (VerificationKeySource CommitteeColdKey) -> Parser (VerificationKeySource CommitteeHotKey -> File () 'Out -> GovernanceCommitteeCreateHotKeyAuthorizationCertificateCmdArgs era) forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b <$> Parser (VerificationKeySource CommitteeColdKey) pColdCredential Parser (VerificationKeySource CommitteeHotKey -> File () 'Out -> GovernanceCommitteeCreateHotKeyAuthorizationCertificateCmdArgs era) -> Parser (VerificationKeySource CommitteeHotKey) -> Parser (File () 'Out -> GovernanceCommitteeCreateHotKeyAuthorizationCertificateCmdArgs 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 (VerificationKeySource CommitteeHotKey) pHotCredential Parser (File () 'Out -> GovernanceCommitteeCreateHotKeyAuthorizationCertificateCmdArgs era) -> Parser (File () 'Out) -> Parser (GovernanceCommitteeCreateHotKeyAuthorizationCertificateCmdArgs 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 (GovernanceCommitteeCmds era) -> ParserInfo (GovernanceCommitteeCmds era)) -> InfoMod (GovernanceCommitteeCmds era) -> ParserInfo (GovernanceCommitteeCmds era) forall a b. (a -> b) -> a -> b $ String -> InfoMod (GovernanceCommitteeCmds era) forall a. String -> InfoMod a Opt.progDesc (String -> InfoMod (GovernanceCommitteeCmds era)) -> String -> InfoMod (GovernanceCommitteeCmds era) forall a b. (a -> b) -> a -> b $ [String] -> String forall a. Monoid a => [a] -> a mconcat [ String "Create hot key authorization certificate for a Constitutional Committee Member" ] pGovernanceCommitteeCreateColdKeyResignationCertificateCmd :: () => ShelleyBasedEra era -> Maybe (Parser (GovernanceCommitteeCmds era)) pGovernanceCommitteeCreateColdKeyResignationCertificateCmd :: forall era. ShelleyBasedEra era -> Maybe (Parser (GovernanceCommitteeCmds era)) pGovernanceCommitteeCreateColdKeyResignationCertificateCmd ShelleyBasedEra era era = do ConwayEraOnwards era w <- ShelleyBasedEra era -> Maybe (ConwayEraOnwards era) forall (eon :: * -> *) era. Eon eon => ShelleyBasedEra era -> Maybe (eon era) forShelleyBasedEraMaybeEon ShelleyBasedEra era era Parser (GovernanceCommitteeCmds era) -> Maybe (Parser (GovernanceCommitteeCmds era)) forall a. a -> Maybe a forall (f :: * -> *) a. Applicative f => a -> f a pure (Parser (GovernanceCommitteeCmds era) -> Maybe (Parser (GovernanceCommitteeCmds era))) -> Parser (GovernanceCommitteeCmds era) -> Maybe (Parser (GovernanceCommitteeCmds era)) forall a b. (a -> b) -> a -> b $ String -> ParserInfo (GovernanceCommitteeCmds era) -> Parser (GovernanceCommitteeCmds era) forall a. String -> ParserInfo a -> Parser a subParser String "create-cold-key-resignation-certificate" (ParserInfo (GovernanceCommitteeCmds era) -> Parser (GovernanceCommitteeCmds era)) -> ParserInfo (GovernanceCommitteeCmds era) -> Parser (GovernanceCommitteeCmds era) forall a b. (a -> b) -> a -> b $ Parser (GovernanceCommitteeCmds era) -> InfoMod (GovernanceCommitteeCmds era) -> ParserInfo (GovernanceCommitteeCmds era) forall a. Parser a -> InfoMod a -> ParserInfo a Opt.info (ConwayEraOnwards era -> (ConwayEraOnwardsConstraints era => Parser (GovernanceCommitteeCmds era)) -> Parser (GovernanceCommitteeCmds era) forall era a. ConwayEraOnwards era -> (ConwayEraOnwardsConstraints era => a) -> a conwayEraOnwardsConstraints ConwayEraOnwards era w ((ConwayEraOnwardsConstraints era => Parser (GovernanceCommitteeCmds era)) -> Parser (GovernanceCommitteeCmds era)) -> (ConwayEraOnwardsConstraints era => Parser (GovernanceCommitteeCmds era)) -> Parser (GovernanceCommitteeCmds era) forall a b. (a -> b) -> a -> b $ ConwayEraOnwards era -> Parser (GovernanceCommitteeCmds era) forall {era}. (EraCrypto (ShelleyLedgerEra era) ~ StandardCrypto) => ConwayEraOnwards era -> Parser (GovernanceCommitteeCmds era) mkParser ConwayEraOnwards era w) (InfoMod (GovernanceCommitteeCmds era) -> ParserInfo (GovernanceCommitteeCmds era)) -> InfoMod (GovernanceCommitteeCmds era) -> ParserInfo (GovernanceCommitteeCmds era) forall a b. (a -> b) -> a -> b $ String -> InfoMod (GovernanceCommitteeCmds era) forall a. String -> InfoMod a Opt.progDesc (String -> InfoMod (GovernanceCommitteeCmds era)) -> String -> InfoMod (GovernanceCommitteeCmds era) forall a b. (a -> b) -> a -> b $ [String] -> String forall a. Monoid a => [a] -> a mconcat [ String "Create cold key resignation certificate for a Constitutional Committee Member" ] where mkParser :: ConwayEraOnwards era -> Parser (GovernanceCommitteeCmds era) mkParser ConwayEraOnwards era w = GovernanceCommitteeCreateColdKeyResignationCertificateCmdArgs era -> GovernanceCommitteeCmds era forall era. GovernanceCommitteeCreateColdKeyResignationCertificateCmdArgs era -> GovernanceCommitteeCmds era GovernanceCommitteeCreateColdKeyResignationCertificateCmd (GovernanceCommitteeCreateColdKeyResignationCertificateCmdArgs era -> GovernanceCommitteeCmds era) -> Parser (GovernanceCommitteeCreateColdKeyResignationCertificateCmdArgs era) -> Parser (GovernanceCommitteeCmds era) forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b <$> ( ConwayEraOnwards era -> VerificationKeySource CommitteeColdKey -> Maybe (PotentiallyCheckedAnchor ResignationMetadataUrl (Anchor (EraCrypto (ShelleyLedgerEra era)))) -> File () 'Out -> GovernanceCommitteeCreateColdKeyResignationCertificateCmdArgs era forall era. ConwayEraOnwards era -> VerificationKeySource CommitteeColdKey -> Maybe (PotentiallyCheckedAnchor ResignationMetadataUrl (Anchor (EraCrypto (ShelleyLedgerEra era)))) -> File () 'Out -> GovernanceCommitteeCreateColdKeyResignationCertificateCmdArgs era GovernanceCommitteeCreateColdKeyResignationCertificateCmdArgs ConwayEraOnwards era w (VerificationKeySource CommitteeColdKey -> Maybe (PotentiallyCheckedAnchor ResignationMetadataUrl (Anchor StandardCrypto)) -> File () 'Out -> GovernanceCommitteeCreateColdKeyResignationCertificateCmdArgs era) -> Parser (VerificationKeySource CommitteeColdKey) -> Parser (Maybe (PotentiallyCheckedAnchor ResignationMetadataUrl (Anchor StandardCrypto)) -> File () 'Out -> GovernanceCommitteeCreateColdKeyResignationCertificateCmdArgs era) forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b <$> Parser (VerificationKeySource CommitteeColdKey) pColdCredential Parser (Maybe (PotentiallyCheckedAnchor ResignationMetadataUrl (Anchor StandardCrypto)) -> File () 'Out -> GovernanceCommitteeCreateColdKeyResignationCertificateCmdArgs era) -> Parser (Maybe (PotentiallyCheckedAnchor ResignationMetadataUrl (Anchor StandardCrypto))) -> Parser (File () 'Out -> GovernanceCommitteeCreateColdKeyResignationCertificateCmdArgs 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 ResignationMetadataUrl (Anchor StandardCrypto)) -> Parser (Maybe (PotentiallyCheckedAnchor ResignationMetadataUrl (Anchor StandardCrypto))) forall (f :: * -> *) a. Alternative f => f a -> f (Maybe a) optional ( Parser (MustCheckHash ResignationMetadataUrl) -> Parser (Anchor StandardCrypto) -> Parser (PotentiallyCheckedAnchor ResignationMetadataUrl (Anchor StandardCrypto)) forall anchorType anchor. Parser (MustCheckHash anchorType) -> Parser anchor -> Parser (PotentiallyCheckedAnchor anchorType anchor) pPotentiallyCheckedAnchorData Parser (MustCheckHash ResignationMetadataUrl) pMustCheckResignationMetadataHash Parser (Anchor StandardCrypto) pAnchor ) Parser (File () 'Out -> GovernanceCommitteeCreateColdKeyResignationCertificateCmdArgs era) -> Parser (File () 'Out) -> Parser (GovernanceCommitteeCreateColdKeyResignationCertificateCmdArgs 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 ) pColdCredential :: Parser (VerificationKeySource CommitteeColdKey) pColdCredential :: Parser (VerificationKeySource CommitteeColdKey) pColdCredential = [Parser (VerificationKeySource CommitteeColdKey)] -> Parser (VerificationKeySource CommitteeColdKey) forall (t :: * -> *) (f :: * -> *) a. (Foldable t, Alternative f) => t (f a) -> f a asum [ VerificationKeyOrHashOrFile CommitteeColdKey -> VerificationKeySource CommitteeColdKey forall keyrole. VerificationKeyOrHashOrFile keyrole -> VerificationKeySource keyrole VksKeyHashFile (VerificationKeyOrHashOrFile CommitteeColdKey -> VerificationKeySource CommitteeColdKey) -> (VerificationKeyOrFile CommitteeColdKey -> VerificationKeyOrHashOrFile CommitteeColdKey) -> VerificationKeyOrFile CommitteeColdKey -> VerificationKeySource CommitteeColdKey forall b c a. (b -> c) -> (a -> b) -> a -> c . VerificationKeyOrFile CommitteeColdKey -> VerificationKeyOrHashOrFile CommitteeColdKey forall keyrole. VerificationKeyOrFile keyrole -> VerificationKeyOrHashOrFile keyrole VerificationKeyOrFile (VerificationKeyOrFile CommitteeColdKey -> VerificationKeySource CommitteeColdKey) -> Parser (VerificationKeyOrFile CommitteeColdKey) -> Parser (VerificationKeySource CommitteeColdKey) forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b <$> Parser (VerificationKeyOrFile CommitteeColdKey) pCommitteeColdVerificationKeyOrFile , VerificationKeyOrHashOrFile CommitteeColdKey -> VerificationKeySource CommitteeColdKey forall keyrole. VerificationKeyOrHashOrFile keyrole -> VerificationKeySource keyrole VksKeyHashFile (VerificationKeyOrHashOrFile CommitteeColdKey -> VerificationKeySource CommitteeColdKey) -> (Hash CommitteeColdKey -> VerificationKeyOrHashOrFile CommitteeColdKey) -> Hash CommitteeColdKey -> VerificationKeySource CommitteeColdKey forall b c a. (b -> c) -> (a -> b) -> a -> c . Hash CommitteeColdKey -> VerificationKeyOrHashOrFile CommitteeColdKey forall keyrole. Hash keyrole -> VerificationKeyOrHashOrFile keyrole VerificationKeyHash (Hash CommitteeColdKey -> VerificationKeySource CommitteeColdKey) -> Parser (Hash CommitteeColdKey) -> Parser (VerificationKeySource CommitteeColdKey) forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b <$> Parser (Hash CommitteeColdKey) pCommitteeColdVerificationKeyHash , ScriptHash -> VerificationKeySource CommitteeColdKey forall keyrole. ScriptHash -> VerificationKeySource keyrole VksScriptHash (ScriptHash -> VerificationKeySource CommitteeColdKey) -> Parser ScriptHash -> Parser (VerificationKeySource CommitteeColdKey) forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b <$> String -> String -> Parser ScriptHash pScriptHash String "cold-script-hash" String "Committee cold Native or Plutus script file hash (hex-encoded). Obtain it with \"cardano-cli hash script ...\"." , File ScriptInAnyLang 'In -> VerificationKeySource CommitteeColdKey forall keyrole. File ScriptInAnyLang 'In -> VerificationKeySource keyrole VksScript (File ScriptInAnyLang 'In -> VerificationKeySource CommitteeColdKey) -> Parser (File ScriptInAnyLang 'In) -> Parser (VerificationKeySource CommitteeColdKey) forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b <$> String -> Maybe String -> String -> Parser (File ScriptInAnyLang 'In) pScriptFor String "cold-script-file" Maybe String forall a. Maybe a Nothing String "Cold Native or Plutus script file" ] pHotCredential :: Parser (VerificationKeySource CommitteeHotKey) pHotCredential :: Parser (VerificationKeySource CommitteeHotKey) pHotCredential = [Parser (VerificationKeySource CommitteeHotKey)] -> Parser (VerificationKeySource CommitteeHotKey) forall (t :: * -> *) (f :: * -> *) a. (Foldable t, Alternative f) => t (f a) -> f a asum [ VerificationKeyOrHashOrFile CommitteeHotKey -> VerificationKeySource CommitteeHotKey forall keyrole. VerificationKeyOrHashOrFile keyrole -> VerificationKeySource keyrole VksKeyHashFile (VerificationKeyOrHashOrFile CommitteeHotKey -> VerificationKeySource CommitteeHotKey) -> (VerificationKeyOrFile CommitteeHotKey -> VerificationKeyOrHashOrFile CommitteeHotKey) -> VerificationKeyOrFile CommitteeHotKey -> VerificationKeySource CommitteeHotKey forall b c a. (b -> c) -> (a -> b) -> a -> c . VerificationKeyOrFile CommitteeHotKey -> VerificationKeyOrHashOrFile CommitteeHotKey forall keyrole. VerificationKeyOrFile keyrole -> VerificationKeyOrHashOrFile keyrole VerificationKeyOrFile (VerificationKeyOrFile CommitteeHotKey -> VerificationKeySource CommitteeHotKey) -> Parser (VerificationKeyOrFile CommitteeHotKey) -> Parser (VerificationKeySource CommitteeHotKey) forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b <$> Parser (VerificationKeyOrFile CommitteeHotKey) pCommitteeHotVerificationKeyOrFile , VerificationKeyOrHashOrFile CommitteeHotKey -> VerificationKeySource CommitteeHotKey forall keyrole. VerificationKeyOrHashOrFile keyrole -> VerificationKeySource keyrole VksKeyHashFile (VerificationKeyOrHashOrFile CommitteeHotKey -> VerificationKeySource CommitteeHotKey) -> (Hash CommitteeHotKey -> VerificationKeyOrHashOrFile CommitteeHotKey) -> Hash CommitteeHotKey -> VerificationKeySource CommitteeHotKey forall b c a. (b -> c) -> (a -> b) -> a -> c . Hash CommitteeHotKey -> VerificationKeyOrHashOrFile CommitteeHotKey forall keyrole. Hash keyrole -> VerificationKeyOrHashOrFile keyrole VerificationKeyHash (Hash CommitteeHotKey -> VerificationKeySource CommitteeHotKey) -> Parser (Hash CommitteeHotKey) -> Parser (VerificationKeySource CommitteeHotKey) forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b <$> Parser (Hash CommitteeHotKey) pCommitteeHotVerificationKeyHash , ScriptHash -> VerificationKeySource CommitteeHotKey forall keyrole. ScriptHash -> VerificationKeySource keyrole VksScriptHash (ScriptHash -> VerificationKeySource CommitteeHotKey) -> Parser ScriptHash -> Parser (VerificationKeySource CommitteeHotKey) forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b <$> String -> String -> Parser ScriptHash pScriptHash String "hot-script-hash" String "Committee hot Native or Plutus script file hash (hex-encoded). Obtain it with \"cardano-cli hash script ...\"." , File ScriptInAnyLang 'In -> VerificationKeySource CommitteeHotKey forall keyrole. File ScriptInAnyLang 'In -> VerificationKeySource keyrole VksScript (File ScriptInAnyLang 'In -> VerificationKeySource CommitteeHotKey) -> Parser (File ScriptInAnyLang 'In) -> Parser (VerificationKeySource CommitteeHotKey) forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b <$> String -> Maybe String -> String -> Parser (File ScriptInAnyLang 'In) pScriptFor String "hot-script-file" Maybe String forall a. Maybe a Nothing String "Hot Native or Plutus script file" ] pAnchor :: Parser (L.Anchor L.StandardCrypto) pAnchor :: Parser (Anchor StandardCrypto) pAnchor = Url -> SafeHash StandardCrypto AnchorData -> Anchor StandardCrypto forall c. Url -> SafeHash c AnchorData -> Anchor c L.Anchor (Url -> SafeHash StandardCrypto AnchorData -> Anchor StandardCrypto) -> Parser Url -> Parser (SafeHash StandardCrypto AnchorData -> Anchor StandardCrypto) forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b <$> (AnchorUrl -> Url) -> Parser AnchorUrl -> Parser Url forall a b. (a -> b) -> Parser a -> Parser b forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b fmap AnchorUrl -> Url unAnchorUrl Parser AnchorUrl pAnchorUrl Parser (SafeHash StandardCrypto AnchorData -> Anchor StandardCrypto) -> Parser (SafeHash StandardCrypto AnchorData) -> Parser (Anchor StandardCrypto) forall a b. Parser (a -> b) -> Parser a -> Parser b forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b <*> Parser (SafeHash StandardCrypto AnchorData) pSafeHash pAnchorUrl :: Parser AnchorUrl pAnchorUrl :: Parser AnchorUrl pAnchorUrl = Url -> AnchorUrl AnchorUrl (Url -> AnchorUrl) -> Parser Url -> Parser AnchorUrl forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b <$> String -> String -> Parser Url pUrl String "resignation-metadata-url" String "Constitutional Committee cold key resignation certificate URL" pSafeHash :: Parser (L.SafeHash L.StandardCrypto L.AnchorData) pSafeHash :: Parser (SafeHash StandardCrypto AnchorData) pSafeHash = ReadM (SafeHash StandardCrypto AnchorData) -> Mod OptionFields (SafeHash StandardCrypto AnchorData) -> Parser (SafeHash StandardCrypto AnchorData) forall a. ReadM a -> Mod OptionFields a -> Parser a Opt.option ReadM (SafeHash StandardCrypto AnchorData) readSafeHash (Mod OptionFields (SafeHash StandardCrypto AnchorData) -> Parser (SafeHash StandardCrypto AnchorData)) -> Mod OptionFields (SafeHash StandardCrypto AnchorData) -> Parser (SafeHash StandardCrypto AnchorData) forall a b. (a -> b) -> a -> b $ [Mod OptionFields (SafeHash StandardCrypto AnchorData)] -> Mod OptionFields (SafeHash StandardCrypto AnchorData) forall a. Monoid a => [a] -> a mconcat [ String -> Mod OptionFields (SafeHash StandardCrypto AnchorData) forall (f :: * -> *) a. HasName f => String -> Mod f a Opt.long String "resignation-metadata-hash" , String -> Mod OptionFields (SafeHash StandardCrypto AnchorData) forall (f :: * -> *) a. HasMetavar f => String -> Mod f a Opt.metavar String "HASH" , String -> Mod OptionFields (SafeHash StandardCrypto AnchorData) forall (f :: * -> *) a. String -> Mod f a Opt.help String "Constitutional Committee cold key resignation certificate metadata hash" ]