Skip to content

Commit 93ec694

Browse files
author
Denis Shevchenko
committed
RTView: history backup, MVP
1 parent 657e416 commit 93ec694

File tree

12 files changed

+460
-111
lines changed

12 files changed

+460
-111
lines changed

cardano-tracer/cardano-tracer.cabal

+2
Original file line numberDiff line numberDiff line change
@@ -123,6 +123,7 @@ library
123123
, bytestring
124124
, cardano-git-rev
125125
, cardano-node
126+
, cassava
126127
, cborg
127128
, containers
128129
, contra-tracer
@@ -149,6 +150,7 @@ library
149150
, trace-dispatcher
150151
, trace-forward
151152
, unordered-containers
153+
, vector
152154
, yaml
153155

154156
if os(linux)

cardano-tracer/src/Cardano/Tracer/Handlers/RTView/Run.hs

+7
Original file line numberDiff line numberDiff line change
@@ -97,6 +97,13 @@ runRTView TracerConfig{logging, network, hasRTView}
9797
lastResources
9898
chainHistory
9999
txHistory
100+
, runHistoricalBackup
101+
connectedNodes
102+
chainHistory
103+
resourcesHistory
104+
txHistory
105+
dpRequestors
106+
currentDPLock
100107
, runEraSettingsUpdater
101108
connectedNodes
102109
eraSettings

cardano-tracer/src/Cardano/Tracer/Handlers/RTView/State/Historical.hs

+21-2
Original file line numberDiff line numberDiff line change
@@ -1,10 +1,13 @@
11
{-# LANGUAGE BangPatterns #-}
2+
{-# LANGUAGE FlexibleInstances #-}
3+
{-# LANGUAGE OverloadedStrings #-}
24

35
module Cardano.Tracer.Handlers.RTView.State.Historical
46
( BlockchainHistory (..)
57
, DataName (..)
68
, History
79
, HistoricalPoint
10+
, HistoricalPoints
811
, POSIXTime
912
, ResourcesHistory (..)
1013
, TransactionsHistory (..)
@@ -20,14 +23,19 @@ module Cardano.Tracer.Handlers.RTView.State.Historical
2023

2124
import Control.Concurrent.STM (atomically)
2225
import Control.Concurrent.STM.TVar (TVar, modifyTVar', newTVarIO, readTVarIO)
26+
import Control.Monad (mzero)
27+
import qualified Data.ByteString.Char8 as BSC
28+
import Data.Csv (FromField (..), ToField (..))
2329
import Data.Map.Strict (Map)
2430
import qualified Data.Map.Strict as M
2531
import Data.Set (Set)
2632
import qualified Data.Set as S
27-
import Data.Text (Text)
33+
import Data.Text (Text, isInfixOf)
34+
import Data.Text.Encoding (decodeUtf8)
2835
import Data.Text.Read (decimal, double)
2936
import Data.Time.Clock (UTCTime)
3037
import Data.Word (Word64)
38+
import Text.Printf (printf)
3139

3240
import Cardano.Tracer.Handlers.RTView.Update.Utils
3341
import Cardano.Tracer.Types (NodeId)
@@ -73,6 +81,17 @@ instance Num ValueH where
7381

7482
type HistoricalPoint = (POSIXTime, ValueH)
7583

84+
instance FromField ValueH where
85+
parseField s =
86+
let t = decodeUtf8 s in
87+
if "." `isInfixOf` t
88+
then either (const mzero) (return . ValueD . fst) $ double t
89+
else either (const mzero) (return . ValueI . fst) $ decimal t
90+
91+
instance ToField ValueH where
92+
toField (ValueI i) = toField i
93+
toField (ValueD d) = BSC.pack $ printf "%.3f" d
94+
7695
type HistoricalPoints = Set HistoricalPoint
7796

7897
-- | Historical points for particular data.
@@ -104,7 +123,7 @@ data DataName
104123
| TxsProcessedNumData
105124
| MempoolBytesData
106125
| TxsInMempoolData
107-
deriving (Eq, Ord)
126+
deriving (Eq, Ord, Read, Show)
108127

109128
type HistoricalData = Map DataName HistoricalPoints
110129
type History = TVar (Map NodeId HistoricalData)

cardano-tracer/src/Cardano/Tracer/Handlers/RTView/System.hs

+13-2
Original file line numberDiff line numberDiff line change
@@ -1,7 +1,8 @@
11
{-# LANGUAGE CPP #-}
22

33
module Cardano.Tracer.Handlers.RTView.System
4-
( getPathToChartsConfig
4+
( getPathToBackupDir
5+
, getPathToChartsConfig
56
, getPathToThemeConfig
67
, getPathsToNotificationsSettings
78
, getPathsToSSLCerts
@@ -59,6 +60,16 @@ getPathsToNotificationsSettings = do
5960
getPathToConfigDir :: IO FilePath
6061
getPathToConfigDir = do
6162
configDir <- D.getXdgDirectory D.XdgConfig ""
62-
let pathToRTViewConfigDir = configDir </> "cardano-rt-view"
63+
let pathToRTViewConfigDir = configDir </> rtViewRootDir
6364
D.createDirectoryIfMissing True pathToRTViewConfigDir
6465
return pathToRTViewConfigDir
66+
67+
getPathToBackupDir :: IO FilePath
68+
getPathToBackupDir = do
69+
dataDir <- D.getXdgDirectory D.XdgData ""
70+
let pathToRTViewBackupDir = dataDir </> rtViewRootDir </> "backup"
71+
D.createDirectoryIfMissing True pathToRTViewBackupDir
72+
return pathToRTViewBackupDir
73+
74+
rtViewRootDir :: FilePath
75+
rtViewRootDir = "cardano-rt-view"

cardano-tracer/src/Cardano/Tracer/Handlers/RTView/UI/Charts.hs

+1-1
Original file line numberDiff line numberDiff line change
@@ -284,7 +284,7 @@ readSavedChartsSettings = liftIO $
284284
[ (chartId, ChartSettings defaultTimeRangeInS defaultUpdatePeriodInS)
285285
| chartId <- chartsIds
286286
]
287-
defaultTimeRangeInS = 0 -- All time
287+
defaultTimeRangeInS = 21600 -- Last 6 hours
288288
defaultUpdatePeriodInS = 15
289289

290290
changeChartsToLightTheme :: UI ()

cardano-tracer/src/Cardano/Tracer/Handlers/RTView/UI/HTML/About.hs

+14-5
Original file line numberDiff line numberDiff line change
@@ -1,17 +1,17 @@
11
{-# LANGUAGE LambdaCase #-}
2-
{-# LANGUAGE MultiWayIf #-}
32

43
module Cardano.Tracer.Handlers.RTView.UI.HTML.About
54
( mkAboutInfo
65
) where
76

7+
import Data.List.Extra (lower)
88
import qualified Data.Text as T
99
import Data.Version (showVersion)
1010
import qualified Graphics.UI.Threepenny as UI
1111
import Graphics.UI.Threepenny.Core
1212
import System.Directory (makeAbsolute)
1313
import System.Environment (getArgs)
14-
import System.Info.Extra (isMac, isWindows)
14+
import System.Info (os)
1515

1616
import Cardano.Git.Rev (gitRev)
1717

@@ -80,9 +80,7 @@ mkAboutInfo = do
8080
, image "rt-view-href-icon" externalLinkSVG
8181
]
8282
, UI.p #. "mb-3" #+
83-
[ string $ if | isWindows -> "Windows"
84-
| isMac -> "macOS"
85-
| otherwise -> "Linux"
83+
[ string currentOS
8684
]
8785
, UI.p #. "mb-3" #+
8886
[ UI.div #. "field has-addons" #+
@@ -109,3 +107,14 @@ mkAboutInfo = do
109107
return info
110108
where
111109
commit = T.unpack . T.take 7 $ gitRev
110+
111+
currentOS :: String
112+
currentOS =
113+
case lower os of
114+
"darwin" -> "macOS"
115+
"mingw32" -> "Windows"
116+
"linux" -> "Linux"
117+
"freebsd" -> "FreeBSD"
118+
"netbsd" -> "NetBSD"
119+
"openbsd" -> "OpenBSD"
120+
_ -> "Unknown"

0 commit comments

Comments
 (0)