{-# 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.PutBucketEncryption
-- 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 uses the @encryption@ subresource to configure default
-- encryption and Amazon S3 Bucket Key for an existing bucket.
--
-- Default encryption for a bucket can use server-side encryption with
-- Amazon S3-managed keys (SSE-S3) or customer managed keys (SSE-KMS). If
-- you specify default encryption using SSE-KMS, you can also configure
-- Amazon S3 Bucket Key. When the default encryption is SSE-KMS, if you
-- upload an object to the bucket and do not specify the KMS key to use for
-- encryption, Amazon S3 uses the default Amazon Web Services managed KMS
-- key for your account. For information about default encryption, see
-- <https://docs.aws.amazon.com/AmazonS3/latest/dev/bucket-encryption.html Amazon S3 default bucket encryption>
-- in the /Amazon S3 User Guide/. For more information about S3 Bucket
-- Keys, see
-- <https://docs.aws.amazon.com/AmazonS3/latest/dev/bucket-key.html Amazon S3 Bucket Keys>
-- in the /Amazon S3 User Guide/.
--
-- This action requires Amazon Web Services Signature Version 4. For more
-- information, see
-- <https://docs.aws.amazon.com/AmazonS3/latest/API/sig-v4-authenticating-requests.html Authenticating Requests (Amazon Web Services Signature Version 4)>.
--
-- To use this operation, you must have permissions to perform the
-- @s3:PutEncryptionConfiguration@ action. The bucket owner has this
-- permission by default. The bucket owner can grant this permission 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>
-- in the Amazon S3 User Guide.
--
-- __Related Resources__
--
-- -   <https://docs.aws.amazon.com/AmazonS3/latest/API/API_GetBucketEncryption.html GetBucketEncryption>
--
-- -   <https://docs.aws.amazon.com/AmazonS3/latest/API/API_DeleteBucketEncryption.html DeleteBucketEncryption>
module Amazonka.S3.PutBucketEncryption
  ( -- * Creating a Request
    PutBucketEncryption (..),
    newPutBucketEncryption,

    -- * Request Lenses
    putBucketEncryption_checksumAlgorithm,
    putBucketEncryption_contentMD5,
    putBucketEncryption_expectedBucketOwner,
    putBucketEncryption_bucket,
    putBucketEncryption_serverSideEncryptionConfiguration,

    -- * Destructuring the Response
    PutBucketEncryptionResponse (..),
    newPutBucketEncryptionResponse,
  )
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:/ 'newPutBucketEncryption' smart constructor.
data PutBucketEncryption = PutBucketEncryption'
  { -- | 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.
    PutBucketEncryption -> Maybe ChecksumAlgorithm
checksumAlgorithm :: Prelude.Maybe ChecksumAlgorithm,
    -- | The base64-encoded 128-bit MD5 digest of the server-side encryption
    -- configuration.
    --
    -- For requests made using the Amazon Web Services Command Line Interface
    -- (CLI) or Amazon Web Services SDKs, this field is calculated
    -- automatically.
    PutBucketEncryption -> 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).
    PutBucketEncryption -> Maybe Text
expectedBucketOwner :: Prelude.Maybe Prelude.Text,
    -- | Specifies default encryption for a bucket using server-side encryption
    -- with Amazon S3-managed keys (SSE-S3) or customer managed keys (SSE-KMS).
    -- For information about the Amazon S3 default encryption feature, see
    -- <https://docs.aws.amazon.com/AmazonS3/latest/dev/bucket-encryption.html Amazon S3 Default Bucket Encryption>
    -- in the /Amazon S3 User Guide/.
    PutBucketEncryption -> BucketName
bucket :: BucketName,
    PutBucketEncryption -> ServerSideEncryptionConfiguration
serverSideEncryptionConfiguration :: ServerSideEncryptionConfiguration
  }
  deriving (PutBucketEncryption -> PutBucketEncryption -> Bool
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: PutBucketEncryption -> PutBucketEncryption -> Bool
$c/= :: PutBucketEncryption -> PutBucketEncryption -> Bool
== :: PutBucketEncryption -> PutBucketEncryption -> Bool
$c== :: PutBucketEncryption -> PutBucketEncryption -> Bool
Prelude.Eq, Int -> PutBucketEncryption -> ShowS
[PutBucketEncryption] -> ShowS
PutBucketEncryption -> String
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [PutBucketEncryption] -> ShowS
$cshowList :: [PutBucketEncryption] -> ShowS
show :: PutBucketEncryption -> String
$cshow :: PutBucketEncryption -> String
showsPrec :: Int -> PutBucketEncryption -> ShowS
$cshowsPrec :: Int -> PutBucketEncryption -> ShowS
Prelude.Show, forall x. Rep PutBucketEncryption x -> PutBucketEncryption
forall x. PutBucketEncryption -> Rep PutBucketEncryption x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cto :: forall x. Rep PutBucketEncryption x -> PutBucketEncryption
$cfrom :: forall x. PutBucketEncryption -> Rep PutBucketEncryption x
Prelude.Generic)

-- |
-- Create a value of 'PutBucketEncryption' 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', 'putBucketEncryption_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', 'putBucketEncryption_contentMD5' - The base64-encoded 128-bit MD5 digest of the server-side encryption
-- configuration.
--
-- For requests made using the Amazon Web Services Command Line Interface
-- (CLI) or Amazon Web Services SDKs, this field is calculated
-- automatically.
--
-- 'expectedBucketOwner', 'putBucketEncryption_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', 'putBucketEncryption_bucket' - Specifies default encryption for a bucket using server-side encryption
-- with Amazon S3-managed keys (SSE-S3) or customer managed keys (SSE-KMS).
-- For information about the Amazon S3 default encryption feature, see
-- <https://docs.aws.amazon.com/AmazonS3/latest/dev/bucket-encryption.html Amazon S3 Default Bucket Encryption>
-- in the /Amazon S3 User Guide/.
--
-- 'serverSideEncryptionConfiguration', 'putBucketEncryption_serverSideEncryptionConfiguration' - Undocumented member.
newPutBucketEncryption ::
  -- | 'bucket'
  BucketName ->
  -- | 'serverSideEncryptionConfiguration'
  ServerSideEncryptionConfiguration ->
  PutBucketEncryption
newPutBucketEncryption :: BucketName
-> ServerSideEncryptionConfiguration -> PutBucketEncryption
newPutBucketEncryption
  BucketName
pBucket_
  ServerSideEncryptionConfiguration
pServerSideEncryptionConfiguration_ =
    PutBucketEncryption'
      { $sel:checksumAlgorithm:PutBucketEncryption' :: Maybe ChecksumAlgorithm
checksumAlgorithm =
          forall a. Maybe a
Prelude.Nothing,
        $sel:contentMD5:PutBucketEncryption' :: Maybe Text
contentMD5 = forall a. Maybe a
Prelude.Nothing,
        $sel:expectedBucketOwner:PutBucketEncryption' :: Maybe Text
expectedBucketOwner = forall a. Maybe a
Prelude.Nothing,
        $sel:bucket:PutBucketEncryption' :: BucketName
bucket = BucketName
pBucket_,
        $sel:serverSideEncryptionConfiguration:PutBucketEncryption' :: ServerSideEncryptionConfiguration
serverSideEncryptionConfiguration =
          ServerSideEncryptionConfiguration
pServerSideEncryptionConfiguration_
      }

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

-- | The base64-encoded 128-bit MD5 digest of the server-side encryption
-- configuration.
--
-- For requests made using the Amazon Web Services Command Line Interface
-- (CLI) or Amazon Web Services SDKs, this field is calculated
-- automatically.
putBucketEncryption_contentMD5 :: Lens.Lens' PutBucketEncryption (Prelude.Maybe Prelude.Text)
putBucketEncryption_contentMD5 :: Lens' PutBucketEncryption (Maybe Text)
putBucketEncryption_contentMD5 = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\PutBucketEncryption' {Maybe Text
contentMD5 :: Maybe Text
$sel:contentMD5:PutBucketEncryption' :: PutBucketEncryption -> Maybe Text
contentMD5} -> Maybe Text
contentMD5) (\s :: PutBucketEncryption
s@PutBucketEncryption' {} Maybe Text
a -> PutBucketEncryption
s {$sel:contentMD5:PutBucketEncryption' :: Maybe Text
contentMD5 = Maybe Text
a} :: PutBucketEncryption)

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

-- | Specifies default encryption for a bucket using server-side encryption
-- with Amazon S3-managed keys (SSE-S3) or customer managed keys (SSE-KMS).
-- For information about the Amazon S3 default encryption feature, see
-- <https://docs.aws.amazon.com/AmazonS3/latest/dev/bucket-encryption.html Amazon S3 Default Bucket Encryption>
-- in the /Amazon S3 User Guide/.
putBucketEncryption_bucket :: Lens.Lens' PutBucketEncryption BucketName
putBucketEncryption_bucket :: Lens' PutBucketEncryption BucketName
putBucketEncryption_bucket = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\PutBucketEncryption' {BucketName
bucket :: BucketName
$sel:bucket:PutBucketEncryption' :: PutBucketEncryption -> BucketName
bucket} -> BucketName
bucket) (\s :: PutBucketEncryption
s@PutBucketEncryption' {} BucketName
a -> PutBucketEncryption
s {$sel:bucket:PutBucketEncryption' :: BucketName
bucket = BucketName
a} :: PutBucketEncryption)

-- | Undocumented member.
putBucketEncryption_serverSideEncryptionConfiguration :: Lens.Lens' PutBucketEncryption ServerSideEncryptionConfiguration
putBucketEncryption_serverSideEncryptionConfiguration :: Lens' PutBucketEncryption ServerSideEncryptionConfiguration
putBucketEncryption_serverSideEncryptionConfiguration = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\PutBucketEncryption' {ServerSideEncryptionConfiguration
serverSideEncryptionConfiguration :: ServerSideEncryptionConfiguration
$sel:serverSideEncryptionConfiguration:PutBucketEncryption' :: PutBucketEncryption -> ServerSideEncryptionConfiguration
serverSideEncryptionConfiguration} -> ServerSideEncryptionConfiguration
serverSideEncryptionConfiguration) (\s :: PutBucketEncryption
s@PutBucketEncryption' {} ServerSideEncryptionConfiguration
a -> PutBucketEncryption
s {$sel:serverSideEncryptionConfiguration:PutBucketEncryption' :: ServerSideEncryptionConfiguration
serverSideEncryptionConfiguration = ServerSideEncryptionConfiguration
a} :: PutBucketEncryption)

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

instance Prelude.Hashable PutBucketEncryption where
  hashWithSalt :: Int -> PutBucketEncryption -> Int
hashWithSalt Int
_salt PutBucketEncryption' {Maybe Text
Maybe ChecksumAlgorithm
BucketName
ServerSideEncryptionConfiguration
serverSideEncryptionConfiguration :: ServerSideEncryptionConfiguration
bucket :: BucketName
expectedBucketOwner :: Maybe Text
contentMD5 :: Maybe Text
checksumAlgorithm :: Maybe ChecksumAlgorithm
$sel:serverSideEncryptionConfiguration:PutBucketEncryption' :: PutBucketEncryption -> ServerSideEncryptionConfiguration
$sel:bucket:PutBucketEncryption' :: PutBucketEncryption -> BucketName
$sel:expectedBucketOwner:PutBucketEncryption' :: PutBucketEncryption -> Maybe Text
$sel:contentMD5:PutBucketEncryption' :: PutBucketEncryption -> Maybe Text
$sel:checksumAlgorithm:PutBucketEncryption' :: PutBucketEncryption -> 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` BucketName
bucket
      forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` ServerSideEncryptionConfiguration
serverSideEncryptionConfiguration

instance Prelude.NFData PutBucketEncryption where
  rnf :: PutBucketEncryption -> ()
rnf PutBucketEncryption' {Maybe Text
Maybe ChecksumAlgorithm
BucketName
ServerSideEncryptionConfiguration
serverSideEncryptionConfiguration :: ServerSideEncryptionConfiguration
bucket :: BucketName
expectedBucketOwner :: Maybe Text
contentMD5 :: Maybe Text
checksumAlgorithm :: Maybe ChecksumAlgorithm
$sel:serverSideEncryptionConfiguration:PutBucketEncryption' :: PutBucketEncryption -> ServerSideEncryptionConfiguration
$sel:bucket:PutBucketEncryption' :: PutBucketEncryption -> BucketName
$sel:expectedBucketOwner:PutBucketEncryption' :: PutBucketEncryption -> Maybe Text
$sel:contentMD5:PutBucketEncryption' :: PutBucketEncryption -> Maybe Text
$sel:checksumAlgorithm:PutBucketEncryption' :: PutBucketEncryption -> 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 BucketName
bucket
      seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf ServerSideEncryptionConfiguration
serverSideEncryptionConfiguration

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

instance Data.ToHeaders PutBucketEncryption where
  toHeaders :: PutBucketEncryption -> [Header]
toHeaders PutBucketEncryption' {Maybe Text
Maybe ChecksumAlgorithm
BucketName
ServerSideEncryptionConfiguration
serverSideEncryptionConfiguration :: ServerSideEncryptionConfiguration
bucket :: BucketName
expectedBucketOwner :: Maybe Text
contentMD5 :: Maybe Text
checksumAlgorithm :: Maybe ChecksumAlgorithm
$sel:serverSideEncryptionConfiguration:PutBucketEncryption' :: PutBucketEncryption -> ServerSideEncryptionConfiguration
$sel:bucket:PutBucketEncryption' :: PutBucketEncryption -> BucketName
$sel:expectedBucketOwner:PutBucketEncryption' :: PutBucketEncryption -> Maybe Text
$sel:contentMD5:PutBucketEncryption' :: PutBucketEncryption -> Maybe Text
$sel:checksumAlgorithm:PutBucketEncryption' :: PutBucketEncryption -> 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
      ]

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

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

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

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

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