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.
@@ -104,9 +116,7 @@ restore pw forced esk = do
104
116
rootId = HD. eskToHdRootId nm esk
105
117
106
118
let -- DEFAULTS for wallet restoration
107
- -- we don't have a spending password during migration
108
- hasSpendingPassword = False
109
- -- we cannot derive an address without a spending password
119
+ hasSpendingPassword = isNothing $ checkPassMatches mempty esk
110
120
defaultAddress = Nothing
111
121
defaultWalletName = HD. WalletName " <Migrated Wallet>"
112
122
defaultAssuranceLevel = HD. AssuranceLevelStrict
@@ -132,3 +142,42 @@ restore pw forced esk = do
132
142
True -> do
133
143
logMsg Error (" Migration failed! " <> msg <> " You are advised to delete the newly created db and try again." )
134
144
exitFailure
145
+
146
+ -- | Verify that the spending password metadata are correctly set. We mistakenly
147
+ -- forgot to port a fix from RCD-47 done on 2.0.x onto 3.0.0 and, for a few
148
+ -- users, have migrated / restored their wallet with a wrong spending password
149
+ -- metadata (arbitrarily set to `False`), making their wallet completely
150
+ -- unusable.
151
+ --
152
+ -- This checks makes sure that the 'hasSpendingPassword' metadata correctly
153
+ -- reflects the wallet condition. To be run on each start-up, unfortunately.
154
+ sanityCheckSpendingPassword
155
+ :: Kernel. PassiveWallet
156
+ -> IO ()
157
+ sanityCheckSpendingPassword pw = do
158
+ let nm = makeNetworkMagic (pw ^. Kernel. walletProtocolMagic)
159
+ wKeys <- Keystore. getKeys (pw ^. Kernel. walletKeystore)
160
+ db <- Kernel. getWalletSnapshot pw
161
+ lastUpdateNow <- InDb <$> getCurrentTimestamp
162
+ forM_ wKeys $ \ esk -> do
163
+ let hasSpendingPassword = case checkPassMatches mempty esk of
164
+ Nothing -> HD. HasSpendingPassword lastUpdateNow
165
+ Just _ -> HD. NoSpendingPassword
166
+ let rootId = HD. eskToHdRootId nm esk
167
+ whenDiscrepancy db rootId hasSpendingPassword restoreTruth >>= \ case
168
+ Left (HD. UnknownHdRoot _) ->
169
+ logMsg Error " Failed to update spending password status, HDRoot is gone?"
170
+ Right _ ->
171
+ return ()
172
+ where
173
+ logMsg = pw ^. Kernel. walletLogMessage
174
+ whenDiscrepancy db rootId hasSpendingPassword action = do
175
+ case (hasSpendingPassword, Kernel. lookupHdRootId db rootId) of
176
+ (_, Left e) ->
177
+ return $ Left e
178
+ (HD. HasSpendingPassword _, Right root) | root ^. HD. hdRootHasPassword == HD. NoSpendingPassword ->
179
+ action rootId hasSpendingPassword
180
+ _ -> -- Avoid making a DB update when there's no need
181
+ return $ Right ()
182
+ restoreTruth rootId hasSpendingPassword =
183
+ void <$> update' (pw ^. Kernel. wallets) (UpdateHdRootPassword rootId hasSpendingPassword)
0 commit comments