{-# 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.SQS.DeleteMessageBatch
-- 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 up to ten messages from the specified queue. This is a batch
-- version of @ @@DeleteMessage@@.@ The result of the action on 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@.
--
-- 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@
module Amazonka.SQS.DeleteMessageBatch
  ( -- * Creating a Request
    DeleteMessageBatch (..),
    newDeleteMessageBatch,

    -- * Request Lenses
    deleteMessageBatch_queueUrl,
    deleteMessageBatch_entries,

    -- * Destructuring the Response
    DeleteMessageBatchResponse (..),
    newDeleteMessageBatchResponse,

    -- * Response Lenses
    deleteMessageBatchResponse_httpStatus,
    deleteMessageBatchResponse_successful,
    deleteMessageBatchResponse_failed,
  )
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.SQS.Types

-- |
--
-- /See:/ 'newDeleteMessageBatch' smart constructor.
data DeleteMessageBatch = DeleteMessageBatch'
  { -- | The URL of the Amazon SQS queue from which messages are deleted.
    --
    -- Queue URLs and names are case-sensitive.
    DeleteMessageBatch -> Text
queueUrl :: Prelude.Text,
    -- | A list of receipt handles for the messages to be deleted.
    DeleteMessageBatch -> [DeleteMessageBatchRequestEntry]
entries :: [DeleteMessageBatchRequestEntry]
  }
  deriving (DeleteMessageBatch -> DeleteMessageBatch -> Bool
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: DeleteMessageBatch -> DeleteMessageBatch -> Bool
$c/= :: DeleteMessageBatch -> DeleteMessageBatch -> Bool
== :: DeleteMessageBatch -> DeleteMessageBatch -> Bool
$c== :: DeleteMessageBatch -> DeleteMessageBatch -> Bool
Prelude.Eq, ReadPrec [DeleteMessageBatch]
ReadPrec DeleteMessageBatch
Int -> ReadS DeleteMessageBatch
ReadS [DeleteMessageBatch]
forall a.
(Int -> ReadS a)
-> ReadS [a] -> ReadPrec a -> ReadPrec [a] -> Read a
readListPrec :: ReadPrec [DeleteMessageBatch]
$creadListPrec :: ReadPrec [DeleteMessageBatch]
readPrec :: ReadPrec DeleteMessageBatch
$creadPrec :: ReadPrec DeleteMessageBatch
readList :: ReadS [DeleteMessageBatch]
$creadList :: ReadS [DeleteMessageBatch]
readsPrec :: Int -> ReadS DeleteMessageBatch
$creadsPrec :: Int -> ReadS DeleteMessageBatch
Prelude.Read, Int -> DeleteMessageBatch -> ShowS
[DeleteMessageBatch] -> ShowS
DeleteMessageBatch -> String
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [DeleteMessageBatch] -> ShowS
$cshowList :: [DeleteMessageBatch] -> ShowS
show :: DeleteMessageBatch -> String
$cshow :: DeleteMessageBatch -> String
showsPrec :: Int -> DeleteMessageBatch -> ShowS
$cshowsPrec :: Int -> DeleteMessageBatch -> ShowS
Prelude.Show, forall x. Rep DeleteMessageBatch x -> DeleteMessageBatch
forall x. DeleteMessageBatch -> Rep DeleteMessageBatch x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cto :: forall x. Rep DeleteMessageBatch x -> DeleteMessageBatch
$cfrom :: forall x. DeleteMessageBatch -> Rep DeleteMessageBatch x
Prelude.Generic)

-- |
-- Create a value of 'DeleteMessageBatch' 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:
--
-- 'queueUrl', 'deleteMessageBatch_queueUrl' - The URL of the Amazon SQS queue from which messages are deleted.
--
-- Queue URLs and names are case-sensitive.
--
-- 'entries', 'deleteMessageBatch_entries' - A list of receipt handles for the messages to be deleted.
newDeleteMessageBatch ::
  -- | 'queueUrl'
  Prelude.Text ->
  DeleteMessageBatch
newDeleteMessageBatch :: Text -> DeleteMessageBatch
newDeleteMessageBatch Text
pQueueUrl_ =
  DeleteMessageBatch'
    { $sel:queueUrl:DeleteMessageBatch' :: Text
queueUrl = Text
pQueueUrl_,
      $sel:entries:DeleteMessageBatch' :: [DeleteMessageBatchRequestEntry]
entries = forall a. Monoid a => a
Prelude.mempty
    }

-- | The URL of the Amazon SQS queue from which messages are deleted.
--
-- Queue URLs and names are case-sensitive.
deleteMessageBatch_queueUrl :: Lens.Lens' DeleteMessageBatch Prelude.Text
deleteMessageBatch_queueUrl :: Lens' DeleteMessageBatch Text
deleteMessageBatch_queueUrl = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\DeleteMessageBatch' {Text
queueUrl :: Text
$sel:queueUrl:DeleteMessageBatch' :: DeleteMessageBatch -> Text
queueUrl} -> Text
queueUrl) (\s :: DeleteMessageBatch
s@DeleteMessageBatch' {} Text
a -> DeleteMessageBatch
s {$sel:queueUrl:DeleteMessageBatch' :: Text
queueUrl = Text
a} :: DeleteMessageBatch)

-- | A list of receipt handles for the messages to be deleted.
deleteMessageBatch_entries :: Lens.Lens' DeleteMessageBatch [DeleteMessageBatchRequestEntry]
deleteMessageBatch_entries :: Lens' DeleteMessageBatch [DeleteMessageBatchRequestEntry]
deleteMessageBatch_entries = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\DeleteMessageBatch' {[DeleteMessageBatchRequestEntry]
entries :: [DeleteMessageBatchRequestEntry]
$sel:entries:DeleteMessageBatch' :: DeleteMessageBatch -> [DeleteMessageBatchRequestEntry]
entries} -> [DeleteMessageBatchRequestEntry]
entries) (\s :: DeleteMessageBatch
s@DeleteMessageBatch' {} [DeleteMessageBatchRequestEntry]
a -> DeleteMessageBatch
s {$sel:entries:DeleteMessageBatch' :: [DeleteMessageBatchRequestEntry]
entries = [DeleteMessageBatchRequestEntry]
a} :: DeleteMessageBatch) 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 DeleteMessageBatch where
  type
    AWSResponse DeleteMessageBatch =
      DeleteMessageBatchResponse
  request :: (Service -> Service)
-> DeleteMessageBatch -> Request DeleteMessageBatch
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 DeleteMessageBatch
-> ClientResponse ClientBody
-> m (Either
        Error (ClientResponse (AWSResponse DeleteMessageBatch)))
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
"DeleteMessageBatchResult"
      ( \Int
s ResponseHeaders
h [Node]
x ->
          Int
-> [DeleteMessageBatchResultEntry]
-> [BatchResultErrorEntry]
-> DeleteMessageBatchResponse
DeleteMessageBatchResponse'
            forall (f :: * -> *) a b. Functor 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))
            forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
Prelude.<*> (forall a. FromXML a => Text -> [Node] -> Either String [a]
Data.parseXMLList Text
"DeleteMessageBatchResultEntry" [Node]
x)
            forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
Prelude.<*> (forall a. FromXML a => Text -> [Node] -> Either String [a]
Data.parseXMLList Text
"BatchResultErrorEntry" [Node]
x)
      )

instance Prelude.Hashable DeleteMessageBatch where
  hashWithSalt :: Int -> DeleteMessageBatch -> Int
hashWithSalt Int
_salt DeleteMessageBatch' {[DeleteMessageBatchRequestEntry]
Text
entries :: [DeleteMessageBatchRequestEntry]
queueUrl :: Text
$sel:entries:DeleteMessageBatch' :: DeleteMessageBatch -> [DeleteMessageBatchRequestEntry]
$sel:queueUrl:DeleteMessageBatch' :: DeleteMessageBatch -> Text
..} =
    Int
_salt
      forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Text
queueUrl
      forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` [DeleteMessageBatchRequestEntry]
entries

instance Prelude.NFData DeleteMessageBatch where
  rnf :: DeleteMessageBatch -> ()
rnf DeleteMessageBatch' {[DeleteMessageBatchRequestEntry]
Text
entries :: [DeleteMessageBatchRequestEntry]
queueUrl :: Text
$sel:entries:DeleteMessageBatch' :: DeleteMessageBatch -> [DeleteMessageBatchRequestEntry]
$sel:queueUrl:DeleteMessageBatch' :: DeleteMessageBatch -> Text
..} =
    forall a. NFData a => a -> ()
Prelude.rnf Text
queueUrl
      seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf [DeleteMessageBatchRequestEntry]
entries

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

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

instance Data.ToQuery DeleteMessageBatch where
  toQuery :: DeleteMessageBatch -> QueryString
toQuery DeleteMessageBatch' {[DeleteMessageBatchRequestEntry]
Text
entries :: [DeleteMessageBatchRequestEntry]
queueUrl :: Text
$sel:entries:DeleteMessageBatch' :: DeleteMessageBatch -> [DeleteMessageBatchRequestEntry]
$sel:queueUrl:DeleteMessageBatch' :: DeleteMessageBatch -> Text
..} =
    forall a. Monoid a => [a] -> a
Prelude.mconcat
      [ ByteString
"Action"
          forall a. ToQuery a => ByteString -> a -> QueryString
Data.=: (ByteString
"DeleteMessageBatch" :: Prelude.ByteString),
        ByteString
"Version"
          forall a. ToQuery a => ByteString -> a -> QueryString
Data.=: (ByteString
"2012-11-05" :: Prelude.ByteString),
        ByteString
"QueueUrl" forall a. ToQuery a => ByteString -> a -> QueryString
Data.=: Text
queueUrl,
        forall a.
(IsList a, ToQuery (Item a)) =>
ByteString -> a -> QueryString
Data.toQueryList
          ByteString
"DeleteMessageBatchRequestEntry"
          [DeleteMessageBatchRequestEntry]
entries
      ]

-- | For each message in the batch, the response contains a
-- @ @@DeleteMessageBatchResultEntry@@ @ tag if the message is deleted or a
-- @ @@BatchResultErrorEntry@@ @ tag if the message can\'t be deleted.
--
-- /See:/ 'newDeleteMessageBatchResponse' smart constructor.
data DeleteMessageBatchResponse = DeleteMessageBatchResponse'
  { -- | The response's http status code.
    DeleteMessageBatchResponse -> Int
httpStatus :: Prelude.Int,
    -- | A list of @ @@DeleteMessageBatchResultEntry@@ @ items.
    DeleteMessageBatchResponse -> [DeleteMessageBatchResultEntry]
successful :: [DeleteMessageBatchResultEntry],
    -- | A list of @ @@BatchResultErrorEntry@@ @ items.
    DeleteMessageBatchResponse -> [BatchResultErrorEntry]
failed :: [BatchResultErrorEntry]
  }
  deriving (DeleteMessageBatchResponse -> DeleteMessageBatchResponse -> Bool
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: DeleteMessageBatchResponse -> DeleteMessageBatchResponse -> Bool
$c/= :: DeleteMessageBatchResponse -> DeleteMessageBatchResponse -> Bool
== :: DeleteMessageBatchResponse -> DeleteMessageBatchResponse -> Bool
$c== :: DeleteMessageBatchResponse -> DeleteMessageBatchResponse -> Bool
Prelude.Eq, ReadPrec [DeleteMessageBatchResponse]
ReadPrec DeleteMessageBatchResponse
Int -> ReadS DeleteMessageBatchResponse
ReadS [DeleteMessageBatchResponse]
forall a.
(Int -> ReadS a)
-> ReadS [a] -> ReadPrec a -> ReadPrec [a] -> Read a
readListPrec :: ReadPrec [DeleteMessageBatchResponse]
$creadListPrec :: ReadPrec [DeleteMessageBatchResponse]
readPrec :: ReadPrec DeleteMessageBatchResponse
$creadPrec :: ReadPrec DeleteMessageBatchResponse
readList :: ReadS [DeleteMessageBatchResponse]
$creadList :: ReadS [DeleteMessageBatchResponse]
readsPrec :: Int -> ReadS DeleteMessageBatchResponse
$creadsPrec :: Int -> ReadS DeleteMessageBatchResponse
Prelude.Read, Int -> DeleteMessageBatchResponse -> ShowS
[DeleteMessageBatchResponse] -> ShowS
DeleteMessageBatchResponse -> String
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [DeleteMessageBatchResponse] -> ShowS
$cshowList :: [DeleteMessageBatchResponse] -> ShowS
show :: DeleteMessageBatchResponse -> String
$cshow :: DeleteMessageBatchResponse -> String
showsPrec :: Int -> DeleteMessageBatchResponse -> ShowS
$cshowsPrec :: Int -> DeleteMessageBatchResponse -> ShowS
Prelude.Show, forall x.
Rep DeleteMessageBatchResponse x -> DeleteMessageBatchResponse
forall x.
DeleteMessageBatchResponse -> Rep DeleteMessageBatchResponse x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cto :: forall x.
Rep DeleteMessageBatchResponse x -> DeleteMessageBatchResponse
$cfrom :: forall x.
DeleteMessageBatchResponse -> Rep DeleteMessageBatchResponse x
Prelude.Generic)

-- |
-- Create a value of 'DeleteMessageBatchResponse' 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:
--
-- 'httpStatus', 'deleteMessageBatchResponse_httpStatus' - The response's http status code.
--
-- 'successful', 'deleteMessageBatchResponse_successful' - A list of @ @@DeleteMessageBatchResultEntry@@ @ items.
--
-- 'failed', 'deleteMessageBatchResponse_failed' - A list of @ @@BatchResultErrorEntry@@ @ items.
newDeleteMessageBatchResponse ::
  -- | 'httpStatus'
  Prelude.Int ->
  DeleteMessageBatchResponse
newDeleteMessageBatchResponse :: Int -> DeleteMessageBatchResponse
newDeleteMessageBatchResponse Int
pHttpStatus_ =
  DeleteMessageBatchResponse'
    { $sel:httpStatus:DeleteMessageBatchResponse' :: Int
httpStatus =
        Int
pHttpStatus_,
      $sel:successful:DeleteMessageBatchResponse' :: [DeleteMessageBatchResultEntry]
successful = forall a. Monoid a => a
Prelude.mempty,
      $sel:failed:DeleteMessageBatchResponse' :: [BatchResultErrorEntry]
failed = forall a. Monoid a => a
Prelude.mempty
    }

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

-- | A list of @ @@DeleteMessageBatchResultEntry@@ @ items.
deleteMessageBatchResponse_successful :: Lens.Lens' DeleteMessageBatchResponse [DeleteMessageBatchResultEntry]
deleteMessageBatchResponse_successful :: Lens' DeleteMessageBatchResponse [DeleteMessageBatchResultEntry]
deleteMessageBatchResponse_successful = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\DeleteMessageBatchResponse' {[DeleteMessageBatchResultEntry]
successful :: [DeleteMessageBatchResultEntry]
$sel:successful:DeleteMessageBatchResponse' :: DeleteMessageBatchResponse -> [DeleteMessageBatchResultEntry]
successful} -> [DeleteMessageBatchResultEntry]
successful) (\s :: DeleteMessageBatchResponse
s@DeleteMessageBatchResponse' {} [DeleteMessageBatchResultEntry]
a -> DeleteMessageBatchResponse
s {$sel:successful:DeleteMessageBatchResponse' :: [DeleteMessageBatchResultEntry]
successful = [DeleteMessageBatchResultEntry]
a} :: DeleteMessageBatchResponse) 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

-- | A list of @ @@BatchResultErrorEntry@@ @ items.
deleteMessageBatchResponse_failed :: Lens.Lens' DeleteMessageBatchResponse [BatchResultErrorEntry]
deleteMessageBatchResponse_failed :: Lens' DeleteMessageBatchResponse [BatchResultErrorEntry]
deleteMessageBatchResponse_failed = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\DeleteMessageBatchResponse' {[BatchResultErrorEntry]
failed :: [BatchResultErrorEntry]
$sel:failed:DeleteMessageBatchResponse' :: DeleteMessageBatchResponse -> [BatchResultErrorEntry]
failed} -> [BatchResultErrorEntry]
failed) (\s :: DeleteMessageBatchResponse
s@DeleteMessageBatchResponse' {} [BatchResultErrorEntry]
a -> DeleteMessageBatchResponse
s {$sel:failed:DeleteMessageBatchResponse' :: [BatchResultErrorEntry]
failed = [BatchResultErrorEntry]
a} :: DeleteMessageBatchResponse) 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 Prelude.NFData DeleteMessageBatchResponse where
  rnf :: DeleteMessageBatchResponse -> ()
rnf DeleteMessageBatchResponse' {Int
[BatchResultErrorEntry]
[DeleteMessageBatchResultEntry]
failed :: [BatchResultErrorEntry]
successful :: [DeleteMessageBatchResultEntry]
httpStatus :: Int
$sel:failed:DeleteMessageBatchResponse' :: DeleteMessageBatchResponse -> [BatchResultErrorEntry]
$sel:successful:DeleteMessageBatchResponse' :: DeleteMessageBatchResponse -> [DeleteMessageBatchResultEntry]
$sel:httpStatus:DeleteMessageBatchResponse' :: DeleteMessageBatchResponse -> Int
..} =
    forall a. NFData a => a -> ()
Prelude.rnf Int
httpStatus
      seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf [DeleteMessageBatchResultEntry]
successful
      seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf [BatchResultErrorEntry]
failed