{-# 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.DeleteOptionGroup
-- 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 an existing option group.
module Amazonka.RDS.DeleteOptionGroup
  ( -- * Creating a Request
    DeleteOptionGroup (..),
    newDeleteOptionGroup,

    -- * Request Lenses
    deleteOptionGroup_optionGroupName,

    -- * Destructuring the Response
    DeleteOptionGroupResponse (..),
    newDeleteOptionGroupResponse,
  )
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:/ 'newDeleteOptionGroup' smart constructor.
data DeleteOptionGroup = DeleteOptionGroup'
  { -- | The name of the option group to be deleted.
    --
    -- You can\'t delete default option groups.
    DeleteOptionGroup -> Text
optionGroupName :: Prelude.Text
  }
  deriving (DeleteOptionGroup -> DeleteOptionGroup -> Bool
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: DeleteOptionGroup -> DeleteOptionGroup -> Bool
$c/= :: DeleteOptionGroup -> DeleteOptionGroup -> Bool
== :: DeleteOptionGroup -> DeleteOptionGroup -> Bool
$c== :: DeleteOptionGroup -> DeleteOptionGroup -> Bool
Prelude.Eq, ReadPrec [DeleteOptionGroup]
ReadPrec DeleteOptionGroup
Int -> ReadS DeleteOptionGroup
ReadS [DeleteOptionGroup]
forall a.
(Int -> ReadS a)
-> ReadS [a] -> ReadPrec a -> ReadPrec [a] -> Read a
readListPrec :: ReadPrec [DeleteOptionGroup]
$creadListPrec :: ReadPrec [DeleteOptionGroup]
readPrec :: ReadPrec DeleteOptionGroup
$creadPrec :: ReadPrec DeleteOptionGroup
readList :: ReadS [DeleteOptionGroup]
$creadList :: ReadS [DeleteOptionGroup]
readsPrec :: Int -> ReadS DeleteOptionGroup
$creadsPrec :: Int -> ReadS DeleteOptionGroup
Prelude.Read, Int -> DeleteOptionGroup -> ShowS
[DeleteOptionGroup] -> ShowS
DeleteOptionGroup -> String
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [DeleteOptionGroup] -> ShowS
$cshowList :: [DeleteOptionGroup] -> ShowS
show :: DeleteOptionGroup -> String
$cshow :: DeleteOptionGroup -> String
showsPrec :: Int -> DeleteOptionGroup -> ShowS
$cshowsPrec :: Int -> DeleteOptionGroup -> ShowS
Prelude.Show, forall x. Rep DeleteOptionGroup x -> DeleteOptionGroup
forall x. DeleteOptionGroup -> Rep DeleteOptionGroup x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cto :: forall x. Rep DeleteOptionGroup x -> DeleteOptionGroup
$cfrom :: forall x. DeleteOptionGroup -> Rep DeleteOptionGroup x
Prelude.Generic)

-- |
-- Create a value of 'DeleteOptionGroup' 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:
--
-- 'optionGroupName', 'deleteOptionGroup_optionGroupName' - The name of the option group to be deleted.
--
-- You can\'t delete default option groups.
newDeleteOptionGroup ::
  -- | 'optionGroupName'
  Prelude.Text ->
  DeleteOptionGroup
newDeleteOptionGroup :: Text -> DeleteOptionGroup
newDeleteOptionGroup Text
pOptionGroupName_ =
  DeleteOptionGroup'
    { $sel:optionGroupName:DeleteOptionGroup' :: Text
optionGroupName =
        Text
pOptionGroupName_
    }

-- | The name of the option group to be deleted.
--
-- You can\'t delete default option groups.
deleteOptionGroup_optionGroupName :: Lens.Lens' DeleteOptionGroup Prelude.Text
deleteOptionGroup_optionGroupName :: Lens' DeleteOptionGroup Text
deleteOptionGroup_optionGroupName = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\DeleteOptionGroup' {Text
optionGroupName :: Text
$sel:optionGroupName:DeleteOptionGroup' :: DeleteOptionGroup -> Text
optionGroupName} -> Text
optionGroupName) (\s :: DeleteOptionGroup
s@DeleteOptionGroup' {} Text
a -> DeleteOptionGroup
s {$sel:optionGroupName:DeleteOptionGroup' :: Text
optionGroupName = Text
a} :: DeleteOptionGroup)

instance Core.AWSRequest DeleteOptionGroup where
  type
    AWSResponse DeleteOptionGroup =
      DeleteOptionGroupResponse
  request :: (Service -> Service)
-> DeleteOptionGroup -> Request DeleteOptionGroup
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 DeleteOptionGroup
-> ClientResponse ClientBody
-> m (Either
        Error (ClientResponse (AWSResponse DeleteOptionGroup)))
response =
    forall (m :: * -> *) a.
MonadResource m =>
AWSResponse a
-> (ByteStringLazy -> IO ByteStringLazy)
-> Service
-> Proxy a
-> ClientResponse ClientBody
-> m (Either Error (ClientResponse (AWSResponse a)))
Response.receiveNull DeleteOptionGroupResponse
DeleteOptionGroupResponse'

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

instance Prelude.NFData DeleteOptionGroup where
  rnf :: DeleteOptionGroup -> ()
rnf DeleteOptionGroup' {Text
optionGroupName :: Text
$sel:optionGroupName:DeleteOptionGroup' :: DeleteOptionGroup -> Text
..} =
    forall a. NFData a => a -> ()
Prelude.rnf Text
optionGroupName

instance Data.ToHeaders DeleteOptionGroup where
  toHeaders :: DeleteOptionGroup -> [Header]
toHeaders = forall a b. a -> b -> a
Prelude.const forall a. Monoid a => a
Prelude.mempty

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

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

-- | /See:/ 'newDeleteOptionGroupResponse' smart constructor.
data DeleteOptionGroupResponse = DeleteOptionGroupResponse'
  {
  }
  deriving (DeleteOptionGroupResponse -> DeleteOptionGroupResponse -> Bool
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: DeleteOptionGroupResponse -> DeleteOptionGroupResponse -> Bool
$c/= :: DeleteOptionGroupResponse -> DeleteOptionGroupResponse -> Bool
== :: DeleteOptionGroupResponse -> DeleteOptionGroupResponse -> Bool
$c== :: DeleteOptionGroupResponse -> DeleteOptionGroupResponse -> Bool
Prelude.Eq, ReadPrec [DeleteOptionGroupResponse]
ReadPrec DeleteOptionGroupResponse
Int -> ReadS DeleteOptionGroupResponse
ReadS [DeleteOptionGroupResponse]
forall a.
(Int -> ReadS a)
-> ReadS [a] -> ReadPrec a -> ReadPrec [a] -> Read a
readListPrec :: ReadPrec [DeleteOptionGroupResponse]
$creadListPrec :: ReadPrec [DeleteOptionGroupResponse]
readPrec :: ReadPrec DeleteOptionGroupResponse
$creadPrec :: ReadPrec DeleteOptionGroupResponse
readList :: ReadS [DeleteOptionGroupResponse]
$creadList :: ReadS [DeleteOptionGroupResponse]
readsPrec :: Int -> ReadS DeleteOptionGroupResponse
$creadsPrec :: Int -> ReadS DeleteOptionGroupResponse
Prelude.Read, Int -> DeleteOptionGroupResponse -> ShowS
[DeleteOptionGroupResponse] -> ShowS
DeleteOptionGroupResponse -> String
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [DeleteOptionGroupResponse] -> ShowS
$cshowList :: [DeleteOptionGroupResponse] -> ShowS
show :: DeleteOptionGroupResponse -> String
$cshow :: DeleteOptionGroupResponse -> String
showsPrec :: Int -> DeleteOptionGroupResponse -> ShowS
$cshowsPrec :: Int -> DeleteOptionGroupResponse -> ShowS
Prelude.Show, forall x.
Rep DeleteOptionGroupResponse x -> DeleteOptionGroupResponse
forall x.
DeleteOptionGroupResponse -> Rep DeleteOptionGroupResponse x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cto :: forall x.
Rep DeleteOptionGroupResponse x -> DeleteOptionGroupResponse
$cfrom :: forall x.
DeleteOptionGroupResponse -> Rep DeleteOptionGroupResponse x
Prelude.Generic)

-- |
-- Create a value of 'DeleteOptionGroupResponse' 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.
newDeleteOptionGroupResponse ::
  DeleteOptionGroupResponse
newDeleteOptionGroupResponse :: DeleteOptionGroupResponse
newDeleteOptionGroupResponse =
  DeleteOptionGroupResponse
DeleteOptionGroupResponse'

instance Prelude.NFData DeleteOptionGroupResponse where
  rnf :: DeleteOptionGroupResponse -> ()
rnf DeleteOptionGroupResponse
_ = ()