{-# 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.Container.Types.Product where
import Network.Google.Container.Types.Sum
import Network.Google.Prelude
newtype NetworkPolicyConfig =
NetworkPolicyConfig'
{ _npcDisabled :: Maybe Bool
}
deriving (Eq, Show, Data, Typeable, Generic)
networkPolicyConfig
:: NetworkPolicyConfig
networkPolicyConfig = NetworkPolicyConfig' {_npcDisabled = Nothing}
npcDisabled :: Lens' NetworkPolicyConfig (Maybe Bool)
npcDisabled
= lens _npcDisabled (\ s a -> s{_npcDisabled = a})
instance FromJSON NetworkPolicyConfig where
parseJSON
= withObject "NetworkPolicyConfig"
(\ o -> NetworkPolicyConfig' <$> (o .:? "disabled"))
instance ToJSON NetworkPolicyConfig where
toJSON NetworkPolicyConfig'{..}
= object
(catMaybes [("disabled" .=) <$> _npcDisabled])
data ListUsableSubnetworksResponse =
ListUsableSubnetworksResponse'
{ _lusrNextPageToken :: !(Maybe Text)
, _lusrSubnetworks :: !(Maybe [UsableSubnetwork])
}
deriving (Eq, Show, Data, Typeable, Generic)
listUsableSubnetworksResponse
:: ListUsableSubnetworksResponse
listUsableSubnetworksResponse =
ListUsableSubnetworksResponse'
{_lusrNextPageToken = Nothing, _lusrSubnetworks = Nothing}
lusrNextPageToken :: Lens' ListUsableSubnetworksResponse (Maybe Text)
lusrNextPageToken
= lens _lusrNextPageToken
(\ s a -> s{_lusrNextPageToken = a})
lusrSubnetworks :: Lens' ListUsableSubnetworksResponse [UsableSubnetwork]
lusrSubnetworks
= lens _lusrSubnetworks
(\ s a -> s{_lusrSubnetworks = a})
. _Default
. _Coerce
instance FromJSON ListUsableSubnetworksResponse where
parseJSON
= withObject "ListUsableSubnetworksResponse"
(\ o ->
ListUsableSubnetworksResponse' <$>
(o .:? "nextPageToken") <*>
(o .:? "subnetworks" .!= mempty))
instance ToJSON ListUsableSubnetworksResponse where
toJSON ListUsableSubnetworksResponse'{..}
= object
(catMaybes
[("nextPageToken" .=) <$> _lusrNextPageToken,
("subnetworks" .=) <$> _lusrSubnetworks])
data UpdateNodePoolRequest =
UpdateNodePoolRequest'
{ _unprZone :: !(Maybe Text)
, _unprNodePoolId :: !(Maybe Text)
, _unprImageType :: !(Maybe Text)
, _unprName :: !(Maybe Text)
, _unprClusterId :: !(Maybe Text)
, _unprNodeVersion :: !(Maybe Text)
, _unprProjectId :: !(Maybe Text)
}
deriving (Eq, Show, Data, Typeable, Generic)
updateNodePoolRequest
:: UpdateNodePoolRequest
updateNodePoolRequest =
UpdateNodePoolRequest'
{ _unprZone = Nothing
, _unprNodePoolId = Nothing
, _unprImageType = Nothing
, _unprName = Nothing
, _unprClusterId = Nothing
, _unprNodeVersion = Nothing
, _unprProjectId = Nothing
}
unprZone :: Lens' UpdateNodePoolRequest (Maybe Text)
unprZone = lens _unprZone (\ s a -> s{_unprZone = a})
unprNodePoolId :: Lens' UpdateNodePoolRequest (Maybe Text)
unprNodePoolId
= lens _unprNodePoolId
(\ s a -> s{_unprNodePoolId = a})
unprImageType :: Lens' UpdateNodePoolRequest (Maybe Text)
unprImageType
= lens _unprImageType
(\ s a -> s{_unprImageType = a})
unprName :: Lens' UpdateNodePoolRequest (Maybe Text)
unprName = lens _unprName (\ s a -> s{_unprName = a})
unprClusterId :: Lens' UpdateNodePoolRequest (Maybe Text)
unprClusterId
= lens _unprClusterId
(\ s a -> s{_unprClusterId = a})
unprNodeVersion :: Lens' UpdateNodePoolRequest (Maybe Text)
unprNodeVersion
= lens _unprNodeVersion
(\ s a -> s{_unprNodeVersion = a})
unprProjectId :: Lens' UpdateNodePoolRequest (Maybe Text)
unprProjectId
= lens _unprProjectId
(\ s a -> s{_unprProjectId = a})
instance FromJSON UpdateNodePoolRequest where
parseJSON
= withObject "UpdateNodePoolRequest"
(\ o ->
UpdateNodePoolRequest' <$>
(o .:? "zone") <*> (o .:? "nodePoolId") <*>
(o .:? "imageType")
<*> (o .:? "name")
<*> (o .:? "clusterId")
<*> (o .:? "nodeVersion")
<*> (o .:? "projectId"))
instance ToJSON UpdateNodePoolRequest where
toJSON UpdateNodePoolRequest'{..}
= object
(catMaybes
[("zone" .=) <$> _unprZone,
("nodePoolId" .=) <$> _unprNodePoolId,
("imageType" .=) <$> _unprImageType,
("name" .=) <$> _unprName,
("clusterId" .=) <$> _unprClusterId,
("nodeVersion" .=) <$> _unprNodeVersion,
("projectId" .=) <$> _unprProjectId])
data UpdateMasterRequest =
UpdateMasterRequest'
{ _umrZone :: !(Maybe Text)
, _umrName :: !(Maybe Text)
, _umrClusterId :: !(Maybe Text)
, _umrProjectId :: !(Maybe Text)
, _umrMasterVersion :: !(Maybe Text)
}
deriving (Eq, Show, Data, Typeable, Generic)
updateMasterRequest
:: UpdateMasterRequest
updateMasterRequest =
UpdateMasterRequest'
{ _umrZone = Nothing
, _umrName = Nothing
, _umrClusterId = Nothing
, _umrProjectId = Nothing
, _umrMasterVersion = Nothing
}
umrZone :: Lens' UpdateMasterRequest (Maybe Text)
umrZone = lens _umrZone (\ s a -> s{_umrZone = a})
umrName :: Lens' UpdateMasterRequest (Maybe Text)
umrName = lens _umrName (\ s a -> s{_umrName = a})
umrClusterId :: Lens' UpdateMasterRequest (Maybe Text)
umrClusterId
= lens _umrClusterId (\ s a -> s{_umrClusterId = a})
umrProjectId :: Lens' UpdateMasterRequest (Maybe Text)
umrProjectId
= lens _umrProjectId (\ s a -> s{_umrProjectId = a})
umrMasterVersion :: Lens' UpdateMasterRequest (Maybe Text)
umrMasterVersion
= lens _umrMasterVersion
(\ s a -> s{_umrMasterVersion = a})
instance FromJSON UpdateMasterRequest where
parseJSON
= withObject "UpdateMasterRequest"
(\ o ->
UpdateMasterRequest' <$>
(o .:? "zone") <*> (o .:? "name") <*>
(o .:? "clusterId")
<*> (o .:? "projectId")
<*> (o .:? "masterVersion"))
instance ToJSON UpdateMasterRequest where
toJSON UpdateMasterRequest'{..}
= object
(catMaybes
[("zone" .=) <$> _umrZone, ("name" .=) <$> _umrName,
("clusterId" .=) <$> _umrClusterId,
("projectId" .=) <$> _umrProjectId,
("masterVersion" .=) <$> _umrMasterVersion])
data StartIPRotationRequest =
StartIPRotationRequest'
{ _sirrZone :: !(Maybe Text)
, _sirrRotateCredentials :: !(Maybe Bool)
, _sirrName :: !(Maybe Text)
, _sirrClusterId :: !(Maybe Text)
, _sirrProjectId :: !(Maybe Text)
}
deriving (Eq, Show, Data, Typeable, Generic)
startIPRotationRequest
:: StartIPRotationRequest
startIPRotationRequest =
StartIPRotationRequest'
{ _sirrZone = Nothing
, _sirrRotateCredentials = Nothing
, _sirrName = Nothing
, _sirrClusterId = Nothing
, _sirrProjectId = Nothing
}
sirrZone :: Lens' StartIPRotationRequest (Maybe Text)
sirrZone = lens _sirrZone (\ s a -> s{_sirrZone = a})
sirrRotateCredentials :: Lens' StartIPRotationRequest (Maybe Bool)
sirrRotateCredentials
= lens _sirrRotateCredentials
(\ s a -> s{_sirrRotateCredentials = a})
sirrName :: Lens' StartIPRotationRequest (Maybe Text)
sirrName = lens _sirrName (\ s a -> s{_sirrName = a})
sirrClusterId :: Lens' StartIPRotationRequest (Maybe Text)
sirrClusterId
= lens _sirrClusterId
(\ s a -> s{_sirrClusterId = a})
sirrProjectId :: Lens' StartIPRotationRequest (Maybe Text)
sirrProjectId
= lens _sirrProjectId
(\ s a -> s{_sirrProjectId = a})
instance FromJSON StartIPRotationRequest where
parseJSON
= withObject "StartIPRotationRequest"
(\ o ->
StartIPRotationRequest' <$>
(o .:? "zone") <*> (o .:? "rotateCredentials") <*>
(o .:? "name")
<*> (o .:? "clusterId")
<*> (o .:? "projectId"))
instance ToJSON StartIPRotationRequest where
toJSON StartIPRotationRequest'{..}
= object
(catMaybes
[("zone" .=) <$> _sirrZone,
("rotateCredentials" .=) <$> _sirrRotateCredentials,
("name" .=) <$> _sirrName,
("clusterId" .=) <$> _sirrClusterId,
("projectId" .=) <$> _sirrProjectId])
data SetLegacyAbacRequest =
SetLegacyAbacRequest'
{ _slarEnabled :: !(Maybe Bool)
, _slarZone :: !(Maybe Text)
, _slarName :: !(Maybe Text)
, _slarClusterId :: !(Maybe Text)
, _slarProjectId :: !(Maybe Text)
}
deriving (Eq, Show, Data, Typeable, Generic)
setLegacyAbacRequest
:: SetLegacyAbacRequest
setLegacyAbacRequest =
SetLegacyAbacRequest'
{ _slarEnabled = Nothing
, _slarZone = Nothing
, _slarName = Nothing
, _slarClusterId = Nothing
, _slarProjectId = Nothing
}
slarEnabled :: Lens' SetLegacyAbacRequest (Maybe Bool)
slarEnabled
= lens _slarEnabled (\ s a -> s{_slarEnabled = a})
slarZone :: Lens' SetLegacyAbacRequest (Maybe Text)
slarZone = lens _slarZone (\ s a -> s{_slarZone = a})
slarName :: Lens' SetLegacyAbacRequest (Maybe Text)
slarName = lens _slarName (\ s a -> s{_slarName = a})
slarClusterId :: Lens' SetLegacyAbacRequest (Maybe Text)
slarClusterId
= lens _slarClusterId
(\ s a -> s{_slarClusterId = a})
slarProjectId :: Lens' SetLegacyAbacRequest (Maybe Text)
slarProjectId
= lens _slarProjectId
(\ s a -> s{_slarProjectId = a})
instance FromJSON SetLegacyAbacRequest where
parseJSON
= withObject "SetLegacyAbacRequest"
(\ o ->
SetLegacyAbacRequest' <$>
(o .:? "enabled") <*> (o .:? "zone") <*>
(o .:? "name")
<*> (o .:? "clusterId")
<*> (o .:? "projectId"))
instance ToJSON SetLegacyAbacRequest where
toJSON SetLegacyAbacRequest'{..}
= object
(catMaybes
[("enabled" .=) <$> _slarEnabled,
("zone" .=) <$> _slarZone, ("name" .=) <$> _slarName,
("clusterId" .=) <$> _slarClusterId,
("projectId" .=) <$> _slarProjectId])
newtype HorizontalPodAutoscaling =
HorizontalPodAutoscaling'
{ _hpaDisabled :: Maybe Bool
}
deriving (Eq, Show, Data, Typeable, Generic)
horizontalPodAutoscaling
:: HorizontalPodAutoscaling
horizontalPodAutoscaling = HorizontalPodAutoscaling' {_hpaDisabled = Nothing}
hpaDisabled :: Lens' HorizontalPodAutoscaling (Maybe Bool)
hpaDisabled
= lens _hpaDisabled (\ s a -> s{_hpaDisabled = a})
instance FromJSON HorizontalPodAutoscaling where
parseJSON
= withObject "HorizontalPodAutoscaling"
(\ o ->
HorizontalPodAutoscaling' <$> (o .:? "disabled"))
instance ToJSON HorizontalPodAutoscaling where
toJSON HorizontalPodAutoscaling'{..}
= object
(catMaybes [("disabled" .=) <$> _hpaDisabled])
data SetMasterAuthRequest =
SetMasterAuthRequest'
{ _smarAction :: !(Maybe SetMasterAuthRequestAction)
, _smarZone :: !(Maybe Text)
, _smarName :: !(Maybe Text)
, _smarClusterId :: !(Maybe Text)
, _smarProjectId :: !(Maybe Text)
, _smarUpdate :: !(Maybe MasterAuth)
}
deriving (Eq, Show, Data, Typeable, Generic)
setMasterAuthRequest
:: SetMasterAuthRequest
setMasterAuthRequest =
SetMasterAuthRequest'
{ _smarAction = Nothing
, _smarZone = Nothing
, _smarName = Nothing
, _smarClusterId = Nothing
, _smarProjectId = Nothing
, _smarUpdate = Nothing
}
smarAction :: Lens' SetMasterAuthRequest (Maybe SetMasterAuthRequestAction)
smarAction
= lens _smarAction (\ s a -> s{_smarAction = a})
smarZone :: Lens' SetMasterAuthRequest (Maybe Text)
smarZone = lens _smarZone (\ s a -> s{_smarZone = a})
smarName :: Lens' SetMasterAuthRequest (Maybe Text)
smarName = lens _smarName (\ s a -> s{_smarName = a})
smarClusterId :: Lens' SetMasterAuthRequest (Maybe Text)
smarClusterId
= lens _smarClusterId
(\ s a -> s{_smarClusterId = a})
smarProjectId :: Lens' SetMasterAuthRequest (Maybe Text)
smarProjectId
= lens _smarProjectId
(\ s a -> s{_smarProjectId = a})
smarUpdate :: Lens' SetMasterAuthRequest (Maybe MasterAuth)
smarUpdate
= lens _smarUpdate (\ s a -> s{_smarUpdate = a})
instance FromJSON SetMasterAuthRequest where
parseJSON
= withObject "SetMasterAuthRequest"
(\ o ->
SetMasterAuthRequest' <$>
(o .:? "action") <*> (o .:? "zone") <*>
(o .:? "name")
<*> (o .:? "clusterId")
<*> (o .:? "projectId")
<*> (o .:? "update"))
instance ToJSON SetMasterAuthRequest where
toJSON SetMasterAuthRequest'{..}
= object
(catMaybes
[("action" .=) <$> _smarAction,
("zone" .=) <$> _smarZone, ("name" .=) <$> _smarName,
("clusterId" .=) <$> _smarClusterId,
("projectId" .=) <$> _smarProjectId,
("update" .=) <$> _smarUpdate])
data ListOperationsResponse =
ListOperationsResponse'
{ _lorOperations :: !(Maybe [Operation])
, _lorMissingZones :: !(Maybe [Text])
}
deriving (Eq, Show, Data, Typeable, Generic)
listOperationsResponse
:: ListOperationsResponse
listOperationsResponse =
ListOperationsResponse' {_lorOperations = Nothing, _lorMissingZones = Nothing}
lorOperations :: Lens' ListOperationsResponse [Operation]
lorOperations
= lens _lorOperations
(\ s a -> s{_lorOperations = a})
. _Default
. _Coerce
lorMissingZones :: Lens' ListOperationsResponse [Text]
lorMissingZones
= lens _lorMissingZones
(\ s a -> s{_lorMissingZones = a})
. _Default
. _Coerce
instance FromJSON ListOperationsResponse where
parseJSON
= withObject "ListOperationsResponse"
(\ o ->
ListOperationsResponse' <$>
(o .:? "operations" .!= mempty) <*>
(o .:? "missingZones" .!= mempty))
instance ToJSON ListOperationsResponse where
toJSON ListOperationsResponse'{..}
= object
(catMaybes
[("operations" .=) <$> _lorOperations,
("missingZones" .=) <$> _lorMissingZones])
data CreateClusterRequest =
CreateClusterRequest'
{ _ccrParent :: !(Maybe Text)
, _ccrCluster :: !(Maybe Cluster)
, _ccrZone :: !(Maybe Text)
, _ccrProjectId :: !(Maybe Text)
}
deriving (Eq, Show, Data, Typeable, Generic)
createClusterRequest
:: CreateClusterRequest
createClusterRequest =
CreateClusterRequest'
{ _ccrParent = Nothing
, _ccrCluster = Nothing
, _ccrZone = Nothing
, _ccrProjectId = Nothing
}
ccrParent :: Lens' CreateClusterRequest (Maybe Text)
ccrParent
= lens _ccrParent (\ s a -> s{_ccrParent = a})
ccrCluster :: Lens' CreateClusterRequest (Maybe Cluster)
ccrCluster
= lens _ccrCluster (\ s a -> s{_ccrCluster = a})
ccrZone :: Lens' CreateClusterRequest (Maybe Text)
ccrZone = lens _ccrZone (\ s a -> s{_ccrZone = a})
ccrProjectId :: Lens' CreateClusterRequest (Maybe Text)
ccrProjectId
= lens _ccrProjectId (\ s a -> s{_ccrProjectId = a})
instance FromJSON CreateClusterRequest where
parseJSON
= withObject "CreateClusterRequest"
(\ o ->
CreateClusterRequest' <$>
(o .:? "parent") <*> (o .:? "cluster") <*>
(o .:? "zone")
<*> (o .:? "projectId"))
instance ToJSON CreateClusterRequest where
toJSON CreateClusterRequest'{..}
= object
(catMaybes
[("parent" .=) <$> _ccrParent,
("cluster" .=) <$> _ccrCluster,
("zone" .=) <$> _ccrZone,
("projectId" .=) <$> _ccrProjectId])
data Cluster =
Cluster'
{ _cStatus :: !(Maybe ClusterStatus)
, _cNodePools :: !(Maybe [NodePool])
, _cEnableKubernetesAlpha :: !(Maybe Bool)
, _cResourceLabels :: !(Maybe ClusterResourceLabels)
, _cTpuIPv4CIdRBlock :: !(Maybe Text)
, _cNodeConfig :: !(Maybe NodeConfig)
, _cNodeIPv4CIdRSize :: !(Maybe (Textual Int32))
, _cClusterIPv4CIdR :: !(Maybe Text)
, _cLocation :: !(Maybe Text)
, _cInitialNodeCount :: !(Maybe (Textual Int32))
, _cCurrentNodeVersion :: !(Maybe Text)
, _cNetwork :: !(Maybe Text)
, _cInitialClusterVersion :: !(Maybe Text)
, _cZone :: !(Maybe Text)
, _cAddonsConfig :: !(Maybe AddonsConfig)
, _cServicesIPv4CIdR :: !(Maybe Text)
, _cIPAllocationPolicy :: !(Maybe IPAllocationPolicy)
, _cMasterAuthorizedNetworksConfig :: !(Maybe MasterAuthorizedNetworksConfig)
, _cLegacyAbac :: !(Maybe LegacyAbac)
, _cNetworkConfig :: !(Maybe NetworkConfig)
, _cMasterAuth :: !(Maybe MasterAuth)
, _cSelfLink :: !(Maybe Text)
, _cName :: !(Maybe Text)
, _cCurrentMasterVersion :: !(Maybe Text)
, _cStatusMessage :: !(Maybe Text)
, _cDefaultMaxPodsConstraint :: !(Maybe MaxPodsConstraint)
, _cSubnetwork :: !(Maybe Text)
, _cCurrentNodeCount :: !(Maybe (Textual Int32))
, _cPrivateClusterConfig :: !(Maybe PrivateClusterConfig)
, _cMaintenancePolicy :: !(Maybe MaintenancePolicy)
, _cConditions :: !(Maybe [StatusCondition])
, _cEnableTpu :: !(Maybe Bool)
, _cEndpoint :: !(Maybe Text)
, _cExpireTime :: !(Maybe Text)
, _cNetworkPolicy :: !(Maybe NetworkPolicy)
, _cLocations :: !(Maybe [Text])
, _cLoggingService :: !(Maybe Text)
, _cLabelFingerprint :: !(Maybe Text)
, _cDescription :: !(Maybe Text)
, _cInstanceGroupURLs :: !(Maybe [Text])
, _cMonitoringService :: !(Maybe Text)
, _cCreateTime :: !(Maybe Text)
}
deriving (Eq, Show, Data, Typeable, Generic)
cluster
:: Cluster
cluster =
Cluster'
{ _cStatus = Nothing
, _cNodePools = Nothing
, _cEnableKubernetesAlpha = Nothing
, _cResourceLabels = Nothing
, _cTpuIPv4CIdRBlock = Nothing
, _cNodeConfig = Nothing
, _cNodeIPv4CIdRSize = Nothing
, _cClusterIPv4CIdR = Nothing
, _cLocation = Nothing
, _cInitialNodeCount = Nothing
, _cCurrentNodeVersion = Nothing
, _cNetwork = Nothing
, _cInitialClusterVersion = Nothing
, _cZone = Nothing
, _cAddonsConfig = Nothing
, _cServicesIPv4CIdR = Nothing
, _cIPAllocationPolicy = Nothing
, _cMasterAuthorizedNetworksConfig = Nothing
, _cLegacyAbac = Nothing
, _cNetworkConfig = Nothing
, _cMasterAuth = Nothing
, _cSelfLink = Nothing
, _cName = Nothing
, _cCurrentMasterVersion = Nothing
, _cStatusMessage = Nothing
, _cDefaultMaxPodsConstraint = Nothing
, _cSubnetwork = Nothing
, _cCurrentNodeCount = Nothing
, _cPrivateClusterConfig = Nothing
, _cMaintenancePolicy = Nothing
, _cConditions = Nothing
, _cEnableTpu = Nothing
, _cEndpoint = Nothing
, _cExpireTime = Nothing
, _cNetworkPolicy = Nothing
, _cLocations = Nothing
, _cLoggingService = Nothing
, _cLabelFingerprint = Nothing
, _cDescription = Nothing
, _cInstanceGroupURLs = Nothing
, _cMonitoringService = Nothing
, _cCreateTime = Nothing
}
cStatus :: Lens' Cluster (Maybe ClusterStatus)
cStatus = lens _cStatus (\ s a -> s{_cStatus = a})
cNodePools :: Lens' Cluster [NodePool]
cNodePools
= lens _cNodePools (\ s a -> s{_cNodePools = a}) .
_Default
. _Coerce
cEnableKubernetesAlpha :: Lens' Cluster (Maybe Bool)
cEnableKubernetesAlpha
= lens _cEnableKubernetesAlpha
(\ s a -> s{_cEnableKubernetesAlpha = a})
cResourceLabels :: Lens' Cluster (Maybe ClusterResourceLabels)
cResourceLabels
= lens _cResourceLabels
(\ s a -> s{_cResourceLabels = a})
cTpuIPv4CIdRBlock :: Lens' Cluster (Maybe Text)
cTpuIPv4CIdRBlock
= lens _cTpuIPv4CIdRBlock
(\ s a -> s{_cTpuIPv4CIdRBlock = a})
cNodeConfig :: Lens' Cluster (Maybe NodeConfig)
cNodeConfig
= lens _cNodeConfig (\ s a -> s{_cNodeConfig = a})
cNodeIPv4CIdRSize :: Lens' Cluster (Maybe Int32)
cNodeIPv4CIdRSize
= lens _cNodeIPv4CIdRSize
(\ s a -> s{_cNodeIPv4CIdRSize = a})
. mapping _Coerce
cClusterIPv4CIdR :: Lens' Cluster (Maybe Text)
cClusterIPv4CIdR
= lens _cClusterIPv4CIdR
(\ s a -> s{_cClusterIPv4CIdR = a})
cLocation :: Lens' Cluster (Maybe Text)
cLocation
= lens _cLocation (\ s a -> s{_cLocation = a})
cInitialNodeCount :: Lens' Cluster (Maybe Int32)
cInitialNodeCount
= lens _cInitialNodeCount
(\ s a -> s{_cInitialNodeCount = a})
. mapping _Coerce
cCurrentNodeVersion :: Lens' Cluster (Maybe Text)
cCurrentNodeVersion
= lens _cCurrentNodeVersion
(\ s a -> s{_cCurrentNodeVersion = a})
cNetwork :: Lens' Cluster (Maybe Text)
cNetwork = lens _cNetwork (\ s a -> s{_cNetwork = a})
cInitialClusterVersion :: Lens' Cluster (Maybe Text)
cInitialClusterVersion
= lens _cInitialClusterVersion
(\ s a -> s{_cInitialClusterVersion = a})
cZone :: Lens' Cluster (Maybe Text)
cZone = lens _cZone (\ s a -> s{_cZone = a})
cAddonsConfig :: Lens' Cluster (Maybe AddonsConfig)
cAddonsConfig
= lens _cAddonsConfig
(\ s a -> s{_cAddonsConfig = a})
cServicesIPv4CIdR :: Lens' Cluster (Maybe Text)
cServicesIPv4CIdR
= lens _cServicesIPv4CIdR
(\ s a -> s{_cServicesIPv4CIdR = a})
cIPAllocationPolicy :: Lens' Cluster (Maybe IPAllocationPolicy)
cIPAllocationPolicy
= lens _cIPAllocationPolicy
(\ s a -> s{_cIPAllocationPolicy = a})
cMasterAuthorizedNetworksConfig :: Lens' Cluster (Maybe MasterAuthorizedNetworksConfig)
cMasterAuthorizedNetworksConfig
= lens _cMasterAuthorizedNetworksConfig
(\ s a -> s{_cMasterAuthorizedNetworksConfig = a})
cLegacyAbac :: Lens' Cluster (Maybe LegacyAbac)
cLegacyAbac
= lens _cLegacyAbac (\ s a -> s{_cLegacyAbac = a})
cNetworkConfig :: Lens' Cluster (Maybe NetworkConfig)
cNetworkConfig
= lens _cNetworkConfig
(\ s a -> s{_cNetworkConfig = a})
cMasterAuth :: Lens' Cluster (Maybe MasterAuth)
cMasterAuth
= lens _cMasterAuth (\ s a -> s{_cMasterAuth = a})
cSelfLink :: Lens' Cluster (Maybe Text)
cSelfLink
= lens _cSelfLink (\ s a -> s{_cSelfLink = a})
cName :: Lens' Cluster (Maybe Text)
cName = lens _cName (\ s a -> s{_cName = a})
cCurrentMasterVersion :: Lens' Cluster (Maybe Text)
cCurrentMasterVersion
= lens _cCurrentMasterVersion
(\ s a -> s{_cCurrentMasterVersion = a})
cStatusMessage :: Lens' Cluster (Maybe Text)
cStatusMessage
= lens _cStatusMessage
(\ s a -> s{_cStatusMessage = a})
cDefaultMaxPodsConstraint :: Lens' Cluster (Maybe MaxPodsConstraint)
cDefaultMaxPodsConstraint
= lens _cDefaultMaxPodsConstraint
(\ s a -> s{_cDefaultMaxPodsConstraint = a})
cSubnetwork :: Lens' Cluster (Maybe Text)
cSubnetwork
= lens _cSubnetwork (\ s a -> s{_cSubnetwork = a})
cCurrentNodeCount :: Lens' Cluster (Maybe Int32)
cCurrentNodeCount
= lens _cCurrentNodeCount
(\ s a -> s{_cCurrentNodeCount = a})
. mapping _Coerce
cPrivateClusterConfig :: Lens' Cluster (Maybe PrivateClusterConfig)
cPrivateClusterConfig
= lens _cPrivateClusterConfig
(\ s a -> s{_cPrivateClusterConfig = a})
cMaintenancePolicy :: Lens' Cluster (Maybe MaintenancePolicy)
cMaintenancePolicy
= lens _cMaintenancePolicy
(\ s a -> s{_cMaintenancePolicy = a})
cConditions :: Lens' Cluster [StatusCondition]
cConditions
= lens _cConditions (\ s a -> s{_cConditions = a}) .
_Default
. _Coerce
cEnableTpu :: Lens' Cluster (Maybe Bool)
cEnableTpu
= lens _cEnableTpu (\ s a -> s{_cEnableTpu = a})
cEndpoint :: Lens' Cluster (Maybe Text)
cEndpoint
= lens _cEndpoint (\ s a -> s{_cEndpoint = a})
cExpireTime :: Lens' Cluster (Maybe Text)
cExpireTime
= lens _cExpireTime (\ s a -> s{_cExpireTime = a})
cNetworkPolicy :: Lens' Cluster (Maybe NetworkPolicy)
cNetworkPolicy
= lens _cNetworkPolicy
(\ s a -> s{_cNetworkPolicy = a})
cLocations :: Lens' Cluster [Text]
cLocations
= lens _cLocations (\ s a -> s{_cLocations = a}) .
_Default
. _Coerce
cLoggingService :: Lens' Cluster (Maybe Text)
cLoggingService
= lens _cLoggingService
(\ s a -> s{_cLoggingService = a})
cLabelFingerprint :: Lens' Cluster (Maybe Text)
cLabelFingerprint
= lens _cLabelFingerprint
(\ s a -> s{_cLabelFingerprint = a})
cDescription :: Lens' Cluster (Maybe Text)
cDescription
= lens _cDescription (\ s a -> s{_cDescription = a})
cInstanceGroupURLs :: Lens' Cluster [Text]
cInstanceGroupURLs
= lens _cInstanceGroupURLs
(\ s a -> s{_cInstanceGroupURLs = a})
. _Default
. _Coerce
cMonitoringService :: Lens' Cluster (Maybe Text)
cMonitoringService
= lens _cMonitoringService
(\ s a -> s{_cMonitoringService = a})
cCreateTime :: Lens' Cluster (Maybe Text)
cCreateTime
= lens _cCreateTime (\ s a -> s{_cCreateTime = a})
instance FromJSON Cluster where
parseJSON
= withObject "Cluster"
(\ o ->
Cluster' <$>
(o .:? "status") <*> (o .:? "nodePools" .!= mempty)
<*> (o .:? "enableKubernetesAlpha")
<*> (o .:? "resourceLabels")
<*> (o .:? "tpuIpv4CidrBlock")
<*> (o .:? "nodeConfig")
<*> (o .:? "nodeIpv4CidrSize")
<*> (o .:? "clusterIpv4Cidr")
<*> (o .:? "location")
<*> (o .:? "initialNodeCount")
<*> (o .:? "currentNodeVersion")
<*> (o .:? "network")
<*> (o .:? "initialClusterVersion")
<*> (o .:? "zone")
<*> (o .:? "addonsConfig")
<*> (o .:? "servicesIpv4Cidr")
<*> (o .:? "ipAllocationPolicy")
<*> (o .:? "masterAuthorizedNetworksConfig")
<*> (o .:? "legacyAbac")
<*> (o .:? "networkConfig")
<*> (o .:? "masterAuth")
<*> (o .:? "selfLink")
<*> (o .:? "name")
<*> (o .:? "currentMasterVersion")
<*> (o .:? "statusMessage")
<*> (o .:? "defaultMaxPodsConstraint")
<*> (o .:? "subnetwork")
<*> (o .:? "currentNodeCount")
<*> (o .:? "privateClusterConfig")
<*> (o .:? "maintenancePolicy")
<*> (o .:? "conditions" .!= mempty)
<*> (o .:? "enableTpu")
<*> (o .:? "endpoint")
<*> (o .:? "expireTime")
<*> (o .:? "networkPolicy")
<*> (o .:? "locations" .!= mempty)
<*> (o .:? "loggingService")
<*> (o .:? "labelFingerprint")
<*> (o .:? "description")
<*> (o .:? "instanceGroupUrls" .!= mempty)
<*> (o .:? "monitoringService")
<*> (o .:? "createTime"))
instance ToJSON Cluster where
toJSON Cluster'{..}
= object
(catMaybes
[("status" .=) <$> _cStatus,
("nodePools" .=) <$> _cNodePools,
("enableKubernetesAlpha" .=) <$>
_cEnableKubernetesAlpha,
("resourceLabels" .=) <$> _cResourceLabels,
("tpuIpv4CidrBlock" .=) <$> _cTpuIPv4CIdRBlock,
("nodeConfig" .=) <$> _cNodeConfig,
("nodeIpv4CidrSize" .=) <$> _cNodeIPv4CIdRSize,
("clusterIpv4Cidr" .=) <$> _cClusterIPv4CIdR,
("location" .=) <$> _cLocation,
("initialNodeCount" .=) <$> _cInitialNodeCount,
("currentNodeVersion" .=) <$> _cCurrentNodeVersion,
("network" .=) <$> _cNetwork,
("initialClusterVersion" .=) <$>
_cInitialClusterVersion,
("zone" .=) <$> _cZone,
("addonsConfig" .=) <$> _cAddonsConfig,
("servicesIpv4Cidr" .=) <$> _cServicesIPv4CIdR,
("ipAllocationPolicy" .=) <$> _cIPAllocationPolicy,
("masterAuthorizedNetworksConfig" .=) <$>
_cMasterAuthorizedNetworksConfig,
("legacyAbac" .=) <$> _cLegacyAbac,
("networkConfig" .=) <$> _cNetworkConfig,
("masterAuth" .=) <$> _cMasterAuth,
("selfLink" .=) <$> _cSelfLink,
("name" .=) <$> _cName,
("currentMasterVersion" .=) <$>
_cCurrentMasterVersion,
("statusMessage" .=) <$> _cStatusMessage,
("defaultMaxPodsConstraint" .=) <$>
_cDefaultMaxPodsConstraint,
("subnetwork" .=) <$> _cSubnetwork,
("currentNodeCount" .=) <$> _cCurrentNodeCount,
("privateClusterConfig" .=) <$>
_cPrivateClusterConfig,
("maintenancePolicy" .=) <$> _cMaintenancePolicy,
("conditions" .=) <$> _cConditions,
("enableTpu" .=) <$> _cEnableTpu,
("endpoint" .=) <$> _cEndpoint,
("expireTime" .=) <$> _cExpireTime,
("networkPolicy" .=) <$> _cNetworkPolicy,
("locations" .=) <$> _cLocations,
("loggingService" .=) <$> _cLoggingService,
("labelFingerprint" .=) <$> _cLabelFingerprint,
("description" .=) <$> _cDescription,
("instanceGroupUrls" .=) <$> _cInstanceGroupURLs,
("monitoringService" .=) <$> _cMonitoringService,
("createTime" .=) <$> _cCreateTime])
data CancelOperationRequest =
CancelOperationRequest'
{ _corZone :: !(Maybe Text)
, _corName :: !(Maybe Text)
, _corProjectId :: !(Maybe Text)
, _corOperationId :: !(Maybe Text)
}
deriving (Eq, Show, Data, Typeable, Generic)
cancelOperationRequest
:: CancelOperationRequest
cancelOperationRequest =
CancelOperationRequest'
{ _corZone = Nothing
, _corName = Nothing
, _corProjectId = Nothing
, _corOperationId = Nothing
}
corZone :: Lens' CancelOperationRequest (Maybe Text)
corZone = lens _corZone (\ s a -> s{_corZone = a})
corName :: Lens' CancelOperationRequest (Maybe Text)
corName = lens _corName (\ s a -> s{_corName = a})
corProjectId :: Lens' CancelOperationRequest (Maybe Text)
corProjectId
= lens _corProjectId (\ s a -> s{_corProjectId = a})
corOperationId :: Lens' CancelOperationRequest (Maybe Text)
corOperationId
= lens _corOperationId
(\ s a -> s{_corOperationId = a})
instance FromJSON CancelOperationRequest where
parseJSON
= withObject "CancelOperationRequest"
(\ o ->
CancelOperationRequest' <$>
(o .:? "zone") <*> (o .:? "name") <*>
(o .:? "projectId")
<*> (o .:? "operationId"))
instance ToJSON CancelOperationRequest where
toJSON CancelOperationRequest'{..}
= object
(catMaybes
[("zone" .=) <$> _corZone, ("name" .=) <$> _corName,
("projectId" .=) <$> _corProjectId,
("operationId" .=) <$> _corOperationId])
data UpdateClusterRequest =
UpdateClusterRequest'
{ _ucrZone :: !(Maybe Text)
, _ucrName :: !(Maybe Text)
, _ucrClusterId :: !(Maybe Text)
, _ucrProjectId :: !(Maybe Text)
, _ucrUpdate :: !(Maybe ClusterUpdate)
}
deriving (Eq, Show, Data, Typeable, Generic)
updateClusterRequest
:: UpdateClusterRequest
updateClusterRequest =
UpdateClusterRequest'
{ _ucrZone = Nothing
, _ucrName = Nothing
, _ucrClusterId = Nothing
, _ucrProjectId = Nothing
, _ucrUpdate = Nothing
}
ucrZone :: Lens' UpdateClusterRequest (Maybe Text)
ucrZone = lens _ucrZone (\ s a -> s{_ucrZone = a})
ucrName :: Lens' UpdateClusterRequest (Maybe Text)
ucrName = lens _ucrName (\ s a -> s{_ucrName = a})
ucrClusterId :: Lens' UpdateClusterRequest (Maybe Text)
ucrClusterId
= lens _ucrClusterId (\ s a -> s{_ucrClusterId = a})
ucrProjectId :: Lens' UpdateClusterRequest (Maybe Text)
ucrProjectId
= lens _ucrProjectId (\ s a -> s{_ucrProjectId = a})
ucrUpdate :: Lens' UpdateClusterRequest (Maybe ClusterUpdate)
ucrUpdate
= lens _ucrUpdate (\ s a -> s{_ucrUpdate = a})
instance FromJSON UpdateClusterRequest where
parseJSON
= withObject "UpdateClusterRequest"
(\ o ->
UpdateClusterRequest' <$>
(o .:? "zone") <*> (o .:? "name") <*>
(o .:? "clusterId")
<*> (o .:? "projectId")
<*> (o .:? "update"))
instance ToJSON UpdateClusterRequest where
toJSON UpdateClusterRequest'{..}
= object
(catMaybes
[("zone" .=) <$> _ucrZone, ("name" .=) <$> _ucrName,
("clusterId" .=) <$> _ucrClusterId,
("projectId" .=) <$> _ucrProjectId,
("update" .=) <$> _ucrUpdate])
data SetAddonsConfigRequest =
SetAddonsConfigRequest'
{ _sacrZone :: !(Maybe Text)
, _sacrAddonsConfig :: !(Maybe AddonsConfig)
, _sacrName :: !(Maybe Text)
, _sacrClusterId :: !(Maybe Text)
, _sacrProjectId :: !(Maybe Text)
}
deriving (Eq, Show, Data, Typeable, Generic)
setAddonsConfigRequest
:: SetAddonsConfigRequest
setAddonsConfigRequest =
SetAddonsConfigRequest'
{ _sacrZone = Nothing
, _sacrAddonsConfig = Nothing
, _sacrName = Nothing
, _sacrClusterId = Nothing
, _sacrProjectId = Nothing
}
sacrZone :: Lens' SetAddonsConfigRequest (Maybe Text)
sacrZone = lens _sacrZone (\ s a -> s{_sacrZone = a})
sacrAddonsConfig :: Lens' SetAddonsConfigRequest (Maybe AddonsConfig)
sacrAddonsConfig
= lens _sacrAddonsConfig
(\ s a -> s{_sacrAddonsConfig = a})
sacrName :: Lens' SetAddonsConfigRequest (Maybe Text)
sacrName = lens _sacrName (\ s a -> s{_sacrName = a})
sacrClusterId :: Lens' SetAddonsConfigRequest (Maybe Text)
sacrClusterId
= lens _sacrClusterId
(\ s a -> s{_sacrClusterId = a})
sacrProjectId :: Lens' SetAddonsConfigRequest (Maybe Text)
sacrProjectId
= lens _sacrProjectId
(\ s a -> s{_sacrProjectId = a})
instance FromJSON SetAddonsConfigRequest where
parseJSON
= withObject "SetAddonsConfigRequest"
(\ o ->
SetAddonsConfigRequest' <$>
(o .:? "zone") <*> (o .:? "addonsConfig") <*>
(o .:? "name")
<*> (o .:? "clusterId")
<*> (o .:? "projectId"))
instance ToJSON SetAddonsConfigRequest where
toJSON SetAddonsConfigRequest'{..}
= object
(catMaybes
[("zone" .=) <$> _sacrZone,
("addonsConfig" .=) <$> _sacrAddonsConfig,
("name" .=) <$> _sacrName,
("clusterId" .=) <$> _sacrClusterId,
("projectId" .=) <$> _sacrProjectId])
data NodeConfig =
NodeConfig'
{ _ncLocalSsdCount :: !(Maybe (Textual Int32))
, _ncDiskSizeGb :: !(Maybe (Textual Int32))
, _ncTaints :: !(Maybe [NodeTaint])
, _ncOAuthScopes :: !(Maybe [Text])
, _ncServiceAccount :: !(Maybe Text)
, _ncAccelerators :: !(Maybe [AcceleratorConfig])
, _ncImageType :: !(Maybe Text)
, _ncMachineType :: !(Maybe Text)
, _ncMetadata :: !(Maybe NodeConfigMetadata)
, _ncDiskType :: !(Maybe Text)
, _ncLabels :: !(Maybe NodeConfigLabels)
, _ncMinCPUPlatform :: !(Maybe Text)
, _ncTags :: !(Maybe [Text])
, _ncPreemptible :: !(Maybe Bool)
}
deriving (Eq, Show, Data, Typeable, Generic)
nodeConfig
:: NodeConfig
nodeConfig =
NodeConfig'
{ _ncLocalSsdCount = Nothing
, _ncDiskSizeGb = Nothing
, _ncTaints = Nothing
, _ncOAuthScopes = Nothing
, _ncServiceAccount = Nothing
, _ncAccelerators = Nothing
, _ncImageType = Nothing
, _ncMachineType = Nothing
, _ncMetadata = Nothing
, _ncDiskType = Nothing
, _ncLabels = Nothing
, _ncMinCPUPlatform = Nothing
, _ncTags = Nothing
, _ncPreemptible = Nothing
}
ncLocalSsdCount :: Lens' NodeConfig (Maybe Int32)
ncLocalSsdCount
= lens _ncLocalSsdCount
(\ s a -> s{_ncLocalSsdCount = a})
. mapping _Coerce
ncDiskSizeGb :: Lens' NodeConfig (Maybe Int32)
ncDiskSizeGb
= lens _ncDiskSizeGb (\ s a -> s{_ncDiskSizeGb = a})
. mapping _Coerce
ncTaints :: Lens' NodeConfig [NodeTaint]
ncTaints
= lens _ncTaints (\ s a -> s{_ncTaints = a}) .
_Default
. _Coerce
ncOAuthScopes :: Lens' NodeConfig [Text]
ncOAuthScopes
= lens _ncOAuthScopes
(\ s a -> s{_ncOAuthScopes = a})
. _Default
. _Coerce
ncServiceAccount :: Lens' NodeConfig (Maybe Text)
ncServiceAccount
= lens _ncServiceAccount
(\ s a -> s{_ncServiceAccount = a})
ncAccelerators :: Lens' NodeConfig [AcceleratorConfig]
ncAccelerators
= lens _ncAccelerators
(\ s a -> s{_ncAccelerators = a})
. _Default
. _Coerce
ncImageType :: Lens' NodeConfig (Maybe Text)
ncImageType
= lens _ncImageType (\ s a -> s{_ncImageType = a})
ncMachineType :: Lens' NodeConfig (Maybe Text)
ncMachineType
= lens _ncMachineType
(\ s a -> s{_ncMachineType = a})
ncMetadata :: Lens' NodeConfig (Maybe NodeConfigMetadata)
ncMetadata
= lens _ncMetadata (\ s a -> s{_ncMetadata = a})
ncDiskType :: Lens' NodeConfig (Maybe Text)
ncDiskType
= lens _ncDiskType (\ s a -> s{_ncDiskType = a})
ncLabels :: Lens' NodeConfig (Maybe NodeConfigLabels)
ncLabels = lens _ncLabels (\ s a -> s{_ncLabels = a})
ncMinCPUPlatform :: Lens' NodeConfig (Maybe Text)
ncMinCPUPlatform
= lens _ncMinCPUPlatform
(\ s a -> s{_ncMinCPUPlatform = a})
ncTags :: Lens' NodeConfig [Text]
ncTags
= lens _ncTags (\ s a -> s{_ncTags = a}) . _Default .
_Coerce
ncPreemptible :: Lens' NodeConfig (Maybe Bool)
ncPreemptible
= lens _ncPreemptible
(\ s a -> s{_ncPreemptible = a})
instance FromJSON NodeConfig where
parseJSON
= withObject "NodeConfig"
(\ o ->
NodeConfig' <$>
(o .:? "localSsdCount") <*> (o .:? "diskSizeGb") <*>
(o .:? "taints" .!= mempty)
<*> (o .:? "oauthScopes" .!= mempty)
<*> (o .:? "serviceAccount")
<*> (o .:? "accelerators" .!= mempty)
<*> (o .:? "imageType")
<*> (o .:? "machineType")
<*> (o .:? "metadata")
<*> (o .:? "diskType")
<*> (o .:? "labels")
<*> (o .:? "minCpuPlatform")
<*> (o .:? "tags" .!= mempty)
<*> (o .:? "preemptible"))
instance ToJSON NodeConfig where
toJSON NodeConfig'{..}
= object
(catMaybes
[("localSsdCount" .=) <$> _ncLocalSsdCount,
("diskSizeGb" .=) <$> _ncDiskSizeGb,
("taints" .=) <$> _ncTaints,
("oauthScopes" .=) <$> _ncOAuthScopes,
("serviceAccount" .=) <$> _ncServiceAccount,
("accelerators" .=) <$> _ncAccelerators,
("imageType" .=) <$> _ncImageType,
("machineType" .=) <$> _ncMachineType,
("metadata" .=) <$> _ncMetadata,
("diskType" .=) <$> _ncDiskType,
("labels" .=) <$> _ncLabels,
("minCpuPlatform" .=) <$> _ncMinCPUPlatform,
("tags" .=) <$> _ncTags,
("preemptible" .=) <$> _ncPreemptible])
newtype HTTPLoadBalancing =
HTTPLoadBalancing'
{ _httplbDisabled :: Maybe Bool
}
deriving (Eq, Show, Data, Typeable, Generic)
hTTPLoadBalancing
:: HTTPLoadBalancing
hTTPLoadBalancing = HTTPLoadBalancing' {_httplbDisabled = Nothing}
httplbDisabled :: Lens' HTTPLoadBalancing (Maybe Bool)
httplbDisabled
= lens _httplbDisabled
(\ s a -> s{_httplbDisabled = a})
instance FromJSON HTTPLoadBalancing where
parseJSON
= withObject "HTTPLoadBalancing"
(\ o -> HTTPLoadBalancing' <$> (o .:? "disabled"))
instance ToJSON HTTPLoadBalancing where
toJSON HTTPLoadBalancing'{..}
= object
(catMaybes [("disabled" .=) <$> _httplbDisabled])
data Operation =
Operation'
{ _oNodepoolConditions :: !(Maybe [StatusCondition])
, _oStatus :: !(Maybe OperationStatus)
, _oLocation :: !(Maybe Text)
, _oStartTime :: !(Maybe Text)
, _oZone :: !(Maybe Text)
, _oSelfLink :: !(Maybe Text)
, _oName :: !(Maybe Text)
, _oStatusMessage :: !(Maybe Text)
, _oEndTime :: !(Maybe Text)
, _oClusterConditions :: !(Maybe [StatusCondition])
, _oOperationType :: !(Maybe OperationOperationType)
, _oTargetLink :: !(Maybe Text)
, _oDetail :: !(Maybe Text)
}
deriving (Eq, Show, Data, Typeable, Generic)
operation
:: Operation
operation =
Operation'
{ _oNodepoolConditions = Nothing
, _oStatus = Nothing
, _oLocation = Nothing
, _oStartTime = Nothing
, _oZone = Nothing
, _oSelfLink = Nothing
, _oName = Nothing
, _oStatusMessage = Nothing
, _oEndTime = Nothing
, _oClusterConditions = Nothing
, _oOperationType = Nothing
, _oTargetLink = Nothing
, _oDetail = Nothing
}
oNodepoolConditions :: Lens' Operation [StatusCondition]
oNodepoolConditions
= lens _oNodepoolConditions
(\ s a -> s{_oNodepoolConditions = a})
. _Default
. _Coerce
oStatus :: Lens' Operation (Maybe OperationStatus)
oStatus = lens _oStatus (\ s a -> s{_oStatus = a})
oLocation :: Lens' Operation (Maybe Text)
oLocation
= lens _oLocation (\ s a -> s{_oLocation = a})
oStartTime :: Lens' Operation (Maybe Text)
oStartTime
= lens _oStartTime (\ s a -> s{_oStartTime = a})
oZone :: Lens' Operation (Maybe Text)
oZone = lens _oZone (\ s a -> s{_oZone = a})
oSelfLink :: Lens' Operation (Maybe Text)
oSelfLink
= lens _oSelfLink (\ s a -> s{_oSelfLink = a})
oName :: Lens' Operation (Maybe Text)
oName = lens _oName (\ s a -> s{_oName = a})
oStatusMessage :: Lens' Operation (Maybe Text)
oStatusMessage
= lens _oStatusMessage
(\ s a -> s{_oStatusMessage = a})
oEndTime :: Lens' Operation (Maybe Text)
oEndTime = lens _oEndTime (\ s a -> s{_oEndTime = a})
oClusterConditions :: Lens' Operation [StatusCondition]
oClusterConditions
= lens _oClusterConditions
(\ s a -> s{_oClusterConditions = a})
. _Default
. _Coerce
oOperationType :: Lens' Operation (Maybe OperationOperationType)
oOperationType
= lens _oOperationType
(\ s a -> s{_oOperationType = a})
oTargetLink :: Lens' Operation (Maybe Text)
oTargetLink
= lens _oTargetLink (\ s a -> s{_oTargetLink = a})
oDetail :: Lens' Operation (Maybe Text)
oDetail = lens _oDetail (\ s a -> s{_oDetail = a})
instance FromJSON Operation where
parseJSON
= withObject "Operation"
(\ o ->
Operation' <$>
(o .:? "nodepoolConditions" .!= mempty) <*>
(o .:? "status")
<*> (o .:? "location")
<*> (o .:? "startTime")
<*> (o .:? "zone")
<*> (o .:? "selfLink")
<*> (o .:? "name")
<*> (o .:? "statusMessage")
<*> (o .:? "endTime")
<*> (o .:? "clusterConditions" .!= mempty)
<*> (o .:? "operationType")
<*> (o .:? "targetLink")
<*> (o .:? "detail"))
instance ToJSON Operation where
toJSON Operation'{..}
= object
(catMaybes
[("nodepoolConditions" .=) <$> _oNodepoolConditions,
("status" .=) <$> _oStatus,
("location" .=) <$> _oLocation,
("startTime" .=) <$> _oStartTime,
("zone" .=) <$> _oZone,
("selfLink" .=) <$> _oSelfLink,
("name" .=) <$> _oName,
("statusMessage" .=) <$> _oStatusMessage,
("endTime" .=) <$> _oEndTime,
("clusterConditions" .=) <$> _oClusterConditions,
("operationType" .=) <$> _oOperationType,
("targetLink" .=) <$> _oTargetLink,
("detail" .=) <$> _oDetail])
newtype ClusterResourceLabels =
ClusterResourceLabels'
{ _crlAddtional :: HashMap Text Text
}
deriving (Eq, Show, Data, Typeable, Generic)
clusterResourceLabels
:: HashMap Text Text
-> ClusterResourceLabels
clusterResourceLabels pCrlAddtional_ =
ClusterResourceLabels' {_crlAddtional = _Coerce # pCrlAddtional_}
crlAddtional :: Lens' ClusterResourceLabels (HashMap Text Text)
crlAddtional
= lens _crlAddtional (\ s a -> s{_crlAddtional = a})
. _Coerce
instance FromJSON ClusterResourceLabels where
parseJSON
= withObject "ClusterResourceLabels"
(\ o ->
ClusterResourceLabels' <$> (parseJSONObject o))
instance ToJSON ClusterResourceLabels where
toJSON = toJSON . _crlAddtional
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
data SetNodePoolAutoscalingRequest =
SetNodePoolAutoscalingRequest'
{ _snparAutoscaling :: !(Maybe NodePoolAutoscaling)
, _snparZone :: !(Maybe Text)
, _snparNodePoolId :: !(Maybe Text)
, _snparName :: !(Maybe Text)
, _snparClusterId :: !(Maybe Text)
, _snparProjectId :: !(Maybe Text)
}
deriving (Eq, Show, Data, Typeable, Generic)
setNodePoolAutoscalingRequest
:: SetNodePoolAutoscalingRequest
setNodePoolAutoscalingRequest =
SetNodePoolAutoscalingRequest'
{ _snparAutoscaling = Nothing
, _snparZone = Nothing
, _snparNodePoolId = Nothing
, _snparName = Nothing
, _snparClusterId = Nothing
, _snparProjectId = Nothing
}
snparAutoscaling :: Lens' SetNodePoolAutoscalingRequest (Maybe NodePoolAutoscaling)
snparAutoscaling
= lens _snparAutoscaling
(\ s a -> s{_snparAutoscaling = a})
snparZone :: Lens' SetNodePoolAutoscalingRequest (Maybe Text)
snparZone
= lens _snparZone (\ s a -> s{_snparZone = a})
snparNodePoolId :: Lens' SetNodePoolAutoscalingRequest (Maybe Text)
snparNodePoolId
= lens _snparNodePoolId
(\ s a -> s{_snparNodePoolId = a})
snparName :: Lens' SetNodePoolAutoscalingRequest (Maybe Text)
snparName
= lens _snparName (\ s a -> s{_snparName = a})
snparClusterId :: Lens' SetNodePoolAutoscalingRequest (Maybe Text)
snparClusterId
= lens _snparClusterId
(\ s a -> s{_snparClusterId = a})
snparProjectId :: Lens' SetNodePoolAutoscalingRequest (Maybe Text)
snparProjectId
= lens _snparProjectId
(\ s a -> s{_snparProjectId = a})
instance FromJSON SetNodePoolAutoscalingRequest where
parseJSON
= withObject "SetNodePoolAutoscalingRequest"
(\ o ->
SetNodePoolAutoscalingRequest' <$>
(o .:? "autoscaling") <*> (o .:? "zone") <*>
(o .:? "nodePoolId")
<*> (o .:? "name")
<*> (o .:? "clusterId")
<*> (o .:? "projectId"))
instance ToJSON SetNodePoolAutoscalingRequest where
toJSON SetNodePoolAutoscalingRequest'{..}
= object
(catMaybes
[("autoscaling" .=) <$> _snparAutoscaling,
("zone" .=) <$> _snparZone,
("nodePoolId" .=) <$> _snparNodePoolId,
("name" .=) <$> _snparName,
("clusterId" .=) <$> _snparClusterId,
("projectId" .=) <$> _snparProjectId])
data CompleteIPRotationRequest =
CompleteIPRotationRequest'
{ _cirrZone :: !(Maybe Text)
, _cirrName :: !(Maybe Text)
, _cirrClusterId :: !(Maybe Text)
, _cirrProjectId :: !(Maybe Text)
}
deriving (Eq, Show, Data, Typeable, Generic)
completeIPRotationRequest
:: CompleteIPRotationRequest
completeIPRotationRequest =
CompleteIPRotationRequest'
{ _cirrZone = Nothing
, _cirrName = Nothing
, _cirrClusterId = Nothing
, _cirrProjectId = Nothing
}
cirrZone :: Lens' CompleteIPRotationRequest (Maybe Text)
cirrZone = lens _cirrZone (\ s a -> s{_cirrZone = a})
cirrName :: Lens' CompleteIPRotationRequest (Maybe Text)
cirrName = lens _cirrName (\ s a -> s{_cirrName = a})
cirrClusterId :: Lens' CompleteIPRotationRequest (Maybe Text)
cirrClusterId
= lens _cirrClusterId
(\ s a -> s{_cirrClusterId = a})
cirrProjectId :: Lens' CompleteIPRotationRequest (Maybe Text)
cirrProjectId
= lens _cirrProjectId
(\ s a -> s{_cirrProjectId = a})
instance FromJSON CompleteIPRotationRequest where
parseJSON
= withObject "CompleteIPRotationRequest"
(\ o ->
CompleteIPRotationRequest' <$>
(o .:? "zone") <*> (o .:? "name") <*>
(o .:? "clusterId")
<*> (o .:? "projectId"))
instance ToJSON CompleteIPRotationRequest where
toJSON CompleteIPRotationRequest'{..}
= object
(catMaybes
[("zone" .=) <$> _cirrZone,
("name" .=) <$> _cirrName,
("clusterId" .=) <$> _cirrClusterId,
("projectId" .=) <$> _cirrProjectId])
data UsableSubnetworkSecondaryRange =
UsableSubnetworkSecondaryRange'
{ _ussrStatus :: !(Maybe UsableSubnetworkSecondaryRangeStatus)
, _ussrRangeName :: !(Maybe Text)
, _ussrIPCIdRRange :: !(Maybe Text)
}
deriving (Eq, Show, Data, Typeable, Generic)
usableSubnetworkSecondaryRange
:: UsableSubnetworkSecondaryRange
usableSubnetworkSecondaryRange =
UsableSubnetworkSecondaryRange'
{ _ussrStatus = Nothing
, _ussrRangeName = Nothing
, _ussrIPCIdRRange = Nothing
}
ussrStatus :: Lens' UsableSubnetworkSecondaryRange (Maybe UsableSubnetworkSecondaryRangeStatus)
ussrStatus
= lens _ussrStatus (\ s a -> s{_ussrStatus = a})
ussrRangeName :: Lens' UsableSubnetworkSecondaryRange (Maybe Text)
ussrRangeName
= lens _ussrRangeName
(\ s a -> s{_ussrRangeName = a})
ussrIPCIdRRange :: Lens' UsableSubnetworkSecondaryRange (Maybe Text)
ussrIPCIdRRange
= lens _ussrIPCIdRRange
(\ s a -> s{_ussrIPCIdRRange = a})
instance FromJSON UsableSubnetworkSecondaryRange
where
parseJSON
= withObject "UsableSubnetworkSecondaryRange"
(\ o ->
UsableSubnetworkSecondaryRange' <$>
(o .:? "status") <*> (o .:? "rangeName") <*>
(o .:? "ipCidrRange"))
instance ToJSON UsableSubnetworkSecondaryRange where
toJSON UsableSubnetworkSecondaryRange'{..}
= object
(catMaybes
[("status" .=) <$> _ussrStatus,
("rangeName" .=) <$> _ussrRangeName,
("ipCidrRange" .=) <$> _ussrIPCIdRRange])
data NodeManagement =
NodeManagement'
{ _nmAutoUpgrade :: !(Maybe Bool)
, _nmAutoRepair :: !(Maybe Bool)
, _nmUpgradeOptions :: !(Maybe AutoUpgradeOptions)
}
deriving (Eq, Show, Data, Typeable, Generic)
nodeManagement
:: NodeManagement
nodeManagement =
NodeManagement'
{ _nmAutoUpgrade = Nothing
, _nmAutoRepair = Nothing
, _nmUpgradeOptions = Nothing
}
nmAutoUpgrade :: Lens' NodeManagement (Maybe Bool)
nmAutoUpgrade
= lens _nmAutoUpgrade
(\ s a -> s{_nmAutoUpgrade = a})
nmAutoRepair :: Lens' NodeManagement (Maybe Bool)
nmAutoRepair
= lens _nmAutoRepair (\ s a -> s{_nmAutoRepair = a})
nmUpgradeOptions :: Lens' NodeManagement (Maybe AutoUpgradeOptions)
nmUpgradeOptions
= lens _nmUpgradeOptions
(\ s a -> s{_nmUpgradeOptions = a})
instance FromJSON NodeManagement where
parseJSON
= withObject "NodeManagement"
(\ o ->
NodeManagement' <$>
(o .:? "autoUpgrade") <*> (o .:? "autoRepair") <*>
(o .:? "upgradeOptions"))
instance ToJSON NodeManagement where
toJSON NodeManagement'{..}
= object
(catMaybes
[("autoUpgrade" .=) <$> _nmAutoUpgrade,
("autoRepair" .=) <$> _nmAutoRepair,
("upgradeOptions" .=) <$> _nmUpgradeOptions])
data NodeTaint =
NodeTaint'
{ _ntEffect :: !(Maybe NodeTaintEffect)
, _ntValue :: !(Maybe Text)
, _ntKey :: !(Maybe Text)
}
deriving (Eq, Show, Data, Typeable, Generic)
nodeTaint
:: NodeTaint
nodeTaint =
NodeTaint' {_ntEffect = Nothing, _ntValue = Nothing, _ntKey = Nothing}
ntEffect :: Lens' NodeTaint (Maybe NodeTaintEffect)
ntEffect = lens _ntEffect (\ s a -> s{_ntEffect = a})
ntValue :: Lens' NodeTaint (Maybe Text)
ntValue = lens _ntValue (\ s a -> s{_ntValue = a})
ntKey :: Lens' NodeTaint (Maybe Text)
ntKey = lens _ntKey (\ s a -> s{_ntKey = a})
instance FromJSON NodeTaint where
parseJSON
= withObject "NodeTaint"
(\ o ->
NodeTaint' <$>
(o .:? "effect") <*> (o .:? "value") <*>
(o .:? "key"))
instance ToJSON NodeTaint where
toJSON NodeTaint'{..}
= object
(catMaybes
[("effect" .=) <$> _ntEffect,
("value" .=) <$> _ntValue, ("key" .=) <$> _ntKey])
data NodePoolAutoscaling =
NodePoolAutoscaling'
{ _npaMaxNodeCount :: !(Maybe (Textual Int32))
, _npaEnabled :: !(Maybe Bool)
, _npaMinNodeCount :: !(Maybe (Textual Int32))
}
deriving (Eq, Show, Data, Typeable, Generic)
nodePoolAutoscaling
:: NodePoolAutoscaling
nodePoolAutoscaling =
NodePoolAutoscaling'
{ _npaMaxNodeCount = Nothing
, _npaEnabled = Nothing
, _npaMinNodeCount = Nothing
}
npaMaxNodeCount :: Lens' NodePoolAutoscaling (Maybe Int32)
npaMaxNodeCount
= lens _npaMaxNodeCount
(\ s a -> s{_npaMaxNodeCount = a})
. mapping _Coerce
npaEnabled :: Lens' NodePoolAutoscaling (Maybe Bool)
npaEnabled
= lens _npaEnabled (\ s a -> s{_npaEnabled = a})
npaMinNodeCount :: Lens' NodePoolAutoscaling (Maybe Int32)
npaMinNodeCount
= lens _npaMinNodeCount
(\ s a -> s{_npaMinNodeCount = a})
. mapping _Coerce
instance FromJSON NodePoolAutoscaling where
parseJSON
= withObject "NodePoolAutoscaling"
(\ o ->
NodePoolAutoscaling' <$>
(o .:? "maxNodeCount") <*> (o .:? "enabled") <*>
(o .:? "minNodeCount"))
instance ToJSON NodePoolAutoscaling where
toJSON NodePoolAutoscaling'{..}
= object
(catMaybes
[("maxNodeCount" .=) <$> _npaMaxNodeCount,
("enabled" .=) <$> _npaEnabled,
("minNodeCount" .=) <$> _npaMinNodeCount])
data SetMaintenancePolicyRequest =
SetMaintenancePolicyRequest'
{ _smprZone :: !(Maybe Text)
, _smprName :: !(Maybe Text)
, _smprClusterId :: !(Maybe Text)
, _smprMaintenancePolicy :: !(Maybe MaintenancePolicy)
, _smprProjectId :: !(Maybe Text)
}
deriving (Eq, Show, Data, Typeable, Generic)
setMaintenancePolicyRequest
:: SetMaintenancePolicyRequest
setMaintenancePolicyRequest =
SetMaintenancePolicyRequest'
{ _smprZone = Nothing
, _smprName = Nothing
, _smprClusterId = Nothing
, _smprMaintenancePolicy = Nothing
, _smprProjectId = Nothing
}
smprZone :: Lens' SetMaintenancePolicyRequest (Maybe Text)
smprZone = lens _smprZone (\ s a -> s{_smprZone = a})
smprName :: Lens' SetMaintenancePolicyRequest (Maybe Text)
smprName = lens _smprName (\ s a -> s{_smprName = a})
smprClusterId :: Lens' SetMaintenancePolicyRequest (Maybe Text)
smprClusterId
= lens _smprClusterId
(\ s a -> s{_smprClusterId = a})
smprMaintenancePolicy :: Lens' SetMaintenancePolicyRequest (Maybe MaintenancePolicy)
smprMaintenancePolicy
= lens _smprMaintenancePolicy
(\ s a -> s{_smprMaintenancePolicy = a})
smprProjectId :: Lens' SetMaintenancePolicyRequest (Maybe Text)
smprProjectId
= lens _smprProjectId
(\ s a -> s{_smprProjectId = a})
instance FromJSON SetMaintenancePolicyRequest where
parseJSON
= withObject "SetMaintenancePolicyRequest"
(\ o ->
SetMaintenancePolicyRequest' <$>
(o .:? "zone") <*> (o .:? "name") <*>
(o .:? "clusterId")
<*> (o .:? "maintenancePolicy")
<*> (o .:? "projectId"))
instance ToJSON SetMaintenancePolicyRequest where
toJSON SetMaintenancePolicyRequest'{..}
= object
(catMaybes
[("zone" .=) <$> _smprZone,
("name" .=) <$> _smprName,
("clusterId" .=) <$> _smprClusterId,
("maintenancePolicy" .=) <$> _smprMaintenancePolicy,
("projectId" .=) <$> _smprProjectId])
data UsableSubnetwork =
UsableSubnetwork'
{ _usNetwork :: !(Maybe Text)
, _usStatusMessage :: !(Maybe Text)
, _usSecondaryIPRanges :: !(Maybe [UsableSubnetworkSecondaryRange])
, _usIPCIdRRange :: !(Maybe Text)
, _usSubnetwork :: !(Maybe Text)
}
deriving (Eq, Show, Data, Typeable, Generic)
usableSubnetwork
:: UsableSubnetwork
usableSubnetwork =
UsableSubnetwork'
{ _usNetwork = Nothing
, _usStatusMessage = Nothing
, _usSecondaryIPRanges = Nothing
, _usIPCIdRRange = Nothing
, _usSubnetwork = Nothing
}
usNetwork :: Lens' UsableSubnetwork (Maybe Text)
usNetwork
= lens _usNetwork (\ s a -> s{_usNetwork = a})
usStatusMessage :: Lens' UsableSubnetwork (Maybe Text)
usStatusMessage
= lens _usStatusMessage
(\ s a -> s{_usStatusMessage = a})
usSecondaryIPRanges :: Lens' UsableSubnetwork [UsableSubnetworkSecondaryRange]
usSecondaryIPRanges
= lens _usSecondaryIPRanges
(\ s a -> s{_usSecondaryIPRanges = a})
. _Default
. _Coerce
usIPCIdRRange :: Lens' UsableSubnetwork (Maybe Text)
usIPCIdRRange
= lens _usIPCIdRRange
(\ s a -> s{_usIPCIdRRange = a})
usSubnetwork :: Lens' UsableSubnetwork (Maybe Text)
usSubnetwork
= lens _usSubnetwork (\ s a -> s{_usSubnetwork = a})
instance FromJSON UsableSubnetwork where
parseJSON
= withObject "UsableSubnetwork"
(\ o ->
UsableSubnetwork' <$>
(o .:? "network") <*> (o .:? "statusMessage") <*>
(o .:? "secondaryIpRanges" .!= mempty)
<*> (o .:? "ipCidrRange")
<*> (o .:? "subnetwork"))
instance ToJSON UsableSubnetwork where
toJSON UsableSubnetwork'{..}
= object
(catMaybes
[("network" .=) <$> _usNetwork,
("statusMessage" .=) <$> _usStatusMessage,
("secondaryIpRanges" .=) <$> _usSecondaryIPRanges,
("ipCidrRange" .=) <$> _usIPCIdRRange,
("subnetwork" .=) <$> _usSubnetwork])
newtype KubernetesDashboard =
KubernetesDashboard'
{ _kdDisabled :: Maybe Bool
}
deriving (Eq, Show, Data, Typeable, Generic)
kubernetesDashboard
:: KubernetesDashboard
kubernetesDashboard = KubernetesDashboard' {_kdDisabled = Nothing}
kdDisabled :: Lens' KubernetesDashboard (Maybe Bool)
kdDisabled
= lens _kdDisabled (\ s a -> s{_kdDisabled = a})
instance FromJSON KubernetesDashboard where
parseJSON
= withObject "KubernetesDashboard"
(\ o -> KubernetesDashboard' <$> (o .:? "disabled"))
instance ToJSON KubernetesDashboard where
toJSON KubernetesDashboard'{..}
= object
(catMaybes [("disabled" .=) <$> _kdDisabled])
newtype ClientCertificateConfig =
ClientCertificateConfig'
{ _cccIssueClientCertificate :: Maybe Bool
}
deriving (Eq, Show, Data, Typeable, Generic)
clientCertificateConfig
:: ClientCertificateConfig
clientCertificateConfig =
ClientCertificateConfig' {_cccIssueClientCertificate = Nothing}
cccIssueClientCertificate :: Lens' ClientCertificateConfig (Maybe Bool)
cccIssueClientCertificate
= lens _cccIssueClientCertificate
(\ s a -> s{_cccIssueClientCertificate = a})
instance FromJSON ClientCertificateConfig where
parseJSON
= withObject "ClientCertificateConfig"
(\ o ->
ClientCertificateConfig' <$>
(o .:? "issueClientCertificate"))
instance ToJSON ClientCertificateConfig where
toJSON ClientCertificateConfig'{..}
= object
(catMaybes
[("issueClientCertificate" .=) <$>
_cccIssueClientCertificate])
data SetLabelsRequest =
SetLabelsRequest'
{ _slrResourceLabels :: !(Maybe SetLabelsRequestResourceLabels)
, _slrZone :: !(Maybe Text)
, _slrName :: !(Maybe Text)
, _slrClusterId :: !(Maybe Text)
, _slrProjectId :: !(Maybe Text)
, _slrLabelFingerprint :: !(Maybe Text)
}
deriving (Eq, Show, Data, Typeable, Generic)
setLabelsRequest
:: SetLabelsRequest
setLabelsRequest =
SetLabelsRequest'
{ _slrResourceLabels = Nothing
, _slrZone = Nothing
, _slrName = Nothing
, _slrClusterId = Nothing
, _slrProjectId = Nothing
, _slrLabelFingerprint = Nothing
}
slrResourceLabels :: Lens' SetLabelsRequest (Maybe SetLabelsRequestResourceLabels)
slrResourceLabels
= lens _slrResourceLabels
(\ s a -> s{_slrResourceLabels = a})
slrZone :: Lens' SetLabelsRequest (Maybe Text)
slrZone = lens _slrZone (\ s a -> s{_slrZone = a})
slrName :: Lens' SetLabelsRequest (Maybe Text)
slrName = lens _slrName (\ s a -> s{_slrName = a})
slrClusterId :: Lens' SetLabelsRequest (Maybe Text)
slrClusterId
= lens _slrClusterId (\ s a -> s{_slrClusterId = a})
slrProjectId :: Lens' SetLabelsRequest (Maybe Text)
slrProjectId
= lens _slrProjectId (\ s a -> s{_slrProjectId = a})
slrLabelFingerprint :: Lens' SetLabelsRequest (Maybe Text)
slrLabelFingerprint
= lens _slrLabelFingerprint
(\ s a -> s{_slrLabelFingerprint = a})
instance FromJSON SetLabelsRequest where
parseJSON
= withObject "SetLabelsRequest"
(\ o ->
SetLabelsRequest' <$>
(o .:? "resourceLabels") <*> (o .:? "zone") <*>
(o .:? "name")
<*> (o .:? "clusterId")
<*> (o .:? "projectId")
<*> (o .:? "labelFingerprint"))
instance ToJSON SetLabelsRequest where
toJSON SetLabelsRequest'{..}
= object
(catMaybes
[("resourceLabels" .=) <$> _slrResourceLabels,
("zone" .=) <$> _slrZone, ("name" .=) <$> _slrName,
("clusterId" .=) <$> _slrClusterId,
("projectId" .=) <$> _slrProjectId,
("labelFingerprint" .=) <$> _slrLabelFingerprint])
data GetOpenIdConfigResponse =
GetOpenIdConfigResponse'
{ _goicrIdTokenSigningAlgValuesSupported :: !(Maybe [Text])
, _goicrResponseTypesSupported :: !(Maybe [Text])
, _goicrJWKsURI :: !(Maybe Text)
, _goicrGrantTypes :: !(Maybe [Text])
, _goicrClaimsSupported :: !(Maybe [Text])
, _goicrIssuer :: !(Maybe Text)
, _goicrSubjectTypesSupported :: !(Maybe [Text])
}
deriving (Eq, Show, Data, Typeable, Generic)
getOpenIdConfigResponse
:: GetOpenIdConfigResponse
getOpenIdConfigResponse =
GetOpenIdConfigResponse'
{ _goicrIdTokenSigningAlgValuesSupported = Nothing
, _goicrResponseTypesSupported = Nothing
, _goicrJWKsURI = Nothing
, _goicrGrantTypes = Nothing
, _goicrClaimsSupported = Nothing
, _goicrIssuer = Nothing
, _goicrSubjectTypesSupported = Nothing
}
goicrIdTokenSigningAlgValuesSupported :: Lens' GetOpenIdConfigResponse [Text]
goicrIdTokenSigningAlgValuesSupported
= lens _goicrIdTokenSigningAlgValuesSupported
(\ s a ->
s{_goicrIdTokenSigningAlgValuesSupported = a})
. _Default
. _Coerce
goicrResponseTypesSupported :: Lens' GetOpenIdConfigResponse [Text]
goicrResponseTypesSupported
= lens _goicrResponseTypesSupported
(\ s a -> s{_goicrResponseTypesSupported = a})
. _Default
. _Coerce
goicrJWKsURI :: Lens' GetOpenIdConfigResponse (Maybe Text)
goicrJWKsURI
= lens _goicrJWKsURI (\ s a -> s{_goicrJWKsURI = a})
goicrGrantTypes :: Lens' GetOpenIdConfigResponse [Text]
goicrGrantTypes
= lens _goicrGrantTypes
(\ s a -> s{_goicrGrantTypes = a})
. _Default
. _Coerce
goicrClaimsSupported :: Lens' GetOpenIdConfigResponse [Text]
goicrClaimsSupported
= lens _goicrClaimsSupported
(\ s a -> s{_goicrClaimsSupported = a})
. _Default
. _Coerce
goicrIssuer :: Lens' GetOpenIdConfigResponse (Maybe Text)
goicrIssuer
= lens _goicrIssuer (\ s a -> s{_goicrIssuer = a})
goicrSubjectTypesSupported :: Lens' GetOpenIdConfigResponse [Text]
goicrSubjectTypesSupported
= lens _goicrSubjectTypesSupported
(\ s a -> s{_goicrSubjectTypesSupported = a})
. _Default
. _Coerce
instance FromJSON GetOpenIdConfigResponse where
parseJSON
= withObject "GetOpenIdConfigResponse"
(\ o ->
GetOpenIdConfigResponse' <$>
(o .:? "id_token_signing_alg_values_supported" .!=
mempty)
<*> (o .:? "response_types_supported" .!= mempty)
<*> (o .:? "jwks_uri")
<*> (o .:? "grant_types" .!= mempty)
<*> (o .:? "claims_supported" .!= mempty)
<*> (o .:? "issuer")
<*> (o .:? "subject_types_supported" .!= mempty))
instance ToJSON GetOpenIdConfigResponse where
toJSON GetOpenIdConfigResponse'{..}
= object
(catMaybes
[("id_token_signing_alg_values_supported" .=) <$>
_goicrIdTokenSigningAlgValuesSupported,
("response_types_supported" .=) <$>
_goicrResponseTypesSupported,
("jwks_uri" .=) <$> _goicrJWKsURI,
("grant_types" .=) <$> _goicrGrantTypes,
("claims_supported" .=) <$> _goicrClaimsSupported,
("issuer" .=) <$> _goicrIssuer,
("subject_types_supported" .=) <$>
_goicrSubjectTypesSupported])
data JWK =
JWK'
{ _jCrv :: !(Maybe Text)
, _jAlg :: !(Maybe Text)
, _jUse :: !(Maybe Text)
, _jKid :: !(Maybe Text)
, _jN :: !(Maybe Text)
, _jE :: !(Maybe Text)
, _jX :: !(Maybe Text)
, _jKty :: !(Maybe Text)
, _jY :: !(Maybe Text)
}
deriving (Eq, Show, Data, Typeable, Generic)
jwk
:: JWK
jwk =
JWK'
{ _jCrv = Nothing
, _jAlg = Nothing
, _jUse = Nothing
, _jKid = Nothing
, _jN = Nothing
, _jE = Nothing
, _jX = Nothing
, _jKty = Nothing
, _jY = Nothing
}
jCrv :: Lens' JWK (Maybe Text)
jCrv = lens _jCrv (\ s a -> s{_jCrv = a})
jAlg :: Lens' JWK (Maybe Text)
jAlg = lens _jAlg (\ s a -> s{_jAlg = a})
jUse :: Lens' JWK (Maybe Text)
jUse = lens _jUse (\ s a -> s{_jUse = a})
jKid :: Lens' JWK (Maybe Text)
jKid = lens _jKid (\ s a -> s{_jKid = a})
jN :: Lens' JWK (Maybe Text)
jN = lens _jN (\ s a -> s{_jN = a})
jE :: Lens' JWK (Maybe Text)
jE = lens _jE (\ s a -> s{_jE = a})
jX :: Lens' JWK (Maybe Text)
jX = lens _jX (\ s a -> s{_jX = a})
jKty :: Lens' JWK (Maybe Text)
jKty = lens _jKty (\ s a -> s{_jKty = a})
jY :: Lens' JWK (Maybe Text)
jY = lens _jY (\ s a -> s{_jY = a})
instance FromJSON JWK where
parseJSON
= withObject "JWK"
(\ o ->
JWK' <$>
(o .:? "crv") <*> (o .:? "alg") <*> (o .:? "use") <*>
(o .:? "kid")
<*> (o .:? "n")
<*> (o .:? "e")
<*> (o .:? "x")
<*> (o .:? "kty")
<*> (o .:? "y"))
instance ToJSON JWK where
toJSON JWK'{..}
= object
(catMaybes
[("crv" .=) <$> _jCrv, ("alg" .=) <$> _jAlg,
("use" .=) <$> _jUse, ("kid" .=) <$> _jKid,
("n" .=) <$> _jN, ("e" .=) <$> _jE, ("x" .=) <$> _jX,
("kty" .=) <$> _jKty, ("y" .=) <$> _jY])
newtype MaintenanceWindow =
MaintenanceWindow'
{ _mwDailyMaintenanceWindow :: Maybe DailyMaintenanceWindow
}
deriving (Eq, Show, Data, Typeable, Generic)
maintenanceWindow
:: MaintenanceWindow
maintenanceWindow = MaintenanceWindow' {_mwDailyMaintenanceWindow = Nothing}
mwDailyMaintenanceWindow :: Lens' MaintenanceWindow (Maybe DailyMaintenanceWindow)
mwDailyMaintenanceWindow
= lens _mwDailyMaintenanceWindow
(\ s a -> s{_mwDailyMaintenanceWindow = a})
instance FromJSON MaintenanceWindow where
parseJSON
= withObject "MaintenanceWindow"
(\ o ->
MaintenanceWindow' <$>
(o .:? "dailyMaintenanceWindow"))
instance ToJSON MaintenanceWindow where
toJSON MaintenanceWindow'{..}
= object
(catMaybes
[("dailyMaintenanceWindow" .=) <$>
_mwDailyMaintenanceWindow])
newtype MaxPodsConstraint =
MaxPodsConstraint'
{ _mpcMaxPodsPerNode :: Maybe (Textual Int64)
}
deriving (Eq, Show, Data, Typeable, Generic)
maxPodsConstraint
:: MaxPodsConstraint
maxPodsConstraint = MaxPodsConstraint' {_mpcMaxPodsPerNode = Nothing}
mpcMaxPodsPerNode :: Lens' MaxPodsConstraint (Maybe Int64)
mpcMaxPodsPerNode
= lens _mpcMaxPodsPerNode
(\ s a -> s{_mpcMaxPodsPerNode = a})
. mapping _Coerce
instance FromJSON MaxPodsConstraint where
parseJSON
= withObject "MaxPodsConstraint"
(\ o ->
MaxPodsConstraint' <$> (o .:? "maxPodsPerNode"))
instance ToJSON MaxPodsConstraint where
toJSON MaxPodsConstraint'{..}
= object
(catMaybes
[("maxPodsPerNode" .=) <$> _mpcMaxPodsPerNode])
data IPAllocationPolicy =
IPAllocationPolicy'
{ _iapServicesSecondaryRangeName :: !(Maybe Text)
, _iapTpuIPv4CIdRBlock :: !(Maybe Text)
, _iapNodeIPv4CIdR :: !(Maybe Text)
, _iapUseIPAliases :: !(Maybe Bool)
, _iapClusterIPv4CIdR :: !(Maybe Text)
, _iapSubnetworkName :: !(Maybe Text)
, _iapClusterSecondaryRangeName :: !(Maybe Text)
, _iapNodeIPv4CIdRBlock :: !(Maybe Text)
, _iapServicesIPv4CIdR :: !(Maybe Text)
, _iapClusterIPv4CIdRBlock :: !(Maybe Text)
, _iapServicesIPv4CIdRBlock :: !(Maybe Text)
, _iapCreateSubnetwork :: !(Maybe Bool)
}
deriving (Eq, Show, Data, Typeable, Generic)
ipAllocationPolicy
:: IPAllocationPolicy
ipAllocationPolicy =
IPAllocationPolicy'
{ _iapServicesSecondaryRangeName = Nothing
, _iapTpuIPv4CIdRBlock = Nothing
, _iapNodeIPv4CIdR = Nothing
, _iapUseIPAliases = Nothing
, _iapClusterIPv4CIdR = Nothing
, _iapSubnetworkName = Nothing
, _iapClusterSecondaryRangeName = Nothing
, _iapNodeIPv4CIdRBlock = Nothing
, _iapServicesIPv4CIdR = Nothing
, _iapClusterIPv4CIdRBlock = Nothing
, _iapServicesIPv4CIdRBlock = Nothing
, _iapCreateSubnetwork = Nothing
}
iapServicesSecondaryRangeName :: Lens' IPAllocationPolicy (Maybe Text)
iapServicesSecondaryRangeName
= lens _iapServicesSecondaryRangeName
(\ s a -> s{_iapServicesSecondaryRangeName = a})
iapTpuIPv4CIdRBlock :: Lens' IPAllocationPolicy (Maybe Text)
iapTpuIPv4CIdRBlock
= lens _iapTpuIPv4CIdRBlock
(\ s a -> s{_iapTpuIPv4CIdRBlock = a})
iapNodeIPv4CIdR :: Lens' IPAllocationPolicy (Maybe Text)
iapNodeIPv4CIdR
= lens _iapNodeIPv4CIdR
(\ s a -> s{_iapNodeIPv4CIdR = a})
iapUseIPAliases :: Lens' IPAllocationPolicy (Maybe Bool)
iapUseIPAliases
= lens _iapUseIPAliases
(\ s a -> s{_iapUseIPAliases = a})
iapClusterIPv4CIdR :: Lens' IPAllocationPolicy (Maybe Text)
iapClusterIPv4CIdR
= lens _iapClusterIPv4CIdR
(\ s a -> s{_iapClusterIPv4CIdR = a})
iapSubnetworkName :: Lens' IPAllocationPolicy (Maybe Text)
iapSubnetworkName
= lens _iapSubnetworkName
(\ s a -> s{_iapSubnetworkName = a})
iapClusterSecondaryRangeName :: Lens' IPAllocationPolicy (Maybe Text)
iapClusterSecondaryRangeName
= lens _iapClusterSecondaryRangeName
(\ s a -> s{_iapClusterSecondaryRangeName = a})
iapNodeIPv4CIdRBlock :: Lens' IPAllocationPolicy (Maybe Text)
iapNodeIPv4CIdRBlock
= lens _iapNodeIPv4CIdRBlock
(\ s a -> s{_iapNodeIPv4CIdRBlock = a})
iapServicesIPv4CIdR :: Lens' IPAllocationPolicy (Maybe Text)
iapServicesIPv4CIdR
= lens _iapServicesIPv4CIdR
(\ s a -> s{_iapServicesIPv4CIdR = a})
iapClusterIPv4CIdRBlock :: Lens' IPAllocationPolicy (Maybe Text)
iapClusterIPv4CIdRBlock
= lens _iapClusterIPv4CIdRBlock
(\ s a -> s{_iapClusterIPv4CIdRBlock = a})
iapServicesIPv4CIdRBlock :: Lens' IPAllocationPolicy (Maybe Text)
iapServicesIPv4CIdRBlock
= lens _iapServicesIPv4CIdRBlock
(\ s a -> s{_iapServicesIPv4CIdRBlock = a})
iapCreateSubnetwork :: Lens' IPAllocationPolicy (Maybe Bool)
iapCreateSubnetwork
= lens _iapCreateSubnetwork
(\ s a -> s{_iapCreateSubnetwork = a})
instance FromJSON IPAllocationPolicy where
parseJSON
= withObject "IPAllocationPolicy"
(\ o ->
IPAllocationPolicy' <$>
(o .:? "servicesSecondaryRangeName") <*>
(o .:? "tpuIpv4CidrBlock")
<*> (o .:? "nodeIpv4Cidr")
<*> (o .:? "useIpAliases")
<*> (o .:? "clusterIpv4Cidr")
<*> (o .:? "subnetworkName")
<*> (o .:? "clusterSecondaryRangeName")
<*> (o .:? "nodeIpv4CidrBlock")
<*> (o .:? "servicesIpv4Cidr")
<*> (o .:? "clusterIpv4CidrBlock")
<*> (o .:? "servicesIpv4CidrBlock")
<*> (o .:? "createSubnetwork"))
instance ToJSON IPAllocationPolicy where
toJSON IPAllocationPolicy'{..}
= object
(catMaybes
[("servicesSecondaryRangeName" .=) <$>
_iapServicesSecondaryRangeName,
("tpuIpv4CidrBlock" .=) <$> _iapTpuIPv4CIdRBlock,
("nodeIpv4Cidr" .=) <$> _iapNodeIPv4CIdR,
("useIpAliases" .=) <$> _iapUseIPAliases,
("clusterIpv4Cidr" .=) <$> _iapClusterIPv4CIdR,
("subnetworkName" .=) <$> _iapSubnetworkName,
("clusterSecondaryRangeName" .=) <$>
_iapClusterSecondaryRangeName,
("nodeIpv4CidrBlock" .=) <$> _iapNodeIPv4CIdRBlock,
("servicesIpv4Cidr" .=) <$> _iapServicesIPv4CIdR,
("clusterIpv4CidrBlock" .=) <$>
_iapClusterIPv4CIdRBlock,
("servicesIpv4CidrBlock" .=) <$>
_iapServicesIPv4CIdRBlock,
("createSubnetwork" .=) <$> _iapCreateSubnetwork])
data AddonsConfig =
AddonsConfig'
{ _acNetworkPolicyConfig :: !(Maybe NetworkPolicyConfig)
, _acHorizontalPodAutoscaling :: !(Maybe HorizontalPodAutoscaling)
, _acHTTPLoadBalancing :: !(Maybe HTTPLoadBalancing)
, _acKubernetesDashboard :: !(Maybe KubernetesDashboard)
}
deriving (Eq, Show, Data, Typeable, Generic)
addonsConfig
:: AddonsConfig
addonsConfig =
AddonsConfig'
{ _acNetworkPolicyConfig = Nothing
, _acHorizontalPodAutoscaling = Nothing
, _acHTTPLoadBalancing = Nothing
, _acKubernetesDashboard = Nothing
}
acNetworkPolicyConfig :: Lens' AddonsConfig (Maybe NetworkPolicyConfig)
acNetworkPolicyConfig
= lens _acNetworkPolicyConfig
(\ s a -> s{_acNetworkPolicyConfig = a})
acHorizontalPodAutoscaling :: Lens' AddonsConfig (Maybe HorizontalPodAutoscaling)
acHorizontalPodAutoscaling
= lens _acHorizontalPodAutoscaling
(\ s a -> s{_acHorizontalPodAutoscaling = a})
acHTTPLoadBalancing :: Lens' AddonsConfig (Maybe HTTPLoadBalancing)
acHTTPLoadBalancing
= lens _acHTTPLoadBalancing
(\ s a -> s{_acHTTPLoadBalancing = a})
acKubernetesDashboard :: Lens' AddonsConfig (Maybe KubernetesDashboard)
acKubernetesDashboard
= lens _acKubernetesDashboard
(\ s a -> s{_acKubernetesDashboard = a})
instance FromJSON AddonsConfig where
parseJSON
= withObject "AddonsConfig"
(\ o ->
AddonsConfig' <$>
(o .:? "networkPolicyConfig") <*>
(o .:? "horizontalPodAutoscaling")
<*> (o .:? "httpLoadBalancing")
<*> (o .:? "kubernetesDashboard"))
instance ToJSON AddonsConfig where
toJSON AddonsConfig'{..}
= object
(catMaybes
[("networkPolicyConfig" .=) <$>
_acNetworkPolicyConfig,
("horizontalPodAutoscaling" .=) <$>
_acHorizontalPodAutoscaling,
("httpLoadBalancing" .=) <$> _acHTTPLoadBalancing,
("kubernetesDashboard" .=) <$>
_acKubernetesDashboard])
data NetworkConfig =
NetworkConfig'
{ _ncNetwork :: !(Maybe Text)
, _ncSubnetwork :: !(Maybe Text)
}
deriving (Eq, Show, Data, Typeable, Generic)
networkConfig
:: NetworkConfig
networkConfig = NetworkConfig' {_ncNetwork = Nothing, _ncSubnetwork = Nothing}
ncNetwork :: Lens' NetworkConfig (Maybe Text)
ncNetwork
= lens _ncNetwork (\ s a -> s{_ncNetwork = a})
ncSubnetwork :: Lens' NetworkConfig (Maybe Text)
ncSubnetwork
= lens _ncSubnetwork (\ s a -> s{_ncSubnetwork = a})
instance FromJSON NetworkConfig where
parseJSON
= withObject "NetworkConfig"
(\ o ->
NetworkConfig' <$>
(o .:? "network") <*> (o .:? "subnetwork"))
instance ToJSON NetworkConfig where
toJSON NetworkConfig'{..}
= object
(catMaybes
[("network" .=) <$> _ncNetwork,
("subnetwork" .=) <$> _ncSubnetwork])
data NodePool =
NodePool'
{ _npStatus :: !(Maybe NodePoolStatus)
, _npAutoscaling :: !(Maybe NodePoolAutoscaling)
, _npConfig :: !(Maybe NodeConfig)
, _npInitialNodeCount :: !(Maybe (Textual Int32))
, _npManagement :: !(Maybe NodeManagement)
, _npMaxPodsConstraint :: !(Maybe MaxPodsConstraint)
, _npSelfLink :: !(Maybe Text)
, _npName :: !(Maybe Text)
, _npStatusMessage :: !(Maybe Text)
, _npVersion :: !(Maybe Text)
, _npConditions :: !(Maybe [StatusCondition])
, _npInstanceGroupURLs :: !(Maybe [Text])
}
deriving (Eq, Show, Data, Typeable, Generic)
nodePool
:: NodePool
nodePool =
NodePool'
{ _npStatus = Nothing
, _npAutoscaling = Nothing
, _npConfig = Nothing
, _npInitialNodeCount = Nothing
, _npManagement = Nothing
, _npMaxPodsConstraint = Nothing
, _npSelfLink = Nothing
, _npName = Nothing
, _npStatusMessage = Nothing
, _npVersion = Nothing
, _npConditions = Nothing
, _npInstanceGroupURLs = Nothing
}
npStatus :: Lens' NodePool (Maybe NodePoolStatus)
npStatus = lens _npStatus (\ s a -> s{_npStatus = a})
npAutoscaling :: Lens' NodePool (Maybe NodePoolAutoscaling)
npAutoscaling
= lens _npAutoscaling
(\ s a -> s{_npAutoscaling = a})
npConfig :: Lens' NodePool (Maybe NodeConfig)
npConfig = lens _npConfig (\ s a -> s{_npConfig = a})
npInitialNodeCount :: Lens' NodePool (Maybe Int32)
npInitialNodeCount
= lens _npInitialNodeCount
(\ s a -> s{_npInitialNodeCount = a})
. mapping _Coerce
npManagement :: Lens' NodePool (Maybe NodeManagement)
npManagement
= lens _npManagement (\ s a -> s{_npManagement = a})
npMaxPodsConstraint :: Lens' NodePool (Maybe MaxPodsConstraint)
npMaxPodsConstraint
= lens _npMaxPodsConstraint
(\ s a -> s{_npMaxPodsConstraint = a})
npSelfLink :: Lens' NodePool (Maybe Text)
npSelfLink
= lens _npSelfLink (\ s a -> s{_npSelfLink = a})
npName :: Lens' NodePool (Maybe Text)
npName = lens _npName (\ s a -> s{_npName = a})
npStatusMessage :: Lens' NodePool (Maybe Text)
npStatusMessage
= lens _npStatusMessage
(\ s a -> s{_npStatusMessage = a})
npVersion :: Lens' NodePool (Maybe Text)
npVersion
= lens _npVersion (\ s a -> s{_npVersion = a})
npConditions :: Lens' NodePool [StatusCondition]
npConditions
= lens _npConditions (\ s a -> s{_npConditions = a})
. _Default
. _Coerce
npInstanceGroupURLs :: Lens' NodePool [Text]
npInstanceGroupURLs
= lens _npInstanceGroupURLs
(\ s a -> s{_npInstanceGroupURLs = a})
. _Default
. _Coerce
instance FromJSON NodePool where
parseJSON
= withObject "NodePool"
(\ o ->
NodePool' <$>
(o .:? "status") <*> (o .:? "autoscaling") <*>
(o .:? "config")
<*> (o .:? "initialNodeCount")
<*> (o .:? "management")
<*> (o .:? "maxPodsConstraint")
<*> (o .:? "selfLink")
<*> (o .:? "name")
<*> (o .:? "statusMessage")
<*> (o .:? "version")
<*> (o .:? "conditions" .!= mempty)
<*> (o .:? "instanceGroupUrls" .!= mempty))
instance ToJSON NodePool where
toJSON NodePool'{..}
= object
(catMaybes
[("status" .=) <$> _npStatus,
("autoscaling" .=) <$> _npAutoscaling,
("config" .=) <$> _npConfig,
("initialNodeCount" .=) <$> _npInitialNodeCount,
("management" .=) <$> _npManagement,
("maxPodsConstraint" .=) <$> _npMaxPodsConstraint,
("selfLink" .=) <$> _npSelfLink,
("name" .=) <$> _npName,
("statusMessage" .=) <$> _npStatusMessage,
("version" .=) <$> _npVersion,
("conditions" .=) <$> _npConditions,
("instanceGroupUrls" .=) <$> _npInstanceGroupURLs])
data SetNodePoolManagementRequest =
SetNodePoolManagementRequest'
{ _snpmrManagement :: !(Maybe NodeManagement)
,