{-# 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.RDS.ModifyGlobalCluster
-- Copyright   : (c) 2013-2023 Brendan Hay
-- License     : Mozilla Public License, v. 2.0.
-- Maintainer  : Brendan Hay
-- Stability   : auto-generated
-- Portability : non-portable (GHC extensions)
--
-- Modify a setting for an Amazon Aurora global cluster. You can change one
-- or more database configuration parameters by specifying these parameters
-- and the new values in the request. For more information on Amazon
-- Aurora, see
-- <https://docs.aws.amazon.com/AmazonRDS/latest/AuroraUserGuide/CHAP_AuroraOverview.html What is Amazon Aurora?>
-- in the /Amazon Aurora User Guide/.
--
-- This action only applies to Aurora DB clusters.
module Amazonka.RDS.ModifyGlobalCluster
  ( -- * Creating a Request
    ModifyGlobalCluster (..),
    newModifyGlobalCluster,

    -- * Request Lenses
    modifyGlobalCluster_allowMajorVersionUpgrade,
    modifyGlobalCluster_deletionProtection,
    modifyGlobalCluster_engineVersion,
    modifyGlobalCluster_globalClusterIdentifier,
    modifyGlobalCluster_newGlobalClusterIdentifier,

    -- * Destructuring the Response
    ModifyGlobalClusterResponse (..),
    newModifyGlobalClusterResponse,

    -- * Response Lenses
    modifyGlobalClusterResponse_globalCluster,
    modifyGlobalClusterResponse_httpStatus,
  )
where

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

-- | /See:/ 'newModifyGlobalCluster' smart constructor.
data ModifyGlobalCluster = ModifyGlobalCluster'
  { -- | A value that indicates whether major version upgrades are allowed.
    --
    -- Constraints: You must allow major version upgrades when specifying a
    -- value for the @EngineVersion@ parameter that is a different major
    -- version than the DB cluster\'s current version.
    --
    -- If you upgrade the major version of a global database, the cluster and
    -- DB instance parameter groups are set to the default parameter groups for
    -- the new version. Apply any custom parameter groups after completing the
    -- upgrade.
    ModifyGlobalCluster -> Maybe Bool
allowMajorVersionUpgrade :: Prelude.Maybe Prelude.Bool,
    -- | Indicates if the global database cluster has deletion protection
    -- enabled. The global database cluster can\'t be deleted when deletion
    -- protection is enabled.
    ModifyGlobalCluster -> Maybe Bool
deletionProtection :: Prelude.Maybe Prelude.Bool,
    -- | The version number of the database engine to which you want to upgrade.
    -- Changing this parameter results in an outage. The change is applied
    -- during the next maintenance window unless @ApplyImmediately@ is enabled.
    --
    -- To list all of the available engine versions for @aurora@ (for MySQL
    -- 5.6-compatible Aurora), use the following command:
    --
    -- @aws rds describe-db-engine-versions --engine aurora --query \'*[]|[?SupportsGlobalDatabases == \`true\`].[EngineVersion]\'@
    --
    -- To list all of the available engine versions for @aurora-mysql@ (for
    -- MySQL 5.7-compatible and MySQL 8.0-compatible Aurora), use the following
    -- command:
    --
    -- @aws rds describe-db-engine-versions --engine aurora-mysql --query \'*[]|[?SupportsGlobalDatabases == \`true\`].[EngineVersion]\'@
    --
    -- To list all of the available engine versions for @aurora-postgresql@,
    -- use the following command:
    --
    -- @aws rds describe-db-engine-versions --engine aurora-postgresql --query \'*[]|[?SupportsGlobalDatabases == \`true\`].[EngineVersion]\'@
    ModifyGlobalCluster -> Maybe Text
engineVersion :: Prelude.Maybe Prelude.Text,
    -- | The DB cluster identifier for the global cluster being modified. This
    -- parameter isn\'t case-sensitive.
    --
    -- Constraints:
    --
    -- -   Must match the identifier of an existing global database cluster.
    ModifyGlobalCluster -> Maybe Text
globalClusterIdentifier :: Prelude.Maybe Prelude.Text,
    -- | The new cluster identifier for the global database cluster when
    -- modifying a global database cluster. This value is stored as a lowercase
    -- string.
    --
    -- Constraints:
    --
    -- -   Must contain from 1 to 63 letters, numbers, or hyphens
    --
    -- -   The first character must be a letter
    --
    -- -   Can\'t end with a hyphen or contain two consecutive hyphens
    --
    -- Example: @my-cluster2@
    ModifyGlobalCluster -> Maybe Text
newGlobalClusterIdentifier' :: Prelude.Maybe Prelude.Text
  }
  deriving (ModifyGlobalCluster -> ModifyGlobalCluster -> Bool
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: ModifyGlobalCluster -> ModifyGlobalCluster -> Bool
$c/= :: ModifyGlobalCluster -> ModifyGlobalCluster -> Bool
== :: ModifyGlobalCluster -> ModifyGlobalCluster -> Bool
$c== :: ModifyGlobalCluster -> ModifyGlobalCluster -> Bool
Prelude.Eq, ReadPrec [ModifyGlobalCluster]
ReadPrec ModifyGlobalCluster
Int -> ReadS ModifyGlobalCluster
ReadS [ModifyGlobalCluster]
forall a.
(Int -> ReadS a)
-> ReadS [a] -> ReadPrec a -> ReadPrec [a] -> Read a
readListPrec :: ReadPrec [ModifyGlobalCluster]
$creadListPrec :: ReadPrec [ModifyGlobalCluster]
readPrec :: ReadPrec ModifyGlobalCluster
$creadPrec :: ReadPrec ModifyGlobalCluster
readList :: ReadS [ModifyGlobalCluster]
$creadList :: ReadS [ModifyGlobalCluster]
readsPrec :: Int -> ReadS ModifyGlobalCluster
$creadsPrec :: Int -> ReadS ModifyGlobalCluster
Prelude.Read, Int -> ModifyGlobalCluster -> ShowS
[ModifyGlobalCluster] -> ShowS
ModifyGlobalCluster -> String
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [ModifyGlobalCluster] -> ShowS
$cshowList :: [ModifyGlobalCluster] -> ShowS
show :: ModifyGlobalCluster -> String
$cshow :: ModifyGlobalCluster -> String
showsPrec :: Int -> ModifyGlobalCluster -> ShowS
$cshowsPrec :: Int -> ModifyGlobalCluster -> ShowS
Prelude.Show, forall x. Rep ModifyGlobalCluster x -> ModifyGlobalCluster
forall x. ModifyGlobalCluster -> Rep ModifyGlobalCluster x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cto :: forall x. Rep ModifyGlobalCluster x -> ModifyGlobalCluster
$cfrom :: forall x. ModifyGlobalCluster -> Rep ModifyGlobalCluster x
Prelude.Generic)

-- |
-- Create a value of 'ModifyGlobalCluster' 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:
--
-- 'allowMajorVersionUpgrade', 'modifyGlobalCluster_allowMajorVersionUpgrade' - A value that indicates whether major version upgrades are allowed.
--
-- Constraints: You must allow major version upgrades when specifying a
-- value for the @EngineVersion@ parameter that is a different major
-- version than the DB cluster\'s current version.
--
-- If you upgrade the major version of a global database, the cluster and
-- DB instance parameter groups are set to the default parameter groups for
-- the new version. Apply any custom parameter groups after completing the
-- upgrade.
--
-- 'deletionProtection', 'modifyGlobalCluster_deletionProtection' - Indicates if the global database cluster has deletion protection
-- enabled. The global database cluster can\'t be deleted when deletion
-- protection is enabled.
--
-- 'engineVersion', 'modifyGlobalCluster_engineVersion' - The version number of the database engine to which you want to upgrade.
-- Changing this parameter results in an outage. The change is applied
-- during the next maintenance window unless @ApplyImmediately@ is enabled.
--
-- To list all of the available engine versions for @aurora@ (for MySQL
-- 5.6-compatible Aurora), use the following command:
--
-- @aws rds describe-db-engine-versions --engine aurora --query \'*[]|[?SupportsGlobalDatabases == \`true\`].[EngineVersion]\'@
--
-- To list all of the available engine versions for @aurora-mysql@ (for
-- MySQL 5.7-compatible and MySQL 8.0-compatible Aurora), use the following
-- command:
--
-- @aws rds describe-db-engine-versions --engine aurora-mysql --query \'*[]|[?SupportsGlobalDatabases == \`true\`].[EngineVersion]\'@
--
-- To list all of the available engine versions for @aurora-postgresql@,
-- use the following command:
--
-- @aws rds describe-db-engine-versions --engine aurora-postgresql --query \'*[]|[?SupportsGlobalDatabases == \`true\`].[EngineVersion]\'@
--
-- 'globalClusterIdentifier', 'modifyGlobalCluster_globalClusterIdentifier' - The DB cluster identifier for the global cluster being modified. This
-- parameter isn\'t case-sensitive.
--
-- Constraints:
--
-- -   Must match the identifier of an existing global database cluster.
--
-- 'newGlobalClusterIdentifier'', 'modifyGlobalCluster_newGlobalClusterIdentifier' - The new cluster identifier for the global database cluster when
-- modifying a global database cluster. This value is stored as a lowercase
-- string.
--
-- Constraints:
--
-- -   Must contain from 1 to 63 letters, numbers, or hyphens
--
-- -   The first character must be a letter
--
-- -   Can\'t end with a hyphen or contain two consecutive hyphens
--
-- Example: @my-cluster2@
newModifyGlobalCluster ::
  ModifyGlobalCluster
newModifyGlobalCluster :: ModifyGlobalCluster
newModifyGlobalCluster =
  ModifyGlobalCluster'
    { $sel:allowMajorVersionUpgrade:ModifyGlobalCluster' :: Maybe Bool
allowMajorVersionUpgrade =
        forall a. Maybe a
Prelude.Nothing,
      $sel:deletionProtection:ModifyGlobalCluster' :: Maybe Bool
deletionProtection = forall a. Maybe a
Prelude.Nothing,
      $sel:engineVersion:ModifyGlobalCluster' :: Maybe Text
engineVersion = forall a. Maybe a
Prelude.Nothing,
      $sel:globalClusterIdentifier:ModifyGlobalCluster' :: Maybe Text
globalClusterIdentifier = forall a. Maybe a
Prelude.Nothing,
      $sel:newGlobalClusterIdentifier':ModifyGlobalCluster' :: Maybe Text
newGlobalClusterIdentifier' = forall a. Maybe a
Prelude.Nothing
    }

-- | A value that indicates whether major version upgrades are allowed.
--
-- Constraints: You must allow major version upgrades when specifying a
-- value for the @EngineVersion@ parameter that is a different major
-- version than the DB cluster\'s current version.
--
-- If you upgrade the major version of a global database, the cluster and
-- DB instance parameter groups are set to the default parameter groups for
-- the new version. Apply any custom parameter groups after completing the
-- upgrade.
modifyGlobalCluster_allowMajorVersionUpgrade :: Lens.Lens' ModifyGlobalCluster (Prelude.Maybe Prelude.Bool)
modifyGlobalCluster_allowMajorVersionUpgrade :: Lens' ModifyGlobalCluster (Maybe Bool)
modifyGlobalCluster_allowMajorVersionUpgrade = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\ModifyGlobalCluster' {Maybe Bool
allowMajorVersionUpgrade :: Maybe Bool
$sel:allowMajorVersionUpgrade:ModifyGlobalCluster' :: ModifyGlobalCluster -> Maybe Bool
allowMajorVersionUpgrade} -> Maybe Bool
allowMajorVersionUpgrade) (\s :: ModifyGlobalCluster
s@ModifyGlobalCluster' {} Maybe Bool
a -> ModifyGlobalCluster
s {$sel:allowMajorVersionUpgrade:ModifyGlobalCluster' :: Maybe Bool
allowMajorVersionUpgrade = Maybe Bool
a} :: ModifyGlobalCluster)

-- | Indicates if the global database cluster has deletion protection
-- enabled. The global database cluster can\'t be deleted when deletion
-- protection is enabled.
modifyGlobalCluster_deletionProtection :: Lens.Lens' ModifyGlobalCluster (Prelude.Maybe Prelude.Bool)
modifyGlobalCluster_deletionProtection :: Lens' ModifyGlobalCluster (Maybe Bool)
modifyGlobalCluster_deletionProtection = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\ModifyGlobalCluster' {Maybe Bool
deletionProtection :: Maybe Bool
$sel:deletionProtection:ModifyGlobalCluster' :: ModifyGlobalCluster -> Maybe Bool
deletionProtection} -> Maybe Bool
deletionProtection) (\s :: ModifyGlobalCluster
s@ModifyGlobalCluster' {} Maybe Bool
a -> ModifyGlobalCluster
s {$sel:deletionProtection:ModifyGlobalCluster' :: Maybe Bool
deletionProtection = Maybe Bool
a} :: ModifyGlobalCluster)

-- | The version number of the database engine to which you want to upgrade.
-- Changing this parameter results in an outage. The change is applied
-- during the next maintenance window unless @ApplyImmediately@ is enabled.
--
-- To list all of the available engine versions for @aurora@ (for MySQL
-- 5.6-compatible Aurora), use the following command:
--
-- @aws rds describe-db-engine-versions --engine aurora --query \'*[]|[?SupportsGlobalDatabases == \`true\`].[EngineVersion]\'@
--
-- To list all of the available engine versions for @aurora-mysql@ (for
-- MySQL 5.7-compatible and MySQL 8.0-compatible Aurora), use the following
-- command:
--
-- @aws rds describe-db-engine-versions --engine aurora-mysql --query \'*[]|[?SupportsGlobalDatabases == \`true\`].[EngineVersion]\'@
--
-- To list all of the available engine versions for @aurora-postgresql@,
-- use the following command:
--
-- @aws rds describe-db-engine-versions --engine aurora-postgresql --query \'*[]|[?SupportsGlobalDatabases == \`true\`].[EngineVersion]\'@
modifyGlobalCluster_engineVersion :: Lens.Lens' ModifyGlobalCluster (Prelude.Maybe Prelude.Text)
modifyGlobalCluster_engineVersion :: Lens' ModifyGlobalCluster (Maybe Text)
modifyGlobalCluster_engineVersion = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\ModifyGlobalCluster' {Maybe Text
engineVersion :: Maybe Text
$sel:engineVersion:ModifyGlobalCluster' :: ModifyGlobalCluster -> Maybe Text
engineVersion} -> Maybe Text
engineVersion) (\s :: ModifyGlobalCluster
s@ModifyGlobalCluster' {} Maybe Text
a -> ModifyGlobalCluster
s {$sel:engineVersion:ModifyGlobalCluster' :: Maybe Text
engineVersion = Maybe Text
a} :: ModifyGlobalCluster)

-- | The DB cluster identifier for the global cluster being modified. This
-- parameter isn\'t case-sensitive.
--
-- Constraints:
--
-- -   Must match the identifier of an existing global database cluster.
modifyGlobalCluster_globalClusterIdentifier :: Lens.Lens' ModifyGlobalCluster (Prelude.Maybe Prelude.Text)
modifyGlobalCluster_globalClusterIdentifier :: Lens' ModifyGlobalCluster (Maybe Text)
modifyGlobalCluster_globalClusterIdentifier = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\ModifyGlobalCluster' {Maybe Text
globalClusterIdentifier :: Maybe Text
$sel:globalClusterIdentifier:ModifyGlobalCluster' :: ModifyGlobalCluster -> Maybe Text
globalClusterIdentifier} -> Maybe Text
globalClusterIdentifier) (\s :: ModifyGlobalCluster
s@ModifyGlobalCluster' {} Maybe Text
a -> ModifyGlobalCluster
s {$sel:globalClusterIdentifier:ModifyGlobalCluster' :: Maybe Text
globalClusterIdentifier = Maybe Text
a} :: ModifyGlobalCluster)

-- | The new cluster identifier for the global database cluster when
-- modifying a global database cluster. This value is stored as a lowercase
-- string.
--
-- Constraints:
--
-- -   Must contain from 1 to 63 letters, numbers, or hyphens
--
-- -   The first character must be a letter
--
-- -   Can\'t end with a hyphen or contain two consecutive hyphens
--
-- Example: @my-cluster2@
modifyGlobalCluster_newGlobalClusterIdentifier :: Lens.Lens' ModifyGlobalCluster (Prelude.Maybe Prelude.Text)
modifyGlobalCluster_newGlobalClusterIdentifier :: Lens' ModifyGlobalCluster (Maybe Text)
modifyGlobalCluster_newGlobalClusterIdentifier = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\ModifyGlobalCluster' {Maybe Text
newGlobalClusterIdentifier' :: Maybe Text
$sel:newGlobalClusterIdentifier':ModifyGlobalCluster' :: ModifyGlobalCluster -> Maybe Text
newGlobalClusterIdentifier'} -> Maybe Text
newGlobalClusterIdentifier') (\s :: ModifyGlobalCluster
s@ModifyGlobalCluster' {} Maybe Text
a -> ModifyGlobalCluster
s {$sel:newGlobalClusterIdentifier':ModifyGlobalCluster' :: Maybe Text
newGlobalClusterIdentifier' = Maybe Text
a} :: ModifyGlobalCluster)

instance Core.AWSRequest ModifyGlobalCluster where
  type
    AWSResponse ModifyGlobalCluster =
      ModifyGlobalClusterResponse
  request :: (Service -> Service)
-> ModifyGlobalCluster -> Request ModifyGlobalCluster
request Service -> Service
overrides =
    forall a. ToRequest a => Service -> a -> Request a
Request.postQuery (Service -> Service
overrides Service
defaultService)
  response :: forall (m :: * -> *).
MonadResource m =>
(ByteStringLazy -> IO ByteStringLazy)
-> Service
-> Proxy ModifyGlobalCluster
-> ClientResponse ClientBody
-> m (Either
        Error (ClientResponse (AWSResponse ModifyGlobalCluster)))
response =
    forall (m :: * -> *) a.
MonadResource m =>
Text
-> (Int
    -> ResponseHeaders -> [Node] -> Either String (AWSResponse a))
-> (ByteStringLazy -> IO ByteStringLazy)
-> Service
-> Proxy a
-> ClientResponse ClientBody
-> m (Either Error (ClientResponse (AWSResponse a)))
Response.receiveXMLWrapper
      Text
"ModifyGlobalClusterResult"
      ( \Int
s ResponseHeaders
h [Node]
x ->
          Maybe GlobalCluster -> Int -> ModifyGlobalClusterResponse
ModifyGlobalClusterResponse'
            forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
Prelude.<$> ([Node]
x forall a. FromXML a => [Node] -> Text -> Either String (Maybe a)
Data..@? Text
"GlobalCluster")
            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 ModifyGlobalCluster where
  hashWithSalt :: Int -> ModifyGlobalCluster -> Int
hashWithSalt Int
_salt ModifyGlobalCluster' {Maybe Bool
Maybe Text
newGlobalClusterIdentifier' :: Maybe Text
globalClusterIdentifier :: Maybe Text
engineVersion :: Maybe Text
deletionProtection :: Maybe Bool
allowMajorVersionUpgrade :: Maybe Bool
$sel:newGlobalClusterIdentifier':ModifyGlobalCluster' :: ModifyGlobalCluster -> Maybe Text
$sel:globalClusterIdentifier:ModifyGlobalCluster' :: ModifyGlobalCluster -> Maybe Text
$sel:engineVersion:ModifyGlobalCluster' :: ModifyGlobalCluster -> Maybe Text
$sel:deletionProtection:ModifyGlobalCluster' :: ModifyGlobalCluster -> Maybe Bool
$sel:allowMajorVersionUpgrade:ModifyGlobalCluster' :: ModifyGlobalCluster -> Maybe Bool
..} =
    Int
_salt
      forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Maybe Bool
allowMajorVersionUpgrade
      forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Maybe Bool
deletionProtection
      forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Maybe Text
engineVersion
      forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Maybe Text
globalClusterIdentifier
      forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Maybe Text
newGlobalClusterIdentifier'

instance Prelude.NFData ModifyGlobalCluster where
  rnf :: ModifyGlobalCluster -> ()
rnf ModifyGlobalCluster' {Maybe Bool
Maybe Text
newGlobalClusterIdentifier' :: Maybe Text
globalClusterIdentifier :: Maybe Text
engineVersion :: Maybe Text
deletionProtection :: Maybe Bool
allowMajorVersionUpgrade :: Maybe Bool
$sel:newGlobalClusterIdentifier':ModifyGlobalCluster' :: ModifyGlobalCluster -> Maybe Text
$sel:globalClusterIdentifier:ModifyGlobalCluster' :: ModifyGlobalCluster -> Maybe Text
$sel:engineVersion:ModifyGlobalCluster' :: ModifyGlobalCluster -> Maybe Text
$sel:deletionProtection:ModifyGlobalCluster' :: ModifyGlobalCluster -> Maybe Bool
$sel:allowMajorVersionUpgrade:ModifyGlobalCluster' :: ModifyGlobalCluster -> Maybe Bool
..} =
    forall a. NFData a => a -> ()
Prelude.rnf Maybe Bool
allowMajorVersionUpgrade
      seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf Maybe Bool
deletionProtection
      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
globalClusterIdentifier
      seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf Maybe Text
newGlobalClusterIdentifier'

instance Data.ToHeaders ModifyGlobalCluster where
  toHeaders :: ModifyGlobalCluster -> ResponseHeaders
toHeaders = forall a b. a -> b -> a
Prelude.const forall a. Monoid a => a
Prelude.mempty

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

instance Data.ToQuery ModifyGlobalCluster where
  toQuery :: ModifyGlobalCluster -> QueryString
toQuery ModifyGlobalCluster' {Maybe Bool
Maybe Text
newGlobalClusterIdentifier' :: Maybe Text
globalClusterIdentifier :: Maybe Text
engineVersion :: Maybe Text
deletionProtection :: Maybe Bool
allowMajorVersionUpgrade :: Maybe Bool
$sel:newGlobalClusterIdentifier':ModifyGlobalCluster' :: ModifyGlobalCluster -> Maybe Text
$sel:globalClusterIdentifier:ModifyGlobalCluster' :: ModifyGlobalCluster -> Maybe Text
$sel:engineVersion:ModifyGlobalCluster' :: ModifyGlobalCluster -> Maybe Text
$sel:deletionProtection:ModifyGlobalCluster' :: ModifyGlobalCluster -> Maybe Bool
$sel:allowMajorVersionUpgrade:ModifyGlobalCluster' :: ModifyGlobalCluster -> Maybe Bool
..} =
    forall a. Monoid a => [a] -> a
Prelude.mconcat
      [ ByteString
"Action"
          forall a. ToQuery a => ByteString -> a -> QueryString
Data.=: (ByteString
"ModifyGlobalCluster" :: Prelude.ByteString),
        ByteString
"Version"
          forall a. ToQuery a => ByteString -> a -> QueryString
Data.=: (ByteString
"2014-10-31" :: Prelude.ByteString),
        ByteString
"AllowMajorVersionUpgrade"
          forall a. ToQuery a => ByteString -> a -> QueryString
Data.=: Maybe Bool
allowMajorVersionUpgrade,
        ByteString
"DeletionProtection" forall a. ToQuery a => ByteString -> a -> QueryString
Data.=: Maybe Bool
deletionProtection,
        ByteString
"EngineVersion" forall a. ToQuery a => ByteString -> a -> QueryString
Data.=: Maybe Text
engineVersion,
        ByteString
"GlobalClusterIdentifier"
          forall a. ToQuery a => ByteString -> a -> QueryString
Data.=: Maybe Text
globalClusterIdentifier,
        ByteString
"NewGlobalClusterIdentifier"
          forall a. ToQuery a => ByteString -> a -> QueryString
Data.=: Maybe Text
newGlobalClusterIdentifier'
      ]

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

-- |
-- Create a value of 'ModifyGlobalClusterResponse' 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:
--
-- 'globalCluster', 'modifyGlobalClusterResponse_globalCluster' - Undocumented member.
--
-- 'httpStatus', 'modifyGlobalClusterResponse_httpStatus' - The response's http status code.
newModifyGlobalClusterResponse ::
  -- | 'httpStatus'
  Prelude.Int ->
  ModifyGlobalClusterResponse
newModifyGlobalClusterResponse :: Int -> ModifyGlobalClusterResponse
newModifyGlobalClusterResponse Int
pHttpStatus_ =
  ModifyGlobalClusterResponse'
    { $sel:globalCluster:ModifyGlobalClusterResponse' :: Maybe GlobalCluster
globalCluster =
        forall a. Maybe a
Prelude.Nothing,
      $sel:httpStatus:ModifyGlobalClusterResponse' :: Int
httpStatus = Int
pHttpStatus_
    }

-- | Undocumented member.
modifyGlobalClusterResponse_globalCluster :: Lens.Lens' ModifyGlobalClusterResponse (Prelude.Maybe GlobalCluster)
modifyGlobalClusterResponse_globalCluster :: Lens' ModifyGlobalClusterResponse (Maybe GlobalCluster)
modifyGlobalClusterResponse_globalCluster = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\ModifyGlobalClusterResponse' {Maybe GlobalCluster
globalCluster :: Maybe GlobalCluster
$sel:globalCluster:ModifyGlobalClusterResponse' :: ModifyGlobalClusterResponse -> Maybe GlobalCluster
globalCluster} -> Maybe GlobalCluster
globalCluster) (\s :: ModifyGlobalClusterResponse
s@ModifyGlobalClusterResponse' {} Maybe GlobalCluster
a -> ModifyGlobalClusterResponse
s {$sel:globalCluster:ModifyGlobalClusterResponse' :: Maybe GlobalCluster
globalCluster = Maybe GlobalCluster
a} :: ModifyGlobalClusterResponse)

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

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