1
+ {-# LANGUAGE RankNTypes #-}
2
+
1
3
module Cardano.Wallet.WalletLayer.Kernel.Internal (
2
4
nextUpdate
3
5
, applyUpdate
4
6
, postponeUpdate
5
7
, resetWalletState
6
8
, importWallet
9
+ , calculateMnemonic
7
10
8
11
, waitForUpdate
9
12
, addUpdate
@@ -15,11 +18,12 @@ import Control.Concurrent.MVar (modifyMVar_)
15
18
import Data.Acid.Advanced (update' )
16
19
import System.IO.Error (isDoesNotExistError )
17
20
18
- import Pos.Chain.Update (ConfirmedProposalState , SoftwareVersion )
21
+ import Pos.Chain.Update (ConfirmedProposalState , SoftwareVersion , HasUpdateConfiguration )
22
+ import Pos.Util.CompileInfo (HasCompileInfo )
19
23
import Pos.Infra.InjectFail (FInject (.. ), testLogFInject )
20
24
21
- import Cardano.Wallet.API.V1.Types (V1 ( .. ), Wallet ,
22
- WalletImport (.. ))
25
+ import Cardano.Wallet.API.V1.Types (V1 ( V1 ), Wallet , BackupPhrase ( BackupPhrase ) ,
26
+ WalletImport (.. ), WalletId , Coin , MnemonicBalance ( MnemonicBalance ) )
23
27
import Cardano.Wallet.Kernel.DB.AcidState (AddUpdate (.. ),
24
28
ClearDB (.. ), GetNextUpdate (.. ), RemoveNextUpdate (.. ))
25
29
import Cardano.Wallet.Kernel.DB.InDb
@@ -31,6 +35,16 @@ import qualified Cardano.Wallet.Kernel.Submission as Submission
31
35
import Cardano.Wallet.WalletLayer (CreateWallet (.. ),
32
36
ImportWalletError (.. ))
33
37
import Cardano.Wallet.WalletLayer.Kernel.Wallets (createWallet )
38
+ import Pos.Core.NetworkMagic (makeNetworkMagic , NetworkMagic )
39
+ import Cardano.Wallet.Kernel.Internal (walletProtocolMagic , walletNode )
40
+ import Cardano.Mnemonic (mnemonicToSeed )
41
+ import Pos.Crypto (safeDeterministicKeyGen , EncryptedSecretKey )
42
+ import Pos.Chain.Txp (TxIn , TxOutAux , toaOut , txOutValue , txOutAddress )
43
+ import Cardano.Wallet.Kernel.DB.HdWallet (eskToHdRootId , isOurs )
44
+ import qualified Cardano.Wallet.Kernel.DB.HdWallet as HD
45
+ import Cardano.Wallet.WalletLayer.Kernel.Conv (toRootId )
46
+ import Cardano.Wallet.Kernel.Decrypt (WalletDecrCredentials , eskToWalletDecrCredentials )
47
+ import Pos.Core.Common (sumCoins )
34
48
35
49
-- | Get next update (if any)
36
50
--
@@ -125,3 +139,34 @@ importWallet pw WalletImport{..} = liftIO $ do
125
139
return $ case res of
126
140
Left e -> Left (ImportWalletCreationFailed e)
127
141
Right importedWallet -> Right importedWallet
142
+
143
+ -- takes a WalletDecrCredentials and transaction, and returns the Coin output, if its ours
144
+ maybeReadcoin :: (HD. HdRootId , WalletDecrCredentials ) -> (TxIn , TxOutAux ) -> Maybe Coin
145
+ maybeReadcoin wkey (_, txout) = case isOurs (txOutAddress . toaOut $ txout) [wkey] of
146
+ (Just _, _) -> Just $ (txOutValue . toaOut) txout
147
+ (Nothing , _)-> Nothing
148
+
149
+ calculateMnemonic :: MonadIO m => Kernel. PassiveWallet -> Maybe Bool -> BackupPhrase -> m MnemonicBalance
150
+ calculateMnemonic wallet mbool (BackupPhrase mnemonic) = do
151
+ let
152
+ nm :: NetworkMagic
153
+ nm = makeNetworkMagic $ wallet ^. walletProtocolMagic
154
+ esk :: EncryptedSecretKey
155
+ (_pubkey, esk) = safeDeterministicKeyGen (mnemonicToSeed mnemonic) mempty
156
+ hdRoot :: HD. HdRootId
157
+ hdRoot = eskToHdRootId nm esk
158
+ walletid :: WalletId
159
+ walletid = toRootId hdRoot
160
+ wdc = eskToWalletDecrCredentials nm esk
161
+ withNode :: (HasCompileInfo , HasUpdateConfiguration ) => Node. Lock (Node. WithNodeState IO ) -> Node. WithNodeState IO [Coin ]
162
+ withNode _lock = Node. filterUtxo (maybeReadcoin (hdRoot, wdc))
163
+ checkBalance = fromMaybe False mbool
164
+ maybeBalance <- case checkBalance of
165
+ True -> do
166
+ my_coins <- liftIO $ Node. withNodeState (wallet ^. walletNode) withNode
167
+ let
168
+ balance :: Integer
169
+ balance = sumCoins my_coins
170
+ pure $ Just $ balance
171
+ False -> pure Nothing
172
+ pure $ MnemonicBalance walletid maybeBalance
0 commit comments