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

Commit f8ea3d9

Browse files
committed
[CBR-243] Remove debugging code
1 parent 76d99ca commit f8ea3d9

File tree

1 file changed

+101
-68
lines changed

1 file changed

+101
-68
lines changed

wallet-new/src/Cardano/Wallet/Kernel/Restore.hs

+101-68
Original file line numberDiff line numberDiff line change
@@ -7,14 +7,17 @@ module Cardano.Wallet.Kernel.Restore
77

88
import Universum
99

10-
import Control.Concurrent (threadDelay)
1110
import Control.Concurrent.Async (async, cancel)
1211
import Control.Concurrent.MVar (modifyMVar_)
1312
import Data.Acid (update)
1413
import qualified Data.Map.Merge.Strict as M
1514
import qualified Data.Map.Strict as M
1615
import Data.Time.Clock (NominalDiffTime, UTCTime, diffUTCTime,
1716
getCurrentTime)
17+
import Formatting (bprint, build, formatToString, (%))
18+
import qualified Formatting.Buildable
19+
20+
import qualified Prelude
1821

1922
import Cardano.Wallet.API.Types.UnitOfMeasure
2023
import Cardano.Wallet.Kernel (walletLogMessage)
@@ -25,6 +28,7 @@ import Cardano.Wallet.Kernel.DB.AcidState (ApplyHistoricalBlock (..),
2528
import Cardano.Wallet.Kernel.DB.BlockContext
2629
import qualified Cardano.Wallet.Kernel.DB.HdWallet as HD
2730
import Cardano.Wallet.Kernel.DB.HdWallet.Create (CreateHdRootError)
31+
import qualified Cardano.Wallet.Kernel.DB.Spec.Update as Spec
2832
import Cardano.Wallet.Kernel.DB.TxMeta.Types
2933
import Cardano.Wallet.Kernel.Decrypt (WalletDecrCredentialsKey (..),
3034
decryptAddress, keyToWalletDecrCredentials)
@@ -42,8 +46,8 @@ import Cardano.Wallet.Kernel.Types (WalletId (..))
4246
import Cardano.Wallet.Kernel.Util.Core (utxoBalance)
4347
import Cardano.Wallet.Kernel.Wallets (createWalletHdRnd)
4448

45-
import Pos.Chain.Block (Blund, HeaderHash, MainBlock, headerHash,
46-
mainBlockSlot)
49+
import Pos.Chain.Block (Block, Blund, HeaderHash, MainBlock, Undo,
50+
headerHash, mainBlockSlot)
4751
import Pos.Chain.Txp (GenesisUtxo (..), Utxo, genesisUtxo)
4852
import Pos.Core (BlockCount (..), Coin, SlotId, flattenSlotIdExplicit,
4953
mkCoin, unsafeIntegerToCoin)
@@ -52,7 +56,7 @@ import Pos.Crypto (EncryptedSecretKey)
5256
import Pos.DB.Block (getFirstGenesisBlockHash, getUndo,
5357
resolveForwardLink)
5458
import Pos.DB.Class (getBlock)
55-
import Pos.Util.Trace (Severity (Debug, Error))
59+
import Pos.Util.Trace (Severity (Error))
5660

5761
-- | Restore a wallet
5862
--
@@ -188,97 +192,96 @@ getWalletInitInfo wKey@(wId, wdc) lock = do
188192
return (addrId ^. HD.hdAddressIdParent, M.singleton inp (out, addrId))
189193

190194
-- | Restore a wallet's transaction history.
195+
--
196+
-- TODO: Think about what we should do if a 'RestorationException' is thrown.
191197
restoreWalletHistoryAsync :: Kernel.PassiveWallet
192198
-> HD.HdRootId
193199
-> HeaderHash
194200
-> SlotId
195201
-> (Blund -> IO (Map HD.HdAccountId PrefilteredBlock, [TxMeta]))
196202
-> IO ()
197203
restoreWalletHistoryAsync wallet rootId target tgtSlot prefilter = do
198-
199-
say "sleeping 10 seconds before starting restoration, so that the tip has a chance to move"
200-
pause 10
201-
202-
-- TODO (@mn): should filter genesis utxo for the first wallet
203-
withNode (getFirstGenesisBlockHash >>= getBlock) >>= \case
204-
Nothing -> say "failed to find genesis block's successor!!" >> finish
205-
Just gbs -> restore (headerHash gbs) NoTimingData
206-
204+
-- 'getFirstGenesisBlockHash' is confusingly named: it returns the hash of
205+
-- the first block /after/ the genesis block.
206+
startingPoint <- withNode $ getFirstGenesisBlockHash
207+
restore startingPoint NoTimingData
207208
where
209+
wId :: WalletId
208210
wId = WalletIdHdRnd rootId
209-
pause = when True . threadDelay . (* 1000000)
210-
211-
say = (wallet ^. walletLogMessage) Debug . ("mnoonan: " <>)
212211

213212
-- Process the restoration of the block with the given 'HeaderHash'.
214-
-- The (UTCTime, Int) pair is used t
215213
restore :: HeaderHash -> TimingData -> IO ()
216214
restore hh timing = do
217-
218-
-- Increment our timing counter, producing an average rate
219-
-- every 5 blocks.
215+
-- Updating the average rate every 5 blocks.
220216
(rate, timing') <- tickTiming 5 timing
221217

222218
-- Update each account's historical checkpoints
223-
(block, undo) <- withNode ((,) <$> getBlock hh <*> getUndo hh)
224-
225-
whenJust ((,) <$> block <*> undo) $ \blund ->
226-
whenRight (fst blund) $ \mb -> do
227-
228-
-- Gather the information we will need to decide if we are within K blocks of the tip.
229-
slotCount <- getSlotCount (wallet ^. walletNode)
230-
let flat = flattenSlotIdExplicit slotCount
231-
232-
-- Filter the blocks by account
233-
(prefilteredBlocks, txMetas) <- prefilter blund
234-
235-
let slotId = mb ^. mainBlockSlot
236-
k <- getSecurityParameter (wallet ^. walletNode)
237-
ctxt <- withNodeState (wallet ^. walletNode) $ \_lock ->
238-
mainBlockContext mb
239-
mErr <- update (wallet ^. wallets) $
240-
ApplyHistoricalBlock k ctxt prefilteredBlocks
241-
242-
case mErr of
243-
Left err -> error $ "restore: unexpected error during applyHistoricalBlock: " <> pretty err
244-
Right () -> return ()
245-
246-
-- Update our progress
247-
let blockPerSec = MeasuredIn . BlockCount . perSecond <$> rate
248-
throughputUpdate = maybe identity (set wriThroughput) blockPerSec
249-
250-
updateRestorationInfo wallet wId ( (wriCurrentSlot .~ flat slotId)
251-
. (wriTargetSlot .~ flat tgtSlot)
252-
. throughputUpdate )
253-
254-
-- Store the TxMetas
255-
forM_ txMetas (putTxMeta (wallet ^. walletMeta))
256-
257-
-- MN TEMPORARY: slow your roll! Add an artificial 5 second delay whenever
258-
-- the throughput rate was updated, so we can look for it in the `wallets`
259-
-- endpoint results.
260-
case rate of
261-
Nothing -> return ()
262-
Just _ -> pause 5
219+
block <- getBlockOrThrow hh
220+
221+
-- Skip EBBs
222+
whenRight block $ \mb -> do
223+
-- Filter the blocks by account
224+
blund <- (Right mb, ) <$> getUndoOrThrow hh
225+
(prefilteredBlocks, txMetas) <- prefilter blund
226+
227+
-- Apply the block
228+
k <- getSecurityParameter (wallet ^. walletNode)
229+
ctxt <- withNode $ mainBlockContext mb
230+
mErr <- update (wallet ^. wallets) $
231+
ApplyHistoricalBlock k ctxt prefilteredBlocks
232+
case mErr of
233+
Left err -> throwM $ RestorationApplyHistoricalBlockFailed err
234+
Right () -> return ()
235+
236+
-- Update our progress
237+
slotCount <- getSlotCount (wallet ^. walletNode)
238+
let flat = flattenSlotIdExplicit slotCount
239+
blockPerSec = MeasuredIn . BlockCount . perSecond <$> rate
240+
throughputUpdate = maybe identity (set wriThroughput) blockPerSec
241+
slotId = mb ^. mainBlockSlot
242+
updateRestorationInfo wallet wId ( (wriCurrentSlot .~ flat slotId)
243+
. (wriTargetSlot .~ flat tgtSlot)
244+
. throughputUpdate )
245+
246+
-- Store the TxMetas
247+
forM_ txMetas (putTxMeta (wallet ^. walletMeta))
263248

264249
-- Get the next block from the node and recurse.
265-
if target == hh
266-
then say "made it to target!" >> finish
267-
else nextBlock hh >>= \case
268-
Nothing -> say "failed to find next block!!" >> finish
250+
if target == hh then
251+
finish
252+
else
253+
nextBlock hh >>= \case
254+
Nothing -> throwM $ RestorationFinishUnreachable target hh
269255
Just header' -> restore header' timing'
270256

271-
-- Step forward to the successor of the given block.
272-
nextBlock :: HeaderHash -> IO (Maybe HeaderHash)
273-
nextBlock hh = withNode (resolveForwardLink hh)
274-
275257
-- TODO (@mn): probably should use some kind of bracket to ensure this cleanup happens.
276258
finish :: IO ()
277259
finish = do
278260
k <- getSecurityParameter (wallet ^. walletNode)
279261
update (wallet ^. wallets) $ RestorationComplete k rootId
280262
modifyMVar_ (wallet ^. walletRestorationTask) (pure . M.delete wId)
281263

264+
-- Step forward to the successor of the given block.
265+
nextBlock :: HeaderHash -> IO (Maybe HeaderHash)
266+
nextBlock hh = withNode (resolveForwardLink hh)
267+
268+
-- Get a block
269+
getBlockOrThrow :: HeaderHash -> IO Block
270+
getBlockOrThrow hh = do
271+
mBlock <- withNode $ getBlock hh
272+
case mBlock of
273+
Nothing -> throwM $ RestorationBlockNotFound hh
274+
Just b -> return b
275+
276+
-- Get undo for a mainblock
277+
-- NOTE: We use this undo information only for input resolution.
278+
getUndoOrThrow :: HeaderHash -> IO Undo
279+
getUndoOrThrow hh = do
280+
mBlock <- withNode $ getUndo hh
281+
case mBlock of
282+
Nothing -> throwM $ RestorationUndoNotFound hh
283+
Just b -> return b
284+
282285
withNode :: forall a. (NodeConstraints => WithNodeState IO a) -> IO a
283286
withNode action = withNodeState (wallet ^. walletNode) (\_lock -> action)
284287

@@ -290,6 +293,10 @@ updateRestorationInfo :: Kernel.PassiveWallet
290293
updateRestorationInfo wallet wId upd =
291294
modifyMVar_ (wallet ^. walletRestorationTask) (pure . M.adjust upd wId)
292295

296+
{-------------------------------------------------------------------------------
297+
Timing information (for throughput calculations)
298+
-------------------------------------------------------------------------------}
299+
293300
-- | Keep track of how many events have happened since a given start time.
294301
data TimingData
295302
= NoTimingData
@@ -312,3 +319,29 @@ tickTiming k' (Timing k start)
312319
-- | Convert a rate to a number of events per second.
313320
perSecond :: Rate -> Word64
314321
perSecond (Rate n dt) = fromInteger $ round (toRational n / toRational dt)
322+
323+
{-------------------------------------------------------------------------------
324+
Exceptions
325+
-------------------------------------------------------------------------------}
326+
327+
-- | Exception during restoration
328+
data RestorationException =
329+
RestorationBlockNotFound HeaderHash
330+
| RestorationUndoNotFound HeaderHash
331+
| RestorationApplyHistoricalBlockFailed Spec.ApplyBlockFailed
332+
| RestorationFinishUnreachable HeaderHash HeaderHash
333+
334+
instance Buildable RestorationException where
335+
build (RestorationBlockNotFound hash) =
336+
bprint ("RestorationBlockNotFound " % build) hash
337+
build (RestorationUndoNotFound hash) =
338+
bprint ("RestorationUndoNotFound " % build) hash
339+
build (RestorationApplyHistoricalBlockFailed err) =
340+
bprint ("RestorationApplyHistoricalBlockFailed " % build) err
341+
build (RestorationFinishUnreachable target final) =
342+
bprint ("RestorationFinishUnreachable " % build % " " % build) target final
343+
344+
instance Show RestorationException where
345+
show = formatToString build
346+
347+
instance Exception RestorationException

0 commit comments

Comments
 (0)