{-# 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.DeleteEventSubscription
-- 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 Amazon Redshift event notification subscription.
module Amazonka.Redshift.DeleteEventSubscription
  ( -- * Creating a Request
    DeleteEventSubscription (..),
    newDeleteEventSubscription,

    -- * Request Lenses
    deleteEventSubscription_subscriptionName,

    -- * Destructuring the Response
    DeleteEventSubscriptionResponse (..),
    newDeleteEventSubscriptionResponse,
  )
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:/ 'newDeleteEventSubscription' smart constructor.
data DeleteEventSubscription = DeleteEventSubscription'
  { -- | The name of the Amazon Redshift event notification subscription to be
    -- deleted.
    DeleteEventSubscription -> Text
subscriptionName :: Prelude.Text
  }
  deriving (DeleteEventSubscription -> DeleteEventSubscription -> Bool
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: DeleteEventSubscription -> DeleteEventSubscription -> Bool
$c/= :: DeleteEventSubscription -> DeleteEventSubscription -> Bool
== :: DeleteEventSubscription -> DeleteEventSubscription -> Bool
$c== :: DeleteEventSubscription -> DeleteEventSubscription -> Bool
Prelude.Eq, ReadPrec [DeleteEventSubscription]
ReadPrec DeleteEventSubscription
Int -> ReadS DeleteEventSubscription
ReadS [DeleteEventSubscription]
forall a.
(Int -> ReadS a)
-> ReadS [a] -> ReadPrec a -> ReadPrec [a] -> Read a
readListPrec :: ReadPrec [DeleteEventSubscription]
$creadListPrec :: ReadPrec [DeleteEventSubscription]
readPrec :: ReadPrec DeleteEventSubscription
$creadPrec :: ReadPrec DeleteEventSubscription
readList :: ReadS [DeleteEventSubscription]
$creadList :: ReadS [DeleteEventSubscription]
readsPrec :: Int -> ReadS DeleteEventSubscription
$creadsPrec :: Int -> ReadS DeleteEventSubscription
Prelude.Read, Int -> DeleteEventSubscription -> ShowS
[DeleteEventSubscription] -> ShowS
DeleteEventSubscription -> String
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [DeleteEventSubscription] -> ShowS
$cshowList :: [DeleteEventSubscription] -> ShowS
show :: DeleteEventSubscription -> String
$cshow :: DeleteEventSubscription -> String
showsPrec :: Int -> DeleteEventSubscription -> ShowS
$cshowsPrec :: Int -> DeleteEventSubscription -> ShowS
Prelude.Show, forall x. Rep DeleteEventSubscription x -> DeleteEventSubscription
forall x. DeleteEventSubscription -> Rep DeleteEventSubscription x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cto :: forall x. Rep DeleteEventSubscription x -> DeleteEventSubscription
$cfrom :: forall x. DeleteEventSubscription -> Rep DeleteEventSubscription x
Prelude.Generic)

-- |
-- Create a value of 'DeleteEventSubscription' 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:
--
-- 'subscriptionName', 'deleteEventSubscription_subscriptionName' - The name of the Amazon Redshift event notification subscription to be
-- deleted.
newDeleteEventSubscription ::
  -- | 'subscriptionName'
  Prelude.Text ->
  DeleteEventSubscription
newDeleteEventSubscription :: Text -> DeleteEventSubscription
newDeleteEventSubscription Text
pSubscriptionName_ =
  DeleteEventSubscription'
    { $sel:subscriptionName:DeleteEventSubscription' :: Text
subscriptionName =
        Text
pSubscriptionName_
    }

-- | The name of the Amazon Redshift event notification subscription to be
-- deleted.
deleteEventSubscription_subscriptionName :: Lens.Lens' DeleteEventSubscription Prelude.Text
deleteEventSubscription_subscriptionName :: Lens' DeleteEventSubscription Text
deleteEventSubscription_subscriptionName = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\DeleteEventSubscription' {Text
subscriptionName :: Text
$sel:subscriptionName:DeleteEventSubscription' :: DeleteEventSubscription -> Text
subscriptionName} -> Text
subscriptionName) (\s :: DeleteEventSubscription
s@DeleteEventSubscription' {} Text
a -> DeleteEventSubscription
s {$sel:subscriptionName:DeleteEventSubscription' :: Text
subscriptionName = Text
a} :: DeleteEventSubscription)

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

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

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

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

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

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

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

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

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