From e21008902d2222a19a4c685bc3952d6e5b35de21 Mon Sep 17 00:00:00 2001 From: John Ky Date: Tue, 23 May 2023 18:53:19 +1000 Subject: [PATCH] Add CCM commands --- cardano-cli/cardano-cli.cabal | 1 + .../src/Cardano/CLI/Shelley/Commands.hs | 35 +++ .../src/Cardano/CLI/Shelley/Parsers.hs | 67 +++++ cardano-cli/src/Cardano/CLI/Shelley/Run.hs | 22 +- .../src/Cardano/CLI/Shelley/Run/Ccm.hs | 244 ++++++++++++++++++ .../cardano-cli-golden/files/golden/help.cli | 41 +++ .../files/golden/help/ccm.cli | 15 ++ .../files/golden/help/ccm_issue-op-cert.cli | 22 ++ .../files/golden/help/ccm_key-gen-VRF.cli | 10 + .../files/golden/help/ccm_key-gen.cli | 15 ++ .../files/golden/help/ccm_key-hash-VRF.cli | 13 + .../files/golden/help/ccm_new-counter.cli | 22 ++ 12 files changed, 497 insertions(+), 10 deletions(-) create mode 100644 cardano-cli/src/Cardano/CLI/Shelley/Run/Ccm.hs create mode 100644 cardano-cli/test/cardano-cli-golden/files/golden/help/ccm.cli create mode 100644 cardano-cli/test/cardano-cli-golden/files/golden/help/ccm_issue-op-cert.cli create mode 100644 cardano-cli/test/cardano-cli-golden/files/golden/help/ccm_key-gen-VRF.cli create mode 100644 cardano-cli/test/cardano-cli-golden/files/golden/help/ccm_key-gen.cli create mode 100644 cardano-cli/test/cardano-cli-golden/files/golden/help/ccm_key-hash-VRF.cli create mode 100644 cardano-cli/test/cardano-cli-golden/files/golden/help/ccm_new-counter.cli diff --git a/cardano-cli/cardano-cli.cabal b/cardano-cli/cardano-cli.cabal index 23a05c3eff..fd768ab72e 100644 --- a/cardano-cli/cardano-cli.cabal +++ b/cardano-cli/cardano-cli.cabal @@ -82,6 +82,7 @@ library Cardano.CLI.Shelley.Run Cardano.CLI.Shelley.Run.Address Cardano.CLI.Shelley.Run.Address.Info + Cardano.CLI.Shelley.Run.Ccm Cardano.CLI.Shelley.Run.Genesis Cardano.CLI.Shelley.Run.Governance Cardano.CLI.Shelley.Run.Key diff --git a/cardano-cli/src/Cardano/CLI/Shelley/Commands.hs b/cardano-cli/src/Cardano/CLI/Shelley/Commands.hs index 0584081e6e..a6192d1101 100644 --- a/cardano-cli/src/Cardano/CLI/Shelley/Commands.hs +++ b/cardano-cli/src/Cardano/CLI/Shelley/Commands.hs @@ -1,5 +1,6 @@ {-# LANGUAGE DataKinds #-} {-# LANGUAGE FlexibleContexts #-} +{-# LANGUAGE LambdaCase #-} {-# LANGUAGE UndecidableInstances #-} -- | Shelley CLI command types @@ -7,6 +8,7 @@ module Cardano.CLI.Shelley.Commands ( -- * CLI command types ShelleyCommand (..) , AddressCmd (..) + , CcmCmd (..) , StakeAddressCmd (..) , KeyCmd (..) , TransactionCmd (..) @@ -64,6 +66,7 @@ import Data.Text (Text) -- data ShelleyCommand = AddressCmd AddressCmd + | CcmCmd CcmCmd | StakeAddressCmd StakeAddressCmd | KeyCmd KeyCmd | TransactionCmd TransactionCmd @@ -78,6 +81,7 @@ renderShelleyCommand :: ShelleyCommand -> Text renderShelleyCommand sc = case sc of AddressCmd cmd -> renderAddressCmd cmd + CcmCmd cmd -> renderCcmCmd cmd StakeAddressCmd cmd -> renderStakeAddressCmd cmd KeyCmd cmd -> renderKeyCmd cmd TransactionCmd cmd -> renderTransactionCmd cmd @@ -272,6 +276,37 @@ renderTransactionCmd cmd = TxGetTxId {} -> "transaction txid" TxView {} -> "transaction view" +data CcmCmd + = CcmKeyGenCold + (VerificationKeyFile Out) + (SigningKeyFile Out) + (OpCertCounterFile Out) + | CcmKeyGenVRF + (VerificationKeyFile Out) + (SigningKeyFile Out) + | CcmKeyHashVRF + (VerificationKeyOrFile VrfKey) + (Maybe (File () Out)) + | CcmNewCounter + ColdVerificationKeyOrFile + Word + (OpCertCounterFile InOut) + | CcmIssueOpCert + (VerificationKeyOrFile KesKey) + (SigningKeyFile In) + (OpCertCounterFile InOut) + KESPeriod + (File () Out) + deriving Show + +renderCcmCmd :: CcmCmd -> Text +renderCcmCmd = \case + CcmKeyGenCold {} -> "ccm key-gen" + CcmKeyGenVRF {} -> "ccm key-gen-VRF" + CcmKeyHashVRF {} -> "ccm key-hash-VRF" + CcmNewCounter {} -> "ccm new-counter" + CcmIssueOpCert{} -> "ccm issue-op-cert" + data NodeCmd = NodeKeyGenCold (VerificationKeyFile Out) (SigningKeyFile Out) (OpCertCounterFile Out) | NodeKeyGenKES (VerificationKeyFile Out) (SigningKeyFile Out) diff --git a/cardano-cli/src/Cardano/CLI/Shelley/Parsers.hs b/cardano-cli/src/Cardano/CLI/Shelley/Parsers.hs index 1d5c193b46..2e46cb1a2b 100644 --- a/cardano-cli/src/Cardano/CLI/Shelley/Parsers.hs +++ b/cardano-cli/src/Cardano/CLI/Shelley/Parsers.hs @@ -78,6 +78,8 @@ parseShelleyCommands envCli = , Opt.commandGroup "Era based commands" , Opt.command "address" $ Opt.info (AddressCmd <$> pAddressCmd envCli) $ Opt.progDesc "Payment address commands" + , Opt.command "ccm" $ + Opt.info (CcmCmd <$> pCcmCmd) $ Opt.progDesc "CCM operation commands" , Opt.command "stake-address" $ Opt.info (StakeAddressCmd <$> pStakeAddressCmd envCli) $ Opt.progDesc "Stake address commands" , Opt.command "key" $ @@ -833,6 +835,71 @@ pTransaction envCli = pTransactionView :: Parser TransactionCmd pTransactionView = TxView <$> pInputTxOrTxBodyFile + +pCcmCmd :: Parser CcmCmd +pCcmCmd = + asum + [ subParser "key-gen" . Opt.info pKeyGenOperator . Opt.progDesc $ mconcat + [ "Create a key pair for a CCM's offline " + , "key and a new certificate issue counter" + ] + , subParser "key-gen-VRF" . Opt.info pKeyGenVRF . Opt.progDesc $ mconcat + [ "Create a key pair for a CCM VRF operational key" + ] + , subParser "key-hash-VRF". Opt.info pKeyHashVRF . Opt.progDesc $ mconcat + [ "Print hash of a CCM's operational VRF key." + ] + , subParser "new-counter" . Opt.info pNewCounter . Opt.progDesc $ mconcat + [ "Create a new certificate issue counter" + ] + , subParser "issue-op-cert" . Opt.info pIssueOpCert . Opt.progDesc $ mconcat + [ "Issue a CCM operational certificate" + ] + ] + where + pKeyGenOperator :: Parser CcmCmd + pKeyGenOperator = + CcmKeyGenCold + <$> pColdVerificationKeyFile + <*> pColdSigningKeyFile + <*> pOperatorCertIssueCounterFile + + pKeyGenVRF :: Parser CcmCmd + pKeyGenVRF = + CcmKeyGenVRF + <$> pVerificationKeyFileOut + <*> pSigningKeyFileOut + + pKeyHashVRF :: Parser CcmCmd + pKeyHashVRF = + CcmKeyHashVRF + <$> pVerificationKeyOrFile AsVrfKey + <*> pMaybeOutputFile + + pNewCounter :: Parser CcmCmd + pNewCounter = + CcmNewCounter + <$> pColdVerificationKeyOrFile + <*> pCounterValue + <*> pOperatorCertIssueCounterFile + + pCounterValue :: Parser Word + pCounterValue = + Opt.option Opt.auto $ mconcat + [ Opt.long "counter-value" + , Opt.metavar "INT" + , Opt.help "The next certificate issue counter value to use." + ] + + pIssueOpCert :: Parser CcmCmd + pIssueOpCert = + CcmIssueOpCert + <$> pKesVerificationKeyOrFile + <*> pColdSigningKeyFile + <*> pOperatorCertIssueCounterFile + <*> pKesPeriod + <*> pOutputFile + pNodeCmd :: Parser NodeCmd pNodeCmd = asum diff --git a/cardano-cli/src/Cardano/CLI/Shelley/Run.hs b/cardano-cli/src/Cardano/CLI/Shelley/Run.hs index bdab475dd8..a38d2cf32c 100644 --- a/cardano-cli/src/Cardano/CLI/Shelley/Run.hs +++ b/cardano-cli/src/Cardano/CLI/Shelley/Run.hs @@ -4,30 +4,29 @@ module Cardano.CLI.Shelley.Run , runShelleyClientCommand ) where -import Control.Monad.Trans.Except (ExceptT) -import Data.Text (Text) - import Cardano.Api -import Control.Monad.Trans.Except.Extra (firstExceptT) -import qualified Data.Text as Text - import Cardano.CLI.Shelley.Parsers - import Cardano.CLI.Shelley.Run.Address +import Cardano.CLI.Shelley.Run.Ccm +import Cardano.CLI.Shelley.Run.Genesis import Cardano.CLI.Shelley.Run.Governance import Cardano.CLI.Shelley.Run.Key import Cardano.CLI.Shelley.Run.Node import Cardano.CLI.Shelley.Run.Pool import Cardano.CLI.Shelley.Run.Query import Cardano.CLI.Shelley.Run.StakeAddress -import Cardano.CLI.Shelley.Run.Transaction - -- Block, System, DevOps -import Cardano.CLI.Shelley.Run.Genesis import Cardano.CLI.Shelley.Run.TextView +import Cardano.CLI.Shelley.Run.Transaction + +import Control.Monad.Trans.Except (ExceptT) +import Control.Monad.Trans.Except.Extra (firstExceptT) +import Data.Text (Text) +import qualified Data.Text as Text data ShelleyClientCmdError = ShelleyCmdAddressError !ShelleyAddressCmdError + | ShelleyCmdCcmError !ShelleyCcmCmdError | ShelleyCmdGenesisError !ShelleyGenesisCmdError | ShelleyCmdGovernanceError !ShelleyGovernanceCmdError | ShelleyCmdNodeError !ShelleyNodeCmdError @@ -43,6 +42,8 @@ renderShelleyClientCmdError cmd err = case err of ShelleyCmdAddressError addrCmdErr -> renderError cmd renderShelleyAddressCmdError addrCmdErr + ShelleyCmdCcmError nodeCmdErr -> + renderError cmd renderShelleyCcmCmdError nodeCmdErr ShelleyCmdGenesisError genesisCmdErr -> renderError cmd (Text.pack . displayError) genesisCmdErr ShelleyCmdGovernanceError govCmdErr -> @@ -77,6 +78,7 @@ renderShelleyClientCmdError cmd err = runShelleyClientCommand :: ShelleyCommand -> ExceptT ShelleyClientCmdError IO () runShelleyClientCommand (AddressCmd cmd) = firstExceptT ShelleyCmdAddressError $ runAddressCmd cmd +runShelleyClientCommand (CcmCmd cmd) = firstExceptT ShelleyCmdCcmError $ runCcmCmd cmd runShelleyClientCommand (StakeAddressCmd cmd) = firstExceptT ShelleyCmdStakeAddressError $ runStakeAddressCmd cmd runShelleyClientCommand (KeyCmd cmd) = firstExceptT ShelleyCmdKeyError $ runKeyCmd cmd runShelleyClientCommand (TransactionCmd cmd) = firstExceptT ShelleyCmdTransactionError $ runTransactionCmd cmd diff --git a/cardano-cli/src/Cardano/CLI/Shelley/Run/Ccm.hs b/cardano-cli/src/Cardano/CLI/Shelley/Run/Ccm.hs new file mode 100644 index 0000000000..f62f32e1b0 --- /dev/null +++ b/cardano-cli/src/Cardano/CLI/Shelley/Run/Ccm.hs @@ -0,0 +1,244 @@ +{-# LANGUAGE DataKinds #-} +{-# LANGUAGE LambdaCase #-} + +module Cardano.CLI.Shelley.Run.Ccm + ( ShelleyCcmCmdError(..) + , renderShelleyCcmCmdError + , runCcmCmd + , runCcmKeyGenCold + , runCcmKeyGenVRF + ) where + +import Cardano.Api +import Cardano.Api.Shelley + +import Cardano.CLI.Shelley.Commands +import Cardano.CLI.Shelley.Key (VerificationKeyOrFile, readVerificationKeyOrFile) +import Cardano.CLI.Types (SigningKeyFile, VerificationKeyFile) + +import Control.Monad.IO.Class (MonadIO (..)) +import Control.Monad.Trans.Except (ExceptT) +import Control.Monad.Trans.Except.Extra (firstExceptT, hoistEither, newExceptT) +import qualified Data.ByteString.Char8 as BS +import Data.String (fromString) +import Data.Text (Text) +import qualified Data.Text as Text +import Data.Word (Word64) + +{- HLINT ignore "Reduce duplication" -} + +data ShelleyCcmCmdError + = ShelleyCcmCmdReadFileError !(FileError TextEnvelopeError) + | ShelleyCcmCmdReadKeyFileError !(FileError InputDecodeError) + | ShelleyCcmCmdWriteFileError !(FileError ()) + | ShelleyCcmCmdOperationalCertificateIssueError !OperationalCertIssueError + | ShelleyCcmCmdVrfSigningKeyCreationError + FilePath + -- ^ Target path + FilePath + -- ^ Temp path + deriving Show + +renderShelleyCcmCmdError :: ShelleyCcmCmdError -> Text +renderShelleyCcmCmdError err = + case err of + ShelleyCcmCmdVrfSigningKeyCreationError targetPath tempPath -> + Text.pack $ "Error creating VRF signing key file. Target path: " <> targetPath + <> " Temporary path: " <> tempPath + + ShelleyCcmCmdReadFileError fileErr -> Text.pack (displayError fileErr) + + ShelleyCcmCmdReadKeyFileError fileErr -> Text.pack (displayError fileErr) + + ShelleyCcmCmdWriteFileError fileErr -> Text.pack (displayError fileErr) + + ShelleyCcmCmdOperationalCertificateIssueError issueErr -> + Text.pack (displayError issueErr) + + +runCcmCmd :: CcmCmd -> ExceptT ShelleyCcmCmdError IO () +runCcmCmd = \case + CcmKeyGenCold vk sk ctr -> runCcmKeyGenCold vk sk ctr + CcmKeyGenVRF vk sk -> runCcmKeyGenVRF vk sk + CcmKeyHashVRF vk mOutFp -> runCcmKeyHashVRF vk mOutFp + CcmNewCounter vk ctr out -> runCcmNewCounter vk ctr out + CcmIssueOpCert vk sk ctr p out -> runCcmIssueOpCert vk sk ctr p out + + +-- +-- Ccm command implementations +-- + +runCcmKeyGenCold :: VerificationKeyFile Out + -> SigningKeyFile Out + -> OpCertCounterFile Out + -> ExceptT ShelleyCcmCmdError IO () +runCcmKeyGenCold vkeyPath skeyPath ocertCtrPath = do + skey <- liftIO $ generateSigningKey AsStakePoolKey + let vkey = getVerificationKey skey + firstExceptT ShelleyCcmCmdWriteFileError + . newExceptT + $ writeLazyByteStringFile skeyPath + $ textEnvelopeToJSON (Just skeyDesc) skey + firstExceptT ShelleyCcmCmdWriteFileError + . newExceptT + $ writeLazyByteStringFile vkeyPath + $ textEnvelopeToJSON (Just vkeyDesc) vkey + firstExceptT ShelleyCcmCmdWriteFileError + . newExceptT + $ writeLazyByteStringFile ocertCtrPath + $ textEnvelopeToJSON (Just ocertCtrDesc) + $ OperationalCertificateIssueCounter initialCounter vkey + where + skeyDesc, vkeyDesc, ocertCtrDesc :: TextEnvelopeDescr + skeyDesc = "Stake Pool Operator Signing Key" + vkeyDesc = "Stake Pool Operator Verification Key" + ocertCtrDesc = "Next certificate issue number: " + <> fromString (show initialCounter) + + initialCounter :: Word64 + initialCounter = 0 + +runCcmKeyGenVRF :: + VerificationKeyFile Out + -> SigningKeyFile Out + -> ExceptT ShelleyCcmCmdError IO () +runCcmKeyGenVRF vkeyPath skeyPath = do + skey <- liftIO $ generateSigningKey AsVrfKey + let vkey = getVerificationKey skey + firstExceptT ShelleyCcmCmdWriteFileError + . newExceptT + $ writeLazyByteStringFileWithOwnerPermissions skeyPath + $ textEnvelopeToJSON (Just skeyDesc) skey + firstExceptT ShelleyCcmCmdWriteFileError + . newExceptT + $ writeLazyByteStringFile vkeyPath + $ textEnvelopeToJSON (Just vkeyDesc) vkey + where + skeyDesc, vkeyDesc :: TextEnvelopeDescr + skeyDesc = "VRF Signing Key" + vkeyDesc = "VRF Verification Key" + +runCcmKeyHashVRF :: VerificationKeyOrFile VrfKey + -> Maybe (File () Out) + -> ExceptT ShelleyCcmCmdError IO () +runCcmKeyHashVRF verKeyOrFile mOutputFp = do + vkey <- firstExceptT ShelleyCcmCmdReadKeyFileError + . newExceptT + $ readVerificationKeyOrFile AsVrfKey verKeyOrFile + + let hexKeyHash = serialiseToRawBytesHex (verificationKeyHash vkey) + + case mOutputFp of + Just fpath -> liftIO $ BS.writeFile (unFile fpath) hexKeyHash + Nothing -> liftIO $ BS.putStrLn hexKeyHash + + +runCcmNewCounter :: ColdVerificationKeyOrFile + -> Word + -> OpCertCounterFile InOut + -> ExceptT ShelleyCcmCmdError IO () +runCcmNewCounter coldVerKeyOrFile counter ocertCtrPath = do + + vkey <- firstExceptT ShelleyCcmCmdReadFileError . newExceptT $ + readColdVerificationKeyOrFile coldVerKeyOrFile + + let ocertIssueCounter = + OperationalCertificateIssueCounter (fromIntegral counter) vkey + + firstExceptT ShelleyCcmCmdWriteFileError . newExceptT + $ writeLazyByteStringFile (onlyOut ocertCtrPath) + $ textEnvelopeToJSON Nothing ocertIssueCounter + + +runCcmIssueOpCert :: VerificationKeyOrFile KesKey + -- ^ This is the hot KES verification key. + -> SigningKeyFile In + -- ^ This is the cold signing key. + -> OpCertCounterFile InOut + -- ^ Counter that establishes the precedence + -- of the operational certificate. + -> KESPeriod + -- ^ Start of the validity period for this certificate. + -> File () Out + -> ExceptT ShelleyCcmCmdError IO () +runCcmIssueOpCert kesVerKeyOrFile stakePoolSKeyFile ocertCtrPath kesPeriod certFile = do + + ocertIssueCounter <- firstExceptT ShelleyCcmCmdReadFileError + . newExceptT + $ readFileTextEnvelope AsOperationalCertificateIssueCounter (onlyIn ocertCtrPath) + + verKeyKes <- firstExceptT ShelleyCcmCmdReadKeyFileError + . newExceptT + $ readVerificationKeyOrFile AsKesKey kesVerKeyOrFile + + signKey <- firstExceptT ShelleyCcmCmdReadKeyFileError + . newExceptT + $ readKeyFileAnyOf + bech32PossibleBlockIssuers + textEnvPossibleBlockIssuers + stakePoolSKeyFile + + (ocert, nextOcertCtr) <- + firstExceptT ShelleyCcmCmdOperationalCertificateIssueError + . hoistEither + $ issueOperationalCertificate + verKeyKes + signKey + kesPeriod + ocertIssueCounter + + -- Write the counter first, to reduce the chance of ending up with + -- a new cert but without updating the counter. + firstExceptT ShelleyCcmCmdWriteFileError + . newExceptT + $ writeLazyByteStringFile (onlyOut ocertCtrPath) + $ textEnvelopeToJSON (Just $ ocertCtrDesc $ getCounter nextOcertCtr) nextOcertCtr + + firstExceptT ShelleyCcmCmdWriteFileError + . newExceptT + $ writeLazyByteStringFile certFile + $ textEnvelopeToJSON Nothing ocert + where + getCounter :: OperationalCertificateIssueCounter -> Word64 + getCounter (OperationalCertificateIssueCounter n _) = n + + ocertCtrDesc :: Word64 -> TextEnvelopeDescr + ocertCtrDesc n = "Next certificate issue number: " <> fromString (show n) + + textEnvPossibleBlockIssuers + :: [FromSomeType HasTextEnvelope + (Either (SigningKey StakePoolKey) + (SigningKey GenesisDelegateExtendedKey))] + textEnvPossibleBlockIssuers = + [ FromSomeType (AsSigningKey AsStakePoolKey) Left + , FromSomeType (AsSigningKey AsGenesisDelegateKey) (Left . castSigningKey) + , FromSomeType (AsSigningKey AsGenesisDelegateExtendedKey) Right + ] + + bech32PossibleBlockIssuers + :: [FromSomeType SerialiseAsBech32 + (Either (SigningKey StakePoolKey) + (SigningKey GenesisDelegateExtendedKey))] + bech32PossibleBlockIssuers = + [FromSomeType (AsSigningKey AsStakePoolKey) Left] + +-- | Read a cold verification key or file. +-- +-- If a filepath is provided, it will be interpreted as a text envelope +-- formatted file. +readColdVerificationKeyOrFile + :: ColdVerificationKeyOrFile + -> IO (Either (FileError TextEnvelopeError) (VerificationKey StakePoolKey)) +readColdVerificationKeyOrFile coldVerKeyOrFile = + case coldVerKeyOrFile of + ColdStakePoolVerificationKey vk -> pure (Right vk) + ColdGenesisDelegateVerificationKey vk -> + pure $ Right (castVerificationKey vk) + ColdVerificationKeyFile fp -> + readFileTextEnvelopeAnyOf + [ FromSomeType (AsVerificationKey AsStakePoolKey) id + , FromSomeType (AsVerificationKey AsGenesisDelegateKey) castVerificationKey + ] + fp + diff --git a/cardano-cli/test/cardano-cli-golden/files/golden/help.cli b/cardano-cli/test/cardano-cli-golden/files/golden/help.cli index b67157136d..ed97549d2b 100644 --- a/cardano-cli/test/cardano-cli-golden/files/golden/help.cli +++ b/cardano-cli/test/cardano-cli-golden/files/golden/help.cli @@ -1030,6 +1030,47 @@ Usage: cardano-cli stake-address delegation-certificate Create a stake address pool delegation certificate +Usage: cardano-cli ccm + (key-gen | key-gen-VRF | key-hash-VRF | new-counter | issue-op-cert) + + CCM operation commands + +Usage: cardano-cli ccm key-gen --cold-verification-key-file FILE + --cold-signing-key-file FILE + --operational-certificate-issue-counter-file FILE + + Create a key pair for a CCM's offline key and a new certificate issue counter + +Usage: cardano-cli ccm key-gen-VRF --verification-key-file FILE + --signing-key-file FILE + + Create a key pair for a CCM VRF operational key + +Usage: cardano-cli ccm key-hash-VRF + (--verification-key STRING | --verification-key-file FILE) + [--out-file FILE] + + Print hash of a CCM's operational VRF key. + +Usage: cardano-cli ccm new-counter + ( --stake-pool-verification-key STRING + | --genesis-delegate-verification-key STRING + | --cold-verification-key-file FILE + ) + --counter-value INT + --operational-certificate-issue-counter-file FILE + + Create a new certificate issue counter + +Usage: cardano-cli ccm issue-op-cert + (--kes-verification-key STRING | --kes-verification-key-file FILE) + --cold-signing-key-file FILE + --operational-certificate-issue-counter-file FILE + --kes-period NATURAL + --out-file FILE + + Issue a CCM operational certificate + Usage: cardano-cli address (key-gen | key-hash | build | info) Payment address commands diff --git a/cardano-cli/test/cardano-cli-golden/files/golden/help/ccm.cli b/cardano-cli/test/cardano-cli-golden/files/golden/help/ccm.cli new file mode 100644 index 0000000000..4d3a7d56ef --- /dev/null +++ b/cardano-cli/test/cardano-cli-golden/files/golden/help/ccm.cli @@ -0,0 +1,15 @@ +Usage: cardano-cli ccm + (key-gen | key-gen-VRF | key-hash-VRF | new-counter | issue-op-cert) + + CCM operation commands + +Available options: + -h,--help Show this help text + +Available commands: + key-gen Create a key pair for a CCM's offline key and a new + certificate issue counter + key-gen-VRF Create a key pair for a CCM VRF operational key + key-hash-VRF Print hash of a CCM's operational VRF key. + new-counter Create a new certificate issue counter + issue-op-cert Issue a CCM operational certificate diff --git a/cardano-cli/test/cardano-cli-golden/files/golden/help/ccm_issue-op-cert.cli b/cardano-cli/test/cardano-cli-golden/files/golden/help/ccm_issue-op-cert.cli new file mode 100644 index 0000000000..ab5843f3ea --- /dev/null +++ b/cardano-cli/test/cardano-cli-golden/files/golden/help/ccm_issue-op-cert.cli @@ -0,0 +1,22 @@ +Usage: cardano-cli ccm issue-op-cert + (--kes-verification-key STRING | --kes-verification-key-file FILE) + --cold-signing-key-file FILE + --operational-certificate-issue-counter-file FILE + --kes-period NATURAL + --out-file FILE + + Issue a CCM operational certificate + +Available options: + --kes-verification-key STRING + A Bech32 or hex-encoded hot KES verification key. + --kes-verification-key-file FILE + Filepath of the hot KES verification key. + --cold-signing-key-file FILE + Filepath of the cold signing key. + --operational-certificate-issue-counter-file FILE + The file with the issue counter for the operational + certificate. + --kes-period NATURAL The start of the KES key validity period. + --out-file FILE The output file. + -h,--help Show this help text diff --git a/cardano-cli/test/cardano-cli-golden/files/golden/help/ccm_key-gen-VRF.cli b/cardano-cli/test/cardano-cli-golden/files/golden/help/ccm_key-gen-VRF.cli new file mode 100644 index 0000000000..2d752125eb --- /dev/null +++ b/cardano-cli/test/cardano-cli-golden/files/golden/help/ccm_key-gen-VRF.cli @@ -0,0 +1,10 @@ +Usage: cardano-cli ccm key-gen-VRF --verification-key-file FILE + --signing-key-file FILE + + Create a key pair for a CCM VRF operational key + +Available options: + --verification-key-file FILE + Output filepath of the verification key. + --signing-key-file FILE Output filepath of the signing key. + -h,--help Show this help text diff --git a/cardano-cli/test/cardano-cli-golden/files/golden/help/ccm_key-gen.cli b/cardano-cli/test/cardano-cli-golden/files/golden/help/ccm_key-gen.cli new file mode 100644 index 0000000000..f5583cdc47 --- /dev/null +++ b/cardano-cli/test/cardano-cli-golden/files/golden/help/ccm_key-gen.cli @@ -0,0 +1,15 @@ +Usage: cardano-cli ccm key-gen --cold-verification-key-file FILE + --cold-signing-key-file FILE + --operational-certificate-issue-counter-file FILE + + Create a key pair for a CCM's offline key and a new certificate issue counter + +Available options: + --cold-verification-key-file FILE + Filepath of the cold verification key. + --cold-signing-key-file FILE + Filepath of the cold signing key. + --operational-certificate-issue-counter-file FILE + The file with the issue counter for the operational + certificate. + -h,--help Show this help text diff --git a/cardano-cli/test/cardano-cli-golden/files/golden/help/ccm_key-hash-VRF.cli b/cardano-cli/test/cardano-cli-golden/files/golden/help/ccm_key-hash-VRF.cli new file mode 100644 index 0000000000..f30c78545c --- /dev/null +++ b/cardano-cli/test/cardano-cli-golden/files/golden/help/ccm_key-hash-VRF.cli @@ -0,0 +1,13 @@ +Usage: cardano-cli ccm key-hash-VRF + (--verification-key STRING | --verification-key-file FILE) + [--out-file FILE] + + Print hash of a CCM's operational VRF key. + +Available options: + --verification-key STRING + Verification key (Bech32 or hex-encoded). + --verification-key-file FILE + Input filepath of the verification key. + --out-file FILE Optional output file. Default is to write to stdout. + -h,--help Show this help text diff --git a/cardano-cli/test/cardano-cli-golden/files/golden/help/ccm_new-counter.cli b/cardano-cli/test/cardano-cli-golden/files/golden/help/ccm_new-counter.cli new file mode 100644 index 0000000000..917d5ce6fb --- /dev/null +++ b/cardano-cli/test/cardano-cli-golden/files/golden/help/ccm_new-counter.cli @@ -0,0 +1,22 @@ +Usage: cardano-cli ccm new-counter + ( --stake-pool-verification-key STRING + | --genesis-delegate-verification-key STRING + | --cold-verification-key-file FILE + ) + --counter-value INT + --operational-certificate-issue-counter-file FILE + + Create a new certificate issue counter + +Available options: + --stake-pool-verification-key STRING + Stake pool verification key (Bech32 or hex-encoded). + --genesis-delegate-verification-key STRING + Genesis delegate verification key (hex-encoded). + --cold-verification-key-file FILE + Filepath of the cold verification key. + --counter-value INT The next certificate issue counter value to use. + --operational-certificate-issue-counter-file FILE + The file with the issue counter for the operational + certificate. + -h,--help Show this help text