{-# 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.PutObjectRetention
-- Copyright   : (c) 2013-2023 Brendan Hay
-- License     : Mozilla Public License, v. 2.0.
-- Maintainer  : Brendan Hay
-- Stability   : auto-generated
-- Portability : non-portable (GHC extensions)
--
-- Places an Object Retention configuration on an object. For more
-- information, see
-- <https://docs.aws.amazon.com/AmazonS3/latest/dev/object-lock.html Locking Objects>.
-- Users or accounts require the @s3:PutObjectRetention@ permission in
-- order to place an Object Retention configuration on objects. Bypassing a
-- Governance Retention configuration requires the
-- @s3:BypassGovernanceRetention@ permission.
--
-- This action is not supported by Amazon S3 on Outposts.
module Amazonka.S3.PutObjectRetention
  ( -- * Creating a Request
    PutObjectRetention (..),
    newPutObjectRetention,

    -- * Request Lenses
    putObjectRetention_bypassGovernanceRetention,
    putObjectRetention_checksumAlgorithm,
    putObjectRetention_contentMD5,
    putObjectRetention_expectedBucketOwner,
    putObjectRetention_requestPayer,
    putObjectRetention_retention,
    putObjectRetention_versionId,
    putObjectRetention_bucket,
    putObjectRetention_key,

    -- * Destructuring the Response
    PutObjectRetentionResponse (..),
    newPutObjectRetentionResponse,

    -- * Response Lenses
    putObjectRetentionResponse_requestCharged,
    putObjectRetentionResponse_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:/ 'newPutObjectRetention' smart constructor.
data PutObjectRetention = PutObjectRetention'
  { -- | Indicates whether this action should bypass Governance-mode
    -- restrictions.
    PutObjectRetention -> 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.
    PutObjectRetention -> Maybe ChecksumAlgorithm
checksumAlgorithm :: Prelude.Maybe ChecksumAlgorithm,
    -- | The MD5 hash for the request body.
    --
    -- For requests made using the Amazon Web Services Command Line Interface
    -- (CLI) or Amazon Web Services SDKs, this field is calculated
    -- automatically.
    PutObjectRetention -> 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).
    PutObjectRetention -> Maybe Text
expectedBucketOwner :: Prelude.Maybe Prelude.Text,
    PutObjectRetention -> Maybe RequestPayer
requestPayer :: Prelude.Maybe RequestPayer,
    -- | The container element for the Object Retention configuration.
    PutObjectRetention -> Maybe ObjectLockRetention
retention :: Prelude.Maybe ObjectLockRetention,
    -- | The version ID for the object that you want to apply this Object
    -- Retention configuration to.
    PutObjectRetention -> Maybe ObjectVersionId
versionId :: Prelude.Maybe ObjectVersionId,
    -- | The bucket name that contains the object you want to apply this Object
    -- Retention configuration to.
    --
    -- 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/.
    PutObjectRetention -> BucketName
bucket :: BucketName,
    -- | The key name for the object that you want to apply this Object Retention
    -- configuration to.
    PutObjectRetention -> ObjectKey
key :: ObjectKey
  }
  deriving (PutObjectRetention -> PutObjectRetention -> Bool
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: PutObjectRetention -> PutObjectRetention -> Bool
$c/= :: PutObjectRetention -> PutObjectRetention -> Bool
== :: PutObjectRetention -> PutObjectRetention -> Bool
$c== :: PutObjectRetention -> PutObjectRetention -> Bool
Prelude.Eq, ReadPrec [PutObjectRetention]
ReadPrec PutObjectRetention
Int -> ReadS PutObjectRetention
ReadS [PutObjectRetention]
forall a.
(Int -> ReadS a)
-> ReadS [a] -> ReadPrec a -> ReadPrec [a] -> Read a
readListPrec :: ReadPrec [PutObjectRetention]
$creadListPrec :: ReadPrec [PutObjectRetention]
readPrec :: ReadPrec PutObjectRetention
$creadPrec :: ReadPrec PutObjectRetention
readList :: ReadS [PutObjectRetention]
$creadList :: ReadS [PutObjectRetention]
readsPrec :: Int -> ReadS PutObjectRetention
$creadsPrec :: Int -> ReadS PutObjectRetention
Prelude.Read, Int -> PutObjectRetention -> ShowS
[PutObjectRetention] -> ShowS
PutObjectRetention -> String
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [PutObjectRetention] -> ShowS
$cshowList :: [PutObjectRetention] -> ShowS
show :: PutObjectRetention -> String
$cshow :: PutObjectRetention -> String
showsPrec :: Int -> PutObjectRetention -> ShowS
$cshowsPrec :: Int -> PutObjectRetention -> ShowS
Prelude.Show, forall x. Rep PutObjectRetention x -> PutObjectRetention
forall x. PutObjectRetention -> Rep PutObjectRetention x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cto :: forall x. Rep PutObjectRetention x -> PutObjectRetention
$cfrom :: forall x. PutObjectRetention -> Rep PutObjectRetention x
Prelude.Generic)

-- |
-- Create a value of 'PutObjectRetention' 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', 'putObjectRetention_bypassGovernanceRetention' - Indicates whether this action should bypass Governance-mode
-- restrictions.
--
-- 'checksumAlgorithm', 'putObjectRetention_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', 'putObjectRetention_contentMD5' - The MD5 hash for the request body.
--
-- For requests made using the Amazon Web Services Command Line Interface
-- (CLI) or Amazon Web Services SDKs, this field is calculated
-- automatically.
--
-- 'expectedBucketOwner', 'putObjectRetention_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).
--
-- 'requestPayer', 'putObjectRetention_requestPayer' - Undocumented member.
--
-- 'retention', 'putObjectRetention_retention' - The container element for the Object Retention configuration.
--
-- 'versionId', 'putObjectRetention_versionId' - The version ID for the object that you want to apply this Object
-- Retention configuration to.
--
-- 'bucket', 'putObjectRetention_bucket' - The bucket name that contains the object you want to apply this Object
-- Retention configuration to.
--
-- 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/.
--
-- 'key', 'putObjectRetention_key' - The key name for the object that you want to apply this Object Retention
-- configuration to.
newPutObjectRetention ::
  -- | 'bucket'
  BucketName ->
  -- | 'key'
  ObjectKey ->
  PutObjectRetention
newPutObjectRetention :: BucketName -> ObjectKey -> PutObjectRetention
newPutObjectRetention BucketName
pBucket_ ObjectKey
pKey_ =
  PutObjectRetention'
    { $sel:bypassGovernanceRetention:PutObjectRetention' :: Maybe Bool
bypassGovernanceRetention =
        forall a. Maybe a
Prelude.Nothing,
      $sel:checksumAlgorithm:PutObjectRetention' :: Maybe ChecksumAlgorithm
checksumAlgorithm = forall a. Maybe a
Prelude.Nothing,
      $sel:contentMD5:PutObjectRetention' :: Maybe Text
contentMD5 = forall a. Maybe a
Prelude.Nothing,
      $sel:expectedBucketOwner:PutObjectRetention' :: Maybe Text
expectedBucketOwner = forall a. Maybe a
Prelude.Nothing,
      $sel:requestPayer:PutObjectRetention' :: Maybe RequestPayer
requestPayer = forall a. Maybe a
Prelude.Nothing,
      $sel:retention:PutObjectRetention' :: Maybe ObjectLockRetention
retention = forall a. Maybe a
Prelude.Nothing,
      $sel:versionId:PutObjectRetention' :: Maybe ObjectVersionId
versionId = forall a. Maybe a
Prelude.Nothing,
      $sel:bucket:PutObjectRetention' :: BucketName
bucket = BucketName
pBucket_,
      $sel:key:PutObjectRetention' :: ObjectKey
key = ObjectKey
pKey_
    }

-- | Indicates whether this action should bypass Governance-mode
-- restrictions.
putObjectRetention_bypassGovernanceRetention :: Lens.Lens' PutObjectRetention (Prelude.Maybe Prelude.Bool)
putObjectRetention_bypassGovernanceRetention :: Lens' PutObjectRetention (Maybe Bool)
putObjectRetention_bypassGovernanceRetention = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\PutObjectRetention' {Maybe Bool
bypassGovernanceRetention :: Maybe Bool
$sel:bypassGovernanceRetention:PutObjectRetention' :: PutObjectRetention -> Maybe Bool
bypassGovernanceRetention} -> Maybe Bool
bypassGovernanceRetention) (\s :: PutObjectRetention
s@PutObjectRetention' {} Maybe Bool
a -> PutObjectRetention
s {$sel:bypassGovernanceRetention:PutObjectRetention' :: Maybe Bool
bypassGovernanceRetention = Maybe Bool
a} :: PutObjectRetention)

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

-- | The MD5 hash for the request body.
--
-- For requests made using the Amazon Web Services Command Line Interface
-- (CLI) or Amazon Web Services SDKs, this field is calculated
-- automatically.
putObjectRetention_contentMD5 :: Lens.Lens' PutObjectRetention (Prelude.Maybe Prelude.Text)
putObjectRetention_contentMD5 :: Lens' PutObjectRetention (Maybe Text)
putObjectRetention_contentMD5 = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\PutObjectRetention' {Maybe Text
contentMD5 :: Maybe Text
$sel:contentMD5:PutObjectRetention' :: PutObjectRetention -> Maybe Text
contentMD5} -> Maybe Text
contentMD5) (\s :: PutObjectRetention
s@PutObjectRetention' {} Maybe Text
a -> PutObjectRetention
s {$sel:contentMD5:PutObjectRetention' :: Maybe Text
contentMD5 = Maybe Text
a} :: PutObjectRetention)

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

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

-- | The container element for the Object Retention configuration.
putObjectRetention_retention :: Lens.Lens' PutObjectRetention (Prelude.Maybe ObjectLockRetention)
putObjectRetention_retention :: Lens' PutObjectRetention (Maybe ObjectLockRetention)
putObjectRetention_retention = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\PutObjectRetention' {Maybe ObjectLockRetention
retention :: Maybe ObjectLockRetention
$sel:retention:PutObjectRetention' :: PutObjectRetention -> Maybe ObjectLockRetention
retention} -> Maybe ObjectLockRetention
retention) (\s :: PutObjectRetention
s@PutObjectRetention' {} Maybe ObjectLockRetention
a -> PutObjectRetention
s {$sel:retention:PutObjectRetention' :: Maybe ObjectLockRetention
retention = Maybe ObjectLockRetention
a} :: PutObjectRetention)

-- | The version ID for the object that you want to apply this Object
-- Retention configuration to.
putObjectRetention_versionId :: Lens.Lens' PutObjectRetention (Prelude.Maybe ObjectVersionId)
putObjectRetention_versionId :: Lens' PutObjectRetention (Maybe ObjectVersionId)
putObjectRetention_versionId = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\PutObjectRetention' {Maybe ObjectVersionId
versionId :: Maybe ObjectVersionId
$sel:versionId:PutObjectRetention' :: PutObjectRetention -> Maybe ObjectVersionId
versionId} -> Maybe ObjectVersionId
versionId) (\s :: PutObjectRetention
s@PutObjectRetention' {} Maybe ObjectVersionId
a -> PutObjectRetention
s {$sel:versionId:PutObjectRetention' :: Maybe ObjectVersionId
versionId = Maybe ObjectVersionId
a} :: PutObjectRetention)

-- | The bucket name that contains the object you want to apply this Object
-- Retention configuration to.
--
-- 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/.
putObjectRetention_bucket :: Lens.Lens' PutObjectRetention BucketName
putObjectRetention_bucket :: Lens' PutObjectRetention BucketName
putObjectRetention_bucket = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\PutObjectRetention' {BucketName
bucket :: BucketName
$sel:bucket:PutObjectRetention' :: PutObjectRetention -> BucketName
bucket} -> BucketName
bucket) (\s :: PutObjectRetention
s@PutObjectRetention' {} BucketName
a -> PutObjectRetention
s {$sel:bucket:PutObjectRetention' :: BucketName
bucket = BucketName
a} :: PutObjectRetention)

-- | The key name for the object that you want to apply this Object Retention
-- configuration to.
putObjectRetention_key :: Lens.Lens' PutObjectRetention ObjectKey
putObjectRetention_key :: Lens' PutObjectRetention ObjectKey
putObjectRetention_key = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\PutObjectRetention' {ObjectKey
key :: ObjectKey
$sel:key:PutObjectRetention' :: PutObjectRetention -> ObjectKey
key} -> ObjectKey
key) (\s :: PutObjectRetention
s@PutObjectRetention' {} ObjectKey
a -> PutObjectRetention
s {$sel:key:PutObjectRetention' :: ObjectKey
key = ObjectKey
a} :: PutObjectRetention)

instance Core.AWSRequest PutObjectRetention where
  type
    AWSResponse PutObjectRetention =
      PutObjectRetentionResponse
  request :: (Service -> Service)
-> PutObjectRetention -> Request PutObjectRetention
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 PutObjectRetention
-> ClientResponse ClientBody
-> m (Either
        Error (ClientResponse (AWSResponse PutObjectRetention)))
response =
    forall (m :: * -> *) a.
MonadResource m =>
(Int -> ResponseHeaders -> () -> Either String (AWSResponse a))
-> (ByteStringLazy -> IO ByteStringLazy)
-> Service
-> Proxy a
-> ClientResponse ClientBody
-> m (Either Error (ClientResponse (AWSResponse a)))
Response.receiveEmpty
      ( \Int
s ResponseHeaders
h ()
x ->
          Maybe RequestCharged -> Int -> PutObjectRetentionResponse
PutObjectRetentionResponse'
            forall (f :: * -> *) a b. Functor 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 PutObjectRetention where
  hashWithSalt :: Int -> PutObjectRetention -> Int
hashWithSalt Int
_salt PutObjectRetention' {Maybe Bool
Maybe Text
Maybe ObjectVersionId
Maybe ChecksumAlgorithm
Maybe ObjectLockRetention
Maybe RequestPayer
ObjectKey
BucketName
key :: ObjectKey
bucket :: BucketName
versionId :: Maybe ObjectVersionId
retention :: Maybe ObjectLockRetention
requestPayer :: Maybe RequestPayer
expectedBucketOwner :: Maybe Text
contentMD5 :: Maybe Text
checksumAlgorithm :: Maybe ChecksumAlgorithm
bypassGovernanceRetention :: Maybe Bool
$sel:key:PutObjectRetention' :: PutObjectRetention -> ObjectKey
$sel:bucket:PutObjectRetention' :: PutObjectRetention -> BucketName
$sel:versionId:PutObjectRetention' :: PutObjectRetention -> Maybe ObjectVersionId
$sel:retention:PutObjectRetention' :: PutObjectRetention -> Maybe ObjectLockRetention
$sel:requestPayer:PutObjectRetention' :: PutObjectRetention -> Maybe RequestPayer
$sel:expectedBucketOwner:PutObjectRetention' :: PutObjectRetention -> Maybe Text
$sel:contentMD5:PutObjectRetention' :: PutObjectRetention -> Maybe Text
$sel:checksumAlgorithm:PutObjectRetention' :: PutObjectRetention -> Maybe ChecksumAlgorithm
$sel:bypassGovernanceRetention:PutObjectRetention' :: PutObjectRetention -> 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
contentMD5
      forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Maybe Text
expectedBucketOwner
      forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Maybe RequestPayer
requestPayer
      forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Maybe ObjectLockRetention
retention
      forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Maybe ObjectVersionId
versionId
      forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` BucketName
bucket
      forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` ObjectKey
key

instance Prelude.NFData PutObjectRetention where
  rnf :: PutObjectRetention -> ()
rnf PutObjectRetention' {Maybe Bool
Maybe Text
Maybe ObjectVersionId
Maybe ChecksumAlgorithm
Maybe ObjectLockRetention
Maybe RequestPayer
ObjectKey
BucketName
key :: ObjectKey
bucket :: BucketName
versionId :: Maybe ObjectVersionId
retention :: Maybe ObjectLockRetention
requestPayer :: Maybe RequestPayer
expectedBucketOwner :: Maybe Text
contentMD5 :: Maybe Text
checksumAlgorithm :: Maybe ChecksumAlgorithm
bypassGovernanceRetention :: Maybe Bool
$sel:key:PutObjectRetention' :: PutObjectRetention -> ObjectKey
$sel:bucket:PutObjectRetention' :: PutObjectRetention -> BucketName
$sel:versionId:PutObjectRetention' :: PutObjectRetention -> Maybe ObjectVersionId
$sel:retention:PutObjectRetention' :: PutObjectRetention -> Maybe ObjectLockRetention
$sel:requestPayer:PutObjectRetention' :: PutObjectRetention -> Maybe RequestPayer
$sel:expectedBucketOwner:PutObjectRetention' :: PutObjectRetention -> Maybe Text
$sel:contentMD5:PutObjectRetention' :: PutObjectRetention -> Maybe Text
$sel:checksumAlgorithm:PutObjectRetention' :: PutObjectRetention -> Maybe ChecksumAlgorithm
$sel:bypassGovernanceRetention:PutObjectRetention' :: PutObjectRetention -> 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
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 RequestPayer
requestPayer
      seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf Maybe ObjectLockRetention
retention
      seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf Maybe ObjectVersionId
versionId
      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 ObjectKey
key

instance Data.ToElement PutObjectRetention where
  toElement :: PutObjectRetention -> Element
toElement PutObjectRetention' {Maybe Bool
Maybe Text
Maybe ObjectVersionId
Maybe ChecksumAlgorithm
Maybe ObjectLockRetention
Maybe RequestPayer
ObjectKey
BucketName
key :: ObjectKey
bucket :: BucketName
versionId :: Maybe ObjectVersionId
retention :: Maybe ObjectLockRetention
requestPayer :: Maybe RequestPayer
expectedBucketOwner :: Maybe Text
contentMD5 :: Maybe Text
checksumAlgorithm :: Maybe ChecksumAlgorithm
bypassGovernanceRetention :: Maybe Bool
$sel:key:PutObjectRetention' :: PutObjectRetention -> ObjectKey
$sel:bucket:PutObjectRetention' :: PutObjectRetention -> BucketName
$sel:versionId:PutObjectRetention' :: PutObjectRetention -> Maybe ObjectVersionId
$sel:retention:PutObjectRetention' :: PutObjectRetention -> Maybe ObjectLockRetention
$sel:requestPayer:PutObjectRetention' :: PutObjectRetention -> Maybe RequestPayer
$sel:expectedBucketOwner:PutObjectRetention' :: PutObjectRetention -> Maybe Text
$sel:contentMD5:PutObjectRetention' :: PutObjectRetention -> Maybe Text
$sel:checksumAlgorithm:PutObjectRetention' :: PutObjectRetention -> Maybe ChecksumAlgorithm
$sel:bypassGovernanceRetention:PutObjectRetention' :: PutObjectRetention -> Maybe Bool
..} =
    forall a. ToXML a => Name -> a -> Element
Data.mkElement
      Name
"{http://s3.amazonaws.com/doc/2006-03-01/}Retention"
      Maybe ObjectLockRetention
retention

instance Data.ToHeaders PutObjectRetention where
  toHeaders :: PutObjectRetention -> ResponseHeaders
toHeaders PutObjectRetention' {Maybe Bool
Maybe Text
Maybe ObjectVersionId
Maybe ChecksumAlgorithm
Maybe ObjectLockRetention
Maybe RequestPayer
ObjectKey
BucketName
key :: ObjectKey
bucket :: BucketName
versionId :: Maybe ObjectVersionId
retention :: Maybe ObjectLockRetention
requestPayer :: Maybe RequestPayer
expectedBucketOwner :: Maybe Text
contentMD5 :: Maybe Text
checksumAlgorithm :: Maybe ChecksumAlgorithm
bypassGovernanceRetention :: Maybe Bool
$sel:key:PutObjectRetention' :: PutObjectRetention -> ObjectKey
$sel:bucket:PutObjectRetention' :: PutObjectRetention -> BucketName
$sel:versionId:PutObjectRetention' :: PutObjectRetention -> Maybe ObjectVersionId
$sel:retention:PutObjectRetention' :: PutObjectRetention -> Maybe ObjectLockRetention
$sel:requestPayer:PutObjectRetention' :: PutObjectRetention -> Maybe RequestPayer
$sel:expectedBucketOwner:PutObjectRetention' :: PutObjectRetention -> Maybe Text
$sel:contentMD5:PutObjectRetention' :: PutObjectRetention -> Maybe Text
$sel:checksumAlgorithm:PutObjectRetention' :: PutObjectRetention -> Maybe ChecksumAlgorithm
$sel:bypassGovernanceRetention:PutObjectRetention' :: PutObjectRetention -> 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
"Content-MD5" forall a. ToHeader a => HeaderName -> a -> ResponseHeaders
Data.=# Maybe Text
contentMD5,
        HeaderName
"x-amz-expected-bucket-owner"
          forall a. ToHeader a => HeaderName -> a -> ResponseHeaders
Data.=# Maybe Text
expectedBucketOwner,
        HeaderName
"x-amz-request-payer" forall a. ToHeader a => HeaderName -> a -> ResponseHeaders
Data.=# Maybe RequestPayer
requestPayer
      ]

instance Data.ToPath PutObjectRetention where
  toPath :: PutObjectRetention -> ByteString
toPath PutObjectRetention' {Maybe Bool
Maybe Text
Maybe ObjectVersionId
Maybe ChecksumAlgorithm
Maybe ObjectLockRetention
Maybe RequestPayer
ObjectKey
BucketName
key :: ObjectKey
bucket :: BucketName
versionId :: Maybe ObjectVersionId
retention :: Maybe ObjectLockRetention
requestPayer :: Maybe RequestPayer
expectedBucketOwner :: Maybe Text
contentMD5 :: Maybe Text
checksumAlgorithm :: Maybe ChecksumAlgorithm
bypassGovernanceRetention :: Maybe Bool
$sel:key:PutObjectRetention' :: PutObjectRetention -> ObjectKey
$sel:bucket:PutObjectRetention' :: PutObjectRetention -> BucketName
$sel:versionId:PutObjectRetention' :: PutObjectRetention -> Maybe ObjectVersionId
$sel:retention:PutObjectRetention' :: PutObjectRetention -> Maybe ObjectLockRetention
$sel:requestPayer:PutObjectRetention' :: PutObjectRetention -> Maybe RequestPayer
$sel:expectedBucketOwner:PutObjectRetention' :: PutObjectRetention -> Maybe Text
$sel:contentMD5:PutObjectRetention' :: PutObjectRetention -> Maybe Text
$sel:checksumAlgorithm:PutObjectRetention' :: PutObjectRetention -> Maybe ChecksumAlgorithm
$sel:bypassGovernanceRetention:PutObjectRetention' :: PutObjectRetention -> Maybe Bool
..} =
    forall a. Monoid a => [a] -> a
Prelude.mconcat
      [ByteString
"/", forall a. ToByteString a => a -> ByteString
Data.toBS BucketName
bucket, ByteString
"/", forall a. ToByteString a => a -> ByteString
Data.toBS ObjectKey
key]

instance Data.ToQuery PutObjectRetention where
  toQuery :: PutObjectRetention -> QueryString
toQuery PutObjectRetention' {Maybe Bool
Maybe Text
Maybe ObjectVersionId
Maybe ChecksumAlgorithm
Maybe ObjectLockRetention
Maybe RequestPayer
ObjectKey
BucketName
key :: ObjectKey
bucket :: BucketName
versionId :: Maybe ObjectVersionId
retention :: Maybe ObjectLockRetention
requestPayer :: Maybe RequestPayer
expectedBucketOwner :: Maybe Text
contentMD5 :: Maybe Text
checksumAlgorithm :: Maybe ChecksumAlgorithm
bypassGovernanceRetention :: Maybe Bool
$sel:key:PutObjectRetention' :: PutObjectRetention -> ObjectKey
$sel:bucket:PutObjectRetention' :: PutObjectRetention -> BucketName
$sel:versionId:PutObjectRetention' :: PutObjectRetention -> Maybe ObjectVersionId
$sel:retention:PutObjectRetention' :: PutObjectRetention -> Maybe ObjectLockRetention
$sel:requestPayer:PutObjectRetention' :: PutObjectRetention -> Maybe RequestPayer
$sel:expectedBucketOwner:PutObjectRetention' :: PutObjectRetention -> Maybe Text
$sel:contentMD5:PutObjectRetention' :: PutObjectRetention -> Maybe Text
$sel:checksumAlgorithm:PutObjectRetention' :: PutObjectRetention -> Maybe ChecksumAlgorithm
$sel:bypassGovernanceRetention:PutObjectRetention' :: PutObjectRetention -> Maybe Bool
..} =
    forall a. Monoid a => [a] -> a
Prelude.mconcat
      [ByteString
"versionId" forall a. ToQuery a => ByteString -> a -> QueryString
Data.=: Maybe ObjectVersionId
versionId, QueryString
"retention"]

-- | /See:/ 'newPutObjectRetentionResponse' smart constructor.
data PutObjectRetentionResponse = PutObjectRetentionResponse'
  { PutObjectRetentionResponse -> Maybe RequestCharged
requestCharged :: Prelude.Maybe RequestCharged,
    -- | The response's http status code.
    PutObjectRetentionResponse -> Int
httpStatus :: Prelude.Int
  }
  deriving (PutObjectRetentionResponse -> PutObjectRetentionResponse -> Bool
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: PutObjectRetentionResponse -> PutObjectRetentionResponse -> Bool
$c/= :: PutObjectRetentionResponse -> PutObjectRetentionResponse -> Bool
== :: PutObjectRetentionResponse -> PutObjectRetentionResponse -> Bool
$c== :: PutObjectRetentionResponse -> PutObjectRetentionResponse -> Bool
Prelude.Eq, ReadPrec [PutObjectRetentionResponse]
ReadPrec PutObjectRetentionResponse
Int -> ReadS PutObjectRetentionResponse
ReadS [PutObjectRetentionResponse]
forall a.
(Int -> ReadS a)
-> ReadS [a] -> ReadPrec a -> ReadPrec [a] -> Read a
readListPrec :: ReadPrec [PutObjectRetentionResponse]
$creadListPrec :: ReadPrec [PutObjectRetentionResponse]
readPrec :: ReadPrec PutObjectRetentionResponse
$creadPrec :: ReadPrec PutObjectRetentionResponse
readList :: ReadS [PutObjectRetentionResponse]
$creadList :: ReadS [PutObjectRetentionResponse]
readsPrec :: Int -> ReadS PutObjectRetentionResponse
$creadsPrec :: Int -> ReadS PutObjectRetentionResponse
Prelude.Read, Int -> PutObjectRetentionResponse -> ShowS
[PutObjectRetentionResponse] -> ShowS
PutObjectRetentionResponse -> String
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [PutObjectRetentionResponse] -> ShowS
$cshowList :: [PutObjectRetentionResponse] -> ShowS
show :: PutObjectRetentionResponse -> String
$cshow :: PutObjectRetentionResponse -> String
showsPrec :: Int -> PutObjectRetentionResponse -> ShowS
$cshowsPrec :: Int -> PutObjectRetentionResponse -> ShowS
Prelude.Show, forall x.
Rep PutObjectRetentionResponse x -> PutObjectRetentionResponse
forall x.
PutObjectRetentionResponse -> Rep PutObjectRetentionResponse x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cto :: forall x.
Rep PutObjectRetentionResponse x -> PutObjectRetentionResponse
$cfrom :: forall x.
PutObjectRetentionResponse -> Rep PutObjectRetentionResponse x
Prelude.Generic)

-- |
-- Create a value of 'PutObjectRetentionResponse' 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:
--
-- 'requestCharged', 'putObjectRetentionResponse_requestCharged' - Undocumented member.
--
-- 'httpStatus', 'putObjectRetentionResponse_httpStatus' - The response's http status code.
newPutObjectRetentionResponse ::
  -- | 'httpStatus'
  Prelude.Int ->
  PutObjectRetentionResponse
newPutObjectRetentionResponse :: Int -> PutObjectRetentionResponse
newPutObjectRetentionResponse Int
pHttpStatus_ =
  PutObjectRetentionResponse'
    { $sel:requestCharged:PutObjectRetentionResponse' :: Maybe RequestCharged
requestCharged =
        forall a. Maybe a
Prelude.Nothing,
      $sel:httpStatus:PutObjectRetentionResponse' :: Int
httpStatus = Int
pHttpStatus_
    }

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

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

instance Prelude.NFData PutObjectRetentionResponse where
  rnf :: PutObjectRetentionResponse -> ()
rnf PutObjectRetentionResponse' {Int
Maybe RequestCharged
httpStatus :: Int
requestCharged :: Maybe RequestCharged
$sel:httpStatus:PutObjectRetentionResponse' :: PutObjectRetentionResponse -> Int
$sel:requestCharged:PutObjectRetentionResponse' :: PutObjectRetentionResponse -> Maybe RequestCharged
..} =
    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