{-# 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.DocumentDB.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 DocumentDB global cluster. You can change
-- one or more configuration parameters (for example: deletion protection),
-- or the global cluster identifier by specifying these parameters and the
-- new values in the request.
--
-- This action only applies to Amazon DocumentDB clusters.
module Amazonka.DocumentDB.ModifyGlobalCluster
  ( -- * Creating a Request
    ModifyGlobalCluster (..),
    newModifyGlobalCluster,

    -- * Request Lenses
    modifyGlobalCluster_deletionProtection,
    modifyGlobalCluster_newGlobalClusterIdentifier,
    modifyGlobalCluster_globalClusterIdentifier,

    -- * 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 Amazonka.DocumentDB.Types
import qualified Amazonka.Prelude as Prelude
import qualified Amazonka.Request as Request
import qualified Amazonka.Response as Response

-- | Represents the input to ModifyGlobalCluster.
--
-- /See:/ 'newModifyGlobalCluster' smart constructor.
data ModifyGlobalCluster = ModifyGlobalCluster'
  { -- | Indicates if the global cluster has deletion protection enabled. The
    -- global cluster can\'t be deleted when deletion protection is enabled.
    ModifyGlobalCluster -> Maybe Bool
deletionProtection :: Prelude.Maybe Prelude.Bool,
    -- | The new identifier for a global cluster when you modify a global
    -- cluster. This value is stored as a lowercase string.
    --
    -- -   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,
    -- | The identifier for the global cluster being modified. This parameter
    -- isn\'t case-sensitive.
    --
    -- Constraints:
    --
    -- -   Must match the identifier of an existing global cluster.
    ModifyGlobalCluster -> Text
globalClusterIdentifier :: 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:
--
-- 'deletionProtection', 'modifyGlobalCluster_deletionProtection' - Indicates if the global cluster has deletion protection enabled. The
-- global cluster can\'t be deleted when deletion protection is enabled.
--
-- 'newGlobalClusterIdentifier'', 'modifyGlobalCluster_newGlobalClusterIdentifier' - The new identifier for a global cluster when you modify a global
-- cluster. This value is stored as a lowercase string.
--
-- -   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@
--
-- 'globalClusterIdentifier', 'modifyGlobalCluster_globalClusterIdentifier' - The identifier for the global cluster being modified. This parameter
-- isn\'t case-sensitive.
--
-- Constraints:
--
-- -   Must match the identifier of an existing global cluster.
newModifyGlobalCluster ::
  -- | 'globalClusterIdentifier'
  Prelude.Text ->
  ModifyGlobalCluster
newModifyGlobalCluster :: Text -> ModifyGlobalCluster
newModifyGlobalCluster Text
pGlobalClusterIdentifier_ =
  ModifyGlobalCluster'
    { $sel:deletionProtection:ModifyGlobalCluster' :: Maybe Bool
deletionProtection =
        forall a. Maybe a
Prelude.Nothing,
      $sel:newGlobalClusterIdentifier':ModifyGlobalCluster' :: Maybe Text
newGlobalClusterIdentifier' = forall a. Maybe a
Prelude.Nothing,
      $sel:globalClusterIdentifier:ModifyGlobalCluster' :: Text
globalClusterIdentifier = Text
pGlobalClusterIdentifier_
    }

-- | Indicates if the global cluster has deletion protection enabled. The
-- global 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 new identifier for a global cluster when you modify a global
-- cluster. This value is stored as a lowercase string.
--
-- -   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)

-- | The identifier for the global cluster being modified. This parameter
-- isn\'t case-sensitive.
--
-- Constraints:
--
-- -   Must match the identifier of an existing global cluster.
modifyGlobalCluster_globalClusterIdentifier :: Lens.Lens' ModifyGlobalCluster Prelude.Text
modifyGlobalCluster_globalClusterIdentifier :: Lens' ModifyGlobalCluster Text
modifyGlobalCluster_globalClusterIdentifier = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\ModifyGlobalCluster' {Text
globalClusterIdentifier :: Text
$sel:globalClusterIdentifier:ModifyGlobalCluster' :: ModifyGlobalCluster -> Text
globalClusterIdentifier} -> Text
globalClusterIdentifier) (\s :: ModifyGlobalCluster
s@ModifyGlobalCluster' {} Text
a -> ModifyGlobalCluster
s {$sel:globalClusterIdentifier:ModifyGlobalCluster' :: Text
globalClusterIdentifier = 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
Text
globalClusterIdentifier :: Text
newGlobalClusterIdentifier' :: Maybe Text
deletionProtection :: Maybe Bool
$sel:globalClusterIdentifier:ModifyGlobalCluster' :: ModifyGlobalCluster -> Text
$sel:newGlobalClusterIdentifier':ModifyGlobalCluster' :: ModifyGlobalCluster -> Maybe Text
$sel:deletionProtection:ModifyGlobalCluster' :: ModifyGlobalCluster -> Maybe Bool
..} =
    Int
_salt
      forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Maybe Bool
deletionProtection
      forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Maybe Text
newGlobalClusterIdentifier'
      forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Text
globalClusterIdentifier

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

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
Text
globalClusterIdentifier :: Text
newGlobalClusterIdentifier' :: Maybe Text
deletionProtection :: Maybe Bool
$sel:globalClusterIdentifier:ModifyGlobalCluster' :: ModifyGlobalCluster -> Text
$sel:newGlobalClusterIdentifier':ModifyGlobalCluster' :: ModifyGlobalCluster -> Maybe Text
$sel:deletionProtection: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
"DeletionProtection" forall a. ToQuery a => ByteString -> a -> QueryString
Data.=: Maybe Bool
deletionProtection,
        ByteString
"NewGlobalClusterIdentifier"
          forall a. ToQuery a => ByteString -> a -> QueryString
Data.=: Maybe Text
newGlobalClusterIdentifier',
        ByteString
"GlobalClusterIdentifier"
          forall a. ToQuery a => ByteString -> a -> QueryString
Data.=: Text
globalClusterIdentifier
      ]

-- | /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