11{-# LANGUAGE BangPatterns #-}
22{-# LANGUAGE LambdaCase #-}
3+ {-# LANGUAGE MultiWayIf #-}
34{-# LANGUAGE NamedFieldPuns #-}
45{-# LANGUAGE OverloadedStrings #-}
56{-# LANGUAGE ScopedTypeVariables #-}
@@ -24,8 +25,8 @@ import Cardano.Tracer.Handlers.RTView.UI.HTML.NoNodes
2425import Cardano.Tracer.Handlers.RTView.UI.Types
2526import Cardano.Tracer.Handlers.RTView.UI.Utils
2627import Cardano.Tracer.Handlers.RTView.Update.NodeInfo
27- import Cardano.Tracer.Handlers.Utils
2828import Cardano.Tracer.Handlers.RTView.Utils
29+ import Cardano.Tracer.Handlers.Utils
2930import Cardano.Tracer.Types
3031import Cardano.Tracer.Utils
3132
@@ -36,9 +37,9 @@ import Control.Monad.Extra (whenJust, whenJustM, whenM)
3637import Data.List (find )
3738import Data.List.NonEmpty (NonEmpty )
3839import qualified Data.Map.Strict as M
39- import Data.Maybe (fromMaybe )
4040import Data.Set (Set , (\\) )
4141import qualified Data.Set as S
42+ import Data.Text (isInfixOf )
4243import qualified Data.Text as T
4344import Data.Text.Read (decimal , double )
4445import Data.Time.Calendar (diffDays )
@@ -253,7 +254,7 @@ setBlockReplayProgress connected acceptedMetrics = do
253254 forM_ connected $ \ nodeId ->
254255 whenJust (M. lookup nodeId allMetrics) $ \ (ekgStore, _) -> do
255256 metrics <- liftIO $ getListOfMetrics ekgStore
256- whenJust (lookup " ChainDB.BlockReplayProgress " metrics) $ \ metricValue ->
257+ whenJust (find ( \ (x, _) -> " blockReplayProgress " `isInfixOf` x) metrics) $ \ (_, metricValue) ->
257258 updateBlockReplayProgress nodeId metricValue
258259 where
259260 updateBlockReplayProgress (NodeId anId) mValue =
@@ -275,10 +276,7 @@ setProducerMode connected acceptedMetrics = do
275276 forM_ connected $ \ nodeId@ (NodeId anId) ->
276277 whenJust (M. lookup nodeId allMetrics) $ \ (ekgStore, _) ->
277278 forMM_ (liftIO $ getListOfMetrics ekgStore) $ \ (mName, _) ->
278- case mName of
279- " Forge.NodeIsLeader" -> showProducerMode anId
280- " Forge.NodeIsLeaderNum" -> showProducerMode anId
281- _ -> return ()
279+ when (" nodeIsLeader" `isInfixOf` mName) $ showProducerMode anId
282280 where
283281 -- The presence of these metrics is a proof that this node is
284282 -- configured as a producer, so display corresponding icon.
@@ -297,16 +295,16 @@ setLeadershipStats connected displayed acceptedMetrics = do
297295 whenJust (M. lookup nodeId allMetrics) $ \ (ekgStore, _) -> do
298296 metrics <- liftIO $ getListOfMetrics ekgStore
299297 forM_ metrics $ \ (mName, mValue) ->
300- case mName of
298+ if
301299 -- How many times this node was a leader.
302- " Forge.NodeIsLeaderNum " -> setDisplayedValue nodeId displayed (anId <> " __node-leadership" ) mValue
300+ | " nodeIsLeader " `isInfixOf` mName -> setDisplayedValue nodeId displayed (anId <> " __node-leadership" ) mValue
303301 -- How many blocks were forged by this node.
304- " Forge.BlocksForgedNum " -> setDisplayedValue nodeId displayed (anId <> " __node-forged-blocks" ) mValue
302+ | " blocksForged " `isInfixOf` mName -> setDisplayedValue nodeId displayed (anId <> " __node-forged-blocks" ) mValue
305303 -- How many times this node could not forge.
306- " Forge.NodeCannotForgeNum " -> setDisplayedValue nodeId displayed (anId <> " __node-cannot-forge" ) mValue
304+ | " nodeCannotForge " `isInfixOf` mName -> setDisplayedValue nodeId displayed (anId <> " __node-cannot-forge" ) mValue
307305 -- How many slots were missed in this node.
308- " Forge.SlotsMissed " -> setDisplayedValue nodeId displayed (anId <> " __node-missed-slots" ) mValue
309- _ -> return ()
306+ | " slotsMissed " `isInfixOf` mName -> setDisplayedValue nodeId displayed (anId <> " __node-missed-slots" ) mValue
307+ | otherwise -> return ()
310308
311309setEraEpochInfo
312310 :: Set NodeId
@@ -322,7 +320,7 @@ setEraEpochInfo connected displayed acceptedMetrics nodesEraSettings = do
322320 case M. lookup nodeId allMetrics of
323321 Just (ekgStore, _) -> do
324322 metrics <- liftIO $ getListOfMetrics ekgStore
325- return $ fromMaybe " " $ lookup " ChainDB.Epoch " metrics
323+ return $ maybe " " snd (find ( \ (x, _) -> " epoch " `isInfixOf` x) metrics)
326324 Nothing -> return " "
327325 unless (T. null epochS) $
328326 setDisplayedValue nodeId displayed (anId <> " __node-epoch-num" ) epochS
@@ -377,7 +375,7 @@ setEraEpochInfo connected displayed acceptedMetrics nodesEraSettings = do
377375 updateEpochSlotProgress EraSettings {esEpochLength} nodeId@ (NodeId anId) allMetrics =
378376 whenJust (M. lookup nodeId allMetrics) $ \ (ekgStore, _) -> do
379377 metrics <- liftIO $ getListOfMetrics ekgStore
380- whenJust (lookup " ChainDB.SlotInEpoch " metrics) $ \ slotInEpochS ->
378+ whenJust (find ( \ (x, _) -> " slotInEpoch " `isInfixOf` x) metrics) $ \ (_, slotInEpochS) ->
381379 case decimal slotInEpochS of
382380 Left _ -> return ()
383381 Right (slotInEpoch :: Int , _ ) -> do
0 commit comments