-
Notifications
You must be signed in to change notification settings - Fork 631
[CSL-1585] Namespace cardano EKG metrics #1464
Changes from 4 commits
f12bd50
ecb03dd
a928322
a32c641
6f5b0ff
3a6d2f5
File filter
Filter by extension
Conversations
Jump to
Diff view
Diff view
There are no files selected for viewing
Original file line number | Diff line number | Diff line change |
---|---|---|
@@ -0,0 +1,13 @@ | ||
{-# LANGUAGE OverloadedStrings #-} | ||
module Pos.System.Metrics.Constants ( | ||
cardanoNamespace | ||
, withCardanoNamespace | ||
) where | ||
There was a problem hiding this comment. Choose a reason for hiding this commentThe 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 |
Original file line number | Diff line number | Diff line change |
---|---|---|
@@ -1,5 +1,6 @@ | ||
{-# LANGUAGE CPP #-} | ||
{-# LANGUAGE ExistentialQuantification #-} | ||
{-# LANGUAGE CPP #-} | ||
{-# LANGUAGE OverloadedStrings #-} | ||
There was a problem hiding this comment. Choose a reason for hiding this commentThe reason will be displayed to describe this comment to others. Learn more. In |
||
|
||
#if !defined(mingw32_HOST_OS) | ||
#define POSIX | ||
|
@@ -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 | ||
|
||
{------------------------------------------------------------------------------- | ||
|
@@ -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 | ||
|
||
|
@@ -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 | ||
|
Original file line number | Diff line number | Diff line change |
---|---|---|
|
@@ -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 () | ||
|
@@ -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' | ||
There was a problem hiding this comment. Choose a reason for hiding this commentThe reason will be displayed to describe this comment to others. Learn more. You don't need |
||
liftIO $ Metrics.registerGcMetrics ekgStore' | ||
mEkgServer <- case npEkgParams of | ||
Nothing -> return Nothing | ||
|
Original file line number | Diff line number | Diff line change |
---|---|---|
@@ -0,0 +1,47 @@ | ||
{-# OPTIONS_GHC -fno-warn-name-shadowing #-} | ||
There was a problem hiding this comment. Choose a reason for hiding this commentThe 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 | ||
There was a problem hiding this comment. Choose a reason for hiding this commentThe 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) |
There was a problem hiding this comment.
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.
There was a problem hiding this comment.
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 😉