{-# 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.Redshift.DeleteClusterParameterGroup
-- 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 specified Amazon Redshift parameter group.
--
-- You cannot delete a parameter group if it is associated with a cluster.
module Amazonka.Redshift.DeleteClusterParameterGroup
  ( -- * Creating a Request
    DeleteClusterParameterGroup (..),
    newDeleteClusterParameterGroup,

    -- * Request Lenses
    deleteClusterParameterGroup_parameterGroupName,

    -- * Destructuring the Response
    DeleteClusterParameterGroupResponse (..),
    newDeleteClusterParameterGroupResponse,
  )
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.Redshift.Types
import qualified Amazonka.Request as Request
import qualified Amazonka.Response as Response

-- |
--
-- /See:/ 'newDeleteClusterParameterGroup' smart constructor.
data DeleteClusterParameterGroup = DeleteClusterParameterGroup'
  { -- | The name of the parameter group to be deleted.
    --
    -- Constraints:
    --
    -- -   Must be the name of an existing cluster parameter group.
    --
    -- -   Cannot delete a default cluster parameter group.
    DeleteClusterParameterGroup -> Text
parameterGroupName :: Prelude.Text
  }
  deriving (DeleteClusterParameterGroup -> DeleteClusterParameterGroup -> Bool
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: DeleteClusterParameterGroup -> DeleteClusterParameterGroup -> Bool
$c/= :: DeleteClusterParameterGroup -> DeleteClusterParameterGroup -> Bool
== :: DeleteClusterParameterGroup -> DeleteClusterParameterGroup -> Bool
$c== :: DeleteClusterParameterGroup -> DeleteClusterParameterGroup -> Bool
Prelude.Eq, ReadPrec [DeleteClusterParameterGroup]
ReadPrec DeleteClusterParameterGroup
Int -> ReadS DeleteClusterParameterGroup
ReadS [DeleteClusterParameterGroup]
forall a.
(Int -> ReadS a)
-> ReadS [a] -> ReadPrec a -> ReadPrec [a] -> Read a
readListPrec :: ReadPrec [DeleteClusterParameterGroup]
$creadListPrec :: ReadPrec [DeleteClusterParameterGroup]
readPrec :: ReadPrec DeleteClusterParameterGroup
$creadPrec :: ReadPrec DeleteClusterParameterGroup
readList :: ReadS [DeleteClusterParameterGroup]
$creadList :: ReadS [DeleteClusterParameterGroup]
readsPrec :: Int -> ReadS DeleteClusterParameterGroup
$creadsPrec :: Int -> ReadS DeleteClusterParameterGroup
Prelude.Read, Int -> DeleteClusterParameterGroup -> ShowS
[DeleteClusterParameterGroup] -> ShowS
DeleteClusterParameterGroup -> String
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [DeleteClusterParameterGroup] -> ShowS
$cshowList :: [DeleteClusterParameterGroup] -> ShowS
show :: DeleteClusterParameterGroup -> String
$cshow :: DeleteClusterParameterGroup -> String
showsPrec :: Int -> DeleteClusterParameterGroup -> ShowS
$cshowsPrec :: Int -> DeleteClusterParameterGroup -> ShowS
Prelude.Show, forall x.
Rep DeleteClusterParameterGroup x -> DeleteClusterParameterGroup
forall x.
DeleteClusterParameterGroup -> Rep DeleteClusterParameterGroup x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cto :: forall x.
Rep DeleteClusterParameterGroup x -> DeleteClusterParameterGroup
$cfrom :: forall x.
DeleteClusterParameterGroup -> Rep DeleteClusterParameterGroup x
Prelude.Generic)

-- |
-- Create a value of 'DeleteClusterParameterGroup' 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:
--
-- 'parameterGroupName', 'deleteClusterParameterGroup_parameterGroupName' - The name of the parameter group to be deleted.
--
-- Constraints:
--
-- -   Must be the name of an existing cluster parameter group.
--
-- -   Cannot delete a default cluster parameter group.
newDeleteClusterParameterGroup ::
  -- | 'parameterGroupName'
  Prelude.Text ->
  DeleteClusterParameterGroup
newDeleteClusterParameterGroup :: Text -> DeleteClusterParameterGroup
newDeleteClusterParameterGroup Text
pParameterGroupName_ =
  DeleteClusterParameterGroup'
    { $sel:parameterGroupName:DeleteClusterParameterGroup' :: Text
parameterGroupName =
        Text
pParameterGroupName_
    }

-- | The name of the parameter group to be deleted.
--
-- Constraints:
--
-- -   Must be the name of an existing cluster parameter group.
--
-- -   Cannot delete a default cluster parameter group.
deleteClusterParameterGroup_parameterGroupName :: Lens.Lens' DeleteClusterParameterGroup Prelude.Text
deleteClusterParameterGroup_parameterGroupName :: Lens' DeleteClusterParameterGroup Text
deleteClusterParameterGroup_parameterGroupName = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\DeleteClusterParameterGroup' {Text
parameterGroupName :: Text
$sel:parameterGroupName:DeleteClusterParameterGroup' :: DeleteClusterParameterGroup -> Text
parameterGroupName} -> Text
parameterGroupName) (\s :: DeleteClusterParameterGroup
s@DeleteClusterParameterGroup' {} Text
a -> DeleteClusterParameterGroup
s {$sel:parameterGroupName:DeleteClusterParameterGroup' :: Text
parameterGroupName = Text
a} :: DeleteClusterParameterGroup)

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

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

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

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

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

instance Data.ToQuery DeleteClusterParameterGroup where
  toQuery :: DeleteClusterParameterGroup -> QueryString
toQuery DeleteClusterParameterGroup' {Text
parameterGroupName :: Text
$sel:parameterGroupName:DeleteClusterParameterGroup' :: DeleteClusterParameterGroup -> Text
..} =
    forall a. Monoid a => [a] -> a
Prelude.mconcat
      [ ByteString
"Action"
          forall a. ToQuery a => ByteString -> a -> QueryString
Data.=: ( ByteString
"DeleteClusterParameterGroup" ::
                      Prelude.ByteString
                  ),
        ByteString
"Version"
          forall a. ToQuery a => ByteString -> a -> QueryString
Data.=: (ByteString
"2012-12-01" :: Prelude.ByteString),
        ByteString
"ParameterGroupName" forall a. ToQuery a => ByteString -> a -> QueryString
Data.=: Text
parameterGroupName
      ]

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

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

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