Skip to content

Commit

Permalink
Rebase on master and update Byron signing key serialisation tests
Browse files Browse the repository at this point in the history
Review fixes
  • Loading branch information
Jimbo4350 committed Jan 12, 2021
1 parent 26be788 commit e333fe5
Show file tree
Hide file tree
Showing 7 changed files with 61 additions and 48 deletions.
6 changes: 3 additions & 3 deletions src/Cardano/CLI/Byron/Delegation.hs
Original file line number Diff line number Diff line change
Expand Up @@ -116,9 +116,9 @@ checkDlgCert cert magic issuerVK' delegateVK' =
serialiseDelegationCert :: Dlg.Certificate -> ByteString
serialiseDelegationCert = LB.toStrict . canonicalEncodePretty

serialiseByronWitness :: ByronWitness -> ByteString
serialiseByronWitness :: SomeByronSigningKey -> ByteString
serialiseByronWitness sk =
case sk of
LegacyWitness bSkey -> serialiseToRawBytes bSkey
NonLegacyWitness legBKey -> serialiseToRawBytes legBKey
AByronSigningKeyLegacy bSkey -> serialiseToRawBytes bSkey
AByronSigningKey legBKey -> serialiseToRawBytes legBKey

20 changes: 9 additions & 11 deletions src/Cardano/CLI/Byron/Key.hs
Original file line number Diff line number Diff line change
Expand Up @@ -6,7 +6,6 @@ module Cardano.CLI.Byron.Key
, NewSigningKeyFile(..)
, NewVerificationKeyFile(..)
, VerificationKeyFile(..)
, keygen
, prettyPublicKey
, readByronSigningKey
, readPaymentVerificationKey
Expand Down Expand Up @@ -41,11 +40,14 @@ data ByronKeyFailure
| LegacySigningKeyDeserialisationFailed !FilePath
| SigningKeyDeserialisationFailed !FilePath
| VerificationKeyDeserialisationFailed !FilePath !Text
| CannotMigrateFromNonLegacySigningKey !FilePath
deriving Show

renderByronKeyFailure :: ByronKeyFailure -> Text
renderByronKeyFailure err =
case err of
CannotMigrateFromNonLegacySigningKey fp ->
"Migrate from non-legacy Byron key unnecessary: " <> textShow fp
ReadSigningKeyFailure sKeyFp readErr ->
"Error reading signing key at: " <> textShow sKeyFp <> " Error: " <> textShow readErr
ReadVerificationKeyFailure vKeyFp readErr ->
Expand Down Expand Up @@ -74,23 +76,23 @@ prettyPublicKey (ByronVerificationKey vk) =
"\n public key (hex): "% Crypto.fullVerificationKeyHexF)
(Common.addressHash vk) vk vk

byronWitnessToVerKey :: ByronWitness -> VerificationKey ByronKey
byronWitnessToVerKey (LegacyWitness sKeyLeg) = castVerificationKey $ getVerificationKey sKeyLeg
byronWitnessToVerKey (NonLegacyWitness sKeyNonLeg) = getVerificationKey sKeyNonLeg
byronWitnessToVerKey :: SomeByronSigningKey -> VerificationKey ByronKey
byronWitnessToVerKey (AByronSigningKeyLegacy sKeyLeg) = castVerificationKey $ getVerificationKey sKeyLeg
byronWitnessToVerKey (AByronSigningKey sKeyNonLeg) = getVerificationKey sKeyNonLeg

-- TODO: we need to support password-protected secrets.
-- | Read signing key from a file.
readByronSigningKey :: ByronKeyFormat -> SigningKeyFile -> ExceptT ByronKeyFailure IO ByronWitness
readByronSigningKey :: ByronKeyFormat -> SigningKeyFile -> ExceptT ByronKeyFailure IO SomeByronSigningKey
readByronSigningKey bKeyFormat (SigningKeyFile fp) = do
sK <- handleIOExceptT (ReadSigningKeyFailure fp . T.pack . displayException) $ SB.readFile fp
case bKeyFormat of
LegacyByronKeyFormat ->
case deserialiseFromRawBytes (AsSigningKey AsByronKeyLegacy) sK of
Just legKey -> right $ LegacyWitness legKey
Just legKey -> right $ AByronSigningKeyLegacy legKey
Nothing -> left $ LegacySigningKeyDeserialisationFailed fp
NonLegacyByronKeyFormat ->
case deserialiseFromRawBytes (AsSigningKey AsByronKey) sK of
Just nonLegSKey -> right $ NonLegacyWitness nonLegSKey
Just nonLegSKey -> right $ AByronSigningKey nonLegSKey
Nothing -> left $ SigningKeyDeserialisationFailed fp

-- | Read verification key from a file. Throw an error if the file can't be read
Expand All @@ -103,7 +105,3 @@ readPaymentVerificationKey (VerificationKeyFile fp) = do
-- Convert error to 'CliError'
firstExceptT (VerificationKeyDeserialisationFailed fp . T.pack . show) eVk

-- | Generate a cryptographically random signing key.
keygen :: IO (SigningKey ByronKey)
keygen = generateSigningKey AsByronKey

16 changes: 11 additions & 5 deletions src/Cardano/CLI/Byron/Run.hs
Original file line number Diff line number Diff line change
Expand Up @@ -8,7 +8,7 @@ module Cardano.CLI.Byron.Run

import Cardano.Prelude

import Control.Monad.Trans.Except.Extra (firstExceptT, hoistEither)
import Control.Monad.Trans.Except.Extra (firstExceptT, hoistEither, left)
import qualified Data.ByteString.Char8 as BS
import qualified Data.Text as Text
import qualified Data.Text.Lazy.Builder as Builder
Expand All @@ -21,7 +21,8 @@ import qualified Cardano.Crypto.Hashing as Crypto
import qualified Cardano.Crypto.Signing as Crypto

import Cardano.Api hiding (UpdateProposal)
import Cardano.Api.Byron (Tx (..), VerificationKey (..))
import Cardano.Api.Byron (SigningKey (..), SomeByronSigningKey (..), Tx (..),
VerificationKey (..))

import Ouroboros.Consensus.Byron.Ledger (ByronBlock)
import Ouroboros.Consensus.Ledger.SupportsMempool (ApplyTxErr)
Expand Down Expand Up @@ -128,9 +129,14 @@ runPrettySigningKeyPublic bKeyFormat skF = do
runMigrateDelegateKeyFrom
:: ByronKeyFormat -> SigningKeyFile -> NewSigningKeyFile
-> ExceptT ByronClientCmdError IO ()
runMigrateDelegateKeyFrom oldKeyformat oldKey (NewSigningKeyFile newKey) = do
runMigrateDelegateKeyFrom oldKeyformat oldKey@(SigningKeyFile fp) (NewSigningKeyFile newKey) = do
sk <- firstExceptT ByronCmdKeyFailure $ readByronSigningKey oldKeyformat oldKey
firstExceptT ByronCmdHelpersError . ensureNewFileLBS newKey $ serialiseByronWitness sk
migratedWitness <- case sk of
AByronSigningKeyLegacy (ByronSigningKeyLegacy sKey) ->
return . AByronSigningKey $ ByronSigningKey sKey
AByronSigningKey _ ->
left . ByronCmdKeyFailure $ CannotMigrateFromNonLegacySigningKey fp
firstExceptT ByronCmdHelpersError . ensureNewFileLBS newKey $ serialiseByronWitness migratedWitness

runPrintGenesisHash :: GenesisFile -> ExceptT ByronClientCmdError IO ()
runPrintGenesisHash genFp = do
Expand Down Expand Up @@ -160,7 +166,7 @@ runPrintSigningKeyAddress bKeyFormat networkid skF = do

runKeygen :: NewSigningKeyFile -> ExceptT ByronClientCmdError IO ()
runKeygen (NewSigningKeyFile skF) = do
sK <- liftIO keygen
sK <- liftIO $ generateSigningKey AsByronKey
firstExceptT ByronCmdHelpersError . ensureNewFileLBS skF $ serialiseToRawBytes sK

runToVerification :: ByronKeyFormat -> SigningKeyFile -> NewVerificationKeyFile -> ExceptT ByronClientCmdError IO ()
Expand Down
16 changes: 8 additions & 8 deletions src/Cardano/CLI/Byron/Tx.hs
Original file line number Diff line number Diff line change
Expand Up @@ -43,9 +43,9 @@ import Ouroboros.Consensus.HardFork.Combinator.Degenerate (GenTx (Dege

import Cardano.Api (LocalNodeConnectInfo (..), NetworkId, TxBody, Witness,
makeByronTransaction, submitTxToNodeLocal)
import Cardano.Api.Byron (Address (..), ByronAddr, ByronEra, ByronWitness (..),
NodeConsensusMode (ByronMode), Tx (..), TxIn, TxOut (..),
VerificationKey (..), fromByronTxIn, makeByronKeyWitness,
import Cardano.Api.Byron (Address (..), ByronAddr, ByronEra,
NodeConsensusMode (ByronMode), SomeByronSigningKey (..), Tx (..), TxIn,
TxOut (..), VerificationKey (..), fromByronTxIn, makeByronKeyWitness,
makeSignedTransaction)
import Cardano.CLI.Byron.Key (byronWitnessToVerKey)
import Cardano.CLI.Environment
Expand Down Expand Up @@ -137,7 +137,7 @@ genesisUTxOTxIn gc vk genAddr =
txSpendGenesisUTxOByronPBFT
:: Genesis.Config
-> NetworkId
-> ByronWitness
-> SomeByronSigningKey
-> Address ByronAddr
-> [TxOut ByronEra]
-> Tx ByronEra
Expand All @@ -156,7 +156,7 @@ txSpendGenesisUTxOByronPBFT gc nId sk (ByronAddress bAddr) outs =
-- signed by the given key.
txSpendUTxOByronPBFT
:: NetworkId
-> ByronWitness
-> SomeByronSigningKey
-> [TxIn]
-> [TxOut ByronEra]
-> Tx ByronEra
Expand All @@ -166,11 +166,11 @@ txSpendUTxOByronPBFT nId sk txIn outs =
Right txBody -> let bWit = fromByronWitness sk nId txBody
in makeSignedTransaction [bWit] txBody

fromByronWitness :: ByronWitness -> NetworkId -> TxBody ByronEra -> Witness ByronEra
fromByronWitness :: SomeByronSigningKey -> NetworkId -> TxBody ByronEra -> Witness ByronEra
fromByronWitness bw nId txBody =
case bw of
LegacyWitness sk -> makeByronKeyWitness nId txBody sk
NonLegacyWitness sk' -> makeByronKeyWitness nId txBody sk'
AByronSigningKeyLegacy sk -> makeByronKeyWitness nId txBody sk
AByronSigningKey sk' -> makeByronKeyWitness nId txBody sk'

-- | Submit a transaction to a node specified by topology info.
nodeSubmitTx
Expand Down
15 changes: 8 additions & 7 deletions src/Cardano/CLI/Shelley/Run/Key.hs
Original file line number Diff line number Diff line change
Expand Up @@ -31,7 +31,8 @@ import qualified Cardano.Crypto.Signing as Byron
import qualified Shelley.Spec.Ledger.Keys as Shelley

import Cardano.Api
import Cardano.Api.Byron
import Cardano.Api.Byron hiding (SomeByronSigningKey (..))
import qualified Cardano.Api.Byron as ByronApi
import Cardano.Api.Crypto.Ed25519Bip32 (xPrvFromBytes)
import Cardano.Api.Shelley

Expand Down Expand Up @@ -336,18 +337,18 @@ convertByronSigningKey mPwd byronFormat convert
(OutputFile skeyPathNew) = do


witness <- firstExceptT ShelleyKeyCmdByronKeyFailure
$ Byron.readByronSigningKey byronFormat skeyPathOld
sKey <- firstExceptT ShelleyKeyCmdByronKeyFailure
$ Byron.readByronSigningKey byronFormat skeyPathOld

unprotectedSk <- case witness of
LegacyWitness (ByronSigningKeyLegacy sk@(Crypto.SigningKey xprv)) ->
-- Account for password protected legacy Byron keys
unprotectedSk <- case sKey of
ByronApi.AByronSigningKeyLegacy (ByronSigningKeyLegacy sk@(Crypto.SigningKey xprv)) ->
case mPwd of
-- Change password to empty string
Just pwd -> return . Crypto.SigningKey
$ Crypto.xPrvChangePass (encodeUtf8 pwd) (encodeUtf8 "") xprv
Nothing -> return sk
NonLegacyWitness _ ->
left . ShelleyKeyCmdNonLegacyKey $ unSigningKeyFile skeyPathOld
ByronApi.AByronSigningKey (ByronSigningKey sk) -> return sk


let sk' :: SigningKey keyrole
Expand Down
2 changes: 1 addition & 1 deletion src/Cardano/CLI/Shelley/Run/Transaction.hs
Original file line number Diff line number Diff line change
Expand Up @@ -25,7 +25,7 @@ import Control.Monad.Trans.Except.Extra (firstExceptT, handleIOExceptT
newExceptT)

import Cardano.Api
import Cardano.Api.Byron
import Cardano.Api.Byron hiding (SomeByronSigningKey (..))
import Cardano.Api.Shelley
import Ouroboros.Consensus.Shelley.Eras (StandardAllegra, StandardMary, StandardShelley)

Expand Down
34 changes: 21 additions & 13 deletions test/Test/Golden/Byron/SigningKeys.hs
Original file line number Diff line number Diff line change
@@ -1,5 +1,4 @@
{-# LANGUAGE OverloadedStrings #-}
{-# LANGUAGE TemplateHaskell #-}

module Test.Golden.Byron.SigningKeys
( tests
Expand All @@ -12,13 +11,14 @@ import qualified Data.ByteString.Lazy as LB

import qualified Cardano.Crypto.Signing as Crypto

import Cardano.CLI.Byron.Key (deserialiseSigningKey, keygen, readEraSigningKey,
serialiseSigningKey)
import Cardano.Api.Byron

import Cardano.CLI.Byron.Key (readByronSigningKey)
import Cardano.CLI.Byron.Legacy (decodeLegacyDelegateKey)
import Cardano.CLI.Shelley.Commands
import Cardano.CLI.Types (SigningKeyFile (..))

import Hedgehog (Property, checkParallel, discover, property, success)
import Hedgehog (Group (..), Property, checkSequential, property, success)
import qualified Hedgehog.Extras.Test.Base as H
import Hedgehog.Internal.Property (failWith)
import Test.OptParse
Expand Down Expand Up @@ -71,12 +71,10 @@ prop_print_nonLegacy_signing_key_address = propertyOnce $ do

prop_generate_and_read_nonlegacy_signingkeys :: Property
prop_generate_and_read_nonlegacy_signingkeys = property $ do
byronSkey <- liftIO $ keygen Crypto.emptyPassphrase
case serialiseSigningKey NonLegacyByronKeyFormat byronSkey of
Left err -> failWith Nothing $ show err
Right sKeyBS -> case deserialiseSigningKey NonLegacyByronKeyFormat "" sKeyBS of
Left err -> failWith Nothing $ show err
Right _ -> success
byronSkey <- liftIO $ generateSigningKey AsByronKey
case deserialiseFromRawBytes (AsSigningKey AsByronKey) (serialiseToRawBytes byronSkey ) of
Nothing -> failWith Nothing "Failed to deserialise non-legacy Byron signing key."
Just _ -> success

prop_migrate_legacy_to_nonlegacy_signingkeys :: Property
prop_migrate_legacy_to_nonlegacy_signingkeys =
Expand All @@ -88,11 +86,10 @@ prop_migrate_legacy_to_nonlegacy_signingkeys =
[ "migrate-delegate-key-from"
, "--byron-legacy-formats"
, "--from", legKeyFp
, "--byron-formats"
, "--to", nonLegacyKeyFp
]

eSignKey <- liftIO . runExceptT . readEraSigningKey NonLegacyByronKeyFormat
eSignKey <- liftIO . runExceptT . readByronSigningKey NonLegacyByronKeyFormat
$ SigningKeyFile nonLegacyKeyFp

case eSignKey of
Expand All @@ -117,4 +114,15 @@ prop_deserialiseLegacy_Signing_Key_API = propertyOnce $ do

tests :: IO Bool
tests =
checkParallel $$discover
checkSequential
$ Group "Byron Signing Key Serialisation"
[ ("prop_deserialise_legacy_signing_Key", prop_deserialise_legacy_signing_Key)
, ("prop_print_legacy_signing_key_address", prop_print_legacy_signing_key_address)
, ("prop_deserialise_nonLegacy_signing_Key", prop_deserialise_nonLegacy_signing_Key)
, ("prop_print_nonLegacy_signing_key_address", prop_print_nonLegacy_signing_key_address)
, ("prop_generate_and_read_nonlegacy_signingkeys", prop_generate_and_read_nonlegacy_signingkeys)
, ("prop_migrate_legacy_to_nonlegacy_signingkeys", prop_migrate_legacy_to_nonlegacy_signingkeys)
, ("prop_deserialise_NonLegacy_Signing_Key_API", prop_deserialise_NonLegacy_Signing_Key_API)
, ("prop_deserialiseLegacy_Signing_Key_API", prop_deserialiseLegacy_Signing_Key_API)
]

0 comments on commit e333fe5

Please sign in to comment.