{-# LANGUAGE DataKinds #-} {-# LANGUAGE GADTs #-} module Cardano.CLI.EraBased.Governance.Vote.Option ( pGovernanceVoteCmds ) where import Cardano.Api import Cardano.CLI.EraBased.Common.Option import Cardano.CLI.EraBased.Governance.Vote.Command ( GovernanceVoteCmds (..) , GovernanceVoteCreateCmdArgs (GovernanceVoteCreateCmdArgs) , GovernanceVoteViewCmdArgs (GovernanceVoteViewCmdArgs) ) import Cardano.CLI.Parser import Cardano.CLI.Type.Governance import Control.Applicative (optional) import Data.Foldable import Options.Applicative (Parser) import Options.Applicative qualified as Opt pGovernanceVoteCmds :: () => ShelleyBasedEra era -> Maybe (Parser (GovernanceVoteCmds era)) pGovernanceVoteCmds :: forall era. ShelleyBasedEra era -> Maybe (Parser (GovernanceVoteCmds era)) pGovernanceVoteCmds ShelleyBasedEra era era = String -> InfoMod (GovernanceVoteCmds era) -> [Maybe (Parser (GovernanceVoteCmds era))] -> Maybe (Parser (GovernanceVoteCmds era)) forall a. String -> InfoMod a -> [Maybe (Parser a)] -> Maybe (Parser a) subInfoParser String "vote" (String -> InfoMod (GovernanceVoteCmds era) forall a. String -> InfoMod a Opt.progDesc String "Vote commands.") [ ShelleyBasedEra era -> Maybe (Parser (GovernanceVoteCmds era)) forall era. ShelleyBasedEra era -> Maybe (Parser (GovernanceVoteCmds era)) pGovernanceVoteCreateCmd ShelleyBasedEra era era , ShelleyBasedEra era -> Maybe (Parser (GovernanceVoteCmds era)) forall era. ShelleyBasedEra era -> Maybe (Parser (GovernanceVoteCmds era)) pGovernanceVoteViewCmd ShelleyBasedEra era era ] pGovernanceVoteCreateCmd :: () => ShelleyBasedEra era -> Maybe (Parser (GovernanceVoteCmds era)) pGovernanceVoteCreateCmd :: forall era. ShelleyBasedEra era -> Maybe (Parser (GovernanceVoteCmds era)) pGovernanceVoteCreateCmd 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 (GovernanceVoteCmds era) -> Maybe (Parser (GovernanceVoteCmds era)) forall a. a -> Maybe a forall (f :: * -> *) a. Applicative f => a -> f a pure (Parser (GovernanceVoteCmds era) -> Maybe (Parser (GovernanceVoteCmds era))) -> Parser (GovernanceVoteCmds era) -> Maybe (Parser (GovernanceVoteCmds era)) forall a b. (a -> b) -> a -> b $ Mod CommandFields (GovernanceVoteCmds era) -> Parser (GovernanceVoteCmds era) forall a. Mod CommandFields a -> Parser a Opt.hsubparser (Mod CommandFields (GovernanceVoteCmds era) -> Parser (GovernanceVoteCmds era)) -> Mod CommandFields (GovernanceVoteCmds era) -> Parser (GovernanceVoteCmds era) forall a b. (a -> b) -> a -> b $ String -> ParserInfo (GovernanceVoteCmds era) -> Mod CommandFields (GovernanceVoteCmds era) forall a. String -> ParserInfo a -> Mod CommandFields a commandWithMetavar String "create" (ParserInfo (GovernanceVoteCmds era) -> Mod CommandFields (GovernanceVoteCmds era)) -> ParserInfo (GovernanceVoteCmds era) -> Mod CommandFields (GovernanceVoteCmds era) forall a b. (a -> b) -> a -> b $ Parser (GovernanceVoteCmds era) -> InfoMod (GovernanceVoteCmds era) -> ParserInfo (GovernanceVoteCmds era) forall a. Parser a -> InfoMod a -> ParserInfo a Opt.info ( GovernanceVoteCreateCmdArgs era -> GovernanceVoteCmds era forall era. GovernanceVoteCreateCmdArgs era -> GovernanceVoteCmds era GovernanceVoteCreateCmd (GovernanceVoteCreateCmdArgs era -> GovernanceVoteCmds era) -> Parser (GovernanceVoteCreateCmdArgs era) -> Parser (GovernanceVoteCmds era) forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b <$> ConwayEraOnwards era -> Parser (GovernanceVoteCreateCmdArgs era) forall era. ConwayEraOnwards era -> Parser (GovernanceVoteCreateCmdArgs era) pGovernanceVoteCreateCmdArgs ConwayEraOnwards era w ) (InfoMod (GovernanceVoteCmds era) -> ParserInfo (GovernanceVoteCmds era)) -> InfoMod (GovernanceVoteCmds era) -> ParserInfo (GovernanceVoteCmds era) forall a b. (a -> b) -> a -> b $ String -> InfoMod (GovernanceVoteCmds era) forall a. String -> InfoMod a Opt.progDesc String "Vote creation." pGovernanceVoteCreateCmdArgs :: () => ConwayEraOnwards era -> Parser (GovernanceVoteCreateCmdArgs era) pGovernanceVoteCreateCmdArgs :: forall era. ConwayEraOnwards era -> Parser (GovernanceVoteCreateCmdArgs era) pGovernanceVoteCreateCmdArgs ConwayEraOnwards era cOnwards = ConwayEraOnwards era -> Vote -> (TxId, Word16) -> AnyVotingStakeVerificationKeyOrHashOrFile -> Maybe (PotentiallyCheckedAnchor VoteUrl (VoteUrl, SafeHash StandardCrypto AnchorData)) -> VoteFile 'Out -> GovernanceVoteCreateCmdArgs era forall era. ConwayEraOnwards era -> Vote -> (TxId, Word16) -> AnyVotingStakeVerificationKeyOrHashOrFile -> Maybe (PotentiallyCheckedAnchor VoteUrl (VoteUrl, SafeHash StandardCrypto AnchorData)) -> VoteFile 'Out -> GovernanceVoteCreateCmdArgs era GovernanceVoteCreateCmdArgs ConwayEraOnwards era cOnwards (Vote -> (TxId, Word16) -> AnyVotingStakeVerificationKeyOrHashOrFile -> Maybe (PotentiallyCheckedAnchor VoteUrl (VoteUrl, SafeHash StandardCrypto AnchorData)) -> VoteFile 'Out -> GovernanceVoteCreateCmdArgs era) -> Parser Vote -> Parser ((TxId, Word16) -> AnyVotingStakeVerificationKeyOrHashOrFile -> Maybe (PotentiallyCheckedAnchor VoteUrl (VoteUrl, SafeHash StandardCrypto AnchorData)) -> VoteFile 'Out -> GovernanceVoteCreateCmdArgs era) forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b <$> Parser Vote pVoteChoice Parser ((TxId, Word16) -> AnyVotingStakeVerificationKeyOrHashOrFile -> Maybe (PotentiallyCheckedAnchor VoteUrl (VoteUrl, SafeHash StandardCrypto AnchorData)) -> VoteFile 'Out -> GovernanceVoteCreateCmdArgs era) -> Parser (TxId, Word16) -> Parser (AnyVotingStakeVerificationKeyOrHashOrFile -> Maybe (PotentiallyCheckedAnchor VoteUrl (VoteUrl, SafeHash StandardCrypto AnchorData)) -> VoteFile 'Out -> GovernanceVoteCreateCmdArgs 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 (TxId, Word16) pGovernanceActionId Parser (AnyVotingStakeVerificationKeyOrHashOrFile -> Maybe (PotentiallyCheckedAnchor VoteUrl (VoteUrl, SafeHash StandardCrypto AnchorData)) -> VoteFile 'Out -> GovernanceVoteCreateCmdArgs era) -> Parser AnyVotingStakeVerificationKeyOrHashOrFile -> Parser (Maybe (PotentiallyCheckedAnchor VoteUrl (VoteUrl, SafeHash StandardCrypto AnchorData)) -> VoteFile 'Out -> GovernanceVoteCreateCmdArgs 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 AnyVotingStakeVerificationKeyOrHashOrFile pAnyVotingStakeVerificationKeyOrHashOrFile Parser (Maybe (PotentiallyCheckedAnchor VoteUrl (VoteUrl, SafeHash StandardCrypto AnchorData)) -> VoteFile 'Out -> GovernanceVoteCreateCmdArgs era) -> Parser (Maybe (PotentiallyCheckedAnchor VoteUrl (VoteUrl, SafeHash StandardCrypto AnchorData))) -> Parser (VoteFile 'Out -> GovernanceVoteCreateCmdArgs 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 VoteUrl (VoteUrl, SafeHash StandardCrypto AnchorData)) -> Parser (Maybe (PotentiallyCheckedAnchor VoteUrl (VoteUrl, SafeHash StandardCrypto AnchorData))) forall (f :: * -> *) a. Alternative f => f a -> f (Maybe a) optional ( Parser (MustCheckHash VoteUrl) -> Parser (VoteUrl, SafeHash StandardCrypto AnchorData) -> Parser (PotentiallyCheckedAnchor VoteUrl (VoteUrl, SafeHash StandardCrypto AnchorData)) forall anchorType anchor. Parser (MustCheckHash anchorType) -> Parser anchor -> Parser (PotentiallyCheckedAnchor anchorType anchor) pPotentiallyCheckedAnchorData Parser (MustCheckHash VoteUrl) pMustCheckVoteUrl Parser (VoteUrl, SafeHash StandardCrypto AnchorData) pVoteAnchor ) Parser (VoteFile 'Out -> GovernanceVoteCreateCmdArgs era) -> Parser (VoteFile 'Out) -> Parser (GovernanceVoteCreateCmdArgs era) forall a b. Parser (a -> b) -> Parser a -> Parser b forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b <*> String -> String -> Parser (VoteFile 'Out) forall a. String -> String -> Parser (File a 'Out) pFileOutDirection String "out-file" String "Output filepath of the vote." pAnyVotingStakeVerificationKeyOrHashOrFile :: Parser AnyVotingStakeVerificationKeyOrHashOrFile pAnyVotingStakeVerificationKeyOrHashOrFile :: Parser AnyVotingStakeVerificationKeyOrHashOrFile pAnyVotingStakeVerificationKeyOrHashOrFile = [Parser AnyVotingStakeVerificationKeyOrHashOrFile] -> Parser AnyVotingStakeVerificationKeyOrHashOrFile forall (t :: * -> *) (f :: * -> *) a. (Foldable t, Alternative f) => t (f a) -> f a asum [ VerificationKeyOrHashOrFileOrScriptHash DRepKey -> AnyVotingStakeVerificationKeyOrHashOrFile AnyDRepVerificationKeyOrHashOrFileOrScriptHash (VerificationKeyOrHashOrFileOrScriptHash DRepKey -> AnyVotingStakeVerificationKeyOrHashOrFile) -> Parser (VerificationKeyOrHashOrFileOrScriptHash DRepKey) -> Parser AnyVotingStakeVerificationKeyOrHashOrFile forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b <$> Parser (VerificationKeyOrHashOrFileOrScriptHash DRepKey) pDRepVerificationKeyOrHashOrFileOrScriptHash , VerificationKeyOrHashOrFile StakePoolKey -> AnyVotingStakeVerificationKeyOrHashOrFile AnyStakePoolVerificationKeyOrHashOrFile (VerificationKeyOrHashOrFile StakePoolKey -> AnyVotingStakeVerificationKeyOrHashOrFile) -> Parser (VerificationKeyOrHashOrFile StakePoolKey) -> Parser AnyVotingStakeVerificationKeyOrHashOrFile forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b <$> Maybe String -> Parser (VerificationKeyOrHashOrFile StakePoolKey) pStakePoolVerificationKeyOrHashOrFile Maybe String forall a. Maybe a Nothing , VerificationKeyOrHashOrFileOrScriptHash CommitteeHotKey -> AnyVotingStakeVerificationKeyOrHashOrFile AnyCommitteeHotVerificationKeyOrHashOrFileOrScriptHash (VerificationKeyOrHashOrFileOrScriptHash CommitteeHotKey -> AnyVotingStakeVerificationKeyOrHashOrFile) -> Parser (VerificationKeyOrHashOrFileOrScriptHash CommitteeHotKey) -> Parser AnyVotingStakeVerificationKeyOrHashOrFile forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b <$> Parser (VerificationKeyOrHashOrFileOrScriptHash CommitteeHotKey) pCommitteeHotVerificationKeyOrHashOrVerificationFileOrScriptHash ] pGovernanceVoteViewCmd :: () => ShelleyBasedEra era -> Maybe (Parser (GovernanceVoteCmds era)) pGovernanceVoteViewCmd :: forall era. ShelleyBasedEra era -> Maybe (Parser (GovernanceVoteCmds era)) pGovernanceVoteViewCmd 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 (GovernanceVoteCmds era) -> Maybe (Parser (GovernanceVoteCmds era)) forall a. a -> Maybe a forall (f :: * -> *) a. Applicative f => a -> f a pure (Parser (GovernanceVoteCmds era) -> Maybe (Parser (GovernanceVoteCmds era))) -> Parser (GovernanceVoteCmds era) -> Maybe (Parser (GovernanceVoteCmds era)) forall a b. (a -> b) -> a -> b $ Mod CommandFields (GovernanceVoteCmds era) -> Parser (GovernanceVoteCmds era) forall a. Mod CommandFields a -> Parser a Opt.hsubparser (Mod CommandFields (GovernanceVoteCmds era) -> Parser (GovernanceVoteCmds era)) -> Mod CommandFields (GovernanceVoteCmds era) -> Parser (GovernanceVoteCmds era) forall a b. (a -> b) -> a -> b $ String -> ParserInfo (GovernanceVoteCmds era) -> Mod CommandFields (GovernanceVoteCmds era) forall a. String -> ParserInfo a -> Mod CommandFields a commandWithMetavar String "view" (ParserInfo (GovernanceVoteCmds era) -> Mod CommandFields (GovernanceVoteCmds era)) -> ParserInfo (GovernanceVoteCmds era) -> Mod CommandFields (GovernanceVoteCmds era) forall a b. (a -> b) -> a -> b $ Parser (GovernanceVoteCmds era) -> InfoMod (GovernanceVoteCmds era) -> ParserInfo (GovernanceVoteCmds era) forall a. Parser a -> InfoMod a -> ParserInfo a Opt.info (GovernanceVoteViewCmdArgs era -> GovernanceVoteCmds era forall era. GovernanceVoteViewCmdArgs era -> GovernanceVoteCmds era GovernanceVoteViewCmd (GovernanceVoteViewCmdArgs era -> GovernanceVoteCmds era) -> Parser (GovernanceVoteViewCmdArgs era) -> Parser (GovernanceVoteCmds era) forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b <$> ConwayEraOnwards era -> Parser (GovernanceVoteViewCmdArgs era) forall era. ConwayEraOnwards era -> Parser (GovernanceVoteViewCmdArgs era) pGovernanceVoteViewCmdArgs ConwayEraOnwards era w) (InfoMod (GovernanceVoteCmds era) -> ParserInfo (GovernanceVoteCmds era)) -> InfoMod (GovernanceVoteCmds era) -> ParserInfo (GovernanceVoteCmds era) forall a b. (a -> b) -> a -> b $ String -> InfoMod (GovernanceVoteCmds era) forall a. String -> InfoMod a Opt.progDesc String "Vote viewing." pGovernanceVoteViewCmdArgs :: ConwayEraOnwards era -> Parser (GovernanceVoteViewCmdArgs era) pGovernanceVoteViewCmdArgs :: forall era. ConwayEraOnwards era -> Parser (GovernanceVoteViewCmdArgs era) pGovernanceVoteViewCmdArgs ConwayEraOnwards era cOnwards = ConwayEraOnwards era -> ViewOutputFormat -> VoteFile 'In -> Maybe (File () 'Out) -> GovernanceVoteViewCmdArgs era forall era. ConwayEraOnwards era -> ViewOutputFormat -> VoteFile 'In -> Maybe (File () 'Out) -> GovernanceVoteViewCmdArgs era GovernanceVoteViewCmdArgs ConwayEraOnwards era cOnwards (ViewOutputFormat -> VoteFile 'In -> Maybe (File () 'Out) -> GovernanceVoteViewCmdArgs era) -> Parser ViewOutputFormat -> Parser (VoteFile 'In -> Maybe (File () 'Out) -> GovernanceVoteViewCmdArgs era) forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b <$> Parser ViewOutputFormat pGovernanceVoteViewOutputFormat Parser (VoteFile 'In -> Maybe (File () 'Out) -> GovernanceVoteViewCmdArgs era) -> Parser (VoteFile 'In) -> Parser (Maybe (File () 'Out) -> GovernanceVoteViewCmdArgs era) forall a b. Parser (a -> b) -> Parser a -> Parser b forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b <*> String -> String -> Parser (VoteFile 'In) forall a. String -> String -> Parser (File a 'In) pFileInDirection String "vote-file" String "Input filepath of the vote." Parser (Maybe (File () 'Out) -> GovernanceVoteViewCmdArgs era) -> Parser (Maybe (File () 'Out)) -> Parser (GovernanceVoteViewCmdArgs 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 (Maybe (File () 'Out)) forall content. Parser (Maybe (File content 'Out)) pMaybeOutputFile