{-# 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.Subscribe
-- Copyright   : (c) 2013-2023 Brendan Hay
-- License     : Mozilla Public License, v. 2.0.
-- Maintainer  : Brendan Hay
-- Stability   : auto-generated
-- Portability : non-portable (GHC extensions)
--
-- Subscribes an endpoint to an Amazon SNS topic. If the endpoint type is
-- HTTP\/S or email, or if the endpoint and the topic are not in the same
-- Amazon Web Services account, the endpoint owner must run the
-- @ConfirmSubscription@ action to confirm the subscription.
--
-- You call the @ConfirmSubscription@ action with the token from the
-- subscription response. Confirmation tokens are valid for three days.
--
-- This action is throttled at 100 transactions per second (TPS).
module Amazonka.SNS.Subscribe
  ( -- * Creating a Request
    Subscribe (..),
    newSubscribe,

    -- * Request Lenses
    subscribe_attributes,
    subscribe_endpoint,
    subscribe_returnSubscriptionArn,
    subscribe_topicArn,
    subscribe_protocol,

    -- * Destructuring the Response
    SubscribeResponse (..),
    newSubscribeResponse,

    -- * Response Lenses
    subscribeResponse_subscriptionArn,
    subscribeResponse_httpStatus,
  )
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 Subscribe action.
--
-- /See:/ 'newSubscribe' smart constructor.
data Subscribe = Subscribe'
  { -- | A map of attributes with their corresponding values.
    --
    -- The following lists the names, descriptions, and values of the special
    -- request parameters that the @Subscribe@ 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/.
    Subscribe -> Maybe (HashMap Text Text)
attributes :: Prelude.Maybe (Prelude.HashMap Prelude.Text Prelude.Text),
    -- | The endpoint that you want to receive notifications. Endpoints vary by
    -- protocol:
    --
    -- -   For the @http@ protocol, the (public) endpoint is a URL beginning
    --     with @http:\/\/@.
    --
    -- -   For the @https@ protocol, the (public) endpoint is a URL beginning
    --     with @https:\/\/@.
    --
    -- -   For the @email@ protocol, the endpoint is an email address.
    --
    -- -   For the @email-json@ protocol, the endpoint is an email address.
    --
    -- -   For the @sms@ protocol, the endpoint is a phone number of an
    --     SMS-enabled device.
    --
    -- -   For the @sqs@ protocol, the endpoint is the ARN of an Amazon SQS
    --     queue.
    --
    -- -   For the @application@ protocol, the endpoint is the EndpointArn of a
    --     mobile app and device.
    --
    -- -   For the @lambda@ protocol, the endpoint is the ARN of an Lambda
    --     function.
    --
    -- -   For the @firehose@ protocol, the endpoint is the ARN of an Amazon
    --     Kinesis Data Firehose delivery stream.
    Subscribe -> Maybe Text
endpoint :: Prelude.Maybe Prelude.Text,
    -- | Sets whether the response from the @Subscribe@ request includes the
    -- subscription ARN, even if the subscription is not yet confirmed.
    --
    -- If you set this parameter to @true@, the response includes the ARN in
    -- all cases, even if the subscription is not yet confirmed. In addition to
    -- the ARN for confirmed subscriptions, the response also includes the
    -- @pending subscription@ ARN value for subscriptions that aren\'t yet
    -- confirmed. A subscription becomes confirmed when the subscriber calls
    -- the @ConfirmSubscription@ action with a confirmation token.
    --
    -- The default value is @false@.
    Subscribe -> Maybe Bool
returnSubscriptionArn :: Prelude.Maybe Prelude.Bool,
    -- | The ARN of the topic you want to subscribe to.
    Subscribe -> Text
topicArn :: Prelude.Text,
    -- | The protocol that you want to use. Supported protocols include:
    --
    -- -   @http@ – delivery of JSON-encoded message via HTTP POST
    --
    -- -   @https@ – delivery of JSON-encoded message via HTTPS POST
    --
    -- -   @email@ – delivery of message via SMTP
    --
    -- -   @email-json@ – delivery of JSON-encoded message via SMTP
    --
    -- -   @sms@ – delivery of message via SMS
    --
    -- -   @sqs@ – delivery of JSON-encoded message to an Amazon SQS queue
    --
    -- -   @application@ – delivery of JSON-encoded message to an EndpointArn
    --     for a mobile app and device
    --
    -- -   @lambda@ – delivery of JSON-encoded message to an Lambda function
    --
    -- -   @firehose@ – delivery of JSON-encoded message to an Amazon Kinesis
    --     Data Firehose delivery stream.
    Subscribe -> Text
protocol :: Prelude.Text
  }
  deriving (Subscribe -> Subscribe -> Bool
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: Subscribe -> Subscribe -> Bool
$c/= :: Subscribe -> Subscribe -> Bool
== :: Subscribe -> Subscribe -> Bool
$c== :: Subscribe -> Subscribe -> Bool
Prelude.Eq, ReadPrec [Subscribe]
ReadPrec Subscribe
Int -> ReadS Subscribe
ReadS [Subscribe]
forall a.
(Int -> ReadS a)
-> ReadS [a] -> ReadPrec a -> ReadPrec [a] -> Read a
readListPrec :: ReadPrec [Subscribe]
$creadListPrec :: ReadPrec [Subscribe]
readPrec :: ReadPrec Subscribe
$creadPrec :: ReadPrec Subscribe
readList :: ReadS [Subscribe]
$creadList :: ReadS [Subscribe]
readsPrec :: Int -> ReadS Subscribe
$creadsPrec :: Int -> ReadS Subscribe
Prelude.Read, Int -> Subscribe -> ShowS
[Subscribe] -> ShowS
Subscribe -> String
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [Subscribe] -> ShowS
$cshowList :: [Subscribe] -> ShowS
show :: Subscribe -> String
$cshow :: Subscribe -> String
showsPrec :: Int -> Subscribe -> ShowS
$cshowsPrec :: Int -> Subscribe -> ShowS
Prelude.Show, forall x. Rep Subscribe x -> Subscribe
forall x. Subscribe -> Rep Subscribe x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cto :: forall x. Rep Subscribe x -> Subscribe
$cfrom :: forall x. Subscribe -> Rep Subscribe x
Prelude.Generic)

-- |
-- Create a value of 'Subscribe' 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:
--
-- 'attributes', 'subscribe_attributes' - A map of attributes with their corresponding values.
--
-- The following lists the names, descriptions, and values of the special
-- request parameters that the @Subscribe@ 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/.
--
-- 'endpoint', 'subscribe_endpoint' - The endpoint that you want to receive notifications. Endpoints vary by
-- protocol:
--
-- -   For the @http@ protocol, the (public) endpoint is a URL beginning
--     with @http:\/\/@.
--
-- -   For the @https@ protocol, the (public) endpoint is a URL beginning
--     with @https:\/\/@.
--
-- -   For the @email@ protocol, the endpoint is an email address.
--
-- -   For the @email-json@ protocol, the endpoint is an email address.
--
-- -   For the @sms@ protocol, the endpoint is a phone number of an
--     SMS-enabled device.
--
-- -   For the @sqs@ protocol, the endpoint is the ARN of an Amazon SQS
--     queue.
--
-- -   For the @application@ protocol, the endpoint is the EndpointArn of a
--     mobile app and device.
--
-- -   For the @lambda@ protocol, the endpoint is the ARN of an Lambda
--     function.
--
-- -   For the @firehose@ protocol, the endpoint is the ARN of an Amazon
--     Kinesis Data Firehose delivery stream.
--
-- 'returnSubscriptionArn', 'subscribe_returnSubscriptionArn' - Sets whether the response from the @Subscribe@ request includes the
-- subscription ARN, even if the subscription is not yet confirmed.
--
-- If you set this parameter to @true@, the response includes the ARN in
-- all cases, even if the subscription is not yet confirmed. In addition to
-- the ARN for confirmed subscriptions, the response also includes the
-- @pending subscription@ ARN value for subscriptions that aren\'t yet
-- confirmed. A subscription becomes confirmed when the subscriber calls
-- the @ConfirmSubscription@ action with a confirmation token.
--
-- The default value is @false@.
--
-- 'topicArn', 'subscribe_topicArn' - The ARN of the topic you want to subscribe to.
--
-- 'protocol', 'subscribe_protocol' - The protocol that you want to use. Supported protocols include:
--
-- -   @http@ – delivery of JSON-encoded message via HTTP POST
--
-- -   @https@ – delivery of JSON-encoded message via HTTPS POST
--
-- -   @email@ – delivery of message via SMTP
--
-- -   @email-json@ – delivery of JSON-encoded message via SMTP
--
-- -   @sms@ – delivery of message via SMS
--
-- -   @sqs@ – delivery of JSON-encoded message to an Amazon SQS queue
--
-- -   @application@ – delivery of JSON-encoded message to an EndpointArn
--     for a mobile app and device
--
-- -   @lambda@ – delivery of JSON-encoded message to an Lambda function
--
-- -   @firehose@ – delivery of JSON-encoded message to an Amazon Kinesis
--     Data Firehose delivery stream.
newSubscribe ::
  -- | 'topicArn'
  Prelude.Text ->
  -- | 'protocol'
  Prelude.Text ->
  Subscribe
newSubscribe :: Text -> Text -> Subscribe
newSubscribe Text
pTopicArn_ Text
pProtocol_ =
  Subscribe'
    { $sel:attributes:Subscribe' :: Maybe (HashMap Text Text)
attributes = forall a. Maybe a
Prelude.Nothing,
      $sel:endpoint:Subscribe' :: Maybe Text
endpoint = forall a. Maybe a
Prelude.Nothing,
      $sel:returnSubscriptionArn:Subscribe' :: Maybe Bool
returnSubscriptionArn = forall a. Maybe a
Prelude.Nothing,
      $sel:topicArn:Subscribe' :: Text
topicArn = Text
pTopicArn_,
      $sel:protocol:Subscribe' :: Text
protocol = Text
pProtocol_
    }

-- | A map of attributes with their corresponding values.
--
-- The following lists the names, descriptions, and values of the special
-- request parameters that the @Subscribe@ 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/.
subscribe_attributes :: Lens.Lens' Subscribe (Prelude.Maybe (Prelude.HashMap Prelude.Text Prelude.Text))
subscribe_attributes :: Lens' Subscribe (Maybe (HashMap Text Text))
subscribe_attributes = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\Subscribe' {Maybe (HashMap Text Text)
attributes :: Maybe (HashMap Text Text)
$sel:attributes:Subscribe' :: Subscribe -> Maybe (HashMap Text Text)
attributes} -> Maybe (HashMap Text Text)
attributes) (\s :: Subscribe
s@Subscribe' {} Maybe (HashMap Text Text)
a -> Subscribe
s {$sel:attributes:Subscribe' :: Maybe (HashMap Text Text)
attributes = Maybe (HashMap Text Text)
a} :: Subscribe) forall b c a. (b -> c) -> (a -> b) -> a -> c
Prelude.. forall (f :: * -> *) (g :: * -> *) s t a b.
(Functor f, Functor g) =>
AnIso s t a b -> Iso (f s) (g t) (f a) (g b)
Lens.mapping forall s t a b. (Coercible s a, Coercible t b) => Iso s t a b
Lens.coerced

-- | The endpoint that you want to receive notifications. Endpoints vary by
-- protocol:
--
-- -   For the @http@ protocol, the (public) endpoint is a URL beginning
--     with @http:\/\/@.
--
-- -   For the @https@ protocol, the (public) endpoint is a URL beginning
--     with @https:\/\/@.
--
-- -   For the @email@ protocol, the endpoint is an email address.
--
-- -   For the @email-json@ protocol, the endpoint is an email address.
--
-- -   For the @sms@ protocol, the endpoint is a phone number of an
--     SMS-enabled device.
--
-- -   For the @sqs@ protocol, the endpoint is the ARN of an Amazon SQS
--     queue.
--
-- -   For the @application@ protocol, the endpoint is the EndpointArn of a
--     mobile app and device.
--
-- -   For the @lambda@ protocol, the endpoint is the ARN of an Lambda
--     function.
--
-- -   For the @firehose@ protocol, the endpoint is the ARN of an Amazon
--     Kinesis Data Firehose delivery stream.
subscribe_endpoint :: Lens.Lens' Subscribe (Prelude.Maybe Prelude.Text)
subscribe_endpoint :: Lens' Subscribe (Maybe Text)
subscribe_endpoint = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\Subscribe' {Maybe Text
endpoint :: Maybe Text
$sel:endpoint:Subscribe' :: Subscribe -> Maybe Text
endpoint} -> Maybe Text
endpoint) (\s :: Subscribe
s@Subscribe' {} Maybe Text
a -> Subscribe
s {$sel:endpoint:Subscribe' :: Maybe Text
endpoint = Maybe Text
a} :: Subscribe)

-- | Sets whether the response from the @Subscribe@ request includes the
-- subscription ARN, even if the subscription is not yet confirmed.
--
-- If you set this parameter to @true@, the response includes the ARN in
-- all cases, even if the subscription is not yet confirmed. In addition to
-- the ARN for confirmed subscriptions, the response also includes the
-- @pending subscription@ ARN value for subscriptions that aren\'t yet
-- confirmed. A subscription becomes confirmed when the subscriber calls
-- the @ConfirmSubscription@ action with a confirmation token.
--
-- The default value is @false@.
subscribe_returnSubscriptionArn :: Lens.Lens' Subscribe (Prelude.Maybe Prelude.Bool)
subscribe_returnSubscriptionArn :: Lens' Subscribe (Maybe Bool)
subscribe_returnSubscriptionArn = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\Subscribe' {Maybe Bool
returnSubscriptionArn :: Maybe Bool
$sel:returnSubscriptionArn:Subscribe' :: Subscribe -> Maybe Bool
returnSubscriptionArn} -> Maybe Bool
returnSubscriptionArn) (\s :: Subscribe
s@Subscribe' {} Maybe Bool
a -> Subscribe
s {$sel:returnSubscriptionArn:Subscribe' :: Maybe Bool
returnSubscriptionArn = Maybe Bool
a} :: Subscribe)

-- | The ARN of the topic you want to subscribe to.
subscribe_topicArn :: Lens.Lens' Subscribe Prelude.Text
subscribe_topicArn :: Lens' Subscribe Text
subscribe_topicArn = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\Subscribe' {Text
topicArn :: Text
$sel:topicArn:Subscribe' :: Subscribe -> Text
topicArn} -> Text
topicArn) (\s :: Subscribe
s@Subscribe' {} Text
a -> Subscribe
s {$sel:topicArn:Subscribe' :: Text
topicArn = Text
a} :: Subscribe)

-- | The protocol that you want to use. Supported protocols include:
--
-- -   @http@ – delivery of JSON-encoded message via HTTP POST
--
-- -   @https@ – delivery of JSON-encoded message via HTTPS POST
--
-- -   @email@ – delivery of message via SMTP
--
-- -   @email-json@ – delivery of JSON-encoded message via SMTP
--
-- -   @sms@ – delivery of message via SMS
--
-- -   @sqs@ – delivery of JSON-encoded message to an Amazon SQS queue
--
-- -   @application@ – delivery of JSON-encoded message to an EndpointArn
--     for a mobile app and device
--
-- -   @lambda@ – delivery of JSON-encoded message to an Lambda function
--
-- -   @firehose@ – delivery of JSON-encoded message to an Amazon Kinesis
--     Data Firehose delivery stream.
subscribe_protocol :: Lens.Lens' Subscribe Prelude.Text
subscribe_protocol :: Lens' Subscribe Text
subscribe_protocol = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\Subscribe' {Text
protocol :: Text
$sel:protocol:Subscribe' :: Subscribe -> Text
protocol} -> Text
protocol) (\s :: Subscribe
s@Subscribe' {} Text
a -> Subscribe
s {$sel:protocol:Subscribe' :: Text
protocol = Text
a} :: Subscribe)

instance Core.AWSRequest Subscribe where
  type AWSResponse Subscribe = SubscribeResponse
  request :: (Service -> Service) -> Subscribe -> Request Subscribe
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 Subscribe
-> ClientResponse ClientBody
-> m (Either Error (ClientResponse (AWSResponse Subscribe)))
response =
    forall (m :: * -> *) a.
MonadResource m =>
Text
-> (Int
    -> ResponseHeaders -> [Node] -> Either String (AWSResponse a))
-> (ByteStringLazy -> IO ByteStringLazy)
-> Service
-> Proxy a
-> ClientResponse ClientBody
-> m (Either Error (ClientResponse (AWSResponse a)))
Response.receiveXMLWrapper
      Text
"SubscribeResult"
      ( \Int
s ResponseHeaders
h [Node]
x ->
          Maybe Text -> Int -> SubscribeResponse
SubscribeResponse'
            forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
Prelude.<$> ([Node]
x forall a. FromXML a => [Node] -> Text -> Either String (Maybe a)
Data..@? Text
"SubscriptionArn")
            forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
Prelude.<*> (forall (f :: * -> *) a. Applicative f => a -> f a
Prelude.pure (forall a. Enum a => a -> Int
Prelude.fromEnum Int
s))
      )

instance Prelude.Hashable Subscribe where
  hashWithSalt :: Int -> Subscribe -> Int
hashWithSalt Int
_salt Subscribe' {Maybe Bool
Maybe Text
Maybe (HashMap Text Text)
Text
protocol :: Text
topicArn :: Text
returnSubscriptionArn :: Maybe Bool
endpoint :: Maybe Text
attributes :: Maybe (HashMap Text Text)
$sel:protocol:Subscribe' :: Subscribe -> Text
$sel:topicArn:Subscribe' :: Subscribe -> Text
$sel:returnSubscriptionArn:Subscribe' :: Subscribe -> Maybe Bool
$sel:endpoint:Subscribe' :: Subscribe -> Maybe Text
$sel:attributes:Subscribe' :: Subscribe -> Maybe (HashMap Text Text)
..} =
    Int
_salt
      forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Maybe (HashMap Text Text)
attributes
      forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Maybe Text
endpoint
      forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Maybe Bool
returnSubscriptionArn
      forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Text
topicArn
      forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Text
protocol

instance Prelude.NFData Subscribe where
  rnf :: Subscribe -> ()
rnf Subscribe' {Maybe Bool
Maybe Text
Maybe (HashMap Text Text)
Text
protocol :: Text
topicArn :: Text
returnSubscriptionArn :: Maybe Bool
endpoint :: Maybe Text
attributes :: Maybe (HashMap Text Text)
$sel:protocol:Subscribe' :: Subscribe -> Text
$sel:topicArn:Subscribe' :: Subscribe -> Text
$sel:returnSubscriptionArn:Subscribe' :: Subscribe -> Maybe Bool
$sel:endpoint:Subscribe' :: Subscribe -> Maybe Text
$sel:attributes:Subscribe' :: Subscribe -> Maybe (HashMap Text Text)
..} =
    forall a. NFData a => a -> ()
Prelude.rnf Maybe (HashMap Text Text)
attributes
      seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf Maybe Text
endpoint
      seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf Maybe Bool
returnSubscriptionArn
      seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf Text
topicArn
      seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf Text
protocol

instance Data.ToHeaders Subscribe where
  toHeaders :: Subscribe -> ResponseHeaders
toHeaders = forall a b. a -> b -> a
Prelude.const forall a. Monoid a => a
Prelude.mempty

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

instance Data.ToQuery Subscribe where
  toQuery :: Subscribe -> QueryString
toQuery Subscribe' {Maybe Bool
Maybe Text
Maybe (HashMap Text Text)
Text
protocol :: Text
topicArn :: Text
returnSubscriptionArn :: Maybe Bool
endpoint :: Maybe Text
attributes :: Maybe (HashMap Text Text)
$sel:protocol:Subscribe' :: Subscribe -> Text
$sel:topicArn:Subscribe' :: Subscribe -> Text
$sel:returnSubscriptionArn:Subscribe' :: Subscribe -> Maybe Bool
$sel:endpoint:Subscribe' :: Subscribe -> Maybe Text
$sel:attributes:Subscribe' :: Subscribe -> Maybe (HashMap Text Text)
..} =
    forall a. Monoid a => [a] -> a
Prelude.mconcat
      [ ByteString
"Action"
          forall a. ToQuery a => ByteString -> a -> QueryString
Data.=: (ByteString
"Subscribe" :: Prelude.ByteString),
        ByteString
"Version"
          forall a. ToQuery a => ByteString -> a -> QueryString
Data.=: (ByteString
"2010-03-31" :: Prelude.ByteString),
        ByteString
"Attributes"
          forall a. ToQuery a => ByteString -> a -> QueryString
Data.=: forall a. ToQuery a => a -> QueryString
Data.toQuery
            ( forall k v.
(ToQuery k, ToQuery v) =>
ByteString
-> ByteString -> ByteString -> HashMap k v -> QueryString
Data.toQueryMap ByteString
"entry" ByteString
"key" ByteString
"value"
                forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
Prelude.<$> Maybe (HashMap Text Text)
attributes
            ),
        ByteString
"Endpoint" forall a. ToQuery a => ByteString -> a -> QueryString
Data.=: Maybe Text
endpoint,
        ByteString
"ReturnSubscriptionArn"
          forall a. ToQuery a => ByteString -> a -> QueryString
Data.=: Maybe Bool
returnSubscriptionArn,
        ByteString
"TopicArn" forall a. ToQuery a => ByteString -> a -> QueryString
Data.=: Text
topicArn,
        ByteString
"Protocol" forall a. ToQuery a => ByteString -> a -> QueryString
Data.=: Text
protocol
      ]

-- | Response for Subscribe action.
--
-- /See:/ 'newSubscribeResponse' smart constructor.
data SubscribeResponse = SubscribeResponse'
  { -- | The ARN of the subscription if it is confirmed, or the string \"pending
    -- confirmation\" if the subscription requires confirmation. However, if
    -- the API request parameter @ReturnSubscriptionArn@ is true, then the
    -- value is always the subscription ARN, even if the subscription requires
    -- confirmation.
    SubscribeResponse -> Maybe Text
subscriptionArn :: Prelude.Maybe Prelude.Text,
    -- | The response's http status code.
    SubscribeResponse -> Int
httpStatus :: Prelude.Int
  }
  deriving (SubscribeResponse -> SubscribeResponse -> Bool
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: SubscribeResponse -> SubscribeResponse -> Bool
$c/= :: SubscribeResponse -> SubscribeResponse -> Bool
== :: SubscribeResponse -> SubscribeResponse -> Bool
$c== :: SubscribeResponse -> SubscribeResponse -> Bool
Prelude.Eq, ReadPrec [SubscribeResponse]
ReadPrec SubscribeResponse
Int -> ReadS SubscribeResponse
ReadS [SubscribeResponse]
forall a.
(Int -> ReadS a)
-> ReadS [a] -> ReadPrec a -> ReadPrec [a] -> Read a
readListPrec :: ReadPrec [SubscribeResponse]
$creadListPrec :: ReadPrec [SubscribeResponse]
readPrec :: ReadPrec SubscribeResponse
$creadPrec :: ReadPrec SubscribeResponse
readList :: ReadS [SubscribeResponse]
$creadList :: ReadS [SubscribeResponse]
readsPrec :: Int -> ReadS SubscribeResponse
$creadsPrec :: Int -> ReadS SubscribeResponse
Prelude.Read, Int -> SubscribeResponse -> ShowS
[SubscribeResponse] -> ShowS
SubscribeResponse -> String
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [SubscribeResponse] -> ShowS
$cshowList :: [SubscribeResponse] -> ShowS
show :: SubscribeResponse -> String
$cshow :: SubscribeResponse -> String
showsPrec :: Int -> SubscribeResponse -> ShowS
$cshowsPrec :: Int -> SubscribeResponse -> ShowS
Prelude.Show, forall x. Rep SubscribeResponse x -> SubscribeResponse
forall x. SubscribeResponse -> Rep SubscribeResponse x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cto :: forall x. Rep SubscribeResponse x -> SubscribeResponse
$cfrom :: forall x. SubscribeResponse -> Rep SubscribeResponse x
Prelude.Generic)

-- |
-- Create a value of 'SubscribeResponse' 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', 'subscribeResponse_subscriptionArn' - The ARN of the subscription if it is confirmed, or the string \"pending
-- confirmation\" if the subscription requires confirmation. However, if
-- the API request parameter @ReturnSubscriptionArn@ is true, then the
-- value is always the subscription ARN, even if the subscription requires
-- confirmation.
--
-- 'httpStatus', 'subscribeResponse_httpStatus' - The response's http status code.
newSubscribeResponse ::
  -- | 'httpStatus'
  Prelude.Int ->
  SubscribeResponse
newSubscribeResponse :: Int -> SubscribeResponse
newSubscribeResponse Int
pHttpStatus_ =
  SubscribeResponse'
    { $sel:subscriptionArn:SubscribeResponse' :: Maybe Text
subscriptionArn =
        forall a. Maybe a
Prelude.Nothing,
      $sel:httpStatus:SubscribeResponse' :: Int
httpStatus = Int
pHttpStatus_
    }

-- | The ARN of the subscription if it is confirmed, or the string \"pending
-- confirmation\" if the subscription requires confirmation. However, if
-- the API request parameter @ReturnSubscriptionArn@ is true, then the
-- value is always the subscription ARN, even if the subscription requires
-- confirmation.
subscribeResponse_subscriptionArn :: Lens.Lens' SubscribeResponse (Prelude.Maybe Prelude.Text)
subscribeResponse_subscriptionArn :: Lens' SubscribeResponse (Maybe Text)
subscribeResponse_subscriptionArn = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\SubscribeResponse' {Maybe Text
subscriptionArn :: Maybe Text
$sel:subscriptionArn:SubscribeResponse' :: SubscribeResponse -> Maybe Text
subscriptionArn} -> Maybe Text
subscriptionArn) (\s :: SubscribeResponse
s@SubscribeResponse' {} Maybe Text
a -> SubscribeResponse
s {$sel:subscriptionArn:SubscribeResponse' :: Maybe Text
subscriptionArn = Maybe Text
a} :: SubscribeResponse)

-- | The response's http status code.
subscribeResponse_httpStatus :: Lens.Lens' SubscribeResponse Prelude.Int
subscribeResponse_httpStatus :: Lens' SubscribeResponse Int
subscribeResponse_httpStatus = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\SubscribeResponse' {Int
httpStatus :: Int
$sel:httpStatus:SubscribeResponse' :: SubscribeResponse -> Int
httpStatus} -> Int
httpStatus) (\s :: SubscribeResponse
s@SubscribeResponse' {} Int
a -> SubscribeResponse
s {$sel:httpStatus:SubscribeResponse' :: Int
httpStatus = Int
a} :: SubscribeResponse)

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