{-# 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.DeleteDBCluster
-- Copyright   : (c) 2013-2023 Brendan Hay
-- License     : Mozilla Public License, v. 2.0.
-- Maintainer  : Brendan Hay
-- Stability   : auto-generated
-- Portability : non-portable (GHC extensions)
--
-- The DeleteDBCluster action deletes a previously provisioned DB cluster.
-- When you delete a DB cluster, all automated backups for that DB cluster
-- are deleted and can\'t be recovered. Manual DB cluster snapshots of the
-- specified DB cluster are not deleted.
--
-- 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/.
--
-- For more information on Multi-AZ DB clusters, see
-- <https://docs.aws.amazon.com/AmazonRDS/latest/UserGuide/multi-az-db-clusters-concepts.html Multi-AZ deployments with two readable standby DB instances>
-- in the /Amazon RDS User Guide/.
module Amazonka.RDS.DeleteDBCluster
  ( -- * Creating a Request
    DeleteDBCluster (..),
    newDeleteDBCluster,

    -- * Request Lenses
    deleteDBCluster_finalDBSnapshotIdentifier,
    deleteDBCluster_skipFinalSnapshot,
    deleteDBCluster_dbClusterIdentifier,

    -- * Destructuring the Response
    DeleteDBClusterResponse (..),
    newDeleteDBClusterResponse,

    -- * Response Lenses
    deleteDBClusterResponse_dbCluster,
    deleteDBClusterResponse_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:/ 'newDeleteDBCluster' smart constructor.
data DeleteDBCluster = DeleteDBCluster'
  { -- | The DB cluster snapshot identifier of the new DB cluster snapshot
    -- created when @SkipFinalSnapshot@ is disabled.
    --
    -- Specifying this parameter and also skipping the creation of a final DB
    -- cluster snapshot with the @SkipFinalShapshot@ parameter results in an
    -- error.
    --
    -- Constraints:
    --
    -- -   Must be 1 to 255 letters, numbers, or hyphens.
    --
    -- -   First character must be a letter
    --
    -- -   Can\'t end with a hyphen or contain two consecutive hyphens
    DeleteDBCluster -> Maybe Text
finalDBSnapshotIdentifier :: Prelude.Maybe Prelude.Text,
    -- | A value that indicates whether to skip the creation of a final DB
    -- cluster snapshot before the DB cluster is deleted. If skip is specified,
    -- no DB cluster snapshot is created. If skip isn\'t specified, a DB
    -- cluster snapshot is created before the DB cluster is deleted. By
    -- default, skip isn\'t specified, and the DB cluster snapshot is created.
    -- By default, this parameter is disabled.
    --
    -- You must specify a @FinalDBSnapshotIdentifier@ parameter if
    -- @SkipFinalSnapshot@ is disabled.
    DeleteDBCluster -> Maybe Bool
skipFinalSnapshot :: Prelude.Maybe Prelude.Bool,
    -- | The DB cluster identifier for the DB cluster to be deleted. This
    -- parameter isn\'t case-sensitive.
    --
    -- Constraints:
    --
    -- -   Must match an existing DBClusterIdentifier.
    DeleteDBCluster -> Text
dbClusterIdentifier :: Prelude.Text
  }
  deriving (DeleteDBCluster -> DeleteDBCluster -> Bool
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: DeleteDBCluster -> DeleteDBCluster -> Bool
$c/= :: DeleteDBCluster -> DeleteDBCluster -> Bool
== :: DeleteDBCluster -> DeleteDBCluster -> Bool
$c== :: DeleteDBCluster -> DeleteDBCluster -> Bool
Prelude.Eq, ReadPrec [DeleteDBCluster]
ReadPrec DeleteDBCluster
Int -> ReadS DeleteDBCluster
ReadS [DeleteDBCluster]
forall a.
(Int -> ReadS a)
-> ReadS [a] -> ReadPrec a -> ReadPrec [a] -> Read a
readListPrec :: ReadPrec [DeleteDBCluster]
$creadListPrec :: ReadPrec [DeleteDBCluster]
readPrec :: ReadPrec DeleteDBCluster
$creadPrec :: ReadPrec DeleteDBCluster
readList :: ReadS [DeleteDBCluster]
$creadList :: ReadS [DeleteDBCluster]
readsPrec :: Int -> ReadS DeleteDBCluster
$creadsPrec :: Int -> ReadS DeleteDBCluster
Prelude.Read, Int -> DeleteDBCluster -> ShowS
[DeleteDBCluster] -> ShowS
DeleteDBCluster -> String
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [DeleteDBCluster] -> ShowS
$cshowList :: [DeleteDBCluster] -> ShowS
show :: DeleteDBCluster -> String
$cshow :: DeleteDBCluster -> String
showsPrec :: Int -> DeleteDBCluster -> ShowS
$cshowsPrec :: Int -> DeleteDBCluster -> ShowS
Prelude.Show, forall x. Rep DeleteDBCluster x -> DeleteDBCluster
forall x. DeleteDBCluster -> Rep DeleteDBCluster x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cto :: forall x. Rep DeleteDBCluster x -> DeleteDBCluster
$cfrom :: forall x. DeleteDBCluster -> Rep DeleteDBCluster x
Prelude.Generic)

-- |
-- Create a value of 'DeleteDBCluster' 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:
--
-- 'finalDBSnapshotIdentifier', 'deleteDBCluster_finalDBSnapshotIdentifier' - The DB cluster snapshot identifier of the new DB cluster snapshot
-- created when @SkipFinalSnapshot@ is disabled.
--
-- Specifying this parameter and also skipping the creation of a final DB
-- cluster snapshot with the @SkipFinalShapshot@ parameter results in an
-- error.
--
-- Constraints:
--
-- -   Must be 1 to 255 letters, numbers, or hyphens.
--
-- -   First character must be a letter
--
-- -   Can\'t end with a hyphen or contain two consecutive hyphens
--
-- 'skipFinalSnapshot', 'deleteDBCluster_skipFinalSnapshot' - A value that indicates whether to skip the creation of a final DB
-- cluster snapshot before the DB cluster is deleted. If skip is specified,
-- no DB cluster snapshot is created. If skip isn\'t specified, a DB
-- cluster snapshot is created before the DB cluster is deleted. By
-- default, skip isn\'t specified, and the DB cluster snapshot is created.
-- By default, this parameter is disabled.
--
-- You must specify a @FinalDBSnapshotIdentifier@ parameter if
-- @SkipFinalSnapshot@ is disabled.
--
-- 'dbClusterIdentifier', 'deleteDBCluster_dbClusterIdentifier' - The DB cluster identifier for the DB cluster to be deleted. This
-- parameter isn\'t case-sensitive.
--
-- Constraints:
--
-- -   Must match an existing DBClusterIdentifier.
newDeleteDBCluster ::
  -- | 'dbClusterIdentifier'
  Prelude.Text ->
  DeleteDBCluster
newDeleteDBCluster :: Text -> DeleteDBCluster
newDeleteDBCluster Text
pDBClusterIdentifier_ =
  DeleteDBCluster'
    { $sel:finalDBSnapshotIdentifier:DeleteDBCluster' :: Maybe Text
finalDBSnapshotIdentifier =
        forall a. Maybe a
Prelude.Nothing,
      $sel:skipFinalSnapshot:DeleteDBCluster' :: Maybe Bool
skipFinalSnapshot = forall a. Maybe a
Prelude.Nothing,
      $sel:dbClusterIdentifier:DeleteDBCluster' :: Text
dbClusterIdentifier = Text
pDBClusterIdentifier_
    }

-- | The DB cluster snapshot identifier of the new DB cluster snapshot
-- created when @SkipFinalSnapshot@ is disabled.
--
-- Specifying this parameter and also skipping the creation of a final DB
-- cluster snapshot with the @SkipFinalShapshot@ parameter results in an
-- error.
--
-- Constraints:
--
-- -   Must be 1 to 255 letters, numbers, or hyphens.
--
-- -   First character must be a letter
--
-- -   Can\'t end with a hyphen or contain two consecutive hyphens
deleteDBCluster_finalDBSnapshotIdentifier :: Lens.Lens' DeleteDBCluster (Prelude.Maybe Prelude.Text)
deleteDBCluster_finalDBSnapshotIdentifier :: Lens' DeleteDBCluster (Maybe Text)
deleteDBCluster_finalDBSnapshotIdentifier = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\DeleteDBCluster' {Maybe Text
finalDBSnapshotIdentifier :: Maybe Text
$sel:finalDBSnapshotIdentifier:DeleteDBCluster' :: DeleteDBCluster -> Maybe Text
finalDBSnapshotIdentifier} -> Maybe Text
finalDBSnapshotIdentifier) (\s :: DeleteDBCluster
s@DeleteDBCluster' {} Maybe Text
a -> DeleteDBCluster
s {$sel:finalDBSnapshotIdentifier:DeleteDBCluster' :: Maybe Text
finalDBSnapshotIdentifier = Maybe Text
a} :: DeleteDBCluster)

-- | A value that indicates whether to skip the creation of a final DB
-- cluster snapshot before the DB cluster is deleted. If skip is specified,
-- no DB cluster snapshot is created. If skip isn\'t specified, a DB
-- cluster snapshot is created before the DB cluster is deleted. By
-- default, skip isn\'t specified, and the DB cluster snapshot is created.
-- By default, this parameter is disabled.
--
-- You must specify a @FinalDBSnapshotIdentifier@ parameter if
-- @SkipFinalSnapshot@ is disabled.
deleteDBCluster_skipFinalSnapshot :: Lens.Lens' DeleteDBCluster (Prelude.Maybe Prelude.Bool)
deleteDBCluster_skipFinalSnapshot :: Lens' DeleteDBCluster (Maybe Bool)
deleteDBCluster_skipFinalSnapshot = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\DeleteDBCluster' {Maybe Bool
skipFinalSnapshot :: Maybe Bool
$sel:skipFinalSnapshot:DeleteDBCluster' :: DeleteDBCluster -> Maybe Bool
skipFinalSnapshot} -> Maybe Bool
skipFinalSnapshot) (\s :: DeleteDBCluster
s@DeleteDBCluster' {} Maybe Bool
a -> DeleteDBCluster
s {$sel:skipFinalSnapshot:DeleteDBCluster' :: Maybe Bool
skipFinalSnapshot = Maybe Bool
a} :: DeleteDBCluster)

-- | The DB cluster identifier for the DB cluster to be deleted. This
-- parameter isn\'t case-sensitive.
--
-- Constraints:
--
-- -   Must match an existing DBClusterIdentifier.
deleteDBCluster_dbClusterIdentifier :: Lens.Lens' DeleteDBCluster Prelude.Text
deleteDBCluster_dbClusterIdentifier :: Lens' DeleteDBCluster Text
deleteDBCluster_dbClusterIdentifier = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\DeleteDBCluster' {Text
dbClusterIdentifier :: Text
$sel:dbClusterIdentifier:DeleteDBCluster' :: DeleteDBCluster -> Text
dbClusterIdentifier} -> Text
dbClusterIdentifier) (\s :: DeleteDBCluster
s@DeleteDBCluster' {} Text
a -> DeleteDBCluster
s {$sel:dbClusterIdentifier:DeleteDBCluster' :: Text
dbClusterIdentifier = Text
a} :: DeleteDBCluster)

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

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

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

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

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

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

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

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

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

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