{-# 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.DeleteCustomDBEngineVersion
-- 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 custom engine version. To run this command, make sure you meet
-- the following prerequisites:
--
-- -   The CEV must not be the default for RDS Custom. If it is, change the
--     default before running this command.
--
-- -   The CEV must not be associated with an RDS Custom DB instance, RDS
--     Custom instance snapshot, or automated backup of your RDS Custom
--     instance.
--
-- Typically, deletion takes a few minutes.
--
-- The MediaImport service that imports files from Amazon S3 to create CEVs
-- isn\'t integrated with Amazon Web Services CloudTrail. If you turn on
-- data logging for Amazon RDS in CloudTrail, calls to the
-- @DeleteCustomDbEngineVersion@ event aren\'t logged. However, you might
-- see calls from the API gateway that accesses your Amazon S3 bucket.
-- These calls originate from the MediaImport service for the
-- @DeleteCustomDbEngineVersion@ event.
--
-- For more information, see
-- <https://docs.aws.amazon.com/AmazonRDS/latest/UserGuide/custom-cev.html#custom-cev.delete Deleting a CEV>
-- in the /Amazon RDS User Guide/.
module Amazonka.RDS.DeleteCustomDBEngineVersion
  ( -- * Creating a Request
    DeleteCustomDBEngineVersion (..),
    newDeleteCustomDBEngineVersion,

    -- * Request Lenses
    deleteCustomDBEngineVersion_engine,
    deleteCustomDBEngineVersion_engineVersion,

    -- * Destructuring the Response
    DBEngineVersion (..),
    newDBEngineVersion,

    -- * Response Lenses
    dbEngineVersion_createTime,
    dbEngineVersion_customDBEngineVersionManifest,
    dbEngineVersion_dbEngineDescription,
    dbEngineVersion_dbEngineMediaType,
    dbEngineVersion_dbEngineVersionArn,
    dbEngineVersion_dbEngineVersionDescription,
    dbEngineVersion_dbParameterGroupFamily,
    dbEngineVersion_databaseInstallationFilesS3BucketName,
    dbEngineVersion_databaseInstallationFilesS3Prefix,
    dbEngineVersion_defaultCharacterSet,
    dbEngineVersion_engine,
    dbEngineVersion_engineVersion,
    dbEngineVersion_exportableLogTypes,
    dbEngineVersion_image,
    dbEngineVersion_kmsKeyId,
    dbEngineVersion_majorEngineVersion,
    dbEngineVersion_status,
    dbEngineVersion_supportedCACertificateIdentifiers,
    dbEngineVersion_supportedCharacterSets,
    dbEngineVersion_supportedEngineModes,
    dbEngineVersion_supportedFeatureNames,
    dbEngineVersion_supportedNcharCharacterSets,
    dbEngineVersion_supportedTimezones,
    dbEngineVersion_supportsBabelfish,
    dbEngineVersion_supportsCertificateRotationWithoutRestart,
    dbEngineVersion_supportsGlobalDatabases,
    dbEngineVersion_supportsLogExportsToCloudwatchLogs,
    dbEngineVersion_supportsParallelQuery,
    dbEngineVersion_supportsReadReplica,
    dbEngineVersion_tagList,
    dbEngineVersion_validUpgradeTarget,
  )
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:/ 'newDeleteCustomDBEngineVersion' smart constructor.
data DeleteCustomDBEngineVersion = DeleteCustomDBEngineVersion'
  { -- | The database engine. The only supported engine is @custom-oracle-ee@.
    DeleteCustomDBEngineVersion -> Text
engine :: Prelude.Text,
    -- | The custom engine version (CEV) for your DB instance. This option is
    -- required for RDS Custom, but optional for Amazon RDS. The combination of
    -- @Engine@ and @EngineVersion@ is unique per customer per Amazon Web
    -- Services Region.
    DeleteCustomDBEngineVersion -> Text
engineVersion :: Prelude.Text
  }
  deriving (DeleteCustomDBEngineVersion -> DeleteCustomDBEngineVersion -> Bool
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: DeleteCustomDBEngineVersion -> DeleteCustomDBEngineVersion -> Bool
$c/= :: DeleteCustomDBEngineVersion -> DeleteCustomDBEngineVersion -> Bool
== :: DeleteCustomDBEngineVersion -> DeleteCustomDBEngineVersion -> Bool
$c== :: DeleteCustomDBEngineVersion -> DeleteCustomDBEngineVersion -> Bool
Prelude.Eq, ReadPrec [DeleteCustomDBEngineVersion]
ReadPrec DeleteCustomDBEngineVersion
Int -> ReadS DeleteCustomDBEngineVersion
ReadS [DeleteCustomDBEngineVersion]
forall a.
(Int -> ReadS a)
-> ReadS [a] -> ReadPrec a -> ReadPrec [a] -> Read a
readListPrec :: ReadPrec [DeleteCustomDBEngineVersion]
$creadListPrec :: ReadPrec [DeleteCustomDBEngineVersion]
readPrec :: ReadPrec DeleteCustomDBEngineVersion
$creadPrec :: ReadPrec DeleteCustomDBEngineVersion
readList :: ReadS [DeleteCustomDBEngineVersion]
$creadList :: ReadS [DeleteCustomDBEngineVersion]
readsPrec :: Int -> ReadS DeleteCustomDBEngineVersion
$creadsPrec :: Int -> ReadS DeleteCustomDBEngineVersion
Prelude.Read, Int -> DeleteCustomDBEngineVersion -> ShowS
[DeleteCustomDBEngineVersion] -> ShowS
DeleteCustomDBEngineVersion -> String
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [DeleteCustomDBEngineVersion] -> ShowS
$cshowList :: [DeleteCustomDBEngineVersion] -> ShowS
show :: DeleteCustomDBEngineVersion -> String
$cshow :: DeleteCustomDBEngineVersion -> String
showsPrec :: Int -> DeleteCustomDBEngineVersion -> ShowS
$cshowsPrec :: Int -> DeleteCustomDBEngineVersion -> ShowS
Prelude.Show, forall x.
Rep DeleteCustomDBEngineVersion x -> DeleteCustomDBEngineVersion
forall x.
DeleteCustomDBEngineVersion -> Rep DeleteCustomDBEngineVersion x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cto :: forall x.
Rep DeleteCustomDBEngineVersion x -> DeleteCustomDBEngineVersion
$cfrom :: forall x.
DeleteCustomDBEngineVersion -> Rep DeleteCustomDBEngineVersion x
Prelude.Generic)

-- |
-- Create a value of 'DeleteCustomDBEngineVersion' 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:
--
-- 'engine', 'deleteCustomDBEngineVersion_engine' - The database engine. The only supported engine is @custom-oracle-ee@.
--
-- 'engineVersion', 'deleteCustomDBEngineVersion_engineVersion' - The custom engine version (CEV) for your DB instance. This option is
-- required for RDS Custom, but optional for Amazon RDS. The combination of
-- @Engine@ and @EngineVersion@ is unique per customer per Amazon Web
-- Services Region.
newDeleteCustomDBEngineVersion ::
  -- | 'engine'
  Prelude.Text ->
  -- | 'engineVersion'
  Prelude.Text ->
  DeleteCustomDBEngineVersion
newDeleteCustomDBEngineVersion :: Text -> Text -> DeleteCustomDBEngineVersion
newDeleteCustomDBEngineVersion
  Text
pEngine_
  Text
pEngineVersion_ =
    DeleteCustomDBEngineVersion'
      { $sel:engine:DeleteCustomDBEngineVersion' :: Text
engine = Text
pEngine_,
        $sel:engineVersion:DeleteCustomDBEngineVersion' :: Text
engineVersion = Text
pEngineVersion_
      }

-- | The database engine. The only supported engine is @custom-oracle-ee@.
deleteCustomDBEngineVersion_engine :: Lens.Lens' DeleteCustomDBEngineVersion Prelude.Text
deleteCustomDBEngineVersion_engine :: Lens' DeleteCustomDBEngineVersion Text
deleteCustomDBEngineVersion_engine = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\DeleteCustomDBEngineVersion' {Text
engine :: Text
$sel:engine:DeleteCustomDBEngineVersion' :: DeleteCustomDBEngineVersion -> Text
engine} -> Text
engine) (\s :: DeleteCustomDBEngineVersion
s@DeleteCustomDBEngineVersion' {} Text
a -> DeleteCustomDBEngineVersion
s {$sel:engine:DeleteCustomDBEngineVersion' :: Text
engine = Text
a} :: DeleteCustomDBEngineVersion)

-- | The custom engine version (CEV) for your DB instance. This option is
-- required for RDS Custom, but optional for Amazon RDS. The combination of
-- @Engine@ and @EngineVersion@ is unique per customer per Amazon Web
-- Services Region.
deleteCustomDBEngineVersion_engineVersion :: Lens.Lens' DeleteCustomDBEngineVersion Prelude.Text
deleteCustomDBEngineVersion_engineVersion :: Lens' DeleteCustomDBEngineVersion Text
deleteCustomDBEngineVersion_engineVersion = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\DeleteCustomDBEngineVersion' {Text
engineVersion :: Text
$sel:engineVersion:DeleteCustomDBEngineVersion' :: DeleteCustomDBEngineVersion -> Text
engineVersion} -> Text
engineVersion) (\s :: DeleteCustomDBEngineVersion
s@DeleteCustomDBEngineVersion' {} Text
a -> DeleteCustomDBEngineVersion
s {$sel:engineVersion:DeleteCustomDBEngineVersion' :: Text
engineVersion = Text
a} :: DeleteCustomDBEngineVersion)

instance Core.AWSRequest DeleteCustomDBEngineVersion where
  type
    AWSResponse DeleteCustomDBEngineVersion =
      DBEngineVersion
  request :: (Service -> Service)
-> DeleteCustomDBEngineVersion
-> Request DeleteCustomDBEngineVersion
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 DeleteCustomDBEngineVersion
-> ClientResponse ClientBody
-> m (Either
        Error (ClientResponse (AWSResponse DeleteCustomDBEngineVersion)))
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
"DeleteCustomDBEngineVersionResult"
      (\Int
s ResponseHeaders
h [Node]
x -> forall a. FromXML a => [Node] -> Either String a
Data.parseXML [Node]
x)

instance Prelude.Hashable DeleteCustomDBEngineVersion where
  hashWithSalt :: Int -> DeleteCustomDBEngineVersion -> Int
hashWithSalt Int
_salt DeleteCustomDBEngineVersion' {Text
engineVersion :: Text
engine :: Text
$sel:engineVersion:DeleteCustomDBEngineVersion' :: DeleteCustomDBEngineVersion -> Text
$sel:engine:DeleteCustomDBEngineVersion' :: DeleteCustomDBEngineVersion -> Text
..} =
    Int
_salt
      forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Text
engine
      forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Text
engineVersion

instance Prelude.NFData DeleteCustomDBEngineVersion where
  rnf :: DeleteCustomDBEngineVersion -> ()
rnf DeleteCustomDBEngineVersion' {Text
engineVersion :: Text
engine :: Text
$sel:engineVersion:DeleteCustomDBEngineVersion' :: DeleteCustomDBEngineVersion -> Text
$sel:engine:DeleteCustomDBEngineVersion' :: DeleteCustomDBEngineVersion -> Text
..} =
    forall a. NFData a => a -> ()
Prelude.rnf Text
engine
      seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf Text
engineVersion

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

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

instance Data.ToQuery DeleteCustomDBEngineVersion where
  toQuery :: DeleteCustomDBEngineVersion -> QueryString
toQuery DeleteCustomDBEngineVersion' {Text
engineVersion :: Text
engine :: Text
$sel:engineVersion:DeleteCustomDBEngineVersion' :: DeleteCustomDBEngineVersion -> Text
$sel:engine:DeleteCustomDBEngineVersion' :: DeleteCustomDBEngineVersion -> Text
..} =
    forall a. Monoid a => [a] -> a
Prelude.mconcat
      [ ByteString
"Action"
          forall a. ToQuery a => ByteString -> a -> QueryString
Data.=: ( ByteString
"DeleteCustomDBEngineVersion" ::
                      Prelude.ByteString
                  ),
        ByteString
"Version"
          forall a. ToQuery a => ByteString -> a -> QueryString
Data.=: (ByteString
"2014-10-31" :: Prelude.ByteString),
        ByteString
"Engine" forall a. ToQuery a => ByteString -> a -> QueryString
Data.=: Text
engine,
        ByteString
"EngineVersion" forall a. ToQuery a => ByteString -> a -> QueryString
Data.=: Text
engineVersion
      ]