{-# 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.PutBucketReplication
-- Copyright   : (c) 2013-2023 Brendan Hay
-- License     : Mozilla Public License, v. 2.0.
-- Maintainer  : Brendan Hay
-- Stability   : auto-generated
-- Portability : non-portable (GHC extensions)
--
-- Creates a replication configuration or replaces an existing one. For
-- more information, see
-- <https://docs.aws.amazon.com/AmazonS3/latest/dev/replication.html Replication>
-- in the /Amazon S3 User Guide/.
--
-- Specify the replication configuration in the request body. In the
-- replication configuration, you provide the name of the destination
-- bucket or buckets where you want Amazon S3 to replicate objects, the IAM
-- role that Amazon S3 can assume to replicate objects on your behalf, and
-- other relevant information.
--
-- A replication configuration must include at least one rule, and can
-- contain a maximum of 1,000. Each rule identifies a subset of objects to
-- replicate by filtering the objects in the source bucket. To choose
-- additional subsets of objects to replicate, add a rule for each subset.
--
-- To specify a subset of the objects in the source bucket to apply a
-- replication rule to, add the Filter element as a child of the Rule
-- element. You can filter objects based on an object key prefix, one or
-- more object tags, or both. When you add the Filter element in the
-- configuration, you must also add the following elements:
-- @DeleteMarkerReplication@, @Status@, and @Priority@.
--
-- If you are using an earlier version of the replication configuration,
-- Amazon S3 handles replication of delete markers differently. For more
-- information, see
-- <https://docs.aws.amazon.com/AmazonS3/latest/dev/replication-add-config.html#replication-backward-compat-considerations Backward Compatibility>.
--
-- For information about enabling versioning on a bucket, see
-- <https://docs.aws.amazon.com/AmazonS3/latest/dev/Versioning.html Using Versioning>.
--
-- __Handling Replication of Encrypted Objects__
--
-- By default, Amazon S3 doesn\'t replicate objects that are stored at rest
-- using server-side encryption with KMS keys. To replicate Amazon Web
-- Services KMS-encrypted objects, add the following:
-- @SourceSelectionCriteria@, @SseKmsEncryptedObjects@, @Status@,
-- @EncryptionConfiguration@, and @ReplicaKmsKeyID@. For information about
-- replication configuration, see
-- <https://docs.aws.amazon.com/AmazonS3/latest/dev/replication-config-for-kms-objects.html Replicating Objects Created with SSE Using KMS keys>.
--
-- For information on @PutBucketReplication@ errors, see
-- <https://docs.aws.amazon.com/AmazonS3/latest/API/ErrorResponses.html#ReplicationErrorCodeList List of replication-related error codes>
--
-- __Permissions__
--
-- To create a @PutBucketReplication@ request, you must have
-- @s3:PutReplicationConfiguration@ permissions for the bucket.
--
-- By default, a resource owner, in this case the Amazon Web Services
-- account that created the bucket, can perform this operation. The
-- resource owner can also grant others permissions to perform the
-- operation. For more information about permissions, see
-- <https://docs.aws.amazon.com/AmazonS3/latest/dev/using-with-s3-actions.html Specifying Permissions in a Policy>
-- and
-- <https://docs.aws.amazon.com/AmazonS3/latest/userguide/s3-access-control.html Managing Access Permissions to Your Amazon S3 Resources>.
--
-- To perform this operation, the user or role performing the action must
-- have the
-- <https://docs.aws.amazon.com/IAM/latest/UserGuide/id_roles_use_passrole.html iam:PassRole>
-- permission.
--
-- The following operations are related to @PutBucketReplication@:
--
-- -   <https://docs.aws.amazon.com/AmazonS3/latest/API/API_GetBucketReplication.html GetBucketReplication>
--
-- -   <https://docs.aws.amazon.com/AmazonS3/latest/API/API_DeleteBucketReplication.html DeleteBucketReplication>
module Amazonka.S3.PutBucketReplication
  ( -- * Creating a Request
    PutBucketReplication (..),
    newPutBucketReplication,

    -- * Request Lenses
    putBucketReplication_checksumAlgorithm,
    putBucketReplication_contentMD5,
    putBucketReplication_expectedBucketOwner,
    putBucketReplication_token,
    putBucketReplication_bucket,
    putBucketReplication_replicationConfiguration,

    -- * Destructuring the Response
    PutBucketReplicationResponse (..),
    newPutBucketReplicationResponse,
  )
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:/ 'newPutBucketReplication' smart constructor.
data PutBucketReplication = PutBucketReplication'
  { -- | 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.
    PutBucketReplication -> Maybe ChecksumAlgorithm
checksumAlgorithm :: Prelude.Maybe ChecksumAlgorithm,
    -- | The base64-encoded 128-bit MD5 digest of the data. You must use this
    -- header as a message integrity check to verify that the request body was
    -- not corrupted in transit. For more information, see
    -- <http://www.ietf.org/rfc/rfc1864.txt RFC 1864>.
    --
    -- For requests made using the Amazon Web Services Command Line Interface
    -- (CLI) or Amazon Web Services SDKs, this field is calculated
    -- automatically.
    PutBucketReplication -> Maybe Text
contentMD5 :: Prelude.Maybe Prelude.Text,
    -- | 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).
    PutBucketReplication -> Maybe Text
expectedBucketOwner :: Prelude.Maybe Prelude.Text,
    -- | A token to allow Object Lock to be enabled for an existing bucket.
    PutBucketReplication -> Maybe Text
token :: Prelude.Maybe Prelude.Text,
    -- | The name of the bucket
    PutBucketReplication -> BucketName
bucket :: BucketName,
    PutBucketReplication -> ReplicationConfiguration
replicationConfiguration :: ReplicationConfiguration
  }
  deriving (PutBucketReplication -> PutBucketReplication -> Bool
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: PutBucketReplication -> PutBucketReplication -> Bool
$c/= :: PutBucketReplication -> PutBucketReplication -> Bool
== :: PutBucketReplication -> PutBucketReplication -> Bool
$c== :: PutBucketReplication -> PutBucketReplication -> Bool
Prelude.Eq, ReadPrec [PutBucketReplication]
ReadPrec PutBucketReplication
Int -> ReadS PutBucketReplication
ReadS [PutBucketReplication]
forall a.
(Int -> ReadS a)
-> ReadS [a] -> ReadPrec a -> ReadPrec [a] -> Read a
readListPrec :: ReadPrec [PutBucketReplication]
$creadListPrec :: ReadPrec [PutBucketReplication]
readPrec :: ReadPrec PutBucketReplication
$creadPrec :: ReadPrec PutBucketReplication
readList :: ReadS [PutBucketReplication]
$creadList :: ReadS [PutBucketReplication]
readsPrec :: Int -> ReadS PutBucketReplication
$creadsPrec :: Int -> ReadS PutBucketReplication
Prelude.Read, Int -> PutBucketReplication -> ShowS
[PutBucketReplication] -> ShowS
PutBucketReplication -> String
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [PutBucketReplication] -> ShowS
$cshowList :: [PutBucketReplication] -> ShowS
show :: PutBucketReplication -> String
$cshow :: PutBucketReplication -> String
showsPrec :: Int -> PutBucketReplication -> ShowS
$cshowsPrec :: Int -> PutBucketReplication -> ShowS
Prelude.Show, forall x. Rep PutBucketReplication x -> PutBucketReplication
forall x. PutBucketReplication -> Rep PutBucketReplication x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cto :: forall x. Rep PutBucketReplication x -> PutBucketReplication
$cfrom :: forall x. PutBucketReplication -> Rep PutBucketReplication x
Prelude.Generic)

-- |
-- Create a value of 'PutBucketReplication' 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:
--
-- 'checksumAlgorithm', 'putBucketReplication_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.
--
-- 'contentMD5', 'putBucketReplication_contentMD5' - The base64-encoded 128-bit MD5 digest of the data. You must use this
-- header as a message integrity check to verify that the request body was
-- not corrupted in transit. For more information, see
-- <http://www.ietf.org/rfc/rfc1864.txt RFC 1864>.
--
-- For requests made using the Amazon Web Services Command Line Interface
-- (CLI) or Amazon Web Services SDKs, this field is calculated
-- automatically.
--
-- 'expectedBucketOwner', 'putBucketReplication_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).
--
-- 'token', 'putBucketReplication_token' - A token to allow Object Lock to be enabled for an existing bucket.
--
-- 'bucket', 'putBucketReplication_bucket' - The name of the bucket
--
-- 'replicationConfiguration', 'putBucketReplication_replicationConfiguration' - Undocumented member.
newPutBucketReplication ::
  -- | 'bucket'
  BucketName ->
  -- | 'replicationConfiguration'
  ReplicationConfiguration ->
  PutBucketReplication
newPutBucketReplication :: BucketName -> ReplicationConfiguration -> PutBucketReplication
newPutBucketReplication
  BucketName
pBucket_
  ReplicationConfiguration
pReplicationConfiguration_ =
    PutBucketReplication'
      { $sel:checksumAlgorithm:PutBucketReplication' :: Maybe ChecksumAlgorithm
checksumAlgorithm =
          forall a. Maybe a
Prelude.Nothing,
        $sel:contentMD5:PutBucketReplication' :: Maybe Text
contentMD5 = forall a. Maybe a
Prelude.Nothing,
        $sel:expectedBucketOwner:PutBucketReplication' :: Maybe Text
expectedBucketOwner = forall a. Maybe a
Prelude.Nothing,
        $sel:token:PutBucketReplication' :: Maybe Text
token = forall a. Maybe a
Prelude.Nothing,
        $sel:bucket:PutBucketReplication' :: BucketName
bucket = BucketName
pBucket_,
        $sel:replicationConfiguration:PutBucketReplication' :: ReplicationConfiguration
replicationConfiguration =
          ReplicationConfiguration
pReplicationConfiguration_
      }

-- | 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.
putBucketReplication_checksumAlgorithm :: Lens.Lens' PutBucketReplication (Prelude.Maybe ChecksumAlgorithm)
putBucketReplication_checksumAlgorithm :: Lens' PutBucketReplication (Maybe ChecksumAlgorithm)
putBucketReplication_checksumAlgorithm = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\PutBucketReplication' {Maybe ChecksumAlgorithm
checksumAlgorithm :: Maybe ChecksumAlgorithm
$sel:checksumAlgorithm:PutBucketReplication' :: PutBucketReplication -> Maybe ChecksumAlgorithm
checksumAlgorithm} -> Maybe ChecksumAlgorithm
checksumAlgorithm) (\s :: PutBucketReplication
s@PutBucketReplication' {} Maybe ChecksumAlgorithm
a -> PutBucketReplication
s {$sel:checksumAlgorithm:PutBucketReplication' :: Maybe ChecksumAlgorithm
checksumAlgorithm = Maybe ChecksumAlgorithm
a} :: PutBucketReplication)

-- | The base64-encoded 128-bit MD5 digest of the data. You must use this
-- header as a message integrity check to verify that the request body was
-- not corrupted in transit. For more information, see
-- <http://www.ietf.org/rfc/rfc1864.txt RFC 1864>.
--
-- For requests made using the Amazon Web Services Command Line Interface
-- (CLI) or Amazon Web Services SDKs, this field is calculated
-- automatically.
putBucketReplication_contentMD5 :: Lens.Lens' PutBucketReplication (Prelude.Maybe Prelude.Text)
putBucketReplication_contentMD5 :: Lens' PutBucketReplication (Maybe Text)
putBucketReplication_contentMD5 = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\PutBucketReplication' {Maybe Text
contentMD5 :: Maybe Text
$sel:contentMD5:PutBucketReplication' :: PutBucketReplication -> Maybe Text
contentMD5} -> Maybe Text
contentMD5) (\s :: PutBucketReplication
s@PutBucketReplication' {} Maybe Text
a -> PutBucketReplication
s {$sel:contentMD5:PutBucketReplication' :: Maybe Text
contentMD5 = Maybe Text
a} :: PutBucketReplication)

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

-- | A token to allow Object Lock to be enabled for an existing bucket.
putBucketReplication_token :: Lens.Lens' PutBucketReplication (Prelude.Maybe Prelude.Text)
putBucketReplication_token :: Lens' PutBucketReplication (Maybe Text)
putBucketReplication_token = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\PutBucketReplication' {Maybe Text
token :: Maybe Text
$sel:token:PutBucketReplication' :: PutBucketReplication -> Maybe Text
token} -> Maybe Text
token) (\s :: PutBucketReplication
s@PutBucketReplication' {} Maybe Text
a -> PutBucketReplication
s {$sel:token:PutBucketReplication' :: Maybe Text
token = Maybe Text
a} :: PutBucketReplication)

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

-- | Undocumented member.
putBucketReplication_replicationConfiguration :: Lens.Lens' PutBucketReplication ReplicationConfiguration
putBucketReplication_replicationConfiguration :: Lens' PutBucketReplication ReplicationConfiguration
putBucketReplication_replicationConfiguration = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\PutBucketReplication' {ReplicationConfiguration
replicationConfiguration :: ReplicationConfiguration
$sel:replicationConfiguration:PutBucketReplication' :: PutBucketReplication -> ReplicationConfiguration
replicationConfiguration} -> ReplicationConfiguration
replicationConfiguration) (\s :: PutBucketReplication
s@PutBucketReplication' {} ReplicationConfiguration
a -> PutBucketReplication
s {$sel:replicationConfiguration:PutBucketReplication' :: ReplicationConfiguration
replicationConfiguration = ReplicationConfiguration
a} :: PutBucketReplication)

instance Core.AWSRequest PutBucketReplication where
  type
    AWSResponse PutBucketReplication =
      PutBucketReplicationResponse
  request :: (Service -> Service)
-> PutBucketReplication -> Request PutBucketReplication
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, ToElement a) => Service -> a -> Request a
Request.putXML (Service -> Service
overrides Service
defaultService)
  response :: forall (m :: * -> *).
MonadResource m =>
(ByteStringLazy -> IO ByteStringLazy)
-> Service
-> Proxy PutBucketReplication
-> ClientResponse ClientBody
-> m (Either
        Error (ClientResponse (AWSResponse PutBucketReplication)))
response =
    forall (m :: * -> *) a.
MonadResource m =>
AWSResponse a
-> (ByteStringLazy -> IO ByteStringLazy)
-> Service
-> Proxy a
-> ClientResponse ClientBody
-> m (Either Error (ClientResponse (AWSResponse a)))
Response.receiveNull PutBucketReplicationResponse
PutBucketReplicationResponse'

instance Prelude.Hashable PutBucketReplication where
  hashWithSalt :: Int -> PutBucketReplication -> Int
hashWithSalt Int
_salt PutBucketReplication' {Maybe Text
Maybe ChecksumAlgorithm
BucketName
ReplicationConfiguration
replicationConfiguration :: ReplicationConfiguration
bucket :: BucketName
token :: Maybe Text
expectedBucketOwner :: Maybe Text
contentMD5 :: Maybe Text
checksumAlgorithm :: Maybe ChecksumAlgorithm
$sel:replicationConfiguration:PutBucketReplication' :: PutBucketReplication -> ReplicationConfiguration
$sel:bucket:PutBucketReplication' :: PutBucketReplication -> BucketName
$sel:token:PutBucketReplication' :: PutBucketReplication -> Maybe Text
$sel:expectedBucketOwner:PutBucketReplication' :: PutBucketReplication -> Maybe Text
$sel:contentMD5:PutBucketReplication' :: PutBucketReplication -> Maybe Text
$sel:checksumAlgorithm:PutBucketReplication' :: PutBucketReplication -> Maybe ChecksumAlgorithm
..} =
    Int
_salt
      forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Maybe ChecksumAlgorithm
checksumAlgorithm
      forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Maybe Text
contentMD5
      forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Maybe Text
expectedBucketOwner
      forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Maybe Text
token
      forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` BucketName
bucket
      forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` ReplicationConfiguration
replicationConfiguration

instance Prelude.NFData PutBucketReplication where
  rnf :: PutBucketReplication -> ()
rnf PutBucketReplication' {Maybe Text
Maybe ChecksumAlgorithm
BucketName
ReplicationConfiguration
replicationConfiguration :: ReplicationConfiguration
bucket :: BucketName
token :: Maybe Text
expectedBucketOwner :: Maybe Text
contentMD5 :: Maybe Text
checksumAlgorithm :: Maybe ChecksumAlgorithm
$sel:replicationConfiguration:PutBucketReplication' :: PutBucketReplication -> ReplicationConfiguration
$sel:bucket:PutBucketReplication' :: PutBucketReplication -> BucketName
$sel:token:PutBucketReplication' :: PutBucketReplication -> Maybe Text
$sel:expectedBucketOwner:PutBucketReplication' :: PutBucketReplication -> Maybe Text
$sel:contentMD5:PutBucketReplication' :: PutBucketReplication -> Maybe Text
$sel:checksumAlgorithm:PutBucketReplication' :: PutBucketReplication -> Maybe ChecksumAlgorithm
..} =
    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
contentMD5
      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
token
      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 ReplicationConfiguration
replicationConfiguration

instance Data.ToElement PutBucketReplication where
  toElement :: PutBucketReplication -> Element
toElement PutBucketReplication' {Maybe Text
Maybe ChecksumAlgorithm
BucketName
ReplicationConfiguration
replicationConfiguration :: ReplicationConfiguration
bucket :: BucketName
token :: Maybe Text
expectedBucketOwner :: Maybe Text
contentMD5 :: Maybe Text
checksumAlgorithm :: Maybe ChecksumAlgorithm
$sel:replicationConfiguration:PutBucketReplication' :: PutBucketReplication -> ReplicationConfiguration
$sel:bucket:PutBucketReplication' :: PutBucketReplication -> BucketName
$sel:token:PutBucketReplication' :: PutBucketReplication -> Maybe Text
$sel:expectedBucketOwner:PutBucketReplication' :: PutBucketReplication -> Maybe Text
$sel:contentMD5:PutBucketReplication' :: PutBucketReplication -> Maybe Text
$sel:checksumAlgorithm:PutBucketReplication' :: PutBucketReplication -> Maybe ChecksumAlgorithm
..} =
    forall a. ToXML a => Name -> a -> Element
Data.mkElement
      Name
"{http://s3.amazonaws.com/doc/2006-03-01/}ReplicationConfiguration"
      ReplicationConfiguration
replicationConfiguration

instance Data.ToHeaders PutBucketReplication where
  toHeaders :: PutBucketReplication -> [Header]
toHeaders PutBucketReplication' {Maybe Text
Maybe ChecksumAlgorithm
BucketName
ReplicationConfiguration
replicationConfiguration :: ReplicationConfiguration
bucket :: BucketName
token :: Maybe Text
expectedBucketOwner :: Maybe Text
contentMD5 :: Maybe Text
checksumAlgorithm :: Maybe ChecksumAlgorithm
$sel:replicationConfiguration:PutBucketReplication' :: PutBucketReplication -> ReplicationConfiguration
$sel:bucket:PutBucketReplication' :: PutBucketReplication -> BucketName
$sel:token:PutBucketReplication' :: PutBucketReplication -> Maybe Text
$sel:expectedBucketOwner:PutBucketReplication' :: PutBucketReplication -> Maybe Text
$sel:contentMD5:PutBucketReplication' :: PutBucketReplication -> Maybe Text
$sel:checksumAlgorithm:PutBucketReplication' :: PutBucketReplication -> Maybe ChecksumAlgorithm
..} =
    forall a. Monoid a => [a] -> a
Prelude.mconcat
      [ HeaderName
"x-amz-sdk-checksum-algorithm"
          forall a. ToHeader a => HeaderName -> a -> [Header]
Data.=# Maybe ChecksumAlgorithm
checksumAlgorithm,
        HeaderName
"Content-MD5" forall a. ToHeader a => HeaderName -> a -> [Header]
Data.=# Maybe Text
contentMD5,
        HeaderName
"x-amz-expected-bucket-owner"
          forall a. ToHeader a => HeaderName -> a -> [Header]
Data.=# Maybe Text
expectedBucketOwner,
        HeaderName
"x-amz-bucket-object-lock-token" forall a. ToHeader a => HeaderName -> a -> [Header]
Data.=# Maybe Text
token
      ]

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

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

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

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

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