{-# 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.PublishBatch
-- Copyright   : (c) 2013-2023 Brendan Hay
-- License     : Mozilla Public License, v. 2.0.
-- Maintainer  : Brendan Hay
-- Stability   : auto-generated
-- Portability : non-portable (GHC extensions)
--
-- Publishes up to ten messages to the specified topic. This is a batch
-- version of @Publish@. For FIFO topics, multiple messages within a single
-- batch are published in the order they are sent, and messages are
-- deduplicated within the batch and across batches for 5 minutes.
--
-- The result of publishing each message is reported individually in the
-- response. Because the batch request can result in a combination of
-- successful and unsuccessful actions, you should check for batch errors
-- even when the call returns an HTTP status code of @200@.
--
-- The maximum allowed individual message size and the maximum total
-- payload size (the sum of the individual lengths of all of the batched
-- messages) are both 256 KB (262,144 bytes).
--
-- Some actions take lists of parameters. These lists are specified using
-- the @param.n@ notation. Values of @n@ are integers starting from 1. For
-- example, a parameter list with two elements looks like this:
--
-- &AttributeName.1=first
--
-- &AttributeName.2=second
--
-- If you send a batch message to a topic, Amazon SNS publishes the batch
-- message to each endpoint that is subscribed to the topic. The format of
-- the batch message depends on the notification protocol for each
-- subscribed endpoint.
--
-- When a @messageId@ is returned, the batch message is saved and Amazon
-- SNS immediately delivers the message to subscribers.
module Amazonka.SNS.PublishBatch
  ( -- * Creating a Request
    PublishBatch (..),
    newPublishBatch,

    -- * Request Lenses
    publishBatch_topicArn,
    publishBatch_publishBatchRequestEntries,

    -- * Destructuring the Response
    PublishBatchResponse (..),
    newPublishBatchResponse,

    -- * Response Lenses
    publishBatchResponse_failed,
    publishBatchResponse_successful,
    publishBatchResponse_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

-- | /See:/ 'newPublishBatch' smart constructor.
data PublishBatch = PublishBatch'
  { -- | The Amazon resource name (ARN) of the topic you want to batch publish
    -- to.
    PublishBatch -> Text
topicArn :: Prelude.Text,
    -- | A list of @PublishBatch@ request entries to be sent to the SNS topic.
    PublishBatch -> [PublishBatchRequestEntry]
publishBatchRequestEntries :: [PublishBatchRequestEntry]
  }
  deriving (PublishBatch -> PublishBatch -> Bool
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: PublishBatch -> PublishBatch -> Bool
$c/= :: PublishBatch -> PublishBatch -> Bool
== :: PublishBatch -> PublishBatch -> Bool
$c== :: PublishBatch -> PublishBatch -> Bool
Prelude.Eq, ReadPrec [PublishBatch]
ReadPrec PublishBatch
Int -> ReadS PublishBatch
ReadS [PublishBatch]
forall a.
(Int -> ReadS a)
-> ReadS [a] -> ReadPrec a -> ReadPrec [a] -> Read a
readListPrec :: ReadPrec [PublishBatch]
$creadListPrec :: ReadPrec [PublishBatch]
readPrec :: ReadPrec PublishBatch
$creadPrec :: ReadPrec PublishBatch
readList :: ReadS [PublishBatch]
$creadList :: ReadS [PublishBatch]
readsPrec :: Int -> ReadS PublishBatch
$creadsPrec :: Int -> ReadS PublishBatch
Prelude.Read, Int -> PublishBatch -> ShowS
[PublishBatch] -> ShowS
PublishBatch -> String
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [PublishBatch] -> ShowS
$cshowList :: [PublishBatch] -> ShowS
show :: PublishBatch -> String
$cshow :: PublishBatch -> String
showsPrec :: Int -> PublishBatch -> ShowS
$cshowsPrec :: Int -> PublishBatch -> ShowS
Prelude.Show, forall x. Rep PublishBatch x -> PublishBatch
forall x. PublishBatch -> Rep PublishBatch x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cto :: forall x. Rep PublishBatch x -> PublishBatch
$cfrom :: forall x. PublishBatch -> Rep PublishBatch x
Prelude.Generic)

-- |
-- Create a value of 'PublishBatch' 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:
--
-- 'topicArn', 'publishBatch_topicArn' - The Amazon resource name (ARN) of the topic you want to batch publish
-- to.
--
-- 'publishBatchRequestEntries', 'publishBatch_publishBatchRequestEntries' - A list of @PublishBatch@ request entries to be sent to the SNS topic.
newPublishBatch ::
  -- | 'topicArn'
  Prelude.Text ->
  PublishBatch
newPublishBatch :: Text -> PublishBatch
newPublishBatch Text
pTopicArn_ =
  PublishBatch'
    { $sel:topicArn:PublishBatch' :: Text
topicArn = Text
pTopicArn_,
      $sel:publishBatchRequestEntries:PublishBatch' :: [PublishBatchRequestEntry]
publishBatchRequestEntries = forall a. Monoid a => a
Prelude.mempty
    }

-- | The Amazon resource name (ARN) of the topic you want to batch publish
-- to.
publishBatch_topicArn :: Lens.Lens' PublishBatch Prelude.Text
publishBatch_topicArn :: Lens' PublishBatch Text
publishBatch_topicArn = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\PublishBatch' {Text
topicArn :: Text
$sel:topicArn:PublishBatch' :: PublishBatch -> Text
topicArn} -> Text
topicArn) (\s :: PublishBatch
s@PublishBatch' {} Text
a -> PublishBatch
s {$sel:topicArn:PublishBatch' :: Text
topicArn = Text
a} :: PublishBatch)

-- | A list of @PublishBatch@ request entries to be sent to the SNS topic.
publishBatch_publishBatchRequestEntries :: Lens.Lens' PublishBatch [PublishBatchRequestEntry]
publishBatch_publishBatchRequestEntries :: Lens' PublishBatch [PublishBatchRequestEntry]
publishBatch_publishBatchRequestEntries = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\PublishBatch' {[PublishBatchRequestEntry]
publishBatchRequestEntries :: [PublishBatchRequestEntry]
$sel:publishBatchRequestEntries:PublishBatch' :: PublishBatch -> [PublishBatchRequestEntry]
publishBatchRequestEntries} -> [PublishBatchRequestEntry]
publishBatchRequestEntries) (\s :: PublishBatch
s@PublishBatch' {} [PublishBatchRequestEntry]
a -> PublishBatch
s {$sel:publishBatchRequestEntries:PublishBatch' :: [PublishBatchRequestEntry]
publishBatchRequestEntries = [PublishBatchRequestEntry]
a} :: PublishBatch) forall b c a. (b -> c) -> (a -> b) -> a -> c
Prelude.. forall s t a b. (Coercible s a, Coercible t b) => Iso s t a b
Lens.coerced

instance Core.AWSRequest PublishBatch where
  type AWSResponse PublishBatch = PublishBatchResponse
  request :: (Service -> Service) -> PublishBatch -> Request PublishBatch
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 PublishBatch
-> ClientResponse ClientBody
-> m (Either Error (ClientResponse (AWSResponse PublishBatch)))
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
"PublishBatchResult"
      ( \Int
s ResponseHeaders
h [Node]
x ->
          Maybe [BatchResultErrorEntry]
-> Maybe [PublishBatchResultEntry] -> Int -> PublishBatchResponse
PublishBatchResponse'
            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
"Failed"
                            forall (f :: * -> *) a. Functor f => f (Maybe a) -> a -> f a
Core..!@ forall a. Monoid a => a
Prelude.mempty
                            forall (m :: * -> *) a b. Monad m => m a -> (a -> m b) -> m b
Prelude.>>= forall (f :: * -> *) a b.
Applicative f =>
([a] -> f b) -> [a] -> f (Maybe b)
Core.may (forall a. FromXML a => Text -> [Node] -> Either String [a]
Data.parseXMLList Text
"member")
                        )
            forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
Prelude.<*> ( [Node]
x
                            forall a. FromXML a => [Node] -> Text -> Either String (Maybe a)
Data..@? Text
"Successful"
                            forall (f :: * -> *) a. Functor f => f (Maybe a) -> a -> f a
Core..!@ forall a. Monoid a => a
Prelude.mempty
                            forall (m :: * -> *) a b. Monad m => m a -> (a -> m b) -> m b
Prelude.>>= forall (f :: * -> *) a b.
Applicative f =>
([a] -> f b) -> [a] -> f (Maybe b)
Core.may (forall a. FromXML a => Text -> [Node] -> Either String [a]
Data.parseXMLList Text
"member")
                        )
            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 PublishBatch where
  hashWithSalt :: Int -> PublishBatch -> Int
hashWithSalt Int
_salt PublishBatch' {[PublishBatchRequestEntry]
Text
publishBatchRequestEntries :: [PublishBatchRequestEntry]
topicArn :: Text
$sel:publishBatchRequestEntries:PublishBatch' :: PublishBatch -> [PublishBatchRequestEntry]
$sel:topicArn:PublishBatch' :: PublishBatch -> Text
..} =
    Int
_salt
      forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Text
topicArn
      forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` [PublishBatchRequestEntry]
publishBatchRequestEntries

instance Prelude.NFData PublishBatch where
  rnf :: PublishBatch -> ()
rnf PublishBatch' {[PublishBatchRequestEntry]
Text
publishBatchRequestEntries :: [PublishBatchRequestEntry]
topicArn :: Text
$sel:publishBatchRequestEntries:PublishBatch' :: PublishBatch -> [PublishBatchRequestEntry]
$sel:topicArn:PublishBatch' :: PublishBatch -> Text
..} =
    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 [PublishBatchRequestEntry]
publishBatchRequestEntries

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

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

instance Data.ToQuery PublishBatch where
  toQuery :: PublishBatch -> QueryString
toQuery PublishBatch' {[PublishBatchRequestEntry]
Text
publishBatchRequestEntries :: [PublishBatchRequestEntry]
topicArn :: Text
$sel:publishBatchRequestEntries:PublishBatch' :: PublishBatch -> [PublishBatchRequestEntry]
$sel:topicArn:PublishBatch' :: PublishBatch -> Text
..} =
    forall a. Monoid a => [a] -> a
Prelude.mconcat
      [ ByteString
"Action"
          forall a. ToQuery a => ByteString -> a -> QueryString
Data.=: (ByteString
"PublishBatch" :: Prelude.ByteString),
        ByteString
"Version"
          forall a. ToQuery a => ByteString -> a -> QueryString
Data.=: (ByteString
"2010-03-31" :: Prelude.ByteString),
        ByteString
"TopicArn" forall a. ToQuery a => ByteString -> a -> QueryString
Data.=: Text
topicArn,
        ByteString
"PublishBatchRequestEntries"
          forall a. ToQuery a => ByteString -> a -> QueryString
Data.=: forall a.
(IsList a, ToQuery (Item a)) =>
ByteString -> a -> QueryString
Data.toQueryList ByteString
"member" [PublishBatchRequestEntry]
publishBatchRequestEntries
      ]

-- | /See:/ 'newPublishBatchResponse' smart constructor.
data PublishBatchResponse = PublishBatchResponse'
  { -- | A list of failed @PublishBatch@ responses.
    PublishBatchResponse -> Maybe [BatchResultErrorEntry]
failed :: Prelude.Maybe [BatchResultErrorEntry],
    -- | A list of successful @PublishBatch@ responses.
    PublishBatchResponse -> Maybe [PublishBatchResultEntry]
successful :: Prelude.Maybe [PublishBatchResultEntry],
    -- | The response's http status code.
    PublishBatchResponse -> Int
httpStatus :: Prelude.Int
  }
  deriving (PublishBatchResponse -> PublishBatchResponse -> Bool
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: PublishBatchResponse -> PublishBatchResponse -> Bool
$c/= :: PublishBatchResponse -> PublishBatchResponse -> Bool
== :: PublishBatchResponse -> PublishBatchResponse -> Bool
$c== :: PublishBatchResponse -> PublishBatchResponse -> Bool
Prelude.Eq, ReadPrec [PublishBatchResponse]
ReadPrec PublishBatchResponse
Int -> ReadS PublishBatchResponse
ReadS [PublishBatchResponse]
forall a.
(Int -> ReadS a)
-> ReadS [a] -> ReadPrec a -> ReadPrec [a] -> Read a
readListPrec :: ReadPrec [PublishBatchResponse]
$creadListPrec :: ReadPrec [PublishBatchResponse]
readPrec :: ReadPrec PublishBatchResponse
$creadPrec :: ReadPrec PublishBatchResponse
readList :: ReadS [PublishBatchResponse]
$creadList :: ReadS [PublishBatchResponse]
readsPrec :: Int -> ReadS PublishBatchResponse
$creadsPrec :: Int -> ReadS PublishBatchResponse
Prelude.Read, Int -> PublishBatchResponse -> ShowS
[PublishBatchResponse] -> ShowS
PublishBatchResponse -> String
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [PublishBatchResponse] -> ShowS
$cshowList :: [PublishBatchResponse] -> ShowS
show :: PublishBatchResponse -> String
$cshow :: PublishBatchResponse -> String
showsPrec :: Int -> PublishBatchResponse -> ShowS
$cshowsPrec :: Int -> PublishBatchResponse -> ShowS
Prelude.Show, forall x. Rep PublishBatchResponse x -> PublishBatchResponse
forall x. PublishBatchResponse -> Rep PublishBatchResponse x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cto :: forall x. Rep PublishBatchResponse x -> PublishBatchResponse
$cfrom :: forall x. PublishBatchResponse -> Rep PublishBatchResponse x
Prelude.Generic)

-- |
-- Create a value of 'PublishBatchResponse' 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:
--
-- 'failed', 'publishBatchResponse_failed' - A list of failed @PublishBatch@ responses.
--
-- 'successful', 'publishBatchResponse_successful' - A list of successful @PublishBatch@ responses.
--
-- 'httpStatus', 'publishBatchResponse_httpStatus' - The response's http status code.
newPublishBatchResponse ::
  -- | 'httpStatus'
  Prelude.Int ->
  PublishBatchResponse
newPublishBatchResponse :: Int -> PublishBatchResponse
newPublishBatchResponse Int
pHttpStatus_ =
  PublishBatchResponse'
    { $sel:failed:PublishBatchResponse' :: Maybe [BatchResultErrorEntry]
failed = forall a. Maybe a
Prelude.Nothing,
      $sel:successful:PublishBatchResponse' :: Maybe [PublishBatchResultEntry]
successful = forall a. Maybe a
Prelude.Nothing,
      $sel:httpStatus:PublishBatchResponse' :: Int
httpStatus = Int
pHttpStatus_
    }

-- | A list of failed @PublishBatch@ responses.
publishBatchResponse_failed :: Lens.Lens' PublishBatchResponse (Prelude.Maybe [BatchResultErrorEntry])
publishBatchResponse_failed :: Lens' PublishBatchResponse (Maybe [BatchResultErrorEntry])
publishBatchResponse_failed = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\PublishBatchResponse' {Maybe [BatchResultErrorEntry]
failed :: Maybe [BatchResultErrorEntry]
$sel:failed:PublishBatchResponse' :: PublishBatchResponse -> Maybe [BatchResultErrorEntry]
failed} -> Maybe [BatchResultErrorEntry]
failed) (\s :: PublishBatchResponse
s@PublishBatchResponse' {} Maybe [BatchResultErrorEntry]
a -> PublishBatchResponse
s {$sel:failed:PublishBatchResponse' :: Maybe [BatchResultErrorEntry]
failed = Maybe [BatchResultErrorEntry]
a} :: PublishBatchResponse) 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

-- | A list of successful @PublishBatch@ responses.
publishBatchResponse_successful :: Lens.Lens' PublishBatchResponse (Prelude.Maybe [PublishBatchResultEntry])
publishBatchResponse_successful :: Lens' PublishBatchResponse (Maybe [PublishBatchResultEntry])
publishBatchResponse_successful = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\PublishBatchResponse' {Maybe [PublishBatchResultEntry]
successful :: Maybe [PublishBatchResultEntry]
$sel:successful:PublishBatchResponse' :: PublishBatchResponse -> Maybe [PublishBatchResultEntry]
successful} -> Maybe [PublishBatchResultEntry]
successful) (\s :: PublishBatchResponse
s@PublishBatchResponse' {} Maybe [PublishBatchResultEntry]
a -> PublishBatchResponse
s {$sel:successful:PublishBatchResponse' :: Maybe [PublishBatchResultEntry]
successful = Maybe [PublishBatchResultEntry]
a} :: PublishBatchResponse) 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 response's http status code.
publishBatchResponse_httpStatus :: Lens.Lens' PublishBatchResponse Prelude.Int
publishBatchResponse_httpStatus :: Lens' PublishBatchResponse Int
publishBatchResponse_httpStatus = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\PublishBatchResponse' {Int
httpStatus :: Int
$sel:httpStatus:PublishBatchResponse' :: PublishBatchResponse -> Int
httpStatus} -> Int
httpStatus) (\s :: PublishBatchResponse
s@PublishBatchResponse' {} Int
a -> PublishBatchResponse
s {$sel:httpStatus:PublishBatchResponse' :: Int
httpStatus = Int
a} :: PublishBatchResponse)

instance Prelude.NFData PublishBatchResponse where
  rnf :: PublishBatchResponse -> ()
rnf PublishBatchResponse' {Int
Maybe [BatchResultErrorEntry]
Maybe [PublishBatchResultEntry]
httpStatus :: Int
successful :: Maybe [PublishBatchResultEntry]
failed :: Maybe [BatchResultErrorEntry]
$sel:httpStatus:PublishBatchResponse' :: PublishBatchResponse -> Int
$sel:successful:PublishBatchResponse' :: PublishBatchResponse -> Maybe [PublishBatchResultEntry]
$sel:failed:PublishBatchResponse' :: PublishBatchResponse -> Maybe [BatchResultErrorEntry]
..} =
    forall a. NFData a => a -> ()
Prelude.rnf Maybe [BatchResultErrorEntry]
failed
      seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf Maybe [PublishBatchResultEntry]
successful
      seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf Int
httpStatus