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

Commit 3fe70b0

Browse files
author
Denis Shevchenko
authored
Merge pull request #3468 from input-output-hk/CHW-5-api-wallets-impl
[CHW] Implement basic handlers for work with external wallets.
2 parents 7e7de6d + 00f1714 commit 3fe70b0

File tree

7 files changed

+141
-27
lines changed

7 files changed

+141
-27
lines changed

server/Main.hs

+5-5
Original file line numberDiff line numberDiff line change
@@ -29,12 +29,12 @@ import Pos.Launcher.Configuration (AssetLockPath (..),
2929
import Pos.Util (logException)
3030
import Pos.Util.CompileInfo (HasCompileInfo, withCompileInfo)
3131
import Pos.Util.UserSecret (usVss)
32-
import Pos.Wallet.Web (bracketWalletWS, bracketWalletWebDB, getSKById,
33-
getWalletAddresses, runWRealMode)
32+
import Pos.Wallet.Web (bracketWalletWS, bracketWalletWebDB,
33+
getKeyById, getWalletAddresses, runWRealMode)
3434
import Pos.Wallet.Web.Mode (WalletWebMode)
3535
import Pos.Wallet.Web.State (askWalletDB, askWalletSnapshot,
3636
flushWalletStorage)
37-
import Pos.Wallet.Web.Tracking.Decrypt (eskToWalletDecrCredentials)
37+
import Pos.Wallet.Web.Tracking.Decrypt (keyToWalletDecrCredentials)
3838
import Pos.Wallet.Web.Tracking.Sync (syncWallet)
3939
import System.Wlog (LoggerName, Severity (..), logInfo, logMessage,
4040
usingLoggerName)
@@ -100,8 +100,8 @@ actionWithWallet pm txpConfig sscParams nodeParams ntpConfig wArgs@WalletBackend
100100
syncWallets :: WalletWebMode ()
101101
syncWallets = do
102102
addrs <- getWalletAddresses <$> askWalletSnapshot
103-
sks <- mapM getSKById addrs
104-
forM_ sks (syncWallet . eskToWalletDecrCredentials)
103+
keys' <- mapM getKeyById addrs
104+
forM_ keys' (syncWallet . keyToWalletDecrCredentials)
105105

106106
plugins :: TVar NtpStatus -> Plugins.Plugin WalletWebMode
107107
plugins ntpStatus =

src/Cardano/Wallet/API/V1/LegacyHandlers/Addresses.hs

+2-2
Original file line numberDiff line numberDiff line change
@@ -27,7 +27,7 @@ import qualified Pos.Wallet.Web.State.State as V0State
2727
import Pos.Wallet.Web.State.Storage (getWalletAddresses)
2828
import qualified Pos.Wallet.Web.State.Storage as V0
2929
import qualified Pos.Wallet.Web.Tracking as V0 (txMempoolToModifier)
30-
import Pos.Wallet.Web.Tracking.Decrypt (eskToWalletDecrCredentials)
30+
import Pos.Wallet.Web.Tracking.Decrypt (keyToWalletDecrCredentials)
3131

3232
import Cardano.Wallet.API.Indices (IxSet)
3333
import Cardano.Wallet.API.Request
@@ -126,6 +126,6 @@ getAddress addrText = do
126126
Just (_walletMeta, V0.AddressInfo{..}) -> do
127127
let accId = adiWAddressMeta ^. V0.wamAccount
128128
mps <- V0.withTxpLocalData V0.getMempoolSnapshot
129-
accMod <- V0.txMempoolToModifier ws mps . eskToWalletDecrCredentials =<< V0.findKey accId
129+
accMod <- V0.txMempoolToModifier ws mps . keyToWalletDecrCredentials =<< V0.findKey accId
130130
let caddr = V0.getWAddress ws accMod adiWAddressMeta
131131
single <$> migrate caddr

src/Cardano/Wallet/API/V1/LegacyHandlers/Wallets.hs

+99-11
Original file line numberDiff line numberDiff line change
@@ -6,6 +6,7 @@ module Cardano.Wallet.API.V1.LegacyHandlers.Wallets (
66
, newWallet
77
) where
88

9+
import Formatting (build, sformat)
910
import Universum
1011
import UnliftIO (MonadUnliftIO)
1112

@@ -21,9 +22,11 @@ import Cardano.Wallet.API.V1.Types as V1
2122
import qualified Cardano.Wallet.API.V1.Wallets as Wallets
2223
import qualified Cardano.Wallet.Kernel.DB.Util.IxSet as IxSet
2324
import Pos.Chain.Update ()
25+
import Pos.Client.KeyStorage (addPublicKey)
2426
import qualified Pos.Core as Core
2527

26-
import Pos.Util (HasLens (..))
28+
import Pos.Util (HasLens (..), maybeThrow)
29+
import Pos.Util.Servant (encodeCType)
2730
import qualified Pos.Wallet.WalletMode as V0
2831
import Pos.Wallet.Web.Methods.Logic (MonadWalletLogic,
2932
MonadWalletLogicRead)
@@ -199,25 +202,110 @@ checkExternalWallet _encodedRootPK =
199202
-- | Creates a new or restores an existing external @wallet@ given a 'NewExternalWallet' payload.
200203
-- Returns to the client the representation of the created or restored wallet in the 'Wallet' type.
201204
newExternalWallet
205+
:: ( MonadThrow m
206+
, MonadUnliftIO m
207+
-- , HasLens SyncQueue ctx SyncQueue
208+
, V0.MonadBlockchainInfo m
209+
, V0.MonadWalletLogic ctx m
210+
)
211+
=> NewExternalWallet
212+
-> m (WalletResponse Wallet)
213+
newExternalWallet (NewExternalWallet rootPK assuranceLevel name operation) = do
214+
let newExternalWalletHandler CreateWallet = createNewExternalWallet
215+
newExternalWalletHandler RestoreWallet = restoreExternalWallet
216+
walletMeta <- V0.CWalletMeta <$> pure name
217+
<*> migrate assuranceLevel
218+
<*> pure 0
219+
single <$> do
220+
v0wallet <- newExternalWalletHandler operation walletMeta rootPK
221+
ws <- V0.askWalletSnapshot
222+
migrateWallet ws v0wallet True
223+
224+
-- | Creates new external wallet.
225+
createNewExternalWallet
226+
:: ( MonadThrow m
227+
, V0.MonadWalletLogic ctx m
228+
)
229+
=> V0.CWalletMeta
230+
-> PublicKeyAsBase58
231+
-> m V0.CWallet
232+
createNewExternalWallet walletMeta encodedRootPK = do
233+
rootPK <- case mkPublicKeyFromBase58 encodedRootPK of
234+
Left problem -> throwM (InvalidPublicKey $ sformat build problem)
235+
Right rootPK -> return rootPK
236+
237+
-- This extended public key will be used during synchronization
238+
-- with the blockchain.
239+
addPublicKey rootPK
240+
241+
let walletId = encodeCType . Core.makePubKeyAddressBoot $ rootPK
242+
isReady = True -- We don't need to sync new wallet with the blockchain.
243+
244+
-- Create new external wallet.
245+
-- This is safe: if the client will try to create an external wallet from the same
246+
-- root public key - error will be thrown.
247+
void $ V0.createWalletSafe walletId walletMeta isReady
248+
249+
addInitAccountInExternalWallet walletId
250+
251+
V0.getWallet walletId
252+
253+
-- | Restore external wallet using it's root public key and metadata.
254+
restoreExternalWallet
202255
:: -- ( MonadThrow m
203256
-- , MonadUnliftIO m
204257
-- , HasLens SyncQueue ctx SyncQueue
205-
-- , V0.MonadBlockchainInfo m
206258
-- , V0.MonadWalletLogic ctx m
207259
-- )
208260
-- =>
209-
NewExternalWallet
210-
-> m (WalletResponse Wallet)
211-
newExternalWallet NewExternalWallet{..} =
212-
error "[CHW-80], Cardano Hardware Wallet, new external wallet, legacy handler, unimplemented yet."
261+
V0.CWalletMeta
262+
-> PublicKeyAsBase58
263+
-> m V0.CWallet
264+
restoreExternalWallet _walletMeta _encodedRootPK =
265+
error "[CHW-54], restore external wallet, unimplemented yet."
266+
267+
addInitAccountInExternalWallet
268+
:: ( MonadThrow m
269+
, V0.MonadWalletLogic ctx m
270+
)
271+
=> V0.CId V0.Wal
272+
-> m ()
273+
addInitAccountInExternalWallet walletId = do
274+
let accountName = "Initial account"
275+
accountMeta = V0.CAccountMeta accountName
276+
accountInit = V0.CAccountInit accountMeta walletId
277+
includeUnready = True
278+
void $ V0.newExternalAccountIncludeUnready includeUnready accountInit
213279

214280
-- | On the disk, once imported or created, there's so far not much difference
215281
-- between a wallet and an external wallet, except one: node stores a public key
216282
-- for external wallet, there's no secret key.
217283
deleteExternalWallet
218-
:: -- (V0.MonadWalletLogic ctx m)
219-
-- =>
220-
PublicKeyAsBase58
284+
:: (V0.MonadWalletLogic ctx m)
285+
=> PublicKeyAsBase58
221286
-> m NoContent
222-
deleteExternalWallet _encodedRootPK =
223-
error "[CHW-106], Cardano Hardware Wallet, delete external wallet, legacy handler, unimplemented yet."
287+
deleteExternalWallet encodedRootPK =
288+
case V1.mkPublicKeyFromBase58 encodedRootPK of
289+
Left problem -> throwM (InvalidPublicKey $ sformat build problem)
290+
Right rootPK -> V0.deleteExternalWallet rootPK
291+
292+
migrateWallet
293+
:: ( V0.MonadWalletLogicRead ctx m
294+
, V0.MonadBlockchainInfo m
295+
)
296+
=> V0.WalletSnapshot
297+
-> V0.CWallet
298+
-> Bool
299+
-> m Wallet
300+
migrateWallet snapshot wallet walletIsReady = do
301+
let walletId = V0.cwId wallet
302+
walletInfo <- if walletIsReady
303+
then maybeThrow WalletNotFound $ V0.getWalletInfo walletId snapshot
304+
else
305+
-- Wallet is not ready yet (because of restoring),
306+
-- the only information we can provide is the default one.
307+
pure $ V0.getUnreadyWalletInfo snapshot
308+
walletIsExternal <- V0.isWalletExternal walletId
309+
let walletType = if walletIsExternal then WalletExternal else WalletRegular
310+
currentDepth <- V0.networkChainDifficulty
311+
migrate (wallet, walletInfo, walletType, currentDepth)

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

+23-1
Original file line numberDiff line numberDiff line change
@@ -41,6 +41,7 @@ module Cardano.Wallet.API.V1.Types (
4141
, ExternalWallet (..)
4242
, PublicKeyAsBase58
4343
, mkPublicKeyAsBase58
44+
, mkPublicKeyFromBase58
4445
, NewExternalWallet (..)
4546
, WalletAndTxHistory (..)
4647
-- * Addresses
@@ -151,7 +152,7 @@ import Data.Swagger.Internal.TypeShape (GenericHasSimpleShape,
151152
import Data.Text (Text, dropEnd, toLower)
152153
import qualified Data.Text as T
153154
import Data.Version (Version)
154-
import Formatting (bprint, build, fconst, int, sformat, (%))
155+
import Formatting (bprint, build, fconst, int, sformat, stext, (%))
155156
import qualified Formatting.Buildable
156157
import Generics.SOP.TH (deriveGeneric)
157158
import GHC.Generics (Generic, Rep)
@@ -618,6 +619,27 @@ mkPublicKeyAsBase58 (PublicKey xPub) = PublicKeyAsBase58Unsafe encodedXPub
618619
where
619620
encodedXPub = decodeUtf8 $ encodeBase58 bitcoinAlphabet (CC.unXPub xPub)
620621

622+
-- | Possible problems with Base58-encoded extended public key.
623+
data Base58PublicKeyError
624+
= PublicKeyNotInBase58Form
625+
| NotAPublicKey !Text
626+
deriving Show
627+
628+
instance Buildable Base58PublicKeyError where
629+
build PublicKeyNotInBase58Form =
630+
"Extended public key is not in Base58-format."
631+
build (NotAPublicKey msg) =
632+
bprint ("It is not an extended public key: "%stext) msg
633+
634+
-- | Decoder for 'PublicKey' in Base58-format.
635+
mkPublicKeyFromBase58 :: PublicKeyAsBase58 -> Either Base58PublicKeyError PublicKey
636+
mkPublicKeyFromBase58 (PublicKeyAsBase58Unsafe encodedXPub) = do
637+
case (decodeBase58 bitcoinAlphabet . encodeUtf8 $ encodedXPub) of
638+
Nothing -> Left PublicKeyNotInBase58Form
639+
Just rawKey -> case CC.xpub rawKey of
640+
Left problem -> Left $ NotAPublicKey (toText problem)
641+
Right xPub -> Right $ PublicKey xPub
642+
621643
-- | Type for representation address in Base58-format.
622644
-- We use it for external wallets.
623645
newtype AddressAsBase58 = AddressAsBase58Unsafe

src/Cardano/Wallet/Kernel/Pending.hs

+3-2
Original file line numberDiff line numberDiff line change
@@ -31,7 +31,8 @@ import Cardano.Wallet.Kernel.Read (getWalletCredentials)
3131
import Cardano.Wallet.Kernel.Submission (Cancelled, addPending)
3232
import Cardano.Wallet.Kernel.Types (WalletId (..))
3333

34-
import Pos.Wallet.Web.Tracking.Decrypt (eskToWalletDecrCredentials)
34+
import Pos.Wallet.Web.Tracking.Decrypt (WalletDecrCredentialsKey (..),
35+
keyToWalletDecrCredentials)
3536

3637
{-------------------------------------------------------------------------------
3738
Submit pending transactions
@@ -105,7 +106,7 @@ newTx ActiveWallet{..} accountId tx mbMeta upd = do
105106
map f $ filterOurs wKey identity addrs
106107
where
107108
f (address,addressId) = initHdAddress addressId (InDb address)
108-
wKey = (wid, eskToWalletDecrCredentials esk)
109+
wKey = (wid, keyToWalletDecrCredentials $ KeyForRegular esk)
109110

110111
putTxMeta' :: Maybe TxMeta -> IO ()
111112
putTxMeta' (Just meta) = putTxMeta (walletPassive ^. walletMeta) meta

src/Cardano/Wallet/Kernel/PrefilterTx.hs

+4-3
Original file line numberDiff line numberDiff line change
@@ -30,7 +30,8 @@ import Pos.Core.Txp (TxId, TxIn (..), TxOut (..), TxOutAux (..))
3030
import Pos.Crypto (EncryptedSecretKey)
3131
import Pos.Wallet.Web.State.Storage (WAddressMeta (..))
3232
import Pos.Wallet.Web.Tracking.Decrypt (WalletDecrCredentials,
33-
eskToWalletDecrCredentials, selectOwnAddresses)
33+
WalletDecrCredentialsKey (..), keyToWalletDecrCredentials,
34+
selectOwnAddresses)
3435

3536
import Cardano.Wallet.Kernel.DB.BlockMeta
3637
import Cardano.Wallet.Kernel.DB.HdWallet
@@ -168,7 +169,7 @@ prefilterUtxo :: HdRootId -> EncryptedSecretKey -> Utxo -> Map HdAccountId (Utxo
168169
prefilterUtxo rootId esk utxo = map toPrefilteredUtxo prefUtxo
169170
where
170171
(_,prefUtxo) = prefilterUtxo' wKey utxo
171-
wKey = (WalletIdHdRnd rootId, eskToWalletDecrCredentials esk)
172+
wKey = (WalletIdHdRnd rootId, keyToWalletDecrCredentials $ KeyForRegular esk)
172173

173174
-- | Produce Utxo along with all (extended) addresses occurring in the Utxo
174175
toPrefilteredUtxo :: UtxoWithAddrId -> (Utxo,[AddrWithId])
@@ -262,7 +263,7 @@ prefilterBlock block wid esk =
262263
, metas)
263264
where
264265
wdc :: WalletDecrCredentials
265-
wdc = eskToWalletDecrCredentials esk
266+
wdc = keyToWalletDecrCredentials $ KeyForRegular esk
266267
wKey = (wid, wdc)
267268

268269
inps :: [Map HdAccountId (Set TxIn)]

src/Cardano/Wallet/Server/Plugins.hs

+5-3
Original file line numberDiff line numberDiff line change
@@ -182,9 +182,11 @@ legacyWalletBackend pm txpConfig WalletBackendParams {..} ntpStatus = pure $ \di
182182
handleV0Errors se =
183183
let maskSensitive err =
184184
case err of
185-
V0.RequestError _ -> err
186-
V0.InternalError _ -> V0.RequestError "InternalError"
187-
V0.DecodeError _ -> V0.RequestError "DecodeError"
185+
V0.RequestError _ -> err
186+
V0.DuplicateWalletError _ -> V0.RequestError "DuplicateWalletError"
187+
V0.NoSuchWalletError _ -> V0.RequestError "NoSuchWalletError"
188+
V0.InternalError _ -> V0.RequestError "InternalError"
189+
V0.DecodeError _ -> V0.RequestError "DecodeError"
188190
reify :: V0.WalletError -> V1.WalletError
189191
reify = V1.UnknownError . sformat build . maskSensitive
190192
in fmap (responseLBS badRequest400 [applicationJson] . encode . reify) (fromException se)

0 commit comments

Comments
 (0)