{-# LANGUAGE DataKinds #-}
{-# LANGUAGE DuplicateRecordFields #-}
{-# LANGUAGE FlexibleContexts #-}
{-# LANGUAGE GADTs #-}
{-# LANGUAGE LambdaCase #-}
{-# LANGUAGE StandaloneDeriving #-}
module Cardano.CLI.EraBased.Commands.Governance.Actions
( GovernanceActionCmds (..)
, GovernanceActionUpdateCommitteeCmdArgs (..)
, GovernanceActionCreateConstitutionCmdArgs (..)
, GovernanceActionCreateNoConfidenceCmdArgs (..)
, GovernanceActionInfoCmdArgs (..)
, GovernanceActionViewCmdArgs (..)
, GovernanceActionProtocolParametersUpdateCmdArgs (..)
, GovernanceActionTreasuryWithdrawalCmdArgs (..)
, UpdateProtocolParametersConwayOnwards (..)
, UpdateProtocolParametersPreConway (..)
, GovernanceActionHardforkInitCmdArgs (..)
, CostModelsFile (..)
, renderGovernanceActionCmds
)
where
import Cardano.Api
import qualified Cardano.Api.Ledger as L
import Cardano.Api.Shelley
import Cardano.CLI.Types.Common
import Cardano.CLI.Types.Key
import Data.Text (Text)
import Data.Word
data GovernanceActionCmds era
= GovernanceActionCreateConstitutionCmd !(GovernanceActionCreateConstitutionCmdArgs era)
| GovernanceActionUpdateCommitteeCmd !(GovernanceActionUpdateCommitteeCmdArgs era)
| GovernanceActionCreateNoConfidenceCmd !(GovernanceActionCreateNoConfidenceCmdArgs era)
| GovernanceActionProtocolParametersUpdateCmd !(GovernanceActionProtocolParametersUpdateCmdArgs era)
| GovernanceActionTreasuryWithdrawalCmd !(GovernanceActionTreasuryWithdrawalCmdArgs era)
| GovernanceActionHardforkInitCmd !(GovernanceActionHardforkInitCmdArgs era)
| GovernanceActionInfoCmd !(GovernanceActionInfoCmdArgs era)
| GovernanceActionViewCmd !(GovernanceActionViewCmdArgs era)
deriving Int -> GovernanceActionCmds era -> ShowS
[GovernanceActionCmds era] -> ShowS
GovernanceActionCmds era -> String
(Int -> GovernanceActionCmds era -> ShowS)
-> (GovernanceActionCmds era -> String)
-> ([GovernanceActionCmds era] -> ShowS)
-> Show (GovernanceActionCmds era)
forall era. Int -> GovernanceActionCmds era -> ShowS
forall era. [GovernanceActionCmds era] -> ShowS
forall era. GovernanceActionCmds era -> String
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
$cshowsPrec :: forall era. Int -> GovernanceActionCmds era -> ShowS
showsPrec :: Int -> GovernanceActionCmds era -> ShowS
$cshow :: forall era. GovernanceActionCmds era -> String
show :: GovernanceActionCmds era -> String
$cshowList :: forall era. [GovernanceActionCmds era] -> ShowS
showList :: [GovernanceActionCmds era] -> ShowS
Show
data GovernanceActionUpdateCommitteeCmdArgs era
= GovernanceActionUpdateCommitteeCmdArgs
{ forall era.
GovernanceActionUpdateCommitteeCmdArgs era -> ConwayEraOnwards era
eon :: !(ConwayEraOnwards era)
, forall era. GovernanceActionUpdateCommitteeCmdArgs era -> Network
networkId :: !L.Network
, forall era. GovernanceActionUpdateCommitteeCmdArgs era -> Lovelace
deposit :: !Lovelace
, forall era.
GovernanceActionUpdateCommitteeCmdArgs era -> StakeIdentifier
returnAddress :: !StakeIdentifier
, forall era.
GovernanceActionUpdateCommitteeCmdArgs era -> ProposalUrl
proposalUrl :: !ProposalUrl
, forall era.
GovernanceActionUpdateCommitteeCmdArgs era
-> SafeHash StandardCrypto AnchorData
proposalHash :: !(L.SafeHash L.StandardCrypto L.AnchorData)
, forall era.
GovernanceActionUpdateCommitteeCmdArgs era
-> MustCheckHash ProposalUrl
checkProposalHash :: !(MustCheckHash ProposalUrl)
, forall era.
GovernanceActionUpdateCommitteeCmdArgs era
-> [VerificationKeyOrHashOrFileOrScriptHash CommitteeColdKey]
oldCommitteeVkeySource :: ![VerificationKeyOrHashOrFileOrScriptHash CommitteeColdKey]
, forall era.
GovernanceActionUpdateCommitteeCmdArgs era
-> [(VerificationKeyOrHashOrFileOrScriptHash CommitteeColdKey,
EpochNo)]
newCommitteeVkeySource :: ![(VerificationKeyOrHashOrFileOrScriptHash CommitteeColdKey, EpochNo)]
, forall era. GovernanceActionUpdateCommitteeCmdArgs era -> Rational
requiredThreshold :: !Rational
, forall era.
GovernanceActionUpdateCommitteeCmdArgs era -> Maybe (TxId, Word16)
mPrevGovernanceActionId :: !(Maybe (TxId, Word16))
, forall era.
GovernanceActionUpdateCommitteeCmdArgs era -> File () 'Out
outFile :: !(File () Out)
}
deriving Int -> GovernanceActionUpdateCommitteeCmdArgs era -> ShowS
[GovernanceActionUpdateCommitteeCmdArgs era] -> ShowS
GovernanceActionUpdateCommitteeCmdArgs era -> String
(Int -> GovernanceActionUpdateCommitteeCmdArgs era -> ShowS)
-> (GovernanceActionUpdateCommitteeCmdArgs era -> String)
-> ([GovernanceActionUpdateCommitteeCmdArgs era] -> ShowS)
-> Show (GovernanceActionUpdateCommitteeCmdArgs era)
forall era.
Int -> GovernanceActionUpdateCommitteeCmdArgs era -> ShowS
forall era. [GovernanceActionUpdateCommitteeCmdArgs era] -> ShowS
forall era. GovernanceActionUpdateCommitteeCmdArgs era -> String
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
$cshowsPrec :: forall era.
Int -> GovernanceActionUpdateCommitteeCmdArgs era -> ShowS
showsPrec :: Int -> GovernanceActionUpdateCommitteeCmdArgs era -> ShowS
$cshow :: forall era. GovernanceActionUpdateCommitteeCmdArgs era -> String
show :: GovernanceActionUpdateCommitteeCmdArgs era -> String
$cshowList :: forall era. [GovernanceActionUpdateCommitteeCmdArgs era] -> ShowS
showList :: [GovernanceActionUpdateCommitteeCmdArgs era] -> ShowS
Show
data GovernanceActionCreateConstitutionCmdArgs era
= GovernanceActionCreateConstitutionCmdArgs
{ forall era.
GovernanceActionCreateConstitutionCmdArgs era
-> ConwayEraOnwards era
eon :: !(ConwayEraOnwards era)
, forall era.
GovernanceActionCreateConstitutionCmdArgs era -> Network
networkId :: !L.Network
, forall era.
GovernanceActionCreateConstitutionCmdArgs era -> Lovelace
deposit :: !Lovelace
, forall era.
GovernanceActionCreateConstitutionCmdArgs era -> StakeIdentifier
stakeCredential :: !StakeIdentifier
, forall era.
GovernanceActionCreateConstitutionCmdArgs era
-> Maybe (TxId, Word16)
mPrevGovernanceActionId :: !(Maybe (TxId, Word16))
, forall era.
GovernanceActionCreateConstitutionCmdArgs era -> ProposalUrl
proposalUrl :: !ProposalUrl
, forall era.
GovernanceActionCreateConstitutionCmdArgs era
-> SafeHash StandardCrypto AnchorData
proposalHash :: !(L.SafeHash L.StandardCrypto L.AnchorData)
, forall era.
GovernanceActionCreateConstitutionCmdArgs era
-> MustCheckHash ProposalUrl
checkProposalHash :: !(MustCheckHash ProposalUrl)
, forall era.
GovernanceActionCreateConstitutionCmdArgs era -> ConstitutionUrl
constitutionUrl :: !ConstitutionUrl
, forall era.
GovernanceActionCreateConstitutionCmdArgs era
-> SafeHash StandardCrypto AnchorData
constitutionHash :: !(L.SafeHash L.StandardCrypto L.AnchorData)
, forall era.
GovernanceActionCreateConstitutionCmdArgs era
-> MustCheckHash ConstitutionUrl
checkConstitutionHash :: !(MustCheckHash ConstitutionUrl)
, forall era.
GovernanceActionCreateConstitutionCmdArgs era -> Maybe ScriptHash
constitutionScript :: !(Maybe ScriptHash)
, forall era.
GovernanceActionCreateConstitutionCmdArgs era -> File () 'Out
outFile :: !(File () Out)
}
deriving Int -> GovernanceActionCreateConstitutionCmdArgs era -> ShowS
[GovernanceActionCreateConstitutionCmdArgs era] -> ShowS
GovernanceActionCreateConstitutionCmdArgs era -> String
(Int -> GovernanceActionCreateConstitutionCmdArgs era -> ShowS)
-> (GovernanceActionCreateConstitutionCmdArgs era -> String)
-> ([GovernanceActionCreateConstitutionCmdArgs era] -> ShowS)
-> Show (GovernanceActionCreateConstitutionCmdArgs era)
forall era.
Int -> GovernanceActionCreateConstitutionCmdArgs era -> ShowS
forall era.
[GovernanceActionCreateConstitutionCmdArgs era] -> ShowS
forall era. GovernanceActionCreateConstitutionCmdArgs era -> String
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
$cshowsPrec :: forall era.
Int -> GovernanceActionCreateConstitutionCmdArgs era -> ShowS
showsPrec :: Int -> GovernanceActionCreateConstitutionCmdArgs era -> ShowS
$cshow :: forall era. GovernanceActionCreateConstitutionCmdArgs era -> String
show :: GovernanceActionCreateConstitutionCmdArgs era -> String
$cshowList :: forall era.
[GovernanceActionCreateConstitutionCmdArgs era] -> ShowS
showList :: [GovernanceActionCreateConstitutionCmdArgs era] -> ShowS
Show
data GovernanceActionInfoCmdArgs era
= GovernanceActionInfoCmdArgs
{ forall era. GovernanceActionInfoCmdArgs era -> ConwayEraOnwards era
eon :: !(ConwayEraOnwards era)
, forall era. GovernanceActionInfoCmdArgs era -> Network
networkId :: !L.Network
, forall era. GovernanceActionInfoCmdArgs era -> Lovelace
deposit :: !Lovelace
, forall era. GovernanceActionInfoCmdArgs era -> StakeIdentifier
returnStakeAddress :: !StakeIdentifier
, forall era. GovernanceActionInfoCmdArgs era -> ProposalUrl
proposalUrl :: !ProposalUrl
, forall era.
GovernanceActionInfoCmdArgs era
-> SafeHash StandardCrypto AnchorData
proposalHash :: !(L.SafeHash L.StandardCrypto L.AnchorData)
, forall era.
GovernanceActionInfoCmdArgs era -> MustCheckHash ProposalUrl
checkProposalHash :: !(MustCheckHash ProposalUrl)
, forall era. GovernanceActionInfoCmdArgs era -> File () 'Out
outFile :: !(File () Out)
}
deriving Int -> GovernanceActionInfoCmdArgs era -> ShowS
[GovernanceActionInfoCmdArgs era] -> ShowS
GovernanceActionInfoCmdArgs era -> String
(Int -> GovernanceActionInfoCmdArgs era -> ShowS)
-> (GovernanceActionInfoCmdArgs era -> String)
-> ([GovernanceActionInfoCmdArgs era] -> ShowS)
-> Show (GovernanceActionInfoCmdArgs era)
forall era. Int -> GovernanceActionInfoCmdArgs era -> ShowS
forall era. [GovernanceActionInfoCmdArgs era] -> ShowS
forall era. GovernanceActionInfoCmdArgs era -> String
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
$cshowsPrec :: forall era. Int -> GovernanceActionInfoCmdArgs era -> ShowS
showsPrec :: Int -> GovernanceActionInfoCmdArgs era -> ShowS
$cshow :: forall era. GovernanceActionInfoCmdArgs era -> String
show :: GovernanceActionInfoCmdArgs era -> String
$cshowList :: forall era. [GovernanceActionInfoCmdArgs era] -> ShowS
showList :: [GovernanceActionInfoCmdArgs era] -> ShowS
Show
data GovernanceActionCreateNoConfidenceCmdArgs era
= GovernanceActionCreateNoConfidenceCmdArgs
{ forall era.
GovernanceActionCreateNoConfidenceCmdArgs era
-> ConwayEraOnwards era
eon :: !(ConwayEraOnwards era)
, forall era.
GovernanceActionCreateNoConfidenceCmdArgs era -> Network
networkId :: !L.Network
, forall era.
GovernanceActionCreateNoConfidenceCmdArgs era -> Lovelace
deposit :: !Lovelace
, forall era.
GovernanceActionCreateNoConfidenceCmdArgs era -> StakeIdentifier
returnStakeAddress :: !StakeIdentifier
, forall era.
GovernanceActionCreateNoConfidenceCmdArgs era -> ProposalUrl
proposalUrl :: !ProposalUrl
, forall era.
GovernanceActionCreateNoConfidenceCmdArgs era
-> SafeHash StandardCrypto AnchorData
proposalHash :: !(L.SafeHash L.StandardCrypto L.AnchorData)
, forall era.
GovernanceActionCreateNoConfidenceCmdArgs era
-> MustCheckHash ProposalUrl
checkProposalHash :: !(MustCheckHash ProposalUrl)
, forall era.
GovernanceActionCreateNoConfidenceCmdArgs era
-> Maybe (TxId, Word16)
mPrevGovernanceActionId :: !(Maybe (TxId, Word16))
, forall era.
GovernanceActionCreateNoConfidenceCmdArgs era -> File () 'Out
outFile :: !(File () Out)
}
deriving Int -> GovernanceActionCreateNoConfidenceCmdArgs era -> ShowS
[GovernanceActionCreateNoConfidenceCmdArgs era] -> ShowS
GovernanceActionCreateNoConfidenceCmdArgs era -> String
(Int -> GovernanceActionCreateNoConfidenceCmdArgs era -> ShowS)
-> (GovernanceActionCreateNoConfidenceCmdArgs era -> String)
-> ([GovernanceActionCreateNoConfidenceCmdArgs era] -> ShowS)
-> Show (GovernanceActionCreateNoConfidenceCmdArgs era)
forall era.
Int -> GovernanceActionCreateNoConfidenceCmdArgs era -> ShowS
forall era.
[GovernanceActionCreateNoConfidenceCmdArgs era] -> ShowS
forall era. GovernanceActionCreateNoConfidenceCmdArgs era -> String
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
$cshowsPrec :: forall era.
Int -> GovernanceActionCreateNoConfidenceCmdArgs era -> ShowS
showsPrec :: Int -> GovernanceActionCreateNoConfidenceCmdArgs era -> ShowS
$cshow :: forall era. GovernanceActionCreateNoConfidenceCmdArgs era -> String
show :: GovernanceActionCreateNoConfidenceCmdArgs era -> String
$cshowList :: forall era.
[GovernanceActionCreateNoConfidenceCmdArgs era] -> ShowS
showList :: [GovernanceActionCreateNoConfidenceCmdArgs era] -> ShowS
Show
data GovernanceActionProtocolParametersUpdateCmdArgs era
= GovernanceActionProtocolParametersUpdateCmdArgs
{ forall era.
GovernanceActionProtocolParametersUpdateCmdArgs era
-> ShelleyBasedEra era
uppShelleyBasedEra :: !(ShelleyBasedEra era)
, forall era.
GovernanceActionProtocolParametersUpdateCmdArgs era
-> Maybe (UpdateProtocolParametersPreConway era)
uppPreConway :: !(Maybe (UpdateProtocolParametersPreConway era))
, forall era.
GovernanceActionProtocolParametersUpdateCmdArgs era
-> Maybe (UpdateProtocolParametersConwayOnwards era)
uppConwayOnwards :: !(Maybe (UpdateProtocolParametersConwayOnwards era))
, forall era.
GovernanceActionProtocolParametersUpdateCmdArgs era
-> EraBasedProtocolParametersUpdate era
uppNewPParams :: !(EraBasedProtocolParametersUpdate era)
, forall era.
GovernanceActionProtocolParametersUpdateCmdArgs era
-> Maybe (CostModelsFile era)
uppCostModelsFile :: !(Maybe (CostModelsFile era))
, forall era.
GovernanceActionProtocolParametersUpdateCmdArgs era -> File () 'Out
uppFilePath :: !(File () Out)
}
deriving Int -> GovernanceActionProtocolParametersUpdateCmdArgs era -> ShowS
[GovernanceActionProtocolParametersUpdateCmdArgs era] -> ShowS
GovernanceActionProtocolParametersUpdateCmdArgs era -> String
(Int
-> GovernanceActionProtocolParametersUpdateCmdArgs era -> ShowS)
-> (GovernanceActionProtocolParametersUpdateCmdArgs era -> String)
-> ([GovernanceActionProtocolParametersUpdateCmdArgs era] -> ShowS)
-> Show (GovernanceActionProtocolParametersUpdateCmdArgs era)
forall era.
Int -> GovernanceActionProtocolParametersUpdateCmdArgs era -> ShowS
forall era.
[GovernanceActionProtocolParametersUpdateCmdArgs era] -> ShowS
forall era.
GovernanceActionProtocolParametersUpdateCmdArgs era -> String
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
$cshowsPrec :: forall era.
Int -> GovernanceActionProtocolParametersUpdateCmdArgs era -> ShowS
showsPrec :: Int -> GovernanceActionProtocolParametersUpdateCmdArgs era -> ShowS
$cshow :: forall era.
GovernanceActionProtocolParametersUpdateCmdArgs era -> String
show :: GovernanceActionProtocolParametersUpdateCmdArgs era -> String
$cshowList :: forall era.
[GovernanceActionProtocolParametersUpdateCmdArgs era] -> ShowS
showList :: [GovernanceActionProtocolParametersUpdateCmdArgs era] -> ShowS
Show
data GovernanceActionTreasuryWithdrawalCmdArgs era
= GovernanceActionTreasuryWithdrawalCmdArgs
{ forall era.
GovernanceActionTreasuryWithdrawalCmdArgs era
-> ConwayEraOnwards era
eon :: !(ConwayEraOnwards era)
, forall era.
GovernanceActionTreasuryWithdrawalCmdArgs era -> Network
networkId :: !L.Network
, forall era.
GovernanceActionTreasuryWithdrawalCmdArgs era -> Lovelace
deposit :: !Lovelace
, forall era.
GovernanceActionTreasuryWithdrawalCmdArgs era -> StakeIdentifier
returnAddr :: !StakeIdentifier
, forall era.
GovernanceActionTreasuryWithdrawalCmdArgs era -> ProposalUrl
proposalUrl :: !ProposalUrl
, forall era.
GovernanceActionTreasuryWithdrawalCmdArgs era
-> SafeHash StandardCrypto AnchorData
proposalHash :: !(L.SafeHash L.StandardCrypto L.AnchorData)
, forall era.
GovernanceActionTreasuryWithdrawalCmdArgs era
-> MustCheckHash ProposalUrl
checkProposalHash :: !(MustCheckHash ProposalUrl)
, forall era.
GovernanceActionTreasuryWithdrawalCmdArgs era
-> [(StakeIdentifier, Lovelace)]
treasuryWithdrawal :: ![(StakeIdentifier, Lovelace)]
, forall era.
GovernanceActionTreasuryWithdrawalCmdArgs era -> Maybe ScriptHash
constitutionScriptHash :: !(Maybe ScriptHash)
, forall era.
GovernanceActionTreasuryWithdrawalCmdArgs era -> File () 'Out
outFile :: !(File () Out)
}
deriving Int -> GovernanceActionTreasuryWithdrawalCmdArgs era -> ShowS
[GovernanceActionTreasuryWithdrawalCmdArgs era] -> ShowS
GovernanceActionTreasuryWithdrawalCmdArgs era -> String
(Int -> GovernanceActionTreasuryWithdrawalCmdArgs era -> ShowS)
-> (GovernanceActionTreasuryWithdrawalCmdArgs era -> String)
-> ([GovernanceActionTreasuryWithdrawalCmdArgs era] -> ShowS)
-> Show (GovernanceActionTreasuryWithdrawalCmdArgs era)
forall era.
Int -> GovernanceActionTreasuryWithdrawalCmdArgs era -> ShowS
forall era.
[GovernanceActionTreasuryWithdrawalCmdArgs era] -> ShowS
forall era. GovernanceActionTreasuryWithdrawalCmdArgs era -> String
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
$cshowsPrec :: forall era.
Int -> GovernanceActionTreasuryWithdrawalCmdArgs era -> ShowS
showsPrec :: Int -> GovernanceActionTreasuryWithdrawalCmdArgs era -> ShowS
$cshow :: forall era. GovernanceActionTreasuryWithdrawalCmdArgs era -> String
show :: GovernanceActionTreasuryWithdrawalCmdArgs era -> String
$cshowList :: forall era.
[GovernanceActionTreasuryWithdrawalCmdArgs era] -> ShowS
showList :: [GovernanceActionTreasuryWithdrawalCmdArgs era] -> ShowS
Show
data GovernanceActionHardforkInitCmdArgs era
= GovernanceActionHardforkInitCmdArgs
{ forall era.
GovernanceActionHardforkInitCmdArgs era -> ConwayEraOnwards era
eon :: !(ConwayEraOnwards era)
, forall era. GovernanceActionHardforkInitCmdArgs era -> Network
networkId :: !L.Network
, forall era. GovernanceActionHardforkInitCmdArgs era -> Lovelace
deposit :: !Lovelace
, forall era.
GovernanceActionHardforkInitCmdArgs era -> StakeIdentifier
returnStakeAddress :: !StakeIdentifier
, forall era.
GovernanceActionHardforkInitCmdArgs era -> Maybe (TxId, Word16)
mPrevGovernanceActionId :: !(Maybe (TxId, Word16))
, forall era. GovernanceActionHardforkInitCmdArgs era -> ProposalUrl
proposalUrl :: !ProposalUrl
, forall era.
GovernanceActionHardforkInitCmdArgs era
-> SafeHash StandardCrypto AnchorData
proposalHash :: !(L.SafeHash L.StandardCrypto L.AnchorData)
, forall era.
GovernanceActionHardforkInitCmdArgs era
-> MustCheckHash ProposalUrl
checkProposalHash :: !(MustCheckHash ProposalUrl)
, forall era. GovernanceActionHardforkInitCmdArgs era -> ProtVer
protVer :: !L.ProtVer
, forall era. GovernanceActionHardforkInitCmdArgs era -> File () 'Out
outFile :: !(File () Out)
}
deriving Int -> GovernanceActionHardforkInitCmdArgs era -> ShowS
[GovernanceActionHardforkInitCmdArgs era] -> ShowS
GovernanceActionHardforkInitCmdArgs era -> String
(Int -> GovernanceActionHardforkInitCmdArgs era -> ShowS)
-> (GovernanceActionHardforkInitCmdArgs era -> String)
-> ([GovernanceActionHardforkInitCmdArgs era] -> ShowS)
-> Show (GovernanceActionHardforkInitCmdArgs era)
forall era. Int -> GovernanceActionHardforkInitCmdArgs era -> ShowS
forall era. [GovernanceActionHardforkInitCmdArgs era] -> ShowS
forall era. GovernanceActionHardforkInitCmdArgs era -> String
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
$cshowsPrec :: forall era. Int -> GovernanceActionHardforkInitCmdArgs era -> ShowS
showsPrec :: Int -> GovernanceActionHardforkInitCmdArgs era -> ShowS
$cshow :: forall era. GovernanceActionHardforkInitCmdArgs era -> String
show :: GovernanceActionHardforkInitCmdArgs era -> String
$cshowList :: forall era. [GovernanceActionHardforkInitCmdArgs era] -> ShowS
showList :: [GovernanceActionHardforkInitCmdArgs era] -> ShowS
Show
data GovernanceActionViewCmdArgs era
= GovernanceActionViewCmdArgs
{ forall era. GovernanceActionViewCmdArgs era -> ConwayEraOnwards era
eon :: !(ConwayEraOnwards era)
, forall era. GovernanceActionViewCmdArgs era -> ProposalFile 'In
actionFile :: !(ProposalFile In)
, forall era. GovernanceActionViewCmdArgs era -> ViewOutputFormat
outFormat :: !ViewOutputFormat
, forall era. GovernanceActionViewCmdArgs era -> Maybe (File () 'Out)
mOutFile :: !(Maybe (File () Out))
}
deriving Int -> GovernanceActionViewCmdArgs era -> ShowS
[GovernanceActionViewCmdArgs era] -> ShowS
GovernanceActionViewCmdArgs era -> String
(Int -> GovernanceActionViewCmdArgs era -> ShowS)
-> (GovernanceActionViewCmdArgs era -> String)
-> ([GovernanceActionViewCmdArgs era] -> ShowS)
-> Show (GovernanceActionViewCmdArgs era)
forall era. Int -> GovernanceActionViewCmdArgs era -> ShowS
forall era. [GovernanceActionViewCmdArgs era] -> ShowS
forall era. GovernanceActionViewCmdArgs era -> String
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
$cshowsPrec :: forall era. Int -> GovernanceActionViewCmdArgs era -> ShowS
showsPrec :: Int -> GovernanceActionViewCmdArgs era -> ShowS
$cshow :: forall era. GovernanceActionViewCmdArgs era -> String
show :: GovernanceActionViewCmdArgs era -> String
$cshowList :: forall era. [GovernanceActionViewCmdArgs era] -> ShowS
showList :: [GovernanceActionViewCmdArgs era] -> ShowS
Show
data UpdateProtocolParametersConwayOnwards era
= UpdateProtocolParametersConwayOnwards
{ forall era.
UpdateProtocolParametersConwayOnwards era -> ConwayEraOnwards era
eon :: !(ConwayEraOnwards era)
, forall era. UpdateProtocolParametersConwayOnwards era -> Network
networkId :: !L.Network
, forall era. UpdateProtocolParametersConwayOnwards era -> Lovelace
deposit :: !Lovelace
, forall era.
UpdateProtocolParametersConwayOnwards era -> StakeIdentifier
returnAddr :: !StakeIdentifier
, forall era.
UpdateProtocolParametersConwayOnwards era -> ProposalUrl
proposalUrl :: !ProposalUrl
, forall era.
UpdateProtocolParametersConwayOnwards era
-> SafeHash StandardCrypto AnchorData
proposalHash :: !(L.SafeHash L.StandardCrypto L.AnchorData)
, forall era.
UpdateProtocolParametersConwayOnwards era
-> MustCheckHash ProposalUrl
checkProposalHash :: !(MustCheckHash ProposalUrl)
, forall era.
UpdateProtocolParametersConwayOnwards era -> Maybe (TxId, Word16)
governanceActionId :: !(Maybe (TxId, Word16))
, forall era.
UpdateProtocolParametersConwayOnwards era -> Maybe ScriptHash
constitutionScriptHash :: !(Maybe ScriptHash)
}
data CostModelsFile era
= CostModelsFile
{ forall era. CostModelsFile era -> AlonzoEraOnwards era
eon :: !(AlonzoEraOnwards era)
, forall era. CostModelsFile era -> File CostModels 'In
costModelsFile :: !(File L.CostModels In)
}
deriving Int -> CostModelsFile era -> ShowS
[CostModelsFile era] -> ShowS
CostModelsFile era -> String
(Int -> CostModelsFile era -> ShowS)
-> (CostModelsFile era -> String)
-> ([CostModelsFile era] -> ShowS)
-> Show (CostModelsFile era)
forall era. Int -> CostModelsFile era -> ShowS
forall era. [CostModelsFile era] -> ShowS
forall era. CostModelsFile era -> String
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
$cshowsPrec :: forall era. Int -> CostModelsFile era -> ShowS
showsPrec :: Int -> CostModelsFile era -> ShowS
$cshow :: forall era. CostModelsFile era -> String
show :: CostModelsFile era -> String
$cshowList :: forall era. [CostModelsFile era] -> ShowS
showList :: [CostModelsFile era] -> ShowS
Show
deriving instance Show (UpdateProtocolParametersConwayOnwards era)
data UpdateProtocolParametersPreConway era
= UpdateProtocolParametersPreConway
{ forall era.
UpdateProtocolParametersPreConway era -> ShelleyToBabbageEra era
eon :: !(ShelleyToBabbageEra era)
, forall era. UpdateProtocolParametersPreConway era -> EpochNo
expiryEpoch :: !EpochNo
, forall era.
UpdateProtocolParametersPreConway era -> [VerificationKeyFile 'In]
genesisVerificationKeys :: ![VerificationKeyFile In]
}
deriving instance Show (UpdateProtocolParametersPreConway era)
renderGovernanceActionCmds :: GovernanceActionCmds era -> Text
renderGovernanceActionCmds :: forall era. GovernanceActionCmds era -> Text
renderGovernanceActionCmds =
(Text
"governance action " Text -> Text -> Text
forall a. Semigroup a => a -> a -> a
<>) (Text -> Text)
-> (GovernanceActionCmds era -> Text)
-> GovernanceActionCmds era
-> Text
forall b c a. (b -> c) -> (a -> b) -> a -> c
. \case
GovernanceActionCreateConstitutionCmd{} ->
Text
"create-constitution"
GovernanceActionProtocolParametersUpdateCmd{} ->
Text
"create-protocol-parameters-update"
GovernanceActionTreasuryWithdrawalCmd{} ->
Text
"create-treasury-withdrawal"
GovernanceActionUpdateCommitteeCmd{} ->
Text
"update-committee"
GovernanceActionCreateNoConfidenceCmd{} ->
Text
"create-no-confidence"
GovernanceActionHardforkInitCmd{} ->
Text
"create-hardfork"
GovernanceActionInfoCmd{} ->
Text
"create-info"
GovernanceActionViewCmd{} ->
Text
"view"