{-# 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.FailoverGlobalCluster
-- Copyright   : (c) 2013-2023 Brendan Hay
-- License     : Mozilla Public License, v. 2.0.
-- Maintainer  : Brendan Hay
-- Stability   : auto-generated
-- Portability : non-portable (GHC extensions)
--
-- Initiates the failover process for an Aurora global database
-- (GlobalCluster).
--
-- A failover for an Aurora global database promotes one of secondary
-- read-only DB clusters to be the primary DB cluster and demotes the
-- primary DB cluster to being a secondary (read-only) DB cluster. In other
-- words, the role of the current primary DB cluster and the selected
-- (target) DB cluster are switched. The selected secondary DB cluster
-- assumes full read\/write capabilities for the Aurora global database.
--
-- For more information about failing over an Amazon Aurora global
-- database, see
-- <https://docs.aws.amazon.com/AmazonRDS/latest/AuroraUserGuide/aurora-global-database-disaster-recovery.html#aurora-global-database-disaster-recovery.managed-failover Managed planned failover for Amazon Aurora global databases>
-- in the /Amazon Aurora User Guide/.
--
-- This action applies to GlobalCluster (Aurora global databases) only. Use
-- this action only on healthy Aurora global databases with running Aurora
-- DB clusters and no Region-wide outages, to test disaster recovery
-- scenarios or to reconfigure your Aurora global database topology.
module Amazonka.RDS.FailoverGlobalCluster
  ( -- * Creating a Request
    FailoverGlobalCluster (..),
    newFailoverGlobalCluster,

    -- * Request Lenses
    failoverGlobalCluster_globalClusterIdentifier,
    failoverGlobalCluster_targetDbClusterIdentifier,

    -- * Destructuring the Response
    FailoverGlobalClusterResponse (..),
    newFailoverGlobalClusterResponse,

    -- * Response Lenses
    failoverGlobalClusterResponse_globalCluster,
    failoverGlobalClusterResponse_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:/ 'newFailoverGlobalCluster' smart constructor.
data FailoverGlobalCluster = FailoverGlobalCluster'
  { -- | Identifier of the Aurora global database (GlobalCluster) that should be
    -- failed over. The identifier is the unique key assigned by the user when
    -- the Aurora global database was created. In other words, it\'s the name
    -- of the Aurora global database that you want to fail over.
    --
    -- Constraints:
    --
    -- -   Must match the identifier of an existing GlobalCluster (Aurora
    --     global database).
    FailoverGlobalCluster -> Text
globalClusterIdentifier :: Prelude.Text,
    -- | Identifier of the secondary Aurora DB cluster that you want to promote
    -- to primary for the Aurora global database (GlobalCluster.) Use the
    -- Amazon Resource Name (ARN) for the identifier so that Aurora can locate
    -- the cluster in its Amazon Web Services Region.
    FailoverGlobalCluster -> Text
targetDbClusterIdentifier :: Prelude.Text
  }
  deriving (FailoverGlobalCluster -> FailoverGlobalCluster -> Bool
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: FailoverGlobalCluster -> FailoverGlobalCluster -> Bool
$c/= :: FailoverGlobalCluster -> FailoverGlobalCluster -> Bool
== :: FailoverGlobalCluster -> FailoverGlobalCluster -> Bool
$c== :: FailoverGlobalCluster -> FailoverGlobalCluster -> Bool
Prelude.Eq, ReadPrec [FailoverGlobalCluster]
ReadPrec FailoverGlobalCluster
Int -> ReadS FailoverGlobalCluster
ReadS [FailoverGlobalCluster]
forall a.
(Int -> ReadS a)
-> ReadS [a] -> ReadPrec a -> ReadPrec [a] -> Read a
readListPrec :: ReadPrec [FailoverGlobalCluster]
$creadListPrec :: ReadPrec [FailoverGlobalCluster]
readPrec :: ReadPrec FailoverGlobalCluster
$creadPrec :: ReadPrec FailoverGlobalCluster
readList :: ReadS [FailoverGlobalCluster]
$creadList :: ReadS [FailoverGlobalCluster]
readsPrec :: Int -> ReadS FailoverGlobalCluster
$creadsPrec :: Int -> ReadS FailoverGlobalCluster
Prelude.Read, Int -> FailoverGlobalCluster -> ShowS
[FailoverGlobalCluster] -> ShowS
FailoverGlobalCluster -> String
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [FailoverGlobalCluster] -> ShowS
$cshowList :: [FailoverGlobalCluster] -> ShowS
show :: FailoverGlobalCluster -> String
$cshow :: FailoverGlobalCluster -> String
showsPrec :: Int -> FailoverGlobalCluster -> ShowS
$cshowsPrec :: Int -> FailoverGlobalCluster -> ShowS
Prelude.Show, forall x. Rep FailoverGlobalCluster x -> FailoverGlobalCluster
forall x. FailoverGlobalCluster -> Rep FailoverGlobalCluster x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cto :: forall x. Rep FailoverGlobalCluster x -> FailoverGlobalCluster
$cfrom :: forall x. FailoverGlobalCluster -> Rep FailoverGlobalCluster x
Prelude.Generic)

-- |
-- Create a value of 'FailoverGlobalCluster' 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:
--
-- 'globalClusterIdentifier', 'failoverGlobalCluster_globalClusterIdentifier' - Identifier of the Aurora global database (GlobalCluster) that should be
-- failed over. The identifier is the unique key assigned by the user when
-- the Aurora global database was created. In other words, it\'s the name
-- of the Aurora global database that you want to fail over.
--
-- Constraints:
--
-- -   Must match the identifier of an existing GlobalCluster (Aurora
--     global database).
--
-- 'targetDbClusterIdentifier', 'failoverGlobalCluster_targetDbClusterIdentifier' - Identifier of the secondary Aurora DB cluster that you want to promote
-- to primary for the Aurora global database (GlobalCluster.) Use the
-- Amazon Resource Name (ARN) for the identifier so that Aurora can locate
-- the cluster in its Amazon Web Services Region.
newFailoverGlobalCluster ::
  -- | 'globalClusterIdentifier'
  Prelude.Text ->
  -- | 'targetDbClusterIdentifier'
  Prelude.Text ->
  FailoverGlobalCluster
newFailoverGlobalCluster :: Text -> Text -> FailoverGlobalCluster
newFailoverGlobalCluster
  Text
pGlobalClusterIdentifier_
  Text
pTargetDbClusterIdentifier_ =
    FailoverGlobalCluster'
      { $sel:globalClusterIdentifier:FailoverGlobalCluster' :: Text
globalClusterIdentifier =
          Text
pGlobalClusterIdentifier_,
        $sel:targetDbClusterIdentifier:FailoverGlobalCluster' :: Text
targetDbClusterIdentifier =
          Text
pTargetDbClusterIdentifier_
      }

-- | Identifier of the Aurora global database (GlobalCluster) that should be
-- failed over. The identifier is the unique key assigned by the user when
-- the Aurora global database was created. In other words, it\'s the name
-- of the Aurora global database that you want to fail over.
--
-- Constraints:
--
-- -   Must match the identifier of an existing GlobalCluster (Aurora
--     global database).
failoverGlobalCluster_globalClusterIdentifier :: Lens.Lens' FailoverGlobalCluster Prelude.Text
failoverGlobalCluster_globalClusterIdentifier :: Lens' FailoverGlobalCluster Text
failoverGlobalCluster_globalClusterIdentifier = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\FailoverGlobalCluster' {Text
globalClusterIdentifier :: Text
$sel:globalClusterIdentifier:FailoverGlobalCluster' :: FailoverGlobalCluster -> Text
globalClusterIdentifier} -> Text
globalClusterIdentifier) (\s :: FailoverGlobalCluster
s@FailoverGlobalCluster' {} Text
a -> FailoverGlobalCluster
s {$sel:globalClusterIdentifier:FailoverGlobalCluster' :: Text
globalClusterIdentifier = Text
a} :: FailoverGlobalCluster)

-- | Identifier of the secondary Aurora DB cluster that you want to promote
-- to primary for the Aurora global database (GlobalCluster.) Use the
-- Amazon Resource Name (ARN) for the identifier so that Aurora can locate
-- the cluster in its Amazon Web Services Region.
failoverGlobalCluster_targetDbClusterIdentifier :: Lens.Lens' FailoverGlobalCluster Prelude.Text
failoverGlobalCluster_targetDbClusterIdentifier :: Lens' FailoverGlobalCluster Text
failoverGlobalCluster_targetDbClusterIdentifier = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\FailoverGlobalCluster' {Text
targetDbClusterIdentifier :: Text
$sel:targetDbClusterIdentifier:FailoverGlobalCluster' :: FailoverGlobalCluster -> Text
targetDbClusterIdentifier} -> Text
targetDbClusterIdentifier) (\s :: FailoverGlobalCluster
s@FailoverGlobalCluster' {} Text
a -> FailoverGlobalCluster
s {$sel:targetDbClusterIdentifier:FailoverGlobalCluster' :: Text
targetDbClusterIdentifier = Text
a} :: FailoverGlobalCluster)

instance Core.AWSRequest FailoverGlobalCluster where
  type
    AWSResponse FailoverGlobalCluster =
      FailoverGlobalClusterResponse
  request :: (Service -> Service)
-> FailoverGlobalCluster -> Request FailoverGlobalCluster
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 FailoverGlobalCluster
-> ClientResponse ClientBody
-> m (Either
        Error (ClientResponse (AWSResponse FailoverGlobalCluster)))
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
"FailoverGlobalClusterResult"
      ( \Int
s ResponseHeaders
h [Node]
x ->
          Maybe GlobalCluster -> Int -> FailoverGlobalClusterResponse
FailoverGlobalClusterResponse'
            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 FailoverGlobalCluster where
  hashWithSalt :: Int -> FailoverGlobalCluster -> Int
hashWithSalt Int
_salt FailoverGlobalCluster' {Text
targetDbClusterIdentifier :: Text
globalClusterIdentifier :: Text
$sel:targetDbClusterIdentifier:FailoverGlobalCluster' :: FailoverGlobalCluster -> Text
$sel:globalClusterIdentifier:FailoverGlobalCluster' :: FailoverGlobalCluster -> Text
..} =
    Int
_salt
      forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Text
globalClusterIdentifier
      forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Text
targetDbClusterIdentifier

instance Prelude.NFData FailoverGlobalCluster where
  rnf :: FailoverGlobalCluster -> ()
rnf FailoverGlobalCluster' {Text
targetDbClusterIdentifier :: Text
globalClusterIdentifier :: Text
$sel:targetDbClusterIdentifier:FailoverGlobalCluster' :: FailoverGlobalCluster -> Text
$sel:globalClusterIdentifier:FailoverGlobalCluster' :: FailoverGlobalCluster -> Text
..} =
    forall a. NFData a => a -> ()
Prelude.rnf Text
globalClusterIdentifier
      seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf Text
targetDbClusterIdentifier

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

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

instance Data.ToQuery FailoverGlobalCluster where
  toQuery :: FailoverGlobalCluster -> QueryString
toQuery FailoverGlobalCluster' {Text
targetDbClusterIdentifier :: Text
globalClusterIdentifier :: Text
$sel:targetDbClusterIdentifier:FailoverGlobalCluster' :: FailoverGlobalCluster -> Text
$sel:globalClusterIdentifier:FailoverGlobalCluster' :: FailoverGlobalCluster -> Text
..} =
    forall a. Monoid a => [a] -> a
Prelude.mconcat
      [ ByteString
"Action"
          forall a. ToQuery a => ByteString -> a -> QueryString
Data.=: (ByteString
"FailoverGlobalCluster" :: Prelude.ByteString),
        ByteString
"Version"
          forall a. ToQuery a => ByteString -> a -> QueryString
Data.=: (ByteString
"2014-10-31" :: Prelude.ByteString),
        ByteString
"GlobalClusterIdentifier"
          forall a. ToQuery a => ByteString -> a -> QueryString
Data.=: Text
globalClusterIdentifier,
        ByteString
"TargetDbClusterIdentifier"
          forall a. ToQuery a => ByteString -> a -> QueryString
Data.=: Text
targetDbClusterIdentifier
      ]

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

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

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

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

instance Prelude.NFData FailoverGlobalClusterResponse where
  rnf :: FailoverGlobalClusterResponse -> ()
rnf FailoverGlobalClusterResponse' {Int
Maybe GlobalCluster
httpStatus :: Int
globalCluster :: Maybe GlobalCluster
$sel:httpStatus:FailoverGlobalClusterResponse' :: FailoverGlobalClusterResponse -> Int
$sel:globalCluster:FailoverGlobalClusterResponse' :: FailoverGlobalClusterResponse -> 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