{-# LANGUAGE BlockArguments #-}
{-# LANGUAGE DeriveAnyClass #-}
{-# LANGUAGE DeriveGeneric #-}
{-# LANGUAGE DeriveTraversable #-}
{-# LANGUAGE DerivingStrategies #-}
{-# LANGUAGE DuplicateRecordFields #-}
{-# LANGUAGE FlexibleContexts #-}
{-# LANGUAGE FlexibleInstances #-}
{-# LANGUAGE GeneralizedNewtypeDeriving #-}
{-# LANGUAGE InstanceSigs #-}
{-# LANGUAGE LambdaCase #-}
{-# LANGUAGE OverloadedLabels #-}
{-# LANGUAGE OverloadedRecordDot #-}
{-# LANGUAGE OverloadedStrings #-}
{-# LANGUAGE RecordWildCards #-}
{-# LANGUAGE TemplateHaskell #-}
{-# LANGUAGE TypeApplications #-}
{-# LANGUAGE TypeFamilies #-}
{-# LANGUAGE UndecidableInstances #-}
module Language.EO.Phi.Metrics.Data where
import Data.Aeson (ToJSON (..), Value (..), withObject, (.:), (.=))
import Data.Aeson qualified as Aeson
import Data.Aeson.Types (FromJSON (..), Parser)
import Data.Generics.Labels ()
import Data.List (groupBy, intercalate)
import GHC.Generics (Generic)
import Language.EO.Phi.Rules.Common ()
import Language.EO.Phi.TH (deriveJSON)
data Metrics a = Metrics
{ forall a. Metrics a -> a
dataless :: a
, forall a. Metrics a -> a
applications :: a
, forall a. Metrics a -> a
formations :: a
, forall a. Metrics a -> a
dispatches :: a
}
deriving stock (Int -> Metrics a -> ShowS
[Metrics a] -> ShowS
Metrics a -> String
(Int -> Metrics a -> ShowS)
-> (Metrics a -> String)
-> ([Metrics a] -> ShowS)
-> Show (Metrics a)
forall a. Show a => Int -> Metrics a -> ShowS
forall a. Show a => [Metrics a] -> ShowS
forall a. Show a => Metrics a -> String
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
$cshowsPrec :: forall a. Show a => Int -> Metrics a -> ShowS
showsPrec :: Int -> Metrics a -> ShowS
$cshow :: forall a. Show a => Metrics a -> String
show :: Metrics a -> String
$cshowList :: forall a. Show a => [Metrics a] -> ShowS
showList :: [Metrics a] -> ShowS
Show, (forall x. Metrics a -> Rep (Metrics a) x)
-> (forall x. Rep (Metrics a) x -> Metrics a)
-> Generic (Metrics a)
forall x. Rep (Metrics a) x -> Metrics a
forall x. Metrics a -> Rep (Metrics a) x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
forall a x. Rep (Metrics a) x -> Metrics a
forall a x. Metrics a -> Rep (Metrics a) x
$cfrom :: forall a x. Metrics a -> Rep (Metrics a) x
from :: forall x. Metrics a -> Rep (Metrics a) x
$cto :: forall a x. Rep (Metrics a) x -> Metrics a
to :: forall x. Rep (Metrics a) x -> Metrics a
Generic, Metrics a -> Metrics a -> Bool
(Metrics a -> Metrics a -> Bool)
-> (Metrics a -> Metrics a -> Bool) -> Eq (Metrics a)
forall a. Eq a => Metrics a -> Metrics a -> Bool
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
$c== :: forall a. Eq a => Metrics a -> Metrics a -> Bool
== :: Metrics a -> Metrics a -> Bool
$c/= :: forall a. Eq a => Metrics a -> Metrics a -> Bool
/= :: Metrics a -> Metrics a -> Bool
Eq, (forall a b. (a -> b) -> Metrics a -> Metrics b)
-> (forall a b. a -> Metrics b -> Metrics a) -> Functor Metrics
forall a b. a -> Metrics b -> Metrics a
forall a b. (a -> b) -> Metrics a -> Metrics b
forall (f :: * -> *).
(forall a b. (a -> b) -> f a -> f b)
-> (forall a b. a -> f b -> f a) -> Functor f
$cfmap :: forall a b. (a -> b) -> Metrics a -> Metrics b
fmap :: forall a b. (a -> b) -> Metrics a -> Metrics b
$c<$ :: forall a b. a -> Metrics b -> Metrics a
<$ :: forall a b. a -> Metrics b -> Metrics a
Functor, (forall m. Monoid m => Metrics m -> m)
-> (forall m a. Monoid m => (a -> m) -> Metrics a -> m)
-> (forall m a. Monoid m => (a -> m) -> Metrics a -> m)
-> (forall a b. (a -> b -> b) -> b -> Metrics a -> b)
-> (forall a b. (a -> b -> b) -> b -> Metrics a -> b)
-> (forall b a. (b -> a -> b) -> b -> Metrics a -> b)
-> (forall b a. (b -> a -> b) -> b -> Metrics a -> b)
-> (forall a. (a -> a -> a) -> Metrics a -> a)
-> (forall a. (a -> a -> a) -> Metrics a -> a)
-> (forall a. Metrics a -> [a])
-> (forall a. Metrics a -> Bool)
-> (forall a. Metrics a -> Int)
-> (forall a. Eq a => a -> Metrics a -> Bool)
-> (forall a. Ord a => Metrics a -> a)
-> (forall a. Ord a => Metrics a -> a)
-> (forall a. Num a => Metrics a -> a)
-> (forall a. Num a => Metrics a -> a)
-> Foldable Metrics
forall a. Eq a => a -> Metrics a -> Bool
forall a. Num a => Metrics a -> a
forall a. Ord a => Metrics a -> a
forall m. Monoid m => Metrics m -> m
forall a. Metrics a -> Bool
forall a. Metrics a -> Int
forall a. Metrics a -> [a]
forall a. (a -> a -> a) -> Metrics a -> a
forall m a. Monoid m => (a -> m) -> Metrics a -> m
forall b a. (b -> a -> b) -> b -> Metrics a -> b
forall a b. (a -> b -> b) -> b -> Metrics a -> b
forall (t :: * -> *).
(forall m. Monoid m => t m -> m)
-> (forall m a. Monoid m => (a -> m) -> t a -> m)
-> (forall m a. Monoid m => (a -> m) -> t a -> m)
-> (forall a b. (a -> b -> b) -> b -> t a -> b)
-> (forall a b. (a -> b -> b) -> b -> t a -> b)
-> (forall b a. (b -> a -> b) -> b -> t a -> b)
-> (forall b a. (b -> a -> b) -> b -> t a -> b)
-> (forall a. (a -> a -> a) -> t a -> a)
-> (forall a. (a -> a -> a) -> t a -> a)
-> (forall a. t a -> [a])
-> (forall a. t a -> Bool)
-> (forall a. t a -> Int)
-> (forall a. Eq a => a -> t a -> Bool)
-> (forall a. Ord a => t a -> a)
-> (forall a. Ord a => t a -> a)
-> (forall a. Num a => t a -> a)
-> (forall a. Num a => t a -> a)
-> Foldable t
$cfold :: forall m. Monoid m => Metrics m -> m
fold :: forall m. Monoid m => Metrics m -> m
$cfoldMap :: forall m a. Monoid m => (a -> m) -> Metrics a -> m
foldMap :: forall m a. Monoid m => (a -> m) -> Metrics a -> m
$cfoldMap' :: forall m a. Monoid m => (a -> m) -> Metrics a -> m
foldMap' :: forall m a. Monoid m => (a -> m) -> Metrics a -> m
$cfoldr :: forall a b. (a -> b -> b) -> b -> Metrics a -> b
foldr :: forall a b. (a -> b -> b) -> b -> Metrics a -> b
$cfoldr' :: forall a b. (a -> b -> b) -> b -> Metrics a -> b
foldr' :: forall a b. (a -> b -> b) -> b -> Metrics a -> b
$cfoldl :: forall b a. (b -> a -> b) -> b -> Metrics a -> b
foldl :: forall b a. (b -> a -> b) -> b -> Metrics a -> b
$cfoldl' :: forall b a. (b -> a -> b) -> b -> Metrics a -> b
foldl' :: forall b a. (b -> a -> b) -> b -> Metrics a -> b
$cfoldr1 :: forall a. (a -> a -> a) -> Metrics a -> a
foldr1 :: forall a. (a -> a -> a) -> Metrics a -> a
$cfoldl1 :: forall a. (a -> a -> a) -> Metrics a -> a
foldl1 :: forall a. (a -> a -> a) -> Metrics a -> a
$ctoList :: forall a. Metrics a -> [a]
toList :: forall a. Metrics a -> [a]
$cnull :: forall a. Metrics a -> Bool
null :: forall a. Metrics a -> Bool
$clength :: forall a. Metrics a -> Int
length :: forall a. Metrics a -> Int
$celem :: forall a. Eq a => a -> Metrics a -> Bool
elem :: forall a. Eq a => a -> Metrics a -> Bool
$cmaximum :: forall a. Ord a => Metrics a -> a
maximum :: forall a. Ord a => Metrics a -> a
$cminimum :: forall a. Ord a => Metrics a -> a
minimum :: forall a. Ord a => Metrics a -> a
$csum :: forall a. Num a => Metrics a -> a
sum :: forall a. Num a => Metrics a -> a
$cproduct :: forall a. Num a => Metrics a -> a
product :: forall a. Num a => Metrics a -> a
Foldable, Functor Metrics
Foldable Metrics
(Functor Metrics, Foldable Metrics) =>
(forall (f :: * -> *) a b.
Applicative f =>
(a -> f b) -> Metrics a -> f (Metrics b))
-> (forall (f :: * -> *) a.
Applicative f =>
Metrics (f a) -> f (Metrics a))
-> (forall (m :: * -> *) a b.
Monad m =>
(a -> m b) -> Metrics a -> m (Metrics b))
-> (forall (m :: * -> *) a.
Monad m =>
Metrics (m a) -> m (Metrics a))
-> Traversable Metrics
forall (t :: * -> *).
(Functor t, Foldable t) =>
(forall (f :: * -> *) a b.
Applicative f =>
(a -> f b) -> t a -> f (t b))
-> (forall (f :: * -> *) a. Applicative f => t (f a) -> f (t a))
-> (forall (m :: * -> *) a b.
Monad m =>
(a -> m b) -> t a -> m (t b))
-> (forall (m :: * -> *) a. Monad m => t (m a) -> m (t a))
-> Traversable t
forall (m :: * -> *) a. Monad m => Metrics (m a) -> m (Metrics a)
forall (f :: * -> *) a.
Applicative f =>
Metrics (f a) -> f (Metrics a)
forall (m :: * -> *) a b.
Monad m =>
(a -> m b) -> Metrics a -> m (Metrics b)
forall (f :: * -> *) a b.
Applicative f =>
(a -> f b) -> Metrics a -> f (Metrics b)
$ctraverse :: forall (f :: * -> *) a b.
Applicative f =>
(a -> f b) -> Metrics a -> f (Metrics b)
traverse :: forall (f :: * -> *) a b.
Applicative f =>
(a -> f b) -> Metrics a -> f (Metrics b)
$csequenceA :: forall (f :: * -> *) a.
Applicative f =>
Metrics (f a) -> f (Metrics a)
sequenceA :: forall (f :: * -> *) a.
Applicative f =>
Metrics (f a) -> f (Metrics a)
$cmapM :: forall (m :: * -> *) a b.
Monad m =>
(a -> m b) -> Metrics a -> m (Metrics b)
mapM :: forall (m :: * -> *) a b.
Monad m =>
(a -> m b) -> Metrics a -> m (Metrics b)
$csequence :: forall (m :: * -> *) a. Monad m => Metrics (m a) -> m (Metrics a)
sequence :: forall (m :: * -> *) a. Monad m => Metrics (m a) -> m (Metrics a)
Traversable)
$(deriveJSON ''Metrics)
toListMetrics :: Metrics a -> [a]
toListMetrics :: forall a. Metrics a -> [a]
toListMetrics = (a -> [a]) -> Metrics a -> [a]
forall m a. Monoid m => (a -> m) -> Metrics a -> m
forall (t :: * -> *) m a.
(Foldable t, Monoid m) =>
(a -> m) -> t a -> m
foldMap (a -> [a] -> [a]
forall a. a -> [a] -> [a]
: [])
instance Applicative Metrics where
pure :: a -> Metrics a
pure :: forall a. a -> Metrics a
pure a
a =
Metrics
{ $sel:dataless:Metrics :: a
dataless = a
a
, $sel:applications:Metrics :: a
applications = a
a
, $sel:formations:Metrics :: a
formations = a
a
, $sel:dispatches:Metrics :: a
dispatches = a
a
}
(<*>) :: Metrics (a -> b) -> Metrics a -> Metrics b
Metrics (a -> b)
x <*> :: forall a b. Metrics (a -> b) -> Metrics a -> Metrics b
<*> Metrics a
y =
Metrics
{ $sel:dataless:Metrics :: b
dataless = Metrics (a -> b)
x.dataless Metrics a
y.dataless
, $sel:applications:Metrics :: b
applications = Metrics (a -> b)
x.applications Metrics a
y.applications
, $sel:formations:Metrics :: b
formations = Metrics (a -> b)
x.formations Metrics a
y.formations
, $sel:dispatches:Metrics :: b
dispatches = Metrics (a -> b)
x.dispatches Metrics a
y.dispatches
}
instance (Num a) => Num (Metrics a) where
(+) :: Metrics a -> Metrics a -> Metrics a
+ :: Metrics a -> Metrics a -> Metrics a
(+) Metrics a
x Metrics a
y = a -> a -> a
forall a. Num a => a -> a -> a
(+) (a -> a -> a) -> Metrics a -> Metrics (a -> a)
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> Metrics a
x Metrics (a -> a) -> Metrics a -> Metrics a
forall a b. Metrics (a -> b) -> Metrics a -> Metrics b
forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
<*> Metrics a
y
(-) :: Metrics a -> Metrics a -> Metrics a
(-) Metrics a
x Metrics a
y = (-) (a -> a -> a) -> Metrics a -> Metrics (a -> a)
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> Metrics a
x Metrics (a -> a) -> Metrics a -> Metrics a
forall a b. Metrics (a -> b) -> Metrics a -> Metrics b
forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
<*> Metrics a
y
(*) :: Metrics a -> Metrics a -> Metrics a
* :: Metrics a -> Metrics a -> Metrics a
(*) Metrics a
x Metrics a
y = a -> a -> a
forall a. Num a => a -> a -> a
(*) (a -> a -> a) -> Metrics a -> Metrics (a -> a)
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> Metrics a
x Metrics (a -> a) -> Metrics a -> Metrics a
forall a b. Metrics (a -> b) -> Metrics a -> Metrics b
forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
<*> Metrics a
y
negate :: Metrics a -> Metrics a
negate :: Metrics a -> Metrics a
negate = (a -> a
forall a. Num a => a -> a
negate (a -> a) -> Metrics a -> Metrics a
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$>)
abs :: Metrics a -> Metrics a
abs :: Metrics a -> Metrics a
abs = (a -> a
forall a. Num a => a -> a
abs (a -> a) -> Metrics a -> Metrics a
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$>)
signum :: Metrics a -> Metrics a
signum :: Metrics a -> Metrics a
signum = (a -> a
forall a. Num a => a -> a
signum (a -> a) -> Metrics a -> Metrics a
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$>)
fromInteger :: Integer -> Metrics a
fromInteger :: Integer -> Metrics a
fromInteger Integer
x = a -> Metrics a
forall a. a -> Metrics a
forall (f :: * -> *) a. Applicative f => a -> f a
pure (a -> Metrics a) -> a -> Metrics a
forall a b. (a -> b) -> a -> b
$ Integer -> a
forall a. Num a => Integer -> a
fromInteger Integer
x
instance (Fractional a) => Fractional (Metrics a) where
fromRational :: Rational -> Metrics a
fromRational :: Rational -> Metrics a
fromRational Rational
_ = Metrics a
0
(/) :: Metrics a -> Metrics a -> Metrics a
/ :: Metrics a -> Metrics a -> Metrics a
(/) Metrics a
x Metrics a
y = a -> a -> a
forall a. Fractional a => a -> a -> a
(/) (a -> a -> a) -> Metrics a -> Metrics (a -> a)
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> Metrics a
x Metrics (a -> a) -> Metrics a -> Metrics a
forall a b. Metrics (a -> b) -> Metrics a -> Metrics b
forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
<*> Metrics a
y
instance (Num a) => Semigroup (Metrics a) where
(<>) :: Metrics a -> Metrics a -> Metrics a
<> :: Metrics a -> Metrics a -> Metrics a
(<>) = Metrics a -> Metrics a -> Metrics a
forall a. Num a => a -> a -> a
(+)
instance (Num a) => Monoid (Metrics a) where
mempty :: Metrics a
mempty :: Metrics a
mempty = Metrics a
0
type MetricsCount = Metrics Int
data BindingMetrics = BindingMetrics
{ BindingMetrics -> String
name :: String
, BindingMetrics -> MetricsCount
metrics :: MetricsCount
}
deriving stock (Int -> BindingMetrics -> ShowS
[BindingMetrics] -> ShowS
BindingMetrics -> String
(Int -> BindingMetrics -> ShowS)
-> (BindingMetrics -> String)
-> ([BindingMetrics] -> ShowS)
-> Show BindingMetrics
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
$cshowsPrec :: Int -> BindingMetrics -> ShowS
showsPrec :: Int -> BindingMetrics -> ShowS
$cshow :: BindingMetrics -> String
show :: BindingMetrics -> String
$cshowList :: [BindingMetrics] -> ShowS
showList :: [BindingMetrics] -> ShowS
Show, (forall x. BindingMetrics -> Rep BindingMetrics x)
-> (forall x. Rep BindingMetrics x -> BindingMetrics)
-> Generic BindingMetrics
forall x. Rep BindingMetrics x -> BindingMetrics
forall x. BindingMetrics -> Rep BindingMetrics x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cfrom :: forall x. BindingMetrics -> Rep BindingMetrics x
from :: forall x. BindingMetrics -> Rep BindingMetrics x
$cto :: forall x. Rep BindingMetrics x -> BindingMetrics
to :: forall x. Rep BindingMetrics x -> BindingMetrics
Generic, BindingMetrics -> BindingMetrics -> Bool
(BindingMetrics -> BindingMetrics -> Bool)
-> (BindingMetrics -> BindingMetrics -> Bool) -> Eq BindingMetrics
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
$c== :: BindingMetrics -> BindingMetrics -> Bool
== :: BindingMetrics -> BindingMetrics -> Bool
$c/= :: BindingMetrics -> BindingMetrics -> Bool
/= :: BindingMetrics -> BindingMetrics -> Bool
Eq)
$(deriveJSON ''BindingMetrics)
type Path = [String]
data BindingsByPathMetrics = BindingsByPathMetrics
{ BindingsByPathMetrics -> Path
path :: Path
, BindingsByPathMetrics -> [BindingMetrics]
bindingsMetrics :: [BindingMetrics]
}
deriving (Int -> BindingsByPathMetrics -> ShowS
[BindingsByPathMetrics] -> ShowS
BindingsByPathMetrics -> String
(Int -> BindingsByPathMetrics -> ShowS)
-> (BindingsByPathMetrics -> String)
-> ([BindingsByPathMetrics] -> ShowS)
-> Show BindingsByPathMetrics
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
$cshowsPrec :: Int -> BindingsByPathMetrics -> ShowS
showsPrec :: Int -> BindingsByPathMetrics -> ShowS
$cshow :: BindingsByPathMetrics -> String
show :: BindingsByPathMetrics -> String
$cshowList :: [BindingsByPathMetrics] -> ShowS
showList :: [BindingsByPathMetrics] -> ShowS
Show, (forall x. BindingsByPathMetrics -> Rep BindingsByPathMetrics x)
-> (forall x. Rep BindingsByPathMetrics x -> BindingsByPathMetrics)
-> Generic BindingsByPathMetrics
forall x. Rep BindingsByPathMetrics x -> BindingsByPathMetrics
forall x. BindingsByPathMetrics -> Rep BindingsByPathMetrics x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cfrom :: forall x. BindingsByPathMetrics -> Rep BindingsByPathMetrics x
from :: forall x. BindingsByPathMetrics -> Rep BindingsByPathMetrics x
$cto :: forall x. Rep BindingsByPathMetrics x -> BindingsByPathMetrics
to :: forall x. Rep BindingsByPathMetrics x -> BindingsByPathMetrics
Generic, BindingsByPathMetrics -> BindingsByPathMetrics -> Bool
(BindingsByPathMetrics -> BindingsByPathMetrics -> Bool)
-> (BindingsByPathMetrics -> BindingsByPathMetrics -> Bool)
-> Eq BindingsByPathMetrics
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
$c== :: BindingsByPathMetrics -> BindingsByPathMetrics -> Bool
== :: BindingsByPathMetrics -> BindingsByPathMetrics -> Bool
$c/= :: BindingsByPathMetrics -> BindingsByPathMetrics -> Bool
/= :: BindingsByPathMetrics -> BindingsByPathMetrics -> Bool
Eq)
splitStringOn :: Char -> String -> Path
splitStringOn :: Char -> String -> Path
splitStringOn Char
sep = (String -> Bool) -> Path -> Path
forall a. (a -> Bool) -> [a] -> [a]
filter (String -> String -> Bool
forall a. Eq a => a -> a -> Bool
/= [Char
sep]) (Path -> Path) -> (String -> Path) -> String -> Path
forall b c a. (b -> c) -> (a -> b) -> a -> c
. (Char -> Char -> Bool) -> String -> Path
forall a. (a -> a -> Bool) -> [a] -> [[a]]
groupBy (\Char
a Char
b -> Char
a Char -> Char -> Bool
forall a. Eq a => a -> a -> Bool
/= Char
sep Bool -> Bool -> Bool
&& Char
b Char -> Char -> Bool
forall a. Eq a => a -> a -> Bool
/= Char
sep)
splitPath :: String -> Path
splitPath :: String -> Path
splitPath = Char -> String -> Path
splitStringOn Char
'.'
instance FromJSON BindingsByPathMetrics where
parseJSON :: Value -> Parser BindingsByPathMetrics
parseJSON :: Value -> Parser BindingsByPathMetrics
parseJSON = String
-> (Object -> Parser BindingsByPathMetrics)
-> Value
-> Parser BindingsByPathMetrics
forall a. String -> (Object -> Parser a) -> Value -> Parser a
withObject String
"BindingsByPathMetrics" ((Object -> Parser BindingsByPathMetrics)
-> Value -> Parser BindingsByPathMetrics)
-> (Object -> Parser BindingsByPathMetrics)
-> Value
-> Parser BindingsByPathMetrics
forall a b. (a -> b) -> a -> b
$ \Object
obj -> do
Path
path <- String -> Path
splitPath (String -> Path) -> Parser String -> Parser Path
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> (Object
obj Object -> Key -> Parser String
forall a. FromJSON a => Object -> Key -> Parser a
.: Key
"path")
[BindingMetrics]
bindingsMetrics <- Object
obj Object -> Key -> Parser [BindingMetrics]
forall a. FromJSON a => Object -> Key -> Parser a
.: Key
"bindings-metrics"
BindingsByPathMetrics -> Parser BindingsByPathMetrics
forall a. a -> Parser a
forall (f :: * -> *) a. Applicative f => a -> f a
pure BindingsByPathMetrics{Path
[BindingMetrics]
$sel:path:BindingsByPathMetrics :: Path
$sel:bindingsMetrics:BindingsByPathMetrics :: [BindingMetrics]
path :: Path
bindingsMetrics :: [BindingMetrics]
..}
instance ToJSON BindingsByPathMetrics where
toJSON :: BindingsByPathMetrics -> Value
toJSON :: BindingsByPathMetrics -> Value
toJSON BindingsByPathMetrics{Path
[BindingMetrics]
$sel:path:BindingsByPathMetrics :: BindingsByPathMetrics -> Path
$sel:bindingsMetrics:BindingsByPathMetrics :: BindingsByPathMetrics -> [BindingMetrics]
path :: Path
bindingsMetrics :: [BindingMetrics]
..} =
[Pair] -> Value
Aeson.object
[ Key
"path" Key -> String -> Pair
forall kv v. (KeyValue kv, ToJSON v) => Key -> v -> kv
forall v. ToJSON v => Key -> v -> Pair
.= String -> Path -> String
forall a. [a] -> [[a]] -> [a]
intercalate String
"." Path
path
, Key
"bindings-metrics" Key -> [BindingMetrics] -> Pair
forall kv v. (KeyValue kv, ToJSON v) => Key -> v -> kv
forall v. ToJSON v => Key -> v -> Pair
.= [BindingMetrics]
bindingsMetrics
]
data ObjectMetrics = ObjectMetrics
{ ObjectMetrics -> Maybe BindingsByPathMetrics
bindingsByPathMetrics :: Maybe BindingsByPathMetrics
, ObjectMetrics -> MetricsCount
thisObjectMetrics :: MetricsCount
}
deriving (Int -> ObjectMetrics -> ShowS
[ObjectMetrics] -> ShowS
ObjectMetrics -> String
(Int -> ObjectMetrics -> ShowS)
-> (ObjectMetrics -> String)
-> ([ObjectMetrics] -> ShowS)
-> Show ObjectMetrics
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
$cshowsPrec :: Int -> ObjectMetrics -> ShowS
showsPrec :: Int -> ObjectMetrics -> ShowS
$cshow :: ObjectMetrics -> String
show :: ObjectMetrics -> String
$cshowList :: [ObjectMetrics] -> ShowS
showList :: [ObjectMetrics] -> ShowS
Show, (forall x. ObjectMetrics -> Rep ObjectMetrics x)
-> (forall x. Rep ObjectMetrics x -> ObjectMetrics)
-> Generic ObjectMetrics
forall x. Rep ObjectMetrics x -> ObjectMetrics
forall x. ObjectMetrics -> Rep ObjectMetrics x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cfrom :: forall x. ObjectMetrics -> Rep ObjectMetrics x
from :: forall x. ObjectMetrics -> Rep ObjectMetrics x
$cto :: forall x. Rep ObjectMetrics x -> ObjectMetrics
to :: forall x. Rep ObjectMetrics x -> ObjectMetrics
Generic, ObjectMetrics -> ObjectMetrics -> Bool
(ObjectMetrics -> ObjectMetrics -> Bool)
-> (ObjectMetrics -> ObjectMetrics -> Bool) -> Eq ObjectMetrics
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
$c== :: ObjectMetrics -> ObjectMetrics -> Bool
== :: ObjectMetrics -> ObjectMetrics -> Bool
$c/= :: ObjectMetrics -> ObjectMetrics -> Bool
/= :: ObjectMetrics -> ObjectMetrics -> Bool
Eq)
$(deriveJSON ''ObjectMetrics)
data ProgramMetrics = ProgramMetrics
{ ProgramMetrics -> Maybe BindingsByPathMetrics
bindingsByPathMetrics :: Maybe BindingsByPathMetrics
, ProgramMetrics -> MetricsCount
programMetrics :: MetricsCount
}
deriving (Int -> ProgramMetrics -> ShowS
[ProgramMetrics] -> ShowS
ProgramMetrics -> String
(Int -> ProgramMetrics -> ShowS)
-> (ProgramMetrics -> String)
-> ([ProgramMetrics] -> ShowS)
-> Show ProgramMetrics
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
$cshowsPrec :: Int -> ProgramMetrics -> ShowS
showsPrec :: Int -> ProgramMetrics -> ShowS
$cshow :: ProgramMetrics -> String
show :: ProgramMetrics -> String
$cshowList :: [ProgramMetrics] -> ShowS
showList :: [ProgramMetrics] -> ShowS
Show, (forall x. ProgramMetrics -> Rep ProgramMetrics x)
-> (forall x. Rep ProgramMetrics x -> ProgramMetrics)
-> Generic ProgramMetrics
forall x. Rep ProgramMetrics x -> ProgramMetrics
forall x. ProgramMetrics -> Rep ProgramMetrics x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cfrom :: forall x. ProgramMetrics -> Rep ProgramMetrics x
from :: forall x. ProgramMetrics -> Rep ProgramMetrics x
$cto :: forall x. Rep ProgramMetrics x -> ProgramMetrics
to :: forall x. Rep ProgramMetrics x -> ProgramMetrics
Generic, ProgramMetrics -> ProgramMetrics -> Bool
(ProgramMetrics -> ProgramMetrics -> Bool)
-> (ProgramMetrics -> ProgramMetrics -> Bool) -> Eq ProgramMetrics
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
$c== :: ProgramMetrics -> ProgramMetrics -> Bool
== :: ProgramMetrics -> ProgramMetrics -> Bool
$c/= :: ProgramMetrics -> ProgramMetrics -> Bool
/= :: ProgramMetrics -> ProgramMetrics -> Bool
Eq)
$(deriveJSON ''ProgramMetrics)