{-# LANGUAGE TemplateHaskell #-}
module Hasura.Server.Telemetry.Types
(
RelationshipMetric (..),
PermissionMetric (..),
ActionMetric (..),
Metrics (..),
SourceMetadata (..),
HasuraTelemetry (..),
TelemetryPayload (..),
Topic (..),
RequestDimensions (..),
RequestTimings (..),
QueryType (..),
Locality (..),
Transport (..),
ServiceTimingMetrics (..),
ServiceTimingMetric (..),
RunningTimeBucket (..),
RequestTimingsCount (..),
)
where
import CI qualified
import Data.Aeson qualified as A
import Data.Aeson.TH qualified as A
import Hasura.Prelude
import Hasura.RQL.Types.Metadata.Instances ()
import Hasura.SQL.Backend (BackendType)
import Hasura.Server.Telemetry.Counters
import Hasura.Server.Types
import Hasura.Server.Version
data RelationshipMetric = RelationshipMetric
{ RelationshipMetric -> Int
_rmManual :: Int,
RelationshipMetric -> Int
_rmAuto :: Int
}
deriving (Int -> RelationshipMetric -> ShowS
[RelationshipMetric] -> ShowS
RelationshipMetric -> String
(Int -> RelationshipMetric -> ShowS)
-> (RelationshipMetric -> String)
-> ([RelationshipMetric] -> ShowS)
-> Show RelationshipMetric
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [RelationshipMetric] -> ShowS
$cshowList :: [RelationshipMetric] -> ShowS
show :: RelationshipMetric -> String
$cshow :: RelationshipMetric -> String
showsPrec :: Int -> RelationshipMetric -> ShowS
$cshowsPrec :: Int -> RelationshipMetric -> ShowS
Show, RelationshipMetric -> RelationshipMetric -> Bool
(RelationshipMetric -> RelationshipMetric -> Bool)
-> (RelationshipMetric -> RelationshipMetric -> Bool)
-> Eq RelationshipMetric
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: RelationshipMetric -> RelationshipMetric -> Bool
$c/= :: RelationshipMetric -> RelationshipMetric -> Bool
== :: RelationshipMetric -> RelationshipMetric -> Bool
$c== :: RelationshipMetric -> RelationshipMetric -> Bool
Eq)
$(A.deriveToJSON hasuraJSON ''RelationshipMetric)
data PermissionMetric = PermissionMetric
{ PermissionMetric -> Int
_pmSelect :: Int,
PermissionMetric -> Int
_pmInsert :: Int,
PermissionMetric -> Int
_pmUpdate :: Int,
PermissionMetric -> Int
_pmDelete :: Int,
PermissionMetric -> Int
_pmRoles :: Int
}
deriving (Int -> PermissionMetric -> ShowS
[PermissionMetric] -> ShowS
PermissionMetric -> String
(Int -> PermissionMetric -> ShowS)
-> (PermissionMetric -> String)
-> ([PermissionMetric] -> ShowS)
-> Show PermissionMetric
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [PermissionMetric] -> ShowS
$cshowList :: [PermissionMetric] -> ShowS
show :: PermissionMetric -> String
$cshow :: PermissionMetric -> String
showsPrec :: Int -> PermissionMetric -> ShowS
$cshowsPrec :: Int -> PermissionMetric -> ShowS
Show, PermissionMetric -> PermissionMetric -> Bool
(PermissionMetric -> PermissionMetric -> Bool)
-> (PermissionMetric -> PermissionMetric -> Bool)
-> Eq PermissionMetric
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: PermissionMetric -> PermissionMetric -> Bool
$c/= :: PermissionMetric -> PermissionMetric -> Bool
== :: PermissionMetric -> PermissionMetric -> Bool
$c== :: PermissionMetric -> PermissionMetric -> Bool
Eq)
$(A.deriveToJSON hasuraJSON ''PermissionMetric)
data ActionMetric = ActionMetric
{ ActionMetric -> Int
_amSynchronous :: Int,
ActionMetric -> Int
_amAsynchronous :: Int,
ActionMetric -> Int
_amQueryActions :: Int,
ActionMetric -> Int
_amTypeRelationships :: Int,
ActionMetric -> Int
_amCustomTypes :: Int
}
deriving (Int -> ActionMetric -> ShowS
[ActionMetric] -> ShowS
ActionMetric -> String
(Int -> ActionMetric -> ShowS)
-> (ActionMetric -> String)
-> ([ActionMetric] -> ShowS)
-> Show ActionMetric
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [ActionMetric] -> ShowS
$cshowList :: [ActionMetric] -> ShowS
show :: ActionMetric -> String
$cshow :: ActionMetric -> String
showsPrec :: Int -> ActionMetric -> ShowS
$cshowsPrec :: Int -> ActionMetric -> ShowS
Show, ActionMetric -> ActionMetric -> Bool
(ActionMetric -> ActionMetric -> Bool)
-> (ActionMetric -> ActionMetric -> Bool) -> Eq ActionMetric
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: ActionMetric -> ActionMetric -> Bool
$c/= :: ActionMetric -> ActionMetric -> Bool
== :: ActionMetric -> ActionMetric -> Bool
$c== :: ActionMetric -> ActionMetric -> Bool
Eq)
$(A.deriveToJSON hasuraJSON ''ActionMetric)
data Metrics = Metrics
{ Metrics -> Int
_mtTables :: Int,
Metrics -> Int
_mtViews :: Int,
Metrics -> Int
_mtEnumTables :: Int,
Metrics -> RelationshipMetric
_mtRelationships :: RelationshipMetric,
Metrics -> PermissionMetric
_mtPermissions :: PermissionMetric,
Metrics -> Int
_mtEventTriggers :: Int,
Metrics -> Int
_mtFunctions :: Int,
Metrics -> Maybe Int
_mtRemoteSchemas :: Maybe Int,
Metrics -> Maybe ServiceTimingMetrics
_mtServiceTimings :: Maybe ServiceTimingMetrics,
Metrics -> Maybe ActionMetric
_mtActions :: Maybe ActionMetric
}
deriving (Int -> Metrics -> ShowS
[Metrics] -> ShowS
Metrics -> String
(Int -> Metrics -> ShowS)
-> (Metrics -> String) -> ([Metrics] -> ShowS) -> Show Metrics
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [Metrics] -> ShowS
$cshowList :: [Metrics] -> ShowS
show :: Metrics -> String
$cshow :: Metrics -> String
showsPrec :: Int -> Metrics -> ShowS
$cshowsPrec :: Int -> Metrics -> ShowS
Show, Metrics -> Metrics -> Bool
(Metrics -> Metrics -> Bool)
-> (Metrics -> Metrics -> Bool) -> Eq Metrics
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: Metrics -> Metrics -> Bool
$c/= :: Metrics -> Metrics -> Bool
== :: Metrics -> Metrics -> Bool
$c== :: Metrics -> Metrics -> Bool
Eq)
$(A.deriveToJSON hasuraJSON ''Metrics)
data SourceMetadata = SourceMetadata
{ SourceMetadata -> Maybe DbUid
_smDbUid :: Maybe DbUid,
SourceMetadata -> BackendType
_smDbKind :: BackendType,
SourceMetadata -> Maybe DbVersion
_smDbVersion :: Maybe DbVersion
}
deriving (Int -> SourceMetadata -> ShowS
[SourceMetadata] -> ShowS
SourceMetadata -> String
(Int -> SourceMetadata -> ShowS)
-> (SourceMetadata -> String)
-> ([SourceMetadata] -> ShowS)
-> Show SourceMetadata
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [SourceMetadata] -> ShowS
$cshowList :: [SourceMetadata] -> ShowS
show :: SourceMetadata -> String
$cshow :: SourceMetadata -> String
showsPrec :: Int -> SourceMetadata -> ShowS
$cshowsPrec :: Int -> SourceMetadata -> ShowS
Show, SourceMetadata -> SourceMetadata -> Bool
(SourceMetadata -> SourceMetadata -> Bool)
-> (SourceMetadata -> SourceMetadata -> Bool) -> Eq SourceMetadata
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: SourceMetadata -> SourceMetadata -> Bool
$c/= :: SourceMetadata -> SourceMetadata -> Bool
== :: SourceMetadata -> SourceMetadata -> Bool
$c== :: SourceMetadata -> SourceMetadata -> Bool
Eq)
$(A.deriveToJSON hasuraJSON ''SourceMetadata)
data HasuraTelemetry = HasuraTelemetry
{ HasuraTelemetry -> MetadataDbId
_htMetadataDbUid :: MetadataDbId,
HasuraTelemetry -> InstanceId
_htInstanceUid :: InstanceId,
HasuraTelemetry -> Version
_htHasuraVersion :: Version,
HasuraTelemetry -> Maybe CI
_htCi :: Maybe CI.CI,
HasuraTelemetry -> SourceMetadata
_htSourceMetadata :: SourceMetadata,
HasuraTelemetry -> Metrics
_htMetrics :: Metrics
}
deriving (Int -> HasuraTelemetry -> ShowS
[HasuraTelemetry] -> ShowS
HasuraTelemetry -> String
(Int -> HasuraTelemetry -> ShowS)
-> (HasuraTelemetry -> String)
-> ([HasuraTelemetry] -> ShowS)
-> Show HasuraTelemetry
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [HasuraTelemetry] -> ShowS
$cshowList :: [HasuraTelemetry] -> ShowS
show :: HasuraTelemetry -> String
$cshow :: HasuraTelemetry -> String
showsPrec :: Int -> HasuraTelemetry -> ShowS
$cshowsPrec :: Int -> HasuraTelemetry -> ShowS
Show)
$(A.deriveToJSON hasuraJSON ''HasuraTelemetry)
newtype Topic = Topic {Topic -> Text
getTopic :: Text}
deriving (Int -> Topic -> ShowS
[Topic] -> ShowS
Topic -> String
(Int -> Topic -> ShowS)
-> (Topic -> String) -> ([Topic] -> ShowS) -> Show Topic
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [Topic] -> ShowS
$cshowList :: [Topic] -> ShowS
show :: Topic -> String
$cshow :: Topic -> String
showsPrec :: Int -> Topic -> ShowS
$cshowsPrec :: Int -> Topic -> ShowS
Show, Topic -> Topic -> Bool
(Topic -> Topic -> Bool) -> (Topic -> Topic -> Bool) -> Eq Topic
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: Topic -> Topic -> Bool
$c/= :: Topic -> Topic -> Bool
== :: Topic -> Topic -> Bool
$c== :: Topic -> Topic -> Bool
Eq, [Topic] -> Value
[Topic] -> Encoding
Topic -> Value
Topic -> Encoding
(Topic -> Value)
-> (Topic -> Encoding)
-> ([Topic] -> Value)
-> ([Topic] -> Encoding)
-> ToJSON Topic
forall a.
(a -> Value)
-> (a -> Encoding)
-> ([a] -> Value)
-> ([a] -> Encoding)
-> ToJSON a
toEncodingList :: [Topic] -> Encoding
$ctoEncodingList :: [Topic] -> Encoding
toJSONList :: [Topic] -> Value
$ctoJSONList :: [Topic] -> Value
toEncoding :: Topic -> Encoding
$ctoEncoding :: Topic -> Encoding
toJSON :: Topic -> Value
$ctoJSON :: Topic -> Value
A.ToJSON, Value -> Parser [Topic]
Value -> Parser Topic
(Value -> Parser Topic)
-> (Value -> Parser [Topic]) -> FromJSON Topic
forall a.
(Value -> Parser a) -> (Value -> Parser [a]) -> FromJSON a
parseJSONList :: Value -> Parser [Topic]
$cparseJSONList :: Value -> Parser [Topic]
parseJSON :: Value -> Parser Topic
$cparseJSON :: Value -> Parser Topic
A.FromJSON)
data TelemetryPayload = TelemetryPayload
{ TelemetryPayload -> Topic
_tpTopic :: Topic,
TelemetryPayload -> HasuraTelemetry
_tpData :: HasuraTelemetry
}
deriving (Int -> TelemetryPayload -> ShowS
[TelemetryPayload] -> ShowS
TelemetryPayload -> String
(Int -> TelemetryPayload -> ShowS)
-> (TelemetryPayload -> String)
-> ([TelemetryPayload] -> ShowS)
-> Show TelemetryPayload
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [TelemetryPayload] -> ShowS
$cshowList :: [TelemetryPayload] -> ShowS
show :: TelemetryPayload -> String
$cshow :: TelemetryPayload -> String
showsPrec :: Int -> TelemetryPayload -> ShowS
$cshowsPrec :: Int -> TelemetryPayload -> ShowS
Show)
$(A.deriveToJSON hasuraJSON ''TelemetryPayload)