{-# 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.FailoverDBCluster
-- Copyright   : (c) 2013-2023 Brendan Hay
-- License     : Mozilla Public License, v. 2.0.
-- Maintainer  : Brendan Hay
-- Stability   : auto-generated
-- Portability : non-portable (GHC extensions)
--
-- Forces a failover for a cluster.
--
-- A failover for a cluster promotes one of the Amazon DocumentDB replicas
-- (read-only instances) in the cluster to be the primary instance (the
-- cluster writer).
--
-- If the primary instance fails, Amazon DocumentDB automatically fails
-- over to an Amazon DocumentDB replica, if one exists. You can force a
-- failover when you want to simulate a failure of a primary instance for
-- testing.
module Amazonka.DocumentDB.FailoverDBCluster
  ( -- * Creating a Request
    FailoverDBCluster (..),
    newFailoverDBCluster,

    -- * Request Lenses
    failoverDBCluster_dbClusterIdentifier,
    failoverDBCluster_targetDBInstanceIdentifier,

    -- * Destructuring the Response
    FailoverDBClusterResponse (..),
    newFailoverDBClusterResponse,

    -- * Response Lenses
    failoverDBClusterResponse_dbCluster,
    failoverDBClusterResponse_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 FailoverDBCluster.
--
-- /See:/ 'newFailoverDBCluster' smart constructor.
data FailoverDBCluster = FailoverDBCluster'
  { -- | A cluster identifier to force a failover for. This parameter is not case
    -- sensitive.
    --
    -- Constraints:
    --
    -- -   Must match the identifier of an existing @DBCluster@.
    FailoverDBCluster -> Maybe Text
dbClusterIdentifier :: Prelude.Maybe Prelude.Text,
    -- | The name of the instance to promote to the primary instance.
    --
    -- You must specify the instance identifier for an Amazon DocumentDB
    -- replica in the cluster. For example, @mydbcluster-replica1@.
    FailoverDBCluster -> Maybe Text
targetDBInstanceIdentifier :: Prelude.Maybe Prelude.Text
  }
  deriving (FailoverDBCluster -> FailoverDBCluster -> Bool
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: FailoverDBCluster -> FailoverDBCluster -> Bool
$c/= :: FailoverDBCluster -> FailoverDBCluster -> Bool
== :: FailoverDBCluster -> FailoverDBCluster -> Bool
$c== :: FailoverDBCluster -> FailoverDBCluster -> Bool
Prelude.Eq, ReadPrec [FailoverDBCluster]
ReadPrec FailoverDBCluster
Int -> ReadS FailoverDBCluster
ReadS [FailoverDBCluster]
forall a.
(Int -> ReadS a)
-> ReadS [a] -> ReadPrec a -> ReadPrec [a] -> Read a
readListPrec :: ReadPrec [FailoverDBCluster]
$creadListPrec :: ReadPrec [FailoverDBCluster]
readPrec :: ReadPrec FailoverDBCluster
$creadPrec :: ReadPrec FailoverDBCluster
readList :: ReadS [FailoverDBCluster]
$creadList :: ReadS [FailoverDBCluster]
readsPrec :: Int -> ReadS FailoverDBCluster
$creadsPrec :: Int -> ReadS FailoverDBCluster
Prelude.Read, Int -> FailoverDBCluster -> ShowS
[FailoverDBCluster] -> ShowS
FailoverDBCluster -> String
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [FailoverDBCluster] -> ShowS
$cshowList :: [FailoverDBCluster] -> ShowS
show :: FailoverDBCluster -> String
$cshow :: FailoverDBCluster -> String
showsPrec :: Int -> FailoverDBCluster -> ShowS
$cshowsPrec :: Int -> FailoverDBCluster -> ShowS
Prelude.Show, forall x. Rep FailoverDBCluster x -> FailoverDBCluster
forall x. FailoverDBCluster -> Rep FailoverDBCluster x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cto :: forall x. Rep FailoverDBCluster x -> FailoverDBCluster
$cfrom :: forall x. FailoverDBCluster -> Rep FailoverDBCluster x
Prelude.Generic)

-- |
-- Create a value of 'FailoverDBCluster' 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:
--
-- 'dbClusterIdentifier', 'failoverDBCluster_dbClusterIdentifier' - A cluster identifier to force a failover for. This parameter is not case
-- sensitive.
--
-- Constraints:
--
-- -   Must match the identifier of an existing @DBCluster@.
--
-- 'targetDBInstanceIdentifier', 'failoverDBCluster_targetDBInstanceIdentifier' - The name of the instance to promote to the primary instance.
--
-- You must specify the instance identifier for an Amazon DocumentDB
-- replica in the cluster. For example, @mydbcluster-replica1@.
newFailoverDBCluster ::
  FailoverDBCluster
newFailoverDBCluster :: FailoverDBCluster
newFailoverDBCluster =
  FailoverDBCluster'
    { $sel:dbClusterIdentifier:FailoverDBCluster' :: Maybe Text
dbClusterIdentifier =
        forall a. Maybe a
Prelude.Nothing,
      $sel:targetDBInstanceIdentifier:FailoverDBCluster' :: Maybe Text
targetDBInstanceIdentifier = forall a. Maybe a
Prelude.Nothing
    }

-- | A cluster identifier to force a failover for. This parameter is not case
-- sensitive.
--
-- Constraints:
--
-- -   Must match the identifier of an existing @DBCluster@.
failoverDBCluster_dbClusterIdentifier :: Lens.Lens' FailoverDBCluster (Prelude.Maybe Prelude.Text)
failoverDBCluster_dbClusterIdentifier :: Lens' FailoverDBCluster (Maybe Text)
failoverDBCluster_dbClusterIdentifier = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\FailoverDBCluster' {Maybe Text
dbClusterIdentifier :: Maybe Text
$sel:dbClusterIdentifier:FailoverDBCluster' :: FailoverDBCluster -> Maybe Text
dbClusterIdentifier} -> Maybe Text
dbClusterIdentifier) (\s :: FailoverDBCluster
s@FailoverDBCluster' {} Maybe Text
a -> FailoverDBCluster
s {$sel:dbClusterIdentifier:FailoverDBCluster' :: Maybe Text
dbClusterIdentifier = Maybe Text
a} :: FailoverDBCluster)

-- | The name of the instance to promote to the primary instance.
--
-- You must specify the instance identifier for an Amazon DocumentDB
-- replica in the cluster. For example, @mydbcluster-replica1@.
failoverDBCluster_targetDBInstanceIdentifier :: Lens.Lens' FailoverDBCluster (Prelude.Maybe Prelude.Text)
failoverDBCluster_targetDBInstanceIdentifier :: Lens' FailoverDBCluster (Maybe Text)
failoverDBCluster_targetDBInstanceIdentifier = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\FailoverDBCluster' {Maybe Text
targetDBInstanceIdentifier :: Maybe Text
$sel:targetDBInstanceIdentifier:FailoverDBCluster' :: FailoverDBCluster -> Maybe Text
targetDBInstanceIdentifier} -> Maybe Text
targetDBInstanceIdentifier) (\s :: FailoverDBCluster
s@FailoverDBCluster' {} Maybe Text
a -> FailoverDBCluster
s {$sel:targetDBInstanceIdentifier:FailoverDBCluster' :: Maybe Text
targetDBInstanceIdentifier = Maybe Text
a} :: FailoverDBCluster)

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

instance Prelude.NFData FailoverDBCluster where
  rnf :: FailoverDBCluster -> ()
rnf FailoverDBCluster' {Maybe Text
targetDBInstanceIdentifier :: Maybe Text
dbClusterIdentifier :: Maybe Text
$sel:targetDBInstanceIdentifier:FailoverDBCluster' :: FailoverDBCluster -> Maybe Text
$sel:dbClusterIdentifier:FailoverDBCluster' :: FailoverDBCluster -> Maybe Text
..} =
    forall a. NFData a => a -> ()
Prelude.rnf Maybe Text
dbClusterIdentifier
      seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf Maybe Text
targetDBInstanceIdentifier

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

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

instance Data.ToQuery FailoverDBCluster where
  toQuery :: FailoverDBCluster -> QueryString
toQuery FailoverDBCluster' {Maybe Text
targetDBInstanceIdentifier :: Maybe Text
dbClusterIdentifier :: Maybe Text
$sel:targetDBInstanceIdentifier:FailoverDBCluster' :: FailoverDBCluster -> Maybe Text
$sel:dbClusterIdentifier:FailoverDBCluster' :: FailoverDBCluster -> Maybe Text
..} =
    forall a. Monoid a => [a] -> a
Prelude.mconcat
      [ ByteString
"Action"
          forall a. ToQuery a => ByteString -> a -> QueryString
Data.=: (ByteString
"FailoverDBCluster" :: Prelude.ByteString),
        ByteString
"Version"
          forall a. ToQuery a => ByteString -> a -> QueryString
Data.=: (ByteString
"2014-10-31" :: Prelude.ByteString),
        ByteString
"DBClusterIdentifier" forall a. ToQuery a => ByteString -> a -> QueryString
Data.=: Maybe Text
dbClusterIdentifier,
        ByteString
"TargetDBInstanceIdentifier"
          forall a. ToQuery a => ByteString -> a -> QueryString
Data.=: Maybe Text
targetDBInstanceIdentifier
      ]

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

-- |
-- Create a value of 'FailoverDBClusterResponse' 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:
--
-- 'dbCluster', 'failoverDBClusterResponse_dbCluster' - Undocumented member.
--
-- 'httpStatus', 'failoverDBClusterResponse_httpStatus' - The response's http status code.
newFailoverDBClusterResponse ::
  -- | 'httpStatus'
  Prelude.Int ->
  FailoverDBClusterResponse
newFailoverDBClusterResponse :: Int -> FailoverDBClusterResponse
newFailoverDBClusterResponse Int
pHttpStatus_ =
  FailoverDBClusterResponse'
    { $sel:dbCluster:FailoverDBClusterResponse' :: Maybe DBCluster
dbCluster =
        forall a. Maybe a
Prelude.Nothing,
      $sel:httpStatus:FailoverDBClusterResponse' :: Int
httpStatus = Int
pHttpStatus_
    }

-- | Undocumented member.
failoverDBClusterResponse_dbCluster :: Lens.Lens' FailoverDBClusterResponse (Prelude.Maybe DBCluster)
failoverDBClusterResponse_dbCluster :: Lens' FailoverDBClusterResponse (Maybe DBCluster)
failoverDBClusterResponse_dbCluster = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\FailoverDBClusterResponse' {Maybe DBCluster
dbCluster :: Maybe DBCluster
$sel:dbCluster:FailoverDBClusterResponse' :: FailoverDBClusterResponse -> Maybe DBCluster
dbCluster} -> Maybe DBCluster
dbCluster) (\s :: FailoverDBClusterResponse
s@FailoverDBClusterResponse' {} Maybe DBCluster
a -> FailoverDBClusterResponse
s {$sel:dbCluster:FailoverDBClusterResponse' :: Maybe DBCluster
dbCluster = Maybe DBCluster
a} :: FailoverDBClusterResponse)

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

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