This repository has been archived by the owner on Mar 1, 2019. It is now read-only.
-
Notifications
You must be signed in to change notification settings - Fork 12
clean-up access to encrypted secret keys and address pools construction #360
Open
KtorZ
wants to merge
1
commit into
develop
Choose a base branch
from
KtorZ/357/restructure-pool-construction
base: develop
Could not load branches
Branch not found: {{ refName }}
Loading
Could not load tags
Nothing to show
Loading
Are you sure you want to change the base?
Some commits from the old base branch may be removed from the timeline,
and old review comments may become outdated.
Open
Changes from all commits
Commits
File filter
Filter by extension
Conversations
Failed to load comments.
Loading
Jump to
Jump to file
Failed to load files.
Loading
Diff view
Diff view
There are no files selected for viewing
This file contains bidirectional Unicode text that may be interpreted or compiled differently than what appears below. To review, open the file in an editor that reveals hidden Unicode characters.
Learn more about bidirectional Unicode characters
This file contains bidirectional Unicode text that may be interpreted or compiled differently than what appears below. To review, open the file in an editor that reveals hidden Unicode characters.
Learn more about bidirectional Unicode characters
This file contains bidirectional Unicode text that may be interpreted or compiled differently than what appears below. To review, open the file in an editor that reveals hidden Unicode characters.
Learn more about bidirectional Unicode characters
This file contains bidirectional Unicode text that may be interpreted or compiled differently than what appears below. To review, open the file in an editor that reveals hidden Unicode characters.
Learn more about bidirectional Unicode characters
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) | ||
|
||
|
@@ -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 | ||
|
||
|
@@ -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 | ||
There was a problem hiding this comment. Choose a reason for hiding this commentThe 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 |
||
:: 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 | ||
There was a problem hiding this comment. Choose a reason for hiding this commentThe 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 |
||
& 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, | ||
|
Add this suggestion to a batch that can be applied as a single commit.
This suggestion is invalid because no changes were made to the code.
Suggestions cannot be applied while the pull request is closed.
Suggestions cannot be applied while viewing a subset of changes.
Only one suggestion per line can be applied in a batch.
Add this suggestion to a batch that can be applied as a single commit.
Applying suggestions on deleted lines is not supported.
You must change the existing code in this line in order to create a valid suggestion.
Outdated suggestions cannot be applied.
This suggestion has been applied or marked resolved.
Suggestions cannot be applied from pending reviews.
Suggestions cannot be applied on multi-line comments.
Suggestions cannot be applied while the pull request is queued to merge.
Suggestion cannot be applied right now. Please check back later.
There was a problem hiding this comment.
Choose a reason for hiding this comment
The reason will be displayed to describe this comment to others. Learn more.
Maybe just match explicitly?
And the same for
invariantEO
..