module System.Nagios.Plugin.Ekg.Types (
MetricTree
) where
import Control.Applicative
import Control.Monad
import Data.Aeson
import Data.Aeson.Types
import Data.Int
import Data.HashMap.Strict (HashMap)
import qualified Data.HashMap.Strict as HM
import Data.Map (Map)
import qualified Data.Map as M
import Data.Monoid
import Data.Text (Text)
import qualified Data.Text as T
import System.Nagios.Plugin
data EkgMetric =
EkgCounter Int64
| EkgGauge Double
| EkgLabel
| EkgDistribution
deriving (Eq, Show)
instance FromJSON EkgMetric where
parseJSON (Object o) = do
metric_type <- o .: "type"
case metric_type of
"c" -> EkgCounter <$> o .: "val"
"g" -> EkgGauge <$> o .: "val"
"l" -> return EkgLabel
"d" -> return EkgDistribution
x -> fail $ "Invalid metric type " <> T.unpack x
parseJSON _ = fail "EkgMetric must be an object"
data MetricNode =
Leaf EkgMetric
| Branch (Map Text MetricNode)
instance FromJSON MetricNode where
parseJSON (Object o) = do
leaf <- isLeaf <$> parseJSON (Object o)
if leaf
then Leaf <$> parseJSON (Object o)
else Branch <$> parseJSON (Object o)
where
isLeaf :: HashMap Text Value -> Bool
isLeaf m = HM.member "type" m &&
(HM.member "val" m ||
(HM.member "variance" m && HM.member "mean" m)
)
parseJSON x = fail $ "MetricNode must be an object, not " <> show x
newtype MetricTree = MetricTree
{ unMetricTree :: Map Text MetricNode }
instance FromJSON MetricTree where
parseJSON (Object o) = MetricTree <$> parseJSON (Object o)
parseJSON _ = fail "MetricTree must be an object"
instance ToPerfData MetricTree where
toPerfData (MetricTree m) = M.foldrWithKey (renderValue Nothing) [] m
renderMetric :: Text
-> EkgMetric
-> Maybe PerfDatum
renderMetric lbl (EkgCounter n) =
Just $ barePerfDatum lbl (IntegralValue n) Counter
renderMetric lbl (EkgGauge n) =
Just $ barePerfDatum lbl (RealValue n) NullUnit
renderMetric _ EkgLabel = Nothing
renderMetric _ EkgDistribution = Nothing
renderValue :: Maybe Text
-> Text
-> MetricNode
-> [PerfDatum]
-> [PerfDatum]
renderValue prefix lbl (Leaf val) acc =
case renderMetric (withPrefix prefix lbl) val of
Nothing -> acc
Just pd -> pd : acc
renderValue prefix lbl (Branch branch) acc = acc
<> M.foldrWithKey (renderValue (Just $ withPrefix prefix lbl)) [] branch
withPrefix :: Maybe Text
-> Text
-> Text
withPrefix Nothing suff = suff
withPrefix (Just prefix) suff = prefix <> "_" <> suff