Skip to content

Commit

Permalink
Merge #1822
Browse files Browse the repository at this point in the history
1822: Add command for converting Byron, Icarus, and Shelley style cardano-address signing keys r=intricate a=intricate

Closes #1756 

Help text output of the new command added by this PR:

```
Usage: cardano-cli shelley key convert-cardano-address-key (--shelley-payment-key |
                                                                     
                                                                     --shelley-stake-key |
                                                                     
                                                                     --icarus-payment-key |
                                                                     
                                                                     --byron-payment-key)
                                                                   --signing-key-file FILE
                                                                   --out-file FILE
  Convert a cardano-address extended signing key to a corresponding
  Shelley-format key.

Available options:
  --shelley-payment-key    Use a Shelley-era extended payment key.
  --shelley-stake-key      Use a Shelley-era extended stake key.
  --icarus-payment-key     Use a Byron-era extended payment key formatted in the
                           Icarus style.
  --byron-payment-key      Use a Byron-era extended payment key formatted in the
                           deprecated Byron style.
  --signing-key-file FILE  Input filepath of the signing key.
  --out-file FILE          The output file.
```

Co-authored-by: Luke Nadur <19835357+intricate@users.noreply.github.com>
  • Loading branch information
iohk-bors[bot] and intricate authored Sep 15, 2020
2 parents f8178d8 + 289de30 commit 696a928
Show file tree
Hide file tree
Showing 12 changed files with 448 additions and 56 deletions.
1 change: 1 addition & 0 deletions cardano-cli/cardano-cli.cabal
Original file line number Diff line number Diff line change
Expand Up @@ -235,6 +235,7 @@ test-suite cardano-cli-golden
Test.Golden.Shelley.Genesis.KeyGenGenesis
Test.Golden.Shelley.Genesis.KeyGenUtxo
Test.Golden.Shelley.Genesis.KeyHash
Test.Golden.Shelley.Key.ConvertCardanoAddressKey
Test.Golden.Shelley.Node.IssueOpCert
Test.Golden.Shelley.Node.KeyGen
Test.Golden.Shelley.Node.KeyGenKes
Expand Down
11 changes: 11 additions & 0 deletions cardano-cli/src/Cardano/CLI/Shelley/Commands.hs
Original file line number Diff line number Diff line change
Expand Up @@ -22,6 +22,7 @@ module Cardano.CLI.Shelley.Commands
, AddressKeyType (..)
, ByronKeyType (..)
, ByronKeyFormat (..)
, CardanoAddressKeyType (..)
, GenesisDir (..)
, TxInCount (..)
, TxOutCount (..)
Expand Down Expand Up @@ -136,6 +137,7 @@ data KeyCmd
| KeyConvertITNStakeKey SomeKeyFile OutputFile
| KeyConvertITNExtendedToStakeKey SomeKeyFile OutputFile
| KeyConvertITNBip32ToStakeKey SomeKeyFile OutputFile
| KeyConvertCardanoAddressSigningKey CardanoAddressKeyType SigningKeyFile OutputFile
deriving (Eq, Show)

renderKeyCmd :: KeyCmd -> Text
Expand All @@ -148,6 +150,7 @@ renderKeyCmd cmd =
KeyConvertITNStakeKey {} -> "key convert-itn-key"
KeyConvertITNExtendedToStakeKey {} -> "key convert-itn-extended-key"
KeyConvertITNBip32ToStakeKey {} -> "key convert-itn-bip32-key"
KeyConvertCardanoAddressSigningKey {} -> "key convert-cardano-address-signing-key"

data TransactionCmd
= TxBuildRaw
Expand Down Expand Up @@ -395,6 +398,14 @@ data ByronKeyFormat = NonLegacyByronKeyFormat
| LegacyByronKeyFormat
deriving (Eq, Show)

-- | The type of @cardano-address@ key.
data CardanoAddressKeyType
= CardanoAddressShelleyPaymentKey
| CardanoAddressShelleyStakeKey
| CardanoAddressIcarusPaymentKey
| CardanoAddressByronPaymentKey
deriving (Eq, Show)

newtype OpCertCounterFile
= OpCertCounterFile FilePath
deriving (Eq, Show)
Expand Down
31 changes: 31 additions & 0 deletions cardano-cli/src/Cardano/CLI/Shelley/Parsers.hs
Original file line number Diff line number Diff line change
Expand Up @@ -273,6 +273,11 @@ pKeyCmd =
Opt.progDesc $ "Convert an Incentivized Testnet (ITN) BIP32 "
++ "(Ed25519Bip32) signing key to a corresponding "
++ "Shelley stake signing key"

, Opt.command "convert-cardano-address-key" $
Opt.info pKeyConvertCardanoAddressSigningKey $
Opt.progDesc $ "Convert a cardano-address extended signing key "
++ "to a corresponding Shelley-format key."
]
where
pKeyGetVerificationKey :: Parser KeyCmd
Expand Down Expand Up @@ -411,6 +416,32 @@ pKeyCmd =
<> Opt.completer (Opt.bashCompleter "file")
)

pKeyConvertCardanoAddressSigningKey :: Parser KeyCmd
pKeyConvertCardanoAddressSigningKey =
KeyConvertCardanoAddressSigningKey
<$> pCardanoAddressKeyType
<*> pSigningKeyFile Input
<*> pOutputFile

pCardanoAddressKeyType :: Parser CardanoAddressKeyType
pCardanoAddressKeyType =
Opt.flag' CardanoAddressShelleyPaymentKey
( Opt.long "shelley-payment-key"
<> Opt.help "Use a Shelley-era extended payment key."
)
<|> Opt.flag' CardanoAddressShelleyStakeKey
( Opt.long "shelley-stake-key"
<> Opt.help "Use a Shelley-era extended stake key."
)
<|> Opt.flag' CardanoAddressIcarusPaymentKey
( Opt.long "icarus-payment-key"
<> Opt.help "Use a Byron-era extended payment key formatted in the Icarus style."
)
<|> Opt.flag' CardanoAddressByronPaymentKey
( Opt.long "byron-payment-key"
<> Opt.help "Use a Byron-era extended payment key formatted in the deprecated Byron style."
)

pTransaction :: Parser TransactionCmd
pTransaction =
Opt.subparser $
Expand Down
226 changes: 174 additions & 52 deletions cardano-cli/src/Cardano/CLI/Shelley/Run/Key.hs
Original file line number Diff line number Diff line change
Expand Up @@ -7,7 +7,7 @@ module Cardano.CLI.Shelley.Run.Key
, runKeyCmd

-- * Exports for testing
, decodeBech32Key
, decodeBech32
) where

import Cardano.Prelude
Expand All @@ -32,7 +32,7 @@ import qualified Cardano.Crypto.Signing as Byron
import qualified Shelley.Spec.Ledger.Keys as Shelley

import Cardano.Api.Shelley.ITN (xprvFromBytes)
import Cardano.Api.Typed hiding (Bech32DecodeError (..))
import Cardano.Api.Typed

import Cardano.CLI.Byron.Key (CardanoEra (..))
import qualified Cardano.CLI.Byron.Key as Byron
Expand All @@ -51,8 +51,10 @@ data ShelleyKeyCmdError
!Text
-- ^ Text representation of the parse error. Unfortunately, the actual
-- error type isn't exported.
| ShelleyKeyCmdItnKeyConvError !ConversionError
| ShelleyKeyCmdItnKeyConvError !ItnKeyConversionError
| ShelleyKeyCmdWrongKeyTypeError
| ShelleyKeyCmdCardanoAddressSigningKeyFileError
!(FileError CardanoAddressSigningKeyConversionError)
deriving Show

renderShelleyKeyCmdError :: ShelleyKeyCmdError -> Text
Expand All @@ -66,6 +68,8 @@ renderShelleyKeyCmdError err =
ShelleyKeyCmdItnKeyConvError convErr -> renderConversionError convErr
ShelleyKeyCmdWrongKeyTypeError -> Text.pack "Please use a signing key file \
\when converting ITN BIP32 or Extended keys"
ShelleyKeyCmdCardanoAddressSigningKeyFileError fileErr ->
Text.pack (displayError fileErr)

runKeyCmd :: KeyCmd -> ExceptT ShelleyKeyCmdError IO ()
runKeyCmd cmd =
Expand All @@ -89,6 +93,8 @@ runKeyCmd cmd =
KeyConvertITNBip32ToStakeKey itnPrivKeyFile outFile ->
runConvertITNBip32ToStakeKey itnPrivKeyFile outFile

KeyConvertCardanoAddressSigningKey keyType skfOld skfNew ->
runConvertCardanoAddressSigningKey keyType skfOld skfNew

runGetVerificationKey :: SigningKeyFile
-> VerificationKeyFile
Expand Down Expand Up @@ -438,86 +444,202 @@ runConvertITNBip32ToStakeKey (ASigningKeyFile (SigningKeyFile sk)) (OutputFile o
firstExceptT ShelleyKeyCmdWriteFileError . newExceptT
$ writeFileTextEnvelope outFile Nothing skey

data ConversionError
= Bech32DecodingError
-- ^ Bech32 key
!Text
!Bech32.DecodingError
| Bech32ErrorExtractingByes !Bech32.DataPart
| Bech32ReadError !FilePath !IOException
| ITNError !Bech32.HumanReadablePart !Bech32.DataPart
| SigningKeyDeserializationError !ByteString
| VerificationKeyDeserializationError !ByteString
-- | An error that can occur while converting an Incentivized Testnet (ITN)
-- key.
data ItnKeyConversionError
= ItnKeyBech32DecodeError !Bech32DecodeError
| ItnReadBech32FileError !FilePath !IOException
| ItnSigningKeyDeserialisationError !ByteString
| ItnVerificationKeyDeserialisationError !ByteString
deriving Show

renderConversionError :: ConversionError -> Text
-- | Render an error message for an 'ItnKeyConversionError'.
renderConversionError :: ItnKeyConversionError -> Text
renderConversionError err =
case err of
Bech32DecodingError key decErr ->
"Error decoding Bech32 key: " <> key <> " Error: " <> textShow decErr
Bech32ErrorExtractingByes dp ->
"Unable to extract bytes from: " <> Bech32.dataPartToText dp
Bech32ReadError fp readErr ->
"Error reading bech32 key at: " <> textShow fp
ItnKeyBech32DecodeError decErr ->
"Error decoding Bech32 key: " <> Text.pack (displayError decErr)
ItnReadBech32FileError fp readErr ->
"Error reading Bech32 key at: " <> textShow fp
<> " Error: " <> Text.pack (displayException readErr)
ITNError hRpart dp ->
"Error extracting a ByteString from DataPart: " <> Bech32.dataPartToText dp <>
" With human readable part: " <> Bech32.humanReadablePartToText hRpart
SigningKeyDeserializationError sKey ->
"Error deserialising signing key: " <> textShow (BSC.unpack sKey)
VerificationKeyDeserializationError vKey ->
ItnSigningKeyDeserialisationError _sKey ->
-- Sensitive data, such as the signing key, is purposely not included in
-- the error message.
"Error deserialising signing key."
ItnVerificationKeyDeserialisationError vKey ->
"Error deserialising verification key: " <> textShow (BSC.unpack vKey)

-- | Convert public ed25519 key to a Shelley stake verification key
convertITNVerificationKey :: Text -> Either ConversionError (VerificationKey StakeKey)
convertITNVerificationKey :: Text -> Either ItnKeyConversionError (VerificationKey StakeKey)
convertITNVerificationKey pubKey = do
(_, _, keyBS) <- decodeBech32Key pubKey
(_, _, keyBS) <- first ItnKeyBech32DecodeError (decodeBech32 pubKey)
case DSIGN.rawDeserialiseVerKeyDSIGN keyBS of
Just verKey -> Right . StakeVerificationKey $ Shelley.VKey verKey
Nothing -> Left $ VerificationKeyDeserializationError keyBS
Nothing -> Left $ ItnVerificationKeyDeserialisationError keyBS

-- | Convert private ed22519 key to a Shelley signing key.
convertITNSigningKey :: Text -> Either ConversionError (SigningKey StakeKey)
convertITNSigningKey :: Text -> Either ItnKeyConversionError (SigningKey StakeKey)
convertITNSigningKey privKey = do
(_, _, keyBS) <- decodeBech32Key privKey
(_, _, keyBS) <- first ItnKeyBech32DecodeError (decodeBech32 privKey)
case DSIGN.rawDeserialiseSignKeyDSIGN keyBS of
Just signKey -> Right $ StakeSigningKey signKey
Nothing -> Left $ SigningKeyDeserializationError keyBS
Nothing -> Left $ ItnSigningKeyDeserialisationError keyBS

-- | Convert extended private ed22519 key to a Shelley signing key
-- Extended private key = 64 bytes,
-- Public key = 32 bytes.
convertITNExtendedSigningKey :: Text -> Either ConversionError (SigningKey StakeExtendedKey)
convertITNExtendedSigningKey :: Text -> Either ItnKeyConversionError (SigningKey StakeExtendedKey)
convertITNExtendedSigningKey privKey = do
(_, _, privkeyBS) <- decodeBech32Key privKey
(_, _, privkeyBS) <- first ItnKeyBech32DecodeError (decodeBech32 privKey)
let dummyChainCode = BS.replicate 32 0
case xprvFromBytes $ BS.concat [privkeyBS, dummyChainCode] of
Just xprv -> Right $ StakeExtendedSigningKey xprv
Nothing -> Left $ SigningKeyDeserializationError privkeyBS
Nothing -> Left $ ItnSigningKeyDeserialisationError privkeyBS

-- BIP32 Private key = 96 bytes (64 bytes extended private key + 32 bytes chaincode)
-- BIP32 Public Key = 64 Bytes
convertITNBIP32SigningKey :: Text -> Either ConversionError (SigningKey StakeExtendedKey)
convertITNBIP32SigningKey :: Text -> Either ItnKeyConversionError (SigningKey StakeExtendedKey)
convertITNBIP32SigningKey privKey = do
(_, _, privkeyBS) <- decodeBech32Key privKey
(_, _, privkeyBS) <- first ItnKeyBech32DecodeError (decodeBech32 privKey)
case xprvFromBytes privkeyBS of
Just xprv -> Right $ StakeExtendedSigningKey xprv
Nothing -> Left $ SigningKeyDeserializationError privkeyBS

-- | Convert ITN Bech32 public or private keys to 'ByteString's
decodeBech32Key :: Text
-> Either ConversionError
(Bech32.HumanReadablePart, Bech32.DataPart, ByteString)
decodeBech32Key key =
case Bech32.decodeLenient key of
Left err -> Left $ Bech32DecodingError key err
Right (hRpart, dataPart) -> case Bech32.dataPartToBytes dataPart of
Nothing -> Left $ ITNError hRpart dataPart
Just bs -> Right (hRpart, dataPart, bs)

readFileITNKey :: FilePath -> IO (Either ConversionError Text)
Nothing -> Left $ ItnSigningKeyDeserialisationError privkeyBS

readFileITNKey :: FilePath -> IO (Either ItnKeyConversionError Text)
readFileITNKey fp = do
eStr <- Exception.try $ readFile fp
case eStr of
Left e -> return . Left $ Bech32ReadError fp e
Left e -> return . Left $ ItnReadBech32FileError fp e
Right str -> return . Right . Text.concat $ Text.words str

--------------------------------------------------------------------------------
-- `cardano-address` extended signing key conversions
--------------------------------------------------------------------------------

runConvertCardanoAddressSigningKey
:: CardanoAddressKeyType
-> SigningKeyFile
-> OutputFile
-> ExceptT ShelleyKeyCmdError IO ()
runConvertCardanoAddressSigningKey keyType skFile (OutputFile outFile) = do
sKey <- firstExceptT ShelleyKeyCmdCardanoAddressSigningKeyFileError
. newExceptT
$ readSomeCardanoAddressSigningKeyFile keyType skFile
firstExceptT ShelleyKeyCmdWriteFileError . newExceptT
$ writeSomeCardanoAddressSigningKeyFile outFile sKey

-- | Some kind of signing key that was converted from a @cardano-address@
-- signing key.
data SomeCardanoAddressSigningKey
= ACardanoAddrShelleyPaymentSigningKey !(SigningKey PaymentExtendedKey)
| ACardanoAddrShelleyStakeSigningKey !(SigningKey StakeExtendedKey)
| ACardanoAddrByronSigningKey !(SigningKey ByronKey)

-- | An error that can occur while converting a @cardano-address@ extended
-- signing key.
data CardanoAddressSigningKeyConversionError
= CardanoAddressSigningKeyBech32DecodeError !Bech32DecodeError
-- ^ There was an error in decoding the string as Bech32.
| CardanoAddressSigningKeyDeserialisationError !ByteString
-- ^ There was an error in converting the @cardano-address@ extended signing
-- key.
deriving (Show, Eq)

instance Error CardanoAddressSigningKeyConversionError where
displayError = Text.unpack . renderCardanoAddressSigningKeyConversionError

-- | Render an error message for a 'CardanoAddressSigningKeyConversionError'.
renderCardanoAddressSigningKeyConversionError
:: CardanoAddressSigningKeyConversionError
-> Text
renderCardanoAddressSigningKeyConversionError err =
case err of
CardanoAddressSigningKeyBech32DecodeError decErr ->
Text.pack (displayError decErr)
CardanoAddressSigningKeyDeserialisationError _bs ->
-- Sensitive data, such as the signing key, is purposely not included in
-- the error message.
"Error deserialising cardano-address signing key."

-- | Decode a Bech32-encoded string.
decodeBech32
:: Text
-> Either Bech32DecodeError (Bech32.HumanReadablePart, Bech32.DataPart, ByteString)
decodeBech32 bech32Str =
case Bech32.decodeLenient bech32Str of
Left err -> Left (Bech32DecodingError err)
Right (hrPart, dataPart) ->
case Bech32.dataPartToBytes dataPart of
Nothing ->
Left $ Bech32DataPartToBytesError (Bech32.dataPartToText dataPart)
Just bs -> Right (hrPart, dataPart, bs)

-- | Convert a Ed25519 BIP32 extended signing key (96 bytes) to a @cardano-crypto@
-- style extended signing key.
--
-- Note that both the ITN and @cardano-address@ use this key format.
convertBip32SigningKey
:: ByteString
-> Either CardanoAddressSigningKeyConversionError Crypto.XPrv
convertBip32SigningKey signingKeyBs =
case xprvFromBytes signingKeyBs of
Just xPrv -> Right xPrv
Nothing ->
Left $ CardanoAddressSigningKeyDeserialisationError signingKeyBs

-- | Read a file containing a Bech32-encoded Ed25519 BIP32 extended signing
-- key.
readBech32Bip32SigningKeyFile
:: SigningKeyFile
-> IO (Either (FileError CardanoAddressSigningKeyConversionError) Crypto.XPrv)
readBech32Bip32SigningKeyFile (SigningKeyFile fp) = do
eStr <- Exception.try $ readFile fp
case eStr of
Left e -> pure . Left $ FileIOError fp e
Right str ->
case decodeBech32 (Text.concat $ Text.words str) of
Left err ->
pure $ Left $
FileError fp (CardanoAddressSigningKeyBech32DecodeError err)
Right (_hrPart, _dataPart, bs) ->
pure $ first (FileError fp) (convertBip32SigningKey bs)

-- | Read a file containing a Bech32-encoded @cardano-address@ extended
-- signing key.
readSomeCardanoAddressSigningKeyFile
:: CardanoAddressKeyType
-> SigningKeyFile
-> IO (Either (FileError CardanoAddressSigningKeyConversionError) SomeCardanoAddressSigningKey)
readSomeCardanoAddressSigningKeyFile keyType skFile = do
xPrv <- readBech32Bip32SigningKeyFile skFile
pure (toSomeCardanoAddressSigningKey <$> xPrv)
where
toSomeCardanoAddressSigningKey :: Crypto.XPrv -> SomeCardanoAddressSigningKey
toSomeCardanoAddressSigningKey xPrv =
case keyType of
CardanoAddressShelleyPaymentKey ->
ACardanoAddrShelleyPaymentSigningKey
(PaymentExtendedSigningKey xPrv)
CardanoAddressShelleyStakeKey ->
ACardanoAddrShelleyStakeSigningKey (StakeExtendedSigningKey xPrv)
CardanoAddressIcarusPaymentKey ->
ACardanoAddrByronSigningKey $
ByronSigningKey (Byron.SigningKey xPrv)
CardanoAddressByronPaymentKey ->
ACardanoAddrByronSigningKey $
ByronSigningKey (Byron.SigningKey xPrv)

-- | Write a text envelope formatted file containing a @cardano-address@
-- extended signing key, but converted to a format supported by @cardano-cli@.
writeSomeCardanoAddressSigningKeyFile
:: FilePath
-> SomeCardanoAddressSigningKey
-> IO (Either (FileError ()) ())
writeSomeCardanoAddressSigningKeyFile outFile skey =
case skey of
ACardanoAddrShelleyPaymentSigningKey sk ->
writeFileTextEnvelope outFile Nothing sk
ACardanoAddrShelleyStakeSigningKey sk ->
writeFileTextEnvelope outFile Nothing sk
ACardanoAddrByronSigningKey sk ->
writeFileTextEnvelope outFile Nothing sk
Loading

0 comments on commit 696a928

Please sign in to comment.