1
- module Cardano.Wallet.Kernel.Migration (migrateLegacyDataLayer ) where
1
+ {-# LANGUAGE LambdaCase #-}
2
+
3
+ module Cardano.Wallet.Kernel.Migration
4
+ ( migrateLegacyDataLayer
5
+ , sanityCheckSpendingPassword
6
+ ) where
2
7
3
8
import Universum
4
9
10
+ import Data.Acid.Advanced (update' )
5
11
import Data.Text (pack )
6
12
import Data.Time (defaultTimeLocale , formatTime , getCurrentTime ,
7
13
iso8601DateFormat )
14
+ import Pos.Crypto.Signing (checkPassMatches )
8
15
import System.Directory (doesDirectoryExist , makeAbsolute , renamePath )
9
16
10
17
import Formatting ((%) )
@@ -15,10 +22,15 @@ import Pos.Crypto (EncryptedSecretKey)
15
22
import Pos.Util.Wlog (Severity (.. ))
16
23
17
24
import qualified Cardano.Wallet.Kernel as Kernel
25
+ import Cardano.Wallet.Kernel.DB.AcidState (UpdateHdRootPassword (.. ))
18
26
import qualified Cardano.Wallet.Kernel.DB.HdWallet as HD
27
+ import Cardano.Wallet.Kernel.DB.InDb (InDb (.. ))
28
+ import qualified Cardano.Wallet.Kernel.DB.Read as Kernel
19
29
import qualified Cardano.Wallet.Kernel.Internal as Kernel
20
30
import Cardano.Wallet.Kernel.Keystore as Keystore
31
+ import qualified Cardano.Wallet.Kernel.Read as Kernel
21
32
import Cardano.Wallet.Kernel.Restore (restoreWallet )
33
+ import Cardano.Wallet.Kernel.Util.Core (getCurrentTimestamp )
22
34
23
35
{- ------------------------------------------------------------------------------
24
36
Pure helper functions for migration.
@@ -105,7 +117,7 @@ restore pw forced esk = do
105
117
106
118
let -- DEFAULTS for wallet restoration
107
119
-- we don't have a spending password during migration
108
- hasSpendingPassword = False
120
+ hasSpendingPassword = isNothing $ checkPassMatches mempty esk
109
121
-- we cannot derive an address without a spending password
110
122
defaultAddress = Nothing
111
123
defaultWalletName = HD. WalletName " <Migrated Wallet>"
@@ -132,3 +144,42 @@ restore pw forced esk = do
132
144
True -> do
133
145
logMsg Error (" Migration failed! " <> msg <> " You are advised to delete the newly created db and try again." )
134
146
exitFailure
147
+
148
+ -- | Verify that the spending password metadata are correctly set. We mistakenly
149
+ -- forgot to port a fix from RCD-47 done on 2.0.x onto 3.0.0 and, for a few
150
+ -- users, have migrated / restored their wallet with a wrong spending password
151
+ -- metadata (arbitrarily set to `False`), making their wallet completely
152
+ -- unusable.
153
+ --
154
+ -- This checks makes sure that the 'hasSpendingPassword' metadata correctly
155
+ -- reflects the wallet condition. To be run on each start-up, unfortunately.
156
+ sanityCheckSpendingPassword
157
+ :: Kernel. PassiveWallet
158
+ -> IO ()
159
+ sanityCheckSpendingPassword pw = do
160
+ let nm = makeNetworkMagic (pw ^. Kernel. walletProtocolMagic)
161
+ wKeys <- Keystore. getKeys (pw ^. Kernel. walletKeystore)
162
+ db <- Kernel. getWalletSnapshot pw
163
+ lastUpdateNow <- InDb <$> getCurrentTimestamp
164
+ forM_ wKeys $ \ esk -> do
165
+ let hasSpendingPassword = case checkPassMatches mempty esk of
166
+ Nothing -> HD. NoSpendingPassword
167
+ Just _ -> HD. HasSpendingPassword lastUpdateNow
168
+ let rootId = HD. eskToHdRootId nm esk
169
+ whenDiscrepancy db rootId hasSpendingPassword restoreTruth >>= \ case
170
+ Left (HD. UnknownHdRoot _) ->
171
+ logMsg Error " Failed to update spending password status, HDRoot is gone?"
172
+ Right _ ->
173
+ return ()
174
+ where
175
+ logMsg = pw ^. Kernel. walletLogMessage
176
+ whenDiscrepancy db rootId hasSpendingPassword action = do
177
+ case (hasSpendingPassword, Kernel. lookupHdRootId db rootId) of
178
+ (_, Left e) ->
179
+ return $ Left e
180
+ (HD. HasSpendingPassword _, Right root) | root ^. HD. hdRootHasPassword == HD. NoSpendingPassword ->
181
+ action rootId hasSpendingPassword
182
+ _ -> -- Avoid making a DB update when there's no need
183
+ return $ Right ()
184
+ restoreTruth rootId hasSpendingPassword =
185
+ void <$> update' (pw ^. Kernel. wallets) (UpdateHdRootPassword rootId hasSpendingPassword)
0 commit comments