{-# LANGUAGE DeriveGeneric #-}
{-# LANGUAGE DuplicateRecordFields #-}
{-# LANGUAGE NamedFieldPuns #-}
{-# LANGUAGE OverloadedStrings #-}
{-# LANGUAGE RecordWildCards #-}
{-# LANGUAGE StrictData #-}
{-# LANGUAGE TypeFamilies #-}
{-# LANGUAGE NoImplicitPrelude #-}
{-# OPTIONS_GHC -fno-warn-unused-binds #-}
{-# OPTIONS_GHC -fno-warn-unused-imports #-}
{-# OPTIONS_GHC -fno-warn-unused-matches #-}

-- Derived from AWS service descriptions, licensed under Apache 2.0.

-- |
-- Module      : Amazonka.ECS.UpdateCluster
-- Copyright   : (c) 2013-2023 Brendan Hay
-- License     : Mozilla Public License, v. 2.0.
-- Maintainer  : Brendan Hay
-- Stability   : auto-generated
-- Portability : non-portable (GHC extensions)
--
-- Updates the cluster.
module Amazonka.ECS.UpdateCluster
  ( -- * Creating a Request
    UpdateCluster (..),
    newUpdateCluster,

    -- * Request Lenses
    updateCluster_configuration,
    updateCluster_serviceConnectDefaults,
    updateCluster_settings,
    updateCluster_cluster,

    -- * Destructuring the Response
    UpdateClusterResponse (..),
    newUpdateClusterResponse,

    -- * Response Lenses
    updateClusterResponse_cluster,
    updateClusterResponse_httpStatus,
  )
where

import qualified Amazonka.Core as Core
import qualified Amazonka.Core.Lens.Internal as Lens
import qualified Amazonka.Data as Data
import Amazonka.ECS.Types
import qualified Amazonka.Prelude as Prelude
import qualified Amazonka.Request as Request
import qualified Amazonka.Response as Response

-- | /See:/ 'newUpdateCluster' smart constructor.
data UpdateCluster = UpdateCluster'
  { -- | The execute command configuration for the cluster.
    UpdateCluster -> Maybe ClusterConfiguration
configuration :: Prelude.Maybe ClusterConfiguration,
    -- | Use this parameter to set a default Service Connect namespace. After you
    -- set a default Service Connect namespace, any new services with Service
    -- Connect turned on that are created in the cluster are added as client
    -- services in the namespace. This setting only applies to new services
    -- that set the @enabled@ parameter to @true@ in the
    -- @ServiceConnectConfiguration@. You can set the namespace of each service
    -- individually in the @ServiceConnectConfiguration@ to override this
    -- default parameter.
    --
    -- Tasks that run in a namespace can use short names to connect to services
    -- in the namespace. Tasks can connect to services across all of the
    -- clusters in the namespace. Tasks connect through a managed proxy
    -- container that collects logs and metrics for increased visibility. Only
    -- the tasks that Amazon ECS services create are supported with Service
    -- Connect. For more information, see
    -- <https://docs.aws.amazon.com/AmazonECS/latest/developerguide/service-connect.html Service Connect>
    -- in the /Amazon Elastic Container Service Developer Guide/.
    UpdateCluster -> Maybe ClusterServiceConnectDefaultsRequest
serviceConnectDefaults :: Prelude.Maybe ClusterServiceConnectDefaultsRequest,
    -- | The cluster settings for your cluster.
    UpdateCluster -> Maybe [ClusterSetting]
settings :: Prelude.Maybe [ClusterSetting],
    -- | The name of the cluster to modify the settings for.
    UpdateCluster -> Text
cluster :: Prelude.Text
  }
  deriving (UpdateCluster -> UpdateCluster -> Bool
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: UpdateCluster -> UpdateCluster -> Bool
$c/= :: UpdateCluster -> UpdateCluster -> Bool
== :: UpdateCluster -> UpdateCluster -> Bool
$c== :: UpdateCluster -> UpdateCluster -> Bool
Prelude.Eq, ReadPrec [UpdateCluster]
ReadPrec UpdateCluster
Int -> ReadS UpdateCluster
ReadS [UpdateCluster]
forall a.
(Int -> ReadS a)
-> ReadS [a] -> ReadPrec a -> ReadPrec [a] -> Read a
readListPrec :: ReadPrec [UpdateCluster]
$creadListPrec :: ReadPrec [UpdateCluster]
readPrec :: ReadPrec UpdateCluster
$creadPrec :: ReadPrec UpdateCluster
readList :: ReadS [UpdateCluster]
$creadList :: ReadS [UpdateCluster]
readsPrec :: Int -> ReadS UpdateCluster
$creadsPrec :: Int -> ReadS UpdateCluster
Prelude.Read, Int -> UpdateCluster -> ShowS
[UpdateCluster] -> ShowS
UpdateCluster -> String
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [UpdateCluster] -> ShowS
$cshowList :: [UpdateCluster] -> ShowS
show :: UpdateCluster -> String
$cshow :: UpdateCluster -> String
showsPrec :: Int -> UpdateCluster -> ShowS
$cshowsPrec :: Int -> UpdateCluster -> ShowS
Prelude.Show, forall x. Rep UpdateCluster x -> UpdateCluster
forall x. UpdateCluster -> Rep UpdateCluster x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cto :: forall x. Rep UpdateCluster x -> UpdateCluster
$cfrom :: forall x. UpdateCluster -> Rep UpdateCluster x
Prelude.Generic)

-- |
-- Create a value of 'UpdateCluster' with all optional fields omitted.
--
-- Use <https://hackage.haskell.org/package/generic-lens generic-lens> or <https://hackage.haskell.org/package/optics optics> to modify other optional fields.
--
-- The following record fields are available, with the corresponding lenses provided
-- for backwards compatibility:
--
-- 'configuration', 'updateCluster_configuration' - The execute command configuration for the cluster.
--
-- 'serviceConnectDefaults', 'updateCluster_serviceConnectDefaults' - Use this parameter to set a default Service Connect namespace. After you
-- set a default Service Connect namespace, any new services with Service
-- Connect turned on that are created in the cluster are added as client
-- services in the namespace. This setting only applies to new services
-- that set the @enabled@ parameter to @true@ in the
-- @ServiceConnectConfiguration@. You can set the namespace of each service
-- individually in the @ServiceConnectConfiguration@ to override this
-- default parameter.
--
-- Tasks that run in a namespace can use short names to connect to services
-- in the namespace. Tasks can connect to services across all of the
-- clusters in the namespace. Tasks connect through a managed proxy
-- container that collects logs and metrics for increased visibility. Only
-- the tasks that Amazon ECS services create are supported with Service
-- Connect. For more information, see
-- <https://docs.aws.amazon.com/AmazonECS/latest/developerguide/service-connect.html Service Connect>
-- in the /Amazon Elastic Container Service Developer Guide/.
--
-- 'settings', 'updateCluster_settings' - The cluster settings for your cluster.
--
-- 'cluster', 'updateCluster_cluster' - The name of the cluster to modify the settings for.
newUpdateCluster ::
  -- | 'cluster'
  Prelude.Text ->
  UpdateCluster
newUpdateCluster :: Text -> UpdateCluster
newUpdateCluster Text
pCluster_ =
  UpdateCluster'
    { $sel:configuration:UpdateCluster' :: Maybe ClusterConfiguration
configuration = forall a. Maybe a
Prelude.Nothing,
      $sel:serviceConnectDefaults:UpdateCluster' :: Maybe ClusterServiceConnectDefaultsRequest
serviceConnectDefaults = forall a. Maybe a
Prelude.Nothing,
      $sel:settings:UpdateCluster' :: Maybe [ClusterSetting]
settings = forall a. Maybe a
Prelude.Nothing,
      $sel:cluster:UpdateCluster' :: Text
cluster = Text
pCluster_
    }

-- | The execute command configuration for the cluster.
updateCluster_configuration :: Lens.Lens' UpdateCluster (Prelude.Maybe ClusterConfiguration)
updateCluster_configuration :: Lens' UpdateCluster (Maybe ClusterConfiguration)
updateCluster_configuration = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\UpdateCluster' {Maybe ClusterConfiguration
configuration :: Maybe ClusterConfiguration
$sel:configuration:UpdateCluster' :: UpdateCluster -> Maybe ClusterConfiguration
configuration} -> Maybe ClusterConfiguration
configuration) (\s :: UpdateCluster
s@UpdateCluster' {} Maybe ClusterConfiguration
a -> UpdateCluster
s {$sel:configuration:UpdateCluster' :: Maybe ClusterConfiguration
configuration = Maybe ClusterConfiguration
a} :: UpdateCluster)

-- | Use this parameter to set a default Service Connect namespace. After you
-- set a default Service Connect namespace, any new services with Service
-- Connect turned on that are created in the cluster are added as client
-- services in the namespace. This setting only applies to new services
-- that set the @enabled@ parameter to @true@ in the
-- @ServiceConnectConfiguration@. You can set the namespace of each service
-- individually in the @ServiceConnectConfiguration@ to override this
-- default parameter.
--
-- Tasks that run in a namespace can use short names to connect to services
-- in the namespace. Tasks can connect to services across all of the
-- clusters in the namespace. Tasks connect through a managed proxy
-- container that collects logs and metrics for increased visibility. Only
-- the tasks that Amazon ECS services create are supported with Service
-- Connect. For more information, see
-- <https://docs.aws.amazon.com/AmazonECS/latest/developerguide/service-connect.html Service Connect>
-- in the /Amazon Elastic Container Service Developer Guide/.
updateCluster_serviceConnectDefaults :: Lens.Lens' UpdateCluster (Prelude.Maybe ClusterServiceConnectDefaultsRequest)
updateCluster_serviceConnectDefaults :: Lens' UpdateCluster (Maybe ClusterServiceConnectDefaultsRequest)
updateCluster_serviceConnectDefaults = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\UpdateCluster' {Maybe ClusterServiceConnectDefaultsRequest
serviceConnectDefaults :: Maybe ClusterServiceConnectDefaultsRequest
$sel:serviceConnectDefaults:UpdateCluster' :: UpdateCluster -> Maybe ClusterServiceConnectDefaultsRequest
serviceConnectDefaults} -> Maybe ClusterServiceConnectDefaultsRequest
serviceConnectDefaults) (\s :: UpdateCluster
s@UpdateCluster' {} Maybe ClusterServiceConnectDefaultsRequest
a -> UpdateCluster
s {$sel:serviceConnectDefaults:UpdateCluster' :: Maybe ClusterServiceConnectDefaultsRequest
serviceConnectDefaults = Maybe ClusterServiceConnectDefaultsRequest
a} :: UpdateCluster)

-- | The cluster settings for your cluster.
updateCluster_settings :: Lens.Lens' UpdateCluster (Prelude.Maybe [ClusterSetting])
updateCluster_settings :: Lens' UpdateCluster (Maybe [ClusterSetting])
updateCluster_settings = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\UpdateCluster' {Maybe [ClusterSetting]
settings :: Maybe [ClusterSetting]
$sel:settings:UpdateCluster' :: UpdateCluster -> Maybe [ClusterSetting]
settings} -> Maybe [ClusterSetting]
settings) (\s :: UpdateCluster
s@UpdateCluster' {} Maybe [ClusterSetting]
a -> UpdateCluster
s {$sel:settings:UpdateCluster' :: Maybe [ClusterSetting]
settings = Maybe [ClusterSetting]
a} :: UpdateCluster) forall b c a. (b -> c) -> (a -> b) -> a -> c
Prelude.. forall (f :: * -> *) (g :: * -> *) s t a b.
(Functor f, Functor g) =>
AnIso s t a b -> Iso (f s) (g t) (f a) (g b)
Lens.mapping forall s t a b. (Coercible s a, Coercible t b) => Iso s t a b
Lens.coerced

-- | The name of the cluster to modify the settings for.
updateCluster_cluster :: Lens.Lens' UpdateCluster Prelude.Text
updateCluster_cluster :: Lens' UpdateCluster Text
updateCluster_cluster = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\UpdateCluster' {Text
cluster :: Text
$sel:cluster:UpdateCluster' :: UpdateCluster -> Text
cluster} -> Text
cluster) (\s :: UpdateCluster
s@UpdateCluster' {} Text
a -> UpdateCluster
s {$sel:cluster:UpdateCluster' :: Text
cluster = Text
a} :: UpdateCluster)

instance Core.AWSRequest UpdateCluster where
  type
    AWSResponse UpdateCluster =
      UpdateClusterResponse
  request :: (Service -> Service) -> UpdateCluster -> Request UpdateCluster
request Service -> Service
overrides =
    forall a. (ToRequest a, ToJSON a) => Service -> a -> Request a
Request.postJSON (Service -> Service
overrides Service
defaultService)
  response :: forall (m :: * -> *).
MonadResource m =>
(ByteStringLazy -> IO ByteStringLazy)
-> Service
-> Proxy UpdateCluster
-> ClientResponse ClientBody
-> m (Either Error (ClientResponse (AWSResponse UpdateCluster)))
response =
    forall (m :: * -> *) a.
MonadResource m =>
(Int -> ResponseHeaders -> Object -> Either String (AWSResponse a))
-> (ByteStringLazy -> IO ByteStringLazy)
-> Service
-> Proxy a
-> ClientResponse ClientBody
-> m (Either Error (ClientResponse (AWSResponse a)))
Response.receiveJSON
      ( \Int
s ResponseHeaders
h Object
x ->
          Maybe Cluster -> Int -> UpdateClusterResponse
UpdateClusterResponse'
            forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
Prelude.<$> (Object
x forall a. FromJSON a => Object -> Key -> Either String (Maybe a)
Data..?> Key
"cluster")
            forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
Prelude.<*> (forall (f :: * -> *) a. Applicative f => a -> f a
Prelude.pure (forall a. Enum a => a -> Int
Prelude.fromEnum Int
s))
      )

instance Prelude.Hashable UpdateCluster where
  hashWithSalt :: Int -> UpdateCluster -> Int
hashWithSalt Int
_salt UpdateCluster' {Maybe [ClusterSetting]
Maybe ClusterServiceConnectDefaultsRequest
Maybe ClusterConfiguration
Text
cluster :: Text
settings :: Maybe [ClusterSetting]
serviceConnectDefaults :: Maybe ClusterServiceConnectDefaultsRequest
configuration :: Maybe ClusterConfiguration
$sel:cluster:UpdateCluster' :: UpdateCluster -> Text
$sel:settings:UpdateCluster' :: UpdateCluster -> Maybe [ClusterSetting]
$sel:serviceConnectDefaults:UpdateCluster' :: UpdateCluster -> Maybe ClusterServiceConnectDefaultsRequest
$sel:configuration:UpdateCluster' :: UpdateCluster -> Maybe ClusterConfiguration
..} =
    Int
_salt
      forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Maybe ClusterConfiguration
configuration
      forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Maybe ClusterServiceConnectDefaultsRequest
serviceConnectDefaults
      forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Maybe [ClusterSetting]
settings
      forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Text
cluster

instance Prelude.NFData UpdateCluster where
  rnf :: UpdateCluster -> ()
rnf UpdateCluster' {Maybe [ClusterSetting]
Maybe ClusterServiceConnectDefaultsRequest
Maybe ClusterConfiguration
Text
cluster :: Text
settings :: Maybe [ClusterSetting]
serviceConnectDefaults :: Maybe ClusterServiceConnectDefaultsRequest
configuration :: Maybe ClusterConfiguration
$sel:cluster:UpdateCluster' :: UpdateCluster -> Text
$sel:settings:UpdateCluster' :: UpdateCluster -> Maybe [ClusterSetting]
$sel:serviceConnectDefaults:UpdateCluster' :: UpdateCluster -> Maybe ClusterServiceConnectDefaultsRequest
$sel:configuration:UpdateCluster' :: UpdateCluster -> Maybe ClusterConfiguration
..} =
    forall a. NFData a => a -> ()
Prelude.rnf Maybe ClusterConfiguration
configuration
      seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf Maybe ClusterServiceConnectDefaultsRequest
serviceConnectDefaults
      seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf Maybe [ClusterSetting]
settings
      seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf Text
cluster

instance Data.ToHeaders UpdateCluster where
  toHeaders :: UpdateCluster -> ResponseHeaders
toHeaders =
    forall a b. a -> b -> a
Prelude.const
      ( forall a. Monoid a => [a] -> a
Prelude.mconcat
          [ HeaderName
"X-Amz-Target"
              forall a. ToHeader a => HeaderName -> a -> ResponseHeaders
Data.=# ( ByteString
"AmazonEC2ContainerServiceV20141113.UpdateCluster" ::
                          Prelude.ByteString
                      ),
            HeaderName
"Content-Type"
              forall a. ToHeader a => HeaderName -> a -> ResponseHeaders
Data.=# ( ByteString
"application/x-amz-json-1.1" ::
                          Prelude.ByteString
                      )
          ]
      )

instance Data.ToJSON UpdateCluster where
  toJSON :: UpdateCluster -> Value
toJSON UpdateCluster' {Maybe [ClusterSetting]
Maybe ClusterServiceConnectDefaultsRequest
Maybe ClusterConfiguration
Text
cluster :: Text
settings :: Maybe [ClusterSetting]
serviceConnectDefaults :: Maybe ClusterServiceConnectDefaultsRequest
configuration :: Maybe ClusterConfiguration
$sel:cluster:UpdateCluster' :: UpdateCluster -> Text
$sel:settings:UpdateCluster' :: UpdateCluster -> Maybe [ClusterSetting]
$sel:serviceConnectDefaults:UpdateCluster' :: UpdateCluster -> Maybe ClusterServiceConnectDefaultsRequest
$sel:configuration:UpdateCluster' :: UpdateCluster -> Maybe ClusterConfiguration
..} =
    [Pair] -> Value
Data.object
      ( forall a. [Maybe a] -> [a]
Prelude.catMaybes
          [ (Key
"configuration" forall kv v. (KeyValue kv, ToJSON v) => Key -> v -> kv
Data..=) forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
Prelude.<$> Maybe ClusterConfiguration
configuration,
            (Key
"serviceConnectDefaults" forall kv v. (KeyValue kv, ToJSON v) => Key -> v -> kv
Data..=)
              forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
Prelude.<$> Maybe ClusterServiceConnectDefaultsRequest
serviceConnectDefaults,
            (Key
"settings" forall kv v. (KeyValue kv, ToJSON v) => Key -> v -> kv
Data..=) forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
Prelude.<$> Maybe [ClusterSetting]
settings,
            forall a. a -> Maybe a
Prelude.Just (Key
"cluster" forall kv v. (KeyValue kv, ToJSON v) => Key -> v -> kv
Data..= Text
cluster)
          ]
      )

instance Data.ToPath UpdateCluster where
  toPath :: UpdateCluster -> ByteString
toPath = forall a b. a -> b -> a
Prelude.const ByteString
"/"

instance Data.ToQuery UpdateCluster where
  toQuery :: UpdateCluster -> QueryString
toQuery = forall a b. a -> b -> a
Prelude.const forall a. Monoid a => a
Prelude.mempty

-- | /See:/ 'newUpdateClusterResponse' smart constructor.
data UpdateClusterResponse = UpdateClusterResponse'
  { -- | Details about the cluster.
    UpdateClusterResponse -> Maybe Cluster
cluster :: Prelude.Maybe Cluster,
    -- | The response's http status code.
    UpdateClusterResponse -> Int
httpStatus :: Prelude.Int
  }
  deriving (UpdateClusterResponse -> UpdateClusterResponse -> Bool
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: UpdateClusterResponse -> UpdateClusterResponse -> Bool
$c/= :: UpdateClusterResponse -> UpdateClusterResponse -> Bool
== :: UpdateClusterResponse -> UpdateClusterResponse -> Bool
$c== :: UpdateClusterResponse -> UpdateClusterResponse -> Bool
Prelude.Eq, ReadPrec [UpdateClusterResponse]
ReadPrec UpdateClusterResponse
Int -> ReadS UpdateClusterResponse
ReadS [UpdateClusterResponse]
forall a.
(Int -> ReadS a)
-> ReadS [a] -> ReadPrec a -> ReadPrec [a] -> Read a
readListPrec :: ReadPrec [UpdateClusterResponse]
$creadListPrec :: ReadPrec [UpdateClusterResponse]
readPrec :: ReadPrec UpdateClusterResponse
$creadPrec :: ReadPrec UpdateClusterResponse
readList :: ReadS [UpdateClusterResponse]
$creadList :: ReadS [UpdateClusterResponse]
readsPrec :: Int -> ReadS UpdateClusterResponse
$creadsPrec :: Int -> ReadS UpdateClusterResponse
Prelude.Read, Int -> UpdateClusterResponse -> ShowS
[UpdateClusterResponse] -> ShowS
UpdateClusterResponse -> String
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [UpdateClusterResponse] -> ShowS
$cshowList :: [UpdateClusterResponse] -> ShowS
show :: UpdateClusterResponse -> String
$cshow :: UpdateClusterResponse -> String
showsPrec :: Int -> UpdateClusterResponse -> ShowS
$cshowsPrec :: Int -> UpdateClusterResponse -> ShowS
Prelude.Show, forall x. Rep UpdateClusterResponse x -> UpdateClusterResponse
forall x. UpdateClusterResponse -> Rep UpdateClusterResponse x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cto :: forall x. Rep UpdateClusterResponse x -> UpdateClusterResponse
$cfrom :: forall x. UpdateClusterResponse -> Rep UpdateClusterResponse x
Prelude.Generic)

-- |
-- Create a value of 'UpdateClusterResponse' with all optional fields omitted.
--
-- Use <https://hackage.haskell.org/package/generic-lens generic-lens> or <https://hackage.haskell.org/package/optics optics> to modify other optional fields.
--
-- The following record fields are available, with the corresponding lenses provided
-- for backwards compatibility:
--
-- 'cluster', 'updateClusterResponse_cluster' - Details about the cluster.
--
-- 'httpStatus', 'updateClusterResponse_httpStatus' - The response's http status code.
newUpdateClusterResponse ::
  -- | 'httpStatus'
  Prelude.Int ->
  UpdateClusterResponse
newUpdateClusterResponse :: Int -> UpdateClusterResponse
newUpdateClusterResponse Int
pHttpStatus_ =
  UpdateClusterResponse'
    { $sel:cluster:UpdateClusterResponse' :: Maybe Cluster
cluster = forall a. Maybe a
Prelude.Nothing,
      $sel:httpStatus:UpdateClusterResponse' :: Int
httpStatus = Int
pHttpStatus_
    }

-- | Details about the cluster.
updateClusterResponse_cluster :: Lens.Lens' UpdateClusterResponse (Prelude.Maybe Cluster)
updateClusterResponse_cluster :: Lens' UpdateClusterResponse (Maybe Cluster)
updateClusterResponse_cluster = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\UpdateClusterResponse' {Maybe Cluster
cluster :: Maybe Cluster
$sel:cluster:UpdateClusterResponse' :: UpdateClusterResponse -> Maybe Cluster
cluster} -> Maybe Cluster
cluster) (\s :: UpdateClusterResponse
s@UpdateClusterResponse' {} Maybe Cluster
a -> UpdateClusterResponse
s {$sel:cluster:UpdateClusterResponse' :: Maybe Cluster
cluster = Maybe Cluster
a} :: UpdateClusterResponse)

-- | The response's http status code.
updateClusterResponse_httpStatus :: Lens.Lens' UpdateClusterResponse Prelude.Int
updateClusterResponse_httpStatus :: Lens' UpdateClusterResponse Int
updateClusterResponse_httpStatus = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\UpdateClusterResponse' {Int
httpStatus :: Int
$sel:httpStatus:UpdateClusterResponse' :: UpdateClusterResponse -> Int
httpStatus} -> Int
httpStatus) (\s :: UpdateClusterResponse
s@UpdateClusterResponse' {} Int
a -> UpdateClusterResponse
s {$sel:httpStatus:UpdateClusterResponse' :: Int
httpStatus = Int
a} :: UpdateClusterResponse)

instance Prelude.NFData UpdateClusterResponse where
  rnf :: UpdateClusterResponse -> ()
rnf UpdateClusterResponse' {Int
Maybe Cluster
httpStatus :: Int
cluster :: Maybe Cluster
$sel:httpStatus:UpdateClusterResponse' :: UpdateClusterResponse -> Int
$sel:cluster:UpdateClusterResponse' :: UpdateClusterResponse -> Maybe Cluster
..} =
    forall a. NFData a => a -> ()
Prelude.rnf Maybe Cluster
cluster
      seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf Int
httpStatus