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

[CBR-437] Kernel.Wallets.updatePassword should record if the user decided to remove it #3621

Merged
merged 1 commit into from
Sep 21, 2018
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
10 changes: 9 additions & 1 deletion wallet-new/src/Cardano/Wallet/Kernel/Wallets.hs
Original file line number Diff line number Diff line change
Expand Up @@ -384,7 +384,15 @@ updatePassword pw hdRootId oldPassword newPassword = do
-- was set.
-- Fix this properly as part of [CBR-404].
lastUpdateNow <- InDb <$> getCurrentTimestamp
let hasSpendingPassword = HD.HasSpendingPassword lastUpdateNow

-- There is no such thing as "removing" the spending password.
-- However, it can be set to the empty string. We check for that
-- here and update 'hasSpendingPassword' on 'HdRoot' accordingly.
let hasSpendingPassword =
if newPassword == emptyPassphrase
then HD.NoSpendingPassword
else HD.HasSpendingPassword lastUpdateNow

res <- update' (pw ^. wallets)
(UpdateHdRootPassword hdRootId hasSpendingPassword)
case res of
Expand Down
20 changes: 20 additions & 0 deletions wallet-new/test/unit/Test/Spec/Wallets.hs
Original file line number Diff line number Diff line change
@@ -1,4 +1,5 @@
{-# LANGUAGE DataKinds #-}
{-# LANGUAGE LambdaCase #-}
{-# LANGUAGE TypeApplications #-}
module Test.Spec.Wallets (
spec
Expand All @@ -23,6 +24,7 @@ import qualified Cardano.Wallet.Kernel.BIP39 as BIP39
import Cardano.Wallet.Kernel.DB.HdWallet (AssuranceLevel (..),
HdRootId (..), UnknownHdRoot (..), WalletName (..),
hdRootId)
import qualified Cardano.Wallet.Kernel.DB.HdWallet as HD
import Cardano.Wallet.Kernel.DB.HdWallet.Create
(CreateHdRootError (..))
import Cardano.Wallet.Kernel.DB.InDb (InDb (..))
Expand Down Expand Up @@ -327,6 +329,24 @@ spec = describe "Wallets" $ do
newKey `shouldSatisfy` isJust
(fmap hash newKey) `shouldSatisfy` (not . (==) (fmap hash oldKey))

prop "correctly updates hdRootHasPassword" $ do
monadicIO $ do
newPwd <- pick arbitrary
withNewWalletFixture $ \ _ _ wallet Fixture{..} -> do
res <- Kernel.updatePassword wallet
fixtureHdRootId
(unV1 fixtureSpendingPassword)
newPwd
let passphraseIsEmpty = newPwd == emptyPassphrase
let satisfied = \case
HD.NoSpendingPassword -> passphraseIsEmpty
HD.HasSpendingPassword _ -> not passphraseIsEmpty
case res of
Left e -> fail (show e)
Right (_, newRoot) -> do
(newRoot ^. HD.hdRootHasPassword) `shouldSatisfy` satisfied


describe "Wallet update password (Servant)" $ do
prop "works as expected in the happy path scenario" $ withMaxSuccess 50 $ do
monadicIO $ do
Expand Down