Skip to content
This repository has been archived by the owner on Mar 1, 2019. It is now read-only.

clean-up access to encrypted secret keys and address pools construction #360

Open
wants to merge 1 commit into
base: develop
Choose a base branch
from
Open
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
22 changes: 17 additions & 5 deletions src/Cardano/Wallet/Kernel/BListener.hs
Original file line number Diff line number Diff line change
Expand Up @@ -34,7 +34,8 @@ import Pos.Crypto (EncryptedSecretKey)
import Pos.DB.Block (getBlund)
import Pos.Util.Log (Severity (..))

import Cardano.Wallet.Kernel.AddressPool (AddressPool)
import Cardano.Wallet.Kernel.AddressPool (AddressPool,
ErrAddressPoolInvalid (..))
import Cardano.Wallet.Kernel.DB.AcidState (ApplyBlock (..),
ObservableRollbackUseInTestsOnly (..), SwitchToFork (..),
SwitchToForkInternalError (..))
Expand All @@ -53,12 +54,12 @@ import qualified Cardano.Wallet.Kernel.NodeStateAdaptor as Node
import Cardano.Wallet.Kernel.Prefiltering (PrefilteredBlock)
import qualified Cardano.Wallet.Kernel.Prefiltering as P
import Cardano.Wallet.Kernel.Read (foreignPendingByAccount,
getEosPools, getFOWallets, getWalletSnapshot)
getAddressPools, getEncryptedSecretKeys,
getWalletSnapshot)
import Cardano.Wallet.Kernel.Restore
import qualified Cardano.Wallet.Kernel.Submission as Submission
import Cardano.Wallet.Kernel.Util.NonEmptyMap (NonEmptyMap)
import qualified Cardano.Wallet.Kernel.Util.NonEmptyMap as NEM
import Cardano.Wallet.Kernel.Wallets (mkEosAddress)
import Cardano.Wallet.WalletLayer.Kernel.Wallets
(blundToResolvedBlock)

Expand All @@ -78,9 +79,20 @@ prefilterContext
prefilterContext pw = do
db <- getWalletSnapshot pw
let foreigns = fmap Pending.txIns . foreignPendingByAccount $ db
hdFOs <- getFOWallets pw db
hdEOs <- getEosPools db (mkEosAddress $ pw ^. walletProtocolMagic)
hdFOs <- Map.traverseWithKey invariantFO =<< getEncryptedSecretKeys pw db
hdEOs <- Map.traverseWithKey invariantEO $ getAddressPools (pw ^. walletProtocolMagic) db
return (foreigns, hdFOs, hdEOs)
where
invariantFO :: HdRootId -> Maybe a -> IO a
invariantFO rootId = flip maybe return $ fail $ toString $
"Cardano.Wallet.Kernel.BListener: invariant violation: encrypted secret key \
\hasn't been found for the given root id: " <> sformat build rootId
Copy link
Contributor

@denisshevchenko denisshevchenko Feb 25, 2019

Choose a reason for hiding this comment

The reason will be displayed to describe this comment to others. Learn more.

Maybe just match explicitly?

    invariantFO :: HdRootId -> Maybe a -> IO a
    invariantFO rootId (Just k) = return k
    invariantFO rootId Nothing = fail $ toString $
        "Cardano.Wallet.Kernel.BListener: invariant violation: encrypted secret key \
        \hasn't been found for the given root id: " <> sformat build rootId

And the same for invariantEO..


invariantEO :: HdAccountId -> Either ErrAddressPoolInvalid a -> IO a
invariantEO accId = flip either return $ \err -> fail $ toString $
"Cardano.Wallet.Kernel.BListener: invariant violation: recovered invalid \
\address pool for the given account: " <> sformat build accId <> " ( "
<> sformat build err <> " )"

-- | Prefilter a resolved block for all wallets. If no wallets are present
-- we return Nothing. If either wallet type is present, we return only the
Expand Down
38 changes: 1 addition & 37 deletions src/Cardano/Wallet/Kernel/DB/HdWallet.hs
Original file line number Diff line number Diff line change
Expand Up @@ -99,9 +99,6 @@ module Cardano.Wallet.Kernel.DB.HdWallet (
, assumeHdAccountExists
-- * IsOurs
, IsOurs(..)
-- Address pool
, mkAddressPool
, mkAddressPoolExisting
) where

import Universum hiding ((:|))
Expand All @@ -125,8 +122,7 @@ import qualified Pos.Crypto as Core

import Cardano.Wallet.API.V1.Types (WalAddress (..))
import Cardano.Wallet.Kernel.AddressPool (AddressPool,
ErrAddressPoolInvalid (..), emptyAddressPool,
initAddressPool, lookupAddressPool)
lookupAddressPool)
import Cardano.Wallet.Kernel.AddressPoolGap (AddressPoolGap)
import Cardano.Wallet.Kernel.DB.BlockContext
import Cardano.Wallet.Kernel.DB.HdRootId (HdRootId)
Expand All @@ -136,8 +132,6 @@ import Cardano.Wallet.Kernel.DB.Util.AcidState
import Cardano.Wallet.Kernel.DB.Util.IxSet hiding (foldl')
import qualified Cardano.Wallet.Kernel.DB.Util.IxSet as IxSet hiding (Indexable)
import qualified Cardano.Wallet.Kernel.DB.Util.Zoomable as Z
import Cardano.Wallet.Kernel.Ed25519Bip44 (ChangeChain (..),
deriveAddressPublicKey)
import Cardano.Wallet.Kernel.NodeStateAdaptor (SecurityParameter (..))
import qualified Cardano.Wallet.Kernel.Util.StrictList as SL
import Cardano.Wallet.Kernel.Util.StrictNonEmpty (StrictNonEmpty (..))
Expand Down Expand Up @@ -564,36 +558,6 @@ decryptHdLvl2DerivationPath hdPass addr = do
[a,b] -> Just (HdAccountIx a, HdAddressIx b)
_ -> Nothing

{-------------------------------------------------------------------------------
create AddressPool for account
-------------------------------------------------------------------------------}

mkAddressPool
:: (Core.PublicKey -> Core.Address)
-> Core.PublicKey
-> AddressPoolGap
-> AddressPool Core.Address
mkAddressPool mkAddress accPK gap
= emptyAddressPool gap (mkAddressBuilder mkAddress accPK)

mkAddressPoolExisting
:: (Core.PublicKey -> Core.Address)
-> Core.PublicKey
-> AddressPoolGap
-> [(Core.Address, Word32)]
-> Either ErrAddressPoolInvalid (AddressPool Core.Address)
mkAddressPoolExisting mkAddress accPK gap addrs
= initAddressPool gap (mkAddressBuilder mkAddress accPK) addrs

mkAddressBuilder
:: (Core.PublicKey -> Core.Address)
-> Core.PublicKey
-> Word32
-> Core.Address
mkAddressBuilder mkAddress accPK addrIx
= case deriveAddressPublicKey accPK ExternalChain addrIx of
Nothing -> error "mkAddressPool: maximum number of addresses reached."
Just addrPK -> mkAddress addrPK

{-------------------------------------------------------------------------------
isOurs for Hd Sequential wallets
Expand Down
24 changes: 14 additions & 10 deletions src/Cardano/Wallet/Kernel/Pending.hs
Original file line number Diff line number Diff line change
Expand Up @@ -9,16 +9,11 @@ module Cardano.Wallet.Kernel.Pending (

import Universum hiding (State)

import qualified Data.List.NonEmpty as NE
import qualified Data.Map.Strict as Map

import Control.Concurrent.MVar (modifyMVar_)

import Data.Acid.Advanced (update')

import Pos.Chain.Txp (Tx (..), TxAux (..), TxOut (..))
import Pos.Core (Coin (..))
import Pos.Crypto (EncryptedSecretKey)
import qualified Data.List.NonEmpty as NE
import qualified Data.Map.Strict as Map
import Formatting (build, sformat)

import Cardano.Wallet.Kernel.DB.AcidState (CancelPending (..),
NewForeign (..), NewForeignError (..), NewPending (..),
Expand All @@ -29,9 +24,13 @@ import Cardano.Wallet.Kernel.DB.InDb
import qualified Cardano.Wallet.Kernel.DB.Spec.Pending as Pending
import Cardano.Wallet.Kernel.DB.TxMeta (TxMeta, putTxMeta)
import Cardano.Wallet.Kernel.Internal
import Cardano.Wallet.Kernel.Read (getFOWallets, getWalletSnapshot)
import Cardano.Wallet.Kernel.Read (getEncryptedSecretKeys,
getWalletSnapshot)
import Cardano.Wallet.Kernel.Submission (Cancelled, addPending)
import Cardano.Wallet.Kernel.Util.Core
import Pos.Chain.Txp (Tx (..), TxAux (..), TxOut (..))
import Pos.Core (Coin (..))
import Pos.Crypto (EncryptedSecretKey)

{-------------------------------------------------------------------------------
Submit pending transactions
Expand Down Expand Up @@ -89,7 +88,7 @@ newTx :: forall e. ActiveWallet
newTx ActiveWallet{..} accountId tx partialMeta upd = do
snapshot <- getWalletSnapshot walletPassive
-- run the update
hdRnds <- getFOWallets walletPassive snapshot
hdRnds <- Map.traverseWithKey invariant =<< getEncryptedSecretKeys walletPassive snapshot

let allOurAddresses = fst <$> allOurs hdRnds
res <- upd $ allOurAddresses
Expand All @@ -107,6 +106,11 @@ newTx ActiveWallet{..} accountId tx partialMeta upd = do
submitTx
return (Right txMeta)
where
invariant :: HdRootId -> Maybe a -> IO a
invariant rootId = flip maybe return $ fail $ toString $
"Cardano.Wallet.Kernel.Pending.newTx: invariant violation: encrypted secret key \
\hasn't been found for the given root id: " <> sformat build rootId

(txOut :: [TxOut]) = NE.toList $ (_txOutputs . taTx $ tx)

-- | NOTE: we recognise addresses in the transaction outputs that belong to _all_ wallets,
Expand Down
183 changes: 75 additions & 108 deletions src/Cardano/Wallet/Kernel/Read.hs
Original file line number Diff line number Diff line change
@@ -1,25 +1,19 @@
{-# LANGUAGE MultiWayIf #-}

-- | Read-only access to the DB
module Cardano.Wallet.Kernel.Read (
-- * Read-only access to the DB
DB -- opaque
-- ** HdRnd Helper
, getFOWallets
-- ** Eos Helper
, getEosPools
, addressPoolGapByRootId
, getWalletOwnership
, getWalletsByOwnership
, eosAccountsByRootId
, WalletOwnership (..)
-- Errors
, GetAddressPoolGapError (..)
-- ** The only effectful getter you will ever need
, getWalletSnapshot
-- ** Pure getters acting on a DB snapshot
, module Getters
) where
module Cardano.Wallet.Kernel.Read
( DB
, getEncryptedSecretKeys
, getAddressPools
, addressPoolGapByRootId
, getWalletOwnership
, getWalletsByOwnership
, eosAccountsByRootId
, WalletOwnership (..)
, GetAddressPoolGapError (..)
, getWalletSnapshot
, module Getters
) where

import Universum hiding (State)

Expand All @@ -28,27 +22,27 @@ import Data.List (nub)
import qualified Data.Map.Strict as Map
import Formatting (bprint, build, sformat, (%))
import qualified Formatting.Buildable
import Serokell.Util (listJson)

import Pos.Core (Address)
import Pos.Core.NetworkMagic (NetworkMagic, makeNetworkMagic)
import Pos.Core (Address, makePubKeyAddressBoot)
import Pos.Core.NetworkMagic (makeNetworkMagic)
import Pos.Crypto (EncryptedSecretKey, ProtocolMagic, PublicKey)
import Pos.Util.Wlog (Severity (..))

import Cardano.Wallet.Kernel.AddressPool (AddressPool)
import Cardano.Wallet.Kernel.AddressPool (AddressPool,
ErrAddressPoolInvalid (..), initAddressPool)
import Cardano.Wallet.Kernel.AddressPoolGap (AddressPoolGap)
import Cardano.Wallet.Kernel.DB.AcidState (DB, Snapshot (..),
dbHdWallets)
import Cardano.Wallet.Kernel.DB.HdRootId (HdRootId)
import Cardano.Wallet.Kernel.DB.HdWallet (HdAccountBase (..),
HdAccountId, HdAddress, HdRoot, getHdAddressIx,
hdAccountBase, hdAddressAddress, hdAddressId,
hdAddressIdIx, hdRootId, hdWalletsRoots,
mkAddressPoolExisting)
HdAccountId, HdRoot, getHdAddressIx, hdAccountBase,
hdAddressAddress, hdAddressId, hdAddressIdIx, hdRootId,
hdWalletsRoots)
import Cardano.Wallet.Kernel.DB.InDb (fromDb)
import Cardano.Wallet.Kernel.DB.Read as Getters
import Cardano.Wallet.Kernel.DB.Util.IxSet (Indexed (..))
import Cardano.Wallet.Kernel.DB.Util.IxSet (ixedIndexed)
import qualified Cardano.Wallet.Kernel.DB.Util.IxSet as IxSet
import Cardano.Wallet.Kernel.Ed25519Bip44 (ChangeChain (..),
deriveAddressPublicKey)
import Cardano.Wallet.Kernel.Internal
import qualified Cardano.Wallet.Kernel.Keystore as Keystore

Expand All @@ -60,96 +54,69 @@ getWalletSnapshot pw = query' (pw ^. wallets) Snapshot
Get Prefiltering context for all HdRnd wallets
-------------------------------------------------------------------------------}

-- | Prefiltering Context for HdRnd wallets
getFOWallets
getEncryptedSecretKeys
:: PassiveWallet
-> DB
-> IO (Map HdRootId EncryptedSecretKey)
getFOWallets pw db
= getWalletCredentials db
(pw ^. walletKeystore)
(pw ^. walletProtocolMagic)
(pw ^. walletLogMessage)

-- | Get wallet credentials
--
-- For wallets without a corresponding secret key we log an error. This
-- indicates a bug somewhere, but there is not much we can do about it here,
-- since this runs in the context of applying a block.
getWalletCredentials
:: DB
-> Keystore.Keystore
-> ProtocolMagic
-> (Severity -> Text -> IO ())
-> IO (Map HdRootId EncryptedSecretKey)
getWalletCredentials snapshot ks pm logger = do
(creds, missing) <- fmap partitionEithers $
forM (walletIds snapshot) $ \walletId ->
aux walletId <$> Keystore.lookup nm walletId ks
unless (null missing) $ logger Error (errMissing missing)
return (Map.fromList creds)
-> IO (Map HdRootId (Maybe EncryptedSecretKey))
getEncryptedSecretKeys pw db =
Map.fromList <$> forM (walletIds db) lookup'
where
nm :: NetworkMagic
nm = makeNetworkMagic pm

aux :: HdRootId
-> Maybe EncryptedSecretKey
-> Either (HdRootId, EncryptedSecretKey) HdRootId
aux walletId Nothing = Right walletId
aux walletId (Just esk) = Left (walletId, esk)
lookup' :: HdRootId -> IO (HdRootId, Maybe EncryptedSecretKey)
lookup' rootId = fmap (rootId,) $ Keystore.lookup
(makeNetworkMagic $ pw ^. walletProtocolMagic)
rootId
(pw ^. walletKeystore)

errMissing :: [HdRootId] -> Text
errMissing = sformat ("Root key missing for " % listJson)

{-------------------------------------------------------------------------------
Get Prefiltering context for all EOS wallets
-------------------------------------------------------------------------------}

-- | Gathers all Eo accounts in all Eo roots and builds an AddressPool
-- for each Eo account by using the existing addresses for the account.
--
-- NOTE: Fo wallet accounts are ignored.
getEosPools
:: MonadIO m
=> DB
-> (PublicKey -> Address)
-> m (Map HdAccountId (AddressPool Address))
getEosPools db mkAddress
= return . Map.fromList $ concatMap toAccountAddressPools' allRoots
getAddressPools
:: ProtocolMagic
-> DB
-> Map HdAccountId (Either ErrAddressPoolInvalid (AddressPool Address))
getAddressPools pm db = Map.unions $ do
(gap, accounts) <- map externallyOwnedRoots $ IxSet.toList $ db ^. dbHdWallets . hdWalletsRoots
return $ flip Map.mapWithKey accounts $ \accountId pubKey ->
initAddressPool gap (mkAddress pubKey) (addressesByAccountId' db accountId)
where
allRoots = IxSet.toList $ db ^. dbHdWallets . hdWalletsRoots

toAccountAddressPools' :: HdRoot -> [(HdAccountId, AddressPool Address)]
toAccountAddressPools' root
= toAccountAddressPools root (eosAccountsByRootId (root ^. hdRootId) db)

toAccountAddressPools
-- NOTE:
-- We arbitrarily take the maximum AddressPoolGap here. This is rather
-- incorrect but will go away with the next PR as part of #357!
externallyOwnedRoots
Copy link
Contributor

Choose a reason for hiding this comment

The reason will be displayed to describe this comment to others. Learn more.

Maybe we have to unify our naming? I mean that in some places we use a full form externallyOwned, but in other places we use a short one, EO...

:: HdRoot
-> Maybe (Either GetAddressPoolGapError ([(HdAccountId, PublicKey)], AddressPoolGap))
-> [(HdAccountId, AddressPool Address)]
toAccountAddressPools _root accs
= case accs of
Nothing -> [] -- not an Eos root
(Just (Left err)) -> error (sformat build err)
(Just (Right (accs_,gap))) -> map (mkPool gap) accs_

mkPool
:: AddressPoolGap
-> (HdAccountId, PublicKey)
-> (HdAccountId, AddressPool Address)
mkPool gap (accId,pk)
= case mkAddressPoolExisting mkAddress pk gap (getAddrs accId) of
Left invalidPoolErr -> error (sformat build invalidPoolErr)
Right pool -> (accId, pool)

getAddrs :: HdAccountId -> [(Address, Word32)]
getAddrs accId
= map (toAddr . _ixedIndexed) $
IxSet.toList (Getters.addressesByAccountId db accId)

toAddr :: HdAddress -> (Address, Word32)
toAddr a = ( a ^. hdAddressAddress . fromDb
, getHdAddressIx (a ^. hdAddressId . hdAddressIdIx))
-> (AddressPoolGap, Map HdAccountId PublicKey)
externallyOwnedRoots root = bimap maximum Map.unions $ unzip $ catMaybes $ do
account <- IxSet.toList $ Getters.accountsByRootId db (root ^. hdRootId)
return $ case account ^. hdAccountBase of
HdAccountBaseFO{} ->
Nothing
(HdAccountBaseEO accId pubKey gap) ->
Just (gap, Map.singleton accId pubKey)

addressesByAccountId'
:: DB
-> HdAccountId
-> [(Address, Word32)]
addressesByAccountId' _db accId = addressesByAccountId db accId
Copy link
Contributor

Choose a reason for hiding this comment

The reason will be displayed to describe this comment to others. Learn more.

If the first argument is not used - why do we need it? Maybe just remove _db?

& IxSet.toList
& map (view ixedIndexed)
& map (\x ->
( x ^. hdAddressAddress . fromDb
, getHdAddressIx (x ^. hdAddressId . hdAddressIdIx)
))

mkAddress
:: PublicKey
-> Word32
-> Address
mkAddress accPK ix = case deriveAddressPublicKey accPK ExternalChain ix of
Just addrPK -> makePubKeyAddressBoot (makeNetworkMagic pm) addrPK
Nothing -> error $
"Cardano.Wallet.Kernel.Read.mkAddress: maximum number of \
\addresses reached when trying to create an address with \
\at the following index: " <> sformat build ix


-- | For a given rootId, returns either Nothing if this is not an Eo wallet,
Expand Down