Skip to content

Commit

Permalink
cardano-node: More NodeVersionTracer
Browse files Browse the repository at this point in the history
  • Loading branch information
jutaro committed Apr 7, 2024
1 parent 2b2eabf commit a8991f1
Show file tree
Hide file tree
Showing 2 changed files with 66 additions and 29 deletions.
92 changes: 64 additions & 28 deletions cardano-node/src/Cardano/Node/Tracing/Tracers/NodeVersion.hs
Original file line number Diff line number Diff line change
@@ -1,13 +1,26 @@
{-# LANGUAGE OverloadedStrings #-}
{-# LANGUAGE RecordWildCards #-}
{-# LANGUAGE TemplateHaskell #-}

{-# OPTIONS_GHC -Wno-name-shadowing #-}

module Cardano.Node.Tracing.Tracers.NodeVersion
(
NodeVersion (..)
NodeVersionTrace (..)
, getNodeVersion
)
where

import Cardano.Git.Rev (gitRev)
import Data.Version
import Cardano.Logging
import Data.Aeson (toJSON, (.=))
import Data.Text (Text, intercalate, pack)

import Data.Version (Version (..), showVersion)

import Paths_cardano_node (version)
import System.Info (arch, compilerName, compilerVersion, os)
import Cardano.Git.Rev (gitRev)


data NodeVersionTrace = NodeVersionTrace
{ applicationName :: Text
Expand All @@ -25,19 +38,22 @@ getNodeVersion =
applicationVersion = version
osName = pack os
architecture = pack arch
compilerName = pack compilerName
compilerVersion = compilerVersion
gitRevision = gitRev
in NodeVersion {..}
compilerName = pack System.Info.compilerName
compilerVersion = System.Info.compilerVersion
gitRevision = $(gitRev)
in NodeVersionTrace {..}

instance MetaTrace NodeVersionTrace where
namespaceFor NodeVersion {} =
namespaceFor NodeVersionTrace {} =
Namespace [] ["NodeVersion"]
severityFor (Namespace _ ["NodeVersion"]) _ = Just Info
severityFor _ _ = Nothing
documentFor NodeVersion {} = Just "Node version information"

documentFor (Namespace _ ["NodeVersion"]) = Just "Node version information"

documentFor _ = Nothing
metricsDocFor NodeVersion {} =

metricsDocFor (Namespace _ ["NodeVersion"]) =
[("Cardano.Version.Major", "Cardano node version information")
,("Cardano.Version.Minor", "Cardano node version information")
,("Cardano.Version.Patch", "Cardano node version information")
Expand All @@ -53,18 +69,20 @@ instance MetaTrace NodeVersionTrace where
,("cardano_build_info", "Cardano node build info")
,("haskell_build_info", "Haskell compiler build information")
]
allNamespaces = [Namespace [] ["NodeVersion"]]
metricsDocFor _ = []

allNamespaces = [Namespace [] ["NodeVersion"]]

instance LogFormatting NodeVersionTrace where
forHuman NodeVersionTrace {..} = mconcat
[ "cardano-node ", pack (showVersion applicationVersion)
, " - ", pack os, "-", pack arch
, " - ", pack compilerName, "-", pack (showVersion compilerVersion)
, "git rev ", gitRev
, " - ", compilerName, "-", pack (showVersion compilerVersion)
, "git rev ", gitRevision
]

forMachine dtal NodeVersionTrace {..} = mconcat
forMachine _dtal NodeVersionTrace {..} = mconcat

[ "applicationName" .= applicationName
, "applicationVersion" .= toJSON applicationVersion
, "osName" .= osName
Expand All @@ -73,26 +91,44 @@ instance LogFormatting NodeVersionTrace where
, "compilerVersion" .= toJSON compilerVersion
, "gitRevision" .= gitRevision]

asMetrics nvt@NodeVersionTrace {..} = mconcat
asMetrics nvt@NodeVersionTrace {..} =
[ IntM "Cardano.Version.Major" (fromIntegral (getMajor applicationVersion))
, IntM "Cardano.Version.Minor" (fromIntegral (getMinor applicationVersion))
, IntM "Cardano.Version.Patch" (fromIntegral (getPatch applicationVersion))
, IntM ("Cardano.Version.VersionTags " ++ getVersionTags applicationVersion) 1
, IntM ("Cardano.Version.GitRevision " ++ gitRevision) 1
, IntM ("Cardano.CompilerName " ++ compilerName) 1
, IntM ("Cardano.CompilerMajor " (fromIntegral (getMajor applicationVersion)))
, IntM ("Cardano.CompilerMinor " (fromIntegral (getMinor applicationVersion)))
, IntM ("Cardano.CompilerPatch " (fromIntegral (getPatch applicationVersion)))
, IntM ("Cardano.CompilerTags " ++ getVersionTags applicationVersion) 1
, IntM ("Cardano.OSName " ++ osName) 1
, IntM ("Cardano.Architecture " ++ architecture) 1
, IntM ("cardano_build_info " ++ getCardanoBuildInfo nvt) 1
, IntM ("haskell_build_info " ++ getHaskellBuildInfo nvt) 1
, IntM ("Cardano.Version.VersionTags " <> getVersionTags applicationVersion) 1
, IntM ("Cardano.Version.GitRevision " <> gitRevision) 1
, IntM ("Cardano.CompilerName " <> compilerName) 1
, IntM "Cardano.CompilerMajor " (fromIntegral (getMajor compilerVersion))
, IntM "Cardano.CompilerMinor " (fromIntegral (getMinor compilerVersion))
, IntM "Cardano.CompilerPatch " (fromIntegral (getPatch compilerVersion))
, IntM ("Cardano.CompilerTags " <> getVersionTags compilerVersion) 1
, IntM ("Cardano.OSName " <> osName) 1
, IntM ("Cardano.Architecture " <> architecture) 1
, IntM ("cardano_build_info " <> getCardanoBuildInfo nvt) 1
, IntM ("haskell_build_info " <> getHaskellBuildInfo nvt) 1
]

getCardanoBuildInfo :: NodeVersionTrace -> Text
getCardanoBuildInfo NodeVersionTrace {..} = showVersion applicationVersion
getCardanoBuildInfo NodeVersionTrace {..} = pack $ showVersion applicationVersion


getHaskellBuildInfo :: NodeVersionTrace -> Text
getHaskellBuildInfo NodeVersionTrace {..} = showVersion compilerVersion
getHaskellBuildInfo NodeVersionTrace {..} = pack $ showVersion compilerVersion

getMajor :: Version -> Int
getMajor (Version (x:_) _) = x
getMajor _ = 0

getMinor :: Version -> Int
getMinor (Version (_:x:_) _) = x
getMinor _ = 0


getPatch :: Version -> Int
getPatch (Version (_:_:x:_) _) = x
getPatch _ = 0

getVersionTags :: Version -> Text
getVersionTags (Version _ tags) = intercalate ", " (map pack tags)


3 changes: 2 additions & 1 deletion cardano-node/src/Cardano/Node/Tracing/Tracers/Startup.hs
Original file line number Diff line number Diff line change
Expand Up @@ -56,7 +56,8 @@ import qualified Data.Map.Strict as Map
import Data.Text (Text, pack)
import Data.Time (getCurrentTime)
import Data.Time.Clock.POSIX (POSIXTime, utcTimeToPOSIXSeconds)
-- import Data.Version (showVersion, versionBranch)
import Data.Version (showVersion, versionBranch)


import Network.Socket (SockAddr)

Expand Down

0 comments on commit a8991f1

Please sign in to comment.