Skip to content

Commit

Permalink
Implementation of mnemonic generation and key derivation
Browse files Browse the repository at this point in the history
  • Loading branch information
palas committed Nov 12, 2024
1 parent cac8f7d commit c34cf64
Show file tree
Hide file tree
Showing 4 changed files with 223 additions and 0 deletions.
2 changes: 2 additions & 0 deletions cardano-api/cardano-api.cabal
Original file line number Diff line number Diff line change
Expand Up @@ -106,6 +106,7 @@ library internal
Cardano.Api.Json
Cardano.Api.Keys.Byron
Cardano.Api.Keys.Class
Cardano.Api.Keys.Mnemonics
Cardano.Api.Keys.Praos
Cardano.Api.Keys.Read
Cardano.Api.Keys.Shelley
Expand Down Expand Up @@ -163,6 +164,7 @@ library internal
base58-bytestring,
bech32 >=1.1.0,
bytestring,
cardano-addresses,
cardano-binary,
cardano-crypto,
cardano-crypto-class ^>=2.1.2,
Expand Down
155 changes: 155 additions & 0 deletions cardano-api/internal/Cardano/Api/Keys/Mnemonics.hs
Original file line number Diff line number Diff line change
@@ -0,0 +1,155 @@
{-# LANGUAGE DataKinds #-}
{-# LANGUAGE InstanceSigs #-}
{-# LANGUAGE TypeApplications #-}

module Cardano.Api.Keys.Mnemonics
( MnemonicSize (..)
, generateMnemonic
, MnemonicToSigningStakeKeyError (..)
, SecondFactor
, ExtendedSigningKeyRole (..)
, signingKeyFromMnemonic
)
where

import Cardano.Api.Keys.Class (Key (..))
import Cardano.Api.Keys.Shelley (AsType, PaymentExtendedKey,
SigningKey (PaymentExtendedSigningKey, StakeExtendedSigningKey),
StakeExtendedKey)
import Cardano.Api.SerialiseRaw (SerialiseAsRawBytesError)

import Cardano.Address.Derivation (Depth (..), DerivationType (..), HardDerivation (..),
Index, XPrv, genMasterKeyFromMnemonic, indexFromWord32)
import Cardano.Address.Style.Shelley (Role (..), Shelley (..))
import Cardano.Mnemonic (MkSomeMnemonic (mkSomeMnemonic), MkSomeMnemonicError (..),
SomeMnemonic, entropyToMnemonic, genEntropy, mnemonicToText, someMnemonicToBytes)

import Control.Monad.IO.Class (MonadIO, liftIO)
import qualified Data.ByteArray as BA
import Data.ByteString (ByteString)
import Data.Either.Combinators (mapLeft, maybeToRight)
import Data.Text (Text)
import Data.Word (Word32)

-- | The size of a mnemonic sentence.
-- The size is given in the number of words in the sentence.
-- The allowed sizes are 9, 12, 15, 18, 21, and 24.
data MnemonicSize
= MS_9
| MS_12
| MS_15
| MS_18
| MS_21
| MS_24
deriving (Eq, Show)

-- | Generate a mnemonic sentence of the given size.
generateMnemonic
:: MonadIO m
=> MnemonicSize
-- ^ The size of the mnemonic sentence to generate.
-- Must be one of 9, 12, 15, 18, 21, or 24.
-> m [Text]
generateMnemonic MS_9 = liftIO (mnemonicToText @9 . entropyToMnemonic <$> genEntropy)
generateMnemonic MS_12 = liftIO (mnemonicToText @12 . entropyToMnemonic <$> genEntropy)
generateMnemonic MS_15 = liftIO (mnemonicToText @15 . entropyToMnemonic <$> genEntropy)
generateMnemonic MS_18 = liftIO (mnemonicToText @18 . entropyToMnemonic <$> genEntropy)
generateMnemonic MS_21 = liftIO (mnemonicToText @21 . entropyToMnemonic <$> genEntropy)
generateMnemonic MS_24 = liftIO (mnemonicToText @24 . entropyToMnemonic <$> genEntropy)

-- | Errors that can occur when converting a mnemonic sentence to a signing key
-- using the 'signingStakeKeyFromMnemonic' function.
data MnemonicToSigningStakeKeyError
= InvalidMnemonicError String
| InvalidSecondFactorMnemonicError String
| InvalidAccountNumberError Word32
| InvalidPaymentKeyNoError Word32
| InternalErrorConvertingToByteString SerialiseAsRawBytesError
deriving (Eq, Show)

-- | The second factor for the key derivation.
data SecondFactor
= -- | Use a mnemonic sentence as the second factor.
FromMnemonic [Text]
| -- | Use a raw byte string as the second factor.
FromByteString ByteString
deriving (Eq, Show)

class ExtendedSigningKeyRole keyrole where
-- | Convert the key role to a derivation role.
asDerivationRole :: AsType keyrole -> Role

-- | Convert an extended private key to a SigningKey.
asSigningKeyRole :: XPrv -> SigningKey keyrole

-- | ExtendedSigningKeyRole instance for the PaymentExtendedKey key role.
instance ExtendedSigningKeyRole PaymentExtendedKey where
asDerivationRole :: AsType PaymentExtendedKey -> Role
asDerivationRole _ = UTxOExternal

asSigningKeyRole :: XPrv -> SigningKey PaymentExtendedKey
asSigningKeyRole = PaymentExtendedSigningKey

-- | ExtendedSigningKeyRole instance for the StakeExtendedKey key role.
instance ExtendedSigningKeyRole StakeExtendedKey where
asDerivationRole :: AsType StakeExtendedKey -> Role
asDerivationRole _ = Stake

asSigningKeyRole :: XPrv -> SigningKey StakeExtendedKey
asSigningKeyRole = StakeExtendedSigningKey

-- | Generate a signing key from a mnemonic sentence.
-- A derivation path is like a file path in a file system. It specifies the
-- location of a key in the key tree. The path is a list of indices, one for each
-- level of the tree. The indices are separated by a forward slash (/).
-- In this function we only ask for two indices: the account number and the
-- payment key number. Each account can have multiple payment keys.
signingKeyFromMnemonic
:: ExtendedSigningKeyRole keyrole
=> AsType keyrole
-- ^ Type of the extended signing key to generate.
-> [Text]
-- ^ The mnemonic sentence. The length must be one of 9, 12, 15, 18, 21, or 24.
-- Each element of the list must be a single word.
-> Maybe SecondFactor
-- ^ The second factor for the key derivation. If 'Nothing', the key is derived
-- without a second factor.
-> Word32
-- ^ The account number in the derivation path. First account is 0.
-> Word32
-- ^ The payment key number in the derivation path. First key is 0.
-> Either MnemonicToSigningStakeKeyError (SigningKey keyrole)
signingKeyFromMnemonic role mnemonicWords mSecondFactor accNo payKeyNo = do
-- Convert raw types to the ones used in the cardano-addresses library
someMnemonic <- mapLeft InvalidMnemonicError $ wordsToSomeMnemonic mnemonicWords
secondFactorBytes <- toSecondFactor mSecondFactor
accIx <-
maybeToRight (InvalidAccountNumberError accNo) $
indexFromWord32 @(Index 'Hardened 'AccountK) (0x80000000 + accNo)
payKeyIx <-
maybeToRight (InvalidPaymentKeyNoError payKeyNo) $ indexFromWord32 @(Index 'Soft 'PaymentK) payKeyNo

-- Derive the rootk key
let rootK = genMasterKeyFromMnemonic someMnemonic secondFactorBytes :: Shelley 'RootK XPrv
-- Derive the account key
accK = deriveAccountPrivateKey rootK accIx
-- Derive the payment key
prvK = deriveAddressPrivateKey accK (asDerivationRole role) payKeyIx

-- Finally we wrap it in the API type
return $ asSigningKeyRole $ getKey prvK
where
-- Convert the ByteString to a SigningKey

-- Convert the mnemonic sentence to a SomeMnemonic value
wordsToSomeMnemonic :: [Text] -> Either String SomeMnemonic
wordsToSomeMnemonic = mapLeft getMkSomeMnemonicError . mkSomeMnemonic @[9, 12, 15, 18, 21, 24]

-- Convert the second factor to a ScrubbedBytes value or mempty if none
toSecondFactor :: Maybe SecondFactor -> Either MnemonicToSigningStakeKeyError BA.ScrubbedBytes
toSecondFactor Nothing = return mempty
toSecondFactor (Just (FromMnemonic secondFactorWords)) =
someMnemonicToBytes
<$> mapLeft InvalidSecondFactorMnemonicError (wordsToSomeMnemonic secondFactorWords)
toSecondFactor (Just (FromByteString secondFactorBytes)) =
return $ BA.convert secondFactorBytes
14 changes: 14 additions & 0 deletions cardano-api/src/Cardano/Api.hs
Original file line number Diff line number Diff line change
Expand Up @@ -177,6 +177,19 @@ module Cardano.Api
, castHash
, renderSafeHashAsHex

-- * Mnemonics

-- | Functions for working with mnemonics
-- ** Mnemonics generation
, MnemonicSize (..)
, generateMnemonic

-- ** Key derivation from mnemonics
, ExtendedSigningKeyRole
, MnemonicToSigningStakeKeyError (..)
, SecondFactor
, signingKeyFromMnemonic

-- * Payment addresses

-- | Constructing and inspecting normal payment addresses
Expand Down Expand Up @@ -1063,6 +1076,7 @@ import Cardano.Api.IPC
import Cardano.Api.IPC.Monad
import Cardano.Api.Keys.Byron
import Cardano.Api.Keys.Class
import Cardano.Api.Keys.Mnemonics
import Cardano.Api.Keys.Read
import Cardano.Api.Keys.Shelley
import Cardano.Api.LedgerState
Expand Down
52 changes: 52 additions & 0 deletions cardano-api/test/cardano-api-test/Test/Cardano/Api/Address.hs
Original file line number Diff line number Diff line change
Expand Up @@ -6,7 +6,9 @@ module Test.Cardano.Api.Address
where

import Cardano.Api
import Cardano.Api.Address (StakeCredential (StakeCredentialByKey))

import Control.Monad (void)
import qualified Data.Aeson as Aeson

import Test.Gen.Cardano.Api.Typed (genAddressByron, genAddressShelley)
Expand All @@ -15,6 +17,8 @@ import Test.Cardano.Api.Orphans ()

import Hedgehog (Property)
import qualified Hedgehog as H
import qualified Hedgehog.Extras as H
import qualified Hedgehog.Gen as H
import Test.Tasty (TestTree, testGroup)
import Test.Tasty.Hedgehog (testProperty)

Expand All @@ -30,6 +34,52 @@ prop_roundtrip_byron_address :: Property
prop_roundtrip_byron_address =
roundtrip_serialise_address AsByronAddress genAddressByron

prop_derive_key_from_mnemonic :: Property
prop_derive_key_from_mnemonic = H.property $ do
ms <- H.forAll $ H.element [MS_9, MS_12, MS_15, MS_18, MS_21, MS_24]
mnemonic <- liftIO $ generateMnemonic ms
void $ H.evalEither $ signingKeyFromMnemonic AsStakeExtendedKey mnemonic Nothing 0 0
H.success

prop_derivation_is_accurate :: Property
prop_derivation_is_accurate = H.propertyOnce $ do
let mnemonic =
[ "captain"
, "kick"
, "bundle"
, "address"
, "forest"
, "cube"
, "skirt"
, "pepper"
, "captain"
, "now"
, "crop"
, "matrix"
, "virus"
, "shallow"
, "bless"
, "throw"
, "spice"
, "smoke"
, "over"
, "proud"
, "minimum"
, "coconut"
, "virus"
, "suspect"
]
signingKey <- H.evalEither $ signingKeyFromMnemonic AsStakeExtendedKey mnemonic Nothing 0 0
let verificationKey =
getVerificationKey (signingKey :: SigningKey StakeExtendedKey) :: VerificationKey StakeExtendedKey
let addr =
serialiseToBech32 $
makeStakeAddress Mainnet $
StakeCredentialByKey $
verificationKeyHash $
castVerificationKey verificationKey
addr H.=== "stake1u97tzhttvsz5n6fej6g05trus39x5uvl0y0k56dyhsc23xcexrk27"

-- -----------------------------------------------------------------------------

roundtrip_serialise_address
Expand Down Expand Up @@ -65,4 +115,6 @@ tests =
, testProperty "roundtrip byron address" prop_roundtrip_byron_address
, testProperty "roundtrip byron address JSON" prop_roundtrip_byron_address_JSON
, testProperty "roundtrip shelley address JSON" prop_roundtrip_shelley_address_JSON
, testProperty "key derivation from random mnemonic" prop_derive_key_from_mnemonic
, testProperty "address from key derivation is accurate" prop_derivation_is_accurate
]

0 comments on commit c34cf64

Please sign in to comment.