diff --git a/cardano-node/src/Cardano/Node/Run.hs b/cardano-node/src/Cardano/Node/Run.hs
index 1f400705fdb..22f323f5471 100644
--- a/cardano-node/src/Cardano/Node/Run.hs
+++ b/cardano-node/src/Cardano/Node/Run.hs
@@ -3,6 +3,7 @@
{-# LANGUAGE DataKinds #-}
{-# LANGUAGE FlexibleContexts #-}
{-# LANGUAGE GADTs #-}
+{-# LANGUAGE LambdaCase #-}
{-# LANGUAGE NamedFieldPuns #-}
{-# LANGUAGE PackageImports #-}
{-# LANGUAGE ScopedTypeVariables #-}
@@ -200,6 +201,11 @@ handleNodeWithTracers cmdPc nc p networkMagic runP = do
networkMagic
nodeKernelData
p2pMode
+
+ startupInfo <- getStartupInfo nc p fp
+ mapM_ (traceWith $ startupTracer tracers) startupInfo
+ traceNodeStartupInfo (nodeStartupInfoTracer tracers) startupInfo
+
handleSimpleNode runP p2pMode tracers nc
(\nk -> do
setNodeKernel nodeKernelData nk
@@ -249,6 +255,17 @@ handleNodeWithTracers cmdPc nc p networkMagic runP = do
forM_ eLoggingLayer
shutdownLoggingLayer
+-- | Currently, we trace only 'ShelleyBased'-info which will be asked
+-- by 'cardano-tracer' service as a datapoint. It can be extended in the future.
+traceNodeStartupInfo
+ :: Tracer IO NodeStartupInfo
+ -> [StartupTrace blk]
+ -> IO ()
+traceNodeStartupInfo t startupTrace =
+ forM_ startupTrace $ \case
+ BIShelley (BasicInfoShelleyBased era _ sl el spkp) ->
+ traceWith t $ NodeStartupInfo era sl el spkp
+ _ -> return ()
logTracingVerbosity :: NodeConfiguration -> Tracer IO String -> IO ()
logTracingVerbosity nc tracer =
diff --git a/cardano-node/src/Cardano/Node/Startup.hs b/cardano-node/src/Cardano/Node/Startup.hs
index 01b5792b24f..3ed9d36f2e6 100644
--- a/cardano-node/src/Cardano/Node/Startup.hs
+++ b/cardano-node/src/Cardano/Node/Startup.hs
@@ -209,3 +209,25 @@ prepareNodeInfo ptcl (SomeConsensusProtocol whichP pForInfo) tc nodeStartTime =
case tcNodeName tc of
Just aName -> return aName
Nothing -> pack <$> getHostName
+
+-- | This information is taken from 'BasicInfoShelleyBased'. It is required for
+-- 'cardano-tracer' service (particularly, for RTView).
+data NodeStartupInfo = NodeStartupInfo {
+ suiEra :: Text
+ , suiSlotLength :: NominalDiffTime
+ , suiEpochLength :: Word64
+ , suiSlotsPerKESPeriod :: Word64
+ } deriving (Eq, Generic, ToJSON, FromJSON, Show)
+
+docNodeStartupInfoTraceEvent :: Documented NodeStartupInfo
+docNodeStartupInfoTraceEvent = Documented
+ [ DocMsg
+ ["NodeStartupInfo"]
+ []
+ "Startup information about this node, required for RTView\
+ \\n\
+ \\n _suiEra_: Name of the current era. \
+ \\n _suiSlotLength_: Slot length, in seconds. \
+ \\n _suiEpochLength_: Epoch length, in slots. \
+ \\n _suiSlotsPerKESPeriod_: KES period length, in slots."
+ ]
diff --git a/cardano-node/src/Cardano/Node/Tracing.hs b/cardano-node/src/Cardano/Node/Tracing.hs
index 3de17877dc3..ecc0b5532a7 100644
--- a/cardano-node/src/Cardano/Node/Tracing.hs
+++ b/cardano-node/src/Cardano/Node/Tracing.hs
@@ -21,7 +21,7 @@ import Ouroboros.Network.NodeToNode (NodeToNodeVersion, RemoteAddress)
import Ouroboros.Network.NodeToClient (LocalAddress, NodeToClientVersion)
import Cardano.Node.Handlers.Shutdown (ShutdownTrace)
-import Cardano.Node.Startup (NodeInfo, StartupTrace)
+import Cardano.Node.Startup (NodeInfo, NodeStartupInfo, StartupTrace)
import Cardano.Logging.Resources
import Cardano.Node.Tracing.StateRep (NodeState)
@@ -46,6 +46,7 @@ data Tracers peer localPeer blk p2p = Tracers
, startupTracer :: Tracer IO (StartupTrace blk)
, shutdownTracer :: Tracer IO ShutdownTrace
, nodeInfoTracer :: Tracer IO NodeInfo
+ , nodeStartupInfoTracer :: Tracer IO NodeStartupInfo
, nodeStateTracer :: Tracer IO NodeState
, resourcesTracer :: Tracer IO ResourceStats
, peersTracer :: Tracer IO [PeerT blk]
diff --git a/cardano-node/src/Cardano/Node/Tracing/Documentation.hs b/cardano-node/src/Cardano/Node/Tracing/Documentation.hs
index 91bde0b903e..8b396ec7043 100644
--- a/cardano-node/src/Cardano/Node/Tracing/Documentation.hs
+++ b/cardano-node/src/Cardano/Node/Tracing/Documentation.hs
@@ -196,6 +196,13 @@ docTracers configFileName outputFileName _ _ _ = do
nodeInfoTrDoc <- documentTracer trConfig nodeInfoTr
(docNodeInfoTraceEvent :: Documented NodeInfo)
+ nodeStartupInfoTr <- mkDataPointTracer
+ trDataPoint
+ (const ["NodeStartupInfo"])
+ configureTracers trConfig docNodeStartupInfoTraceEvent [nodeStartupInfoTr]
+ nodeStartupInfoTrDoc <- documentTracer trConfig nodeStartupInfoTr
+ (docNodeStartupInfoTraceEvent :: Documented NodeStartupInfo)
+
-- State tracer
stateTr <- mkCardanoTracer
trBase trForward mbTrEKG
@@ -865,6 +872,7 @@ docTracers configFileName outputFileName _ _ _ = do
let bl = nodeInfoTrDoc
<> stateTrDoc
+ <> nodeStartupInfoTrDoc
<> resourcesTrDoc
<> startupTrDoc
<> shutdownTrDoc
diff --git a/cardano-node/src/Cardano/Node/Tracing/Tracers.hs b/cardano-node/src/Cardano/Node/Tracing/Tracers.hs
index 157f34d0727..e48af0c1726 100644
--- a/cardano-node/src/Cardano/Node/Tracing/Tracers.hs
+++ b/cardano-node/src/Cardano/Node/Tracing/Tracers.hs
@@ -94,6 +94,11 @@ mkDispatchTracers nodeKernel trBase trForward mbTrEKG trDataPoint trConfig enabl
(const ["NodeInfo"])
configureTracers trConfig docNodeInfoTraceEvent [nodeInfoDP]
+ nodeStartupInfoDP <- mkDataPointTracer
+ trDataPoint
+ (const ["NodeStartupInfo"])
+ configureTracers trConfig docNodeStartupInfoTraceEvent [nodeStartupInfoDP]
+
nodeStateDP <- mkDataPointTracer
trDataPoint
(const ["NodeState"])
@@ -217,6 +222,7 @@ mkDispatchTracers nodeKernel trBase trForward mbTrEKG trDataPoint trConfig enabl
, shutdownTracer = Tracer (traceWith shutdownTr)
<> Tracer (SR.traceNodeStateShutdown nodeStateDP)
, nodeInfoTracer = Tracer (traceWith nodeInfoDP)
+ , nodeStartupInfoTracer = Tracer (traceWith nodeStartupInfoDP)
, nodeStateTracer = Tracer (traceWith stateTr)
<> Tracer (traceWith nodeStateDP)
, resourcesTracer = Tracer (traceWith resourcesTr)
diff --git a/cardano-node/src/Cardano/Tracing/Tracers.hs b/cardano-node/src/Cardano/Tracing/Tracers.hs
index 97e61e412ce..5ba1f507dd2 100644
--- a/cardano-node/src/Cardano/Tracing/Tracers.hs
+++ b/cardano-node/src/Cardano/Tracing/Tracers.hs
@@ -155,6 +155,7 @@ nullTracersP2P = Tracers
, startupTracer = nullTracer
, shutdownTracer = nullTracer
, nodeInfoTracer = nullTracer
+ , nodeStartupInfoTracer = nullTracer
, nodeStateTracer = nullTracer
, resourcesTracer = nullTracer
, peersTracer = nullTracer
@@ -171,6 +172,7 @@ nullTracersNonP2P = Tracers
, startupTracer = nullTracer
, shutdownTracer = nullTracer
, nodeInfoTracer = nullTracer
+ , nodeStartupInfoTracer = nullTracer
, nodeStateTracer = nullTracer
, resourcesTracer = nullTracer
, peersTracer = nullTracer
@@ -333,6 +335,7 @@ mkTracers blockConfig tOpts@(TracingOnLegacy trSel) tr nodeKern ekgDirect enable
, shutdownTracer = toLogObject' verb $ appendName "shutdown" tr
-- The remaining tracers are completely unused by the legacy tracing:
, nodeInfoTracer = nullTracer
+ , nodeStartupInfoTracer = nullTracer
, nodeStateTracer = nullTracer
, resourcesTracer = nullTracer
, peersTracer = nullTracer
@@ -475,6 +478,7 @@ mkTracers _ _ _ _ _ enableP2P =
, startupTracer = nullTracer
, shutdownTracer = nullTracer
, nodeInfoTracer = nullTracer
+ , nodeStartupInfoTracer = nullTracer
, nodeStateTracer = nullTracer
, resourcesTracer = nullTracer
, peersTracer = nullTracer
diff --git a/cardano-tracer/configuration/complete-example.json b/cardano-tracer/configuration/complete-example.json
index 64e97b3ad96..f788e2bf821 100644
--- a/cardano-tracer/configuration/complete-example.json
+++ b/cardano-tracer/configuration/complete-example.json
@@ -1,8 +1,8 @@
{
"networkMagic": 764824073,
"network": {
- "tag": "AcceptAt",
- "contents": "/tmp/forwarder.sock"
+ "tag": "ConnectTo",
+ "contents": ["/tmp/forwarder.sock"]
},
"loRequestNum": 100,
"ekgRequestFreq": 2,
@@ -20,6 +20,10 @@
"epHost": "127.0.0.1",
"epPort": 3000
},
+ "hasRTView": {
+ "epHost": "127.0.0.1",
+ "epPort": 3300
+ },
"logging": [
{
"logRoot": "/tmp/cardano-tracer-h-logs",
diff --git a/cardano-tracer/configuration/complete-example.yaml b/cardano-tracer/configuration/complete-example.yaml
index 6a6b6c3b59c..6afba4a652c 100644
--- a/cardano-tracer/configuration/complete-example.yaml
+++ b/cardano-tracer/configuration/complete-example.yaml
@@ -1,8 +1,9 @@
---
networkMagic: 764824073
network:
- tag: AcceptAt
- contents: "/tmp/forwarder.sock"
+ tag: ConnectTo
+ contents:
+ - "/tmp/forwarder.sock"
loRequestNum: 100
ekgRequestFreq: 2
hasEKG:
@@ -13,6 +14,9 @@ hasEKG:
hasPrometheus:
epHost: 127.0.0.1
epPort: 3000
+hasRTView:
+ epHost: 127.0.0.1
+ epPort: 3300
logging:
- logRoot: "/tmp/cardano-tracer-h-logs"
logMode: FileMode
diff --git a/cardano-tracer/configuration/minimal-example.json b/cardano-tracer/configuration/minimal-example.json
index b005eddf4f1..b76cef04daa 100644
--- a/cardano-tracer/configuration/minimal-example.json
+++ b/cardano-tracer/configuration/minimal-example.json
@@ -1,8 +1,8 @@
{
"networkMagic": 764824073,
"network": {
- "tag": "ConnectTo",
- "contents": ["/tmp/forwarder.sock"]
+ "tag": "AcceptAt",
+ "contents": "/tmp/forwarder.sock"
},
"logging": [
{
diff --git a/cardano-tracer/configuration/minimal-example.yaml b/cardano-tracer/configuration/minimal-example.yaml
index e2d5904cec3..462795f95da 100644
--- a/cardano-tracer/configuration/minimal-example.yaml
+++ b/cardano-tracer/configuration/minimal-example.yaml
@@ -1,9 +1,8 @@
---
networkMagic: 764824073
network:
- tag: ConnectTo
- contents:
- - "/tmp/forwarder.sock"
+ tag: AcceptAt
+ contents: "/tmp/forwarder.sock"
logging:
- logRoot: "/tmp/cardano-tracer-logs"
logMode: FileMode
diff --git a/cardano-tracer/docs/cardano-rtview.md b/cardano-tracer/docs/cardano-rtview.md
new file mode 100644
index 00000000000..52bb34d001d
--- /dev/null
+++ b/cardano-tracer/docs/cardano-rtview.md
@@ -0,0 +1,114 @@
+# Cardano RTView
+
+RTView is a part of `cardano-tracer` [service](https://github.com/input-output-hk/cardano-node/blob/master/cardano-tracer/docs/cardano-tracer.md). It is a real-time monitoring tool for Cardano nodes (RTView is an abbreviation for "Real Time View"). It provides an interactive web page where you can see different kinds of information about connected nodes.
+
+# Contents
+
+1. [Introduction](#Introduction)
+ 1. [Motivation](#Motivation)
+ 2. [Overview](#Overview)
+2. [Configuration](#Configuration)
+3. [Notifications](#Notifications)
+ 1. [SMTP settings](#SMTP-settings)
+ 2. [Note for Gmail users](#Note-for-Gmail-users)
+ 3. [Events](#Events)
+ 4. [Notify period](#Notify-period)
+4. [UI](#UI)
+ 1. [Security Alert](#Security-Alert)
+
+# Introduction
+
+## Motivation
+
+For a long time, Stake Pool Operators used third-party tools for monitoring their Cardano nodes, such as [Grafana](https://grafana.com/grafana/dashboards/12469)-based installations. These third-party solutions work, but they have two main problems:
+
+1. Complex setup, especially for non-technical person.
+2. Limited kinds of displayed information. For example, metrics can be shown, but error messages cannot.
+
+RTView solves both of them:
+
+1. Its setup is as simple as possible: if you have `cardano-tracer` installed, you already have RTView.
+2. Because of using special network protocols integrated into the node, RTView can display any information that the node can provide.
+
+## Overview
+
+You can think of RTView as a SPA (Single Page Application) that can be opened in any modern browser. All the information on it changes dynamically, so you shouldn't refresh it.
+
+When you open it for the first time, you'll see a help message about required configuration.
+
+After your node connects to `cardano-tracer`, you'll see a column with different information, such as the node's name, version, protocol, era, sync percentage, KES values, blockchain info, etc. There is a separate column for each connected node, so you can see and compare their data.
+
+Also, there are dynamic charts for different metrics, such as system metrics, blockchain metrics, transaction metrics, etc.
+
+# Configuration
+
+Since RTView is a part of `cardano-tracer`, the only thing you need to do is to enable RTView (because it's disabled by default). To do it, please add the following lines to `cardano-tracer`'s configuration file.
+
+If you use `json`-configuration:
+
+```
+"hasRTView": {
+ "epHost": "127.0.0.1",
+ "epPort": 3300
+}
+```
+
+Or, if you use `yaml`-configuration:
+
+```
+hasRTView:
+ epHost: 127.0.0.1
+ epPort: 3300
+```
+
+Here `epHost` and `epPort` specify the host and the port for RTView web page.
+
+That's it. Now run `cardano-tracer` and open [127.0.0.1:3300](https://127.0.0.1:3300) in your browser.
+
+# Notifications
+
+RTView can send notifications about specified events (for example, warnings or errors). Click on the bell icon on the top bar to see the corresponding settings.
+
+## SMTP settings
+
+Technically, RTView contains an email client that sends emails using SMTP. That's why you need the SMTP settings of your email provider. Please fill in all the inputs marked with an asterisk in `Settings` window.
+
+You can use `Send test email` button to check if your email settings are correct.
+
+## Note for Gmail users
+
+If you want to set up email notifications using your Gmail account, please make sure that `2-Step Verification` is enabled. You can check it in `Google Account` -> `Security`. After you enabled `2-Step Verification`, please generate the new app password (if you don't have one already) in `Security` -> `App passwords`. You'll need this app password for RTView settings.
+
+Now you can set up RTView notifications:
+
+1. `SMTP host`: `smtp.gmail.com`
+
+2. `SMTP port`: `587`
+
+3. `Username`: most likely, it's your email address
+
+4. `Password`: app password you've generated
+
+5. `SSL`: `STARTTLS`
+
+## Events
+
+When you click on the bell icon on the top bar, you can open `Events` window. Here you can specify events you want to be notified about.
+
+For example, let's have a look at `Warnings` (i.e. all the messages from the node with `Warning` severity level). By default, the corresponding switch is disabled, which means that you won't be notified about warnings at all. But if you enable that switch, you will periodically receive a notification about warnings, if any.
+
+You can use a switch `All events` in the bottom of the window to enable/disable all the events at once. Please note that if you disable all the events, the bell icon on the top bar becomes "slashed".
+
+## Notify period
+
+You can specify how frequently you want to receive notifications for a specific event. To do it, select a value from the dropdown list at the right of the event switch. There are values from `Immediately` to `Every 12 hours`.
+
+If you selected `Immediately`, the new email with the associated event(s) will be sent right away. It can be used for critical events: most likely, you want to know about such events as soon as possible.
+
+If you selected `Every 12 hours`, the new email with associated event(s) will be sent only two times a day. I can be used for non-critical events, like `Warnings`.
+
+# UI
+
+## Security Alert
+
+When you open the web page for the first time, you'll see a warning from your browser, something like "Potential Security Risk Ahead" or "Your connection is not private". This is because `https`-connection between your browser and RTView is using [self-signed certificate](https://en.wikipedia.org/wiki/Self-signed_certificate) generated by [openssl](https://www.openssl.org/) program. So click to `Advanced` button and open the page. Technically, there is no risk at all - your connection **is** private.
diff --git a/cardano-tracer/docs/cardano-tracer.md b/cardano-tracer/docs/cardano-tracer.md
index f2ffbfb24bc..a131abb4bd9 100644
--- a/cardano-tracer/docs/cardano-tracer.md
+++ b/cardano-tracer/docs/cardano-tracer.md
@@ -18,6 +18,7 @@
7. [Prometheus](#Prometheus)
8. [EKG Monitoring](#EKG-monitoring)
9. [Verbosity](#Verbosity)
+ 10. [RTView](#RTView)
# Introduction
@@ -401,3 +402,7 @@ The optional field `verbosity` specifies the verbosity level for the `cardano-tr
3. `Maximum` - all the messages will be shown in standard output. **Caution**: the number of messages can be huge.
Please note that if you skip this field, `ErrorsOnly` verbosity will be used by default.
+
+## RTView
+
+It is a real-time monitoring tool for Cardano nodes (RTView is an abbreviation for "Real Time View"). It provides an interactive web page where you can see different kinds of information about connected nodes. Please read its documentation [here](https://github.com/input-output-hk/cardano-node/blob/master/cardano-tracer/docs/cardano-rtview.md).
diff --git a/cardano-tracer/src/Cardano/Tracer/Handlers/RTView/Notifications/Send.hs b/cardano-tracer/src/Cardano/Tracer/Handlers/RTView/Notifications/Send.hs
index 513d201db32..5d20dc9ed98 100644
--- a/cardano-tracer/src/Cardano/Tracer/Handlers/RTView/Notifications/Send.hs
+++ b/cardano-tracer/src/Cardano/Tracer/Handlers/RTView/Notifications/Send.hs
@@ -5,6 +5,7 @@ module Cardano.Tracer.Handlers.RTView.Notifications.Send
( makeAndSendNotification
) where
+import Control.Concurrent.Extra (Lock)
import Control.Concurrent.STM (atomically)
import Control.Concurrent.STM.TBQueue (flushTBQueue)
import Control.Concurrent.STM.TVar (TVar, modifyTVar', readTVarIO)
@@ -27,10 +28,11 @@ import Cardano.Tracer.Utils
makeAndSendNotification
:: DataPointRequestors
+ -> Lock
-> TVar UTCTime
-> EventsQueue
-> IO ()
-makeAndSendNotification dpRequestors lastTime eventsQueue = do
+makeAndSendNotification dpRequestors currentDPLock lastTime eventsQueue = do
emailSettings <- readSavedEmailSettings
unless (incompleteEmailSettings emailSettings) $ do
events <- atomically $ nub <$> flushTBQueue eventsQueue
@@ -38,7 +40,7 @@ makeAndSendNotification dpRequestors lastTime eventsQueue = do
unless (null nodeIds) $ do
nodeNames <-
forM nodeIds $ \nodeId@(NodeId anId) ->
- askDataPoint dpRequestors nodeId "NodeInfo" >>= \case
+ askDataPoint dpRequestors currentDPLock nodeId "NodeInfo" >>= \case
Nothing -> return anId
Just ni -> return $ niName ni
lastEventTime <- readTVarIO lastTime
diff --git a/cardano-tracer/src/Cardano/Tracer/Handlers/RTView/Notifications/Utils.hs b/cardano-tracer/src/Cardano/Tracer/Handlers/RTView/Notifications/Utils.hs
index dad54aba138..98ff79f2ca6 100644
--- a/cardano-tracer/src/Cardano/Tracer/Handlers/RTView/Notifications/Utils.hs
+++ b/cardano-tracer/src/Cardano/Tracer/Handlers/RTView/Notifications/Utils.hs
@@ -8,6 +8,7 @@ module Cardano.Tracer.Handlers.RTView.Notifications.Utils
, updateNotificationsPeriods
) where
+import Control.Concurrent.Extra (Lock)
import Control.Concurrent.STM (atomically)
import Control.Concurrent.STM.TBQueue (flushTBQueue, isFullTBQueue, newTBQueueIO,
writeTBQueue)
@@ -22,8 +23,11 @@ import Cardano.Tracer.Handlers.RTView.Notifications.Types
import Cardano.Tracer.Handlers.RTView.Update.Utils
import Cardano.Tracer.Types
-initEventsQueues :: DataPointRequestors -> IO EventsQueues
-initEventsQueues dpRequestors = do
+initEventsQueues
+ :: DataPointRequestors
+ -> Lock
+ -> IO EventsQueues
+initEventsQueues dpRequestors currentDPLock = do
lastTime <- newTVarIO nullTime
warnQ <- initEventsQueue
@@ -41,12 +45,13 @@ initEventsQueues dpRequestors = do
(emrgS, emrgP) = evsEmergencies settings
(nodeDisconS, nodeDisconP) = evsNodeDisconnected settings
- warnT <- mkTimer (makeAndSendNotification dpRequestors lastTime warnQ) warnS warnP
- errsT <- mkTimer (makeAndSendNotification dpRequestors lastTime errsQ) errsS errsP
- critT <- mkTimer (makeAndSendNotification dpRequestors lastTime critQ) critS critP
- alrtT <- mkTimer (makeAndSendNotification dpRequestors lastTime alrtQ) alrtS alrtP
- emrgT <- mkTimer (makeAndSendNotification dpRequestors lastTime emrgQ) emrgS emrgP
- nodeDisconT <- mkTimer (makeAndSendNotification dpRequestors lastTime nodeDisconQ) nodeDisconS nodeDisconP
+ warnT <- mkTimer (makeAndSendNotification dpRequestors currentDPLock lastTime warnQ) warnS warnP
+ errsT <- mkTimer (makeAndSendNotification dpRequestors currentDPLock lastTime errsQ) errsS errsP
+ critT <- mkTimer (makeAndSendNotification dpRequestors currentDPLock lastTime critQ) critS critP
+ alrtT <- mkTimer (makeAndSendNotification dpRequestors currentDPLock lastTime alrtQ) alrtS alrtP
+ emrgT <- mkTimer (makeAndSendNotification dpRequestors currentDPLock lastTime emrgQ) emrgS emrgP
+ nodeDisconT <- mkTimer (makeAndSendNotification dpRequestors currentDPLock lastTime nodeDisconQ)
+ nodeDisconS nodeDisconP
newTVarIO $ M.fromList
[ (EventWarnings, (warnQ, warnT))
diff --git a/cardano-tracer/src/Cardano/Tracer/Handlers/RTView/Run.hs b/cardano-tracer/src/Cardano/Tracer/Handlers/RTView/Run.hs
index 8852c4a9d78..f2073731cac 100644
--- a/cardano-tracer/src/Cardano/Tracer/Handlers/RTView/Run.hs
+++ b/cardano-tracer/src/Cardano/Tracer/Handlers/RTView/Run.hs
@@ -8,6 +8,7 @@ module Cardano.Tracer.Handlers.RTView.Run
) where
import Control.Concurrent.Async.Extra (sequenceConcurrently)
+import Control.Concurrent.Extra (Lock)
import Control.Monad (void)
import Control.Monad.Extra (whenJust)
import qualified Data.Text as T
@@ -45,10 +46,12 @@ runRTView
-> AcceptedMetrics
-> SavedTraceObjects
-> DataPointRequestors
+ -> Lock
-> EventsQueues
-> IO ()
runRTView TracerConfig{logging, network, hasRTView}
- connectedNodes acceptedMetrics savedTO dpRequestors eventsQueues =
+ connectedNodes acceptedMetrics savedTO
+ dpRequestors currentDPLock eventsQueues =
whenJust hasRTView $ \(Endpoint host port) -> do
-- Pause to prevent collision between "Listening"-notifications from servers.
sleep 0.3
@@ -78,6 +81,7 @@ runRTView TracerConfig{logging, network, hasRTView}
savedTO
eraSettings
dpRequestors
+ currentDPLock
reloadFlag
logging
network
@@ -96,7 +100,8 @@ runRTView TracerConfig{logging, network, hasRTView}
, runEraSettingsUpdater
connectedNodes
eraSettings
- savedTO
+ dpRequestors
+ currentDPLock
, runErrorsUpdater
connectedNodes
errors
diff --git a/cardano-tracer/src/Cardano/Tracer/Handlers/RTView/State/Displayed.hs b/cardano-tracer/src/Cardano/Tracer/Handlers/RTView/State/Displayed.hs
index d3aaee799d2..aa36c701de4 100644
--- a/cardano-tracer/src/Cardano/Tracer/Handlers/RTView/State/Displayed.hs
+++ b/cardano-tracer/src/Cardano/Tracer/Handlers/RTView/State/Displayed.hs
@@ -1,6 +1,7 @@
module Cardano.Tracer.Handlers.RTView.State.Displayed
( DisplayedElements
, PageReloadedFlag
+ , cleanupDisplayedValues
, getDisplayedValue
, getDisplayedValuePure
, initDisplayedElements
@@ -40,6 +41,12 @@ type DisplayedElements = TVar (Map NodeId DisplayedForNode)
initDisplayedElements :: IO DisplayedElements
initDisplayedElements = newTVarIO M.empty
+cleanupDisplayedValues
+ :: DisplayedElements
+ -> IO ()
+cleanupDisplayedValues displayedElements = atomically $
+ modifyTVar' displayedElements $ M.map (const M.empty)
+
getDisplayedValue
:: DisplayedElements
-> NodeId
diff --git a/cardano-tracer/src/Cardano/Tracer/Handlers/RTView/UI/CSS/Own.hs b/cardano-tracer/src/Cardano/Tracer/Handlers/RTView/UI/CSS/Own.hs
index 16587dcae2b..77b3bea3c4a 100644
--- a/cardano-tracer/src/Cardano/Tracer/Handlers/RTView/UI/CSS/Own.hs
+++ b/cardano-tracer/src/Cardano/Tracer/Handlers/RTView/UI/CSS/Own.hs
@@ -204,6 +204,11 @@ span[data-tooltip] {
margin-top: 6px;
}
+.rt-view-search-errors-icon svg {
+ width: 18px;
+ color: whitesmoke;
+}
+
.rt-view-notifications-errors-select-wrapper {
padding-top: 7px;
padding-bottom: 11px;
@@ -238,6 +243,26 @@ span[data-tooltip] {
cursor: pointer;
}
+@media screen and (min-width: 1024px) {
+ .dark .navbar-item.has-dropdown:hover .navbar-link {
+ background-color: #434360;
+ }
+
+ .dark .navbar-dropdown {
+ background-color: #434360;
+ border-top: 1px solid #aaa;
+ }
+}
+
+.dark .navbar-dropdown.is-right .navbar-item {
+ background-color: #434360;
+ color: #cecece;
+}
+
+.dark .navbar-dropdown.is-right a.navbar-item:hover {
+ background-color: #545478;
+}
+
.dark .rt-view-href-icon svg {
width: 12px;
margin-left: 5px;
@@ -286,6 +311,11 @@ span[data-tooltip] {
cursor: pointer;
}
+.dark .rt-view-copy-icon-on-button svg {
+ width: 20px;
+ color: whitesmoke;
+ margin-top: 5px;
+}
.dark .rt-view-show-hide-pass-icon svg {
width: 20px;
@@ -319,12 +349,6 @@ span[data-tooltip] {
cursor: pointer;
}
-.dark .rt-view-search-errors-icon svg {
- width: 18px;
- color: whitesmoke;
- cursor: pointer;
-}
-
.dark .rt-view-logs-icon svg {
width: 23px;
padding-top: 2px;
@@ -438,6 +462,13 @@ span[data-tooltip] {
display: block;
}
+.dark .rt-view-notification-settings-foot {
+ color: whitesmoke;
+ background-color: #282841;
+ border-top: 1px solid #555;
+ display: block;
+}
+
.dark .rt-view-notifications-title {
color: whitesmoke;
}
@@ -559,6 +590,13 @@ span[data-tooltip] {
color: #0cc9cb;
}
+.dark .rt-view-footer-doc svg {
+ width: 20px;
+ margin-top: 1px;
+ margin-left: 15px;
+ color: #0cc9cb;
+}
+
.dark .rt-view-percent-done {
color: #07e949;
}
@@ -592,6 +630,7 @@ span[data-tooltip] {
.dark .rt-view-label {
font-size: 80%;
font-weight: 600;
+ color: whitesmoke;
}
.dark .rt-view-test-status-message-ok {
@@ -677,6 +716,12 @@ span[data-tooltip] {
cursor: pointer;
}
+.light .rt-view-copy-icon-on-button svg {
+ width: 20px;
+ color: whitesmoke;
+ margin-top: 5px;
+}
+
.light .rt-view-show-hide-pass-icon svg {
width: 20px;
cursor: pointer;
@@ -705,13 +750,7 @@ span[data-tooltip] {
width: 29px;
margin-top: 5px;
margin-right: 5px;
- color: #444;
- cursor: pointer;
-}
-
-.light .rt-view-search-errors-icon svg {
- width: 18px;
- color: #444;
+ color: #0033ad;
cursor: pointer;
}
@@ -821,6 +860,13 @@ span[data-tooltip] {
display: block;
}
+.light .rt-view-notification-settings-foot {
+ color: #555;
+ background-color: whitesmoke;
+ border-top: 1px solid #bebebe;
+ display: block;
+}
+
.light .rt-view-notifications-title {
color: #444;
}
@@ -942,6 +988,13 @@ span[data-tooltip] {
color: #038b8c;
}
+.light .rt-view-footer-doc svg {
+ width: 20px;
+ margin-top: 1px;
+ margin-left: 15px;
+ color: #038b8c;
+}
+
.light .rt-view-percent-done {
color: #048b04;
}
@@ -982,6 +1035,7 @@ span[data-tooltip] {
.light .rt-view-label {
font-size: 80%;
font-weight: 600;
+ color: #555;
}
.light .rt-view-test-status-message-ok {
diff --git a/cardano-tracer/src/Cardano/Tracer/Handlers/RTView/UI/HTML/About.hs b/cardano-tracer/src/Cardano/Tracer/Handlers/RTView/UI/HTML/About.hs
index 1e68cf7ae0b..d51458ebdf5 100644
--- a/cardano-tracer/src/Cardano/Tracer/Handlers/RTView/UI/HTML/About.hs
+++ b/cardano-tracer/src/Cardano/Tracer/Handlers/RTView/UI/HTML/About.hs
@@ -27,10 +27,12 @@ mkAboutInfo = do
["-c", path] -> makeAbsolute path
["--config", path] -> makeAbsolute path
_ -> return ""
- copyPath <- image "has-tooltip-multiline has-tooltip-top rt-view-copy-icon" copySVG
- # set dataTooltip "Click to copy the path"
+
+ copyPath <- UI.button #. "button is-info"
+ #+ [image "rt-view-copy-icon-on-button" copySVG]
on UI.click copyPath . const $
copyTextToClipboard pathToConfig
+
closeIt <- UI.button #. "delete"
pid <- getProcessId
info <-
@@ -56,11 +58,11 @@ mkAboutInfo = do
[ image "rt-view-overview-icon" platformSVG
, string "Platform"
]
- , UI.p #. "mb-3" #+
+ , UI.p #. "mb-3 mt-4" #+
[ image "rt-view-overview-icon" configSVG
, string "Configuration"
]
- , UI.p #. "mb-1" #+
+ , UI.p #. "mb-1 mt-4" #+
[ image "rt-view-overview-icon" serverSVG
, string "Process ID"
]
@@ -83,11 +85,17 @@ mkAboutInfo = do
| otherwise -> "Linux"
]
, UI.p #. "mb-3" #+
- [ UI.span #. ("tag is-info is-light is-rounded is-medium mr-3"
- <> " has-tooltip-multiline has-tooltip-top rt-view-logs-path")
- # set dataTooltip "The path to configuration file"
- # set text (shortenPath pathToConfig)
- , element copyPath
+ [ UI.div #. "field has-addons" #+
+ [ UI.p #. "control" #+
+ [ UI.input #. "input rt-view-logs-input"
+ # set UI.type_ "text"
+ # set (UI.attr "readonly") "readonly"
+ # set UI.value pathToConfig
+ ]
+ , UI.p #. "control" #+
+ [ element copyPath
+ ]
+ ]
]
, UI.p #. "mb-1" #+
[ string $ show pid
diff --git a/cardano-tracer/src/Cardano/Tracer/Handlers/RTView/UI/HTML/Body.hs b/cardano-tracer/src/Cardano/Tracer/Handlers/RTView/UI/HTML/Body.hs
index 8bce46f057e..16029a8fd8c 100644
--- a/cardano-tracer/src/Cardano/Tracer/Handlers/RTView/UI/HTML/Body.hs
+++ b/cardano-tracer/src/Cardano/Tracer/Handlers/RTView/UI/HTML/Body.hs
@@ -554,6 +554,11 @@ footer =
[ image "has-tooltip-multiline has-tooltip-left rt-view-footer-github" githubSVG
# set dataTooltip "Browse our GitHub repository"
]
+ , UI.anchor # set UI.href "https://github.com/input-output-hk/cardano-node/blob/master/cardano-tracer/docs/cardano-rtview.md"
+ # set UI.target "_blank" #+
+ [ image "has-tooltip-multiline has-tooltip-left rt-view-footer-doc" docSVG
+ # set dataTooltip "Read RTView documentation"
+ ]
]
]
]
diff --git a/cardano-tracer/src/Cardano/Tracer/Handlers/RTView/UI/HTML/Main.hs b/cardano-tracer/src/Cardano/Tracer/Handlers/RTView/UI/HTML/Main.hs
index 00d8dd39113..bc741a5897c 100644
--- a/cardano-tracer/src/Cardano/Tracer/Handlers/RTView/UI/HTML/Main.hs
+++ b/cardano-tracer/src/Cardano/Tracer/Handlers/RTView/UI/HTML/Main.hs
@@ -4,6 +4,7 @@ module Cardano.Tracer.Handlers.RTView.UI.HTML.Main
( mkMainPage
) where
+import Control.Concurrent.Extra (Lock)
import Control.Concurrent.STM.TVar (readTVarIO)
import Control.Monad (void)
import Control.Monad.Extra (whenM)
@@ -46,6 +47,7 @@ mkMainPage
-> SavedTraceObjects
-> ErasSettings
-> DataPointRequestors
+ -> Lock
-> PageReloadedFlag
-> NonEmpty LoggingParams
-> Network
@@ -57,7 +59,7 @@ mkMainPage
-> UI.Window
-> UI ()
mkMainPage connectedNodes displayedElements acceptedMetrics savedTO
- nodesEraSettings dpRequestors reloadFlag loggingConfig networkConfig
+ nodesEraSettings dpRequestors currentDPLock reloadFlag loggingConfig networkConfig
resourcesHistory chainHistory txHistory nodesErrors eventsQueues window = do
void $ return window # set UI.title pageTitle
void $ UI.getHead window #+
@@ -120,11 +122,13 @@ mkMainPage connectedNodes displayedElements acceptedMetrics savedTO
updateNodesErrors window connectedNodes nodesErrors
whenM (liftIO $ readTVarIO reloadFlag) $ do
+ liftIO $ cleanupDisplayedValues displayedElements
updateUIAfterReload
window
connectedNodes
displayedElements
dpRequestors
+ currentDPLock
loggingConfig
colors
datasetIndices
@@ -152,6 +156,7 @@ mkMainPage connectedNodes displayedElements acceptedMetrics savedTO
savedTO
nodesEraSettings
dpRequestors
+ currentDPLock
loggingConfig
colors
datasetIndices
@@ -159,18 +164,14 @@ mkMainPage connectedNodes displayedElements acceptedMetrics savedTO
uiErrorsTimer
uiNoNodesProgressTimer
- uiPeersTimer <- UI.timer # set UI.interval 3000
+ uiPeersTimer <- UI.timer # set UI.interval 4000
on UI.tick uiPeersTimer . const $ do
- updateNodesPeers window peers savedTO
+ askNSetNodeState connectedNodes dpRequestors currentDPLock displayedElements
+ updateNodesPeers window connectedNodes dpRequestors currentDPLock peers
updateKESInfo window acceptedMetrics nodesEraSettings displayedElements
- uiNodeStateTimer <- UI.timer # set UI.interval 5000
- on UI.tick uiNodeStateTimer . const $
- askNSetNodeState window connectedNodes dpRequestors displayedElements
-
UI.start uiUptimeTimer
UI.start uiNodesTimer
- UI.start uiNodeStateTimer
UI.start uiPeersTimer
UI.start uiErrorsTimer
UI.start uiEKGTimer
@@ -180,7 +181,6 @@ mkMainPage connectedNodes displayedElements acceptedMetrics savedTO
UI.stop uiNodesTimer
UI.stop uiUptimeTimer
UI.stop uiPeersTimer
- UI.stop uiNodeStateTimer
UI.stop uiEKGTimer
UI.stop uiErrorsTimer
UI.stop uiNoNodesProgressTimer
diff --git a/cardano-tracer/src/Cardano/Tracer/Handlers/RTView/UI/HTML/NoNodes.hs b/cardano-tracer/src/Cardano/Tracer/Handlers/RTView/UI/HTML/NoNodes.hs
index 22a0ee69ee8..96322c82891 100644
--- a/cardano-tracer/src/Cardano/Tracer/Handlers/RTView/UI/HTML/NoNodes.hs
+++ b/cardano-tracer/src/Cardano/Tracer/Handlers/RTView/UI/HTML/NoNodes.hs
@@ -58,13 +58,18 @@ mkNoNodesInfo networkConfig = do
[ UI.span # set UI.html cardanoTracerNote
]
, UI.p #. "mt-5" #+
- [ UI.span # set UI.html cardanoNodeNote
+ [ UI.span # set UI.html localNote
]
, UI.p #. "mt-5" #+
- [ UI.span # set UI.html nodeNameNote
+ [ UI.span # set UI.html sshNote
+ , UI.anchor # set UI.href "https://github.com/input-output-hk/cardano-node/blob/master/cardano-tracer/docs/cardano-tracer.md#distributed-scenario"
+ # set text "here"
+ # set UI.target "_blank"
+ , image "rt-view-href-icon" externalLinkSVG
+ , string "."
]
, UI.p #. "mt-5" #+
- [ UI.span # set UI.html sshNote
+ [ UI.span # set UI.html nodeNameNote
]
, UI.p #. "mt-5" #+
[ string "For more details, please read "
@@ -81,7 +86,7 @@ mkNoNodesInfo networkConfig = do
pleaseWait =
"If your nodes and cardano-tracer
are configured properly, "
<> "the connection between them will be established automatically, "
- <> "but it can take some time."
+ <> "but it may take some time."
intro =
"However, if there is no connection after 1 minute, please check your configuration."
@@ -91,7 +96,8 @@ mkNoNodesInfo networkConfig = do
AcceptAt (LocalSocket p) ->
"Currently, your cardano-tracer
is configured as a server, "
<> "so it accepts connections from your nodes via the local socket "
- <> p <> "
."
+ <> p <> ". Correspondingly, your nodes should be configured to "
+ <> "initiate connections using tracing socket."
ConnectTo addrs ->
let manySocks = NE.length addrs > 1 in
"Currently, your cardano-tracer
is configured as a client, "
@@ -104,26 +110,28 @@ mkNoNodesInfo networkConfig = do
in "sockets " <> intercalate ", " socks <> "."
else
"socket " <> let LocalSocket p = NE.head addrs in p <> "
.")
+ <> " Correspondingly, our nodes should be configured to accept connections using tracing socket."
- cardanoNodeNote =
+ localNote =
case networkConfig of
- AcceptAt (LocalSocket _p) ->
- "Correspondingly, your nodes should be configured to initiate connections using tracing socket."
- <> " Make sure their command line invocations contain --tracer-socket-path-connect"
- <> " PATH-TO-LOCAL-SOCKET
."
+ AcceptAt (LocalSocket p) ->
+ "Thus, if your cardano-tracer
and your nodes are running on the same machine, run "
+ <> "the nodes with this argument: --tracer-socket-path-connect " <> p <> "
."
ConnectTo{} ->
- "Correspondingly, your nodes should be configured to accept connections using tracing socket."
- <> " Make sure their command line invocations contain --tracer-socket-path-accept"
- <> " PATH-TO-LOCAL-SOCKET
."
+ "Thus, if your cardano-tracer
and your nodes are running on the same machine, run "
+ <> "the nodes with this argument: --tracer-socket-path-accept SOCKET
, where "
+ <> "SOCKET
is the path to one of sockets specified in ConnectTo
-list "
+ <> "in cardano-tracer
configuration file."
+
+ sshNote =
+ "But if your cardano-tracer
and your nodes are running on different machines, the only "
+ <> "way to connect them is SSH tunneling with your credentials. Please see an explanation with the "
+ <> "real-life example "
nodeNameNote =
"Also, please add a meaningful name for your nodes using TraceOptionNodeName
field"
<> " in their configuration files. For example:
" <> traceOptionNodeName <> "" - sshNote = - "If your
cardano-tracer
and your nodes are running on different machines, the only "
- <> "way to connect them is SSH tunneling with your credentials."
-
traceOptionNodeName :: String
traceOptionNodeName = [s|
"TraceOptionNodeName": "stk-a-1-IOG1"
diff --git a/cardano-tracer/src/Cardano/Tracer/Handlers/RTView/UI/HTML/Node/Column.hs b/cardano-tracer/src/Cardano/Tracer/Handlers/RTView/UI/HTML/Node/Column.hs
index efc5e8b0dc4..657a51b705e 100644
--- a/cardano-tracer/src/Cardano/Tracer/Handlers/RTView/UI/HTML/Node/Column.hs
+++ b/cardano-tracer/src/Cardano/Tracer/Handlers/RTView/UI/HTML/Node/Column.hs
@@ -65,6 +65,8 @@ addNodeColumn window loggingConfig nodesErrors updateErrorsTimer
, UI.span ## (id' <> "__node-name")
#. "has-text-weight-bold is-size-4 rt-view-node-name"
# set text "Node"
+ , image "has-tooltip-multiline has-tooltip-bottom rt-view-what-icon" whatSVG
+ # set dataTooltip "Node's name, taken from its configuration file"
]
addNodeCell "version" [ UI.span ## (id' <> "__node-version")
# set text "—"
@@ -189,7 +191,7 @@ logsSettings loggingConfig anId =
let pathToSubdir = root > anId
copyPath <- UI.button #. "button is-info"
- #+ [image "rt-view-copy-icon" copySVG]
+ #+ [image "rt-view-copy-icon-on-button" copySVG]
on UI.click copyPath . const $
copyTextToClipboard pathToSubdir
diff --git a/cardano-tracer/src/Cardano/Tracer/Handlers/RTView/UI/Img/Icons.hs b/cardano-tracer/src/Cardano/Tracer/Handlers/RTView/UI/Img/Icons.hs
index 2be1febec7c..9f8638dc377 100644
--- a/cardano-tracer/src/Cardano/Tracer/Handlers/RTView/UI/Img/Icons.hs
+++ b/cardano-tracer/src/Cardano/Tracer/Handlers/RTView/UI/Img/Icons.hs
@@ -61,6 +61,7 @@ module Cardano.Tracer.Handlers.RTView.UI.Img.Icons
, eventsSVG
, settingsSVG
, exportSVG
+ , docSVG
) where
import Data.String.QQ
@@ -237,7 +238,7 @@ copySVG = [s|
serverSVG :: String
serverSVG = [s|
-
+
|]
externalLinkSVG :: String
@@ -360,6 +361,11 @@ exportSVG = [s|
|]
+docSVG :: String
+docSVG = [s|
+
+|]
+
rectangleSVG :: String
rectangleSVG = [s|
diff --git a/cardano-tracer/src/Cardano/Tracer/Handlers/RTView/Update/Chain.hs b/cardano-tracer/src/Cardano/Tracer/Handlers/RTView/Update/Chain.hs
index baf7ddfa107..f87e1b60b0c 100644
--- a/cardano-tracer/src/Cardano/Tracer/Handlers/RTView/Update/Chain.hs
+++ b/cardano-tracer/src/Cardano/Tracer/Handlers/RTView/Update/Chain.hs
@@ -22,11 +22,11 @@ updateBlockchainHistory
-> IO ()
updateBlockchainHistory nodeId (ChainHistory cHistory) metricName metricValue now =
case metricName of
- "cardano.node.density" -> updateChainDensity
- "cardano.node.slotNum" -> updateSlotNum
- "cardano.node.blockNum" -> updateBlockNum
- "cardano.node.slotInEpoch" -> updateSlotInEpoch
- "cardano.node.epoch" -> updateEpoch
+ "ChainDB.Density" -> updateChainDensity
+ "ChainDB.SlotNum" -> updateSlotNum
+ "ChainDB.BlockNum" -> updateBlockNum
+ "ChainDB.SlotInEpoch" -> updateSlotInEpoch
+ "ChainDB.Epoch" -> updateEpoch
_ -> return ()
where
updateChainDensity =
diff --git a/cardano-tracer/src/Cardano/Tracer/Handlers/RTView/Update/EraSettings.hs b/cardano-tracer/src/Cardano/Tracer/Handlers/RTView/Update/EraSettings.hs
index 4bf1f0febd3..f896e3b7c62 100644
--- a/cardano-tracer/src/Cardano/Tracer/Handlers/RTView/Update/EraSettings.hs
+++ b/cardano-tracer/src/Cardano/Tracer/Handlers/RTView/Update/EraSettings.hs
@@ -5,47 +5,44 @@ module Cardano.Tracer.Handlers.RTView.Update.EraSettings
( runEraSettingsUpdater
) where
+import Control.Concurrent.Extra (Lock)
import Control.Concurrent.STM.TVar (readTVarIO)
import Control.Monad (forM_, forever)
-import Control.Monad.Extra (whenJust)
-import qualified Data.Map.Strict as M
+import Control.Monad.Extra (whenJustM)
import Data.Set (Set)
-import qualified Data.Text as T
+import Data.Time.Clock (nominalDiffTimeToSeconds)
import System.Time.Extra (sleep)
+import Cardano.Node.Startup (NodeStartupInfo (..))
+
import Cardano.Tracer.Handlers.RTView.State.EraSettings
-import Cardano.Tracer.Handlers.RTView.State.TraceObjects
import Cardano.Tracer.Handlers.RTView.Update.Utils
import Cardano.Tracer.Types
runEraSettingsUpdater
:: ConnectedNodes
-> ErasSettings
- -> SavedTraceObjects
+ -> DataPointRequestors
+ -> Lock
-> IO ()
-runEraSettingsUpdater connectedNodes settings savedTO = forever $ do
+runEraSettingsUpdater connectedNodes settings dpRequestors currentDPLock = forever $ do
connected <- readTVarIO connectedNodes
- updateErasSettings connected settings savedTO
- sleep 1.0
+ updateErasSettings connected settings dpRequestors currentDPLock
+ sleep 5.0
updateErasSettings
:: Set NodeId
-> ErasSettings
- -> SavedTraceObjects
+ -> DataPointRequestors
+ -> Lock
-> IO ()
-updateErasSettings connected settings savedTO = do
- savedTraceObjects <- readTVarIO savedTO
+updateErasSettings connected settings dpRequestors currentDPLock =
forM_ connected $ \nodeId ->
- whenJust (M.lookup nodeId savedTraceObjects) $ \savedTOForNode ->
- whenJust (M.lookup "Startup.ShelleyBased" savedTOForNode) $ \(trObValue, _, _) ->
- -- Example: "Era Alonzo, Slot length 1s, Epoch length 432000, Slots per KESPeriod 129600"
- case T.words $ T.replace "," "" trObValue of
- [_, era, _, _, slotLen, _, _, epochLen, _, _, _, kesPeriod] ->
- addEraSettings settings nodeId $
- EraSettings
- { esEra = era
- , esSlotLengthInS = readInt (T.init slotLen) 0
- , esEpochLength = readInt epochLen 0
- , esKESPeriodLength = readInt kesPeriod 0
- }
- _ -> return ()
+ whenJustM (askDataPoint dpRequestors currentDPLock nodeId "NodeStartupInfo") $ \nsi ->
+ addEraSettings settings nodeId $
+ EraSettings
+ { esEra = suiEra nsi
+ , esSlotLengthInS = floor . nominalDiffTimeToSeconds $ suiSlotLength nsi
+ , esEpochLength = fromIntegral $ suiEpochLength nsi
+ , esKESPeriodLength = fromIntegral $ suiSlotsPerKESPeriod nsi
+ }
diff --git a/cardano-tracer/src/Cardano/Tracer/Handlers/RTView/Update/KES.hs b/cardano-tracer/src/Cardano/Tracer/Handlers/RTView/Update/KES.hs
index f15de1590f6..3ae97003061 100644
--- a/cardano-tracer/src/Cardano/Tracer/Handlers/RTView/Update/KES.hs
+++ b/cardano-tracer/src/Cardano/Tracer/Handlers/RTView/Update/KES.hs
@@ -34,13 +34,13 @@ updateKESInfo _window acceptedMetrics settings displayed = do
metrics <- liftIO $ getListOfMetrics ekgStore
forM_ metrics $ \(metricName, metricValue) ->
case metricName of
- "cardano.node.currentKESPeriod" ->
+ "Forge.CurrentKESPeriod" ->
setDisplayedValue nodeId displayed (anId <> "__node-current-kes-period") metricValue
- "cardano.node.operationalCertificateExpiryKESPeriod" ->
+ "Forge.OperationalCertificateExpiryKESPeriod" ->
setDisplayedValue nodeId displayed (anId <> "__node-op-cert-expiry-kes-period") metricValue
- "cardano.node.operationalCertificateStartKESPeriod" ->
+ "Forge.OperationalCertificateStartKESPeriod" ->
setDisplayedValue nodeId displayed (anId <> "__node-op-cert-start-kes-period") metricValue
- "cardano.node.remainingKESPeriods" -> do
+ "Forge.RemainingKESPeriods" -> do
setDisplayedValue nodeId displayed (anId <> "__node-remaining-kes-periods") metricValue
allSettings <- liftIO $ readTVarIO settings
whenJust (M.lookup nodeId allSettings) $
diff --git a/cardano-tracer/src/Cardano/Tracer/Handlers/RTView/Update/Leadership.hs b/cardano-tracer/src/Cardano/Tracer/Handlers/RTView/Update/Leadership.hs
index dc2abeecf08..6369ca2d95e 100644
--- a/cardano-tracer/src/Cardano/Tracer/Handlers/RTView/Update/Leadership.hs
+++ b/cardano-tracer/src/Cardano/Tracer/Handlers/RTView/Update/Leadership.hs
@@ -21,23 +21,23 @@ updateLeadershipHistory
updateLeadershipHistory nodeId (ChainHistory cHistory) metricName metricValue now =
case metricName of
-- Slot when the node was a leader, but couldn't forge the block.
- "cardano.node.nodeCannotForge" -> updateNodeCannotForge
+ "Forge.NodeCannotForge" -> updateNodeCannotForge
-- Slot when this node forged last block.
- "cardano.node.forgedSlotLast" -> updateForgedSlotLast
+ "Forge.ForgedSlotLast" -> updateForgedSlotLast
-- Slot when this node is leader.
- "cardano.node.nodeIsLeader" -> updateNodeIsLeader
+ "Forge.NodeIsLeader" -> updateNodeIsLeader
-- Slot when this node made leadership check and concludes it's not leader.
- "cardano.node.nodeNotLeader" -> updateNodeIsNotLeader
+ "Forge.NodeNotLeader" -> updateNodeIsNotLeader
-- Slot when invalid block was forged.
- "cardano.node.forgedInvalidSlotLast" -> updateForgedInvalidSlotLast
+ "Forge.ForgedInvalidSlotLast" -> updateForgedInvalidSlotLast
-- Slot when the node adopted the block it forged.
- "cardano.node.adoptedSlotLast" -> updateAdoptedSlotLast
+ "Forge.AdoptedOwnBlockSlotLast" -> updateAdoptedSlotLast
-- Slot when the node didn't adopted the block it forged, but the block was valid.
- "cardano.node.notAdoptedSlotLast" -> updateNotAdoptedSlotLast
+ "Forge.NotAdoptedSlotLast" -> updateNotAdoptedSlotLast
-- Slot when the leadership check is started.
- "cardano.node.aboutToLeadSlotLast" -> updateAboutToLeadSlotLast
+ "Forge.AboutToLeadSlotLast" -> updateAboutToLeadSlotLast
-- Slot when the leadership check is failed.
- "cardano.node.couldNotForgeSlotLast" -> updateCouldNotForgeSlotLast
+ "Forge.CouldNotForgeSlotLast" -> updateCouldNotForgeSlotLast
_ -> return ()
where
updateNodeCannotForge =
diff --git a/cardano-tracer/src/Cardano/Tracer/Handlers/RTView/Update/NodeInfo.hs b/cardano-tracer/src/Cardano/Tracer/Handlers/RTView/Update/NodeInfo.hs
index e2aff327a42..253351131f0 100644
--- a/cardano-tracer/src/Cardano/Tracer/Handlers/RTView/Update/NodeInfo.hs
+++ b/cardano-tracer/src/Cardano/Tracer/Handlers/RTView/Update/NodeInfo.hs
@@ -4,6 +4,7 @@ module Cardano.Tracer.Handlers.RTView.Update.NodeInfo
( askNSetNodeInfo
) where
+import Control.Concurrent.Extra (Lock)
import Control.Monad (forM_, unless)
import Control.Monad.Extra (whenJustM)
import Data.Set (Set)
@@ -23,13 +24,14 @@ import Cardano.Tracer.Types
askNSetNodeInfo
:: UI.Window
-> DataPointRequestors
+ -> Lock
-> Set NodeId
-> DisplayedElements
-> UI ()
-askNSetNodeInfo window dpRequestors newlyConnected displayedElements =
+askNSetNodeInfo window dpRequestors currentDPLock newlyConnected displayedElements =
unless (S.null newlyConnected) $
forM_ newlyConnected $ \nodeId@(NodeId anId) ->
- whenJustM (liftIO $ askDataPoint dpRequestors nodeId "NodeInfo") $ \ni -> do
+ whenJustM (liftIO $ askDataPoint dpRequestors currentDPLock nodeId "NodeInfo") $ \ni -> do
let nodeNameElId = anId <> "__node-name"
shortName = shortenName $ niName ni
@@ -57,12 +59,10 @@ askNSetNodeInfo window dpRequestors newlyConnected displayedElements =
setProtocol p id' = do
justCleanText id'
- let byronTag = UI.span #. "tag is-warning is-rounded is-medium" # set text "Byron"
- shelleyTag = UI.span #. "tag is-info is-rounded is-medium ml-3" # set text "Shelley"
case p of
- "Byron" -> findAndAdd [byronTag] window id'
- "Shelley" -> findAndAdd [shelleyTag] window id'
- _ -> findAndAdd [byronTag, shelleyTag] window id'
+ "Byron" -> setTextValue id' "Byron"
+ "Shelley" -> setTextValue id' "Shelley"
+ _ -> setTextValue id' "Cardano"
setTime ts id' = do
justCleanText id'
diff --git a/cardano-tracer/src/Cardano/Tracer/Handlers/RTView/Update/NodeState.hs b/cardano-tracer/src/Cardano/Tracer/Handlers/RTView/Update/NodeState.hs
index fc6c8418221..889af2324db 100644
--- a/cardano-tracer/src/Cardano/Tracer/Handlers/RTView/Update/NodeState.hs
+++ b/cardano-tracer/src/Cardano/Tracer/Handlers/RTView/Update/NodeState.hs
@@ -5,11 +5,11 @@ module Cardano.Tracer.Handlers.RTView.Update.NodeState
( askNSetNodeState
) where
+import Control.Concurrent.Extra (Lock)
import Control.Concurrent.STM.TVar (readTVarIO)
import Control.Monad (forM_)
import Control.Monad.Extra (whenJustM)
import Data.Text (pack)
-import qualified Graphics.UI.Threepenny as UI
import Graphics.UI.Threepenny.Core (UI, liftIO)
import Text.Printf (printf)
@@ -23,15 +23,15 @@ import Cardano.Tracer.Types
-- | There is 'NodeState' datapoint, it contains different information
-- about the current state of the node. For example, its sync progress.
askNSetNodeState
- :: UI.Window
- -> ConnectedNodes
+ :: ConnectedNodes
-> DataPointRequestors
+ -> Lock
-> DisplayedElements
-> UI ()
-askNSetNodeState _window connectedNodes dpRequestors displayed = do
+askNSetNodeState connectedNodes dpRequestors currentDPLock displayed = do
connected <- liftIO $ readTVarIO connectedNodes
- forM_ connected $ \nodeId@(NodeId _anId) ->
- whenJustM (liftIO $ askDataPoint dpRequestors nodeId "NodeState") $ \(ns :: NodeState) ->
+ forM_ connected $ \nodeId ->
+ whenJustM (liftIO $ askDataPoint dpRequestors currentDPLock nodeId "NodeState") $ \(ns :: NodeState) ->
case ns of
NodeAddBlock (AddedToCurrentChain _ _ syncPct) -> setSyncProgress nodeId syncPct
_ -> return ()
diff --git a/cardano-tracer/src/Cardano/Tracer/Handlers/RTView/Update/Nodes.hs b/cardano-tracer/src/Cardano/Tracer/Handlers/RTView/Update/Nodes.hs
index 5e6af87d0b7..95533f832ac 100644
--- a/cardano-tracer/src/Cardano/Tracer/Handlers/RTView/Update/Nodes.hs
+++ b/cardano-tracer/src/Cardano/Tracer/Handlers/RTView/Update/Nodes.hs
@@ -11,6 +11,7 @@ module Cardano.Tracer.Handlers.RTView.Update.Nodes
, updateNodesUptime
) where
+import Control.Concurrent.Extra (Lock)
import Control.Concurrent.STM (atomically)
import Control.Concurrent.STM.TVar
import Control.Monad (forM_, unless, when)
@@ -54,6 +55,7 @@ updateNodesUI
-> SavedTraceObjects
-> ErasSettings
-> DataPointRequestors
+ -> Lock
-> NonEmpty LoggingParams
-> Colors
-> DatasetsIndices
@@ -62,8 +64,8 @@ updateNodesUI
-> UI.Timer
-> UI ()
updateNodesUI window connectedNodes displayedElements acceptedMetrics savedTO nodesEraSettings
- dpRequestors loggingConfig colors datasetIndices nodesErrors updateErrorsTimer
- noNodesProgressTimer = do
+ dpRequestors currentDPLock loggingConfig colors datasetIndices nodesErrors
+ updateErrorsTimer noNodesProgressTimer = do
(connected, displayedEls) <- liftIO . atomically $ (,)
<$> readTVar connectedNodes
<*> readTVar displayedElements
@@ -81,7 +83,7 @@ updateNodesUI window connectedNodes displayedElements acceptedMetrics savedTO no
updateErrorsTimer
displayedElements
checkNoNodesState window connected noNodesProgressTimer
- askNSetNodeInfo window dpRequestors newlyConnected displayedElements
+ askNSetNodeInfo window dpRequestors currentDPLock newlyConnected displayedElements
addDatasetsForConnected window newlyConnected colors datasetIndices displayedElements
liftIO $ updateDisplayedElements displayedElements connected
setBlockReplayProgress connected displayedElements acceptedMetrics
@@ -187,7 +189,7 @@ setBlockReplayProgress connected _displayedElements acceptedMetrics = do
forM_ connected $ \nodeId ->
whenJust (M.lookup nodeId allMetrics) $ \(ekgStore, _) -> do
metrics <- liftIO $ getListOfMetrics ekgStore
- whenJust (lookup "Block replay progress (%)" metrics) $ \metricValue ->
+ whenJust (lookup "ChainDB.BlockReplayProgress" metrics) $ \metricValue ->
updateBlockReplayProgress nodeId metricValue
where
updateBlockReplayProgress (NodeId anId) mValue =
@@ -264,13 +266,13 @@ setLeadershipStats connected displayed acceptedMetrics = do
forM_ metrics $ \(mName, mValue) ->
case mName of
-- How many times this node was a leader.
- "nodeIsLeaderNum" -> setDisplayedValue nodeId displayed (anId <> "__node-leadership") mValue
+ "Forge.NodeIsLeaderNum" -> setDisplayedValue nodeId displayed (anId <> "__node-leadership") mValue
-- How many blocks were forged by this node.
- "blocksForgedNum" -> setDisplayedValue nodeId displayed (anId <> "__node-forged-blocks") mValue
+ "Forge.BlocksForgedNum" -> setDisplayedValue nodeId displayed (anId <> "__node-forged-blocks") mValue
-- How many times this node could not forge.
- "nodeCannotForgeNum" -> setDisplayedValue nodeId displayed (anId <> "__node-cannot-forge") mValue
+ "Forge.NodeCannotForgeNum" -> setDisplayedValue nodeId displayed (anId <> "__node-cannot-forge") mValue
-- How many slots were missed in this node.
- "slotsMissed" -> setDisplayedValue nodeId displayed (anId <> "__node-missed-slots") mValue
+ "Forge.SlotsMissed" -> setDisplayedValue nodeId displayed (anId <> "__node-missed-slots") mValue
_ -> return ()
setEraEpochInfo
@@ -282,20 +284,23 @@ setEraEpochInfo
setEraEpochInfo connected displayed acceptedMetrics nodesEraSettings = do
allSettings <- liftIO $ readTVarIO nodesEraSettings
allMetrics <- liftIO $ readTVarIO acceptedMetrics
- forM_ connected $ \nodeId@(NodeId anId) ->
+ forM_ connected $ \nodeId@(NodeId anId) -> do
+ epochS <-
+ case M.lookup nodeId allMetrics of
+ Just (ekgStore, _) -> do
+ metrics <- liftIO $ getListOfMetrics ekgStore
+ return $ fromMaybe "" $ lookup "ChainDB.Epoch" metrics
+ Nothing -> return ""
+ unless (T.null epochS) $
+ setDisplayedValue nodeId displayed (anId <> "__node-epoch-num") epochS
+
whenJust (M.lookup nodeId allSettings) $ \settings -> do
setDisplayedValue nodeId displayed (anId <> "__node-era") $ esEra settings
- whenJust (M.lookup nodeId allMetrics) $ \(ekgStore, _) -> do
- metrics <- liftIO $ getListOfMetrics ekgStore
- let epoch = fromMaybe "" $ lookup "cardano.node.epoch" metrics
- slotInEpoch = fromMaybe "" $ lookup "cardano.node.slotInEpoch" metrics
- updateEpochInfo settings nodeId epoch slotInEpoch
+ updateEpochInfo settings nodeId epochS
where
- updateEpochInfo settings nodeId@(NodeId anId) epochS slotInEpochS =
- unless (T.null epochS || T.null slotInEpochS) $ do
+ updateEpochInfo settings (NodeId anId) epochS =
+ unless (T.null epochS) $ do
let epochNum = readInt epochS 0
- _slotInEpoch = readInt slotInEpochS 0
- setDisplayedValue nodeId displayed (anId <> "__node-epoch-num") epochS
case getEndOfCurrentEpoch settings epochNum of
Nothing -> return ()
Just (_start, end) -> do
diff --git a/cardano-tracer/src/Cardano/Tracer/Handlers/RTView/Update/Peers.hs b/cardano-tracer/src/Cardano/Tracer/Handlers/RTView/Update/Peers.hs
index 4dcbffa88e1..9b0ba9f47a6 100644
--- a/cardano-tracer/src/Cardano/Tracer/Handlers/RTView/Update/Peers.hs
+++ b/cardano-tracer/src/Cardano/Tracer/Handlers/RTView/Update/Peers.hs
@@ -5,73 +5,70 @@ module Cardano.Tracer.Handlers.RTView.Update.Peers
( updateNodesPeers
) where
+import Control.Concurrent.Extra (Lock)
import Control.Concurrent.STM.TVar (readTVarIO)
import Control.Monad (forM_, void)
import Control.Monad.Extra (whenJustM)
import Data.List (find)
import Data.List.Extra (notNull)
-import qualified Data.Map.Strict as M
import Data.Maybe (mapMaybe)
import Data.Set ((\\))
import qualified Data.Set as S
-import Data.Text (Text, unpack)
+import Data.Text (unpack)
import qualified Data.Text as T
import qualified Graphics.UI.Threepenny as UI
import Graphics.UI.Threepenny.Core
+import Cardano.Node.Tracing.Peers
+
import Cardano.Tracer.Handlers.RTView.State.Peers
-import Cardano.Tracer.Handlers.RTView.State.TraceObjects
import Cardano.Tracer.Handlers.RTView.UI.HTML.Node.Peers
import Cardano.Tracer.Handlers.RTView.UI.Utils
+import Cardano.Tracer.Handlers.RTView.Update.Utils
import Cardano.Tracer.Types
import Cardano.Tracer.Utils
updateNodesPeers
:: UI.Window
+ -> ConnectedNodes
+ -> DataPointRequestors
+ -> Lock
-> Peers
- -> SavedTraceObjects
-> UI ()
-updateNodesPeers window displayedPeers savedTO = do
- savedTraceObjects <- liftIO $ readTVarIO savedTO
- forM_ (M.toList savedTraceObjects) $ \(nodeId, savedTOForNode) ->
- forM_ (M.toList savedTOForNode) $ \(namespace, (trObValue, _, _)) ->
- case namespace of
- "Peers" -> doUpdatePeers window nodeId displayedPeers trObValue
- _ -> return ()
+updateNodesPeers window connectedNodes dpRequestors currentDPLock displayedPeers = do
+ connected <- liftIO $ readTVarIO connectedNodes
+ forM_ connected $ \nodeId -> do
+ whenJustM (liftIO $ askDataPoint dpRequestors currentDPLock nodeId "NodePeers") $
+ doUpdatePeers window nodeId displayedPeers
doUpdatePeers
:: UI.Window
-> NodeId
-> Peers
- -> Text
+ -> NodePeers
-> UI ()
-doUpdatePeers window nodeId@(NodeId anId) displayedPeers trObValue =
- if "NodeKernelPeers" `T.isInfixOf` trObValue
- then return () -- It was empty 'TraceObject' (without useful info), ignore it.
- else do
- -- Update peers number.
- setTextValue (anId <> "__node-peers-num") (showT (length peersParts))
- -- If there is at least one connected peer, we enable 'Details' button.
- findAndSet (set UI.enabled $ notNull peersParts)
- window $ anId <> "__node-peers-details-button"
- -- Update particular info about peers.
- let connectedPeers = getConnectedPeers
- connectedPeersAddresses = getConnectedPeersAddresses
- displayedPeersAddresses <- liftIO $ getPeersAddresses displayedPeers nodeId
- if displayedPeersAddresses /= connectedPeersAddresses
- then do
- -- There are some changes with number of peers: some new were connected
- -- and/or some displayed ones were disconnected.
- let disconnectedPeers = displayedPeersAddresses \\ connectedPeersAddresses -- Not in connected
- newlyConnectedPeers = connectedPeersAddresses \\ displayedPeersAddresses -- Not in displayed
- deleteRowsForDisconnected disconnectedPeers
- addRowsForNewlyConnected newlyConnectedPeers connectedPeers
- else
- -- No changes with number of peers, only their data was changed.
- updateConnectedPeersData connectedPeers
+doUpdatePeers window nodeId@(NodeId anId) displayedPeers (NodePeers peersParts) = do
+ -- Update peers number.
+ setTextValue (anId <> "__node-peers-num") (showT (length peersParts))
+ -- If there is at least one connected peer, we enable 'Details' button.
+ findAndSet (set UI.enabled $ notNull peersParts)
+ window $ anId <> "__node-peers-details-button"
+ -- Update particular info about peers.
+ let connectedPeers = getConnectedPeers
+ connectedPeersAddresses = getConnectedPeersAddresses
+ displayedPeersAddresses <- liftIO $ getPeersAddresses displayedPeers nodeId
+ if displayedPeersAddresses /= connectedPeersAddresses
+ then do
+ -- There are some changes with number of peers: some new were connected
+ -- and/or some displayed ones were disconnected.
+ let disconnectedPeers = displayedPeersAddresses \\ connectedPeersAddresses -- Not in connected
+ newlyConnectedPeers = connectedPeersAddresses \\ displayedPeersAddresses -- Not in displayed
+ deleteRowsForDisconnected disconnectedPeers
+ addRowsForNewlyConnected newlyConnectedPeers connectedPeers
+ else
+ -- No changes with number of peers, only their data was changed.
+ updateConnectedPeersData connectedPeers
where
- peersParts = T.splitOn "," trObValue
-
getConnectedPeers = S.fromList $
mapMaybe
(\peerPart -> let peerData = T.words peerPart in
diff --git a/cardano-tracer/src/Cardano/Tracer/Handlers/RTView/Update/Reload.hs b/cardano-tracer/src/Cardano/Tracer/Handlers/RTView/Update/Reload.hs
index d4ebf62d189..adf95996c2b 100644
--- a/cardano-tracer/src/Cardano/Tracer/Handlers/RTView/Update/Reload.hs
+++ b/cardano-tracer/src/Cardano/Tracer/Handlers/RTView/Update/Reload.hs
@@ -5,6 +5,7 @@ module Cardano.Tracer.Handlers.RTView.Update.Reload
( updateUIAfterReload
) where
+import Control.Concurrent.Extra (Lock)
import Control.Concurrent.STM.TVar (readTVarIO)
import Data.List.NonEmpty (NonEmpty)
import qualified Graphics.UI.Threepenny as UI
@@ -23,6 +24,7 @@ updateUIAfterReload
-> ConnectedNodes
-> DisplayedElements
-> DataPointRequestors
+ -> Lock
-> NonEmpty LoggingParams
-> Colors
-> DatasetsIndices
@@ -30,7 +32,7 @@ updateUIAfterReload
-> UI.Timer
-> UI.Timer
-> UI ()
-updateUIAfterReload window connectedNodes displayedElements dpRequestors
+updateUIAfterReload window connectedNodes displayedElements dpRequestors currentDPLock
loggingConfig colors datasetIndices nodesErrors updateErrorsTimer
noNodesProgressTimer = do
-- Ok, web-page was reload (i.e. it's the first update after DOM-rendering),
@@ -44,6 +46,6 @@ updateUIAfterReload window connectedNodes displayedElements dpRequestors
updateErrorsTimer
displayedElements
checkNoNodesState window connected noNodesProgressTimer
- askNSetNodeInfo window dpRequestors connected displayedElements
+ askNSetNodeInfo window dpRequestors currentDPLock connected displayedElements
addDatasetsForConnected window connected colors datasetIndices displayedElements
liftIO $ updateDisplayedElements displayedElements connected
diff --git a/cardano-tracer/src/Cardano/Tracer/Handlers/RTView/Update/Resources.hs b/cardano-tracer/src/Cardano/Tracer/Handlers/RTView/Update/Resources.hs
index 33f81fea789..85437740c75 100644
--- a/cardano-tracer/src/Cardano/Tracer/Handlers/RTView/Update/Resources.hs
+++ b/cardano-tracer/src/Cardano/Tracer/Handlers/RTView/Update/Resources.hs
@@ -29,14 +29,14 @@ updateResourcesHistory
-> IO ()
updateResourcesHistory nodeId (ResHistory rHistory) lastResources metricName metricValue now =
case metricName of
- "stat.cputicks" -> updateCPUUsage
- "mem.resident" -> updateRSSMemory
- "rts.gcLiveBytes" -> updateGCLiveMemory
- "rts.gcMajorNum" -> updateGCMajorNum
- "rts.gcMinorNum" -> updateGCMinorNum
- "rts.gcticks" -> updateCPUTimeGC
- "rts.mutticks" -> updateCPUTimeApp
- "rts.stat.threads" -> updateThreadsNum
+ "Resources.Stat.Cputicks" -> updateCPUUsage
+ "Resources.mem.Resident" -> updateRSSMemory
+ "Resources.RTS.GcLiveBytes" -> updateGCLiveMemory
+ "Resources.RTS.GcMajorNum" -> updateGCMajorNum
+ "Resources.RTS.GcMinorNum" -> updateGCMinorNum
+ "Resources.RTS.Gcticks" -> updateCPUTimeGC
+ "Resources.RTS.Mutticks" -> updateCPUTimeApp
+ "Resources.RTS.Stat.Threads" -> updateThreadsNum
_ -> return ()
where
updateCPUUsage =
diff --git a/cardano-tracer/src/Cardano/Tracer/Handlers/RTView/Update/Transactions.hs b/cardano-tracer/src/Cardano/Tracer/Handlers/RTView/Update/Transactions.hs
index a4fb685523b..499fed21b03 100644
--- a/cardano-tracer/src/Cardano/Tracer/Handlers/RTView/Update/Transactions.hs
+++ b/cardano-tracer/src/Cardano/Tracer/Handlers/RTView/Update/Transactions.hs
@@ -22,9 +22,9 @@ updateTransactionsHistory
-> IO ()
updateTransactionsHistory nodeId (TXHistory tHistory) metricName metricValue now =
case metricName of
- "cardano.node.txsProcessedNum" -> updateTxsProcessedNum
- "cardano.node.mempoolBytes" -> updateMempoolBytes
- "cardano.node.txsInMempool" -> updateTxsInMempool
+ "Mempool.TxsProcessedNum" -> updateTxsProcessedNum
+ "Mempool.MempoolBytes" -> updateMempoolBytes
+ "Mempool.TxsInMempool" -> updateTxsInMempool
_ -> return ()
where
updateTxsProcessedNum =
diff --git a/cardano-tracer/src/Cardano/Tracer/Handlers/RTView/Update/Utils.hs b/cardano-tracer/src/Cardano/Tracer/Handlers/RTView/Update/Utils.hs
index 2ec31cdad2c..08fb44dd181 100644
--- a/cardano-tracer/src/Cardano/Tracer/Handlers/RTView/Update/Utils.hs
+++ b/cardano-tracer/src/Cardano/Tracer/Handlers/RTView/Update/Utils.hs
@@ -1,3 +1,4 @@
+{-# LANGUAGE LambdaCase #-}
{-# LANGUAGE NumericUnderscores #-}
module Cardano.Tracer.Handlers.RTView.Update.Utils
@@ -9,6 +10,7 @@ module Cardano.Tracer.Handlers.RTView.Update.Utils
, nullTime
) where
+import Control.Concurrent.Extra (Lock, withLock)
import Control.Concurrent.STM.TVar (readTVarIO)
import Data.Aeson (FromJSON, decode')
import qualified Data.Map.Strict as M
@@ -35,17 +37,17 @@ import Cardano.Tracer.Types
askDataPoint
:: FromJSON a
=> DataPointRequestors
+ -> Lock
-> NodeId
-> DataPointName
-> IO (Maybe a)
-askDataPoint dpRequestors nodeId dpName = do
+askDataPoint dpRequestors currentDPLock nodeId dpName = withLock currentDPLock $ do
requestors <- readTVarIO dpRequestors
case M.lookup nodeId requestors of
Nothing -> return Nothing
- Just dpRequestor -> do
- dp <- askForDataPoints dpRequestor [dpName]
- case lookup dpName dp of
- Just (Just rawValue) -> return $ decode' rawValue
+ Just dpRequestor ->
+ askForDataPoints dpRequestor [dpName] >>= \case
+ [(_, Just rawDPValue)] -> return $ decode' rawDPValue
_ -> return Nothing
-- | Converts a timestamp to seconds since Unix epoch.
diff --git a/cardano-tracer/src/Cardano/Tracer/Run.hs b/cardano-tracer/src/Cardano/Tracer/Run.hs
index ead9aa55c9b..b2bc2079f0d 100644
--- a/cardano-tracer/src/Cardano/Tracer/Run.hs
+++ b/cardano-tracer/src/Cardano/Tracer/Run.hs
@@ -39,8 +39,9 @@ doRunCardanoTracer config protocolsBrake dpRequestors = do
connectedNodes <- initConnectedNodes
acceptedMetrics <- initAcceptedMetrics
currentLogLock <- newLock
+ currentDPLock <- newLock
savedTO <- initSavedTraceObjects
- eventsQueues <- initEventsQueues dpRequestors
+ eventsQueues <- initEventsQueues dpRequestors currentDPLock
void . sequenceConcurrently $
[ runLogsRotator config currentLogLock
, runMetricsServers config connectedNodes acceptedMetrics
@@ -48,5 +49,5 @@ doRunCardanoTracer config protocolsBrake dpRequestors = do
dpRequestors protocolsBrake currentLogLock
eventsQueues
, runRTView config connectedNodes acceptedMetrics savedTO
- dpRequestors eventsQueues
+ dpRequestors currentDPLock eventsQueues
]
diff --git a/cardano-tracer/test/Cardano/Tracer/Test/Acceptor.hs b/cardano-tracer/test/Cardano/Tracer/Test/Acceptor.hs
index 842c72b5205..a960fb8a283 100644
--- a/cardano-tracer/test/Cardano/Tracer/Test/Acceptor.hs
+++ b/cardano-tracer/test/Cardano/Tracer/Test/Acceptor.hs
@@ -38,7 +38,8 @@ launchAcceptorsSimple mode localSock dpName = do
acceptedMetrics <- initAcceptedMetrics
savedTO <- initSavedTraceObjects
currentLogLock <- newLock
- eventsQueues <- initEventsQueues dpRequestors
+ currentDPLock <- newLock
+ eventsQueues <- initEventsQueues dpRequestors currentDPLock
void . sequenceConcurrently $
[ runAcceptors mkConfig connectedNodes acceptedMetrics savedTO
dpRequestors protocolsBrake currentLogLock eventsQueues
diff --git a/doc/new-tracing/tracers_doc_generated.md b/doc/new-tracing/tracers_doc_generated.md
index 6d0a2f47745..9ca066789b2 100644
--- a/doc/new-tracing/tracers_doc_generated.md
+++ b/doc/new-tracing/tracers_doc_generated.md
@@ -190,6 +190,7 @@
1. [RollBackward](#chainsyncremotereceiverollbackward)
1. [RollForward](#chainsyncremotereceiverollforward)
1. __Send__
+<<<<<<< HEAD
1. [AwaitReply](#chainsyncremotesendawaitreply)
1. [Done](#chainsyncremotesenddone)
1. [FindIntersect](#chainsyncremotesendfindintersect)
@@ -221,6 +222,110 @@
1. [Update](#chainsyncserverblockupdate)
1. __ServerHeader__
1. [Update](#chainsyncserverheaderupdate)
+=======
+ 1. [AwaitReply](#chainsyncserialisednodetonodesendawaitreply)
+ 1. [Done](#chainsyncserialisednodetonodesenddone)
+ 1. [FindIntersect](#chainsyncserialisednodetonodesendfindintersect)
+ 1. [IntersectFound](#chainsyncserialisednodetonodesendintersectfound)
+ 1. [IntersectNotFound](#chainsyncserialisednodetonodesendintersectnotfound)
+ 1. [RequestNext](#chainsyncserialisednodetonodesendrequestnext)
+ 1. [RollBackward](#chainsyncserialisednodetonodesendrollbackward)
+ 1. [RollForward](#chainsyncserialisednodetonodesendrollforward)
+1. __ChainSyncServerBlock__
+ 1. __ChainSyncServerEvent__
+ 1. __Update__
+ 1. [Update](#chainsyncserverblockchainsyncservereventupdateupdate)
+1. __ChainSyncServerHeader__
+ 1. __ChainSyncServerEvent__
+ 1. __Update__
+ 1. [Update](#chainsyncserverheaderchainsyncservereventupdateupdate)
+1. __ConnectionManager__
+ 1. [Connect](#connectionmanagerconnect)
+ 1. [ConnectError](#connectionmanagerconnecterror)
+ 1. [ConnectionCleanup](#connectionmanagerconnectioncleanup)
+ 1. [ConnectionExists](#connectionmanagerconnectionexists)
+ 1. [ConnectionFailure](#connectionmanagerconnectionfailure)
+ 1. [ConnectionHandler](#connectionmanagerconnectionhandler)
+ 1. [ConnectionManagerCounters](#connectionmanagerconnectionmanagercounters)
+ 1. [ConnectionNotFound](#connectionmanagerconnectionnotfound)
+ 1. [ConnectionTimeWait](#connectionmanagerconnectiontimewait)
+ 1. [ConnectionTimeWaitDone](#connectionmanagerconnectiontimewaitdone)
+ 1. [ForbiddenConnection](#connectionmanagerforbiddenconnection)
+ 1. [ForbiddenOperation](#connectionmanagerforbiddenoperation)
+ 1. [ImpossibleConnection](#connectionmanagerimpossibleconnection)
+ 1. [IncludeConnection](#connectionmanagerincludeconnection)
+ 1. [PruneConnections](#connectionmanagerpruneconnections)
+ 1. [Shutdown](#connectionmanagershutdown)
+ 1. [State](#connectionmanagerstate)
+ 1. [TerminatedConnection](#connectionmanagerterminatedconnection)
+ 1. [TerminatingConnection](#connectionmanagerterminatingconnection)
+ 1. [UnexpectedlyFalseAssertion](#connectionmanagerunexpectedlyfalseassertion)
+ 1. [UnknownConnection](#connectionmanagerunknownconnection)
+ 1. [UnregisterConnection](#connectionmanagerunregisterconnection)
+1. __ConnectionManagerTransition__
+ 1. [ConnectionManagerTransition](#connectionmanagertransitionconnectionmanagertransition)
+1. __DNSResolver__
+ 1. [LookupAAAAError](#dnsresolverlookupaaaaerror)
+ 1. [LookupAAAAResult](#dnsresolverlookupaaaaresult)
+ 1. [LookupAError](#dnsresolverlookupaerror)
+ 1. [LookupAResult](#dnsresolverlookuparesult)
+ 1. [LookupException](#dnsresolverlookupexception)
+ 1. [LookupIPv4First](#dnsresolverlookupipv4first)
+ 1. [LookupIPv6First](#dnsresolverlookupipv6first)
+1. __DNSSubscription__
+ 1. __DNS__
+ 1. [AllocateSocket](#dnssubscriptiondnsallocatesocket)
+ 1. [ApplicationException](#dnssubscriptiondnsapplicationexception)
+ 1. [CloseSocket](#dnssubscriptiondnsclosesocket)
+ 1. [ConnectEnd](#dnssubscriptiondnsconnectend)
+ 1. [ConnectException](#dnssubscriptiondnsconnectexception)
+ 1. [ConnectStart](#dnssubscriptiondnsconnectstart)
+ 1. [ConnectionExist](#dnssubscriptiondnsconnectionexist)
+ 1. [MissingLocalAddress](#dnssubscriptiondnsmissinglocaladdress)
+ 1. [Restart](#dnssubscriptiondnsrestart)
+ 1. [SkippingPeer](#dnssubscriptiondnsskippingpeer)
+ 1. [SocketAllocationException](#dnssubscriptiondnssocketallocationexception)
+ 1. [Start](#dnssubscriptiondnsstart)
+ 1. [SubscriptionFailed](#dnssubscriptiondnssubscriptionfailed)
+ 1. [SubscriptionRunning](#dnssubscriptiondnssubscriptionrunning)
+ 1. [SubscriptionWaiting](#dnssubscriptiondnssubscriptionwaiting)
+ 1. [SubscriptionWaitingNewConnection](#dnssubscriptiondnssubscriptionwaitingnewconnection)
+ 1. [TryConnectToPeer](#dnssubscriptiondnstryconnecttopeer)
+ 1. [UnsupportedRemoteAddr](#dnssubscriptiondnsunsupportedremoteaddr)
+1. __DebugPeerSelection__
+ 1. __DebugPeerSelection__
+ 1. [GovernorState](#debugpeerselectiondebugpeerselectiongovernorstate)
+1. __DebugPeerSelectionResponder__
+ 1. __DebugPeerSelection__
+ 1. [GovernorState](#debugpeerselectionresponderdebugpeerselectiongovernorstate)
+1. __DiffusionInit__
+ 1. [ConfiguringLocalSocket](#diffusioninitconfiguringlocalsocket)
+ 1. [ConfiguringServerSocket](#diffusioninitconfiguringserversocket)
+ 1. [CreateSystemdSocketForSnocketPath](#diffusioninitcreatesystemdsocketforsnocketpath)
+ 1. [CreatedLocalSocket](#diffusioninitcreatedlocalsocket)
+ 1. [CreatingServerSocket](#diffusioninitcreatingserversocket)
+ 1. [DiffusionErrored](#diffusioninitdiffusionerrored)
+ 1. [ListeningLocalSocket](#diffusioninitlisteninglocalsocket)
+ 1. [ListeningServerSocket](#diffusioninitlisteningserversocket)
+ 1. [LocalSocketUp](#diffusioninitlocalsocketup)
+ 1. [RunLocalServer](#diffusioninitrunlocalserver)
+ 1. [RunServer](#diffusioninitrunserver)
+ 1. [ServerSocketUp](#diffusioninitserversocketup)
+ 1. [UnsupportedLocalSystemdSocket](#diffusioninitunsupportedlocalsystemdsocket)
+ 1. [UnsupportedReadySocketCase](#diffusioninitunsupportedreadysocketcase)
+ 1. [UsingSystemdSocket](#diffusioninitusingsystemdsocket)
+1. __ErrorPolicy__
+ 1. [AcceptException](#errorpolicyacceptexception)
+ 1. [KeepSuspended](#errorpolicykeepsuspended)
+ 1. [LocalNodeError](#errorpolicylocalnodeerror)
+ 1. [ResumeConsumer](#errorpolicyresumeconsumer)
+ 1. [ResumePeer](#errorpolicyresumepeer)
+ 1. [ResumeProducer](#errorpolicyresumeproducer)
+ 1. [SuspendConsumer](#errorpolicysuspendconsumer)
+ 1. [SuspendPeer](#errorpolicysuspendpeer)
+ 1. [UnhandledApplicationException](#errorpolicyunhandledapplicationexception)
+ 1. [UnhandledConnectionException](#errorpolicyunhandledconnectionexception)
+>>>>>>> 152cc0649 (cardano-node: NodeStartupInfo as datapoint.)
1. __Forge__
1. [KESInfo](#forgekesinfo)
1. __Loop__
@@ -581,11 +686,19 @@
1. [NodeTracingOnlineConfiguring](#nodestatenodetracingonlineconfiguring)
1. [Resources](#resources)
1. __Shutdown__
+<<<<<<< HEAD
1. [Abnormal](#shutdownabnormal)
1. [ArmedAt](#shutdownarmedat)
1. [Requested](#shutdownrequested)
1. [Requesting](#shutdownrequesting)
1. [UnexpectedInput](#shutdownunexpectedinput)
+=======
+ 1. [AbnormalShutdown](#shutdownabnormalshutdown)
+ 1. [RequestingShutdown](#shutdownrequestingshutdown)
+ 1. [ShutdownArmedAt](#shutdownshutdownarmedat)
+ 1. [ShutdownRequested](#shutdownshutdownrequested)
+ 1. [ShutdownUnexpectedInput](#shutdownshutdownunexpectedinput)
+>>>>>>> 152cc0649 (cardano-node: NodeStartupInfo as datapoint.)
1. __Startup__
1. [Byron](#startupbyron)
1. [Common](#startupcommon)
@@ -698,6 +811,7 @@
1. [SendMsgReply](#txsubmissiontxoutboundsendmsgreply)
## [Metrics](#metrics)
+<<<<<<< HEAD
1. __BlockFetch__
1. [BlocksServed](#blockfetchblocksserved)
1. [ConnectedPeers](#blockfetchconnectedpeers)
@@ -783,9 +897,106 @@
1. [Accepted](#txsubmissionaccepted)
1. [Rejected](#txsubmissionrejected)
1. [Submitted](#txsubmissionsubmitted)
+=======
+1. [Block replay progress (%)](#block replay progress (%))
+1. [blocksForgedNum](#blocksforgednum)
+1. __cardano__
+ 1. __node__
+ 1. [aboutToLeadSlotLast](#cardanonodeabouttoleadslotlast)
+ 1. [aboutToLeadSlotLast](#cardanonodeabouttoleadslotlast)
+ 1. [adoptedSlotLast](#cardanonodeadoptedslotlast)
+ 1. [blockContext](#cardanonodeblockcontext)
+ 1. [blockFromFuture](#cardanonodeblockfromfuture)
+ 1. [blocks](#cardanonodeblocks)
+ 1. [blocks](#cardanonodeblocks)
+ 1. [connectedPeers](#cardanonodeconnectedpeers)
+ 1. __connectionManager__
+ 1. [duplexConns](#cardanonodeconnectionmanagerduplexconns)
+ 1. [duplexConns](#cardanonodeconnectionmanagerduplexconns)
+ 1. [fullDuplexConns](#cardanonodeconnectionmanagerfullduplexconns)
+ 1. [fullDuplexConns](#cardanonodeconnectionmanagerfullduplexconns)
+ 1. [inboundConns](#cardanonodeconnectionmanagerinboundconns)
+ 1. [inboundConns](#cardanonodeconnectionmanagerinboundconns)
+ 1. [outboundConns](#cardanonodeconnectionmanageroutboundconns)
+ 1. [outboundConns](#cardanonodeconnectionmanageroutboundconns)
+ 1. [unidirectionalConns](#cardanonodeconnectionmanagerunidirectionalconns)
+ 1. [unidirectionalConns](#cardanonodeconnectionmanagerunidirectionalconns)
+ 1. [couldNotForgeSlotLast](#cardanonodecouldnotforgeslotlast)
+ 1. [couldNotForgeSlotLast](#cardanonodecouldnotforgeslotlast)
+ 1. [currentKESPeriod](#cardanonodecurrentkesperiod)
+ 1. [delegMapSize](#cardanonodedelegmapsize)
+ 1. [density](#cardanonodedensity)
+ 1. [density](#cardanonodedensity)
+ 1. [epoch](#cardanonodeepoch)
+ 1. [epoch](#cardanonodeepoch)
+ 1. [forgedInvalidSlotLast](#cardanonodeforgedinvalidslotlast)
+ 1. [forgedSlotLast](#cardanonodeforgedslotlast)
+ 1. __inbound-governor__
+ 1. [cold](#cardanonodeinbound-governorcold)
+ 1. [cold](#cardanonodeinbound-governorcold)
+ 1. [hot](#cardanonodeinbound-governorhot)
+ 1. [hot](#cardanonodeinbound-governorhot)
+ 1. [idle](#cardanonodeinbound-governoridle)
+ 1. [idle](#cardanonodeinbound-governoridle)
+ 1. [warm](#cardanonodeinbound-governorwarm)
+ 1. [warm](#cardanonodeinbound-governorwarm)
+ 1. [ledgerState](#cardanonodeledgerstate)
+ 1. [ledgerView](#cardanonodeledgerview)
+ 1. [mempoolBytes](#cardanonodemempoolbytes)
+ 1. [mempoolBytes](#cardanonodemempoolbytes)
+ 1. [mempoolBytes](#cardanonodemempoolbytes)
+ 1. [mempoolBytes](#cardanonodemempoolbytes)
+ 1. __metrics__
+ 1. __served__
+ 1. [header](#cardanonodemetricsservedheader)
+ 1. [nodeCannotForge](#cardanonodenodecannotforge)
+ 1. [nodeIsLeader](#cardanonodenodeisleader)
+ 1. [nodeNotLeader](#cardanonodenodenotleader)
+ 1. [notAdoptedSlotLast](#cardanonodenotadoptedslotlast)
+ 1. [operationalCertificateExpiryKESPeriod](#cardanonodeoperationalcertificateexpirykesperiod)
+ 1. [operationalCertificateStartKESPeriod](#cardanonodeoperationalcertificatestartkesperiod)
+ 1. __peerSelection__
+ 1. [cold](#cardanonodepeerselectioncold)
+ 1. [hot](#cardanonodepeerselectionhot)
+ 1. [warm](#cardanonodepeerselectionwarm)
+ 1. [remainingKESPeriods](#cardanonoderemainingkesperiods)
+ 1. __served__
+ 1. [block](#cardanonodeservedblock)
+ 1. [slotInEpoch](#cardanonodeslotinepoch)
+ 1. [slotInEpoch](#cardanonodeslotinepoch)
+ 1. [slotIsImmutable](#cardanonodeslotisimmutable)
+ 1. [slots](#cardanonodeslots)
+ 1. [slots](#cardanonodeslots)
+ 1. __submissions__
+ 1. [accepted](#cardanonodesubmissionsaccepted)
+ 1. [rejected](#cardanonodesubmissionsrejected)
+ 1. [submitted](#cardanonodesubmissionssubmitted)
+ 1. [txsInMempool](#cardanonodetxsinmempool)
+ 1. [txsInMempool](#cardanonodetxsinmempool)
+ 1. [txsInMempool](#cardanonodetxsinmempool)
+ 1. [txsInMempool](#cardanonodetxsinmempool)
+ 1. [txsProcessedNum](#cardanonodetxsprocessednum)
+ 1. [utxoSize](#cardanonodeutxosize)
+1. __mem__
+ 1. [resident](#memresident)
+1. [nodeCannotForgeNum](#nodecannotforgenum)
+1. [nodeIsLeaderNum](#nodeisleadernum)
+1. [peersFromNodeKernel](#peersfromnodekernel)
+1. __rts__
+ 1. [gcLiveBytes](#rtsgclivebytes)
+ 1. [gcMajorNum](#rtsgcmajornum)
+ 1. [gcMinorNum](#rtsgcminornum)
+ 1. [gcticks](#rtsgcticks)
+ 1. [mutticks](#rtsmutticks)
+ 1. [threads](#rtsthreads)
+1. [slotsMissed](#slotsmissed)
+1. __stat__
+ 1. [cputicks](#statcputicks)
+>>>>>>> 152cc0649 (cardano-node: NodeStartupInfo as datapoint.)
## [Datapoints](#datapoints)
1. [NodeInfo](#nodeinfo)
+1. [NodeStartupInfo](#nodestartupinfo)
## Trace Messages
### BlockFetch.Client.AcknowledgedFetchRequest
@@ -3281,6 +3492,7 @@ Backends:
`Forwarder`
Filtered by config value: `Notice`
+<<<<<<< HEAD
### ChainSync.ServerBlock.Update
@@ -3310,6 +3522,9 @@ Backends:
Filtered by config value: `Notice`
### Forge.KESInfo
+=======
+### ChainSyncServerBlock.ChainSyncServerEvent.Update.Update
+>>>>>>> 152cc0649 (cardano-node: NodeStartupInfo as datapoint.)
> kesStartPeriod
@@ -3325,6 +3540,7 @@ Backends:
`Forwarder`
Filtered by config value: `Info`
+<<<<<<< HEAD
### Forge.Loop.AdoptedBlock
@@ -3368,6 +3584,9 @@ Backends:
Filtered by config value: `Info`
### Forge.Loop.DidntAdoptBlock
+=======
+### ChainSyncServerHeader.ChainSyncServerEvent.Update.Update
+>>>>>>> 152cc0649 (cardano-node: NodeStartupInfo as datapoint.)
> We did not adopt the block we produced, but the block was valid. We must have adopted a block that another leader of the same slot produced before we got the chance of adopting our own block. This is very rare, this warrants a warning.
@@ -3381,6 +3600,7 @@ Backends:
`Forwarder`
Filtered by config value: `Info`
+<<<<<<< HEAD
### Forge.Loop.ForgeStateUpdateError
@@ -3394,6 +3614,9 @@ Backends:
`Stdout MachineFormat`,
`Forwarder`
Filtered by config value: `Info`
+=======
+### ConnectionManager.Connect
+>>>>>>> 152cc0649 (cardano-node: NodeStartupInfo as datapoint.)
### Forge.Loop.ForgedBlock
@@ -7853,7 +8076,11 @@ Backends:
`Forwarder`
Filtered by config value: `Notice`
+<<<<<<< HEAD
### Startup.DiffusionInit.LocalSocketUp
+=======
+### Shutdown.ShutdownArmedAt
+>>>>>>> 152cc0649 (cardano-node: NodeStartupInfo as datapoint.)
> LocalSocketUp
@@ -9308,6 +9535,7 @@ Mempool.RemoveTxs
### Mempool.TxsProcessedNum
+<<<<<<< HEAD
Dispatched by:
@@ -9333,6 +9561,17 @@ Net.ConnectionManager.Local.ConnectionManagerCounters
Dispatched by:
Net.ConnectionManager.Remote.ConnectionManagerCounters
+=======
+### cardano.node.metrics.served.header
+
+***
+A counter triggered only on header event
+***
+
+
+Dispatched by:
+ChainSyncServerHeader.ChainSyncServerEvent.Update.Update
+>>>>>>> 152cc0649 (cardano-node: NodeStartupInfo as datapoint.)
### Net.ConnectionManager.FullDuplexConns
@@ -9561,7 +9800,27 @@ TxSubmission.TxInbound.Collected
> _niSystemStartTime_: How long did the start of the node took.
+<<<<<<< HEAD
Configuration: TraceConfig {tcOptions = fromList [([],[ConfSeverity {severity = Notice},ConfDetail {detail = DNormal},ConfBackend {backends = [Stdout MachineFormat,EKGBackend,Forwarder]}]),(["AcceptPolicy"],[ConfSeverity {severity = Info}]),(["BlockFetchClient","CompletedBlockFetch"],[ConfLimiter {maxFrequency = 2.0}]),(["ChainDB"],[ConfSeverity {severity = Info}]),(["ChainDB","AddBlockEvent","AddBlockValidation","ValidCandidate"],[ConfLimiter {maxFrequency = 2.0}]),(["ChainDB","AddBlockEvent","AddedBlockToQueue"],[ConfLimiter {maxFrequency = 2.0}]),(["ChainDB","AddBlockEvent","AddedBlockToVolatileDB"],[ConfLimiter {maxFrequency = 2.0}]),(["ChainDB","CopyToImmutableDBEvent","CopiedBlockToImmutableDB"],[ConfLimiter {maxFrequency = 2.0}]),(["DNSResolver"],[ConfSeverity {severity = Info}]),(["DNSSubscription"],[ConfSeverity {severity = Info}]),(["DiffusionInit"],[ConfSeverity {severity = Info}]),(["ErrorPolicy"],[ConfSeverity {severity = Info}]),(["Forge"],[ConfSeverity {severity = Info}]),(["IpSubscription"],[ConfSeverity {severity = Info}]),(["LocalErrorPolicy"],[ConfSeverity {severity = Info}]),(["Mempool"],[ConfSeverity {severity = Info}]),(["Resources"],[ConfSeverity {severity = Info}])], tcForwarder = TraceOptionForwarder {tofConnQueueSize = 2000, tofDisconnQueueSize = 200000, tofVerbosity = Minimum}, tcNodeName = Nothing, tcPeerFrequency = Just 2000, tcResourceFrequency = Just 5000}
662 log messages.
-Generated at 2022-07-08 01:53:08.217148774 MSK.
\ No newline at end of file
+Generated at 2022-07-08 01:53:08.217148774 MSK.
+=======
+### NodeStartupInfo
+
+
+***
+Startup information about this node, required for RTView
+
+ _suiEra_: Name of the current era.
+ _suiSlotLength_: Slot length, in seconds.
+ _suiEpochLength_: Epoch length, in slots.
+ _suiSlotsPerKESPeriod_: KES period length, in slots.
+***
+
+
+Configuration: TraceConfig {tcOptions = fromList [([],[ConfSeverity {severity = Notice},ConfDetail {detail = DNormal},ConfBackend {backends = [Stdout MachineFormat,EKGBackend,Forwarder]}]),(["AcceptPolicy"],[ConfSeverity {severity = Info}]),(["BlockFetchClient","CompletedBlockFetch"],[ConfLimiter {maxFrequency = 2.0}]),(["ChainDB"],[ConfSeverity {severity = Info}]),(["ChainDB","AddBlockEvent","AddBlockValidation","ValidCandidate"],[ConfLimiter {maxFrequency = 2.0}]),(["ChainDB","AddBlockEvent","AddedBlockToQueue"],[ConfLimiter {maxFrequency = 2.0}]),(["ChainDB","AddBlockEvent","AddedBlockToVolatileDB"],[ConfLimiter {maxFrequency = 2.0}]),(["ChainDB","CopyToImmutableDBEvent","CopiedBlockToImmutableDB"],[ConfLimiter {maxFrequency = 2.0}]),(["DNSResolver"],[ConfSeverity {severity = Info}]),(["DNSSubscription"],[ConfSeverity {severity = Info}]),(["DiffusionInit"],[ConfSeverity {severity = Info}]),(["ErrorPolicy"],[ConfSeverity {severity = Info}]),(["Forge"],[ConfSeverity {severity = Info}]),(["IpSubscription"],[ConfSeverity {severity = Info}]),(["LocalErrorPolicy"],[ConfSeverity {severity = Info}]),(["Mempool"],[ConfSeverity {severity = Info}]),(["Resources"],[ConfSeverity {severity = Info}])], tcForwarder = TraceOptionForwarder {tofConnQueueSize = 2000, tofDisconnQueueSize = 200000, tofVerbosity = Minimum}, tcNodeName = Nothing, tcPeerFrequency = Just 2000, tcResourceFrequency = Just 5000}
+
+669 log messages.
+Generated at 2022-07-04 17:09:35.02423809 +04.
+>>>>>>> 152cc0649 (cardano-node: NodeStartupInfo as datapoint.)