{-# LANGUAGE DeriveDataTypeable #-}
{-# LANGUAGE DeriveGeneric #-}
{-# LANGUAGE NoImplicitPrelude #-}
{-# LANGUAGE OverloadedStrings #-}
{-# LANGUAGE RecordWildCards #-}
{-# OPTIONS_GHC -fno-warn-unused-binds #-}
{-# OPTIONS_GHC -fno-warn-unused-imports #-}
module Network.Google.ServiceConsumerManagement.Types.Product where
import Network.Google.Prelude
import Network.Google.ServiceConsumerManagement.Types.Sum
data SystemParameter =
SystemParameter'
{ _spHTTPHeader :: !(Maybe Text)
, _spURLQueryParameter :: !(Maybe Text)
, _spName :: !(Maybe Text)
}
deriving (Eq, Show, Data, Typeable, Generic)
systemParameter
:: SystemParameter
systemParameter =
SystemParameter'
{_spHTTPHeader = Nothing, _spURLQueryParameter = Nothing, _spName = Nothing}
spHTTPHeader :: Lens' SystemParameter (Maybe Text)
spHTTPHeader
= lens _spHTTPHeader (\ s a -> s{_spHTTPHeader = a})
spURLQueryParameter :: Lens' SystemParameter (Maybe Text)
spURLQueryParameter
= lens _spURLQueryParameter
(\ s a -> s{_spURLQueryParameter = a})
spName :: Lens' SystemParameter (Maybe Text)
spName = lens _spName (\ s a -> s{_spName = a})
instance FromJSON SystemParameter where
parseJSON
= withObject "SystemParameter"
(\ o ->
SystemParameter' <$>
(o .:? "httpHeader") <*> (o .:? "urlQueryParameter")
<*> (o .:? "name"))
instance ToJSON SystemParameter where
toJSON SystemParameter'{..}
= object
(catMaybes
[("httpHeader" .=) <$> _spHTTPHeader,
("urlQueryParameter" .=) <$> _spURLQueryParameter,
("name" .=) <$> _spName])
data MonitoredResourceDescriptor =
MonitoredResourceDescriptor'
{ _mrdName :: !(Maybe Text)
, _mrdDisplayName :: !(Maybe Text)
, _mrdLabels :: !(Maybe [LabelDescriptor])
, _mrdType :: !(Maybe Text)
, _mrdDescription :: !(Maybe Text)
}
deriving (Eq, Show, Data, Typeable, Generic)
monitoredResourceDescriptor
:: MonitoredResourceDescriptor
monitoredResourceDescriptor =
MonitoredResourceDescriptor'
{ _mrdName = Nothing
, _mrdDisplayName = Nothing
, _mrdLabels = Nothing
, _mrdType = Nothing
, _mrdDescription = Nothing
}
mrdName :: Lens' MonitoredResourceDescriptor (Maybe Text)
mrdName = lens _mrdName (\ s a -> s{_mrdName = a})
mrdDisplayName :: Lens' MonitoredResourceDescriptor (Maybe Text)
mrdDisplayName
= lens _mrdDisplayName
(\ s a -> s{_mrdDisplayName = a})
mrdLabels :: Lens' MonitoredResourceDescriptor [LabelDescriptor]
mrdLabels
= lens _mrdLabels (\ s a -> s{_mrdLabels = a}) .
_Default
. _Coerce
mrdType :: Lens' MonitoredResourceDescriptor (Maybe Text)
mrdType = lens _mrdType (\ s a -> s{_mrdType = a})
mrdDescription :: Lens' MonitoredResourceDescriptor (Maybe Text)
mrdDescription
= lens _mrdDescription
(\ s a -> s{_mrdDescription = a})
instance FromJSON MonitoredResourceDescriptor where
parseJSON
= withObject "MonitoredResourceDescriptor"
(\ o ->
MonitoredResourceDescriptor' <$>
(o .:? "name") <*> (o .:? "displayName") <*>
(o .:? "labels" .!= mempty)
<*> (o .:? "type")
<*> (o .:? "description"))
instance ToJSON MonitoredResourceDescriptor where
toJSON MonitoredResourceDescriptor'{..}
= object
(catMaybes
[("name" .=) <$> _mrdName,
("displayName" .=) <$> _mrdDisplayName,
("labels" .=) <$> _mrdLabels,
("type" .=) <$> _mrdType,
("description" .=) <$> _mrdDescription])
data V1Beta1RefreshConsumerResponse =
V1Beta1RefreshConsumerResponse'
deriving (Eq, Show, Data, Typeable, Generic)
v1Beta1RefreshConsumerResponse
:: V1Beta1RefreshConsumerResponse
v1Beta1RefreshConsumerResponse = V1Beta1RefreshConsumerResponse'
instance FromJSON V1Beta1RefreshConsumerResponse
where
parseJSON
= withObject "V1Beta1RefreshConsumerResponse"
(\ o -> pure V1Beta1RefreshConsumerResponse')
instance ToJSON V1Beta1RefreshConsumerResponse where
toJSON = const emptyObject
data DocumentationRule =
DocumentationRule'
{ _drSelector :: !(Maybe Text)
, _drDeprecationDescription :: !(Maybe Text)
, _drDescription :: !(Maybe Text)
}
deriving (Eq, Show, Data, Typeable, Generic)
documentationRule
:: DocumentationRule
documentationRule =
DocumentationRule'
{ _drSelector = Nothing
, _drDeprecationDescription = Nothing
, _drDescription = Nothing
}
drSelector :: Lens' DocumentationRule (Maybe Text)
drSelector
= lens _drSelector (\ s a -> s{_drSelector = a})
drDeprecationDescription :: Lens' DocumentationRule (Maybe Text)
drDeprecationDescription
= lens _drDeprecationDescription
(\ s a -> s{_drDeprecationDescription = a})
drDescription :: Lens' DocumentationRule (Maybe Text)
drDescription
= lens _drDescription
(\ s a -> s{_drDescription = a})
instance FromJSON DocumentationRule where
parseJSON
= withObject "DocumentationRule"
(\ o ->
DocumentationRule' <$>
(o .:? "selector") <*>
(o .:? "deprecationDescription")
<*> (o .:? "description"))
instance ToJSON DocumentationRule where
toJSON DocumentationRule'{..}
= object
(catMaybes
[("selector" .=) <$> _drSelector,
("deprecationDescription" .=) <$>
_drDeprecationDescription,
("description" .=) <$> _drDescription])
data Status =
Status'
{ _sDetails :: !(Maybe [StatusDetailsItem])
, _sCode :: !(Maybe (Textual Int32))
, _sMessage :: !(Maybe Text)
}
deriving (Eq, Show, Data, Typeable, Generic)
status
:: Status
status = Status' {_sDetails = Nothing, _sCode = Nothing, _sMessage = Nothing}
sDetails :: Lens' Status [StatusDetailsItem]
sDetails
= lens _sDetails (\ s a -> s{_sDetails = a}) .
_Default
. _Coerce
sCode :: Lens' Status (Maybe Int32)
sCode
= lens _sCode (\ s a -> s{_sCode = a}) .
mapping _Coerce
sMessage :: Lens' Status (Maybe Text)
sMessage = lens _sMessage (\ s a -> s{_sMessage = a})
instance FromJSON Status where
parseJSON
= withObject "Status"
(\ o ->
Status' <$>
(o .:? "details" .!= mempty) <*> (o .:? "code") <*>
(o .:? "message"))
instance ToJSON Status where
toJSON Status'{..}
= object
(catMaybes
[("details" .=) <$> _sDetails,
("code" .=) <$> _sCode,
("message" .=) <$> _sMessage])
data BillingDestination =
BillingDestination'
{ _bdMetrics :: !(Maybe [Text])
, _bdMonitoredResource :: !(Maybe Text)
}
deriving (Eq, Show, Data, Typeable, Generic)
billingDestination
:: BillingDestination
billingDestination =
BillingDestination' {_bdMetrics = Nothing, _bdMonitoredResource = Nothing}
bdMetrics :: Lens' BillingDestination [Text]
bdMetrics
= lens _bdMetrics (\ s a -> s{_bdMetrics = a}) .
_Default
. _Coerce
bdMonitoredResource :: Lens' BillingDestination (Maybe Text)
bdMonitoredResource
= lens _bdMonitoredResource
(\ s a -> s{_bdMonitoredResource = a})
instance FromJSON BillingDestination where
parseJSON
= withObject "BillingDestination"
(\ o ->
BillingDestination' <$>
(o .:? "metrics" .!= mempty) <*>
(o .:? "monitoredResource"))
instance ToJSON BillingDestination where
toJSON BillingDestination'{..}
= object
(catMaybes
[("metrics" .=) <$> _bdMetrics,
("monitoredResource" .=) <$> _bdMonitoredResource])
newtype Control =
Control'
{ _cEnvironment :: Maybe Text
}
deriving (Eq, Show, Data, Typeable, Generic)
control
:: Control
control = Control' {_cEnvironment = Nothing}
cEnvironment :: Lens' Control (Maybe Text)
cEnvironment
= lens _cEnvironment (\ s a -> s{_cEnvironment = a})
instance FromJSON Control where
parseJSON
= withObject "Control"
(\ o -> Control' <$> (o .:? "environment"))
instance ToJSON Control where
toJSON Control'{..}
= object
(catMaybes [("environment" .=) <$> _cEnvironment])
data AuthRequirement =
AuthRequirement'
{ _arProviderId :: !(Maybe Text)
, _arAudiences :: !(Maybe Text)
}
deriving (Eq, Show, Data, Typeable, Generic)
authRequirement
:: AuthRequirement
authRequirement =
AuthRequirement' {_arProviderId = Nothing, _arAudiences = Nothing}
arProviderId :: Lens' AuthRequirement (Maybe Text)
arProviderId
= lens _arProviderId (\ s a -> s{_arProviderId = a})
arAudiences :: Lens' AuthRequirement (Maybe Text)
arAudiences
= lens _arAudiences (\ s a -> s{_arAudiences = a})
instance FromJSON AuthRequirement where
parseJSON
= withObject "AuthRequirement"
(\ o ->
AuthRequirement' <$>
(o .:? "providerId") <*> (o .:? "audiences"))
instance ToJSON AuthRequirement where
toJSON AuthRequirement'{..}
= object
(catMaybes
[("providerId" .=) <$> _arProviderId,
("audiences" .=) <$> _arAudiences])
newtype Context =
Context'
{ _cRules :: Maybe [ContextRule]
}
deriving (Eq, Show, Data, Typeable, Generic)
context
:: Context
context = Context' {_cRules = Nothing}
cRules :: Lens' Context [ContextRule]
cRules
= lens _cRules (\ s a -> s{_cRules = a}) . _Default .
_Coerce
instance FromJSON Context where
parseJSON
= withObject "Context"
(\ o -> Context' <$> (o .:? "rules" .!= mempty))
instance ToJSON Context where
toJSON Context'{..}
= object (catMaybes [("rules" .=) <$> _cRules])
data LoggingDestination =
LoggingDestination'
{ _ldMonitoredResource :: !(Maybe Text)
, _ldLogs :: !(Maybe [Text])
}
deriving (Eq, Show, Data, Typeable, Generic)
loggingDestination
:: LoggingDestination
loggingDestination =
LoggingDestination' {_ldMonitoredResource = Nothing, _ldLogs = Nothing}
ldMonitoredResource :: Lens' LoggingDestination (Maybe Text)
ldMonitoredResource
= lens _ldMonitoredResource
(\ s a -> s{_ldMonitoredResource = a})
ldLogs :: Lens' LoggingDestination [Text]
ldLogs
= lens _ldLogs (\ s a -> s{_ldLogs = a}) . _Default .
_Coerce
instance FromJSON LoggingDestination where
parseJSON
= withObject "LoggingDestination"
(\ o ->
LoggingDestination' <$>
(o .:? "monitoredResource") <*>
(o .:? "logs" .!= mempty))
instance ToJSON LoggingDestination where
toJSON LoggingDestination'{..}
= object
(catMaybes
[("monitoredResource" .=) <$> _ldMonitoredResource,
("logs" .=) <$> _ldLogs])
data MetricDescriptor =
MetricDescriptor'
{ _mdMetricKind :: !(Maybe MetricDescriptorMetricKind)
, _mdName :: !(Maybe Text)
, _mdMetadata :: !(Maybe MetricDescriptorMetadata)
, _mdDisplayName :: !(Maybe Text)
, _mdLabels :: !(Maybe [LabelDescriptor])
, _mdType :: !(Maybe Text)
, _mdValueType :: !(Maybe MetricDescriptorValueType)
, _mdDescription :: !(Maybe Text)
, _mdUnit :: !(Maybe Text)
}
deriving (Eq, Show, Data, Typeable, Generic)
metricDescriptor
:: MetricDescriptor
metricDescriptor =
MetricDescriptor'
{ _mdMetricKind = Nothing
, _mdName = Nothing
, _mdMetadata = Nothing
, _mdDisplayName = Nothing
, _mdLabels = Nothing
, _mdType = Nothing
, _mdValueType = Nothing
, _mdDescription = Nothing
, _mdUnit = Nothing
}
mdMetricKind :: Lens' MetricDescriptor (Maybe MetricDescriptorMetricKind)
mdMetricKind
= lens _mdMetricKind (\ s a -> s{_mdMetricKind = a})
mdName :: Lens' MetricDescriptor (Maybe Text)
mdName = lens _mdName (\ s a -> s{_mdName = a})
mdMetadata :: Lens' MetricDescriptor (Maybe MetricDescriptorMetadata)
mdMetadata
= lens _mdMetadata (\ s a -> s{_mdMetadata = a})
mdDisplayName :: Lens' MetricDescriptor (Maybe Text)
mdDisplayName
= lens _mdDisplayName
(\ s a -> s{_mdDisplayName = a})
mdLabels :: Lens' MetricDescriptor [LabelDescriptor]
mdLabels
= lens _mdLabels (\ s a -> s{_mdLabels = a}) .
_Default
. _Coerce
mdType :: Lens' MetricDescriptor (Maybe Text)
mdType = lens _mdType (\ s a -> s{_mdType = a})
mdValueType :: Lens' MetricDescriptor (Maybe MetricDescriptorValueType)
mdValueType
= lens _mdValueType (\ s a -> s{_mdValueType = a})
mdDescription :: Lens' MetricDescriptor (Maybe Text)
mdDescription
= lens _mdDescription
(\ s a -> s{_mdDescription = a})
mdUnit :: Lens' MetricDescriptor (Maybe Text)
mdUnit = lens _mdUnit (\ s a -> s{_mdUnit = a})
instance FromJSON MetricDescriptor where
parseJSON
= withObject "MetricDescriptor"
(\ o ->
MetricDescriptor' <$>
(o .:? "metricKind") <*> (o .:? "name") <*>
(o .:? "metadata")
<*> (o .:? "displayName")
<*> (o .:? "labels" .!= mempty)
<*> (o .:? "type")
<*> (o .:? "valueType")
<*> (o .:? "description")
<*> (o .:? "unit"))
instance ToJSON MetricDescriptor where
toJSON MetricDescriptor'{..}
= object
(catMaybes
[("metricKind" .=) <$> _mdMetricKind,
("name" .=) <$> _mdName,
("metadata" .=) <$> _mdMetadata,
("displayName" .=) <$> _mdDisplayName,
("labels" .=) <$> _mdLabels, ("type" .=) <$> _mdType,
("valueType" .=) <$> _mdValueType,
("description" .=) <$> _mdDescription,
("unit" .=) <$> _mdUnit])
data ListOperationsResponse =
ListOperationsResponse'
{ _lorNextPageToken :: !(Maybe Text)
, _lorOperations :: !(Maybe [Operation])
}
deriving (Eq, Show, Data, Typeable, Generic)
listOperationsResponse
:: ListOperationsResponse
listOperationsResponse =
ListOperationsResponse'
{_lorNextPageToken = Nothing, _lorOperations = Nothing}
lorNextPageToken :: Lens' ListOperationsResponse (Maybe Text)
lorNextPageToken
= lens _lorNextPageToken
(\ s a -> s{_lorNextPageToken = a})
lorOperations :: Lens' ListOperationsResponse [Operation]
lorOperations
= lens _lorOperations
(\ s a -> s{_lorOperations = a})
. _Default
. _Coerce
instance FromJSON ListOperationsResponse where
parseJSON
= withObject "ListOperationsResponse"
(\ o ->
ListOperationsResponse' <$>
(o .:? "nextPageToken") <*>
(o .:? "operations" .!= mempty))
instance ToJSON ListOperationsResponse where
toJSON ListOperationsResponse'{..}
= object
(catMaybes
[("nextPageToken" .=) <$> _lorNextPageToken,
("operations" .=) <$> _lorOperations])
data CancelOperationRequest =
CancelOperationRequest'
deriving (Eq, Show, Data, Typeable, Generic)
cancelOperationRequest
:: CancelOperationRequest
cancelOperationRequest = CancelOperationRequest'
instance FromJSON CancelOperationRequest where
parseJSON
= withObject "CancelOperationRequest"
(\ o -> pure CancelOperationRequest')
instance ToJSON CancelOperationRequest where
toJSON = const emptyObject
data BackendRule =
BackendRule'
{ _brJwtAudience :: !(Maybe Text)
, _brSelector :: !(Maybe Text)
, _brMinDeadline :: !(Maybe (Textual Double))
, _brAddress :: !(Maybe Text)
, _brOperationDeadline :: !(Maybe (Textual Double))
, _brDeadline :: !(Maybe (Textual Double))
, _brPathTranslation :: !(Maybe BackendRulePathTranslation)
}
deriving (Eq, Show, Data, Typeable, Generic)
backendRule
:: BackendRule
backendRule =
BackendRule'
{ _brJwtAudience = Nothing
, _brSelector = Nothing
, _brMinDeadline = Nothing
, _brAddress = Nothing
, _brOperationDeadline = Nothing
, _brDeadline = Nothing
, _brPathTranslation = Nothing
}
brJwtAudience :: Lens' BackendRule (Maybe Text)
brJwtAudience
= lens _brJwtAudience
(\ s a -> s{_brJwtAudience = a})
brSelector :: Lens' BackendRule (Maybe Text)
brSelector
= lens _brSelector (\ s a -> s{_brSelector = a})
brMinDeadline :: Lens' BackendRule (Maybe Double)
brMinDeadline
= lens _brMinDeadline
(\ s a -> s{_brMinDeadline = a})
. mapping _Coerce
brAddress :: Lens' BackendRule (Maybe Text)
brAddress
= lens _brAddress (\ s a -> s{_brAddress = a})
brOperationDeadline :: Lens' BackendRule (Maybe Double)
brOperationDeadline
= lens _brOperationDeadline
(\ s a -> s{_brOperationDeadline = a})
. mapping _Coerce
brDeadline :: Lens' BackendRule (Maybe Double)
brDeadline
= lens _brDeadline (\ s a -> s{_brDeadline = a}) .
mapping _Coerce
brPathTranslation :: Lens' BackendRule (Maybe BackendRulePathTranslation)
brPathTranslation
= lens _brPathTranslation
(\ s a -> s{_brPathTranslation = a})
instance FromJSON BackendRule where
parseJSON
= withObject "BackendRule"
(\ o ->
BackendRule' <$>
(o .:? "jwtAudience") <*> (o .:? "selector") <*>
(o .:? "minDeadline")
<*> (o .:? "address")
<*> (o .:? "operationDeadline")
<*> (o .:? "deadline")
<*> (o .:? "pathTranslation"))
instance ToJSON BackendRule where
toJSON BackendRule'{..}
= object
(catMaybes
[("jwtAudience" .=) <$> _brJwtAudience,
("selector" .=) <$> _brSelector,
("minDeadline" .=) <$> _brMinDeadline,
("address" .=) <$> _brAddress,
("operationDeadline" .=) <$> _brOperationDeadline,
("deadline" .=) <$> _brDeadline,
("pathTranslation" .=) <$> _brPathTranslation])
newtype SourceContext =
SourceContext'
{ _scFileName :: Maybe Text
}
deriving (Eq, Show, Data, Typeable, Generic)
sourceContext
:: SourceContext
sourceContext = SourceContext' {_scFileName = Nothing}
scFileName :: Lens' SourceContext (Maybe Text)
scFileName
= lens _scFileName (\ s a -> s{_scFileName = a})
instance FromJSON SourceContext where
parseJSON
= withObject "SourceContext"
(\ o -> SourceContext' <$> (o .:? "fileName"))
instance ToJSON SourceContext where
toJSON SourceContext'{..}
= object
(catMaybes [("fileName" .=) <$> _scFileName])
data SearchTenancyUnitsResponse =
SearchTenancyUnitsResponse'
{ _sturTenancyUnits :: !(Maybe [TenancyUnit])
, _sturNextPageToken :: !(Maybe Text)
}
deriving (Eq, Show, Data, Typeable, Generic)
searchTenancyUnitsResponse
:: SearchTenancyUnitsResponse
searchTenancyUnitsResponse =
SearchTenancyUnitsResponse'
{_sturTenancyUnits = Nothing, _sturNextPageToken = Nothing}
sturTenancyUnits :: Lens' SearchTenancyUnitsResponse [TenancyUnit]
sturTenancyUnits
= lens _sturTenancyUnits
(\ s a -> s{_sturTenancyUnits = a})
. _Default
. _Coerce
sturNextPageToken :: Lens' SearchTenancyUnitsResponse (Maybe Text)
sturNextPageToken
= lens _sturNextPageToken
(\ s a -> s{_sturNextPageToken = a})
instance FromJSON SearchTenancyUnitsResponse where
parseJSON
= withObject "SearchTenancyUnitsResponse"
(\ o ->
SearchTenancyUnitsResponse' <$>
(o .:? "tenancyUnits" .!= mempty) <*>
(o .:? "nextPageToken"))
instance ToJSON SearchTenancyUnitsResponse where
toJSON SearchTenancyUnitsResponse'{..}
= object
(catMaybes
[("tenancyUnits" .=) <$> _sturTenancyUnits,
("nextPageToken" .=) <$> _sturNextPageToken])
data Field =
Field'
{ _fKind :: !(Maybe FieldKind)
, _fOneofIndex :: !(Maybe (Textual Int32))
, _fName :: !(Maybe Text)
, _fJSONName :: !(Maybe Text)
, _fCardinality :: !(Maybe FieldCardinality)
, _fOptions :: !(Maybe [Option])
, _fPacked :: !(Maybe Bool)
, _fDefaultValue :: !(Maybe Text)
, _fNumber :: !(Maybe (Textual Int32))
, _fTypeURL :: !(Maybe Text)
}
deriving (Eq, Show, Data, Typeable, Generic)
field
:: Field
field =
Field'
{ _fKind = Nothing
, _fOneofIndex = Nothing
, _fName = Nothing
, _fJSONName = Nothing
, _fCardinality = Nothing
, _fOptions = Nothing
, _fPacked = Nothing
, _fDefaultValue = Nothing
, _fNumber = Nothing
, _fTypeURL = Nothing
}
fKind :: Lens' Field (Maybe FieldKind)
fKind = lens _fKind (\ s a -> s{_fKind = a})
fOneofIndex :: Lens' Field (Maybe Int32)
fOneofIndex
= lens _fOneofIndex (\ s a -> s{_fOneofIndex = a}) .
mapping _Coerce
fName :: Lens' Field (Maybe Text)
fName = lens _fName (\ s a -> s{_fName = a})
fJSONName :: Lens' Field (Maybe Text)
fJSONName
= lens _fJSONName (\ s a -> s{_fJSONName = a})
fCardinality :: Lens' Field (Maybe FieldCardinality)
fCardinality
= lens _fCardinality (\ s a -> s{_fCardinality = a})
fOptions :: Lens' Field [Option]
fOptions
= lens _fOptions (\ s a -> s{_fOptions = a}) .
_Default
. _Coerce
fPacked :: Lens' Field (Maybe Bool)
fPacked = lens _fPacked (\ s a -> s{_fPacked = a})
fDefaultValue :: Lens' Field (Maybe Text)
fDefaultValue
= lens _fDefaultValue
(\ s a -> s{_fDefaultValue = a})
fNumber :: Lens' Field (Maybe Int32)
fNumber
= lens _fNumber (\ s a -> s{_fNumber = a}) .
mapping _Coerce
fTypeURL :: Lens' Field (Maybe Text)
fTypeURL = lens _fTypeURL (\ s a -> s{_fTypeURL = a})
instance FromJSON Field where
parseJSON
= withObject "Field"
(\ o ->
Field' <$>
(o .:? "kind") <*> (o .:? "oneofIndex") <*>
(o .:? "name")
<*> (o .:? "jsonName")
<*> (o .:? "cardinality")
<*> (o .:? "options" .!= mempty)
<*> (o .:? "packed")
<*> (o .:? "defaultValue")
<*> (o .:? "number")
<*> (o .:? "typeUrl"))
instance ToJSON Field where
toJSON Field'{..}
= object
(catMaybes
[("kind" .=) <$> _fKind,
("oneofIndex" .=) <$> _fOneofIndex,
("name" .=) <$> _fName,
("jsonName" .=) <$> _fJSONName,
("cardinality" .=) <$> _fCardinality,
("options" .=) <$> _fOptions,
("packed" .=) <$> _fPacked,
("defaultValue" .=) <$> _fDefaultValue,
("number" .=) <$> _fNumber,
("typeUrl" .=) <$> _fTypeURL])
data MetricRule =
MetricRule'
{ _mrSelector :: !(Maybe Text)
, _mrMetricCosts :: !(Maybe MetricRuleMetricCosts)
}
deriving (Eq, Show, Data, Typeable, Generic)
metricRule
:: MetricRule
metricRule = MetricRule' {_mrSelector = Nothing, _mrMetricCosts = Nothing}
mrSelector :: Lens' MetricRule (Maybe Text)
mrSelector
= lens _mrSelector (\ s a -> s{_mrSelector = a})
mrMetricCosts :: Lens' MetricRule (Maybe MetricRuleMetricCosts)
mrMetricCosts
= lens _mrMetricCosts
(\ s a -> s{_mrMetricCosts = a})
instance FromJSON MetricRule where
parseJSON
= withObject "MetricRule"
(\ o ->
MetricRule' <$>
(o .:? "selector") <*> (o .:? "metricCosts"))
instance ToJSON MetricRule where
toJSON MetricRule'{..}
= object
(catMaybes
[("selector" .=) <$> _mrSelector,
("metricCosts" .=) <$> _mrMetricCosts])
newtype V1Beta1QuotaOverrideDimensions =
V1Beta1QuotaOverrideDimensions'
{ _vbqodAddtional :: HashMap Text Text
}
deriving (Eq, Show, Data, Typeable, Generic)
v1Beta1QuotaOverrideDimensions
:: HashMap Text Text
-> V1Beta1QuotaOverrideDimensions
v1Beta1QuotaOverrideDimensions pVbqodAddtional_ =
V1Beta1QuotaOverrideDimensions' {_vbqodAddtional = _Coerce # pVbqodAddtional_}
vbqodAddtional :: Lens' V1Beta1QuotaOverrideDimensions (HashMap Text Text)
vbqodAddtional
= lens _vbqodAddtional
(\ s a -> s{_vbqodAddtional = a})
. _Coerce
instance FromJSON V1Beta1QuotaOverrideDimensions
where
parseJSON
= withObject "V1Beta1QuotaOverrideDimensions"
(\ o ->
V1Beta1QuotaOverrideDimensions' <$>
(parseJSONObject o))
instance ToJSON V1Beta1QuotaOverrideDimensions where
toJSON = toJSON . _vbqodAddtional
data Service =
Service'
{ _sControl :: !(Maybe Control)
, _sMetrics :: !(Maybe [MetricDescriptor])
, _sContext :: !(Maybe Context)
, _sAuthentication :: !(Maybe Authentication)
, _sAPIs :: !(Maybe [API])
, _sTypes :: !(Maybe [Type])
, _sSystemTypes :: !(Maybe [Type])
, _sExperimental :: !(Maybe Experimental)
, _sMonitoredResources :: !(Maybe [MonitoredResourceDescriptor])
, _sBackend :: !(Maybe Backend)
, _sMonitoring :: !(Maybe Monitoring)
, _sName :: !(Maybe Text)
, _sSystemParameters :: !(Maybe SystemParameters)
, _sLogs :: !(Maybe [LogDescriptor])
, _sDocumentation :: !(Maybe Documentation)
, _sId :: !(Maybe Text)
, _sUsage :: !(Maybe Usage)
, _sEndpoints :: !(Maybe [Endpoint])
, _sEnums :: !(Maybe [Enum'])
, _sConfigVersion :: !(Maybe (Textual Word32))
, _sHTTP :: !(Maybe HTTP)
, _sTitle :: !(Maybe Text)
, _sProducerProjectId :: !(Maybe Text)
, _sSourceInfo :: !(Maybe SourceInfo)
, _sBilling :: !(Maybe Billing)
, _sCustomError :: !(Maybe CustomError)
, _sLogging :: !(Maybe Logging)
, _sQuota :: !(Maybe Quota)
}
deriving (Eq, Show, Data, Typeable, Generic)
service
:: Service
service =
Service'
{ _sControl = Nothing
, _sMetrics = Nothing
, _sContext = Nothing
, _sAuthentication = Nothing
, _sAPIs = Nothing
, _sTypes = Nothing
, _sSystemTypes = Nothing
, _sExperimental = Nothing
, _sMonitoredResources = Nothing
, _sBackend = Nothing
, _sMonitoring = Nothing
, _sName = Nothing
, _sSystemParameters = Nothing
, _sLogs = Nothing
, _sDocumentation = Nothing
, _sId = Nothing
, _sUsage = Nothing
, _sEndpoints = Nothing
, _sEnums = Nothing
, _sConfigVersion = Nothing
, _sHTTP = Nothing
, _sTitle = Nothing
, _sProducerProjectId = Nothing
, _sSourceInfo = Nothing
, _sBilling = Nothing
, _sCustomError = Nothing
, _sLogging = Nothing
, _sQuota = Nothing
}
sControl :: Lens' Service (Maybe Control)
sControl = lens _sControl (\ s a -> s{_sControl = a})
sMetrics :: Lens' Service [MetricDescriptor]
sMetrics
= lens _sMetrics (\ s a -> s{_sMetrics = a}) .
_Default
. _Coerce
sContext :: Lens' Service (Maybe Context)
sContext = lens _sContext (\ s a -> s{_sContext = a})
sAuthentication :: Lens' Service (Maybe Authentication)
sAuthentication
= lens _sAuthentication
(\ s a -> s{_sAuthentication = a})
sAPIs :: Lens' Service [API]
sAPIs
= lens _sAPIs (\ s a -> s{_sAPIs = a}) . _Default .
_Coerce
sTypes :: Lens' Service [Type]
sTypes
= lens _sTypes (\ s a -> s{_sTypes = a}) . _Default .
_Coerce
sSystemTypes :: Lens' Service [Type]
sSystemTypes
= lens _sSystemTypes (\ s a -> s{_sSystemTypes = a})
. _Default
. _Coerce
sExperimental :: Lens' Service (Maybe Experimental)
sExperimental
= lens _sExperimental
(\ s a -> s{_sExperimental = a})
sMonitoredResources :: Lens' Service [MonitoredResourceDescriptor]
sMonitoredResources
= lens _sMonitoredResources
(\ s a -> s{_sMonitoredResources = a})
. _Default
. _Coerce
sBackend :: Lens' Service (Maybe Backend)
sBackend = lens _sBackend (\ s a -> s{_sBackend = a})
sMonitoring :: Lens' Service (Maybe Monitoring)
sMonitoring
= lens _sMonitoring (\ s a -> s{_sMonitoring = a})
sName :: Lens' Service (Maybe Text)
sName = lens _sName (\ s a -> s{_sName = a})
sSystemParameters :: Lens' Service (Maybe SystemParameters)
sSystemParameters
= lens _sSystemParameters
(\ s a -> s{_sSystemParameters = a})
sLogs :: Lens' Service [LogDescriptor]
sLogs
= lens _sLogs (\ s a -> s{_sLogs = a}) . _Default .
_Coerce
sDocumentation :: Lens' Service (Maybe Documentation)
sDocumentation
= lens _sDocumentation
(\ s a -> s{_sDocumentation = a})
sId :: Lens' Service (Maybe Text)
sId = lens _sId (\ s a -> s{_sId = a})
sUsage :: Lens' Service (Maybe Usage)
sUsage = lens _sUsage (\ s a -> s{_sUsage = a})
sEndpoints :: Lens' Service [Endpoint]
sEndpoints
= lens _sEndpoints (\ s a -> s{_sEndpoints = a}) .
_Default
. _Coerce
sEnums :: Lens' Service [Enum']
sEnums
= lens _sEnums (\ s a -> s{_sEnums = a}) . _Default .
_Coerce
sConfigVersion :: Lens' Service (Maybe Word32)
sConfigVersion
= lens _sConfigVersion
(\ s a -> s{_sConfigVersion = a})
. mapping _Coerce
sHTTP :: Lens' Service (Maybe HTTP)
sHTTP = lens _sHTTP (\ s a -> s{_sHTTP = a})
sTitle :: Lens' Service (Maybe Text)
sTitle = lens _sTitle (\ s a -> s{_sTitle = a})
sProducerProjectId :: Lens' Service (Maybe Text)
sProducerProjectId
= lens _sProducerProjectId
(\ s a -> s{_sProducerProjectId = a})
sSourceInfo :: Lens' Service (Maybe SourceInfo)
sSourceInfo
= lens _sSourceInfo (\ s a -> s{_sSourceInfo = a})
sBilling :: Lens' Service (Maybe Billing)
sBilling = lens _sBilling (\ s a -> s{_sBilling = a})
sCustomError :: Lens' Service (Maybe CustomError)
sCustomError
= lens _sCustomError (\ s a -> s{_sCustomError = a})
sLogging :: Lens' Service (Maybe Logging)
sLogging = lens _sLogging (\ s a -> s{_sLogging = a})
sQuota :: Lens' Service (Maybe Quota)
sQuota = lens _sQuota (\ s a -> s{_sQuota = a})
instance FromJSON Service where
parseJSON
= withObject "Service"
(\ o ->
Service' <$>
(o .:? "control") <*> (o .:? "metrics" .!= mempty)
<*> (o .:? "context")
<*> (o .:? "authentication")
<*> (o .:? "apis" .!= mempty)
<*> (o .:? "types" .!= mempty)
<*> (o .:? "systemTypes" .!= mempty)
<*> (o .:? "experimental")
<*> (o .:? "monitoredResources" .!= mempty)
<*> (o .:? "backend")
<*> (o .:? "monitoring")
<*> (o .:? "name")
<*> (o .:? "systemParameters")
<*> (o .:? "logs" .!= mempty)
<*> (o .:? "documentation")
<*> (o .:? "id")
<*> (o .:? "usage")
<*> (o .:? "endpoints" .!= mempty)
<*> (o .:? "enums" .!= mempty)
<*> (o .:? "configVersion")
<*> (o .:? "http")
<*> (o .:? "title")
<*> (o .:? "producerProjectId")
<*> (o .:? "sourceInfo")
<*> (o .:? "billing")
<*> (o .:? "customError")
<*> (o .:? "logging")
<*> (o .:? "quota"))
instance ToJSON Service where
toJSON Service'{..}
= object
(catMaybes
[("control" .=) <$> _sControl,
("metrics" .=) <$> _sMetrics,
("context" .=) <$> _sContext,
("authentication" .=) <$> _sAuthentication,
("apis" .=) <$> _sAPIs, ("types" .=) <$> _sTypes,
("systemTypes" .=) <$> _sSystemTypes,
("experimental" .=) <$> _sExperimental,
("monitoredResources" .=) <$> _sMonitoredResources,
("backend" .=) <$> _sBackend,
("monitoring" .=) <$> _sMonitoring,
("name" .=) <$> _sName,
("systemParameters" .=) <$> _sSystemParameters,
("logs" .=) <$> _sLogs,
("documentation" .=) <$> _sDocumentation,
("id" .=) <$> _sId, ("usage" .=) <$> _sUsage,
("endpoints" .=) <$> _sEndpoints,
("enums" .=) <$> _sEnums,
("configVersion" .=) <$> _sConfigVersion,
("http" .=) <$> _sHTTP, ("title" .=) <$> _sTitle,
("producerProjectId" .=) <$> _sProducerProjectId,
("sourceInfo" .=) <$> _sSourceInfo,
("billing" .=) <$> _sBilling,
("customError" .=) <$> _sCustomError,
("logging" .=) <$> _sLogging,
("quota" .=) <$> _sQuota])
data Operation =
Operation'
{ _oDone :: !(Maybe Bool)
, _oError :: !(Maybe Status)
, _oResponse :: !(Maybe OperationResponse)
, _oName :: !(Maybe Text)
, _oMetadata :: !(Maybe OperationMetadata)
}
deriving (Eq, Show, Data, Typeable, Generic)
operation
:: Operation
operation =
Operation'
{ _oDone = Nothing
, _oError = Nothing
, _oResponse = Nothing
, _oName = Nothing
, _oMetadata = Nothing
}
oDone :: Lens' Operation (Maybe Bool)
oDone = lens _oDone (\ s a -> s{_oDone = a})
oError :: Lens' Operation (Maybe Status)
oError = lens _oError (\ s a -> s{_oError = a})
oResponse :: Lens' Operation (Maybe OperationResponse)
oResponse
= lens _oResponse (\ s a -> s{_oResponse = a})
oName :: Lens' Operation (Maybe Text)
oName = lens _oName (\ s a -> s{_oName = a})
oMetadata :: Lens' Operation (Maybe OperationMetadata)
oMetadata
= lens _oMetadata (\ s a -> s{_oMetadata = a})
instance FromJSON Operation where
parseJSON
= withObject "Operation"
(\ o ->
Operation' <$>
(o .:? "done") <*> (o .:? "error") <*>
(o .:? "response")
<*> (o .:? "name")
<*> (o .:? "metadata"))
instance ToJSON Operation where
toJSON Operation'{..}
= object
(catMaybes
[("done" .=) <$> _oDone, ("error" .=) <$> _oError,
("response" .=) <$> _oResponse,
("name" .=) <$> _oName,
("metadata" .=) <$> _oMetadata])
data Empty =
Empty'
deriving (Eq, Show, Data, Typeable, Generic)
empty
:: Empty
empty = Empty'
instance FromJSON Empty where
parseJSON = withObject "Empty" (\ o -> pure Empty')
instance ToJSON Empty where
toJSON = const emptyObject
newtype V1Beta1ImportProducerOverridesResponse =
V1Beta1ImportProducerOverridesResponse'
{ _vbiporOverrides :: Maybe [V1Beta1QuotaOverride]
}
deriving (Eq, Show, Data, Typeable, Generic)
v1Beta1ImportProducerOverridesResponse
:: V1Beta1ImportProducerOverridesResponse
v1Beta1ImportProducerOverridesResponse =
V1Beta1ImportProducerOverridesResponse' {_vbiporOverrides = Nothing}
vbiporOverrides :: Lens' V1Beta1ImportProducerOverridesResponse [V1Beta1QuotaOverride]
vbiporOverrides
= lens _vbiporOverrides
(\ s a -> s{_vbiporOverrides = a})
. _Default
. _Coerce
instance FromJSON
V1Beta1ImportProducerOverridesResponse
where
parseJSON
= withObject "V1Beta1ImportProducerOverridesResponse"
(\ o ->
V1Beta1ImportProducerOverridesResponse' <$>
(o .:? "overrides" .!= mempty))
instance ToJSON
V1Beta1ImportProducerOverridesResponse
where
toJSON V1Beta1ImportProducerOverridesResponse'{..}
= object
(catMaybes [("overrides" .=) <$> _vbiporOverrides])
data CustomErrorRule =
CustomErrorRule'
{ _cerIsErrorType :: !(Maybe Bool)
, _cerSelector :: !(Maybe Text)
}
deriving (Eq, Show, Data, Typeable, Generic)
customErrorRule
:: CustomErrorRule
customErrorRule =
CustomErrorRule' {_cerIsErrorType = Nothing, _cerSelector = Nothing}
cerIsErrorType :: Lens' CustomErrorRule (Maybe Bool)
cerIsErrorType
= lens _cerIsErrorType
(\ s a -> s{_cerIsErrorType = a})
cerSelector :: Lens' CustomErrorRule (Maybe Text)
cerSelector
= lens _cerSelector (\ s a -> s{_cerSelector = a})
instance FromJSON CustomErrorRule where
parseJSON
= withObject "CustomErrorRule"
(\ o ->
CustomErrorRule' <$>
(o .:? "isErrorType") <*> (o .:? "selector"))
instance ToJSON CustomErrorRule where
toJSON CustomErrorRule'{..}
= object
(catMaybes
[("isErrorType" .=) <$> _cerIsErrorType,
("selector" .=) <$> _cerSelector])
data V1Beta1EnableConsumerResponse =
V1Beta1EnableConsumerResponse'
deriving (Eq, Show, Data, Typeable, Generic)
v1Beta1EnableConsumerResponse
:: V1Beta1EnableConsumerResponse
v1Beta1EnableConsumerResponse = V1Beta1EnableConsumerResponse'
instance FromJSON V1Beta1EnableConsumerResponse where
parseJSON
= withObject "V1Beta1EnableConsumerResponse"
(\ o -> pure V1Beta1EnableConsumerResponse')
instance ToJSON V1Beta1EnableConsumerResponse where
toJSON = const emptyObject
newtype OptionValue =
OptionValue'
{ _ovAddtional :: HashMap Text JSONValue
}
deriving (Eq, Show, Data, Typeable, Generic)
optionValue
:: HashMap Text JSONValue
-> OptionValue
optionValue pOvAddtional_ =
OptionValue' {_ovAddtional = _Coerce # pOvAddtional_}
ovAddtional :: Lens' OptionValue (HashMap Text JSONValue)
ovAddtional
= lens _ovAddtional (\ s a -> s{_ovAddtional = a}) .
_Coerce
instance FromJSON OptionValue where
parseJSON
= withObject "OptionValue"
(\ o -> OptionValue' <$> (parseJSONObject o))
instance ToJSON OptionValue where
toJSON = toJSON . _ovAddtional
data EnumValue =
EnumValue'
{ _evName :: !(Maybe Text)
, _evOptions :: !(Maybe [Option])
, _evNumber :: !(Maybe (Textual Int32))
}
deriving (Eq, Show, Data, Typeable, Generic)
enumValue
:: EnumValue
enumValue =
EnumValue' {_evName = Nothing, _evOptions = Nothing, _evNumber = Nothing}
evName :: Lens' EnumValue (Maybe Text)
evName = lens _evName (\ s a -> s{_evName = a})
evOptions :: Lens' EnumValue [Option]
evOptions
= lens _evOptions (\ s a -> s{_evOptions = a}) .
_Default
. _Coerce
evNumber :: Lens' EnumValue (Maybe Int32)
evNumber
= lens _evNumber (\ s a -> s{_evNumber = a}) .
mapping _Coerce
instance FromJSON EnumValue where
parseJSON
= withObject "EnumValue"
(\ o ->
EnumValue' <$>
(o .:? "name") <*> (o .:? "options" .!= mempty) <*>
(o .:? "number"))
instance ToJSON EnumValue where
toJSON EnumValue'{..}
= object
(catMaybes
[("name" .=) <$> _evName,
("options" .=) <$> _evOptions,
("number" .=) <$> _evNumber])
data Authentication =
Authentication'
{ _aRules :: !(Maybe [AuthenticationRule])
, _aProviders :: !(Maybe [AuthProvider])
}
deriving (Eq, Show, Data, Typeable, Generic)
authentication
:: Authentication
authentication = Authentication' {_aRules = Nothing, _aProviders = Nothing}
aRules :: Lens' Authentication [AuthenticationRule]
aRules
= lens _aRules (\ s a -> s{_aRules = a}) . _Default .
_Coerce
aProviders :: Lens' Authentication [AuthProvider]
aProviders
= lens _aProviders (\ s a -> s{_aProviders = a}) .
_Default
. _Coerce
instance FromJSON Authentication where
parseJSON
= withObject "Authentication"
(\ o ->
Authentication' <$>
(o .:? "rules" .!= mempty) <*>
(o .:? "providers" .!= mempty))
instance ToJSON Authentication where
toJSON Authentication'{..}
= object
(catMaybes
[("rules" .=) <$> _aRules,
("providers" .=) <$> _aProviders])
data V1EnableConsumerResponse =
V1EnableConsumerResponse'
deriving (Eq, Show, Data, Typeable, Generic)
v1EnableConsumerResponse
:: V1EnableConsumerResponse
v1EnableConsumerResponse = V1EnableConsumerResponse'
instance FromJSON V1EnableConsumerResponse where
parseJSON
= withObject "V1EnableConsumerResponse"
(\ o -> pure V1EnableConsumerResponse')
instance ToJSON V1EnableConsumerResponse where
toJSON = const emptyObject
data Mixin =
Mixin'
{ _mRoot :: !(Maybe Text)
, _mName :: !(Maybe Text)
}
deriving (Eq, Show, Data, Typeable, Generic)
mixin
:: Mixin
mixin = Mixin' {_mRoot = Nothing, _mName = Nothing}
mRoot :: Lens' Mixin (Maybe Text)
mRoot = lens _mRoot (\ s a -> s{_mRoot = a})
mName :: Lens' Mixin (Maybe Text)
mName = lens _mName (\ s a -> s{_mName = a})
instance FromJSON Mixin where
parseJSON
= withObject "Mixin"
(\ o -> Mixin' <$> (o .:? "root") <*> (o .:? "name"))
instance ToJSON Mixin where
toJSON Mixin'{..}
= object
(catMaybes
[("root" .=) <$> _mRoot, ("name" .=) <$> _mName])
data CustomHTTPPattern =
CustomHTTPPattern'
{ _chttppPath :: !(Maybe Text)
, _chttppKind :: !(Maybe Text)
}
deriving (Eq, Show, Data, Typeable, Generic)
customHTTPPattern
:: CustomHTTPPattern
customHTTPPattern =
CustomHTTPPattern' {_chttppPath = Nothing, _chttppKind = Nothing}
chttppPath :: Lens' CustomHTTPPattern (Maybe Text)
chttppPath
= lens _chttppPath (\ s a -> s{_chttppPath = a})
chttppKind :: Lens' CustomHTTPPattern (Maybe Text)
chttppKind
= lens _chttppKind (\ s a -> s{_chttppKind = a})
instance FromJSON CustomHTTPPattern where
parseJSON
= withObject "CustomHTTPPattern"
(\ o ->
CustomHTTPPattern' <$>
(o .:? "path") <*> (o .:? "kind"))
instance ToJSON CustomHTTPPattern where
toJSON CustomHTTPPattern'{..}
= object
(catMaybes
[("path" .=) <$> _chttppPath,
("kind" .=) <$> _chttppKind])
data UsageRule =
UsageRule'
{ _urSelector :: !(Maybe Text)
, _urAllowUnregisteredCalls :: !(Maybe Bool)
, _urSkipServiceControl :: !(Maybe Bool)
}
deriving (Eq, Show, Data, Typeable, Generic)
usageRule
:: UsageRule
usageRule =
UsageRule'
{ _urSelector = Nothing
, _urAllowUnregisteredCalls = Nothing
, _urSkipServiceControl = Nothing
}
urSelector :: Lens' UsageRule (Maybe Text)
urSelector
= lens _urSelector (\ s a -> s{_urSelector = a})
urAllowUnregisteredCalls :: Lens' UsageRule (Maybe Bool)
urAllowUnregisteredCalls
= lens _urAllowUnregisteredCalls
(\ s a -> s{_urAllowUnregisteredCalls = a})
urSkipServiceControl :: Lens' UsageRule (Maybe Bool)
urSkipServiceControl
= lens _urSkipServiceControl
(\ s a -> s{_urSkipServiceControl = a})
instance FromJSON UsageRule where
parseJSON
= withObject "UsageRule"
(\ o ->
UsageRule' <$>
(o .:? "selector") <*>
(o .:? "allowUnregisteredCalls")
<*> (o .:? "skipServiceControl"))
instance ToJSON UsageRule where
toJSON UsageRule'{..}
= object
(catMaybes
[("selector" .=) <$> _urSelector,
("allowUnregisteredCalls" .=) <$>
_urAllowUnregisteredCalls,
("skipServiceControl" .=) <$> _urSkipServiceControl])
newtype StatusDetailsItem =
StatusDetailsItem'
{ _sdiAddtional :: HashMap Text JSONValue
}
deriving (Eq, Show, Data, Typeable, Generic)
statusDetailsItem
:: HashMap Text JSONValue
-> StatusDetailsItem
statusDetailsItem pSdiAddtional_ =
StatusDetailsItem' {_sdiAddtional = _Coerce # pSdiAddtional_}
sdiAddtional :: Lens' StatusDetailsItem (HashMap Text JSONValue)
sdiAddtional
= lens _sdiAddtional (\ s a -> s{_sdiAddtional = a})
. _Coerce
instance FromJSON StatusDetailsItem where
parseJSON
= withObject "StatusDetailsItem"
(\ o -> StatusDetailsItem' <$> (parseJSONObject o))
instance ToJSON StatusDetailsItem where
toJSON = toJSON . _sdiAddtional
data Page =
Page'
{ _pSubpages :: !(Maybe [Page])
, _pContent :: !(Maybe Text)
, _pName :: !(Maybe Text)
}
deriving (Eq, Show, Data, Typeable, Generic)
page
:: Page
page = Page' {_pSubpages = Nothing, _pContent = Nothing, _pName = Nothing}
pSubpages :: Lens' Page [Page]
pSubpages
= lens _pSubpages (\ s a -> s{_pSubpages = a}) .
_Default
. _Coerce
pContent :: Lens' Page (Maybe Text)
pContent = lens _pContent (\ s a -> s{_pContent = a})
pName :: Lens' Page (Maybe Text)
pName = lens _pName (\ s a -> s{_pName = a})
instance FromJSON Page where
parseJSON
= withObject "Page"
(\ o ->
Page' <$>
(o .:? "subpages" .!= mempty) <*> (o .:? "content")
<*> (o .:? "name"))
instance ToJSON Page where
toJSON Page'{..}
= object
(catMaybes
[("subpages" .=) <$> _pSubpages,
("content" .=) <$> _pContent,
("name" .=) <$> _pName])
newtype V1GenerateServiceAccountResponse =
V1GenerateServiceAccountResponse'
{ _vgsarAccount :: Maybe V1ServiceAccount
}
deriving (Eq, Show, Data, Typeable, Generic)
v1GenerateServiceAccountResponse
:: V1GenerateServiceAccountResponse
v1GenerateServiceAccountResponse =
V1GenerateServiceAccountResponse' {_vgsarAccount = Nothing}
vgsarAccount :: Lens' V1GenerateServiceAccountResponse (Maybe V1ServiceAccount)
vgsarAccount
= lens _vgsarAccount (\ s a -> s{_vgsarAccount = a})
instance FromJSON V1GenerateServiceAccountResponse
where
parseJSON
= withObject "V1GenerateServiceAccountResponse"
(\ o ->
V1GenerateServiceAccountResponse' <$>
(o .:? "account"))
instance ToJSON V1GenerateServiceAccountResponse
where
toJSON V1GenerateServiceAccountResponse'{..}
= object
(catMaybes [("account" .=) <$> _vgsarAccount])
data AuthenticationRule =
AuthenticationRule'
{ _arRequirements :: !(Maybe [AuthRequirement])
, _arSelector :: !(Maybe Text)
, _arAllowWithoutCredential :: !(Maybe Bool)
, _arOAuth :: !(Maybe OAuthRequirements)
}
deriving (Eq, Show, Data, Typeable, Generic)
authenticationRule
:: AuthenticationRule
authenticationRule =
AuthenticationRule'
{ _arRequirements = Nothing
, _arSelector = Nothing
, _arAllowWithoutCredential = Nothing
, _arOAuth = Nothing
}
arRequirements :: Lens' AuthenticationRule [AuthRequirement]
arRequirements
= lens _arRequirements
(\ s a -> s{_arRequirements = a})
. _Default
. _Coerce
arSelector :: Lens' AuthenticationRule (Maybe Text)
arSelector
= lens _arSelector (\ s a -> s{_arSelector = a})
arAllowWithoutCredential :: Lens' AuthenticationRule (Maybe Bool)
arAllowWithoutCredential
= lens _arAllowWithoutCredential
(\ s a -> s{_arAllowWithoutCredential = a})
arOAuth :: Lens' AuthenticationRule (Maybe OAuthRequirements)
arOAuth = lens _arOAuth (\ s a -> s{_arOAuth = a})
instance FromJSON AuthenticationRule where
parseJSON
= withObject "AuthenticationRule"
(\ o ->
AuthenticationRule' <$>
(o .:? "requirements" .!= mempty) <*>
(o .:? "selector")
<*> (o .:? "allowWithoutCredential")
<*> (o .:? "oauth"))
instance ToJSON AuthenticationRule where
toJSON AuthenticationRule'{..}
= object
(catMaybes
[("requirements" .=) <$> _arRequirements,
("selector" .=) <$> _arSelector,
("allowWithoutCredential" .=) <$>
_arAllowWithoutCredential,
("oauth" .=) <$> _arOAuth])
newtype V1AddVisibilityLabelsResponse =
V1AddVisibilityLabelsResponse'
{ _vavlrLabels :: Maybe [Text]
}
deriving (Eq, Show, Data, Typeable, Generic)
v1AddVisibilityLabelsResponse
:: V1AddVisibilityLabelsResponse
v1AddVisibilityLabelsResponse =
V1AddVisibilityLabelsResponse' {_vavlrLabels = Nothing}
vavlrLabels :: Lens' V1AddVisibilityLabelsResponse [Text]
vavlrLabels
= lens _vavlrLabels (\ s a -> s{_vavlrLabels = a}) .
_Default
. _Coerce
instance FromJSON V1AddVisibilityLabelsResponse where
parseJSON
= withObject "V1AddVisibilityLabelsResponse"
(\ o ->
V1AddVisibilityLabelsResponse' <$>
(o .:? "labels" .!= mempty))
instance ToJSON V1AddVisibilityLabelsResponse where
toJSON V1AddVisibilityLabelsResponse'{..}
= object (catMaybes [("labels" .=) <$> _vavlrLabels])
data ServiceAccountConfig =
ServiceAccountConfig'
{ _sacAccountId :: !(Maybe Text)
, _sacTenantProjectRoles :: !(Maybe [Text])
}
deriving (Eq, Show, Data, Typeable, Generic)
serviceAccountConfig
:: ServiceAccountConfig
serviceAccountConfig =
ServiceAccountConfig'
{_sacAccountId = Nothing, _sacTenantProjectRoles = Nothing}
sacAccountId :: Lens' ServiceAccountConfig (Maybe Text)
sacAccountId
= lens _sacAccountId (\ s a -> s{_sacAccountId = a})
sacTenantProjectRoles :: Lens' ServiceAccountConfig [Text]
sacTenantProjectRoles
= lens _sacTenantProjectRoles
(\ s a -> s{_sacTenantProjectRoles = a})
. _Default
. _Coerce
instance FromJSON ServiceAccountConfig where
parseJSON
= withObject "ServiceAccountConfig"
(\ o ->
ServiceAccountConfig' <$>
(o .:? "accountId") <*>
(o .:? "tenantProjectRoles" .!= mempty))
instance ToJSON ServiceAccountConfig where
toJSON ServiceAccountConfig'{..}
= object
(catMaybes
[("accountId" .=) <$> _sacAccountId,
("tenantProjectRoles" .=) <$>
_sacTenantProjectRoles])
data V1Beta1QuotaOverride =
V1Beta1QuotaOverride'
{ _vbqoMetric :: !(Maybe Text)
, _vbqoOverrideValue :: !(Maybe (Textual Int64))
, _vbqoName :: !(Maybe Text)
, _vbqoDimensions :: !(Maybe V1Beta1QuotaOverrideDimensions)
, _vbqoUnit :: !(Maybe Text)
}
deriving (Eq, Show, Data, Typeable, Generic)
v1Beta1QuotaOverride
:: V1Beta1QuotaOverride
v1Beta1QuotaOverride =
V1Beta1QuotaOverride'
{ _vbqoMetric = Nothing
, _vbqoOverrideValue = Nothing
, _vbqoName = Nothing
, _vbqoDimensions = Nothing
, _vbqoUnit = Nothing
}
vbqoMetric :: Lens' V1Beta1QuotaOverride (Maybe Text)
vbqoMetric
= lens _vbqoMetric (\ s a -> s{_vbqoMetric = a})
vbqoOverrideValue :: Lens' V1Beta1QuotaOverride (Maybe Int64)
vbqoOverrideValue
= lens _vbqoOverrideValue
(\ s a -> s{_vbqoOverrideValue = a})
. mapping _Coerce
vbqoName :: Lens' V1Beta1QuotaOverride (Maybe Text)
vbqoName = lens _vbqoName (\ s a -> s{_vbqoName = a})
vbqoDimensions :: Lens' V1Beta1QuotaOverride (Maybe V1Beta1QuotaOverrideDimensions)
vbqoDimensions
= lens _vbqoDimensions
(\ s a -> s{_vbqoDimensions = a})
vbqoUnit :: Lens' V1Beta1QuotaOverride (Maybe Text)
vbqoUnit = lens _vbqoUnit (\ s a -> s{_vbqoUnit = a})
instance FromJSON V1Beta1QuotaOverride where
parseJSON
= withObject "V1Beta1QuotaOverride"
(\ o ->
V1Beta1QuotaOverride' <$>
(o .:? "metric") <*> (o .:? "overrideValue") <*>
(o .:? "name")
<*> (o .:? "dimensions")
<*> (o .:? "unit"))
instance ToJSON V1Beta1QuotaOverride where
toJSON V1Beta1QuotaOverride'{..}
= object
(catMaybes
[("metric" .=) <$> _vbqoMetric,
("overrideValue" .=) <$> _vbqoOverrideValue,
("name" .=) <$> _vbqoName,
("dimensions" .=) <$> _vbqoDimensions,
("unit" .=) <$> _vbqoUnit])
newtype MetricRuleMetricCosts =
MetricRuleMetricCosts'
{ _mrmcAddtional :: HashMap Text (Textual Int64)
}
deriving (Eq, Show, Data, Typeable, Generic)
metricRuleMetricCosts
:: HashMap Text Int64
-> MetricRuleMetricCosts
metricRuleMetricCosts pMrmcAddtional_ =
MetricRuleMetricCosts' {_mrmcAddtional = _Coerce # pMrmcAddtional_}
mrmcAddtional :: Lens' MetricRuleMetricCosts (HashMap Text Int64)
mrmcAddtional
= lens _mrmcAddtional
(\ s a -> s{_mrmcAddtional = a})
. _Coerce
instance FromJSON MetricRuleMetricCosts where
parseJSON
= withObject "MetricRuleMetricCosts"
(\ o ->
MetricRuleMetricCosts' <$> (parseJSONObject o))
instance ToJSON MetricRuleMetricCosts where
toJSON = toJSON . _mrmcAddtional
newtype AuthorizationConfig =
AuthorizationConfig'
{ _acProvider :: Maybe Text
}
deriving (Eq, Show, Data, Typeable, Generic)
authorizationConfig
:: AuthorizationConfig
authorizationConfig = AuthorizationConfig' {_acProvider = Nothing}
acProvider :: Lens' AuthorizationConfig (Maybe Text)
acProvider
= lens _acProvider (\ s a -> s{_acProvider = a})
instance FromJSON AuthorizationConfig where
parseJSON
= withObject "AuthorizationConfig"
(\ o -> AuthorizationConfig' <$> (o .:? "provider"))
instance ToJSON AuthorizationConfig where
toJSON AuthorizationConfig'{..}
= object
(catMaybes [("provider" .=) <$> _acProvider])
newtype DeleteTenantProjectRequest =
DeleteTenantProjectRequest'
{ _dtprTag :: Maybe Text
}
deriving (Eq, Show, Data, Typeable, Generic)
deleteTenantProjectRequest
:: DeleteTenantProjectRequest
deleteTenantProjectRequest = DeleteTenantProjectRequest' {_dtprTag = Nothing}
dtprTag :: Lens' DeleteTenantProjectRequest (Maybe Text)
dtprTag = lens _dtprTag (\ s a -> s{_dtprTag = a})
instance FromJSON DeleteTenantProjectRequest where
parseJSON
= withObject "DeleteTenantProjectRequest"
(\ o ->
DeleteTenantProjectRequest' <$> (o .:? "tag"))
instance ToJSON DeleteTenantProjectRequest where
toJSON DeleteTenantProjectRequest'{..}
= object (catMaybes [("tag" .=) <$> _dtprTag])
newtype TenantProjectPolicy =
TenantProjectPolicy'
{ _tppPolicyBindings :: Maybe [PolicyBinding]
}
deriving (Eq, Show, Data, Typeable, Generic)
tenantProjectPolicy
:: TenantProjectPolicy
tenantProjectPolicy = TenantProjectPolicy' {_tppPolicyBindings = Nothing}
tppPolicyBindings :: Lens' TenantProjectPolicy [PolicyBinding]
tppPolicyBindings
= lens _tppPolicyBindings
(\ s a -> s{_tppPolicyBindings = a})
. _Default
. _Coerce
instance FromJSON TenantProjectPolicy where
parseJSON
= withObject "TenantProjectPolicy"
(\ o ->
TenantProjectPolicy' <$>
(o .:? "policyBindings" .!= mempty))
instance ToJSON TenantProjectPolicy where
toJSON TenantProjectPolicy'{..}
= object
(catMaybes
[("policyBindings" .=) <$> _tppPolicyBindings])
data PolicyBinding =
PolicyBinding'
{ _pbMembers :: !(Maybe [Text])
, _pbRole :: !(Maybe Text)
}
deriving (Eq, Show, Data, Typeable, Generic)
policyBinding
:: PolicyBinding
policyBinding = PolicyBinding' {_pbMembers = Nothing, _pbRole = Nothing}
pbMembers :: Lens' PolicyBinding [Text]
pbMembers
= lens _pbMembers (\ s a -> s{_pbMembers = a}) .
_Default
. _Coerce
pbRole :: Lens' PolicyBinding (Maybe Text)
pbRole = lens _pbRole (\ s a -> s{_pbRole = a})
instance FromJSON PolicyBinding where
parseJSON
= withObject "PolicyBinding"
(\ o ->
PolicyBinding' <$>
(o .:? "members" .!= mempty) <*> (o .:? "role"))
instance ToJSON PolicyBinding where
toJSON PolicyBinding'{..}
= object
(catMaybes
[("members" .=) <$> _pbMembers,
("role" .=) <$> _pbRole])
newtype Experimental =
Experimental'
{ _eAuthorization :: Maybe AuthorizationConfig
}
deriving (Eq, Show, Data, Typeable, Generic)
experimental
:: Experimental
experimental = Experimental' {_eAuthorization = Nothing}
eAuthorization :: Lens' Experimental (Maybe AuthorizationConfig)
eAuthorization
= lens _eAuthorization
(\ s a -> s{_eAuthorization = a})
instance FromJSON Experimental where
parseJSON
= withObject "Experimental"
(\ o -> Experimental' <$> (o .:? "authorization"))
instance ToJSON Experimental where
toJSON Experimental'{..}
= object
(catMaybes
[("authorization" .=) <$> _eAuthorization])
newtype Backend =
Backend'
{ _bRules :: Maybe [BackendRule]
}
deriving (Eq, Show, Data, Typeable, Generic)
backend
:: Backend
backend = Backend' {_bRules = Nothing}
bRules :: Lens' Backend [BackendRule]
bRules
= lens _bRules (\ s a -> s{_bRules = a}) . _Default .
_Coerce
instance FromJSON Backend where
parseJSON
= withObject "Backend"
(\ o -> Backend' <$> (o .:? "rules" .!= mempty))
instance ToJSON Backend where
toJSON Backend'{..}
= object (catMaybes [("rules" .=) <$> _bRules])
data TenancyUnit =
TenancyUnit'
{ _tuService :: !(Maybe Text)
, _tuName :: !(Maybe Text)
, _tuTenantResources :: !(Maybe [TenantResource])
, _tuConsumer :: !(Maybe Text)
, _tuCreateTime :: !(Maybe DateTime')
}
deriving (Eq, Show, Data, Typeable, Generic)
tenancyUnit
:: TenancyUnit
tenancyUnit =
TenancyUnit'
{ _tuService = Nothing
, _tuName = Nothing
, _tuTenantResources = Nothing
, _tuConsumer = Nothing
, _tuCreateTime = Nothing
}
tuService :: Lens' TenancyUnit (Maybe Text)
tuService
= lens _tuService (\ s a -> s{_tuService = a})
tuName :: Lens' TenancyUnit (Maybe Text)
tuName = lens _tuName (\ s a -> s{_tuName = a})
tuTenantResources :: Lens' TenancyUnit [TenantResource]
tuTenantResources
= lens _tuTenantResources
(\ s a -> s{_tuTenantResources = a})
. _Default
. _Coerce
tuConsumer :: Lens' TenancyUnit (Maybe Text)
tuConsumer
= lens _tuConsumer (\ s a -> s{_tuConsumer = a})
tuCreateTime :: Lens' TenancyUnit (Maybe UTCTime)
tuCreateTime
= lens _tuCreateTime (\ s a -> s{_tuCreateTime = a})
. mapping _DateTime
instance FromJSON TenancyUnit where
parseJSON
= withObject "TenancyUnit"
(\ o ->
TenancyUnit' <$>
(o .:? "service") <*> (o .:? "name") <*>
(o .:? "tenantResources" .!= mempty)
<*> (o .:? "consumer")
<*> (o .:? "createTime"))
instance ToJSON TenancyUnit where
toJSON TenancyUnit'{..}
= object
(catMaybes
[("service" .=) <$> _tuService,
("name" .=) <$> _tuName,
("tenantResources" .=) <$> _tuTenantResources,
("consumer" .=) <$> _tuConsumer,
("createTime" .=) <$> _tuCreateTime])
data Monitoring =
Monitoring'
{ _mProducerDestinations :: !(Maybe [MonitoringDestination])
, _mConsumerDestinations :: !(Maybe [MonitoringDestination])
}
deriving (Eq, Show, Data, Typeable, Generic)
monitoring
:: Monitoring
monitoring =
Monitoring'
{_mProducerDestinations = Nothing, _mConsumerDestinations = Nothing}
mProducerDestinations :: Lens' Monitoring [MonitoringDestination]
mProducerDestinations
= lens _mProducerDestinations
(\ s a -> s{_mProducerDestinations = a})
. _Default
. _Coerce
mConsumerDestinations :: Lens' Monitoring [MonitoringDestination]
mConsumerDestinations
= lens _mConsumerDestinations
(\ s a -> s{_mConsumerDestinations = a})
. _Default
. _Coerce
instance FromJSON Monitoring where
parseJSON
= withObject "Monitoring"
(\ o ->
Monitoring' <$>
(o .:? "producerDestinations" .!= mempty) <*>
(o .:? "consumerDestinations" .!= mempty))
instance ToJSON Monitoring where
toJSON Monitoring'{..}
= object
(catMaybes
[("producerDestinations" .=) <$>
_mProducerDestinations,
("consumerDestinations" .=) <$>
_mConsumerDestinations])
data LogDescriptor =
LogDescriptor'
{ _ldName :: !(Maybe Text)
, _ldDisplayName :: !(Maybe Text)
, _ldLabels :: !(Maybe [LabelDescriptor])
, _ldDescription :: !(Maybe Text)
}
deriving (Eq, Show, Data, Typeable, Generic)
logDescriptor
:: LogDescriptor
logDescriptor =
LogDescriptor'
{ _ldName = Nothing
, _ldDisplayName = Nothing
, _ldLabels = Nothing
, _ldDescription = Nothing
}
ldName :: Lens' LogDescriptor (Maybe Text)
ldName = lens _ldName (\ s a -> s{_ldName = a})
ldDisplayName :: Lens' LogDescriptor (Maybe Text)
ldDisplayName
= lens _ldDisplayName
(\ s a -> s{_ldDisplayName = a})
ldLabels :: Lens' LogDescriptor [LabelDescriptor]
ldLabels
= lens _ldLabels (\ s a -> s{_ldLabels = a}) .
_Default
. _Coerce
ldDescription :: Lens' LogDescriptor (Maybe Text)
ldDescription
= lens _ldDescription
(\ s a -> s{_ldDescription = a})
instance FromJSON LogDescriptor where
parseJSON
= withObject "LogDescriptor"
(\ o ->
LogDescriptor' <$>
(o .:? "name") <*> (o .:? "displayName") <*>
(o .:? "labels" .!= mempty)
<*> (o .:? "description"))
instance ToJSON LogDescriptor where
toJSON LogDescriptor'{..}
= object
(catMaybes
[("name" .=) <$> _ldName,
("displayName" .=) <$> _ldDisplayName,
("labels" .=) <$> _ldLabels,
("description" .=) <$> _ldDescription])
data Method =
Method'
{ _metRequestStreaming :: !(Maybe Bool)
, _metResponseTypeURL :: !(Maybe Text)
, _metName :: !(Maybe Text)
, _metResponseStreaming :: !(Maybe Bool)
, _metRequestTypeURL :: !(Maybe Text)
, _metOptions :: !(Maybe [Option])
, _metSyntax :: !(Maybe MethodSyntax)
}
deriving (Eq, Show, Data, Typeable, Generic)
method
:: Method
method =
Method'
{ _metRequestStreaming = Nothing
, _metResponseTypeURL = Nothing
, _metName = Nothing
, _metResponseStreaming = Nothing
, _metRequestTypeURL = Nothing
, _metOptions = Nothing
, _metSyntax = Nothing
}
metRequestStreaming :: Lens' Method (Maybe Bool)
metRequestStreaming
= lens _metRequestStreaming
(\ s a -> s{_metRequestStreaming = a})
metResponseTypeURL :: Lens' Method (Maybe Text)
metResponseTypeURL
= lens _metResponseTypeURL
(\ s a -> s{_metResponseTypeURL = a})
metName :: Lens' Method (Maybe Text)
metName = lens _metName (\ s a -> s{_metName = a})
metResponseStreaming :: Lens' Method (Maybe Bool)
metResponseStreaming
= lens _metResponseStreaming
(\ s a -> s{_metResponseStreaming = a})
metRequestTypeURL :: Lens' Method (Maybe Text)
metRequestTypeURL
= lens _metRequestTypeURL
(\ s a -> s{_metRequestTypeURL = a})
metOptions :: Lens' Method [Option]
metOptions
= lens _metOptions (\ s a -> s{_metOptions = a}) .
_Default
. _Coerce
metSyntax :: Lens' Method (Maybe MethodSyntax)
metSyntax
= lens _metSyntax (\ s a -> s{_metSyntax = a})
instance FromJSON Method where
parseJSON
= withObject "Method"
(\ o ->
Method' <$>
(o .:? "requestStreaming") <*>
(o .:? "responseTypeUrl")
<*> (o .:? "name")
<*> (o .:? "responseStreaming")
<*> (o .:? "requestTypeUrl")
<*> (o .:? "options" .!= mempty)
<*> (o .:? "syntax"))
instance ToJSON Method where
toJSON Method'{..}
= object
(catMaybes
[("requestStreaming" .=) <$> _metRequestStreaming,
("responseTypeUrl" .=) <$> _metResponseTypeURL,
("name" .=) <$> _metName,
("responseStreaming" .=) <$> _metResponseStreaming,
("requestTypeUrl" .=) <$> _metRequestTypeURL,
("options" .=) <$> _metOptions,
("syntax" .=) <$> _metSyntax])
data V1RefreshConsumerResponse =
V1RefreshConsumerResponse'
deriving (Eq, Show, Data, Typeable, Generic)
v1RefreshConsumerResponse
:: V1RefreshConsumerResponse
v1RefreshConsumerResponse = V1RefreshConsumerResponse'
instance FromJSON V1RefreshConsumerResponse where
parseJSON
= withObject "V1RefreshConsumerResponse"
(\ o -> pure V1RefreshConsumerResponse')
instance ToJSON V1RefreshConsumerResponse where
toJSON = const emptyObject
newtype SystemParameters =
SystemParameters'
{ _spRules :: Maybe [SystemParameterRule]
}
deriving (Eq, Show, Data, Typeable, Generic)
systemParameters
:: SystemParameters
systemParameters = SystemParameters' {_spRules = Nothing}
spRules :: Lens' SystemParameters [SystemParameterRule]
spRules
= lens _spRules (\ s a -> s{_spRules = a}) . _Default
. _Coerce
instance FromJSON SystemParameters where
parseJSON
= withObject "SystemParameters"
(\ o ->
SystemParameters' <$> (o .:? "rules" .!= mempty))
instance ToJSON SystemParameters where
toJSON SystemParameters'{..}
= object (catMaybes [("rules" .=) <$> _spRules])
data Documentation =
Documentation'
{ _dSummary :: !(Maybe Text)
, _dDocumentationRootURL :: !(Maybe Text)
, _dRules :: !(Maybe [DocumentationRule])
, _dPages :: !(Maybe [Page])
, _dOverview :: !(Maybe Text)
}
deriving (Eq, Show, Data, Typeable, Generic)
documentation
:: Documentation
documentation =
Documentation'
{ _dSummary = Nothing
, _dDocumentationRootURL = Nothing
, _dRules = Nothing
, _dPages = Nothing
, _dOverview = Nothing
}
dSummary :: Lens' Documentation (Maybe Text)
dSummary = lens _dSummary (\ s a -> s{_dSummary = a})
dDocumentationRootURL :: Lens' Documentation (Maybe Text)
dDocumentationRootURL
= lens _dDocumentationRootURL
(\ s a -> s{_dDocumentationRootURL = a})
dRules :: Lens' Documentation [DocumentationRule]
dRules
= lens _dRules (\ s a -> s{_dRules = a}) . _Default .
_Coerce
dPages :: Lens' Documentation [Page]
dPages
= lens _dPages (\ s a -> s{_dPages = a}) . _Default .
_Coerce
dOverview :: Lens' Documentation (Maybe Text)
dOverview
= lens _dOverview (\ s a -> s{_dOverview = a})
instance FromJSON Documentation where
parseJSON
= withObject "Documentation"
(\ o ->
Documentation' <$>
(o .:? "summary") <*> (o .:? "documentationRootUrl")
<*> (o .:? "rules" .!= mempty)
<*> (o .:? "pages" .!= mempty)
<*> (o .:? "overview"))
instance ToJSON Documentation where
toJSON Documentation'{..}
= object
(catMaybes
[("summary" .=) <$> _dSummary,
("documentationRootUrl" .=) <$>
_dDocumentationRootURL,
("rules" .=) <$> _dRules, ("pages" .=) <$> _dPages,
("overview" .=) <$> _dOverview])
data MetricDescriptorMetadata =
MetricDescriptorMetadata'
{ _mdmSamplePeriod :: !(Maybe GDuration)
, _mdmIngestDelay :: !(Maybe GDuration)
, _mdmLaunchStage :: !(Maybe MetricDescriptorMetadataLaunchStage)
}
deriving (Eq, Show, Data, Typeable, Generic)
metricDescriptorMetadata
:: MetricDescriptorMetadata
metricDescriptorMetadata =
MetricDescriptorMetadata'
{ _mdmSamplePeriod = Nothing
, _mdmIngestDelay = Nothing
, _mdmLaunchStage = Nothing
}
mdmSamplePeriod :: Lens' MetricDescriptorMetadata (Maybe Scientific)
mdmSamplePeriod
= lens _mdmSamplePeriod
(\ s a -> s{_mdmSamplePeriod = a})
. mapping _GDuration
mdmIngestDelay :: Lens' MetricDescriptorMetadata (Maybe Scientific)
mdmIngestDelay
= lens _mdmIngestDelay
(\ s a -> s{_mdmIngestDelay = a})
. mapping _GDuration
mdmLaunchStage :: Lens' MetricDescriptorMetadata (Maybe MetricDescriptorMetadataLaunchStage)
mdmLaunchStage
= lens _mdmLaunchStage
(\ s a -> s{_mdmLaunchStage = a})
instance FromJSON MetricDescriptorMetadata where
parseJSON
= withObject "MetricDescriptorMetadata"
(\ o ->
MetricDescriptorMetadata' <$>
(o .:? "samplePeriod") <*> (o .:? "ingestDelay") <*>
(o .:? "launchStage"))
instance ToJSON MetricDescriptorMetadata where
toJSON MetricDescriptorMetadata'{..}
= object
(catMaybes
[("samplePeriod" .=) <$> _mdmSamplePeriod,
("ingestDelay" .=) <$> _mdmIngestDelay,
("launchStage" .=) <$> _mdmLaunchStage])
newtype UndeleteTenantProjectRequest =
UndeleteTenantProjectRequest'
{ _utprTag :: Maybe Text
}
deriving (Eq, Show, Data, Typeable, Generic)
undeleteTenantProjectRequest
:: UndeleteTenantProjectRequest
undeleteTenantProjectRequest =
UndeleteTenantProjectRequest' {_utprTag = Nothing}
utprTag :: Lens' UndeleteTenantProjectRequest (Maybe Text)
utprTag = lens _utprTag (\ s a -> s{_utprTag = a})
instance FromJSON UndeleteTenantProjectRequest where
parseJSON
= withObject "UndeleteTenantProjectRequest"
(\ o ->
UndeleteTenantProjectRequest' <$> (o .:? "tag"))
instance ToJSON UndeleteTenantProjectRequest where
toJSON UndeleteTenantProjectRequest'{..}
= object (catMaybes [("tag" .=) <$> _utprTag])
data SystemParameterRule =
SystemParameterRule'
{ _sprSelector :: !(Maybe Text)
, _sprParameters :: !(Maybe [SystemParameter])
}
deriving (Eq, Show, Data, Typeable, Generic)
systemParameterRule
:: SystemParameterRule
systemParameterRule =
SystemParameterRule' {_sprSelector = Nothing, _sprParameters = Nothing}
sprSelector :: Lens' SystemParameterRule (Maybe Text)
sprSelector
= lens _sprSelector (\ s a -> s{_sprSelector = a})
sprParameters :: Lens' SystemParameterRule [SystemParameter]
sprParameters
= lens _sprParameters
(\ s a -> s{_sprParameters = a})
. _Default
. _Coerce
instance FromJSON SystemParameterRule where
parseJSON
= withObject "SystemParameterRule"
(\ o ->
SystemParameterRule' <$>
(o .:? "selector") <*>
(o .:? "parameters" .!= mempty))
instance ToJSON SystemParameterRule where
toJSON SystemParameterRule'{..}
= object
(catMaybes
[("selector" .=) <$> _sprSelector,
("parameters" .=) <$> _sprParameters])
data LabelDescriptor =
LabelDescriptor'
{ _lKey :: !(Maybe Text)
, _lValueType :: !(Maybe LabelDescriptorValueType)
, _lDescription :: !(Maybe Text)
}
deriving (Eq, Show, Data, Typeable, Generic)
labelDescriptor
:: LabelDescriptor
labelDescriptor =
LabelDescriptor'
{_lKey = Nothing, _lValueType = Nothing, _lDescription = Nothing}
lKey :: Lens' LabelDescriptor (Maybe Text)
lKey = lens _lKey (\ s a -> s{_lKey = a})
lValueType :: Lens' LabelDescriptor (Maybe LabelDescriptorValueType)
lValueType
= lens _lValueType (\ s a -> s{_lValueType = a})
lDescription :: Lens' LabelDescriptor (Maybe Text)
lDescription
= lens _lDescription (\ s a -> s{_lDescription = a})
instance FromJSON LabelDescriptor where
parseJSON
= withObject "LabelDescriptor"
(\ o ->
LabelDescriptor' <$>
(o .:? "key") <*> (o .:? "valueType") <*>
(o .:? "description"))
instance ToJSON LabelDescriptor where
toJSON LabelDescriptor'{..}
= object
(catMaybes
[("key" .=) <$> _lKey,
("valueType" .=) <$> _lValueType,
("description" .=) <$> _lDescription])
data V1Beta1DisableConsumerResponse =
V1Beta1DisableConsumerResponse'
deriving (Eq, Show, Data, Typeable, Generic)
v1Beta1DisableConsumerResponse
:: V1Beta1DisableConsumerResponse
v1Beta1DisableConsumerResponse = V1Beta1DisableConsumerResponse'
instance FromJSON V1Beta1DisableConsumerResponse
where
parseJSON
= withObject "V1Beta1DisableConsumerResponse"
(\ o -> pure V1Beta1DisableConsumerResponse')
instance ToJSON V1Beta1DisableConsumerResponse where
toJSON = const emptyObject
data Usage =
Usage'
{ _uRequirements :: !(Maybe [Text])
, _uRules :: !(Maybe [UsageRule])
, _uProducerNotificationChannel :: !(Maybe Text)
}
deriving (Eq, Show, Data, Typeable, Generic)
usage
:: Usage
usage =
Usage'
{ _uRequirements = Nothing
, _uRules = Nothing
, _uProducerNotificationChannel = Nothing
}
uRequirements :: Lens' Usage [Text]
uRequirements
= lens _uRequirements
(\ s a -> s{_uRequirements = a})
. _Default
. _Coerce
uRules :: Lens' Usage [UsageRule]
uRules
= lens _uRules (\ s a -> s{_uRules = a}) . _Default .
_Coerce
uProducerNotificationChannel :: Lens' Usage (Maybe Text)
uProducerNotificationChannel
= lens _uProducerNotificationChannel
(\ s a -> s{_uProducerNotificationChannel = a})
instance FromJSON Usage where
parseJSON
= withObject "Usage"
(\ o ->
Usage' <$>
(o .:? "requirements" .!= mempty) <*>
(o .:? "rules" .!= mempty)
<*> (o .:? "producerNotificationChannel"))
instance ToJSON Usage where
toJSON Usage'{..}
= object
(catMaybes
[("requirements" .=) <$> _uRequirements,
("rules" .=) <$> _uRules,
("producerNotificationChannel" .=) <$>
_uProducerNotificationChannel])
newtype V1Beta1BatchCreateProducerOverridesResponse =
V1Beta1BatchCreateProducerOverridesResponse'
{ _vbbcporOverrides :: Maybe [V1Beta1QuotaOverride]
}
deriving (Eq, Show, Data, Typeable, Generic)
v1Beta1BatchCreateProducerOverridesResponse
:: V1Beta1BatchCreateProducerOverridesResponse
v1Beta1BatchCreateProducerOverridesResponse =
V1Beta1BatchCreateProducerOverridesResponse' {_vbbcporOverrides = Nothing}
vbbcporOverrides :: Lens' V1Beta1BatchCreateProducerOverridesResponse [V1Beta1QuotaOverride]
vbbcporOverrides
= lens _vbbcporOverrides
(\ s a -> s{_vbbcporOverrides = a})
. _Default
. _Coerce
instance FromJSON
V1Beta1BatchCreateProducerOverridesResponse
where
parseJSON
= withObject
"V1Beta1BatchCreateProducerOverridesResponse"
(\ o ->
V1Beta1BatchCreateProducerOverridesResponse' <$>
(o .:? "overrides" .!= mempty))
instance ToJSON
V1Beta1BatchCreateProducerOverridesResponse
where
toJSON
V1Beta1BatchCreateProducerOverridesResponse'{..}
= object
(catMaybes [("overrides" .=) <$> _vbbcporOverrides])
data HTTP =
HTTP'
{ _hRules :: !(Maybe [HTTPRule])
, _hFullyDecodeReservedExpansion :: !(Maybe Bool)
}
deriving (Eq, Show, Data, Typeable, Generic)
hTTP
:: HTTP
hTTP = HTTP' {_hRules = Nothing, _hFullyDecodeReservedExpansion = Nothing}
hRules :: Lens' HTTP [HTTPRule]
hRules
= lens _hRules (\ s a -> s{_hRules = a}) . _Default .
_Coerce
hFullyDecodeReservedExpansion :: Lens' HTTP (Maybe Bool)
hFullyDecodeReservedExpansion
= lens _hFullyDecodeReservedExpansion
(\ s a -> s{_hFullyDecodeReservedExpansion = a})
instance FromJSON HTTP where
parseJSON
= withObject "HTTP"
(\ o ->
HTTP' <$>
(o .:? "rules" .!= mempty) <*>
(o .:? "fullyDecodeReservedExpansion"))
instance ToJSON HTTP where
toJSON HTTP'{..}
= object
(catMaybes
[("rules" .=) <$> _hRules,
("fullyDecodeReservedExpansion" .=) <$>