{-# 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.DeleteBlueGreenDeployment
-- Copyright   : (c) 2013-2023 Brendan Hay
-- License     : Mozilla Public License, v. 2.0.
-- Maintainer  : Brendan Hay
-- Stability   : auto-generated
-- Portability : non-portable (GHC extensions)
--
-- Deletes a blue\/green deployment.
--
-- For more information, see
-- <https://docs.aws.amazon.com/AmazonRDS/latest/UserGuide/blue-green-deployments.html Using Amazon RDS Blue\/Green Deployments for database updates>
-- in the /Amazon RDS User Guide/ and
-- <https://docs.aws.amazon.com/AmazonRDS/latest/AuroraUserGuide/blue-green-deployments.html Using Amazon RDS Blue\/Green Deployments for database updates>
-- in the /Amazon Aurora User Guide/.
module Amazonka.RDS.DeleteBlueGreenDeployment
  ( -- * Creating a Request
    DeleteBlueGreenDeployment (..),
    newDeleteBlueGreenDeployment,

    -- * Request Lenses
    deleteBlueGreenDeployment_deleteTarget,
    deleteBlueGreenDeployment_blueGreenDeploymentIdentifier,

    -- * Destructuring the Response
    DeleteBlueGreenDeploymentResponse (..),
    newDeleteBlueGreenDeploymentResponse,

    -- * Response Lenses
    deleteBlueGreenDeploymentResponse_blueGreenDeployment,
    deleteBlueGreenDeploymentResponse_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:/ 'newDeleteBlueGreenDeployment' smart constructor.
data DeleteBlueGreenDeployment = DeleteBlueGreenDeployment'
  { -- | A value that indicates whether to delete the resources in the green
    -- environment.
    DeleteBlueGreenDeployment -> Maybe Bool
deleteTarget :: Prelude.Maybe Prelude.Bool,
    -- | The blue\/green deployment identifier of the deployment to be deleted.
    -- This parameter isn\'t case-sensitive.
    --
    -- Constraints:
    --
    -- -   Must match an existing blue\/green deployment identifier.
    DeleteBlueGreenDeployment -> Text
blueGreenDeploymentIdentifier :: Prelude.Text
  }
  deriving (DeleteBlueGreenDeployment -> DeleteBlueGreenDeployment -> Bool
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: DeleteBlueGreenDeployment -> DeleteBlueGreenDeployment -> Bool
$c/= :: DeleteBlueGreenDeployment -> DeleteBlueGreenDeployment -> Bool
== :: DeleteBlueGreenDeployment -> DeleteBlueGreenDeployment -> Bool
$c== :: DeleteBlueGreenDeployment -> DeleteBlueGreenDeployment -> Bool
Prelude.Eq, ReadPrec [DeleteBlueGreenDeployment]
ReadPrec DeleteBlueGreenDeployment
Int -> ReadS DeleteBlueGreenDeployment
ReadS [DeleteBlueGreenDeployment]
forall a.
(Int -> ReadS a)
-> ReadS [a] -> ReadPrec a -> ReadPrec [a] -> Read a
readListPrec :: ReadPrec [DeleteBlueGreenDeployment]
$creadListPrec :: ReadPrec [DeleteBlueGreenDeployment]
readPrec :: ReadPrec DeleteBlueGreenDeployment
$creadPrec :: ReadPrec DeleteBlueGreenDeployment
readList :: ReadS [DeleteBlueGreenDeployment]
$creadList :: ReadS [DeleteBlueGreenDeployment]
readsPrec :: Int -> ReadS DeleteBlueGreenDeployment
$creadsPrec :: Int -> ReadS DeleteBlueGreenDeployment
Prelude.Read, Int -> DeleteBlueGreenDeployment -> ShowS
[DeleteBlueGreenDeployment] -> ShowS
DeleteBlueGreenDeployment -> String
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [DeleteBlueGreenDeployment] -> ShowS
$cshowList :: [DeleteBlueGreenDeployment] -> ShowS
show :: DeleteBlueGreenDeployment -> String
$cshow :: DeleteBlueGreenDeployment -> String
showsPrec :: Int -> DeleteBlueGreenDeployment -> ShowS
$cshowsPrec :: Int -> DeleteBlueGreenDeployment -> ShowS
Prelude.Show, forall x.
Rep DeleteBlueGreenDeployment x -> DeleteBlueGreenDeployment
forall x.
DeleteBlueGreenDeployment -> Rep DeleteBlueGreenDeployment x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cto :: forall x.
Rep DeleteBlueGreenDeployment x -> DeleteBlueGreenDeployment
$cfrom :: forall x.
DeleteBlueGreenDeployment -> Rep DeleteBlueGreenDeployment x
Prelude.Generic)

-- |
-- Create a value of 'DeleteBlueGreenDeployment' 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:
--
-- 'deleteTarget', 'deleteBlueGreenDeployment_deleteTarget' - A value that indicates whether to delete the resources in the green
-- environment.
--
-- 'blueGreenDeploymentIdentifier', 'deleteBlueGreenDeployment_blueGreenDeploymentIdentifier' - The blue\/green deployment identifier of the deployment to be deleted.
-- This parameter isn\'t case-sensitive.
--
-- Constraints:
--
-- -   Must match an existing blue\/green deployment identifier.
newDeleteBlueGreenDeployment ::
  -- | 'blueGreenDeploymentIdentifier'
  Prelude.Text ->
  DeleteBlueGreenDeployment
newDeleteBlueGreenDeployment :: Text -> DeleteBlueGreenDeployment
newDeleteBlueGreenDeployment
  Text
pBlueGreenDeploymentIdentifier_ =
    DeleteBlueGreenDeployment'
      { $sel:deleteTarget:DeleteBlueGreenDeployment' :: Maybe Bool
deleteTarget =
          forall a. Maybe a
Prelude.Nothing,
        $sel:blueGreenDeploymentIdentifier:DeleteBlueGreenDeployment' :: Text
blueGreenDeploymentIdentifier =
          Text
pBlueGreenDeploymentIdentifier_
      }

-- | A value that indicates whether to delete the resources in the green
-- environment.
deleteBlueGreenDeployment_deleteTarget :: Lens.Lens' DeleteBlueGreenDeployment (Prelude.Maybe Prelude.Bool)
deleteBlueGreenDeployment_deleteTarget :: Lens' DeleteBlueGreenDeployment (Maybe Bool)
deleteBlueGreenDeployment_deleteTarget = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\DeleteBlueGreenDeployment' {Maybe Bool
deleteTarget :: Maybe Bool
$sel:deleteTarget:DeleteBlueGreenDeployment' :: DeleteBlueGreenDeployment -> Maybe Bool
deleteTarget} -> Maybe Bool
deleteTarget) (\s :: DeleteBlueGreenDeployment
s@DeleteBlueGreenDeployment' {} Maybe Bool
a -> DeleteBlueGreenDeployment
s {$sel:deleteTarget:DeleteBlueGreenDeployment' :: Maybe Bool
deleteTarget = Maybe Bool
a} :: DeleteBlueGreenDeployment)

-- | The blue\/green deployment identifier of the deployment to be deleted.
-- This parameter isn\'t case-sensitive.
--
-- Constraints:
--
-- -   Must match an existing blue\/green deployment identifier.
deleteBlueGreenDeployment_blueGreenDeploymentIdentifier :: Lens.Lens' DeleteBlueGreenDeployment Prelude.Text
deleteBlueGreenDeployment_blueGreenDeploymentIdentifier :: Lens' DeleteBlueGreenDeployment Text
deleteBlueGreenDeployment_blueGreenDeploymentIdentifier = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\DeleteBlueGreenDeployment' {Text
blueGreenDeploymentIdentifier :: Text
$sel:blueGreenDeploymentIdentifier:DeleteBlueGreenDeployment' :: DeleteBlueGreenDeployment -> Text
blueGreenDeploymentIdentifier} -> Text
blueGreenDeploymentIdentifier) (\s :: DeleteBlueGreenDeployment
s@DeleteBlueGreenDeployment' {} Text
a -> DeleteBlueGreenDeployment
s {$sel:blueGreenDeploymentIdentifier:DeleteBlueGreenDeployment' :: Text
blueGreenDeploymentIdentifier = Text
a} :: DeleteBlueGreenDeployment)

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

instance Prelude.NFData DeleteBlueGreenDeployment where
  rnf :: DeleteBlueGreenDeployment -> ()
rnf DeleteBlueGreenDeployment' {Maybe Bool
Text
blueGreenDeploymentIdentifier :: Text
deleteTarget :: Maybe Bool
$sel:blueGreenDeploymentIdentifier:DeleteBlueGreenDeployment' :: DeleteBlueGreenDeployment -> Text
$sel:deleteTarget:DeleteBlueGreenDeployment' :: DeleteBlueGreenDeployment -> Maybe Bool
..} =
    forall a. NFData a => a -> ()
Prelude.rnf Maybe Bool
deleteTarget
      seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf Text
blueGreenDeploymentIdentifier

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

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

instance Data.ToQuery DeleteBlueGreenDeployment where
  toQuery :: DeleteBlueGreenDeployment -> QueryString
toQuery DeleteBlueGreenDeployment' {Maybe Bool
Text
blueGreenDeploymentIdentifier :: Text
deleteTarget :: Maybe Bool
$sel:blueGreenDeploymentIdentifier:DeleteBlueGreenDeployment' :: DeleteBlueGreenDeployment -> Text
$sel:deleteTarget:DeleteBlueGreenDeployment' :: DeleteBlueGreenDeployment -> Maybe Bool
..} =
    forall a. Monoid a => [a] -> a
Prelude.mconcat
      [ ByteString
"Action"
          forall a. ToQuery a => ByteString -> a -> QueryString
Data.=: (ByteString
"DeleteBlueGreenDeployment" :: Prelude.ByteString),
        ByteString
"Version"
          forall a. ToQuery a => ByteString -> a -> QueryString
Data.=: (ByteString
"2014-10-31" :: Prelude.ByteString),
        ByteString
"DeleteTarget" forall a. ToQuery a => ByteString -> a -> QueryString
Data.=: Maybe Bool
deleteTarget,
        ByteString
"BlueGreenDeploymentIdentifier"
          forall a. ToQuery a => ByteString -> a -> QueryString
Data.=: Text
blueGreenDeploymentIdentifier
      ]

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

-- |
-- Create a value of 'DeleteBlueGreenDeploymentResponse' 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:
--
-- 'blueGreenDeployment', 'deleteBlueGreenDeploymentResponse_blueGreenDeployment' - Undocumented member.
--
-- 'httpStatus', 'deleteBlueGreenDeploymentResponse_httpStatus' - The response's http status code.
newDeleteBlueGreenDeploymentResponse ::
  -- | 'httpStatus'
  Prelude.Int ->
  DeleteBlueGreenDeploymentResponse
newDeleteBlueGreenDeploymentResponse :: Int -> DeleteBlueGreenDeploymentResponse
newDeleteBlueGreenDeploymentResponse Int
pHttpStatus_ =
  DeleteBlueGreenDeploymentResponse'
    { $sel:blueGreenDeployment:DeleteBlueGreenDeploymentResponse' :: Maybe BlueGreenDeployment
blueGreenDeployment =
        forall a. Maybe a
Prelude.Nothing,
      $sel:httpStatus:DeleteBlueGreenDeploymentResponse' :: Int
httpStatus = Int
pHttpStatus_
    }

-- | Undocumented member.
deleteBlueGreenDeploymentResponse_blueGreenDeployment :: Lens.Lens' DeleteBlueGreenDeploymentResponse (Prelude.Maybe BlueGreenDeployment)
deleteBlueGreenDeploymentResponse_blueGreenDeployment :: Lens' DeleteBlueGreenDeploymentResponse (Maybe BlueGreenDeployment)
deleteBlueGreenDeploymentResponse_blueGreenDeployment = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\DeleteBlueGreenDeploymentResponse' {Maybe BlueGreenDeployment
blueGreenDeployment :: Maybe BlueGreenDeployment
$sel:blueGreenDeployment:DeleteBlueGreenDeploymentResponse' :: DeleteBlueGreenDeploymentResponse -> Maybe BlueGreenDeployment
blueGreenDeployment} -> Maybe BlueGreenDeployment
blueGreenDeployment) (\s :: DeleteBlueGreenDeploymentResponse
s@DeleteBlueGreenDeploymentResponse' {} Maybe BlueGreenDeployment
a -> DeleteBlueGreenDeploymentResponse
s {$sel:blueGreenDeployment:DeleteBlueGreenDeploymentResponse' :: Maybe BlueGreenDeployment
blueGreenDeployment = Maybe BlueGreenDeployment
a} :: DeleteBlueGreenDeploymentResponse)

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

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