module Network.Google.Container.Types.Product where
import Network.Google.Container.Types.Sum
import Network.Google.Prelude
newtype ListOperationsResponse = ListOperationsResponse
{ _lorOperations :: Maybe [Operation]
} deriving (Eq,Show,Data,Typeable,Generic)
listOperationsResponse
:: ListOperationsResponse
listOperationsResponse =
ListOperationsResponse
{ _lorOperations = Nothing
}
lorOperations :: Lens' ListOperationsResponse [Operation]
lorOperations
= lens _lorOperations
(\ s a -> s{_lorOperations = a})
. _Default
. _Coerce
instance FromJSON ListOperationsResponse where
parseJSON
= withObject "ListOperationsResponse"
(\ o ->
ListOperationsResponse <$>
(o .:? "operations" .!= mempty))
instance ToJSON ListOperationsResponse where
toJSON ListOperationsResponse{..}
= object
(catMaybes [("operations" .=) <$> _lorOperations])
newtype CreateClusterRequest = CreateClusterRequest
{ _ccrCluster :: Maybe Cluster
} deriving (Eq,Show,Data,Typeable,Generic)
createClusterRequest
:: CreateClusterRequest
createClusterRequest =
CreateClusterRequest
{ _ccrCluster = Nothing
}
ccrCluster :: Lens' CreateClusterRequest (Maybe Cluster)
ccrCluster
= lens _ccrCluster (\ s a -> s{_ccrCluster = a})
instance FromJSON CreateClusterRequest where
parseJSON
= withObject "CreateClusterRequest"
(\ o -> CreateClusterRequest <$> (o .:? "cluster"))
instance ToJSON CreateClusterRequest where
toJSON CreateClusterRequest{..}
= object (catMaybes [("cluster" .=) <$> _ccrCluster])
data Cluster = Cluster
{ _cStatus :: !(Maybe Text)
, _cNodeConfig :: !(Maybe NodeConfig)
, _cNodeIPv4CIdRSize :: !(Maybe (Textual Int32))
, _cClusterIPv4CIdR :: !(Maybe Text)
, _cInitialNodeCount :: !(Maybe (Textual Int32))
, _cCurrentNodeVersion :: !(Maybe Text)
, _cNetwork :: !(Maybe Text)
, _cInitialClusterVersion :: !(Maybe Text)
, _cZone :: !(Maybe Text)
, _cServicesIPv4CIdR :: !(Maybe Text)
, _cMasterAuth :: !(Maybe MasterAuth)
, _cSelfLink :: !(Maybe Text)
, _cName :: !(Maybe Text)
, _cCurrentMasterVersion :: !(Maybe Text)
, _cStatusMessage :: !(Maybe Text)
, _cEndpoint :: !(Maybe Text)
, _cLoggingService :: !(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
, _cNodeConfig = Nothing
, _cNodeIPv4CIdRSize = Nothing
, _cClusterIPv4CIdR = Nothing
, _cInitialNodeCount = Nothing
, _cCurrentNodeVersion = Nothing
, _cNetwork = Nothing
, _cInitialClusterVersion = Nothing
, _cZone = Nothing
, _cServicesIPv4CIdR = Nothing
, _cMasterAuth = Nothing
, _cSelfLink = Nothing
, _cName = Nothing
, _cCurrentMasterVersion = Nothing
, _cStatusMessage = Nothing
, _cEndpoint = Nothing
, _cLoggingService = Nothing
, _cDescription = Nothing
, _cInstanceGroupURLs = Nothing
, _cMonitoringService = Nothing
, _cCreateTime = Nothing
}
cStatus :: Lens' Cluster (Maybe Text)
cStatus = lens _cStatus (\ s a -> s{_cStatus = 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})
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})
cServicesIPv4CIdR :: Lens' Cluster (Maybe Text)
cServicesIPv4CIdR
= lens _cServicesIPv4CIdR
(\ s a -> s{_cServicesIPv4CIdR = 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})
cEndpoint :: Lens' Cluster (Maybe Text)
cEndpoint
= lens _cEndpoint (\ s a -> s{_cEndpoint = a})
cLoggingService :: Lens' Cluster (Maybe Text)
cLoggingService
= lens _cLoggingService
(\ s a -> s{_cLoggingService = 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 .:? "nodeConfig") <*>
(o .:? "nodeIpv4CidrSize")
<*> (o .:? "clusterIpv4Cidr")
<*> (o .:? "initialNodeCount")
<*> (o .:? "currentNodeVersion")
<*> (o .:? "network")
<*> (o .:? "initialClusterVersion")
<*> (o .:? "zone")
<*> (o .:? "servicesIpv4Cidr")
<*> (o .:? "masterAuth")
<*> (o .:? "selfLink")
<*> (o .:? "name")
<*> (o .:? "currentMasterVersion")
<*> (o .:? "statusMessage")
<*> (o .:? "endpoint")
<*> (o .:? "loggingService")
<*> (o .:? "description")
<*> (o .:? "instanceGroupUrls" .!= mempty)
<*> (o .:? "monitoringService")
<*> (o .:? "createTime"))
instance ToJSON Cluster where
toJSON Cluster{..}
= object
(catMaybes
[("status" .=) <$> _cStatus,
("nodeConfig" .=) <$> _cNodeConfig,
("nodeIpv4CidrSize" .=) <$> _cNodeIPv4CIdRSize,
("clusterIpv4Cidr" .=) <$> _cClusterIPv4CIdR,
("initialNodeCount" .=) <$> _cInitialNodeCount,
("currentNodeVersion" .=) <$> _cCurrentNodeVersion,
("network" .=) <$> _cNetwork,
("initialClusterVersion" .=) <$>
_cInitialClusterVersion,
("zone" .=) <$> _cZone,
("servicesIpv4Cidr" .=) <$> _cServicesIPv4CIdR,
("masterAuth" .=) <$> _cMasterAuth,
("selfLink" .=) <$> _cSelfLink,
("name" .=) <$> _cName,
("currentMasterVersion" .=) <$>
_cCurrentMasterVersion,
("statusMessage" .=) <$> _cStatusMessage,
("endpoint" .=) <$> _cEndpoint,
("loggingService" .=) <$> _cLoggingService,
("description" .=) <$> _cDescription,
("instanceGroupUrls" .=) <$> _cInstanceGroupURLs,
("monitoringService" .=) <$> _cMonitoringService,
("createTime" .=) <$> _cCreateTime])
newtype UpdateClusterRequest = UpdateClusterRequest
{ _ucrUpdate :: Maybe ClusterUpdate
} deriving (Eq,Show,Data,Typeable,Generic)
updateClusterRequest
:: UpdateClusterRequest
updateClusterRequest =
UpdateClusterRequest
{ _ucrUpdate = Nothing
}
ucrUpdate :: Lens' UpdateClusterRequest (Maybe ClusterUpdate)
ucrUpdate
= lens _ucrUpdate (\ s a -> s{_ucrUpdate = a})
instance FromJSON UpdateClusterRequest where
parseJSON
= withObject "UpdateClusterRequest"
(\ o -> UpdateClusterRequest <$> (o .:? "update"))
instance ToJSON UpdateClusterRequest where
toJSON UpdateClusterRequest{..}
= object (catMaybes [("update" .=) <$> _ucrUpdate])
data NodeConfig = NodeConfig
{ _ncDiskSizeGb :: !(Maybe (Textual Int32))
, _ncOAuthScopes :: !(Maybe [Text])
, _ncMachineType :: !(Maybe Text)
} deriving (Eq,Show,Data,Typeable,Generic)
nodeConfig
:: NodeConfig
nodeConfig =
NodeConfig
{ _ncDiskSizeGb = Nothing
, _ncOAuthScopes = Nothing
, _ncMachineType = Nothing
}
ncDiskSizeGb :: Lens' NodeConfig (Maybe Int32)
ncDiskSizeGb
= lens _ncDiskSizeGb (\ s a -> s{_ncDiskSizeGb = a})
. mapping _Coerce
ncOAuthScopes :: Lens' NodeConfig [Text]
ncOAuthScopes
= lens _ncOAuthScopes
(\ s a -> s{_ncOAuthScopes = a})
. _Default
. _Coerce
ncMachineType :: Lens' NodeConfig (Maybe Text)
ncMachineType
= lens _ncMachineType
(\ s a -> s{_ncMachineType = a})
instance FromJSON NodeConfig where
parseJSON
= withObject "NodeConfig"
(\ o ->
NodeConfig <$>
(o .:? "diskSizeGb") <*>
(o .:? "oauthScopes" .!= mempty)
<*> (o .:? "machineType"))
instance ToJSON NodeConfig where
toJSON NodeConfig{..}
= object
(catMaybes
[("diskSizeGb" .=) <$> _ncDiskSizeGb,
("oauthScopes" .=) <$> _ncOAuthScopes,
("machineType" .=) <$> _ncMachineType])
data Operation = Operation
{ _oStatus :: !(Maybe Text)
, _oZone :: !(Maybe Text)
, _oSelfLink :: !(Maybe Text)
, _oName :: !(Maybe Text)
, _oStatusMessage :: !(Maybe Text)
, _oOperationType :: !(Maybe Text)
, _oTargetLink :: !(Maybe Text)
} deriving (Eq,Show,Data,Typeable,Generic)
operation
:: Operation
operation =
Operation
{ _oStatus = Nothing
, _oZone = Nothing
, _oSelfLink = Nothing
, _oName = Nothing
, _oStatusMessage = Nothing
, _oOperationType = Nothing
, _oTargetLink = Nothing
}
oStatus :: Lens' Operation (Maybe Text)
oStatus = lens _oStatus (\ s a -> s{_oStatus = 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})
oOperationType :: Lens' Operation (Maybe Text)
oOperationType
= lens _oOperationType
(\ s a -> s{_oOperationType = a})
oTargetLink :: Lens' Operation (Maybe Text)
oTargetLink
= lens _oTargetLink (\ s a -> s{_oTargetLink = a})
instance FromJSON Operation where
parseJSON
= withObject "Operation"
(\ o ->
Operation <$>
(o .:? "status") <*> (o .:? "zone") <*>
(o .:? "selfLink")
<*> (o .:? "name")
<*> (o .:? "statusMessage")
<*> (o .:? "operationType")
<*> (o .:? "targetLink"))
instance ToJSON Operation where
toJSON Operation{..}
= object
(catMaybes
[("status" .=) <$> _oStatus, ("zone" .=) <$> _oZone,
("selfLink" .=) <$> _oSelfLink,
("name" .=) <$> _oName,
("statusMessage" .=) <$> _oStatusMessage,
("operationType" .=) <$> _oOperationType,
("targetLink" .=) <$> _oTargetLink])
data MasterAuth = MasterAuth
{ _maClientKey :: !(Maybe Text)
, _maUsername :: !(Maybe Text)
, _maClientCertificate :: !(Maybe Text)
, _maPassword :: !(Maybe Text)
, _maClusterCaCertificate :: !(Maybe Text)
} deriving (Eq,Show,Data,Typeable,Generic)
masterAuth
:: MasterAuth
masterAuth =
MasterAuth
{ _maClientKey = Nothing
, _maUsername = Nothing
, _maClientCertificate = Nothing
, _maPassword = Nothing
, _maClusterCaCertificate = Nothing
}
maClientKey :: Lens' MasterAuth (Maybe Text)
maClientKey
= lens _maClientKey (\ s a -> s{_maClientKey = a})
maUsername :: Lens' MasterAuth (Maybe Text)
maUsername
= lens _maUsername (\ s a -> s{_maUsername = a})
maClientCertificate :: Lens' MasterAuth (Maybe Text)
maClientCertificate
= lens _maClientCertificate
(\ s a -> s{_maClientCertificate = a})
maPassword :: Lens' MasterAuth (Maybe Text)
maPassword
= lens _maPassword (\ s a -> s{_maPassword = a})
maClusterCaCertificate :: Lens' MasterAuth (Maybe Text)
maClusterCaCertificate
= lens _maClusterCaCertificate
(\ s a -> s{_maClusterCaCertificate = a})
instance FromJSON MasterAuth where
parseJSON
= withObject "MasterAuth"
(\ o ->
MasterAuth <$>
(o .:? "clientKey") <*> (o .:? "username") <*>
(o .:? "clientCertificate")
<*> (o .:? "password")
<*> (o .:? "clusterCaCertificate"))
instance ToJSON MasterAuth where
toJSON MasterAuth{..}
= object
(catMaybes
[("clientKey" .=) <$> _maClientKey,
("username" .=) <$> _maUsername,
("clientCertificate" .=) <$> _maClientCertificate,
("password" .=) <$> _maPassword,
("clusterCaCertificate" .=) <$>
_maClusterCaCertificate])
data ServerConfig = ServerConfig
{ _scValidNodeVersions :: !(Maybe [Text])
, _scDefaultClusterVersion :: !(Maybe Text)
} deriving (Eq,Show,Data,Typeable,Generic)
serverConfig
:: ServerConfig
serverConfig =
ServerConfig
{ _scValidNodeVersions = Nothing
, _scDefaultClusterVersion = Nothing
}
scValidNodeVersions :: Lens' ServerConfig [Text]
scValidNodeVersions
= lens _scValidNodeVersions
(\ s a -> s{_scValidNodeVersions = a})
. _Default
. _Coerce
scDefaultClusterVersion :: Lens' ServerConfig (Maybe Text)
scDefaultClusterVersion
= lens _scDefaultClusterVersion
(\ s a -> s{_scDefaultClusterVersion = a})
instance FromJSON ServerConfig where
parseJSON
= withObject "ServerConfig"
(\ o ->
ServerConfig <$>
(o .:? "validNodeVersions" .!= mempty) <*>
(o .:? "defaultClusterVersion"))
instance ToJSON ServerConfig where
toJSON ServerConfig{..}
= object
(catMaybes
[("validNodeVersions" .=) <$> _scValidNodeVersions,
("defaultClusterVersion" .=) <$>
_scDefaultClusterVersion])
newtype ListClustersResponse = ListClustersResponse
{ _lcrClusters :: Maybe [Cluster]
} deriving (Eq,Show,Data,Typeable,Generic)
listClustersResponse
:: ListClustersResponse
listClustersResponse =
ListClustersResponse
{ _lcrClusters = Nothing
}
lcrClusters :: Lens' ListClustersResponse [Cluster]
lcrClusters
= lens _lcrClusters (\ s a -> s{_lcrClusters = a}) .
_Default
. _Coerce
instance FromJSON ListClustersResponse where
parseJSON
= withObject "ListClustersResponse"
(\ o ->
ListClustersResponse <$>
(o .:? "clusters" .!= mempty))
instance ToJSON ListClustersResponse where
toJSON ListClustersResponse{..}
= object
(catMaybes [("clusters" .=) <$> _lcrClusters])
newtype ClusterUpdate = ClusterUpdate
{ _cuDesiredNodeVersion :: Maybe Text
} deriving (Eq,Show,Data,Typeable,Generic)
clusterUpdate
:: ClusterUpdate
clusterUpdate =
ClusterUpdate
{ _cuDesiredNodeVersion = Nothing
}
cuDesiredNodeVersion :: Lens' ClusterUpdate (Maybe Text)
cuDesiredNodeVersion
= lens _cuDesiredNodeVersion
(\ s a -> s{_cuDesiredNodeVersion = a})
instance FromJSON ClusterUpdate where
parseJSON
= withObject "ClusterUpdate"
(\ o ->
ClusterUpdate <$> (o .:? "desiredNodeVersion"))
instance ToJSON ClusterUpdate where
toJSON ClusterUpdate{..}
= object
(catMaybes
[("desiredNodeVersion" .=) <$>
_cuDesiredNodeVersion])