{-# 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.DeleteBucketReplication
-- 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 the replication configuration from the bucket.
--
-- To use this operation, you must have permissions to perform the
-- @s3:PutReplicationConfiguration@ action. The bucket owner has these
-- permissions by default and can grant it to others. For more information
-- about permissions, see
-- <https://docs.aws.amazon.com/AmazonS3/latest/userguide/using-with-s3-actions.html#using-with-s3-actions-related-to-bucket-subresources Permissions Related to Bucket Subresource Operations>
-- and
-- <https://docs.aws.amazon.com/AmazonS3/latest/userguide/s3-access-control.html Managing Access Permissions to Your Amazon S3 Resources>.
--
-- It can take a while for the deletion of a replication configuration to
-- fully propagate.
--
-- For information about replication configuration, see
-- <https://docs.aws.amazon.com/AmazonS3/latest/dev/replication.html Replication>
-- in the /Amazon S3 User Guide/.
--
-- The following operations are related to @DeleteBucketReplication@:
--
-- -   <https://docs.aws.amazon.com/AmazonS3/latest/API/API_PutBucketReplication.html PutBucketReplication>
--
-- -   <https://docs.aws.amazon.com/AmazonS3/latest/API/API_GetBucketReplication.html GetBucketReplication>
module Amazonka.S3.DeleteBucketReplication
  ( -- * Creating a Request
    DeleteBucketReplication (..),
    newDeleteBucketReplication,

    -- * Request Lenses
    deleteBucketReplication_expectedBucketOwner,
    deleteBucketReplication_bucket,

    -- * Destructuring the Response
    DeleteBucketReplicationResponse (..),
    newDeleteBucketReplicationResponse,
  )
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:/ 'newDeleteBucketReplication' smart constructor.
data DeleteBucketReplication = DeleteBucketReplication'
  { -- | 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).
    DeleteBucketReplication -> Maybe Text
expectedBucketOwner :: Prelude.Maybe Prelude.Text,
    -- | The bucket name.
    DeleteBucketReplication -> BucketName
bucket :: BucketName
  }
  deriving (DeleteBucketReplication -> DeleteBucketReplication -> Bool
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: DeleteBucketReplication -> DeleteBucketReplication -> Bool
$c/= :: DeleteBucketReplication -> DeleteBucketReplication -> Bool
== :: DeleteBucketReplication -> DeleteBucketReplication -> Bool
$c== :: DeleteBucketReplication -> DeleteBucketReplication -> Bool
Prelude.Eq, ReadPrec [DeleteBucketReplication]
ReadPrec DeleteBucketReplication
Int -> ReadS DeleteBucketReplication
ReadS [DeleteBucketReplication]
forall a.
(Int -> ReadS a)
-> ReadS [a] -> ReadPrec a -> ReadPrec [a] -> Read a
readListPrec :: ReadPrec [DeleteBucketReplication]
$creadListPrec :: ReadPrec [DeleteBucketReplication]
readPrec :: ReadPrec DeleteBucketReplication
$creadPrec :: ReadPrec DeleteBucketReplication
readList :: ReadS [DeleteBucketReplication]
$creadList :: ReadS [DeleteBucketReplication]
readsPrec :: Int -> ReadS DeleteBucketReplication
$creadsPrec :: Int -> ReadS DeleteBucketReplication
Prelude.Read, Int -> DeleteBucketReplication -> ShowS
[DeleteBucketReplication] -> ShowS
DeleteBucketReplication -> String
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [DeleteBucketReplication] -> ShowS
$cshowList :: [DeleteBucketReplication] -> ShowS
show :: DeleteBucketReplication -> String
$cshow :: DeleteBucketReplication -> String
showsPrec :: Int -> DeleteBucketReplication -> ShowS
$cshowsPrec :: Int -> DeleteBucketReplication -> ShowS
Prelude.Show, forall x. Rep DeleteBucketReplication x -> DeleteBucketReplication
forall x. DeleteBucketReplication -> Rep DeleteBucketReplication x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cto :: forall x. Rep DeleteBucketReplication x -> DeleteBucketReplication
$cfrom :: forall x. DeleteBucketReplication -> Rep DeleteBucketReplication x
Prelude.Generic)

-- |
-- Create a value of 'DeleteBucketReplication' 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:
--
-- 'expectedBucketOwner', 'deleteBucketReplication_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).
--
-- 'bucket', 'deleteBucketReplication_bucket' - The bucket name.
newDeleteBucketReplication ::
  -- | 'bucket'
  BucketName ->
  DeleteBucketReplication
newDeleteBucketReplication :: BucketName -> DeleteBucketReplication
newDeleteBucketReplication BucketName
pBucket_ =
  DeleteBucketReplication'
    { $sel:expectedBucketOwner:DeleteBucketReplication' :: Maybe Text
expectedBucketOwner =
        forall a. Maybe a
Prelude.Nothing,
      $sel:bucket:DeleteBucketReplication' :: BucketName
bucket = BucketName
pBucket_
    }

-- | 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).
deleteBucketReplication_expectedBucketOwner :: Lens.Lens' DeleteBucketReplication (Prelude.Maybe Prelude.Text)
deleteBucketReplication_expectedBucketOwner :: Lens' DeleteBucketReplication (Maybe Text)
deleteBucketReplication_expectedBucketOwner = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\DeleteBucketReplication' {Maybe Text
expectedBucketOwner :: Maybe Text
$sel:expectedBucketOwner:DeleteBucketReplication' :: DeleteBucketReplication -> Maybe Text
expectedBucketOwner} -> Maybe Text
expectedBucketOwner) (\s :: DeleteBucketReplication
s@DeleteBucketReplication' {} Maybe Text
a -> DeleteBucketReplication
s {$sel:expectedBucketOwner:DeleteBucketReplication' :: Maybe Text
expectedBucketOwner = Maybe Text
a} :: DeleteBucketReplication)

-- | The bucket name.
deleteBucketReplication_bucket :: Lens.Lens' DeleteBucketReplication BucketName
deleteBucketReplication_bucket :: Lens' DeleteBucketReplication BucketName
deleteBucketReplication_bucket = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\DeleteBucketReplication' {BucketName
bucket :: BucketName
$sel:bucket:DeleteBucketReplication' :: DeleteBucketReplication -> BucketName
bucket} -> BucketName
bucket) (\s :: DeleteBucketReplication
s@DeleteBucketReplication' {} BucketName
a -> DeleteBucketReplication
s {$sel:bucket:DeleteBucketReplication' :: BucketName
bucket = BucketName
a} :: DeleteBucketReplication)

instance Core.AWSRequest DeleteBucketReplication where
  type
    AWSResponse DeleteBucketReplication =
      DeleteBucketReplicationResponse
  request :: (Service -> Service)
-> DeleteBucketReplication -> Request DeleteBucketReplication
request Service -> Service
overrides =
    forall a. Request a -> Request a
Request.s3vhost
      forall b c a. (b -> c) -> (a -> b) -> a -> c
Prelude.. forall a. ToRequest a => Service -> a -> Request a
Request.delete (Service -> Service
overrides Service
defaultService)
  response :: forall (m :: * -> *).
MonadResource m =>
(ByteStringLazy -> IO ByteStringLazy)
-> Service
-> Proxy DeleteBucketReplication
-> ClientResponse ClientBody
-> m (Either
        Error (ClientResponse (AWSResponse DeleteBucketReplication)))
response =
    forall (m :: * -> *) a.
MonadResource m =>
AWSResponse a
-> (ByteStringLazy -> IO ByteStringLazy)
-> Service
-> Proxy a
-> ClientResponse ClientBody
-> m (Either Error (ClientResponse (AWSResponse a)))
Response.receiveNull
      DeleteBucketReplicationResponse
DeleteBucketReplicationResponse'

instance Prelude.Hashable DeleteBucketReplication where
  hashWithSalt :: Int -> DeleteBucketReplication -> Int
hashWithSalt Int
_salt DeleteBucketReplication' {Maybe Text
BucketName
bucket :: BucketName
expectedBucketOwner :: Maybe Text
$sel:bucket:DeleteBucketReplication' :: DeleteBucketReplication -> BucketName
$sel:expectedBucketOwner:DeleteBucketReplication' :: DeleteBucketReplication -> Maybe Text
..} =
    Int
_salt
      forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Maybe Text
expectedBucketOwner
      forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` BucketName
bucket

instance Prelude.NFData DeleteBucketReplication where
  rnf :: DeleteBucketReplication -> ()
rnf DeleteBucketReplication' {Maybe Text
BucketName
bucket :: BucketName
expectedBucketOwner :: Maybe Text
$sel:bucket:DeleteBucketReplication' :: DeleteBucketReplication -> BucketName
$sel:expectedBucketOwner:DeleteBucketReplication' :: DeleteBucketReplication -> Maybe Text
..} =
    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 BucketName
bucket

instance Data.ToHeaders DeleteBucketReplication where
  toHeaders :: DeleteBucketReplication -> [Header]
toHeaders DeleteBucketReplication' {Maybe Text
BucketName
bucket :: BucketName
expectedBucketOwner :: Maybe Text
$sel:bucket:DeleteBucketReplication' :: DeleteBucketReplication -> BucketName
$sel:expectedBucketOwner:DeleteBucketReplication' :: DeleteBucketReplication -> Maybe Text
..} =
    forall a. Monoid a => [a] -> a
Prelude.mconcat
      [ HeaderName
"x-amz-expected-bucket-owner"
          forall a. ToHeader a => HeaderName -> a -> [Header]
Data.=# Maybe Text
expectedBucketOwner
      ]

instance Data.ToPath DeleteBucketReplication where
  toPath :: DeleteBucketReplication -> ByteString
toPath DeleteBucketReplication' {Maybe Text
BucketName
bucket :: BucketName
expectedBucketOwner :: Maybe Text
$sel:bucket:DeleteBucketReplication' :: DeleteBucketReplication -> BucketName
$sel:expectedBucketOwner:DeleteBucketReplication' :: DeleteBucketReplication -> Maybe Text
..} =
    forall a. Monoid a => [a] -> a
Prelude.mconcat [ByteString
"/", forall a. ToByteString a => a -> ByteString
Data.toBS BucketName
bucket]

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

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

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

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