{-# 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.DeleteClusterSubnetGroup
-- 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 the specified cluster subnet group.
module Amazonka.Redshift.DeleteClusterSubnetGroup
  ( -- * Creating a Request
    DeleteClusterSubnetGroup (..),
    newDeleteClusterSubnetGroup,

    -- * Request Lenses
    deleteClusterSubnetGroup_clusterSubnetGroupName,

    -- * Destructuring the Response
    DeleteClusterSubnetGroupResponse (..),
    newDeleteClusterSubnetGroupResponse,
  )
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:/ 'newDeleteClusterSubnetGroup' smart constructor.
data DeleteClusterSubnetGroup = DeleteClusterSubnetGroup'
  { -- | The name of the cluster subnet group name to be deleted.
    DeleteClusterSubnetGroup -> Text
clusterSubnetGroupName :: Prelude.Text
  }
  deriving (DeleteClusterSubnetGroup -> DeleteClusterSubnetGroup -> Bool
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: DeleteClusterSubnetGroup -> DeleteClusterSubnetGroup -> Bool
$c/= :: DeleteClusterSubnetGroup -> DeleteClusterSubnetGroup -> Bool
== :: DeleteClusterSubnetGroup -> DeleteClusterSubnetGroup -> Bool
$c== :: DeleteClusterSubnetGroup -> DeleteClusterSubnetGroup -> Bool
Prelude.Eq, ReadPrec [DeleteClusterSubnetGroup]
ReadPrec DeleteClusterSubnetGroup
Int -> ReadS DeleteClusterSubnetGroup
ReadS [DeleteClusterSubnetGroup]
forall a.
(Int -> ReadS a)
-> ReadS [a] -> ReadPrec a -> ReadPrec [a] -> Read a
readListPrec :: ReadPrec [DeleteClusterSubnetGroup]
$creadListPrec :: ReadPrec [DeleteClusterSubnetGroup]
readPrec :: ReadPrec DeleteClusterSubnetGroup
$creadPrec :: ReadPrec DeleteClusterSubnetGroup
readList :: ReadS [DeleteClusterSubnetGroup]
$creadList :: ReadS [DeleteClusterSubnetGroup]
readsPrec :: Int -> ReadS DeleteClusterSubnetGroup
$creadsPrec :: Int -> ReadS DeleteClusterSubnetGroup
Prelude.Read, Int -> DeleteClusterSubnetGroup -> ShowS
[DeleteClusterSubnetGroup] -> ShowS
DeleteClusterSubnetGroup -> String
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [DeleteClusterSubnetGroup] -> ShowS
$cshowList :: [DeleteClusterSubnetGroup] -> ShowS
show :: DeleteClusterSubnetGroup -> String
$cshow :: DeleteClusterSubnetGroup -> String
showsPrec :: Int -> DeleteClusterSubnetGroup -> ShowS
$cshowsPrec :: Int -> DeleteClusterSubnetGroup -> ShowS
Prelude.Show, forall x.
Rep DeleteClusterSubnetGroup x -> DeleteClusterSubnetGroup
forall x.
DeleteClusterSubnetGroup -> Rep DeleteClusterSubnetGroup x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cto :: forall x.
Rep DeleteClusterSubnetGroup x -> DeleteClusterSubnetGroup
$cfrom :: forall x.
DeleteClusterSubnetGroup -> Rep DeleteClusterSubnetGroup x
Prelude.Generic)

-- |
-- Create a value of 'DeleteClusterSubnetGroup' 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:
--
-- 'clusterSubnetGroupName', 'deleteClusterSubnetGroup_clusterSubnetGroupName' - The name of the cluster subnet group name to be deleted.
newDeleteClusterSubnetGroup ::
  -- | 'clusterSubnetGroupName'
  Prelude.Text ->
  DeleteClusterSubnetGroup
newDeleteClusterSubnetGroup :: Text -> DeleteClusterSubnetGroup
newDeleteClusterSubnetGroup Text
pClusterSubnetGroupName_ =
  DeleteClusterSubnetGroup'
    { $sel:clusterSubnetGroupName:DeleteClusterSubnetGroup' :: Text
clusterSubnetGroupName =
        Text
pClusterSubnetGroupName_
    }

-- | The name of the cluster subnet group name to be deleted.
deleteClusterSubnetGroup_clusterSubnetGroupName :: Lens.Lens' DeleteClusterSubnetGroup Prelude.Text
deleteClusterSubnetGroup_clusterSubnetGroupName :: Lens' DeleteClusterSubnetGroup Text
deleteClusterSubnetGroup_clusterSubnetGroupName = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\DeleteClusterSubnetGroup' {Text
clusterSubnetGroupName :: Text
$sel:clusterSubnetGroupName:DeleteClusterSubnetGroup' :: DeleteClusterSubnetGroup -> Text
clusterSubnetGroupName} -> Text
clusterSubnetGroupName) (\s :: DeleteClusterSubnetGroup
s@DeleteClusterSubnetGroup' {} Text
a -> DeleteClusterSubnetGroup
s {$sel:clusterSubnetGroupName:DeleteClusterSubnetGroup' :: Text
clusterSubnetGroupName = Text
a} :: DeleteClusterSubnetGroup)

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

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

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

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

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

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

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

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

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