Skip to content
This repository was archived by the owner on Aug 18, 2020. It is now read-only.

[CBR-533] add a new endpoint to calculate the walletid for a given mnemonic #4237

Merged
merged 4 commits into from
Sep 17, 2019
Merged
Show file tree
Hide file tree
Changes from all commits
Commits
File filter

Filter by extension

Filter by extension

Conversations
Failed to load comments.
Loading
Jump to
Jump to file
Failed to load files.
Loading
Diff view
Diff view
2 changes: 2 additions & 0 deletions CHANGELOG.md
Original file line number Diff line number Diff line change
Expand Up @@ -3,6 +3,8 @@
## Unreleased
- Correct change category in 3.0.3 and add section for unreleased changes [#4232](https://github.com/input-output-hk/cardano-sl/pull/4232)

## Features
- A new endpoint to calculate the walletid of a given mnemonic [#4237](https://github.com/input-output-hk/cardano-sl/pull/4237)

## Cardano SL 3.0.3

Expand Down
6 changes: 6 additions & 0 deletions wallet/shell.nix
Original file line number Diff line number Diff line change
@@ -0,0 +1,6 @@
let
self = import ../. {};
in (self.nix-tools.shellFor {
name = "cardano-wallet";
packages = ps: [ ps.cardano-wallet ];
})
9 changes: 8 additions & 1 deletion wallet/src/Cardano/Wallet/API/Internal.hs
Original file line number Diff line number Diff line change
Expand Up @@ -3,13 +3,15 @@
-- Daedalus client, and aren't useful for wallets, exchanges, and other users.
module Cardano.Wallet.API.Internal where

import Prelude
Copy link
Contributor

Choose a reason for hiding this comment

The reason will be displayed to describe this comment to others. Learn more.

Indentation to match import lines below? Also isn't this import already implicit?


import Pos.Chain.Update (SoftwareVersion)

import Servant

import Cardano.Wallet.API.Response (APIResponse, ValidJSON)
import Cardano.Wallet.API.Types
import Cardano.Wallet.API.V1.Types (V1, Wallet, WalletImport)
import Cardano.Wallet.API.V1.Types (V1, Wallet, WalletImport, BackupPhrase, MnemonicBalance)

type API = Tag "Internal" ('TagDescription
"This section contains endpoints so-called 'Internal'. They are only\
Expand Down Expand Up @@ -37,4 +39,9 @@ type API = Tag "Internal" ('TagDescription
:> Summary "Import a Wallet from disk."
:> ReqBody '[ValidJSON] WalletImport
:> Post '[ValidJSON] (APIResponse Wallet)
:<|> "calculate_mnemonic"
:> Summary "calculates the walletid from a given mnemonic"
:> QueryParam "read_balance" Bool
:> ReqBody '[ValidJSON] BackupPhrase
:> Post '[ValidJSON] (APIResponse MnemonicBalance)
)
8 changes: 7 additions & 1 deletion wallet/src/Cardano/Wallet/API/Internal/Handlers.hs
Original file line number Diff line number Diff line change
Expand Up @@ -8,7 +8,7 @@ import Pos.Chain.Update (SoftwareVersion)

import qualified Cardano.Wallet.API.Internal as Internal
import Cardano.Wallet.API.Response (APIResponse, single)
import Cardano.Wallet.API.V1.Types (V1, Wallet, WalletImport)
import Cardano.Wallet.API.V1.Types (V1, Wallet, WalletImport, BackupPhrase, MnemonicBalance)
import Cardano.Wallet.WalletLayer (PassiveWalletLayer)
import qualified Cardano.Wallet.WalletLayer as WalletLayer

Expand All @@ -18,6 +18,7 @@ handlers w = nextUpdate w
:<|> postponeUpdate w
:<|> resetWalletState w
:<|> importWallet w
:<|> calculateMnemonic w

nextUpdate :: PassiveWalletLayer IO -> Handler (APIResponse (V1 SoftwareVersion))
nextUpdate w = do
Expand All @@ -42,3 +43,8 @@ importWallet w walletImport = do
case res of
Left e -> throwM e
Right importedWallet -> pure $ single importedWallet

calculateMnemonic :: PassiveWalletLayer IO -> Maybe Bool -> BackupPhrase -> Handler (APIResponse MnemonicBalance)
calculateMnemonic w mbool phrase = do
res <- liftIO $ WalletLayer.calculateMnemonic w mbool phrase
pure $ single res
38 changes: 38 additions & 0 deletions wallet/src/Cardano/Wallet/API/V1/Types.hs
Original file line number Diff line number Diff line change
Expand Up @@ -14,6 +14,7 @@
-- The hlint parser fails on the `pattern` function, so we disable the
-- language extension here.
{-# LANGUAGE NoPatternSynonyms #-}
{-# LANGUAGE NamedFieldPuns #-}

-- Needed for the `Buildable`, `SubscriptionStatus` and `NodeId` orphans.
{-# OPTIONS_GHC -fno-warn-orphans #-}
Expand Down Expand Up @@ -110,6 +111,7 @@ module Cardano.Wallet.API.V1.Types (
, msgUtxoNotEnoughFragmented
, toServantError
, toHttpErrorStatus
, MnemonicBalance(..)
, module Cardano.Wallet.Types.UtxoStatistics
) where

Expand Down Expand Up @@ -756,6 +758,42 @@ instance BuildableSafeGen Wallet where
instance Buildable [Wallet] where
build = bprint listJson

data MnemonicBalance = MnemonicBalance {
mbWalletId :: !WalletId
, mbBalance :: !(Maybe Integer)
} deriving (Eq, Ord, Show, Generic)
deriveJSON Aeson.defaultOptions ''MnemonicBalance

instance ToSchema MnemonicBalance where
declareNamedSchema =
genericSchemaDroppingPrefix "mb" (\(--^) props -> props
& "walletId"
--^ "Unique wallet identifier."
& "balance"
--^ "Current balance, in Lovelace."
)

instance Arbitrary MnemonicBalance where
arbitrary = MnemonicBalance <$> arbitrary <*> arbitrary

deriveSafeBuildable ''MnemonicBalance
instance BuildableSafeGen MnemonicBalance where
buildSafeGen sl MnemonicBalance{mbWalletId,mbBalance} = case mbBalance of
Just bal -> bprint ("{"
%" id="%buildSafe sl
%" balance="%build
%" }")
mbWalletId
bal
Nothing -> bprint ("{"
%" id="%buildSafe sl
%" }")
mbWalletId

instance Example MnemonicBalance where
example = do
MnemonicBalance <$> example <*> (pure $ Just 1000000)

instance ToSchema PublicKey where
declareNamedSchema _ =
pure $ NamedSchema (Just "PublicKey") $ mempty
Expand Down
3 changes: 3 additions & 0 deletions wallet/src/Cardano/Wallet/Client.hs
Original file line number Diff line number Diff line change
Expand Up @@ -155,6 +155,7 @@ data WalletClient m
:: m (Either ClientError ())
, importWallet
:: WalletImport -> Resp m Wallet
, calculateMnemonic :: Maybe Bool -> BackupPhrase -> m (Either ClientError (APIResponse MnemonicBalance))
} deriving Generic

data WalletDocClient m = WalletDocClient
Expand Down Expand Up @@ -286,6 +287,8 @@ natMapClient phi f wc = WalletClient
f $ phi $ resetWalletState wc
, importWallet =
f . phi . importWallet wc
, calculateMnemonic =
\x -> f . phi . calculateMnemonic wc x
}

-- | Run the given natural transformation over the 'WalletClient'.
Expand Down
2 changes: 2 additions & 0 deletions wallet/src/Cardano/Wallet/Client/Http.hs
Original file line number Diff line number Diff line change
Expand Up @@ -108,6 +108,7 @@ mkHttpClient baseUrl manager = WalletClient

, importWallet
= run . importWalletR
, calculateMnemonic = \bp qb -> run $ calculateMnemonicR bp qb
}

where
Expand Down Expand Up @@ -162,6 +163,7 @@ mkHttpClient baseUrl manager = WalletClient
:<|> postponeUpdateR
:<|> resetWalletStateR
:<|> importWalletR
:<|> calculateMnemonicR
= internalAPI

addressesAPI
Expand Down
13 changes: 12 additions & 1 deletion wallet/src/Cardano/Wallet/Kernel/DB/HdWallet.hs
Original file line number Diff line number Diff line change
Expand Up @@ -120,14 +120,15 @@ import Pos.Core.NetworkMagic (NetworkMagic (..))
import Pos.Crypto (HDPassphrase)
import qualified Pos.Crypto as Core

import Cardano.Wallet.API.V1.Types (V1 (..))
import Cardano.Wallet.API.V1.Types (V1 (..), WAddressMeta(WAddressMeta))
import Cardano.Wallet.Kernel.DB.BlockContext
import Cardano.Wallet.Kernel.DB.InDb
import Cardano.Wallet.Kernel.DB.Spec
import Cardano.Wallet.Kernel.DB.Util.AcidState
import Cardano.Wallet.Kernel.DB.Util.IxSet hiding (foldl')
import qualified Cardano.Wallet.Kernel.DB.Util.IxSet as IxSet hiding (Indexable)
import qualified Cardano.Wallet.Kernel.DB.Util.Zoomable as Z
import Cardano.Wallet.Kernel.Decrypt (WalletDecrCredentials, decryptAddress)
import Cardano.Wallet.Kernel.NodeStateAdaptor (SecurityParameter (..))
import qualified Cardano.Wallet.Kernel.Util.StrictList as SL
import Cardano.Wallet.Kernel.Util.StrictNonEmpty (StrictNonEmpty (..))
Expand Down Expand Up @@ -535,6 +536,16 @@ instance IsOurs [(HdRootId, Core.EncryptedSecretKey)] where
let addrId = HdAddressId accId addressIx
return $ HdAddress addrId (InDb addr)

instance IsOurs [ (HdRootId, WalletDecrCredentials) ] where
isOurs addr s = (,s) $ foldl' (<|>) Nothing $ flip map s $ \(rootId, wdc) -> do
case decryptAddress wdc (addr::Core.Address) of
Just (WAddressMeta _wid accountIx addressIx _addrv1) -> do
let
accId = HdAccountId rootId (HdAccountIx accountIx)
addrId = HdAddressId accId (HdAddressIx addressIx)
pure (HdAddress addrId (InDb addr))
Nothing -> Nothing

decryptHdLvl2DerivationPath
:: Core.HDPassphrase
-> Core.Address
Expand Down
5 changes: 3 additions & 2 deletions wallet/src/Cardano/Wallet/WalletLayer.hs
Original file line number Diff line number Diff line change
Expand Up @@ -46,8 +46,8 @@ import Cardano.Wallet.API.Request.Filter (FilterOperations (..))
import Cardano.Wallet.API.Request.Sort (SortOperations (..))
import Cardano.Wallet.API.Response (APIResponse, SliceOf (..))
import Cardano.Wallet.API.V1.Types (Account, AccountBalance,
AccountIndex, AccountUpdate, Address, BatchImportResult,
ForceNtpCheck, NewAccount, NewAddress, NewWallet,
AccountIndex, AccountUpdate, Address, BackupPhrase, BatchImportResult,
ForceNtpCheck, NewAccount, NewAddress, NewWallet, MnemonicBalance,
NodeInfo, NodeSettings, PasswordUpdate, Payment,
Redemption, SpendingPassword, Transaction, V1 (..),
Wallet, WalletAddress, WalletId, WalletImport,
Expand Down Expand Up @@ -482,6 +482,7 @@ data PassiveWalletLayer m = PassiveWalletLayer
, postponeUpdate :: m ()
, resetWalletState :: m ()
, importWallet :: WalletImport -> m (Either ImportWalletError Wallet)
, calculateMnemonic :: Maybe Bool -> BackupPhrase -> m MnemonicBalance

-- updates
, waitForUpdate :: m ConfirmedProposalState
Expand Down
1 change: 1 addition & 0 deletions wallet/src/Cardano/Wallet/WalletLayer/Kernel.hs
Original file line number Diff line number Diff line change
Expand Up @@ -144,6 +144,7 @@ bracketPassiveWallet pm mode logFunction keystore node fInjects f = do
, getTransactions = Transactions.getTransactions w
, getTxFromMeta = Transactions.toTransaction w
, getNodeSettings = Settings.getNodeSettings w
, calculateMnemonic = Internal.calculateMnemonic w
}
where
-- Read-only operations
Expand Down
51 changes: 48 additions & 3 deletions wallet/src/Cardano/Wallet/WalletLayer/Kernel/Internal.hs
Original file line number Diff line number Diff line change
@@ -1,9 +1,12 @@
{-# LANGUAGE RankNTypes #-}

module Cardano.Wallet.WalletLayer.Kernel.Internal (
nextUpdate
, applyUpdate
, postponeUpdate
, resetWalletState
, importWallet
, calculateMnemonic

, waitForUpdate
, addUpdate
Expand All @@ -15,11 +18,12 @@ import Control.Concurrent.MVar (modifyMVar_)
import Data.Acid.Advanced (update')
import System.IO.Error (isDoesNotExistError)

import Pos.Chain.Update (ConfirmedProposalState, SoftwareVersion)
import Pos.Chain.Update (ConfirmedProposalState, SoftwareVersion, HasUpdateConfiguration)
import Pos.Util.CompileInfo (HasCompileInfo)
import Pos.Infra.InjectFail (FInject (..), testLogFInject)

import Cardano.Wallet.API.V1.Types (V1 (..), Wallet,
WalletImport (..))
import Cardano.Wallet.API.V1.Types (V1(V1), Wallet, BackupPhrase(BackupPhrase),
WalletImport (..), WalletId, Coin, MnemonicBalance(MnemonicBalance))
import Cardano.Wallet.Kernel.DB.AcidState (AddUpdate (..),
ClearDB (..), GetNextUpdate (..), RemoveNextUpdate (..))
import Cardano.Wallet.Kernel.DB.InDb
Expand All @@ -31,6 +35,16 @@ import qualified Cardano.Wallet.Kernel.Submission as Submission
import Cardano.Wallet.WalletLayer (CreateWallet (..),
ImportWalletError (..))
import Cardano.Wallet.WalletLayer.Kernel.Wallets (createWallet)
import Pos.Core.NetworkMagic (makeNetworkMagic, NetworkMagic)
import Cardano.Wallet.Kernel.Internal (walletProtocolMagic, walletNode)
import Cardano.Mnemonic (mnemonicToSeed)
import Pos.Crypto (safeDeterministicKeyGen, EncryptedSecretKey)
import Pos.Chain.Txp (TxIn, TxOutAux, toaOut, txOutValue, txOutAddress)
import Cardano.Wallet.Kernel.DB.HdWallet (eskToHdRootId, isOurs)
import qualified Cardano.Wallet.Kernel.DB.HdWallet as HD
import Cardano.Wallet.WalletLayer.Kernel.Conv (toRootId)
import Cardano.Wallet.Kernel.Decrypt (WalletDecrCredentials, eskToWalletDecrCredentials)
import Pos.Core.Common (sumCoins)

-- | Get next update (if any)
--
Expand Down Expand Up @@ -125,3 +139,34 @@ importWallet pw WalletImport{..} = liftIO $ do
return $ case res of
Left e -> Left (ImportWalletCreationFailed e)
Right importedWallet -> Right importedWallet

-- takes a WalletDecrCredentials and transaction, and returns the Coin output, if its ours
maybeReadcoin :: (HD.HdRootId, WalletDecrCredentials) -> (TxIn, TxOutAux) -> Maybe Coin
maybeReadcoin wkey (_, txout) = case isOurs (txOutAddress . toaOut $ txout) [wkey] of
(Just _, _) -> Just $ (txOutValue . toaOut) txout
(Nothing, _)-> Nothing

calculateMnemonic :: MonadIO m => Kernel.PassiveWallet -> Maybe Bool -> BackupPhrase -> m MnemonicBalance
calculateMnemonic wallet mbool (BackupPhrase mnemonic) = do
let
nm :: NetworkMagic
nm = makeNetworkMagic $ wallet ^. walletProtocolMagic
esk :: EncryptedSecretKey
(_pubkey, esk) = safeDeterministicKeyGen (mnemonicToSeed mnemonic) mempty
hdRoot :: HD.HdRootId
hdRoot = eskToHdRootId nm esk
walletid :: WalletId
walletid = toRootId hdRoot
wdc = eskToWalletDecrCredentials nm esk
withNode :: (HasCompileInfo, HasUpdateConfiguration) => Node.Lock (Node.WithNodeState IO) -> Node.WithNodeState IO [Coin]
withNode _lock = Node.filterUtxo (maybeReadcoin (hdRoot, wdc))
checkBalance = fromMaybe False mbool
maybeBalance <- case checkBalance of
True -> do
my_coins <- liftIO $ Node.withNodeState (wallet ^. walletNode) withNode
let
balance :: Integer
balance = sumCoins my_coins
pure $ Just $ balance
False -> pure Nothing
pure $ MnemonicBalance walletid maybeBalance