{-# 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.SNS.Unsubscribe
-- 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 subscription. If the subscription requires authentication for
-- deletion, only the owner of the subscription or the topic\'s owner can
-- unsubscribe, and an Amazon Web Services signature is required. If the
-- @Unsubscribe@ call does not require authentication and the requester is
-- not the subscription owner, a final cancellation message is delivered to
-- the endpoint, so that the endpoint owner can easily resubscribe to the
-- topic if the @Unsubscribe@ request was unintended.
--
-- Amazon SQS queue subscriptions require authentication for deletion. Only
-- the owner of the subscription, or the owner of the topic can unsubscribe
-- using the required Amazon Web Services signature.
--
-- This action is throttled at 100 transactions per second (TPS).
module Amazonka.SNS.Unsubscribe
  ( -- * Creating a Request
    Unsubscribe (..),
    newUnsubscribe,

    -- * Request Lenses
    unsubscribe_subscriptionArn,

    -- * Destructuring the Response
    UnsubscribeResponse (..),
    newUnsubscribeResponse,
  )
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 qualified Amazonka.Request as Request
import qualified Amazonka.Response as Response
import Amazonka.SNS.Types

-- | Input for Unsubscribe action.
--
-- /See:/ 'newUnsubscribe' smart constructor.
data Unsubscribe = Unsubscribe'
  { -- | The ARN of the subscription to be deleted.
    Unsubscribe -> Text
subscriptionArn :: Prelude.Text
  }
  deriving (Unsubscribe -> Unsubscribe -> Bool
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: Unsubscribe -> Unsubscribe -> Bool
$c/= :: Unsubscribe -> Unsubscribe -> Bool
== :: Unsubscribe -> Unsubscribe -> Bool
$c== :: Unsubscribe -> Unsubscribe -> Bool
Prelude.Eq, ReadPrec [Unsubscribe]
ReadPrec Unsubscribe
Int -> ReadS Unsubscribe
ReadS [Unsubscribe]
forall a.
(Int -> ReadS a)
-> ReadS [a] -> ReadPrec a -> ReadPrec [a] -> Read a
readListPrec :: ReadPrec [Unsubscribe]
$creadListPrec :: ReadPrec [Unsubscribe]
readPrec :: ReadPrec Unsubscribe
$creadPrec :: ReadPrec Unsubscribe
readList :: ReadS [Unsubscribe]
$creadList :: ReadS [Unsubscribe]
readsPrec :: Int -> ReadS Unsubscribe
$creadsPrec :: Int -> ReadS Unsubscribe
Prelude.Read, Int -> Unsubscribe -> ShowS
[Unsubscribe] -> ShowS
Unsubscribe -> String
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [Unsubscribe] -> ShowS
$cshowList :: [Unsubscribe] -> ShowS
show :: Unsubscribe -> String
$cshow :: Unsubscribe -> String
showsPrec :: Int -> Unsubscribe -> ShowS
$cshowsPrec :: Int -> Unsubscribe -> ShowS
Prelude.Show, forall x. Rep Unsubscribe x -> Unsubscribe
forall x. Unsubscribe -> Rep Unsubscribe x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cto :: forall x. Rep Unsubscribe x -> Unsubscribe
$cfrom :: forall x. Unsubscribe -> Rep Unsubscribe x
Prelude.Generic)

-- |
-- Create a value of 'Unsubscribe' 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:
--
-- 'subscriptionArn', 'unsubscribe_subscriptionArn' - The ARN of the subscription to be deleted.
newUnsubscribe ::
  -- | 'subscriptionArn'
  Prelude.Text ->
  Unsubscribe
newUnsubscribe :: Text -> Unsubscribe
newUnsubscribe Text
pSubscriptionArn_ =
  Unsubscribe' {$sel:subscriptionArn:Unsubscribe' :: Text
subscriptionArn = Text
pSubscriptionArn_}

-- | The ARN of the subscription to be deleted.
unsubscribe_subscriptionArn :: Lens.Lens' Unsubscribe Prelude.Text
unsubscribe_subscriptionArn :: Lens' Unsubscribe Text
unsubscribe_subscriptionArn = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\Unsubscribe' {Text
subscriptionArn :: Text
$sel:subscriptionArn:Unsubscribe' :: Unsubscribe -> Text
subscriptionArn} -> Text
subscriptionArn) (\s :: Unsubscribe
s@Unsubscribe' {} Text
a -> Unsubscribe
s {$sel:subscriptionArn:Unsubscribe' :: Text
subscriptionArn = Text
a} :: Unsubscribe)

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

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

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

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

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

instance Data.ToQuery Unsubscribe where
  toQuery :: Unsubscribe -> QueryString
toQuery Unsubscribe' {Text
subscriptionArn :: Text
$sel:subscriptionArn:Unsubscribe' :: Unsubscribe -> Text
..} =
    forall a. Monoid a => [a] -> a
Prelude.mconcat
      [ ByteString
"Action"
          forall a. ToQuery a => ByteString -> a -> QueryString
Data.=: (ByteString
"Unsubscribe" :: Prelude.ByteString),
        ByteString
"Version"
          forall a. ToQuery a => ByteString -> a -> QueryString
Data.=: (ByteString
"2010-03-31" :: Prelude.ByteString),
        ByteString
"SubscriptionArn" forall a. ToQuery a => ByteString -> a -> QueryString
Data.=: Text
subscriptionArn
      ]

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

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

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