@@ -14,8 +14,7 @@ module Pos.Diffusion.Full.Block
14
14
15
15
import Universum
16
16
17
- import Control.Concurrent (threadDelay )
18
- import Control.Concurrent.Async (cancel )
17
+ import qualified Control.Concurrent.Async as Async
19
18
import qualified Control.Concurrent.STM as Conc
20
19
import Control.Exception (Exception (.. ), throwIO )
21
20
import Control.Lens (to )
@@ -55,7 +54,8 @@ import Pos.Infra.Communication.Protocol (Conversation (..),
55
54
MkListeners (.. ), MsgType (.. ), NodeId , Origin (.. ),
56
55
OutSpecs , constantListeners , recvLimited ,
57
56
waitForConversations , waitForDequeues )
58
- import Pos.Infra.Diffusion.Types (DiffusionHealth (.. ))
57
+ import Pos.Infra.Diffusion.Types (DiffusionHealth (.. ),
58
+ StreamBlocks (.. ))
59
59
import Pos.Infra.Network.Types (Bucket )
60
60
import Pos.Infra.Util.TimeWarp (nodeIdToAddress )
61
61
import Pos.Logic.Types (Logic )
@@ -281,78 +281,28 @@ getBlocks logTrace logic recoveryHeadersMessage enqueue nodeId tipHeaderHash che
281
281
data StreamEntry = StreamEnd | StreamBlock ! Block
282
282
283
283
-- | Stream some blocks from the network.
284
- -- Returns Nothing if streaming is disabled by the client or not supported by the peer.
284
+ -- If streaming is not supported by the client or peer, you get 'Nothing'. We
285
+ -- don't fall back to batching because we can't: that method requires having
286
+ -- all of the header hashes for the blocks you desire.
285
287
streamBlocks
286
288
:: forall t .
287
289
Trace IO (Severity , Text )
288
290
-> Maybe DiffusionHealth
289
291
-> Logic IO
290
- -> Word32
292
+ -> Word32 -- ^ Size of stream window. 0 implies 'Nothing' is returned.
291
293
-> EnqueueMsg
292
294
-> NodeId
293
295
-> HeaderHash
294
296
-> [HeaderHash ]
295
- -> ([ Block ] -> IO t )
297
+ -> StreamBlocks Block IO t
296
298
-> IO (Maybe t )
297
- streamBlocks _ _ _ 0 _ _ _ _ _ = return Nothing -- Fallback to batch mode
298
- streamBlocks logTrace smM logic streamWindow enqueue nodeId tipHeader checkpoints k = do
299
- blockChan <- atomically $ Conc. newTBQueue $ fromIntegral streamWindow
300
- let batchSize = min 64 streamWindow
301
- fallBack <- atomically $ Conc. newTVar False
302
- requestVar <- requestBlocks fallBack blockChan
303
- r <- processBlocks batchSize 0 [] blockChan `finally` (atomically $ do
304
- status <- Conc. readTVar requestVar
305
- case status of
306
- OQ. PacketAborted -> pure (pure () )
307
- OQ. PacketEnqueued -> do
308
- Conc. writeTVar requestVar OQ. PacketAborted
309
- pure (pure () )
310
- OQ. PacketDequeued asyncIO -> pure (cancel asyncIO))
311
- r' <- atomically $ Conc. readTVar fallBack
312
- if r' then pure Nothing
313
- else pure $ Just r
299
+ streamBlocks _ _ _ 0 _ _ _ _ _ =
300
+ return Nothing -- Fallback to batch mode
301
+ streamBlocks logTrace smM logic streamWindow enqueue nodeId tipHeader checkpoints streamBlocksK =
302
+ requestBlocks >>= Async. wait
314
303
where
315
304
316
- processBlocks :: Word32 -> Word32 -> [Block ] -> Conc. TBQueue StreamEntry -> IO t
317
- processBlocks batchSize ! n ! blocks blockChan = do
318
- streamEntry <- atomically $ Conc. readTBQueue blockChan
319
- case streamEntry of
320
- StreamEnd -> k blocks
321
- StreamBlock block -> do
322
- let n' = n + 1
323
- when (n' `mod` 256 == 0 ) $
324
- traceWith logTrace (Debug ,
325
- sformat (" Read block " % shortHashF% " difficulty " % int) (headerHash block)
326
- (block ^. difficultyL))
327
- case smM of
328
- Nothing -> pure ()
329
- Just sm -> liftIO $ Gauge. dec $ dhStreamWriteQueue sm
330
-
331
- if n' `mod` batchSize == 0
332
- then do
333
- _ <- k (block : blocks)
334
- processBlocks batchSize n' [] blockChan
335
- else
336
- processBlocks batchSize n' (block : blocks) blockChan
337
-
338
- writeStreamEnd :: Conc. TBQueue StreamEntry -> IO ()
339
- writeStreamEnd blockChan = writeBlock 1024 blockChan StreamEnd
340
-
341
- -- It is possible that the reader of the TBQueue stops unexpectedly which
342
- -- means that we we will have to use a timeout instead of blocking forever
343
- -- while attempting to write to a full queue.
344
- writeBlock :: Int -> Conc. TBQueue StreamEntry -> StreamEntry -> IO ()
345
- writeBlock delay _ _ | delay >= 4000000 = do
346
- let msg = " Error write timeout to local reader"
347
- traceWith logTrace (Warning , msg)
348
- throwM $ DialogUnexpected msg
349
- writeBlock delay blockChan b = do
350
- isFull <- atomically $ Conc. isFullTBQueue blockChan
351
- if isFull
352
- then do
353
- threadDelay delay
354
- writeBlock (delay * 2 ) blockChan b
355
- else atomically $ Conc. writeTBQueue blockChan b
305
+ batchSize = min 64 streamWindow
356
306
357
307
mkStreamStart :: [HeaderHash ] -> HeaderHash -> MsgStream
358
308
mkStreamStart chain wantedBlock =
@@ -362,49 +312,62 @@ streamBlocks logTrace smM logic streamWindow enqueue nodeId tipHeader checkpoint
362
312
, mssWindow = streamWindow
363
313
}
364
314
365
- requestBlocks :: Conc. TVar Bool -> Conc. TBQueue StreamEntry -> IO (Conc. TVar (OQ. PacketStatus () ))
366
- requestBlocks fallBack blockChan = do
367
- convMap <- enqueue (MsgRequestBlocks (S. singleton nodeId))
368
- (\ _ _ -> (Conversation $ \ it -> requestBlocksConversation blockChan it `onException` writeStreamEnd blockChan) :|
369
- [(Conversation $ \ it -> requestBatch fallBack blockChan it `finally` writeStreamEnd blockChan)]
370
- )
315
+ -- Enqueue a conversation which will attempt to stream.
316
+ -- This returns when the conversation is dequeued, or throws an exception
317
+ -- in case it's aborted or is not enqueued.
318
+ requestBlocks :: IO (Async. Async (Maybe t ))
319
+ requestBlocks = do
320
+ convMap <- enqueue
321
+ (MsgRequestBlocks (S. singleton nodeId))
322
+ (\ _ _ -> (Conversation $ streamBlocksConversation) :|
323
+ [(Conversation $ batchConversation)]
324
+ )
325
+ -- Outbound queue guarantees that the map is either size 0 or 1, since
326
+ -- 'S.singleton nodeId' was given to the enqueue.
371
327
case M. lookup nodeId convMap of
372
- Just tvar -> pure tvar
328
+ Just tvar -> atomically $ do
329
+ pStatus <- Conc. readTVar tvar
330
+ case pStatus of
331
+ OQ. PacketEnqueued -> Conc. retry
332
+ -- Somebody else arborted our call; nothing to do but
333
+ -- throw.
334
+ OQ. PacketAborted -> Conc. throwSTM $ DialogUnexpected $ " streamBlocks: aborted"
335
+ OQ. PacketDequeued streamThread -> pure streamThread
373
336
-- FIXME shouldn't have to deal with this.
374
337
-- One possible solution: do the block request in response to an
375
338
-- unsolicited header, so that's it's all done in one conversation,
376
339
-- and so there's no need to even track the 'nodeId'.
377
- Nothing -> throwM $ DialogUnexpected $ " requestBlocks did not contact given peer"
378
-
379
- requestBatch
380
- :: Conc. TVar Bool
381
- -> Conc. TBQueue StreamEntry
382
- -> ConversationActions MsgGetBlocks MsgBlock
383
- -> IO ()
384
- requestBatch fallBack _ _ = do
385
- -- The peer doesn't support streaming, we need to fall back to batching but
386
- -- the current conversation is unusable since there is no way for us to learn
387
- -- which blocks we shall fetch.
388
- -- We will always have room to write a singel StreamEnd so there is no need to
389
- -- differentiate between normal execution and when we get an expection.
390
- atomically $ writeTVar fallBack True
391
- return ()
392
-
393
- requestBlocksConversation
394
- :: Conc. TBQueue StreamEntry
395
- -> ConversationActions MsgStream MsgStreamBlock
396
- -> IO ()
397
- requestBlocksConversation blockChan conv = do
340
+ Nothing -> throwIO $ DialogUnexpected $ " streamBlocks: did not contact given peer"
341
+
342
+ -- The peer doesn't support streaming, we need to fall back to batching but
343
+ -- the current conversation is unusable since there is no way for us to learn
344
+ -- which blocks we shall fetch.
345
+ batchConversation
346
+ :: ConversationActions MsgGetBlocks MsgBlock
347
+ -> IO (Maybe t )
348
+ batchConversation _ = pure Nothing
349
+
350
+ streamBlocksConversation
351
+ :: ConversationActions MsgStream MsgStreamBlock
352
+ -> IO (Maybe t )
353
+ streamBlocksConversation conv = do
398
354
let newestHash = headerHash tipHeader
399
355
traceWith logTrace (Debug ,
400
356
sformat (" streamBlocks: Requesting stream of blocks from " % listJson% " to " % shortHashF)
401
357
checkpoints
402
358
newestHash)
403
359
send conv $ mkStreamStart checkpoints newestHash
404
360
bvd <- Logic. getAdoptedBVData logic
405
- retrieveBlocks bvd blockChan conv streamWindow
406
- atomically $ Conc. writeTBQueue blockChan StreamEnd
407
- return ()
361
+ -- Two threads are used here: one to pull in blocks, and one to
362
+ -- call into the application 'StreamBlocks' value. The reason:
363
+ -- the latter could do a lot of work for each batch, so having another
364
+ -- thread continually pulling in with a buffer in the middle will
365
+ -- smooth the traffic.
366
+ blockChan <- atomically $ Conc. newTBQueue $ fromIntegral streamWindow
367
+ (_, b) <- Async. concurrently
368
+ (retrieveBlocks bvd blockChan conv streamWindow)
369
+ (processBlocks 0 [] blockChan streamBlocksK)
370
+ pure $ Just b
408
371
409
372
halfStreamWindow = max 1 $ streamWindow `div` 2
410
373
@@ -426,15 +389,14 @@ streamBlocks logTrace smM logic streamWindow enqueue nodeId tipHeader checkpoint
426
389
else return $ window - 1
427
390
block <- retrieveBlock bvd conv
428
391
case block of
429
- MsgStreamNoBlock t -> do
430
- let msg = sformat (" MsgStreamNoBlock " % stext) t
431
- traceWith logTrace (Warning , msg)
392
+ MsgStreamNoBlock e -> do
393
+ let msg = sformat (" MsgStreamNoBlock " % stext) e
394
+ traceWith logTrace (Error , msg)
432
395
throwM $ DialogUnexpected msg
433
396
MsgStreamEnd -> do
397
+ atomically $ Conc. writeTBQueue blockChan StreamEnd
434
398
traceWith logTrace (Debug , sformat (" Streaming done client-side for node" % build) nodeId)
435
- return ()
436
399
MsgStreamBlock b -> do
437
- -- traceWith logTrace (Debug, sformat ("Read block "%shortHashF) (headerHash b))
438
400
atomically $ Conc. writeTBQueue blockChan (StreamBlock b)
439
401
case smM of
440
402
Nothing -> pure ()
@@ -452,10 +414,44 @@ streamBlocks logTrace smM logic streamWindow enqueue nodeId tipHeader checkpoint
452
414
case blockE of
453
415
Nothing -> do
454
416
let msg = sformat (" Error retrieving blocks from peer " % build) nodeId
455
- traceWith logTrace (Warning , msg)
417
+ traceWith logTrace (Error , msg)
456
418
throwM $ DialogUnexpected msg
457
419
Just block -> return block
458
420
421
+ processBlocks
422
+ :: Word32
423
+ -> [Block ]
424
+ -> Conc. TBQueue StreamEntry
425
+ -> StreamBlocks Block IO t
426
+ -> IO t
427
+ processBlocks n ! blocks blockChan k = do
428
+ streamEntry <- atomically $ Conc. readTBQueue blockChan
429
+ case streamEntry of
430
+ StreamEnd -> case blocks of
431
+ [] -> streamBlocksDone k
432
+ (blk: blks) -> do
433
+ k' <- streamBlocksMore k (blk :| blks)
434
+ streamBlocksDone k'
435
+ StreamBlock block -> do
436
+ -- FIXME this logging stuff should go into the particular
437
+ -- 'StreamBlocks' value rather than here.
438
+ let n' = n + 1
439
+ when (n' `mod` 256 == 0 ) $
440
+ traceWith logTrace (Debug ,
441
+ sformat (" Read block " % shortHashF% " difficulty " % int) (headerHash block)
442
+ (block ^. difficultyL))
443
+ case smM of
444
+ Nothing -> pure ()
445
+ Just sm -> liftIO $ Gauge. dec $ dhStreamWriteQueue sm
446
+
447
+ if n' `mod` batchSize == 0
448
+ then do
449
+ k' <- streamBlocksMore k (block :| blocks)
450
+ processBlocks n' [] blockChan k'
451
+ else
452
+ processBlocks n' (block : blocks) blockChan k
453
+
454
+
459
455
requestTip
460
456
:: Trace IO (Severity , Text )
461
457
-> Logic IO
0 commit comments