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

Commit 013ea14

Browse files
Merge #4237
4237: [CBR-533] add a new endpoint to calculate the walletid for a given mnemonic r=disassembler a=cleverca22 ## Description <!--- A brief description of this PR and the problem is trying to solve --> ## Linked issue <!--- Put here the relevant issue from YouTrack --> Co-authored-by: Michael Bishop <[email protected]>
2 parents eaee522 + 8199813 commit 013ea14

File tree

11 files changed

+130
-8
lines changed

11 files changed

+130
-8
lines changed

CHANGELOG.md

+2
Original file line numberDiff line numberDiff line change
@@ -3,6 +3,8 @@
33
## Unreleased
44
- Correct change category in 3.0.3 and add section for unreleased changes [#4232](https://github.com/input-output-hk/cardano-sl/pull/4232)
55

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

79
## Cardano SL 3.0.3
810

wallet/shell.nix

+6
Original file line numberDiff line numberDiff line change
@@ -0,0 +1,6 @@
1+
let
2+
self = import ../. {};
3+
in (self.nix-tools.shellFor {
4+
name = "cardano-wallet";
5+
packages = ps: [ ps.cardano-wallet ];
6+
})

wallet/src/Cardano/Wallet/API/Internal.hs

+8-1
Original file line numberDiff line numberDiff line change
@@ -3,13 +3,15 @@
33
-- Daedalus client, and aren't useful for wallets, exchanges, and other users.
44
module Cardano.Wallet.API.Internal where
55

6+
import Prelude
7+
68
import Pos.Chain.Update (SoftwareVersion)
79

810
import Servant
911

1012
import Cardano.Wallet.API.Response (APIResponse, ValidJSON)
1113
import Cardano.Wallet.API.Types
12-
import Cardano.Wallet.API.V1.Types (V1, Wallet, WalletImport)
14+
import Cardano.Wallet.API.V1.Types (V1, Wallet, WalletImport, BackupPhrase, MnemonicBalance)
1315

1416
type API = Tag "Internal" ('TagDescription
1517
"This section contains endpoints so-called 'Internal'. They are only\
@@ -37,4 +39,9 @@ type API = Tag "Internal" ('TagDescription
3739
:> Summary "Import a Wallet from disk."
3840
:> ReqBody '[ValidJSON] WalletImport
3941
:> Post '[ValidJSON] (APIResponse Wallet)
42+
:<|> "calculate_mnemonic"
43+
:> Summary "calculates the walletid from a given mnemonic"
44+
:> QueryParam "read_balance" Bool
45+
:> ReqBody '[ValidJSON] BackupPhrase
46+
:> Post '[ValidJSON] (APIResponse MnemonicBalance)
4047
)

wallet/src/Cardano/Wallet/API/Internal/Handlers.hs

+7-1
Original file line numberDiff line numberDiff line change
@@ -8,7 +8,7 @@ import Pos.Chain.Update (SoftwareVersion)
88

99
import qualified Cardano.Wallet.API.Internal as Internal
1010
import Cardano.Wallet.API.Response (APIResponse, single)
11-
import Cardano.Wallet.API.V1.Types (V1, Wallet, WalletImport)
11+
import Cardano.Wallet.API.V1.Types (V1, Wallet, WalletImport, BackupPhrase, MnemonicBalance)
1212
import Cardano.Wallet.WalletLayer (PassiveWalletLayer)
1313
import qualified Cardano.Wallet.WalletLayer as WalletLayer
1414

@@ -18,6 +18,7 @@ handlers w = nextUpdate w
1818
:<|> postponeUpdate w
1919
:<|> resetWalletState w
2020
:<|> importWallet w
21+
:<|> calculateMnemonic w
2122

2223
nextUpdate :: PassiveWalletLayer IO -> Handler (APIResponse (V1 SoftwareVersion))
2324
nextUpdate w = do
@@ -42,3 +43,8 @@ importWallet w walletImport = do
4243
case res of
4344
Left e -> throwM e
4445
Right importedWallet -> pure $ single importedWallet
46+
47+
calculateMnemonic :: PassiveWalletLayer IO -> Maybe Bool -> BackupPhrase -> Handler (APIResponse MnemonicBalance)
48+
calculateMnemonic w mbool phrase = do
49+
res <- liftIO $ WalletLayer.calculateMnemonic w mbool phrase
50+
pure $ single res

wallet/src/Cardano/Wallet/API/V1/Types.hs

+38
Original file line numberDiff line numberDiff line change
@@ -14,6 +14,7 @@
1414
-- The hlint parser fails on the `pattern` function, so we disable the
1515
-- language extension here.
1616
{-# LANGUAGE NoPatternSynonyms #-}
17+
{-# LANGUAGE NamedFieldPuns #-}
1718

1819
-- Needed for the `Buildable`, `SubscriptionStatus` and `NodeId` orphans.
1920
{-# OPTIONS_GHC -fno-warn-orphans #-}
@@ -110,6 +111,7 @@ module Cardano.Wallet.API.V1.Types (
110111
, msgUtxoNotEnoughFragmented
111112
, toServantError
112113
, toHttpErrorStatus
114+
, MnemonicBalance(..)
113115
, module Cardano.Wallet.Types.UtxoStatistics
114116
) where
115117

@@ -756,6 +758,42 @@ instance BuildableSafeGen Wallet where
756758
instance Buildable [Wallet] where
757759
build = bprint listJson
758760

761+
data MnemonicBalance = MnemonicBalance {
762+
mbWalletId :: !WalletId
763+
, mbBalance :: !(Maybe Integer)
764+
} deriving (Eq, Ord, Show, Generic)
765+
deriveJSON Aeson.defaultOptions ''MnemonicBalance
766+
767+
instance ToSchema MnemonicBalance where
768+
declareNamedSchema =
769+
genericSchemaDroppingPrefix "mb" (\(--^) props -> props
770+
& "walletId"
771+
--^ "Unique wallet identifier."
772+
& "balance"
773+
--^ "Current balance, in Lovelace."
774+
)
775+
776+
instance Arbitrary MnemonicBalance where
777+
arbitrary = MnemonicBalance <$> arbitrary <*> arbitrary
778+
779+
deriveSafeBuildable ''MnemonicBalance
780+
instance BuildableSafeGen MnemonicBalance where
781+
buildSafeGen sl MnemonicBalance{mbWalletId,mbBalance} = case mbBalance of
782+
Just bal -> bprint ("{"
783+
%" id="%buildSafe sl
784+
%" balance="%build
785+
%" }")
786+
mbWalletId
787+
bal
788+
Nothing -> bprint ("{"
789+
%" id="%buildSafe sl
790+
%" }")
791+
mbWalletId
792+
793+
instance Example MnemonicBalance where
794+
example = do
795+
MnemonicBalance <$> example <*> (pure $ Just 1000000)
796+
759797
instance ToSchema PublicKey where
760798
declareNamedSchema _ =
761799
pure $ NamedSchema (Just "PublicKey") $ mempty

wallet/src/Cardano/Wallet/Client.hs

+3
Original file line numberDiff line numberDiff line change
@@ -155,6 +155,7 @@ data WalletClient m
155155
:: m (Either ClientError ())
156156
, importWallet
157157
:: WalletImport -> Resp m Wallet
158+
, calculateMnemonic :: Maybe Bool -> BackupPhrase -> m (Either ClientError (APIResponse MnemonicBalance))
158159
} deriving Generic
159160

160161
data WalletDocClient m = WalletDocClient
@@ -286,6 +287,8 @@ natMapClient phi f wc = WalletClient
286287
f $ phi $ resetWalletState wc
287288
, importWallet =
288289
f . phi . importWallet wc
290+
, calculateMnemonic =
291+
\x -> f . phi . calculateMnemonic wc x
289292
}
290293

291294
-- | Run the given natural transformation over the 'WalletClient'.

wallet/src/Cardano/Wallet/Client/Http.hs

+2
Original file line numberDiff line numberDiff line change
@@ -108,6 +108,7 @@ mkHttpClient baseUrl manager = WalletClient
108108

109109
, importWallet
110110
= run . importWalletR
111+
, calculateMnemonic = \bp qb -> run $ calculateMnemonicR bp qb
111112
}
112113

113114
where
@@ -162,6 +163,7 @@ mkHttpClient baseUrl manager = WalletClient
162163
:<|> postponeUpdateR
163164
:<|> resetWalletStateR
164165
:<|> importWalletR
166+
:<|> calculateMnemonicR
165167
= internalAPI
166168

167169
addressesAPI

wallet/src/Cardano/Wallet/Kernel/DB/HdWallet.hs

+12-1
Original file line numberDiff line numberDiff line change
@@ -120,14 +120,15 @@ import Pos.Core.NetworkMagic (NetworkMagic (..))
120120
import Pos.Crypto (HDPassphrase)
121121
import qualified Pos.Crypto as Core
122122

123-
import Cardano.Wallet.API.V1.Types (V1 (..))
123+
import Cardano.Wallet.API.V1.Types (V1 (..), WAddressMeta(WAddressMeta))
124124
import Cardano.Wallet.Kernel.DB.BlockContext
125125
import Cardano.Wallet.Kernel.DB.InDb
126126
import Cardano.Wallet.Kernel.DB.Spec
127127
import Cardano.Wallet.Kernel.DB.Util.AcidState
128128
import Cardano.Wallet.Kernel.DB.Util.IxSet hiding (foldl')
129129
import qualified Cardano.Wallet.Kernel.DB.Util.IxSet as IxSet hiding (Indexable)
130130
import qualified Cardano.Wallet.Kernel.DB.Util.Zoomable as Z
131+
import Cardano.Wallet.Kernel.Decrypt (WalletDecrCredentials, decryptAddress)
131132
import Cardano.Wallet.Kernel.NodeStateAdaptor (SecurityParameter (..))
132133
import qualified Cardano.Wallet.Kernel.Util.StrictList as SL
133134
import Cardano.Wallet.Kernel.Util.StrictNonEmpty (StrictNonEmpty (..))
@@ -535,6 +536,16 @@ instance IsOurs [(HdRootId, Core.EncryptedSecretKey)] where
535536
let addrId = HdAddressId accId addressIx
536537
return $ HdAddress addrId (InDb addr)
537538

539+
instance IsOurs [ (HdRootId, WalletDecrCredentials) ] where
540+
isOurs addr s = (,s) $ foldl' (<|>) Nothing $ flip map s $ \(rootId, wdc) -> do
541+
case decryptAddress wdc (addr::Core.Address) of
542+
Just (WAddressMeta _wid accountIx addressIx _addrv1) -> do
543+
let
544+
accId = HdAccountId rootId (HdAccountIx accountIx)
545+
addrId = HdAddressId accId (HdAddressIx addressIx)
546+
pure (HdAddress addrId (InDb addr))
547+
Nothing -> Nothing
548+
538549
decryptHdLvl2DerivationPath
539550
:: Core.HDPassphrase
540551
-> Core.Address

wallet/src/Cardano/Wallet/WalletLayer.hs

+3-2
Original file line numberDiff line numberDiff line change
@@ -46,8 +46,8 @@ import Cardano.Wallet.API.Request.Filter (FilterOperations (..))
4646
import Cardano.Wallet.API.Request.Sort (SortOperations (..))
4747
import Cardano.Wallet.API.Response (APIResponse, SliceOf (..))
4848
import Cardano.Wallet.API.V1.Types (Account, AccountBalance,
49-
AccountIndex, AccountUpdate, Address, BatchImportResult,
50-
ForceNtpCheck, NewAccount, NewAddress, NewWallet,
49+
AccountIndex, AccountUpdate, Address, BackupPhrase, BatchImportResult,
50+
ForceNtpCheck, NewAccount, NewAddress, NewWallet, MnemonicBalance,
5151
NodeInfo, NodeSettings, PasswordUpdate, Payment,
5252
Redemption, SpendingPassword, Transaction, V1 (..),
5353
Wallet, WalletAddress, WalletId, WalletImport,
@@ -482,6 +482,7 @@ data PassiveWalletLayer m = PassiveWalletLayer
482482
, postponeUpdate :: m ()
483483
, resetWalletState :: m ()
484484
, importWallet :: WalletImport -> m (Either ImportWalletError Wallet)
485+
, calculateMnemonic :: Maybe Bool -> BackupPhrase -> m MnemonicBalance
485486

486487
-- updates
487488
, waitForUpdate :: m ConfirmedProposalState

wallet/src/Cardano/Wallet/WalletLayer/Kernel.hs

+1
Original file line numberDiff line numberDiff line change
@@ -144,6 +144,7 @@ bracketPassiveWallet pm mode logFunction keystore node fInjects f = do
144144
, getTransactions = Transactions.getTransactions w
145145
, getTxFromMeta = Transactions.toTransaction w
146146
, getNodeSettings = Settings.getNodeSettings w
147+
, calculateMnemonic = Internal.calculateMnemonic w
147148
}
148149
where
149150
-- Read-only operations

wallet/src/Cardano/Wallet/WalletLayer/Kernel/Internal.hs

+48-3
Original file line numberDiff line numberDiff line change
@@ -1,9 +1,12 @@
1+
{-# LANGUAGE RankNTypes #-}
2+
13
module Cardano.Wallet.WalletLayer.Kernel.Internal (
24
nextUpdate
35
, applyUpdate
46
, postponeUpdate
57
, resetWalletState
68
, importWallet
9+
, calculateMnemonic
710

811
, waitForUpdate
912
, addUpdate
@@ -15,11 +18,12 @@ import Control.Concurrent.MVar (modifyMVar_)
1518
import Data.Acid.Advanced (update')
1619
import System.IO.Error (isDoesNotExistError)
1720

18-
import Pos.Chain.Update (ConfirmedProposalState, SoftwareVersion)
21+
import Pos.Chain.Update (ConfirmedProposalState, SoftwareVersion, HasUpdateConfiguration)
22+
import Pos.Util.CompileInfo (HasCompileInfo)
1923
import Pos.Infra.InjectFail (FInject (..), testLogFInject)
2024

21-
import Cardano.Wallet.API.V1.Types (V1 (..), Wallet,
22-
WalletImport (..))
25+
import Cardano.Wallet.API.V1.Types (V1(V1), Wallet, BackupPhrase(BackupPhrase),
26+
WalletImport (..), WalletId, Coin, MnemonicBalance(MnemonicBalance))
2327
import Cardano.Wallet.Kernel.DB.AcidState (AddUpdate (..),
2428
ClearDB (..), GetNextUpdate (..), RemoveNextUpdate (..))
2529
import Cardano.Wallet.Kernel.DB.InDb
@@ -31,6 +35,16 @@ import qualified Cardano.Wallet.Kernel.Submission as Submission
3135
import Cardano.Wallet.WalletLayer (CreateWallet (..),
3236
ImportWalletError (..))
3337
import Cardano.Wallet.WalletLayer.Kernel.Wallets (createWallet)
38+
import Pos.Core.NetworkMagic (makeNetworkMagic, NetworkMagic)
39+
import Cardano.Wallet.Kernel.Internal (walletProtocolMagic, walletNode)
40+
import Cardano.Mnemonic (mnemonicToSeed)
41+
import Pos.Crypto (safeDeterministicKeyGen, EncryptedSecretKey)
42+
import Pos.Chain.Txp (TxIn, TxOutAux, toaOut, txOutValue, txOutAddress)
43+
import Cardano.Wallet.Kernel.DB.HdWallet (eskToHdRootId, isOurs)
44+
import qualified Cardano.Wallet.Kernel.DB.HdWallet as HD
45+
import Cardano.Wallet.WalletLayer.Kernel.Conv (toRootId)
46+
import Cardano.Wallet.Kernel.Decrypt (WalletDecrCredentials, eskToWalletDecrCredentials)
47+
import Pos.Core.Common (sumCoins)
3448

3549
-- | Get next update (if any)
3650
--
@@ -125,3 +139,34 @@ importWallet pw WalletImport{..} = liftIO $ do
125139
return $ case res of
126140
Left e -> Left (ImportWalletCreationFailed e)
127141
Right importedWallet -> Right importedWallet
142+
143+
-- takes a WalletDecrCredentials and transaction, and returns the Coin output, if its ours
144+
maybeReadcoin :: (HD.HdRootId, WalletDecrCredentials) -> (TxIn, TxOutAux) -> Maybe Coin
145+
maybeReadcoin wkey (_, txout) = case isOurs (txOutAddress . toaOut $ txout) [wkey] of
146+
(Just _, _) -> Just $ (txOutValue . toaOut) txout
147+
(Nothing, _)-> Nothing
148+
149+
calculateMnemonic :: MonadIO m => Kernel.PassiveWallet -> Maybe Bool -> BackupPhrase -> m MnemonicBalance
150+
calculateMnemonic wallet mbool (BackupPhrase mnemonic) = do
151+
let
152+
nm :: NetworkMagic
153+
nm = makeNetworkMagic $ wallet ^. walletProtocolMagic
154+
esk :: EncryptedSecretKey
155+
(_pubkey, esk) = safeDeterministicKeyGen (mnemonicToSeed mnemonic) mempty
156+
hdRoot :: HD.HdRootId
157+
hdRoot = eskToHdRootId nm esk
158+
walletid :: WalletId
159+
walletid = toRootId hdRoot
160+
wdc = eskToWalletDecrCredentials nm esk
161+
withNode :: (HasCompileInfo, HasUpdateConfiguration) => Node.Lock (Node.WithNodeState IO) -> Node.WithNodeState IO [Coin]
162+
withNode _lock = Node.filterUtxo (maybeReadcoin (hdRoot, wdc))
163+
checkBalance = fromMaybe False mbool
164+
maybeBalance <- case checkBalance of
165+
True -> do
166+
my_coins <- liftIO $ Node.withNodeState (wallet ^. walletNode) withNode
167+
let
168+
balance :: Integer
169+
balance = sumCoins my_coins
170+
pure $ Just $ balance
171+
False -> pure Nothing
172+
pure $ MnemonicBalance walletid maybeBalance

0 commit comments

Comments
 (0)