{-# 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.S3.DeleteObjects
-- Copyright   : (c) 2013-2023 Brendan Hay
-- License     : Mozilla Public License, v. 2.0.
-- Maintainer  : Brendan Hay
-- Stability   : auto-generated
-- Portability : non-portable (GHC extensions)
--
-- This action enables you to delete multiple objects from a bucket using a
-- single HTTP request. If you know the object keys that you want to
-- delete, then this action provides a suitable alternative to sending
-- individual delete requests, reducing per-request overhead.
--
-- The request contains a list of up to 1000 keys that you want to delete.
-- In the XML, you provide the object key names, and optionally, version
-- IDs if you want to delete a specific version of the object from a
-- versioning-enabled bucket. For each key, Amazon S3 performs a delete
-- action and returns the result of that delete, success, or failure, in
-- the response. Note that if the object specified in the request is not
-- found, Amazon S3 returns the result as deleted.
--
-- The action supports two modes for the response: verbose and quiet. By
-- default, the action uses verbose mode in which the response includes the
-- result of deletion of each key in your request. In quiet mode the
-- response includes only keys where the delete action encountered an
-- error. For a successful deletion, the action does not return any
-- information about the delete in the response body.
--
-- When performing this action on an MFA Delete enabled bucket, that
-- attempts to delete any versioned objects, you must include an MFA token.
-- If you do not provide one, the entire request will fail, even if there
-- are non-versioned objects you are trying to delete. If you provide an
-- invalid token, whether there are versioned keys in the request or not,
-- the entire Multi-Object Delete request will fail. For information about
-- MFA Delete, see
-- <https://docs.aws.amazon.com/AmazonS3/latest/dev/Versioning.html#MultiFactorAuthenticationDelete MFA Delete>.
--
-- Finally, the Content-MD5 header is required for all Multi-Object Delete
-- requests. Amazon S3 uses the header value to ensure that your request
-- body has not been altered in transit.
--
-- The following operations are related to @DeleteObjects@:
--
-- -   <https://docs.aws.amazon.com/AmazonS3/latest/API/API_CreateMultipartUpload.html CreateMultipartUpload>
--
-- -   <https://docs.aws.amazon.com/AmazonS3/latest/API/API_UploadPart.html UploadPart>
--
-- -   <https://docs.aws.amazon.com/AmazonS3/latest/API/API_CompleteMultipartUpload.html CompleteMultipartUpload>
--
-- -   <https://docs.aws.amazon.com/AmazonS3/latest/API/API_ListParts.html ListParts>
--
-- -   <https://docs.aws.amazon.com/AmazonS3/latest/API/API_AbortMultipartUpload.html AbortMultipartUpload>
module Amazonka.S3.DeleteObjects
  ( -- * Creating a Request
    DeleteObjects (..),
    newDeleteObjects,

    -- * Request Lenses
    deleteObjects_bypassGovernanceRetention,
    deleteObjects_checksumAlgorithm,
    deleteObjects_expectedBucketOwner,
    deleteObjects_mfa,
    deleteObjects_requestPayer,
    deleteObjects_bucket,
    deleteObjects_delete,

    -- * Destructuring the Response
    DeleteObjectsResponse (..),
    newDeleteObjectsResponse,

    -- * Response Lenses
    deleteObjectsResponse_deleted,
    deleteObjectsResponse_errors,
    deleteObjectsResponse_requestCharged,
    deleteObjectsResponse_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.S3.Types

-- | /See:/ 'newDeleteObjects' smart constructor.
data DeleteObjects = DeleteObjects'
  { -- | Specifies whether you want to delete this object even if it has a
    -- Governance-type Object Lock in place. To use this header, you must have
    -- the @s3:BypassGovernanceRetention@ permission.
    DeleteObjects -> Maybe Bool
bypassGovernanceRetention :: Prelude.Maybe Prelude.Bool,
    -- | Indicates the algorithm used to create the checksum for the object when
    -- using the SDK. This header will not provide any additional functionality
    -- if not using the SDK. When sending this header, there must be a
    -- corresponding @x-amz-checksum@ or @x-amz-trailer@ header sent.
    -- Otherwise, Amazon S3 fails the request with the HTTP status code
    -- @400 Bad Request@. For more information, see
    -- <https://docs.aws.amazon.com/AmazonS3/latest/userguide/checking-object-integrity.html Checking object integrity>
    -- in the /Amazon S3 User Guide/.
    --
    -- If you provide an individual checksum, Amazon S3 ignores any provided
    -- @ChecksumAlgorithm@ parameter.
    --
    -- This checksum algorithm must be the same for all parts and it match the
    -- checksum value supplied in the @CreateMultipartUpload@ request.
    DeleteObjects -> Maybe ChecksumAlgorithm
checksumAlgorithm :: Prelude.Maybe ChecksumAlgorithm,
    -- | The account ID of the expected bucket owner. If the bucket is owned by a
    -- different account, the request fails with the HTTP status code
    -- @403 Forbidden@ (access denied).
    DeleteObjects -> Maybe Text
expectedBucketOwner :: Prelude.Maybe Prelude.Text,
    -- | The concatenation of the authentication device\'s serial number, a
    -- space, and the value that is displayed on your authentication device.
    -- Required to permanently delete a versioned object if versioning is
    -- configured with MFA delete enabled.
    DeleteObjects -> Maybe Text
mfa :: Prelude.Maybe Prelude.Text,
    DeleteObjects -> Maybe RequestPayer
requestPayer :: Prelude.Maybe RequestPayer,
    -- | The bucket name containing the objects to delete.
    --
    -- When using this action with an access point, you must direct requests to
    -- the access point hostname. The access point hostname takes the form
    -- /AccessPointName/-/AccountId/.s3-accesspoint./Region/.amazonaws.com.
    -- When using this action with an access point through the Amazon Web
    -- Services SDKs, you provide the access point ARN in place of the bucket
    -- name. For more information about access point ARNs, see
    -- <https://docs.aws.amazon.com/AmazonS3/latest/userguide/using-access-points.html Using access points>
    -- in the /Amazon S3 User Guide/.
    --
    -- When using this action with Amazon S3 on Outposts, you must direct
    -- requests to the S3 on Outposts hostname. The S3 on Outposts hostname
    -- takes the form
    -- @ @/@AccessPointName@/@-@/@AccountId@/@.@/@outpostID@/@.s3-outposts.@/@Region@/@.amazonaws.com@.
    -- When using this action with S3 on Outposts through the Amazon Web
    -- Services SDKs, you provide the Outposts bucket ARN in place of the
    -- bucket name. For more information about S3 on Outposts ARNs, see
    -- <https://docs.aws.amazon.com/AmazonS3/latest/userguide/S3onOutposts.html Using Amazon S3 on Outposts>
    -- in the /Amazon S3 User Guide/.
    DeleteObjects -> BucketName
bucket :: BucketName,
    -- | Container for the request.
    DeleteObjects -> Delete
delete' :: Delete
  }
  deriving (DeleteObjects -> DeleteObjects -> Bool
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: DeleteObjects -> DeleteObjects -> Bool
$c/= :: DeleteObjects -> DeleteObjects -> Bool
== :: DeleteObjects -> DeleteObjects -> Bool
$c== :: DeleteObjects -> DeleteObjects -> Bool
Prelude.Eq, ReadPrec [DeleteObjects]
ReadPrec DeleteObjects
Int -> ReadS DeleteObjects
ReadS [DeleteObjects]
forall a.
(Int -> ReadS a)
-> ReadS [a] -> ReadPrec a -> ReadPrec [a] -> Read a
readListPrec :: ReadPrec [DeleteObjects]
$creadListPrec :: ReadPrec [DeleteObjects]
readPrec :: ReadPrec DeleteObjects
$creadPrec :: ReadPrec DeleteObjects
readList :: ReadS [DeleteObjects]
$creadList :: ReadS [DeleteObjects]
readsPrec :: Int -> ReadS DeleteObjects
$creadsPrec :: Int -> ReadS DeleteObjects
Prelude.Read, Int -> DeleteObjects -> ShowS
[DeleteObjects] -> ShowS
DeleteObjects -> String
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [DeleteObjects] -> ShowS
$cshowList :: [DeleteObjects] -> ShowS
show :: DeleteObjects -> String
$cshow :: DeleteObjects -> String
showsPrec :: Int -> DeleteObjects -> ShowS
$cshowsPrec :: Int -> DeleteObjects -> ShowS
Prelude.Show, forall x. Rep DeleteObjects x -> DeleteObjects
forall x. DeleteObjects -> Rep DeleteObjects x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cto :: forall x. Rep DeleteObjects x -> DeleteObjects
$cfrom :: forall x. DeleteObjects -> Rep DeleteObjects x
Prelude.Generic)

-- |
-- Create a value of 'DeleteObjects' 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:
--
-- 'bypassGovernanceRetention', 'deleteObjects_bypassGovernanceRetention' - Specifies whether you want to delete this object even if it has a
-- Governance-type Object Lock in place. To use this header, you must have
-- the @s3:BypassGovernanceRetention@ permission.
--
-- 'checksumAlgorithm', 'deleteObjects_checksumAlgorithm' - Indicates the algorithm used to create the checksum for the object when
-- using the SDK. This header will not provide any additional functionality
-- if not using the SDK. When sending this header, there must be a
-- corresponding @x-amz-checksum@ or @x-amz-trailer@ header sent.
-- Otherwise, Amazon S3 fails the request with the HTTP status code
-- @400 Bad Request@. For more information, see
-- <https://docs.aws.amazon.com/AmazonS3/latest/userguide/checking-object-integrity.html Checking object integrity>
-- in the /Amazon S3 User Guide/.
--
-- If you provide an individual checksum, Amazon S3 ignores any provided
-- @ChecksumAlgorithm@ parameter.
--
-- This checksum algorithm must be the same for all parts and it match the
-- checksum value supplied in the @CreateMultipartUpload@ request.
--
-- 'expectedBucketOwner', 'deleteObjects_expectedBucketOwner' - The account ID of the expected bucket owner. If the bucket is owned by a
-- different account, the request fails with the HTTP status code
-- @403 Forbidden@ (access denied).
--
-- 'mfa', 'deleteObjects_mfa' - The concatenation of the authentication device\'s serial number, a
-- space, and the value that is displayed on your authentication device.
-- Required to permanently delete a versioned object if versioning is
-- configured with MFA delete enabled.
--
-- 'requestPayer', 'deleteObjects_requestPayer' - Undocumented member.
--
-- 'bucket', 'deleteObjects_bucket' - The bucket name containing the objects to delete.
--
-- When using this action with an access point, you must direct requests to
-- the access point hostname. The access point hostname takes the form
-- /AccessPointName/-/AccountId/.s3-accesspoint./Region/.amazonaws.com.
-- When using this action with an access point through the Amazon Web
-- Services SDKs, you provide the access point ARN in place of the bucket
-- name. For more information about access point ARNs, see
-- <https://docs.aws.amazon.com/AmazonS3/latest/userguide/using-access-points.html Using access points>
-- in the /Amazon S3 User Guide/.
--
-- When using this action with Amazon S3 on Outposts, you must direct
-- requests to the S3 on Outposts hostname. The S3 on Outposts hostname
-- takes the form
-- @ @/@AccessPointName@/@-@/@AccountId@/@.@/@outpostID@/@.s3-outposts.@/@Region@/@.amazonaws.com@.
-- When using this action with S3 on Outposts through the Amazon Web
-- Services SDKs, you provide the Outposts bucket ARN in place of the
-- bucket name. For more information about S3 on Outposts ARNs, see
-- <https://docs.aws.amazon.com/AmazonS3/latest/userguide/S3onOutposts.html Using Amazon S3 on Outposts>
-- in the /Amazon S3 User Guide/.
--
-- 'delete'', 'deleteObjects_delete' - Container for the request.
newDeleteObjects ::
  -- | 'bucket'
  BucketName ->
  -- | 'delete''
  Delete ->
  DeleteObjects
newDeleteObjects :: BucketName -> Delete -> DeleteObjects
newDeleteObjects BucketName
pBucket_ Delete
pDelete_ =
  DeleteObjects'
    { $sel:bypassGovernanceRetention:DeleteObjects' :: Maybe Bool
bypassGovernanceRetention =
        forall a. Maybe a
Prelude.Nothing,
      $sel:checksumAlgorithm:DeleteObjects' :: Maybe ChecksumAlgorithm
checksumAlgorithm = forall a. Maybe a
Prelude.Nothing,
      $sel:expectedBucketOwner:DeleteObjects' :: Maybe Text
expectedBucketOwner = forall a. Maybe a
Prelude.Nothing,
      $sel:mfa:DeleteObjects' :: Maybe Text
mfa = forall a. Maybe a
Prelude.Nothing,
      $sel:requestPayer:DeleteObjects' :: Maybe RequestPayer
requestPayer = forall a. Maybe a
Prelude.Nothing,
      $sel:bucket:DeleteObjects' :: BucketName
bucket = BucketName
pBucket_,
      $sel:delete':DeleteObjects' :: Delete
delete' = Delete
pDelete_
    }

-- | Specifies whether you want to delete this object even if it has a
-- Governance-type Object Lock in place. To use this header, you must have
-- the @s3:BypassGovernanceRetention@ permission.
deleteObjects_bypassGovernanceRetention :: Lens.Lens' DeleteObjects (Prelude.Maybe Prelude.Bool)
deleteObjects_bypassGovernanceRetention :: Lens' DeleteObjects (Maybe Bool)
deleteObjects_bypassGovernanceRetention = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\DeleteObjects' {Maybe Bool
bypassGovernanceRetention :: Maybe Bool
$sel:bypassGovernanceRetention:DeleteObjects' :: DeleteObjects -> Maybe Bool
bypassGovernanceRetention} -> Maybe Bool
bypassGovernanceRetention) (\s :: DeleteObjects
s@DeleteObjects' {} Maybe Bool
a -> DeleteObjects
s {$sel:bypassGovernanceRetention:DeleteObjects' :: Maybe Bool
bypassGovernanceRetention = Maybe Bool
a} :: DeleteObjects)

-- | Indicates the algorithm used to create the checksum for the object when
-- using the SDK. This header will not provide any additional functionality
-- if not using the SDK. When sending this header, there must be a
-- corresponding @x-amz-checksum@ or @x-amz-trailer@ header sent.
-- Otherwise, Amazon S3 fails the request with the HTTP status code
-- @400 Bad Request@. For more information, see
-- <https://docs.aws.amazon.com/AmazonS3/latest/userguide/checking-object-integrity.html Checking object integrity>
-- in the /Amazon S3 User Guide/.
--
-- If you provide an individual checksum, Amazon S3 ignores any provided
-- @ChecksumAlgorithm@ parameter.
--
-- This checksum algorithm must be the same for all parts and it match the
-- checksum value supplied in the @CreateMultipartUpload@ request.
deleteObjects_checksumAlgorithm :: Lens.Lens' DeleteObjects (Prelude.Maybe ChecksumAlgorithm)
deleteObjects_checksumAlgorithm :: Lens' DeleteObjects (Maybe ChecksumAlgorithm)
deleteObjects_checksumAlgorithm = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\DeleteObjects' {Maybe ChecksumAlgorithm
checksumAlgorithm :: Maybe ChecksumAlgorithm
$sel:checksumAlgorithm:DeleteObjects' :: DeleteObjects -> Maybe ChecksumAlgorithm
checksumAlgorithm} -> Maybe ChecksumAlgorithm
checksumAlgorithm) (\s :: DeleteObjects
s@DeleteObjects' {} Maybe ChecksumAlgorithm
a -> DeleteObjects
s {$sel:checksumAlgorithm:DeleteObjects' :: Maybe ChecksumAlgorithm
checksumAlgorithm = Maybe ChecksumAlgorithm
a} :: DeleteObjects)

-- | The account ID of the expected bucket owner. If the bucket is owned by a
-- different account, the request fails with the HTTP status code
-- @403 Forbidden@ (access denied).
deleteObjects_expectedBucketOwner :: Lens.Lens' DeleteObjects (Prelude.Maybe Prelude.Text)
deleteObjects_expectedBucketOwner :: Lens' DeleteObjects (Maybe Text)
deleteObjects_expectedBucketOwner = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\DeleteObjects' {Maybe Text
expectedBucketOwner :: Maybe Text
$sel:expectedBucketOwner:DeleteObjects' :: DeleteObjects -> Maybe Text
expectedBucketOwner} -> Maybe Text
expectedBucketOwner) (\s :: DeleteObjects
s@DeleteObjects' {} Maybe Text
a -> DeleteObjects
s {$sel:expectedBucketOwner:DeleteObjects' :: Maybe Text
expectedBucketOwner = Maybe Text
a} :: DeleteObjects)

-- | The concatenation of the authentication device\'s serial number, a
-- space, and the value that is displayed on your authentication device.
-- Required to permanently delete a versioned object if versioning is
-- configured with MFA delete enabled.
deleteObjects_mfa :: Lens.Lens' DeleteObjects (Prelude.Maybe Prelude.Text)
deleteObjects_mfa :: Lens' DeleteObjects (Maybe Text)
deleteObjects_mfa = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\DeleteObjects' {Maybe Text
mfa :: Maybe Text
$sel:mfa:DeleteObjects' :: DeleteObjects -> Maybe Text
mfa} -> Maybe Text
mfa) (\s :: DeleteObjects
s@DeleteObjects' {} Maybe Text
a -> DeleteObjects
s {$sel:mfa:DeleteObjects' :: Maybe Text
mfa = Maybe Text
a} :: DeleteObjects)

-- | Undocumented member.
deleteObjects_requestPayer :: Lens.Lens' DeleteObjects (Prelude.Maybe RequestPayer)
deleteObjects_requestPayer :: Lens' DeleteObjects (Maybe RequestPayer)
deleteObjects_requestPayer = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\DeleteObjects' {Maybe RequestPayer
requestPayer :: Maybe RequestPayer
$sel:requestPayer:DeleteObjects' :: DeleteObjects -> Maybe RequestPayer
requestPayer} -> Maybe RequestPayer
requestPayer) (\s :: DeleteObjects
s@DeleteObjects' {} Maybe RequestPayer
a -> DeleteObjects
s {$sel:requestPayer:DeleteObjects' :: Maybe RequestPayer
requestPayer = Maybe RequestPayer
a} :: DeleteObjects)

-- | The bucket name containing the objects to delete.
--
-- When using this action with an access point, you must direct requests to
-- the access point hostname. The access point hostname takes the form
-- /AccessPointName/-/AccountId/.s3-accesspoint./Region/.amazonaws.com.
-- When using this action with an access point through the Amazon Web
-- Services SDKs, you provide the access point ARN in place of the bucket
-- name. For more information about access point ARNs, see
-- <https://docs.aws.amazon.com/AmazonS3/latest/userguide/using-access-points.html Using access points>
-- in the /Amazon S3 User Guide/.
--
-- When using this action with Amazon S3 on Outposts, you must direct
-- requests to the S3 on Outposts hostname. The S3 on Outposts hostname
-- takes the form
-- @ @/@AccessPointName@/@-@/@AccountId@/@.@/@outpostID@/@.s3-outposts.@/@Region@/@.amazonaws.com@.
-- When using this action with S3 on Outposts through the Amazon Web
-- Services SDKs, you provide the Outposts bucket ARN in place of the
-- bucket name. For more information about S3 on Outposts ARNs, see
-- <https://docs.aws.amazon.com/AmazonS3/latest/userguide/S3onOutposts.html Using Amazon S3 on Outposts>
-- in the /Amazon S3 User Guide/.
deleteObjects_bucket :: Lens.Lens' DeleteObjects BucketName
deleteObjects_bucket :: Lens' DeleteObjects BucketName
deleteObjects_bucket = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\DeleteObjects' {BucketName
bucket :: BucketName
$sel:bucket:DeleteObjects' :: DeleteObjects -> BucketName
bucket} -> BucketName
bucket) (\s :: DeleteObjects
s@DeleteObjects' {} BucketName
a -> DeleteObjects
s {$sel:bucket:DeleteObjects' :: BucketName
bucket = BucketName
a} :: DeleteObjects)

-- | Container for the request.
deleteObjects_delete :: Lens.Lens' DeleteObjects Delete
deleteObjects_delete :: Lens' DeleteObjects Delete
deleteObjects_delete = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\DeleteObjects' {Delete
delete' :: Delete
$sel:delete':DeleteObjects' :: DeleteObjects -> Delete
delete'} -> Delete
delete') (\s :: DeleteObjects
s@DeleteObjects' {} Delete
a -> DeleteObjects
s {$sel:delete':DeleteObjects' :: Delete
delete' = Delete
a} :: DeleteObjects)

instance Core.AWSRequest DeleteObjects where
  type
    AWSResponse DeleteObjects =
      DeleteObjectsResponse
  request :: (Service -> Service) -> DeleteObjects -> Request DeleteObjects
request Service -> Service
overrides =
    forall a. Request a -> Request a
Request.contentMD5Header
      forall b c a. (b -> c) -> (a -> b) -> a -> c
Prelude.. forall a. Request a -> Request a
Request.s3vhost
      forall b c a. (b -> c) -> (a -> b) -> a -> c
Prelude.. forall a. (ToRequest a, ToElement a) => Service -> a -> Request a
Request.postXML (Service -> Service
overrides Service
defaultService)
  response :: forall (m :: * -> *).
MonadResource m =>
(ByteStringLazy -> IO ByteStringLazy)
-> Service
-> Proxy DeleteObjects
-> ClientResponse ClientBody
-> m (Either Error (ClientResponse (AWSResponse DeleteObjects)))
response =
    forall (m :: * -> *) a.
MonadResource m =>
(Int -> ResponseHeaders -> [Node] -> Either String (AWSResponse a))
-> (ByteStringLazy -> IO ByteStringLazy)
-> Service
-> Proxy a
-> ClientResponse ClientBody
-> m (Either Error (ClientResponse (AWSResponse a)))
Response.receiveXML
      ( \Int
s ResponseHeaders
h [Node]
x ->
          Maybe [DeletedObject]
-> Maybe [S3ServiceError]
-> Maybe RequestCharged
-> Int
-> DeleteObjectsResponse
DeleteObjectsResponse'
            forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f 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
"Deleted") [Node]
x)
            forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f 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
"Error") [Node]
x)
            forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
Prelude.<*> (ResponseHeaders
h forall a.
FromText a =>
ResponseHeaders -> HeaderName -> Either String (Maybe a)
Data..#? HeaderName
"x-amz-request-charged")
            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 DeleteObjects where
  hashWithSalt :: Int -> DeleteObjects -> Int
hashWithSalt Int
_salt DeleteObjects' {Maybe Bool
Maybe Text
Maybe ChecksumAlgorithm
Maybe RequestPayer
BucketName
Delete
delete' :: Delete
bucket :: BucketName
requestPayer :: Maybe RequestPayer
mfa :: Maybe Text
expectedBucketOwner :: Maybe Text
checksumAlgorithm :: Maybe ChecksumAlgorithm
bypassGovernanceRetention :: Maybe Bool
$sel:delete':DeleteObjects' :: DeleteObjects -> Delete
$sel:bucket:DeleteObjects' :: DeleteObjects -> BucketName
$sel:requestPayer:DeleteObjects' :: DeleteObjects -> Maybe RequestPayer
$sel:mfa:DeleteObjects' :: DeleteObjects -> Maybe Text
$sel:expectedBucketOwner:DeleteObjects' :: DeleteObjects -> Maybe Text
$sel:checksumAlgorithm:DeleteObjects' :: DeleteObjects -> Maybe ChecksumAlgorithm
$sel:bypassGovernanceRetention:DeleteObjects' :: DeleteObjects -> Maybe Bool
..} =
    Int
_salt
      forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Maybe Bool
bypassGovernanceRetention
      forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Maybe ChecksumAlgorithm
checksumAlgorithm
      forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Maybe Text
expectedBucketOwner
      forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Maybe Text
mfa
      forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Maybe RequestPayer
requestPayer
      forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` BucketName
bucket
      forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Delete
delete'

instance Prelude.NFData DeleteObjects where
  rnf :: DeleteObjects -> ()
rnf DeleteObjects' {Maybe Bool
Maybe Text
Maybe ChecksumAlgorithm
Maybe RequestPayer
BucketName
Delete
delete' :: Delete
bucket :: BucketName
requestPayer :: Maybe RequestPayer
mfa :: Maybe Text
expectedBucketOwner :: Maybe Text
checksumAlgorithm :: Maybe ChecksumAlgorithm
bypassGovernanceRetention :: Maybe Bool
$sel:delete':DeleteObjects' :: DeleteObjects -> Delete
$sel:bucket:DeleteObjects' :: DeleteObjects -> BucketName
$sel:requestPayer:DeleteObjects' :: DeleteObjects -> Maybe RequestPayer
$sel:mfa:DeleteObjects' :: DeleteObjects -> Maybe Text
$sel:expectedBucketOwner:DeleteObjects' :: DeleteObjects -> Maybe Text
$sel:checksumAlgorithm:DeleteObjects' :: DeleteObjects -> Maybe ChecksumAlgorithm
$sel:bypassGovernanceRetention:DeleteObjects' :: DeleteObjects -> Maybe Bool
..} =
    forall a. NFData a => a -> ()
Prelude.rnf Maybe Bool
bypassGovernanceRetention
      seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf Maybe ChecksumAlgorithm
checksumAlgorithm
      seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf Maybe Text
expectedBucketOwner
      seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf Maybe Text
mfa
      seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf Maybe RequestPayer
requestPayer
      seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf BucketName
bucket
      seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf Delete
delete'

instance Data.ToElement DeleteObjects where
  toElement :: DeleteObjects -> Element
toElement DeleteObjects' {Maybe Bool
Maybe Text
Maybe ChecksumAlgorithm
Maybe RequestPayer
BucketName
Delete
delete' :: Delete
bucket :: BucketName
requestPayer :: Maybe RequestPayer
mfa :: Maybe Text
expectedBucketOwner :: Maybe Text
checksumAlgorithm :: Maybe ChecksumAlgorithm
bypassGovernanceRetention :: Maybe Bool
$sel:delete':DeleteObjects' :: DeleteObjects -> Delete
$sel:bucket:DeleteObjects' :: DeleteObjects -> BucketName
$sel:requestPayer:DeleteObjects' :: DeleteObjects -> Maybe RequestPayer
$sel:mfa:DeleteObjects' :: DeleteObjects -> Maybe Text
$sel:expectedBucketOwner:DeleteObjects' :: DeleteObjects -> Maybe Text
$sel:checksumAlgorithm:DeleteObjects' :: DeleteObjects -> Maybe ChecksumAlgorithm
$sel:bypassGovernanceRetention:DeleteObjects' :: DeleteObjects -> Maybe Bool
..} =
    forall a. ToXML a => Name -> a -> Element
Data.mkElement
      Name
"{http://s3.amazonaws.com/doc/2006-03-01/}Delete"
      Delete
delete'

instance Data.ToHeaders DeleteObjects where
  toHeaders :: DeleteObjects -> ResponseHeaders
toHeaders DeleteObjects' {Maybe Bool
Maybe Text
Maybe ChecksumAlgorithm
Maybe RequestPayer
BucketName
Delete
delete' :: Delete
bucket :: BucketName
requestPayer :: Maybe RequestPayer
mfa :: Maybe Text
expectedBucketOwner :: Maybe Text
checksumAlgorithm :: Maybe ChecksumAlgorithm
bypassGovernanceRetention :: Maybe Bool
$sel:delete':DeleteObjects' :: DeleteObjects -> Delete
$sel:bucket:DeleteObjects' :: DeleteObjects -> BucketName
$sel:requestPayer:DeleteObjects' :: DeleteObjects -> Maybe RequestPayer
$sel:mfa:DeleteObjects' :: DeleteObjects -> Maybe Text
$sel:expectedBucketOwner:DeleteObjects' :: DeleteObjects -> Maybe Text
$sel:checksumAlgorithm:DeleteObjects' :: DeleteObjects -> Maybe ChecksumAlgorithm
$sel:bypassGovernanceRetention:DeleteObjects' :: DeleteObjects -> Maybe Bool
..} =
    forall a. Monoid a => [a] -> a
Prelude.mconcat
      [ HeaderName
"x-amz-bypass-governance-retention"
          forall a. ToHeader a => HeaderName -> a -> ResponseHeaders
Data.=# Maybe Bool
bypassGovernanceRetention,
        HeaderName
"x-amz-sdk-checksum-algorithm"
          forall a. ToHeader a => HeaderName -> a -> ResponseHeaders
Data.=# Maybe ChecksumAlgorithm
checksumAlgorithm,
        HeaderName
"x-amz-expected-bucket-owner"
          forall a. ToHeader a => HeaderName -> a -> ResponseHeaders
Data.=# Maybe Text
expectedBucketOwner,
        HeaderName
"x-amz-mfa" forall a. ToHeader a => HeaderName -> a -> ResponseHeaders
Data.=# Maybe Text
mfa,
        HeaderName
"x-amz-request-payer" forall a. ToHeader a => HeaderName -> a -> ResponseHeaders
Data.=# Maybe RequestPayer
requestPayer
      ]

instance Data.ToPath DeleteObjects where
  toPath :: DeleteObjects -> ByteString
toPath DeleteObjects' {Maybe Bool
Maybe Text
Maybe ChecksumAlgorithm
Maybe RequestPayer
BucketName
Delete
delete' :: Delete
bucket :: BucketName
requestPayer :: Maybe RequestPayer
mfa :: Maybe Text
expectedBucketOwner :: Maybe Text
checksumAlgorithm :: Maybe ChecksumAlgorithm
bypassGovernanceRetention :: Maybe Bool
$sel:delete':DeleteObjects' :: DeleteObjects -> Delete
$sel:bucket:DeleteObjects' :: DeleteObjects -> BucketName
$sel:requestPayer:DeleteObjects' :: DeleteObjects -> Maybe RequestPayer
$sel:mfa:DeleteObjects' :: DeleteObjects -> Maybe Text
$sel:expectedBucketOwner:DeleteObjects' :: DeleteObjects -> Maybe Text
$sel:checksumAlgorithm:DeleteObjects' :: DeleteObjects -> Maybe ChecksumAlgorithm
$sel:bypassGovernanceRetention:DeleteObjects' :: DeleteObjects -> Maybe Bool
..} =
    forall a. Monoid a => [a] -> a
Prelude.mconcat [ByteString
"/", forall a. ToByteString a => a -> ByteString
Data.toBS BucketName
bucket]

instance Data.ToQuery DeleteObjects where
  toQuery :: DeleteObjects -> QueryString
toQuery = forall a b. a -> b -> a
Prelude.const (forall a. Monoid a => [a] -> a
Prelude.mconcat [QueryString
"delete"])

-- | /See:/ 'newDeleteObjectsResponse' smart constructor.
data DeleteObjectsResponse = DeleteObjectsResponse'
  { -- | Container element for a successful delete. It identifies the object that
    -- was successfully deleted.
    DeleteObjectsResponse -> Maybe [DeletedObject]
deleted :: Prelude.Maybe [DeletedObject],
    -- | Container for a failed delete action that describes the object that
    -- Amazon S3 attempted to delete and the error it encountered.
    DeleteObjectsResponse -> Maybe [S3ServiceError]
errors :: Prelude.Maybe [S3ServiceError],
    DeleteObjectsResponse -> Maybe RequestCharged
requestCharged :: Prelude.Maybe RequestCharged,
    -- | The response's http status code.
    DeleteObjectsResponse -> Int
httpStatus :: Prelude.Int
  }
  deriving (DeleteObjectsResponse -> DeleteObjectsResponse -> Bool
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: DeleteObjectsResponse -> DeleteObjectsResponse -> Bool
$c/= :: DeleteObjectsResponse -> DeleteObjectsResponse -> Bool
== :: DeleteObjectsResponse -> DeleteObjectsResponse -> Bool
$c== :: DeleteObjectsResponse -> DeleteObjectsResponse -> Bool
Prelude.Eq, ReadPrec [DeleteObjectsResponse]
ReadPrec DeleteObjectsResponse
Int -> ReadS DeleteObjectsResponse
ReadS [DeleteObjectsResponse]
forall a.
(Int -> ReadS a)
-> ReadS [a] -> ReadPrec a -> ReadPrec [a] -> Read a
readListPrec :: ReadPrec [DeleteObjectsResponse]
$creadListPrec :: ReadPrec [DeleteObjectsResponse]
readPrec :: ReadPrec DeleteObjectsResponse
$creadPrec :: ReadPrec DeleteObjectsResponse
readList :: ReadS [DeleteObjectsResponse]
$creadList :: ReadS [DeleteObjectsResponse]
readsPrec :: Int -> ReadS DeleteObjectsResponse
$creadsPrec :: Int -> ReadS DeleteObjectsResponse
Prelude.Read, Int -> DeleteObjectsResponse -> ShowS
[DeleteObjectsResponse] -> ShowS
DeleteObjectsResponse -> String
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [DeleteObjectsResponse] -> ShowS
$cshowList :: [DeleteObjectsResponse] -> ShowS
show :: DeleteObjectsResponse -> String
$cshow :: DeleteObjectsResponse -> String
showsPrec :: Int -> DeleteObjectsResponse -> ShowS
$cshowsPrec :: Int -> DeleteObjectsResponse -> ShowS
Prelude.Show, forall x. Rep DeleteObjectsResponse x -> DeleteObjectsResponse
forall x. DeleteObjectsResponse -> Rep DeleteObjectsResponse x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cto :: forall x. Rep DeleteObjectsResponse x -> DeleteObjectsResponse
$cfrom :: forall x. DeleteObjectsResponse -> Rep DeleteObjectsResponse x
Prelude.Generic)

-- |
-- Create a value of 'DeleteObjectsResponse' 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:
--
-- 'deleted', 'deleteObjectsResponse_deleted' - Container element for a successful delete. It identifies the object that
-- was successfully deleted.
--
-- 'errors', 'deleteObjectsResponse_errors' - Container for a failed delete action that describes the object that
-- Amazon S3 attempted to delete and the error it encountered.
--
-- 'requestCharged', 'deleteObjectsResponse_requestCharged' - Undocumented member.
--
-- 'httpStatus', 'deleteObjectsResponse_httpStatus' - The response's http status code.
newDeleteObjectsResponse ::
  -- | 'httpStatus'
  Prelude.Int ->
  DeleteObjectsResponse
newDeleteObjectsResponse :: Int -> DeleteObjectsResponse
newDeleteObjectsResponse Int
pHttpStatus_ =
  DeleteObjectsResponse'
    { $sel:deleted:DeleteObjectsResponse' :: Maybe [DeletedObject]
deleted = forall a. Maybe a
Prelude.Nothing,
      $sel:errors:DeleteObjectsResponse' :: Maybe [S3ServiceError]
errors = forall a. Maybe a
Prelude.Nothing,
      $sel:requestCharged:DeleteObjectsResponse' :: Maybe RequestCharged
requestCharged = forall a. Maybe a
Prelude.Nothing,
      $sel:httpStatus:DeleteObjectsResponse' :: Int
httpStatus = Int
pHttpStatus_
    }

-- | Container element for a successful delete. It identifies the object that
-- was successfully deleted.
deleteObjectsResponse_deleted :: Lens.Lens' DeleteObjectsResponse (Prelude.Maybe [DeletedObject])
deleteObjectsResponse_deleted :: Lens' DeleteObjectsResponse (Maybe [DeletedObject])
deleteObjectsResponse_deleted = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\DeleteObjectsResponse' {Maybe [DeletedObject]
deleted :: Maybe [DeletedObject]
$sel:deleted:DeleteObjectsResponse' :: DeleteObjectsResponse -> Maybe [DeletedObject]
deleted} -> Maybe [DeletedObject]
deleted) (\s :: DeleteObjectsResponse
s@DeleteObjectsResponse' {} Maybe [DeletedObject]
a -> DeleteObjectsResponse
s {$sel:deleted:DeleteObjectsResponse' :: Maybe [DeletedObject]
deleted = Maybe [DeletedObject]
a} :: DeleteObjectsResponse) 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

-- | Container for a failed delete action that describes the object that
-- Amazon S3 attempted to delete and the error it encountered.
deleteObjectsResponse_errors :: Lens.Lens' DeleteObjectsResponse (Prelude.Maybe [S3ServiceError])
deleteObjectsResponse_errors :: Lens' DeleteObjectsResponse (Maybe [S3ServiceError])
deleteObjectsResponse_errors = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\DeleteObjectsResponse' {Maybe [S3ServiceError]
errors :: Maybe [S3ServiceError]
$sel:errors:DeleteObjectsResponse' :: DeleteObjectsResponse -> Maybe [S3ServiceError]
errors} -> Maybe [S3ServiceError]
errors) (\s :: DeleteObjectsResponse
s@DeleteObjectsResponse' {} Maybe [S3ServiceError]
a -> DeleteObjectsResponse
s {$sel:errors:DeleteObjectsResponse' :: Maybe [S3ServiceError]
errors = Maybe [S3ServiceError]
a} :: DeleteObjectsResponse) 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

-- | Undocumented member.
deleteObjectsResponse_requestCharged :: Lens.Lens' DeleteObjectsResponse (Prelude.Maybe RequestCharged)
deleteObjectsResponse_requestCharged :: Lens' DeleteObjectsResponse (Maybe RequestCharged)
deleteObjectsResponse_requestCharged = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\DeleteObjectsResponse' {Maybe RequestCharged
requestCharged :: Maybe RequestCharged
$sel:requestCharged:DeleteObjectsResponse' :: DeleteObjectsResponse -> Maybe RequestCharged
requestCharged} -> Maybe RequestCharged
requestCharged) (\s :: DeleteObjectsResponse
s@DeleteObjectsResponse' {} Maybe RequestCharged
a -> DeleteObjectsResponse
s {$sel:requestCharged:DeleteObjectsResponse' :: Maybe RequestCharged
requestCharged = Maybe RequestCharged
a} :: DeleteObjectsResponse)

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

instance Prelude.NFData DeleteObjectsResponse where
  rnf :: DeleteObjectsResponse -> ()
rnf DeleteObjectsResponse' {Int
Maybe [DeletedObject]
Maybe [S3ServiceError]
Maybe RequestCharged
httpStatus :: Int
requestCharged :: Maybe RequestCharged
errors :: Maybe [S3ServiceError]
deleted :: Maybe [DeletedObject]
$sel:httpStatus:DeleteObjectsResponse' :: DeleteObjectsResponse -> Int
$sel:requestCharged:DeleteObjectsResponse' :: DeleteObjectsResponse -> Maybe RequestCharged
$sel:errors:DeleteObjectsResponse' :: DeleteObjectsResponse -> Maybe [S3ServiceError]
$sel:deleted:DeleteObjectsResponse' :: DeleteObjectsResponse -> Maybe [DeletedObject]
..} =
    forall a. NFData a => a -> ()
Prelude.rnf Maybe [DeletedObject]
deleted
      seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf Maybe [S3ServiceError]
errors
      seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf Maybe RequestCharged
requestCharged
      seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf Int
httpStatus