{-# 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.MemoryDb.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)
--
-- Modifies the settings for a cluster. You can use this operation to
-- change one or more cluster configuration settings by specifying the
-- settings and the new values.
module Amazonka.MemoryDb.UpdateCluster
  ( -- * Creating a Request
    UpdateCluster (..),
    newUpdateCluster,

    -- * Request Lenses
    updateCluster_aCLName,
    updateCluster_description,
    updateCluster_engineVersion,
    updateCluster_maintenanceWindow,
    updateCluster_nodeType,
    updateCluster_parameterGroupName,
    updateCluster_replicaConfiguration,
    updateCluster_securityGroupIds,
    updateCluster_shardConfiguration,
    updateCluster_snapshotRetentionLimit,
    updateCluster_snapshotWindow,
    updateCluster_snsTopicArn,
    updateCluster_snsTopicStatus,
    updateCluster_clusterName,

    -- * 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.MemoryDb.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 Access Control List that is associated with the cluster
    UpdateCluster -> Maybe Text
aCLName :: Prelude.Maybe Prelude.Text,
    -- | The description of the cluster to update
    UpdateCluster -> Maybe Text
description :: Prelude.Maybe Prelude.Text,
    -- | The upgraded version of the engine to be run on the nodes. You can
    -- upgrade to a newer engine version, but you cannot downgrade to an
    -- earlier engine version. If you want to use an earlier engine version,
    -- you must delete the existing cluster and create it anew with the earlier
    -- engine version.
    UpdateCluster -> Maybe Text
engineVersion :: Prelude.Maybe Prelude.Text,
    -- | Specifies the weekly time range during which maintenance on the cluster
    -- is performed. It is specified as a range in the format
    -- ddd:hh24:mi-ddd:hh24:mi (24H Clock UTC). The minimum maintenance window
    -- is a 60 minute period.
    --
    -- Valid values for @ddd@ are:
    --
    -- -   @sun@
    --
    -- -   @mon@
    --
    -- -   @tue@
    --
    -- -   @wed@
    --
    -- -   @thu@
    --
    -- -   @fri@
    --
    -- -   @sat@
    --
    -- Example: @sun:23:00-mon:01:30@
    UpdateCluster -> Maybe Text
maintenanceWindow :: Prelude.Maybe Prelude.Text,
    -- | A valid node type that you want to scale this cluster up or down to.
    UpdateCluster -> Maybe Text
nodeType :: Prelude.Maybe Prelude.Text,
    -- | The name of the parameter group to update
    UpdateCluster -> Maybe Text
parameterGroupName :: Prelude.Maybe Prelude.Text,
    -- | The number of replicas that will reside in each shard
    UpdateCluster -> Maybe ReplicaConfigurationRequest
replicaConfiguration :: Prelude.Maybe ReplicaConfigurationRequest,
    -- | The SecurityGroupIds to update
    UpdateCluster -> Maybe [Text]
securityGroupIds :: Prelude.Maybe [Prelude.Text],
    -- | The number of shards in the cluster
    UpdateCluster -> Maybe ShardConfigurationRequest
shardConfiguration :: Prelude.Maybe ShardConfigurationRequest,
    -- | The number of days for which MemoryDB retains automatic cluster
    -- snapshots before deleting them. For example, if you set
    -- SnapshotRetentionLimit to 5, a snapshot that was taken today is retained
    -- for 5 days before being deleted.
    UpdateCluster -> Maybe Int
snapshotRetentionLimit :: Prelude.Maybe Prelude.Int,
    -- | The daily time range (in UTC) during which MemoryDB begins taking a
    -- daily snapshot of your cluster.
    UpdateCluster -> Maybe Text
snapshotWindow :: Prelude.Maybe Prelude.Text,
    -- | The SNS topic ARN to update
    UpdateCluster -> Maybe Text
snsTopicArn :: Prelude.Maybe Prelude.Text,
    -- | The status of the Amazon SNS notification topic. Notifications are sent
    -- only if the status is active.
    UpdateCluster -> Maybe Text
snsTopicStatus :: Prelude.Maybe Prelude.Text,
    -- | The name of the cluster to update
    UpdateCluster -> Text
clusterName :: 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:
--
-- 'aCLName', 'updateCluster_aCLName' - The Access Control List that is associated with the cluster
--
-- 'description', 'updateCluster_description' - The description of the cluster to update
--
-- 'engineVersion', 'updateCluster_engineVersion' - The upgraded version of the engine to be run on the nodes. You can
-- upgrade to a newer engine version, but you cannot downgrade to an
-- earlier engine version. If you want to use an earlier engine version,
-- you must delete the existing cluster and create it anew with the earlier
-- engine version.
--
-- 'maintenanceWindow', 'updateCluster_maintenanceWindow' - Specifies the weekly time range during which maintenance on the cluster
-- is performed. It is specified as a range in the format
-- ddd:hh24:mi-ddd:hh24:mi (24H Clock UTC). The minimum maintenance window
-- is a 60 minute period.
--
-- Valid values for @ddd@ are:
--
-- -   @sun@
--
-- -   @mon@
--
-- -   @tue@
--
-- -   @wed@
--
-- -   @thu@
--
-- -   @fri@
--
-- -   @sat@
--
-- Example: @sun:23:00-mon:01:30@
--
-- 'nodeType', 'updateCluster_nodeType' - A valid node type that you want to scale this cluster up or down to.
--
-- 'parameterGroupName', 'updateCluster_parameterGroupName' - The name of the parameter group to update
--
-- 'replicaConfiguration', 'updateCluster_replicaConfiguration' - The number of replicas that will reside in each shard
--
-- 'securityGroupIds', 'updateCluster_securityGroupIds' - The SecurityGroupIds to update
--
-- 'shardConfiguration', 'updateCluster_shardConfiguration' - The number of shards in the cluster
--
-- 'snapshotRetentionLimit', 'updateCluster_snapshotRetentionLimit' - The number of days for which MemoryDB retains automatic cluster
-- snapshots before deleting them. For example, if you set
-- SnapshotRetentionLimit to 5, a snapshot that was taken today is retained
-- for 5 days before being deleted.
--
-- 'snapshotWindow', 'updateCluster_snapshotWindow' - The daily time range (in UTC) during which MemoryDB begins taking a
-- daily snapshot of your cluster.
--
-- 'snsTopicArn', 'updateCluster_snsTopicArn' - The SNS topic ARN to update
--
-- 'snsTopicStatus', 'updateCluster_snsTopicStatus' - The status of the Amazon SNS notification topic. Notifications are sent
-- only if the status is active.
--
-- 'clusterName', 'updateCluster_clusterName' - The name of the cluster to update
newUpdateCluster ::
  -- | 'clusterName'
  Prelude.Text ->
  UpdateCluster
newUpdateCluster :: Text -> UpdateCluster
newUpdateCluster Text
pClusterName_ =
  UpdateCluster'
    { $sel:aCLName:UpdateCluster' :: Maybe Text
aCLName = forall a. Maybe a
Prelude.Nothing,
      $sel:description:UpdateCluster' :: Maybe Text
description = forall a. Maybe a
Prelude.Nothing,
      $sel:engineVersion:UpdateCluster' :: Maybe Text
engineVersion = forall a. Maybe a
Prelude.Nothing,
      $sel:maintenanceWindow:UpdateCluster' :: Maybe Text
maintenanceWindow = forall a. Maybe a
Prelude.Nothing,
      $sel:nodeType:UpdateCluster' :: Maybe Text
nodeType = forall a. Maybe a
Prelude.Nothing,
      $sel:parameterGroupName:UpdateCluster' :: Maybe Text
parameterGroupName = forall a. Maybe a
Prelude.Nothing,
      $sel:replicaConfiguration:UpdateCluster' :: Maybe ReplicaConfigurationRequest
replicaConfiguration = forall a. Maybe a
Prelude.Nothing,
      $sel:securityGroupIds:UpdateCluster' :: Maybe [Text]
securityGroupIds = forall a. Maybe a
Prelude.Nothing,
      $sel:shardConfiguration:UpdateCluster' :: Maybe ShardConfigurationRequest
shardConfiguration = forall a. Maybe a
Prelude.Nothing,
      $sel:snapshotRetentionLimit:UpdateCluster' :: Maybe Int
snapshotRetentionLimit = forall a. Maybe a
Prelude.Nothing,
      $sel:snapshotWindow:UpdateCluster' :: Maybe Text
snapshotWindow = forall a. Maybe a
Prelude.Nothing,
      $sel:snsTopicArn:UpdateCluster' :: Maybe Text
snsTopicArn = forall a. Maybe a
Prelude.Nothing,
      $sel:snsTopicStatus:UpdateCluster' :: Maybe Text
snsTopicStatus = forall a. Maybe a
Prelude.Nothing,
      $sel:clusterName:UpdateCluster' :: Text
clusterName = Text
pClusterName_
    }

-- | The Access Control List that is associated with the cluster
updateCluster_aCLName :: Lens.Lens' UpdateCluster (Prelude.Maybe Prelude.Text)
updateCluster_aCLName :: Lens' UpdateCluster (Maybe Text)
updateCluster_aCLName = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\UpdateCluster' {Maybe Text
aCLName :: Maybe Text
$sel:aCLName:UpdateCluster' :: UpdateCluster -> Maybe Text
aCLName} -> Maybe Text
aCLName) (\s :: UpdateCluster
s@UpdateCluster' {} Maybe Text
a -> UpdateCluster
s {$sel:aCLName:UpdateCluster' :: Maybe Text
aCLName = Maybe Text
a} :: UpdateCluster)

-- | The description of the cluster to update
updateCluster_description :: Lens.Lens' UpdateCluster (Prelude.Maybe Prelude.Text)
updateCluster_description :: Lens' UpdateCluster (Maybe Text)
updateCluster_description = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\UpdateCluster' {Maybe Text
description :: Maybe Text
$sel:description:UpdateCluster' :: UpdateCluster -> Maybe Text
description} -> Maybe Text
description) (\s :: UpdateCluster
s@UpdateCluster' {} Maybe Text
a -> UpdateCluster
s {$sel:description:UpdateCluster' :: Maybe Text
description = Maybe Text
a} :: UpdateCluster)

-- | The upgraded version of the engine to be run on the nodes. You can
-- upgrade to a newer engine version, but you cannot downgrade to an
-- earlier engine version. If you want to use an earlier engine version,
-- you must delete the existing cluster and create it anew with the earlier
-- engine version.
updateCluster_engineVersion :: Lens.Lens' UpdateCluster (Prelude.Maybe Prelude.Text)
updateCluster_engineVersion :: Lens' UpdateCluster (Maybe Text)
updateCluster_engineVersion = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\UpdateCluster' {Maybe Text
engineVersion :: Maybe Text
$sel:engineVersion:UpdateCluster' :: UpdateCluster -> Maybe Text
engineVersion} -> Maybe Text
engineVersion) (\s :: UpdateCluster
s@UpdateCluster' {} Maybe Text
a -> UpdateCluster
s {$sel:engineVersion:UpdateCluster' :: Maybe Text
engineVersion = Maybe Text
a} :: UpdateCluster)

-- | Specifies the weekly time range during which maintenance on the cluster
-- is performed. It is specified as a range in the format
-- ddd:hh24:mi-ddd:hh24:mi (24H Clock UTC). The minimum maintenance window
-- is a 60 minute period.
--
-- Valid values for @ddd@ are:
--
-- -   @sun@
--
-- -   @mon@
--
-- -   @tue@
--
-- -   @wed@
--
-- -   @thu@
--
-- -   @fri@
--
-- -   @sat@
--
-- Example: @sun:23:00-mon:01:30@
updateCluster_maintenanceWindow :: Lens.Lens' UpdateCluster (Prelude.Maybe Prelude.Text)
updateCluster_maintenanceWindow :: Lens' UpdateCluster (Maybe Text)
updateCluster_maintenanceWindow = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\UpdateCluster' {Maybe Text
maintenanceWindow :: Maybe Text
$sel:maintenanceWindow:UpdateCluster' :: UpdateCluster -> Maybe Text
maintenanceWindow} -> Maybe Text
maintenanceWindow) (\s :: UpdateCluster
s@UpdateCluster' {} Maybe Text
a -> UpdateCluster
s {$sel:maintenanceWindow:UpdateCluster' :: Maybe Text
maintenanceWindow = Maybe Text
a} :: UpdateCluster)

-- | A valid node type that you want to scale this cluster up or down to.
updateCluster_nodeType :: Lens.Lens' UpdateCluster (Prelude.Maybe Prelude.Text)
updateCluster_nodeType :: Lens' UpdateCluster (Maybe Text)
updateCluster_nodeType = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\UpdateCluster' {Maybe Text
nodeType :: Maybe Text
$sel:nodeType:UpdateCluster' :: UpdateCluster -> Maybe Text
nodeType} -> Maybe Text
nodeType) (\s :: UpdateCluster
s@UpdateCluster' {} Maybe Text
a -> UpdateCluster
s {$sel:nodeType:UpdateCluster' :: Maybe Text
nodeType = Maybe Text
a} :: UpdateCluster)

-- | The name of the parameter group to update
updateCluster_parameterGroupName :: Lens.Lens' UpdateCluster (Prelude.Maybe Prelude.Text)
updateCluster_parameterGroupName :: Lens' UpdateCluster (Maybe Text)
updateCluster_parameterGroupName = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\UpdateCluster' {Maybe Text
parameterGroupName :: Maybe Text
$sel:parameterGroupName:UpdateCluster' :: UpdateCluster -> Maybe Text
parameterGroupName} -> Maybe Text
parameterGroupName) (\s :: UpdateCluster
s@UpdateCluster' {} Maybe Text
a -> UpdateCluster
s {$sel:parameterGroupName:UpdateCluster' :: Maybe Text
parameterGroupName = Maybe Text
a} :: UpdateCluster)

-- | The number of replicas that will reside in each shard
updateCluster_replicaConfiguration :: Lens.Lens' UpdateCluster (Prelude.Maybe ReplicaConfigurationRequest)
updateCluster_replicaConfiguration :: Lens' UpdateCluster (Maybe ReplicaConfigurationRequest)
updateCluster_replicaConfiguration = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\UpdateCluster' {Maybe ReplicaConfigurationRequest
replicaConfiguration :: Maybe ReplicaConfigurationRequest
$sel:replicaConfiguration:UpdateCluster' :: UpdateCluster -> Maybe ReplicaConfigurationRequest
replicaConfiguration} -> Maybe ReplicaConfigurationRequest
replicaConfiguration) (\s :: UpdateCluster
s@UpdateCluster' {} Maybe ReplicaConfigurationRequest
a -> UpdateCluster
s {$sel:replicaConfiguration:UpdateCluster' :: Maybe ReplicaConfigurationRequest
replicaConfiguration = Maybe ReplicaConfigurationRequest
a} :: UpdateCluster)

-- | The SecurityGroupIds to update
updateCluster_securityGroupIds :: Lens.Lens' UpdateCluster (Prelude.Maybe [Prelude.Text])
updateCluster_securityGroupIds :: Lens' UpdateCluster (Maybe [Text])
updateCluster_securityGroupIds = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\UpdateCluster' {Maybe [Text]
securityGroupIds :: Maybe [Text]
$sel:securityGroupIds:UpdateCluster' :: UpdateCluster -> Maybe [Text]
securityGroupIds} -> Maybe [Text]
securityGroupIds) (\s :: UpdateCluster
s@UpdateCluster' {} Maybe [Text]
a -> UpdateCluster
s {$sel:securityGroupIds:UpdateCluster' :: Maybe [Text]
securityGroupIds = Maybe [Text]
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 number of shards in the cluster
updateCluster_shardConfiguration :: Lens.Lens' UpdateCluster (Prelude.Maybe ShardConfigurationRequest)
updateCluster_shardConfiguration :: Lens' UpdateCluster (Maybe ShardConfigurationRequest)
updateCluster_shardConfiguration = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\UpdateCluster' {Maybe ShardConfigurationRequest
shardConfiguration :: Maybe ShardConfigurationRequest
$sel:shardConfiguration:UpdateCluster' :: UpdateCluster -> Maybe ShardConfigurationRequest
shardConfiguration} -> Maybe ShardConfigurationRequest
shardConfiguration) (\s :: UpdateCluster
s@UpdateCluster' {} Maybe ShardConfigurationRequest
a -> UpdateCluster
s {$sel:shardConfiguration:UpdateCluster' :: Maybe ShardConfigurationRequest
shardConfiguration = Maybe ShardConfigurationRequest
a} :: UpdateCluster)

-- | The number of days for which MemoryDB retains automatic cluster
-- snapshots before deleting them. For example, if you set
-- SnapshotRetentionLimit to 5, a snapshot that was taken today is retained
-- for 5 days before being deleted.
updateCluster_snapshotRetentionLimit :: Lens.Lens' UpdateCluster (Prelude.Maybe Prelude.Int)
updateCluster_snapshotRetentionLimit :: Lens' UpdateCluster (Maybe Int)
updateCluster_snapshotRetentionLimit = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\UpdateCluster' {Maybe Int
snapshotRetentionLimit :: Maybe Int
$sel:snapshotRetentionLimit:UpdateCluster' :: UpdateCluster -> Maybe Int
snapshotRetentionLimit} -> Maybe Int
snapshotRetentionLimit) (\s :: UpdateCluster
s@UpdateCluster' {} Maybe Int
a -> UpdateCluster
s {$sel:snapshotRetentionLimit:UpdateCluster' :: Maybe Int
snapshotRetentionLimit = Maybe Int
a} :: UpdateCluster)

-- | The daily time range (in UTC) during which MemoryDB begins taking a
-- daily snapshot of your cluster.
updateCluster_snapshotWindow :: Lens.Lens' UpdateCluster (Prelude.Maybe Prelude.Text)
updateCluster_snapshotWindow :: Lens' UpdateCluster (Maybe Text)
updateCluster_snapshotWindow = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\UpdateCluster' {Maybe Text
snapshotWindow :: Maybe Text
$sel:snapshotWindow:UpdateCluster' :: UpdateCluster -> Maybe Text
snapshotWindow} -> Maybe Text
snapshotWindow) (\s :: UpdateCluster
s@UpdateCluster' {} Maybe Text
a -> UpdateCluster
s {$sel:snapshotWindow:UpdateCluster' :: Maybe Text
snapshotWindow = Maybe Text
a} :: UpdateCluster)

-- | The SNS topic ARN to update
updateCluster_snsTopicArn :: Lens.Lens' UpdateCluster (Prelude.Maybe Prelude.Text)
updateCluster_snsTopicArn :: Lens' UpdateCluster (Maybe Text)
updateCluster_snsTopicArn = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\UpdateCluster' {Maybe Text
snsTopicArn :: Maybe Text
$sel:snsTopicArn:UpdateCluster' :: UpdateCluster -> Maybe Text
snsTopicArn} -> Maybe Text
snsTopicArn) (\s :: UpdateCluster
s@UpdateCluster' {} Maybe Text
a -> UpdateCluster
s {$sel:snsTopicArn:UpdateCluster' :: Maybe Text
snsTopicArn = Maybe Text
a} :: UpdateCluster)

-- | The status of the Amazon SNS notification topic. Notifications are sent
-- only if the status is active.
updateCluster_snsTopicStatus :: Lens.Lens' UpdateCluster (Prelude.Maybe Prelude.Text)
updateCluster_snsTopicStatus :: Lens' UpdateCluster (Maybe Text)
updateCluster_snsTopicStatus = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\UpdateCluster' {Maybe Text
snsTopicStatus :: Maybe Text
$sel:snsTopicStatus:UpdateCluster' :: UpdateCluster -> Maybe Text
snsTopicStatus} -> Maybe Text
snsTopicStatus) (\s :: UpdateCluster
s@UpdateCluster' {} Maybe Text
a -> UpdateCluster
s {$sel:snsTopicStatus:UpdateCluster' :: Maybe Text
snsTopicStatus = Maybe Text
a} :: UpdateCluster)

-- | The name of the cluster to update
updateCluster_clusterName :: Lens.Lens' UpdateCluster Prelude.Text
updateCluster_clusterName :: Lens' UpdateCluster Text
updateCluster_clusterName = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\UpdateCluster' {Text
clusterName :: Text
$sel:clusterName:UpdateCluster' :: UpdateCluster -> Text
clusterName} -> Text
clusterName) (\s :: UpdateCluster
s@UpdateCluster' {} Text
a -> UpdateCluster
s {$sel:clusterName:UpdateCluster' :: Text
clusterName = 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 Int
Maybe [Text]
Maybe Text
Maybe ReplicaConfigurationRequest
Maybe ShardConfigurationRequest
Text
clusterName :: Text
snsTopicStatus :: Maybe Text
snsTopicArn :: Maybe Text
snapshotWindow :: Maybe Text
snapshotRetentionLimit :: Maybe Int
shardConfiguration :: Maybe ShardConfigurationRequest
securityGroupIds :: Maybe [Text]
replicaConfiguration :: Maybe ReplicaConfigurationRequest
parameterGroupName :: Maybe Text
nodeType :: Maybe Text
maintenanceWindow :: Maybe Text
engineVersion :: Maybe Text
description :: Maybe Text
aCLName :: Maybe Text
$sel:clusterName:UpdateCluster' :: UpdateCluster -> Text
$sel:snsTopicStatus:UpdateCluster' :: UpdateCluster -> Maybe Text
$sel:snsTopicArn:UpdateCluster' :: UpdateCluster -> Maybe Text
$sel:snapshotWindow:UpdateCluster' :: UpdateCluster -> Maybe Text
$sel:snapshotRetentionLimit:UpdateCluster' :: UpdateCluster -> Maybe Int
$sel:shardConfiguration:UpdateCluster' :: UpdateCluster -> Maybe ShardConfigurationRequest
$sel:securityGroupIds:UpdateCluster' :: UpdateCluster -> Maybe [Text]
$sel:replicaConfiguration:UpdateCluster' :: UpdateCluster -> Maybe ReplicaConfigurationRequest
$sel:parameterGroupName:UpdateCluster' :: UpdateCluster -> Maybe Text
$sel:nodeType:UpdateCluster' :: UpdateCluster -> Maybe Text
$sel:maintenanceWindow:UpdateCluster' :: UpdateCluster -> Maybe Text
$sel:engineVersion:UpdateCluster' :: UpdateCluster -> Maybe Text
$sel:description:UpdateCluster' :: UpdateCluster -> Maybe Text
$sel:aCLName:UpdateCluster' :: UpdateCluster -> Maybe Text
..} =
    Int
_salt
      forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Maybe Text
aCLName
      forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Maybe Text
description
      forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Maybe Text
engineVersion
      forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Maybe Text
maintenanceWindow
      forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Maybe Text
nodeType
      forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Maybe Text
parameterGroupName
      forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Maybe ReplicaConfigurationRequest
replicaConfiguration
      forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Maybe [Text]
securityGroupIds
      forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Maybe ShardConfigurationRequest
shardConfiguration
      forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Maybe Int
snapshotRetentionLimit
      forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Maybe Text
snapshotWindow
      forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Maybe Text
snsTopicArn
      forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Maybe Text
snsTopicStatus
      forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Text
clusterName

instance Prelude.NFData UpdateCluster where
  rnf :: UpdateCluster -> ()
rnf UpdateCluster' {Maybe Int
Maybe [Text]
Maybe Text
Maybe ReplicaConfigurationRequest
Maybe ShardConfigurationRequest
Text
clusterName :: Text
snsTopicStatus :: Maybe Text
snsTopicArn :: Maybe Text
snapshotWindow :: Maybe Text
snapshotRetentionLimit :: Maybe Int
shardConfiguration :: Maybe ShardConfigurationRequest
securityGroupIds :: Maybe [Text]
replicaConfiguration :: Maybe ReplicaConfigurationRequest
parameterGroupName :: Maybe Text
nodeType :: Maybe Text
maintenanceWindow :: Maybe Text
engineVersion :: Maybe Text
description :: Maybe Text
aCLName :: Maybe Text
$sel:clusterName:UpdateCluster' :: UpdateCluster -> Text
$sel:snsTopicStatus:UpdateCluster' :: UpdateCluster -> Maybe Text
$sel:snsTopicArn:UpdateCluster' :: UpdateCluster -> Maybe Text
$sel:snapshotWindow:UpdateCluster' :: UpdateCluster -> Maybe Text
$sel:snapshotRetentionLimit:UpdateCluster' :: UpdateCluster -> Maybe Int
$sel:shardConfiguration:UpdateCluster' :: UpdateCluster -> Maybe ShardConfigurationRequest
$sel:securityGroupIds:UpdateCluster' :: UpdateCluster -> Maybe [Text]
$sel:replicaConfiguration:UpdateCluster' :: UpdateCluster -> Maybe ReplicaConfigurationRequest
$sel:parameterGroupName:UpdateCluster' :: UpdateCluster -> Maybe Text
$sel:nodeType:UpdateCluster' :: UpdateCluster -> Maybe Text
$sel:maintenanceWindow:UpdateCluster' :: UpdateCluster -> Maybe Text
$sel:engineVersion:UpdateCluster' :: UpdateCluster -> Maybe Text
$sel:description:UpdateCluster' :: UpdateCluster -> Maybe Text
$sel:aCLName:UpdateCluster' :: UpdateCluster -> Maybe Text
..} =
    forall a. NFData a => a -> ()
Prelude.rnf Maybe Text
aCLName
      seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf Maybe Text
description
      seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf Maybe Text
engineVersion
      seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf Maybe Text
maintenanceWindow
      seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf Maybe Text
nodeType
      seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf Maybe Text
parameterGroupName
      seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf Maybe ReplicaConfigurationRequest
replicaConfiguration
      seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf Maybe [Text]
securityGroupIds
      seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf Maybe ShardConfigurationRequest
shardConfiguration
      seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf Maybe Int
snapshotRetentionLimit
      seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf Maybe Text
snapshotWindow
      seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf Maybe Text
snsTopicArn
      seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf Maybe Text
snsTopicStatus
      seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf Text
clusterName

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
"AmazonMemoryDB.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 Int
Maybe [Text]
Maybe Text
Maybe ReplicaConfigurationRequest
Maybe ShardConfigurationRequest
Text
clusterName :: Text
snsTopicStatus :: Maybe Text
snsTopicArn :: Maybe Text
snapshotWindow :: Maybe Text
snapshotRetentionLimit :: Maybe Int
shardConfiguration :: Maybe ShardConfigurationRequest
securityGroupIds :: Maybe [Text]
replicaConfiguration :: Maybe ReplicaConfigurationRequest
parameterGroupName :: Maybe Text
nodeType :: Maybe Text
maintenanceWindow :: Maybe Text
engineVersion :: Maybe Text
description :: Maybe Text
aCLName :: Maybe Text
$sel:clusterName:UpdateCluster' :: UpdateCluster -> Text
$sel:snsTopicStatus:UpdateCluster' :: UpdateCluster -> Maybe Text
$sel:snsTopicArn:UpdateCluster' :: UpdateCluster -> Maybe Text
$sel:snapshotWindow:UpdateCluster' :: UpdateCluster -> Maybe Text
$sel:snapshotRetentionLimit:UpdateCluster' :: UpdateCluster -> Maybe Int
$sel:shardConfiguration:UpdateCluster' :: UpdateCluster -> Maybe ShardConfigurationRequest
$sel:securityGroupIds:UpdateCluster' :: UpdateCluster -> Maybe [Text]
$sel:replicaConfiguration:UpdateCluster' :: UpdateCluster -> Maybe ReplicaConfigurationRequest
$sel:parameterGroupName:UpdateCluster' :: UpdateCluster -> Maybe Text
$sel:nodeType:UpdateCluster' :: UpdateCluster -> Maybe Text
$sel:maintenanceWindow:UpdateCluster' :: UpdateCluster -> Maybe Text
$sel:engineVersion:UpdateCluster' :: UpdateCluster -> Maybe Text
$sel:description:UpdateCluster' :: UpdateCluster -> Maybe Text
$sel:aCLName:UpdateCluster' :: UpdateCluster -> Maybe Text
..} =
    [Pair] -> Value
Data.object
      ( forall a. [Maybe a] -> [a]
Prelude.catMaybes
          [ (Key
"ACLName" 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 Text
aCLName,
            (Key
"Description" 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 Text
description,
            (Key
"EngineVersion" 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 Text
engineVersion,
            (Key
"MaintenanceWindow" 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 Text
maintenanceWindow,
            (Key
"NodeType" 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 Text
nodeType,
            (Key
"ParameterGroupName" 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 Text
parameterGroupName,
            (Key
"ReplicaConfiguration" 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 ReplicaConfigurationRequest
replicaConfiguration,
            (Key
"SecurityGroupIds" 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 [Text]
securityGroupIds,
            (Key
"ShardConfiguration" 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 ShardConfigurationRequest
shardConfiguration,
            (Key
"SnapshotRetentionLimit" 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 Int
snapshotRetentionLimit,
            (Key
"SnapshotWindow" 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 Text
snapshotWindow,
            (Key
"SnsTopicArn" 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 Text
snsTopicArn,
            (Key
"SnsTopicStatus" 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 Text
snsTopicStatus,
            forall a. a -> Maybe a
Prelude.Just (Key
"ClusterName" forall kv v. (KeyValue kv, ToJSON v) => Key -> v -> kv
Data..= Text
clusterName)
          ]
      )

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'
  { -- | The updated 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' - The updated 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_
    }

-- | The updated 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