8
8
{-# LANGUAGE TypeFamilies #-}
9
9
{-# LANGUAGE TypeOperators #-}
10
10
{-# LANGUAGE UndecidableInstances #-}
11
+ {-# LANGUAGE ViewPatterns #-}
11
12
12
13
{-# OPTIONS_GHC -Wno-orphans #-}
13
- {-# LANGUAGE InstanceSigs #-}
14
14
15
15
module Cardano.Node.Tracing.Tracers.Consensus
16
16
(
@@ -518,19 +518,19 @@ instance MetaTrace (TraceChainSyncServerEvent blk) where
518
518
--------------------------------------------------------------------------------
519
519
520
520
data CdfCounter = CdfCounter {
521
- limit :: ! Int64
521
+ limit :: ! Double
522
522
, counter :: ! Int64
523
523
}
524
524
525
- decCdf :: a -> CdfCounter -> CdfCounter
526
- decCdf _v cdf = cdf {counter = counter cdf - 1 }
527
-
528
- incCdf :: Ord a => Num a => a -> CdfCounter -> CdfCounter
529
- incCdf v cdf =
530
- if v < fromIntegral (limit cdf)
531
- then cdf {counter = counter cdf + 1 }
532
- else cdf
525
+ decCdf :: Double -> CdfCounter -> CdfCounter
526
+ decCdf v cdf@ CdfCounter {.. }
527
+ | v < limit = cdf {counter = counter - 1 }
528
+ | otherwise = cdf
533
529
530
+ incCdf :: Double -> CdfCounter -> CdfCounter
531
+ incCdf v cdf@ CdfCounter {.. }
532
+ | v < limit = cdf {counter = counter + 1 }
533
+ | otherwise = cdf
534
534
535
535
data ClientMetrics = ClientMetrics {
536
536
cmSlotMap :: IntPSQ Word64 NominalDiffTime
@@ -545,31 +545,22 @@ data ClientMetrics = ClientMetrics {
545
545
546
546
instance LogFormatting ClientMetrics where
547
547
forMachine _dtal _ = mempty
548
+ asMetrics ClientMetrics {cmTraceIt = False } = []
548
549
asMetrics ClientMetrics {.. } =
549
- if cmTraceIt
550
- then
551
- let size = Pq. size cmSlotMap
552
- msgs =
553
- [ DoubleM " blockfetchclient.blockdelay" cmDelay
554
- , IntM " blockfetchclient.blocksize" (fromIntegral cmBlockSize)
555
- ]
556
- <> if cmTraceVars
557
- then cdfMetric " blockfetchclient.blockdelay.cdfOne" cmCdf1sVar
558
- <> cdfMetric " blockfetchclient.blockdelay.cdfThree" cmCdf3sVar
559
- <> cdfMetric " blockfetchclient.blockdelay.cdfFive" cmCdf5sVar
560
- <> lateBlockMetric cmDelay
561
- else []
562
- where
563
- cdfMetric name var =
564
- [ DoubleM name (fromIntegral (counter var) / fromIntegral size)
565
- ]
566
-
567
- lateBlockMetric delay =
568
- [ CounterM " blockfetchclient.lateblocks" Nothing
569
- | delay > 5
570
- ]
571
- in msgs
572
- else []
550
+ [ DoubleM " blockfetchclient.blockdelay" cmDelay
551
+ , IntM " blockfetchclient.blocksize" (fromIntegral cmBlockSize)
552
+ ]
553
+ ++ if cmTraceVars
554
+ then [ cdfMetric " blockfetchclient.blockdelay.cdfOne" cmCdf1sVar
555
+ , cdfMetric " blockfetchclient.blockdelay.cdfThree" cmCdf3sVar
556
+ , cdfMetric " blockfetchclient.blockdelay.cdfFive" cmCdf5sVar
557
+ ]
558
+ ++ lateBlockMetric
559
+ else []
560
+ where
561
+ size = Pq. size cmSlotMap
562
+ cdfMetric name var = DoubleM name (fromIntegral (counter var) / fromIntegral size)
563
+ lateBlockMetric = [ CounterM " blockfetchclient.lateblocks" Nothing | cmDelay > 5 ]
573
564
574
565
instance MetaTrace ClientMetrics where
575
566
namespaceFor _ = Namespace [] [" ClientMetrics" ]
@@ -606,70 +597,57 @@ calculateBlockFetchClientMetrics ::
606
597
ClientMetrics
607
598
-> LoggingContext
608
599
-> BlockFetch. TraceLabelPeer peer (BlockFetch. TraceFetchClientState header )
609
- -> IO ClientMetrics
600
+ -> ClientMetrics
610
601
calculateBlockFetchClientMetrics cm@ ClientMetrics {.. } _lc
611
602
(TraceLabelPeer _ (BlockFetch. CompletedBlockFetch p _ _ _ forgeDelay blockSize)) =
612
603
case pointSlot p of
613
- Origin -> pure cm {cmTraceIt = False } -- Nothing to do for Origin
604
+ Origin -> nothingToDo
614
605
At (SlotNo slotNo) ->
615
- if Pq. null cmSlotMap && forgeDelay > 20
616
- then pure cm {cmTraceIt = False } -- During startup wait until we are in sync
606
+ if Pq. null cmSlotMap && forgeDelay > 20 -- During startup wait until we are in sync
607
+ then nothingToDo
617
608
else processSlot slotNo
618
609
where
619
- processSlot slotNo =
620
- case Pq. lookup (fromIntegral slotNo) cmSlotMap of
621
- Just _ -> pure cm {cmTraceIt = False } -- Duplicate, only track the first
622
- Nothing -> let slotMap' = Pq. insert (fromIntegral slotNo) slotNo forgeDelay cmSlotMap
623
- in if Pq. size slotMap' > 1080
624
- then trimSlotMap slotMap' slotNo
625
- else updateMetrics slotMap' slotNo
626
-
627
- trimSlotMap slotMap' slotNo =
628
- case Pq. minView slotMap' of
629
- Nothing -> pure cm {cmTraceIt = False } -- Error: Just inserted element
630
- Just (_, minSlotNo, minDelay, slotMap'') ->
631
- if minSlotNo == slotNo
632
- then pure cm { cmTraceIt = False , cmSlotMap = slotMap' }
633
- else let (cdf1sVar, cdf3sVar, cdf5sVar) = updateCDFs minDelay forgeDelay
634
- in pure cm
635
- { cmCdf1sVar = cdf1sVar
636
- , cmCdf3sVar = cdf3sVar
637
- , cmCdf5sVar = cdf5sVar
638
- , cmDelay = realToFrac forgeDelay
639
- , cmBlockSize = getSizeInBytes blockSize
640
- , cmTraceVars = True
641
- , cmTraceIt = True
642
- , cmSlotMap = slotMap'' }
643
-
644
- updateMetrics slotMap' _slotNo =
645
- let (cdf1sVar, cdf3sVar, cdf5sVar) = updateCDFs 0 forgeDelay
646
- in if Pq. size slotMap' >= 45
647
- then pure cm
648
- { cmCdf1sVar = cdf1sVar
649
- , cmCdf3sVar = cdf3sVar
650
- , cmCdf5sVar = cdf5sVar
651
- , cmDelay = realToFrac forgeDelay
652
- , cmBlockSize = getSizeInBytes blockSize
653
- , cmTraceVars = True
654
- , cmTraceIt = True
655
- , cmSlotMap = slotMap' }
656
- else pure cm
657
- { cmCdf1sVar = cdf1sVar
658
- , cmCdf3sVar = cdf3sVar
659
- , cmCdf5sVar = cdf5sVar
660
- , cmDelay = realToFrac forgeDelay
661
- , cmBlockSize = getSizeInBytes blockSize
662
- , cmTraceVars = False
663
- , cmTraceIt = True
664
- , cmSlotMap = slotMap' }
665
-
666
- updateCDFs minDelay forgeDelay' =
667
- ( incCdf forgeDelay' (decCdf minDelay cmCdf1sVar)
668
- , incCdf forgeDelay' (decCdf minDelay cmCdf3sVar)
669
- , incCdf forgeDelay' (decCdf minDelay cmCdf5sVar) )
670
-
671
-
672
- calculateBlockFetchClientMetrics cm _lc _ = pure cm
610
+ nothingToDo = cm {cmTraceIt = False }
611
+ delay = realToFrac forgeDelay
612
+
613
+ processSlot slotNo
614
+ | fromIntegral slotNo `Pq.member` cmSlotMap = nothingToDo -- Duplicate, only track the first
615
+ | otherwise =
616
+ let slotMap' = Pq. insert (fromIntegral slotNo) slotNo forgeDelay cmSlotMap
617
+ in if Pq. size slotMap' > 1080 -- TODO: k/2, should come from config file
618
+ then trimSlotMap slotMap' slotNo
619
+ else updateMetrics slotMap'
620
+
621
+ trimSlotMap slotMap' slotNo = case Pq. minView slotMap' of
622
+ Nothing -> nothingToDo -- Error: Just inserted element
623
+ Just (_, minSlotNo, realToFrac -> minDelay, slotMap'')
624
+ | minSlotNo == slotNo -> nothingToDo
625
+ | otherwise -> cm
626
+ { cmCdf1sVar = adjust minDelay cmCdf1sVar
627
+ , cmCdf3sVar = adjust minDelay cmCdf3sVar
628
+ , cmCdf5sVar = adjust minDelay cmCdf5sVar
629
+ , cmDelay = delay
630
+ , cmBlockSize = getSizeInBytes blockSize
631
+ , cmTraceVars = True
632
+ , cmTraceIt = True
633
+ , cmSlotMap = slotMap''
634
+ }
635
+
636
+ updateMetrics slotMap' = cm
637
+ { cmCdf1sVar = update cmCdf1sVar
638
+ , cmCdf3sVar = update cmCdf3sVar
639
+ , cmCdf5sVar = update cmCdf5sVar
640
+ , cmDelay = delay
641
+ , cmBlockSize = getSizeInBytes blockSize
642
+ , cmTraceVars = Pq. size slotMap' >= 45 -- wait until we have at least 45 samples before providing cdf estimates
643
+ , cmTraceIt = True
644
+ , cmSlotMap = slotMap'
645
+ }
646
+
647
+ update = incCdf delay
648
+ adjust d = update . decCdf d
649
+
650
+ calculateBlockFetchClientMetrics cm _lc _ = cm
673
651
674
652
675
653
--------------------------------------------------------------------------------
0 commit comments