{-# 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.SetSubscriptionAttributes
-- Copyright   : (c) 2013-2023 Brendan Hay
-- License     : Mozilla Public License, v. 2.0.
-- Maintainer  : Brendan Hay
-- Stability   : auto-generated
-- Portability : non-portable (GHC extensions)
--
-- Allows a subscription owner to set an attribute of the subscription to a
-- new value.
module Amazonka.SNS.SetSubscriptionAttributes
  ( -- * Creating a Request
    SetSubscriptionAttributes (..),
    newSetSubscriptionAttributes,

    -- * Request Lenses
    setSubscriptionAttributes_attributeValue,
    setSubscriptionAttributes_subscriptionArn,
    setSubscriptionAttributes_attributeName,

    -- * Destructuring the Response
    SetSubscriptionAttributesResponse (..),
    newSetSubscriptionAttributesResponse,
  )
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 SetSubscriptionAttributes action.
--
-- /See:/ 'newSetSubscriptionAttributes' smart constructor.
data SetSubscriptionAttributes = SetSubscriptionAttributes'
  { -- | The new value for the attribute in JSON format.
    SetSubscriptionAttributes -> Maybe Text
attributeValue :: Prelude.Maybe Prelude.Text,
    -- | The ARN of the subscription to modify.
    SetSubscriptionAttributes -> Text
subscriptionArn :: Prelude.Text,
    -- | A map of attributes with their corresponding values.
    --
    -- The following lists the names, descriptions, and values of the special
    -- request parameters that this action uses:
    --
    -- -   @DeliveryPolicy@ – The policy that defines how Amazon SNS retries
    --     failed deliveries to HTTP\/S endpoints.
    --
    -- -   @FilterPolicy@ – The simple JSON object that lets your subscriber
    --     receive only a subset of messages, rather than receiving every
    --     message published to the topic.
    --
    -- -   @FilterPolicyScope@ – This attribute lets you choose the filtering
    --     scope by using one of the following string value types:
    --
    --     -   @MessageAttributes@ (default) – The filter is applied on the
    --         message attributes.
    --
    --     -   @MessageBody@ – The filter is applied on the message body.
    --
    -- -   @RawMessageDelivery@ – When set to @true@, enables raw message
    --     delivery to Amazon SQS or HTTP\/S endpoints. This eliminates the
    --     need for the endpoints to process JSON formatting, which is
    --     otherwise created for Amazon SNS metadata.
    --
    -- -   @RedrivePolicy@ – When specified, sends undeliverable messages to
    --     the specified Amazon SQS dead-letter queue. Messages that can\'t be
    --     delivered due to client errors (for example, when the subscribed
    --     endpoint is unreachable) or server errors (for example, when the
    --     service that powers the subscribed endpoint becomes unavailable) are
    --     held in the dead-letter queue for further analysis or reprocessing.
    --
    -- The following attribute applies only to Amazon Kinesis Data Firehose
    -- delivery stream subscriptions:
    --
    -- -   @SubscriptionRoleArn@ – The ARN of the IAM role that has the
    --     following:
    --
    --     -   Permission to write to the Kinesis Data Firehose delivery stream
    --
    --     -   Amazon SNS listed as a trusted entity
    --
    --     Specifying a valid ARN for this attribute is required for Kinesis
    --     Data Firehose delivery stream subscriptions. For more information,
    --     see
    --     <https://docs.aws.amazon.com/sns/latest/dg/sns-firehose-as-subscriber.html Fanout to Kinesis Data Firehose delivery streams>
    --     in the /Amazon SNS Developer Guide/.
    SetSubscriptionAttributes -> Text
attributeName :: Prelude.Text
  }
  deriving (SetSubscriptionAttributes -> SetSubscriptionAttributes -> Bool
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: SetSubscriptionAttributes -> SetSubscriptionAttributes -> Bool
$c/= :: SetSubscriptionAttributes -> SetSubscriptionAttributes -> Bool
== :: SetSubscriptionAttributes -> SetSubscriptionAttributes -> Bool
$c== :: SetSubscriptionAttributes -> SetSubscriptionAttributes -> Bool
Prelude.Eq, ReadPrec [SetSubscriptionAttributes]
ReadPrec SetSubscriptionAttributes
Int -> ReadS SetSubscriptionAttributes
ReadS [SetSubscriptionAttributes]
forall a.
(Int -> ReadS a)
-> ReadS [a] -> ReadPrec a -> ReadPrec [a] -> Read a
readListPrec :: ReadPrec [SetSubscriptionAttributes]
$creadListPrec :: ReadPrec [SetSubscriptionAttributes]
readPrec :: ReadPrec SetSubscriptionAttributes
$creadPrec :: ReadPrec SetSubscriptionAttributes
readList :: ReadS [SetSubscriptionAttributes]
$creadList :: ReadS [SetSubscriptionAttributes]
readsPrec :: Int -> ReadS SetSubscriptionAttributes
$creadsPrec :: Int -> ReadS SetSubscriptionAttributes
Prelude.Read, Int -> SetSubscriptionAttributes -> ShowS
[SetSubscriptionAttributes] -> ShowS
SetSubscriptionAttributes -> String
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [SetSubscriptionAttributes] -> ShowS
$cshowList :: [SetSubscriptionAttributes] -> ShowS
show :: SetSubscriptionAttributes -> String
$cshow :: SetSubscriptionAttributes -> String
showsPrec :: Int -> SetSubscriptionAttributes -> ShowS
$cshowsPrec :: Int -> SetSubscriptionAttributes -> ShowS
Prelude.Show, forall x.
Rep SetSubscriptionAttributes x -> SetSubscriptionAttributes
forall x.
SetSubscriptionAttributes -> Rep SetSubscriptionAttributes x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cto :: forall x.
Rep SetSubscriptionAttributes x -> SetSubscriptionAttributes
$cfrom :: forall x.
SetSubscriptionAttributes -> Rep SetSubscriptionAttributes x
Prelude.Generic)

-- |
-- Create a value of 'SetSubscriptionAttributes' 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:
--
-- 'attributeValue', 'setSubscriptionAttributes_attributeValue' - The new value for the attribute in JSON format.
--
-- 'subscriptionArn', 'setSubscriptionAttributes_subscriptionArn' - The ARN of the subscription to modify.
--
-- 'attributeName', 'setSubscriptionAttributes_attributeName' - A map of attributes with their corresponding values.
--
-- The following lists the names, descriptions, and values of the special
-- request parameters that this action uses:
--
-- -   @DeliveryPolicy@ – The policy that defines how Amazon SNS retries
--     failed deliveries to HTTP\/S endpoints.
--
-- -   @FilterPolicy@ – The simple JSON object that lets your subscriber
--     receive only a subset of messages, rather than receiving every
--     message published to the topic.
--
-- -   @FilterPolicyScope@ – This attribute lets you choose the filtering
--     scope by using one of the following string value types:
--
--     -   @MessageAttributes@ (default) – The filter is applied on the
--         message attributes.
--
--     -   @MessageBody@ – The filter is applied on the message body.
--
-- -   @RawMessageDelivery@ – When set to @true@, enables raw message
--     delivery to Amazon SQS or HTTP\/S endpoints. This eliminates the
--     need for the endpoints to process JSON formatting, which is
--     otherwise created for Amazon SNS metadata.
--
-- -   @RedrivePolicy@ – When specified, sends undeliverable messages to
--     the specified Amazon SQS dead-letter queue. Messages that can\'t be
--     delivered due to client errors (for example, when the subscribed
--     endpoint is unreachable) or server errors (for example, when the
--     service that powers the subscribed endpoint becomes unavailable) are
--     held in the dead-letter queue for further analysis or reprocessing.
--
-- The following attribute applies only to Amazon Kinesis Data Firehose
-- delivery stream subscriptions:
--
-- -   @SubscriptionRoleArn@ – The ARN of the IAM role that has the
--     following:
--
--     -   Permission to write to the Kinesis Data Firehose delivery stream
--
--     -   Amazon SNS listed as a trusted entity
--
--     Specifying a valid ARN for this attribute is required for Kinesis
--     Data Firehose delivery stream subscriptions. For more information,
--     see
--     <https://docs.aws.amazon.com/sns/latest/dg/sns-firehose-as-subscriber.html Fanout to Kinesis Data Firehose delivery streams>
--     in the /Amazon SNS Developer Guide/.
newSetSubscriptionAttributes ::
  -- | 'subscriptionArn'
  Prelude.Text ->
  -- | 'attributeName'
  Prelude.Text ->
  SetSubscriptionAttributes
newSetSubscriptionAttributes :: Text -> Text -> SetSubscriptionAttributes
newSetSubscriptionAttributes
  Text
pSubscriptionArn_
  Text
pAttributeName_ =
    SetSubscriptionAttributes'
      { $sel:attributeValue:SetSubscriptionAttributes' :: Maybe Text
attributeValue =
          forall a. Maybe a
Prelude.Nothing,
        $sel:subscriptionArn:SetSubscriptionAttributes' :: Text
subscriptionArn = Text
pSubscriptionArn_,
        $sel:attributeName:SetSubscriptionAttributes' :: Text
attributeName = Text
pAttributeName_
      }

-- | The new value for the attribute in JSON format.
setSubscriptionAttributes_attributeValue :: Lens.Lens' SetSubscriptionAttributes (Prelude.Maybe Prelude.Text)
setSubscriptionAttributes_attributeValue :: Lens' SetSubscriptionAttributes (Maybe Text)
setSubscriptionAttributes_attributeValue = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\SetSubscriptionAttributes' {Maybe Text
attributeValue :: Maybe Text
$sel:attributeValue:SetSubscriptionAttributes' :: SetSubscriptionAttributes -> Maybe Text
attributeValue} -> Maybe Text
attributeValue) (\s :: SetSubscriptionAttributes
s@SetSubscriptionAttributes' {} Maybe Text
a -> SetSubscriptionAttributes
s {$sel:attributeValue:SetSubscriptionAttributes' :: Maybe Text
attributeValue = Maybe Text
a} :: SetSubscriptionAttributes)

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

-- | A map of attributes with their corresponding values.
--
-- The following lists the names, descriptions, and values of the special
-- request parameters that this action uses:
--
-- -   @DeliveryPolicy@ – The policy that defines how Amazon SNS retries
--     failed deliveries to HTTP\/S endpoints.
--
-- -   @FilterPolicy@ – The simple JSON object that lets your subscriber
--     receive only a subset of messages, rather than receiving every
--     message published to the topic.
--
-- -   @FilterPolicyScope@ – This attribute lets you choose the filtering
--     scope by using one of the following string value types:
--
--     -   @MessageAttributes@ (default) – The filter is applied on the
--         message attributes.
--
--     -   @MessageBody@ – The filter is applied on the message body.
--
-- -   @RawMessageDelivery@ – When set to @true@, enables raw message
--     delivery to Amazon SQS or HTTP\/S endpoints. This eliminates the
--     need for the endpoints to process JSON formatting, which is
--     otherwise created for Amazon SNS metadata.
--
-- -   @RedrivePolicy@ – When specified, sends undeliverable messages to
--     the specified Amazon SQS dead-letter queue. Messages that can\'t be
--     delivered due to client errors (for example, when the subscribed
--     endpoint is unreachable) or server errors (for example, when the
--     service that powers the subscribed endpoint becomes unavailable) are
--     held in the dead-letter queue for further analysis or reprocessing.
--
-- The following attribute applies only to Amazon Kinesis Data Firehose
-- delivery stream subscriptions:
--
-- -   @SubscriptionRoleArn@ – The ARN of the IAM role that has the
--     following:
--
--     -   Permission to write to the Kinesis Data Firehose delivery stream
--
--     -   Amazon SNS listed as a trusted entity
--
--     Specifying a valid ARN for this attribute is required for Kinesis
--     Data Firehose delivery stream subscriptions. For more information,
--     see
--     <https://docs.aws.amazon.com/sns/latest/dg/sns-firehose-as-subscriber.html Fanout to Kinesis Data Firehose delivery streams>
--     in the /Amazon SNS Developer Guide/.
setSubscriptionAttributes_attributeName :: Lens.Lens' SetSubscriptionAttributes Prelude.Text
setSubscriptionAttributes_attributeName :: Lens' SetSubscriptionAttributes Text
setSubscriptionAttributes_attributeName = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\SetSubscriptionAttributes' {Text
attributeName :: Text
$sel:attributeName:SetSubscriptionAttributes' :: SetSubscriptionAttributes -> Text
attributeName} -> Text
attributeName) (\s :: SetSubscriptionAttributes
s@SetSubscriptionAttributes' {} Text
a -> SetSubscriptionAttributes
s {$sel:attributeName:SetSubscriptionAttributes' :: Text
attributeName = Text
a} :: SetSubscriptionAttributes)

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

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

instance Prelude.NFData SetSubscriptionAttributes where
  rnf :: SetSubscriptionAttributes -> ()
rnf SetSubscriptionAttributes' {Maybe Text
Text
attributeName :: Text
subscriptionArn :: Text
attributeValue :: Maybe Text
$sel:attributeName:SetSubscriptionAttributes' :: SetSubscriptionAttributes -> Text
$sel:subscriptionArn:SetSubscriptionAttributes' :: SetSubscriptionAttributes -> Text
$sel:attributeValue:SetSubscriptionAttributes' :: SetSubscriptionAttributes -> Maybe Text
..} =
    forall a. NFData a => a -> ()
Prelude.rnf Maybe Text
attributeValue
      seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf Text
subscriptionArn
      seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf Text
attributeName

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

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

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

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

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

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