Skip to content
This repository has been archived by the owner on Aug 18, 2020. It is now read-only.

[CSL-1585] Namespace cardano EKG metrics #1464

Merged
Merged
Show file tree
Hide file tree
Changes from 4 commits
Commits
File filter

Filter by extension

Filter by extension

Conversations
Failed to load comments.
Loading
Jump to
Jump to file
Failed to load files.
Loading
Diff view
Diff view
13 changes: 13 additions & 0 deletions core/Pos/System/Metrics/Constants.hs
Original file line number Diff line number Diff line change
@@ -0,0 +1,13 @@
{-# LANGUAGE OverloadedStrings #-}
Copy link
Contributor

Choose a reason for hiding this comment

The reason will be displayed to describe this comment to others. Learn more.

This extension (among many others) is enabled by default.

Copy link
Contributor Author

Choose a reason for hiding this comment

The reason will be displayed to describe this comment to others. Learn more.

Ah, I must have been taken in by flycheck or something 😉

module Pos.System.Metrics.Constants (
cardanoNamespace
, withCardanoNamespace
) where
Copy link
Contributor

Choose a reason for hiding this comment

The reason will be displayed to describe this comment to others. Learn more.

Is this spacing in our style guide? :-)


import Universum

cardanoNamespace :: Text
cardanoNamespace = "cardano"

withCardanoNamespace :: Text -> Text
withCardanoNamespace label = cardanoNamespace <> "." <> label
2 changes: 2 additions & 0 deletions core/cardano-sl-core.cabal
Original file line number Diff line number Diff line change
Expand Up @@ -98,6 +98,8 @@ library
Pos.Binary.Core.Version
Pos.Binary.Core.Genesis

Pos.System.Metrics.Constants

Pos.Util.Arbitrary
Pos.Util.Concurrent
Pos.Util.Concurrent.LockedTVar
Expand Down
10 changes: 6 additions & 4 deletions infra/Pos/Network/Types.hs
Original file line number Diff line number Diff line change
@@ -1,5 +1,6 @@
{-# LANGUAGE CPP #-}
{-# LANGUAGE ExistentialQuantification #-}
{-# LANGUAGE CPP #-}
{-# LANGUAGE OverloadedStrings #-}
Copy link
Contributor

Choose a reason for hiding this comment

The reason will be displayed to describe this comment to others. Learn more.

In infra (and I guess in all other packages) this extension is enabled by default too.


#if !defined(mingw32_HOST_OS)
#define POSIX
Expand Down Expand Up @@ -57,13 +58,14 @@ import Node.Internal (NodeId (..))
import Pos.Network.DnsDomains (DnsDomains (..))
import qualified Pos.Network.DnsDomains as DnsDomains
import qualified Pos.Network.Policy as Policy
import Pos.System.Metrics.Constants (cardanoNamespace)
import Pos.Util.TimeWarp (addressToNodeId)
import qualified System.Metrics as Monitoring
import System.Wlog.CanLog (WithLogger)
import Universum hiding (show)

#if !defined(POSIX)
import qualified Pos.Network.Windows.DnsDomains as Win
import qualified Pos.Network.Windows.DnsDomains as Win
#endif

{-------------------------------------------------------------------------------
Expand Down Expand Up @@ -290,7 +292,7 @@ topologyMaxBucketSize topology bucket =
BucketSubscriptionListener ->
case topologySubscribers topology of
Just (_subscriberType, maxBucketSize) -> maxBucketSize
Nothing -> OQ.BucketSizeMax 0 -- subscription not allowed
Nothing -> OQ.BucketSizeMax 0 -- subscription not allowed
_otherBucket ->
OQ.BucketSizeUnlimited

Expand Down Expand Up @@ -339,7 +341,7 @@ initQueue NetworkConfig{..} mStore = do

case mStore of
Nothing -> return () -- EKG store not used
Just store -> liftIO $ OQ.registerQueueMetrics oq store
Just store -> liftIO $ OQ.registerQueueMetrics (Just (toString cardanoNamespace)) oq store

case ncTopology of
TopologyLightWallet peers -> do
Expand Down
3 changes: 2 additions & 1 deletion node/cardano-sl.cabal
Original file line number Diff line number Diff line change
Expand Up @@ -113,6 +113,7 @@ library
-- Utilities/helpers
Pos.Util
Pos.Util.LoggerName
Pos.Util.Monitor
Pos.Util.Undefined
Pos.Util.BackupPhrase
Pos.Util.JsonLog
Expand Down Expand Up @@ -358,7 +359,7 @@ library
, dlist
, dns
, ed25519
, ekg
, ekg-wai
, ekg-core
, ekg-statsd
, ether >= 0.5
Expand Down
10 changes: 6 additions & 4 deletions node/src/Pos/Launcher/Runner.hs
Original file line number Diff line number Diff line change
Expand Up @@ -32,11 +32,13 @@ import Node (Node, NodeAction (..), NodeEnd
node, simpleNodeEndPoint)
import qualified Node.Conversation as N (Conversation, Converse,
converseWith)
import Node.Util.Monitor (setupMonitor, stopMonitor)
import Node.Util.Monitor (registerMetrics)
import Pos.System.Metrics.Constants (cardanoNamespace)
import Pos.Util.Monitor (stopMonitor)
import qualified System.Metrics as Metrics
import System.Random (newStdGen)
import qualified System.Remote.Monitoring as Monitoring
import qualified System.Remote.Monitoring.Statsd as Monitoring
import qualified System.Remote.Monitoring.Wai as Monitoring
import System.Wlog (WithLogger, logInfo)

import Pos.Binary ()
Expand Down Expand Up @@ -122,8 +124,8 @@ runRealModeDo NodeResources {..} outSpecs action =
case npEnableMetrics of
False -> return Nothing
True -> Just <$> do
ekgStore' <- setupMonitor
(runProduction . runToProd JsonLogDisabled oq) node' nrEkgStore
let ekgStore' = nrEkgStore
registerMetrics (Just cardanoNamespace) (runProduction . runToProd JsonLogDisabled oq) node' ekgStore'
Copy link
Contributor

Choose a reason for hiding this comment

The reason will be displayed to describe this comment to others. Learn more.

You don't need ekgStore' any more. It was only there because the old setupMonitor returned a possibly modified store, and no it doesn't, so there's no need to name the result.

liftIO $ Metrics.registerGcMetrics ekgStore'
mEkgServer <- case npEkgParams of
Nothing -> return Nothing
Expand Down
47 changes: 47 additions & 0 deletions node/src/Pos/Util/Monitor.hs
Original file line number Diff line number Diff line change
@@ -0,0 +1,47 @@
{-# OPTIONS_GHC -fno-warn-name-shadowing #-}
Copy link
Contributor

Choose a reason for hiding this comment

The reason will be displayed to describe this comment to others. Learn more.

I find it much better to avoid name shadowing than to suppress warnings. If there are fundamental reasons why it can't be avoided, it should be justified in comments.

{-# LANGUAGE FlexibleContexts #-}
{-# LANGUAGE GADTs #-}
{-# LANGUAGE RankNTypes #-}

module Pos.Util.Monitor (

startMonitor
, stopMonitor

) where

import Control.Concurrent (killThread)
import Control.Monad.IO.Class
import Mockable.Class
import qualified Mockable.Metrics as Metrics
import Node
Copy link
Contributor

Choose a reason for hiding this comment

The reason will be displayed to describe this comment to others. Learn more.

Imports should be qualified or contain explicit import list, according to style-guide.

import Node.Util.Monitor (registerMetrics)
import Pos.System.Metrics.Constants (cardanoNamespace)
import qualified System.Metrics as Monitoring
import qualified System.Metrics.Distribution as Monitoring.Distribution
import qualified System.Remote.Monitoring.Wai as Monitoring

import Universum

startMonitor
:: ( Mockable Metrics.Metrics m
, Metrics.Distribution m ~ Monitoring.Distribution.Distribution
, MonadIO m
)
=> Int
-> (forall t . m t -> IO t)
-> Node m
-> m Monitoring.Server
startMonitor port lowerIO node = do
store <- liftIO Monitoring.newStore
registerMetrics (Just cardanoNamespace) lowerIO node store
liftIO $ Monitoring.registerGcMetrics store
server <- liftIO $ Monitoring.forkServerWith store "127.0.0.1" port
liftIO . putStrLn $ "Forked EKG server on port " ++ show port
return server

stopMonitor
:: ( MonadIO m )
=> Monitoring.Server
-> m ()
stopMonitor server = liftIO $ killThread (Monitoring.serverThreadId server)
Loading