{-# LANGUAGE DeriveDataTypeable #-}
{-# LANGUAGE DeriveGeneric #-}
{-# LANGUAGE LambdaCase #-}
{-# LANGUAGE NoImplicitPrelude #-}
{-# LANGUAGE OverloadedStrings #-}
{-# OPTIONS_GHC -fno-warn-unused-imports #-}
module Network.Google.Logging.Types.Sum where
import Network.Google.Prelude hiding (Bytes)
data MetricDescriptorValueType
= ValueTypeUnspecified
| Bool
| INT64
| Double
| String
| Distribution
| Money
deriving (Eq, Ord, Enum, Read, Show, Data, Typeable, Generic)
instance Hashable MetricDescriptorValueType
instance FromHttpApiData MetricDescriptorValueType where
parseQueryParam = \case
"VALUE_TYPE_UNSPECIFIED" -> Right ValueTypeUnspecified
"BOOL" -> Right Bool
"INT64" -> Right INT64
"DOUBLE" -> Right Double
"STRING" -> Right String
"DISTRIBUTION" -> Right Distribution
"MONEY" -> Right Money
x -> Left ("Unable to parse MetricDescriptorValueType from: " <> x)
instance ToHttpApiData MetricDescriptorValueType where
toQueryParam = \case
ValueTypeUnspecified -> "VALUE_TYPE_UNSPECIFIED"
Bool -> "BOOL"
INT64 -> "INT64"
Double -> "DOUBLE"
String -> "STRING"
Distribution -> "DISTRIBUTION"
Money -> "MONEY"
instance FromJSON MetricDescriptorValueType where
parseJSON = parseJSONText "MetricDescriptorValueType"
instance ToJSON MetricDescriptorValueType where
toJSON = toJSONText
data LogMetricVersion
= V2
| V1
deriving (Eq, Ord, Enum, Read, Show, Data, Typeable, Generic)
instance Hashable LogMetricVersion
instance FromHttpApiData LogMetricVersion where
parseQueryParam = \case
"V2" -> Right V2
"V1" -> Right V1
x -> Left ("Unable to parse LogMetricVersion from: " <> x)
instance ToHttpApiData LogMetricVersion where
toQueryParam = \case
V2 -> "V2"
V1 -> "V1"
instance FromJSON LogMetricVersion where
parseJSON = parseJSONText "LogMetricVersion"
instance ToJSON LogMetricVersion where
toJSON = toJSONText
data LogSinkOutputVersionFormat
= LSOVFVersionFormatUnspecified
| LSOVFV2
| LSOVFV1
deriving (Eq, Ord, Enum, Read, Show, Data, Typeable, Generic)
instance Hashable LogSinkOutputVersionFormat
instance FromHttpApiData LogSinkOutputVersionFormat where
parseQueryParam = \case
"VERSION_FORMAT_UNSPECIFIED" -> Right LSOVFVersionFormatUnspecified
"V2" -> Right LSOVFV2
"V1" -> Right LSOVFV1
x -> Left ("Unable to parse LogSinkOutputVersionFormat from: " <> x)
instance ToHttpApiData LogSinkOutputVersionFormat where
toQueryParam = \case
LSOVFVersionFormatUnspecified -> "VERSION_FORMAT_UNSPECIFIED"
LSOVFV2 -> "V2"
LSOVFV1 -> "V1"
instance FromJSON LogSinkOutputVersionFormat where
parseJSON = parseJSONText "LogSinkOutputVersionFormat"
instance ToJSON LogSinkOutputVersionFormat where
toJSON = toJSONText
data MetricDescriptorMetadataLaunchStage
= LaunchStageUnspecified
| EarlyAccess
| Alpha
| Beta
| GA
| Deprecated
deriving (Eq, Ord, Enum, Read, Show, Data, Typeable, Generic)
instance Hashable MetricDescriptorMetadataLaunchStage
instance FromHttpApiData MetricDescriptorMetadataLaunchStage where
parseQueryParam = \case
"LAUNCH_STAGE_UNSPECIFIED" -> Right LaunchStageUnspecified
"EARLY_ACCESS" -> Right EarlyAccess
"ALPHA" -> Right Alpha
"BETA" -> Right Beta
"GA" -> Right GA
"DEPRECATED" -> Right Deprecated
x -> Left ("Unable to parse MetricDescriptorMetadataLaunchStage from: " <> x)
instance ToHttpApiData MetricDescriptorMetadataLaunchStage where
toQueryParam = \case
LaunchStageUnspecified -> "LAUNCH_STAGE_UNSPECIFIED"
EarlyAccess -> "EARLY_ACCESS"
Alpha -> "ALPHA"
Beta -> "BETA"
GA -> "GA"
Deprecated -> "DEPRECATED"
instance FromJSON MetricDescriptorMetadataLaunchStage where
parseJSON = parseJSONText "MetricDescriptorMetadataLaunchStage"
instance ToJSON MetricDescriptorMetadataLaunchStage where
toJSON = toJSONText
data LabelDescriptorValueType
= LDVTString
| LDVTBool
| LDVTINT64
deriving (Eq, Ord, Enum, Read, Show, Data, Typeable, Generic)
instance Hashable LabelDescriptorValueType
instance FromHttpApiData LabelDescriptorValueType where
parseQueryParam = \case
"STRING" -> Right LDVTString
"BOOL" -> Right LDVTBool
"INT64" -> Right LDVTINT64
x -> Left ("Unable to parse LabelDescriptorValueType from: " <> x)
instance ToHttpApiData LabelDescriptorValueType where
toQueryParam = \case
LDVTString -> "STRING"
LDVTBool -> "BOOL"
LDVTINT64 -> "INT64"
instance FromJSON LabelDescriptorValueType where
parseJSON = parseJSONText "LabelDescriptorValueType"
instance ToJSON LabelDescriptorValueType where
toJSON = toJSONText
data Xgafv
= X1
| X2
deriving (Eq, Ord, Enum, Read, Show, Data, Typeable, Generic)
instance Hashable Xgafv
instance FromHttpApiData Xgafv where
parseQueryParam = \case
"1" -> Right X1
"2" -> Right X2
x -> Left ("Unable to parse Xgafv from: " <> x)
instance ToHttpApiData Xgafv where
toQueryParam = \case
X1 -> "1"
X2 -> "2"
instance FromJSON Xgafv where
parseJSON = parseJSONText "Xgafv"
instance ToJSON Xgafv where
toJSON = toJSONText
data MetricDescriptorMetricKind
= MetricKindUnspecified
| Gauge
| Delta
| Cumulative
deriving (Eq, Ord, Enum, Read, Show, Data, Typeable, Generic)
instance Hashable MetricDescriptorMetricKind
instance FromHttpApiData MetricDescriptorMetricKind where
parseQueryParam = \case
"METRIC_KIND_UNSPECIFIED" -> Right MetricKindUnspecified
"GAUGE" -> Right Gauge
"DELTA" -> Right Delta
"CUMULATIVE" -> Right Cumulative
x -> Left ("Unable to parse MetricDescriptorMetricKind from: " <> x)
instance ToHttpApiData MetricDescriptorMetricKind where
toQueryParam = \case
MetricKindUnspecified -> "METRIC_KIND_UNSPECIFIED"
Gauge -> "GAUGE"
Delta -> "DELTA"
Cumulative -> "CUMULATIVE"
instance FromJSON MetricDescriptorMetricKind where
parseJSON = parseJSONText "MetricDescriptorMetricKind"
instance ToJSON MetricDescriptorMetricKind where
toJSON = toJSONText
data LogEntrySeverity
= Default
| Debug
| Info
| Notice
| Warning
| Error'
| Critical
| Alert
| Emergency
deriving (Eq, Ord, Enum, Read, Show, Data, Typeable, Generic)
instance Hashable LogEntrySeverity
instance FromHttpApiData LogEntrySeverity where
parseQueryParam = \case
"DEFAULT" -> Right Default
"DEBUG" -> Right Debug
"INFO" -> Right Info
"NOTICE" -> Right Notice
"WARNING" -> Right Warning
"ERROR" -> Right Error'
"CRITICAL" -> Right Critical
"ALERT" -> Right Alert
"EMERGENCY" -> Right Emergency
x -> Left ("Unable to parse LogEntrySeverity from: " <> x)
instance ToHttpApiData LogEntrySeverity where
toQueryParam = \case
Default -> "DEFAULT"
Debug -> "DEBUG"
Info -> "INFO"
Notice -> "NOTICE"
Warning -> "WARNING"
Error' -> "ERROR"
Critical -> "CRITICAL"
Alert -> "ALERT"
Emergency -> "EMERGENCY"
instance FromJSON LogEntrySeverity where
parseJSON = parseJSONText "LogEntrySeverity"
instance ToJSON LogEntrySeverity where
toJSON = toJSONText
data LogLineSeverity
= LLSDefault
| LLSDebug
| LLSInfo
| LLSNotice
| LLSWarning
| LLSError'
| LLSCritical
| LLSAlert
| LLSEmergency
deriving (Eq, Ord, Enum, Read, Show, Data, Typeable, Generic)
instance Hashable LogLineSeverity
instance FromHttpApiData LogLineSeverity where
parseQueryParam = \case
"DEFAULT" -> Right LLSDefault
"DEBUG" -> Right LLSDebug
"INFO" -> Right LLSInfo
"NOTICE" -> Right LLSNotice
"WARNING" -> Right LLSWarning
"ERROR" -> Right LLSError'
"CRITICAL" -> Right LLSCritical
"ALERT" -> Right LLSAlert
"EMERGENCY" -> Right LLSEmergency
x -> Left ("Unable to parse LogLineSeverity from: " <> x)
instance ToHttpApiData LogLineSeverity where
toQueryParam = \case
LLSDefault -> "DEFAULT"
LLSDebug -> "DEBUG"
LLSInfo -> "INFO"
LLSNotice -> "NOTICE"
LLSWarning -> "WARNING"
LLSError' -> "ERROR"
LLSCritical -> "CRITICAL"
LLSAlert -> "ALERT"
LLSEmergency -> "EMERGENCY"
instance FromJSON LogLineSeverity where
parseJSON = parseJSONText "LogLineSeverity"
instance ToJSON LogLineSeverity where
toJSON = toJSONText