{-# LANGUAGE DataKinds #-}
{-# LANGUAGE LambdaCase #-}
module Cardano.CLI.Compatible.StakeAddress.Command
( CompatibleStakeAddressCmds (..)
, renderCompatibleStakeAddressCmds
)
where
import Cardano.Api.Ledger (Coin)
import Cardano.Api.Shelley
import Cardano.CLI.Type.Key
import Prelude
import Data.Text (Text)
data CompatibleStakeAddressCmds era
= CompatibleStakeAddressRegistrationCertificateCmd
(ShelleyBasedEra era)
StakeIdentifier
(Maybe (Featured ConwayEraOnwards era Coin))
(File () Out)
| CompatibleStakeAddressStakeDelegationCertificateCmd
(ShelleyBasedEra era)
StakeIdentifier
(VerificationKeyOrHashOrFile StakePoolKey)
(File () Out)
deriving Int -> CompatibleStakeAddressCmds era -> ShowS
[CompatibleStakeAddressCmds era] -> ShowS
CompatibleStakeAddressCmds era -> String
(Int -> CompatibleStakeAddressCmds era -> ShowS)
-> (CompatibleStakeAddressCmds era -> String)
-> ([CompatibleStakeAddressCmds era] -> ShowS)
-> Show (CompatibleStakeAddressCmds era)
forall era. Int -> CompatibleStakeAddressCmds era -> ShowS
forall era. [CompatibleStakeAddressCmds era] -> ShowS
forall era. CompatibleStakeAddressCmds era -> String
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
$cshowsPrec :: forall era. Int -> CompatibleStakeAddressCmds era -> ShowS
showsPrec :: Int -> CompatibleStakeAddressCmds era -> ShowS
$cshow :: forall era. CompatibleStakeAddressCmds era -> String
show :: CompatibleStakeAddressCmds era -> String
$cshowList :: forall era. [CompatibleStakeAddressCmds era] -> ShowS
showList :: [CompatibleStakeAddressCmds era] -> ShowS
Show
renderCompatibleStakeAddressCmds :: CompatibleStakeAddressCmds era -> Text
renderCompatibleStakeAddressCmds :: forall era. CompatibleStakeAddressCmds era -> Text
renderCompatibleStakeAddressCmds =
Text -> Text -> Text
forall a. Semigroup a => a -> a -> a
(<>) Text
"stake-address " (Text -> Text)
-> (CompatibleStakeAddressCmds era -> Text)
-> CompatibleStakeAddressCmds era
-> Text
forall b c a. (b -> c) -> (a -> b) -> a -> c
. \case
CompatibleStakeAddressRegistrationCertificateCmd{} -> Text
"registration-certificate"
CompatibleStakeAddressStakeDelegationCertificateCmd{} -> Text
"stake-delegation-certificate"