{-# 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 #-}
module Amazonka.S3.CopyObject
  ( 
    CopyObject (..),
    newCopyObject,
    
    copyObject_acl,
    copyObject_bucketKeyEnabled,
    copyObject_cacheControl,
    copyObject_checksumAlgorithm,
    copyObject_contentDisposition,
    copyObject_contentEncoding,
    copyObject_contentLanguage,
    copyObject_contentType,
    copyObject_copySourceIfMatch,
    copyObject_copySourceIfModifiedSince,
    copyObject_copySourceIfNoneMatch,
    copyObject_copySourceIfUnmodifiedSince,
    copyObject_copySourceSSECustomerAlgorithm,
    copyObject_copySourceSSECustomerKey,
    copyObject_copySourceSSECustomerKeyMD5,
    copyObject_expectedBucketOwner,
    copyObject_expectedSourceBucketOwner,
    copyObject_expires,
    copyObject_grantFullControl,
    copyObject_grantRead,
    copyObject_grantReadACP,
    copyObject_grantWriteACP,
    copyObject_metadata,
    copyObject_metadataDirective,
    copyObject_objectLockLegalHoldStatus,
    copyObject_objectLockMode,
    copyObject_objectLockRetainUntilDate,
    copyObject_requestPayer,
    copyObject_sSECustomerAlgorithm,
    copyObject_sSECustomerKey,
    copyObject_sSECustomerKeyMD5,
    copyObject_sSEKMSEncryptionContext,
    copyObject_sSEKMSKeyId,
    copyObject_serverSideEncryption,
    copyObject_storageClass,
    copyObject_tagging,
    copyObject_taggingDirective,
    copyObject_websiteRedirectLocation,
    copyObject_bucket,
    copyObject_copySource,
    copyObject_key,
    
    CopyObjectResponse (..),
    newCopyObjectResponse,
    
    copyObjectResponse_bucketKeyEnabled,
    copyObjectResponse_copyObjectResult,
    copyObjectResponse_copySourceVersionId,
    copyObjectResponse_expiration,
    copyObjectResponse_requestCharged,
    copyObjectResponse_sSECustomerAlgorithm,
    copyObjectResponse_sSECustomerKeyMD5,
    copyObjectResponse_sSEKMSEncryptionContext,
    copyObjectResponse_sSEKMSKeyId,
    copyObjectResponse_serverSideEncryption,
    copyObjectResponse_versionId,
    copyObjectResponse_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
data CopyObject = CopyObject'
  { 
    
    
    CopyObject -> Maybe ObjectCannedACL
acl :: Prelude.Maybe ObjectCannedACL,
    
    
    
    
    
    
    
    CopyObject -> Maybe Bool
bucketKeyEnabled :: Prelude.Maybe Prelude.Bool,
    
    CopyObject -> Maybe Text
cacheControl :: Prelude.Maybe Prelude.Text,
    
    
    
    
    CopyObject -> Maybe ChecksumAlgorithm
checksumAlgorithm :: Prelude.Maybe ChecksumAlgorithm,
    
    CopyObject -> Maybe Text
contentDisposition :: Prelude.Maybe Prelude.Text,
    
    
    
    CopyObject -> Maybe Text
contentEncoding :: Prelude.Maybe Prelude.Text,
    
    CopyObject -> Maybe Text
contentLanguage :: Prelude.Maybe Prelude.Text,
    
    CopyObject -> Maybe Text
contentType :: Prelude.Maybe Prelude.Text,
    
    CopyObject -> Maybe Text
copySourceIfMatch :: Prelude.Maybe Prelude.Text,
    
    CopyObject -> Maybe RFC822
copySourceIfModifiedSince :: Prelude.Maybe Data.RFC822,
    
    
    CopyObject -> Maybe Text
copySourceIfNoneMatch :: Prelude.Maybe Prelude.Text,
    
    CopyObject -> Maybe RFC822
copySourceIfUnmodifiedSince :: Prelude.Maybe Data.RFC822,
    
    
    CopyObject -> Maybe Text
copySourceSSECustomerAlgorithm :: Prelude.Maybe Prelude.Text,
    
    
    
    CopyObject -> Maybe (Sensitive Text)
copySourceSSECustomerKey :: Prelude.Maybe (Data.Sensitive Prelude.Text),
    
    
    
    CopyObject -> Maybe Text
copySourceSSECustomerKeyMD5 :: Prelude.Maybe Prelude.Text,
    
    
    
    CopyObject -> Maybe Text
expectedBucketOwner :: Prelude.Maybe Prelude.Text,
    
    
    
    CopyObject -> Maybe Text
expectedSourceBucketOwner :: Prelude.Maybe Prelude.Text,
    
    CopyObject -> Maybe RFC822
expires :: Prelude.Maybe Data.RFC822,
    
    
    
    
    CopyObject -> Maybe Text
grantFullControl :: Prelude.Maybe Prelude.Text,
    
    
    
    CopyObject -> Maybe Text
grantRead :: Prelude.Maybe Prelude.Text,
    
    
    
    CopyObject -> Maybe Text
grantReadACP :: Prelude.Maybe Prelude.Text,
    
    
    
    CopyObject -> Maybe Text
grantWriteACP :: Prelude.Maybe Prelude.Text,
    
    CopyObject -> HashMap Text Text
metadata :: Prelude.HashMap Prelude.Text Prelude.Text,
    
    
    CopyObject -> Maybe MetadataDirective
metadataDirective :: Prelude.Maybe MetadataDirective,
    
    CopyObject -> Maybe ObjectLockLegalHoldStatus
objectLockLegalHoldStatus :: Prelude.Maybe ObjectLockLegalHoldStatus,
    
    CopyObject -> Maybe ObjectLockMode
objectLockMode :: Prelude.Maybe ObjectLockMode,
    
    
    CopyObject -> Maybe ISO8601
objectLockRetainUntilDate :: Prelude.Maybe Data.ISO8601,
    CopyObject -> Maybe RequestPayer
requestPayer :: Prelude.Maybe RequestPayer,
    
    
    CopyObject -> Maybe Text
sSECustomerAlgorithm :: Prelude.Maybe Prelude.Text,
    
    
    
    
    
    CopyObject -> Maybe (Sensitive Text)
sSECustomerKey :: Prelude.Maybe (Data.Sensitive Prelude.Text),
    
    
    
    CopyObject -> Maybe Text
sSECustomerKeyMD5 :: Prelude.Maybe Prelude.Text,
    
    
    
    CopyObject -> Maybe (Sensitive Text)
sSEKMSEncryptionContext :: Prelude.Maybe (Data.Sensitive Prelude.Text),
    
    
    
    
    
    
    
    CopyObject -> Maybe (Sensitive Text)
sSEKMSKeyId :: Prelude.Maybe (Data.Sensitive Prelude.Text),
    
    
    CopyObject -> Maybe ServerSideEncryption
serverSideEncryption :: Prelude.Maybe ServerSideEncryption,
    
    
    
    
    
    
    
    CopyObject -> Maybe StorageClass
storageClass :: Prelude.Maybe StorageClass,
    
    
    
    CopyObject -> Maybe Text
tagging :: Prelude.Maybe Prelude.Text,
    
    
    CopyObject -> Maybe TaggingDirective
taggingDirective :: Prelude.Maybe TaggingDirective,
    
    
    
    CopyObject -> Maybe Text
websiteRedirectLocation :: Prelude.Maybe Prelude.Text,
    
    
    
    
    
    
    
    
    
    
    
    
    
    
    
    
    
    
    
    
    CopyObject -> BucketName
bucket :: BucketName,
    
    
    
    
    
    
    
    
    
    
    
    
    
    
    
    
    
    
    
    
    
    
    
    
    
    
    
    
    
    
    
    
    
    
    
    
    
    
    
    
    CopyObject -> Text
copySource :: Prelude.Text,
    
    CopyObject -> ObjectKey
key :: ObjectKey
  }
  deriving (CopyObject -> CopyObject -> Bool
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: CopyObject -> CopyObject -> Bool
$c/= :: CopyObject -> CopyObject -> Bool
== :: CopyObject -> CopyObject -> Bool
$c== :: CopyObject -> CopyObject -> Bool
Prelude.Eq, Int -> CopyObject -> ShowS
[CopyObject] -> ShowS
CopyObject -> String
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [CopyObject] -> ShowS
$cshowList :: [CopyObject] -> ShowS
show :: CopyObject -> String
$cshow :: CopyObject -> String
showsPrec :: Int -> CopyObject -> ShowS
$cshowsPrec :: Int -> CopyObject -> ShowS
Prelude.Show, forall x. Rep CopyObject x -> CopyObject
forall x. CopyObject -> Rep CopyObject x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cto :: forall x. Rep CopyObject x -> CopyObject
$cfrom :: forall x. CopyObject -> Rep CopyObject x
Prelude.Generic)
newCopyObject ::
  
  BucketName ->
  
  Prelude.Text ->
  
  ObjectKey ->
  CopyObject
newCopyObject :: BucketName -> Text -> ObjectKey -> CopyObject
newCopyObject BucketName
pBucket_ Text
pCopySource_ ObjectKey
pKey_ =
  CopyObject'
    { $sel:acl:CopyObject' :: Maybe ObjectCannedACL
acl = forall a. Maybe a
Prelude.Nothing,
      $sel:bucketKeyEnabled:CopyObject' :: Maybe Bool
bucketKeyEnabled = forall a. Maybe a
Prelude.Nothing,
      $sel:cacheControl:CopyObject' :: Maybe Text
cacheControl = forall a. Maybe a
Prelude.Nothing,
      $sel:checksumAlgorithm:CopyObject' :: Maybe ChecksumAlgorithm
checksumAlgorithm = forall a. Maybe a
Prelude.Nothing,
      $sel:contentDisposition:CopyObject' :: Maybe Text
contentDisposition = forall a. Maybe a
Prelude.Nothing,
      $sel:contentEncoding:CopyObject' :: Maybe Text
contentEncoding = forall a. Maybe a
Prelude.Nothing,
      $sel:contentLanguage:CopyObject' :: Maybe Text
contentLanguage = forall a. Maybe a
Prelude.Nothing,
      $sel:contentType:CopyObject' :: Maybe Text
contentType = forall a. Maybe a
Prelude.Nothing,
      $sel:copySourceIfMatch:CopyObject' :: Maybe Text
copySourceIfMatch = forall a. Maybe a
Prelude.Nothing,
      $sel:copySourceIfModifiedSince:CopyObject' :: Maybe RFC822
copySourceIfModifiedSince = forall a. Maybe a
Prelude.Nothing,
      $sel:copySourceIfNoneMatch:CopyObject' :: Maybe Text
copySourceIfNoneMatch = forall a. Maybe a
Prelude.Nothing,
      $sel:copySourceIfUnmodifiedSince:CopyObject' :: Maybe RFC822
copySourceIfUnmodifiedSince = forall a. Maybe a
Prelude.Nothing,
      $sel:copySourceSSECustomerAlgorithm:CopyObject' :: Maybe Text
copySourceSSECustomerAlgorithm = forall a. Maybe a
Prelude.Nothing,
      $sel:copySourceSSECustomerKey:CopyObject' :: Maybe (Sensitive Text)
copySourceSSECustomerKey = forall a. Maybe a
Prelude.Nothing,
      $sel:copySourceSSECustomerKeyMD5:CopyObject' :: Maybe Text
copySourceSSECustomerKeyMD5 = forall a. Maybe a
Prelude.Nothing,
      $sel:expectedBucketOwner:CopyObject' :: Maybe Text
expectedBucketOwner = forall a. Maybe a
Prelude.Nothing,
      $sel:expectedSourceBucketOwner:CopyObject' :: Maybe Text
expectedSourceBucketOwner = forall a. Maybe a
Prelude.Nothing,
      $sel:expires:CopyObject' :: Maybe RFC822
expires = forall a. Maybe a
Prelude.Nothing,
      $sel:grantFullControl:CopyObject' :: Maybe Text
grantFullControl = forall a. Maybe a
Prelude.Nothing,
      $sel:grantRead:CopyObject' :: Maybe Text
grantRead = forall a. Maybe a
Prelude.Nothing,
      $sel:grantReadACP:CopyObject' :: Maybe Text
grantReadACP = forall a. Maybe a
Prelude.Nothing,
      $sel:grantWriteACP:CopyObject' :: Maybe Text
grantWriteACP = forall a. Maybe a
Prelude.Nothing,
      $sel:metadata:CopyObject' :: HashMap Text Text
metadata = forall a. Monoid a => a
Prelude.mempty,
      $sel:metadataDirective:CopyObject' :: Maybe MetadataDirective
metadataDirective = forall a. Maybe a
Prelude.Nothing,
      $sel:objectLockLegalHoldStatus:CopyObject' :: Maybe ObjectLockLegalHoldStatus
objectLockLegalHoldStatus = forall a. Maybe a
Prelude.Nothing,
      $sel:objectLockMode:CopyObject' :: Maybe ObjectLockMode
objectLockMode = forall a. Maybe a
Prelude.Nothing,
      $sel:objectLockRetainUntilDate:CopyObject' :: Maybe ISO8601
objectLockRetainUntilDate = forall a. Maybe a
Prelude.Nothing,
      $sel:requestPayer:CopyObject' :: Maybe RequestPayer
requestPayer = forall a. Maybe a
Prelude.Nothing,
      $sel:sSECustomerAlgorithm:CopyObject' :: Maybe Text
sSECustomerAlgorithm = forall a. Maybe a
Prelude.Nothing,
      $sel:sSECustomerKey:CopyObject' :: Maybe (Sensitive Text)
sSECustomerKey = forall a. Maybe a
Prelude.Nothing,
      $sel:sSECustomerKeyMD5:CopyObject' :: Maybe Text
sSECustomerKeyMD5 = forall a. Maybe a
Prelude.Nothing,
      $sel:sSEKMSEncryptionContext:CopyObject' :: Maybe (Sensitive Text)
sSEKMSEncryptionContext = forall a. Maybe a
Prelude.Nothing,
      $sel:sSEKMSKeyId:CopyObject' :: Maybe (Sensitive Text)
sSEKMSKeyId = forall a. Maybe a
Prelude.Nothing,
      $sel:serverSideEncryption:CopyObject' :: Maybe ServerSideEncryption
serverSideEncryption = forall a. Maybe a
Prelude.Nothing,
      $sel:storageClass:CopyObject' :: Maybe StorageClass
storageClass = forall a. Maybe a
Prelude.Nothing,
      $sel:tagging:CopyObject' :: Maybe Text
tagging = forall a. Maybe a
Prelude.Nothing,
      $sel:taggingDirective:CopyObject' :: Maybe TaggingDirective
taggingDirective = forall a. Maybe a
Prelude.Nothing,
      $sel:websiteRedirectLocation:CopyObject' :: Maybe Text
websiteRedirectLocation = forall a. Maybe a
Prelude.Nothing,
      $sel:bucket:CopyObject' :: BucketName
bucket = BucketName
pBucket_,
      $sel:copySource:CopyObject' :: Text
copySource = Text
pCopySource_,
      $sel:key:CopyObject' :: ObjectKey
key = ObjectKey
pKey_
    }
copyObject_acl :: Lens.Lens' CopyObject (Prelude.Maybe ObjectCannedACL)
copyObject_acl :: Lens' CopyObject (Maybe ObjectCannedACL)
copyObject_acl = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\CopyObject' {Maybe ObjectCannedACL
acl :: Maybe ObjectCannedACL
$sel:acl:CopyObject' :: CopyObject -> Maybe ObjectCannedACL
acl} -> Maybe ObjectCannedACL
acl) (\s :: CopyObject
s@CopyObject' {} Maybe ObjectCannedACL
a -> CopyObject
s {$sel:acl:CopyObject' :: Maybe ObjectCannedACL
acl = Maybe ObjectCannedACL
a} :: CopyObject)
copyObject_bucketKeyEnabled :: Lens.Lens' CopyObject (Prelude.Maybe Prelude.Bool)
copyObject_bucketKeyEnabled :: Lens' CopyObject (Maybe Bool)
copyObject_bucketKeyEnabled = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\CopyObject' {Maybe Bool
bucketKeyEnabled :: Maybe Bool
$sel:bucketKeyEnabled:CopyObject' :: CopyObject -> Maybe Bool
bucketKeyEnabled} -> Maybe Bool
bucketKeyEnabled) (\s :: CopyObject
s@CopyObject' {} Maybe Bool
a -> CopyObject
s {$sel:bucketKeyEnabled:CopyObject' :: Maybe Bool
bucketKeyEnabled = Maybe Bool
a} :: CopyObject)
copyObject_cacheControl :: Lens.Lens' CopyObject (Prelude.Maybe Prelude.Text)
copyObject_cacheControl :: Lens' CopyObject (Maybe Text)
copyObject_cacheControl = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\CopyObject' {Maybe Text
cacheControl :: Maybe Text
$sel:cacheControl:CopyObject' :: CopyObject -> Maybe Text
cacheControl} -> Maybe Text
cacheControl) (\s :: CopyObject
s@CopyObject' {} Maybe Text
a -> CopyObject
s {$sel:cacheControl:CopyObject' :: Maybe Text
cacheControl = Maybe Text
a} :: CopyObject)
copyObject_checksumAlgorithm :: Lens.Lens' CopyObject (Prelude.Maybe ChecksumAlgorithm)
copyObject_checksumAlgorithm :: Lens' CopyObject (Maybe ChecksumAlgorithm)
copyObject_checksumAlgorithm = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\CopyObject' {Maybe ChecksumAlgorithm
checksumAlgorithm :: Maybe ChecksumAlgorithm
$sel:checksumAlgorithm:CopyObject' :: CopyObject -> Maybe ChecksumAlgorithm
checksumAlgorithm} -> Maybe ChecksumAlgorithm
checksumAlgorithm) (\s :: CopyObject
s@CopyObject' {} Maybe ChecksumAlgorithm
a -> CopyObject
s {$sel:checksumAlgorithm:CopyObject' :: Maybe ChecksumAlgorithm
checksumAlgorithm = Maybe ChecksumAlgorithm
a} :: CopyObject)
copyObject_contentDisposition :: Lens.Lens' CopyObject (Prelude.Maybe Prelude.Text)
copyObject_contentDisposition :: Lens' CopyObject (Maybe Text)
copyObject_contentDisposition = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\CopyObject' {Maybe Text
contentDisposition :: Maybe Text
$sel:contentDisposition:CopyObject' :: CopyObject -> Maybe Text
contentDisposition} -> Maybe Text
contentDisposition) (\s :: CopyObject
s@CopyObject' {} Maybe Text
a -> CopyObject
s {$sel:contentDisposition:CopyObject' :: Maybe Text
contentDisposition = Maybe Text
a} :: CopyObject)
copyObject_contentEncoding :: Lens.Lens' CopyObject (Prelude.Maybe Prelude.Text)
copyObject_contentEncoding :: Lens' CopyObject (Maybe Text)
copyObject_contentEncoding = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\CopyObject' {Maybe Text
contentEncoding :: Maybe Text
$sel:contentEncoding:CopyObject' :: CopyObject -> Maybe Text
contentEncoding} -> Maybe Text
contentEncoding) (\s :: CopyObject
s@CopyObject' {} Maybe Text
a -> CopyObject
s {$sel:contentEncoding:CopyObject' :: Maybe Text
contentEncoding = Maybe Text
a} :: CopyObject)
copyObject_contentLanguage :: Lens.Lens' CopyObject (Prelude.Maybe Prelude.Text)
copyObject_contentLanguage :: Lens' CopyObject (Maybe Text)
copyObject_contentLanguage = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\CopyObject' {Maybe Text
contentLanguage :: Maybe Text
$sel:contentLanguage:CopyObject' :: CopyObject -> Maybe Text
contentLanguage} -> Maybe Text
contentLanguage) (\s :: CopyObject
s@CopyObject' {} Maybe Text
a -> CopyObject
s {$sel:contentLanguage:CopyObject' :: Maybe Text
contentLanguage = Maybe Text
a} :: CopyObject)
copyObject_contentType :: Lens.Lens' CopyObject (Prelude.Maybe Prelude.Text)
copyObject_contentType :: Lens' CopyObject (Maybe Text)
copyObject_contentType = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\CopyObject' {Maybe Text
contentType :: Maybe Text
$sel:contentType:CopyObject' :: CopyObject -> Maybe Text
contentType} -> Maybe Text
contentType) (\s :: CopyObject
s@CopyObject' {} Maybe Text
a -> CopyObject
s {$sel:contentType:CopyObject' :: Maybe Text
contentType = Maybe Text
a} :: CopyObject)
copyObject_copySourceIfMatch :: Lens.Lens' CopyObject (Prelude.Maybe Prelude.Text)
copyObject_copySourceIfMatch :: Lens' CopyObject (Maybe Text)
copyObject_copySourceIfMatch = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\CopyObject' {Maybe Text
copySourceIfMatch :: Maybe Text
$sel:copySourceIfMatch:CopyObject' :: CopyObject -> Maybe Text
copySourceIfMatch} -> Maybe Text
copySourceIfMatch) (\s :: CopyObject
s@CopyObject' {} Maybe Text
a -> CopyObject
s {$sel:copySourceIfMatch:CopyObject' :: Maybe Text
copySourceIfMatch = Maybe Text
a} :: CopyObject)
copyObject_copySourceIfModifiedSince :: Lens.Lens' CopyObject (Prelude.Maybe Prelude.UTCTime)
copyObject_copySourceIfModifiedSince :: Lens' CopyObject (Maybe UTCTime)
copyObject_copySourceIfModifiedSince = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\CopyObject' {Maybe RFC822
copySourceIfModifiedSince :: Maybe RFC822
$sel:copySourceIfModifiedSince:CopyObject' :: CopyObject -> Maybe RFC822
copySourceIfModifiedSince} -> Maybe RFC822
copySourceIfModifiedSince) (\s :: CopyObject
s@CopyObject' {} Maybe RFC822
a -> CopyObject
s {$sel:copySourceIfModifiedSince:CopyObject' :: Maybe RFC822
copySourceIfModifiedSince = Maybe RFC822
a} :: CopyObject) forall b c a. (b -> c) -> (a -> b) -> a -> c
Prelude.. forall (f :: * -> *) (g :: * -> *) s t a b.
(Functor f, Functor g) =>
AnIso s t a b -> Iso (f s) (g t) (f a) (g b)
Lens.mapping forall (a :: Format). Iso' (Time a) UTCTime
Data._Time
copyObject_copySourceIfNoneMatch :: Lens.Lens' CopyObject (Prelude.Maybe Prelude.Text)
copyObject_copySourceIfNoneMatch :: Lens' CopyObject (Maybe Text)
copyObject_copySourceIfNoneMatch = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\CopyObject' {Maybe Text
copySourceIfNoneMatch :: Maybe Text
$sel:copySourceIfNoneMatch:CopyObject' :: CopyObject -> Maybe Text
copySourceIfNoneMatch} -> Maybe Text
copySourceIfNoneMatch) (\s :: CopyObject
s@CopyObject' {} Maybe Text
a -> CopyObject
s {$sel:copySourceIfNoneMatch:CopyObject' :: Maybe Text
copySourceIfNoneMatch = Maybe Text
a} :: CopyObject)
copyObject_copySourceIfUnmodifiedSince :: Lens.Lens' CopyObject (Prelude.Maybe Prelude.UTCTime)
copyObject_copySourceIfUnmodifiedSince :: Lens' CopyObject (Maybe UTCTime)
copyObject_copySourceIfUnmodifiedSince = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\CopyObject' {Maybe RFC822
copySourceIfUnmodifiedSince :: Maybe RFC822
$sel:copySourceIfUnmodifiedSince:CopyObject' :: CopyObject -> Maybe RFC822
copySourceIfUnmodifiedSince} -> Maybe RFC822
copySourceIfUnmodifiedSince) (\s :: CopyObject
s@CopyObject' {} Maybe RFC822
a -> CopyObject
s {$sel:copySourceIfUnmodifiedSince:CopyObject' :: Maybe RFC822
copySourceIfUnmodifiedSince = Maybe RFC822
a} :: CopyObject) forall b c a. (b -> c) -> (a -> b) -> a -> c
Prelude.. forall (f :: * -> *) (g :: * -> *) s t a b.
(Functor f, Functor g) =>
AnIso s t a b -> Iso (f s) (g t) (f a) (g b)
Lens.mapping forall (a :: Format). Iso' (Time a) UTCTime
Data._Time
copyObject_copySourceSSECustomerAlgorithm :: Lens.Lens' CopyObject (Prelude.Maybe Prelude.Text)
copyObject_copySourceSSECustomerAlgorithm :: Lens' CopyObject (Maybe Text)
copyObject_copySourceSSECustomerAlgorithm = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\CopyObject' {Maybe Text
copySourceSSECustomerAlgorithm :: Maybe Text
$sel:copySourceSSECustomerAlgorithm:CopyObject' :: CopyObject -> Maybe Text
copySourceSSECustomerAlgorithm} -> Maybe Text
copySourceSSECustomerAlgorithm) (\s :: CopyObject
s@CopyObject' {} Maybe Text
a -> CopyObject
s {$sel:copySourceSSECustomerAlgorithm:CopyObject' :: Maybe Text
copySourceSSECustomerAlgorithm = Maybe Text
a} :: CopyObject)
copyObject_copySourceSSECustomerKey :: Lens.Lens' CopyObject (Prelude.Maybe Prelude.Text)
copyObject_copySourceSSECustomerKey :: Lens' CopyObject (Maybe Text)
copyObject_copySourceSSECustomerKey = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\CopyObject' {Maybe (Sensitive Text)
copySourceSSECustomerKey :: Maybe (Sensitive Text)
$sel:copySourceSSECustomerKey:CopyObject' :: CopyObject -> Maybe (Sensitive Text)
copySourceSSECustomerKey} -> Maybe (Sensitive Text)
copySourceSSECustomerKey) (\s :: CopyObject
s@CopyObject' {} Maybe (Sensitive Text)
a -> CopyObject
s {$sel:copySourceSSECustomerKey:CopyObject' :: Maybe (Sensitive Text)
copySourceSSECustomerKey = Maybe (Sensitive Text)
a} :: CopyObject) forall b c a. (b -> c) -> (a -> b) -> a -> c
Prelude.. forall (f :: * -> *) (g :: * -> *) s t a b.
(Functor f, Functor g) =>
AnIso s t a b -> Iso (f s) (g t) (f a) (g b)
Lens.mapping forall a. Iso' (Sensitive a) a
Data._Sensitive
copyObject_copySourceSSECustomerKeyMD5 :: Lens.Lens' CopyObject (Prelude.Maybe Prelude.Text)
copyObject_copySourceSSECustomerKeyMD5 :: Lens' CopyObject (Maybe Text)
copyObject_copySourceSSECustomerKeyMD5 = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\CopyObject' {Maybe Text
copySourceSSECustomerKeyMD5 :: Maybe Text
$sel:copySourceSSECustomerKeyMD5:CopyObject' :: CopyObject -> Maybe Text
copySourceSSECustomerKeyMD5} -> Maybe Text
copySourceSSECustomerKeyMD5) (\s :: CopyObject
s@CopyObject' {} Maybe Text
a -> CopyObject
s {$sel:copySourceSSECustomerKeyMD5:CopyObject' :: Maybe Text
copySourceSSECustomerKeyMD5 = Maybe Text
a} :: CopyObject)
copyObject_expectedBucketOwner :: Lens.Lens' CopyObject (Prelude.Maybe Prelude.Text)
copyObject_expectedBucketOwner :: Lens' CopyObject (Maybe Text)
copyObject_expectedBucketOwner = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\CopyObject' {Maybe Text
expectedBucketOwner :: Maybe Text
$sel:expectedBucketOwner:CopyObject' :: CopyObject -> Maybe Text
expectedBucketOwner} -> Maybe Text
expectedBucketOwner) (\s :: CopyObject
s@CopyObject' {} Maybe Text
a -> CopyObject
s {$sel:expectedBucketOwner:CopyObject' :: Maybe Text
expectedBucketOwner = Maybe Text
a} :: CopyObject)
copyObject_expectedSourceBucketOwner :: Lens.Lens' CopyObject (Prelude.Maybe Prelude.Text)
copyObject_expectedSourceBucketOwner :: Lens' CopyObject (Maybe Text)
copyObject_expectedSourceBucketOwner = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\CopyObject' {Maybe Text
expectedSourceBucketOwner :: Maybe Text
$sel:expectedSourceBucketOwner:CopyObject' :: CopyObject -> Maybe Text
expectedSourceBucketOwner} -> Maybe Text
expectedSourceBucketOwner) (\s :: CopyObject
s@CopyObject' {} Maybe Text
a -> CopyObject
s {$sel:expectedSourceBucketOwner:CopyObject' :: Maybe Text
expectedSourceBucketOwner = Maybe Text
a} :: CopyObject)
copyObject_expires :: Lens.Lens' CopyObject (Prelude.Maybe Prelude.UTCTime)
copyObject_expires :: Lens' CopyObject (Maybe UTCTime)
copyObject_expires = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\CopyObject' {Maybe RFC822
expires :: Maybe RFC822
$sel:expires:CopyObject' :: CopyObject -> Maybe RFC822
expires} -> Maybe RFC822
expires) (\s :: CopyObject
s@CopyObject' {} Maybe RFC822
a -> CopyObject
s {$sel:expires:CopyObject' :: Maybe RFC822
expires = Maybe RFC822
a} :: CopyObject) forall b c a. (b -> c) -> (a -> b) -> a -> c
Prelude.. forall (f :: * -> *) (g :: * -> *) s t a b.
(Functor f, Functor g) =>
AnIso s t a b -> Iso (f s) (g t) (f a) (g b)
Lens.mapping forall (a :: Format). Iso' (Time a) UTCTime
Data._Time
copyObject_grantFullControl :: Lens.Lens' CopyObject (Prelude.Maybe Prelude.Text)
copyObject_grantFullControl :: Lens' CopyObject (Maybe Text)
copyObject_grantFullControl = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\CopyObject' {Maybe Text
grantFullControl :: Maybe Text
$sel:grantFullControl:CopyObject' :: CopyObject -> Maybe Text
grantFullControl} -> Maybe Text
grantFullControl) (\s :: CopyObject
s@CopyObject' {} Maybe Text
a -> CopyObject
s {$sel:grantFullControl:CopyObject' :: Maybe Text
grantFullControl = Maybe Text
a} :: CopyObject)
copyObject_grantRead :: Lens.Lens' CopyObject (Prelude.Maybe Prelude.Text)
copyObject_grantRead :: Lens' CopyObject (Maybe Text)
copyObject_grantRead = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\CopyObject' {Maybe Text
grantRead :: Maybe Text
$sel:grantRead:CopyObject' :: CopyObject -> Maybe Text
grantRead} -> Maybe Text
grantRead) (\s :: CopyObject
s@CopyObject' {} Maybe Text
a -> CopyObject
s {$sel:grantRead:CopyObject' :: Maybe Text
grantRead = Maybe Text
a} :: CopyObject)
copyObject_grantReadACP :: Lens.Lens' CopyObject (Prelude.Maybe Prelude.Text)
copyObject_grantReadACP :: Lens' CopyObject (Maybe Text)
copyObject_grantReadACP = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\CopyObject' {Maybe Text
grantReadACP :: Maybe Text
$sel:grantReadACP:CopyObject' :: CopyObject -> Maybe Text
grantReadACP} -> Maybe Text
grantReadACP) (\s :: CopyObject
s@CopyObject' {} Maybe Text
a -> CopyObject
s {$sel:grantReadACP:CopyObject' :: Maybe Text
grantReadACP = Maybe Text
a} :: CopyObject)
copyObject_grantWriteACP :: Lens.Lens' CopyObject (Prelude.Maybe Prelude.Text)
copyObject_grantWriteACP :: Lens' CopyObject (Maybe Text)
copyObject_grantWriteACP = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\CopyObject' {Maybe Text
grantWriteACP :: Maybe Text
$sel:grantWriteACP:CopyObject' :: CopyObject -> Maybe Text
grantWriteACP} -> Maybe Text
grantWriteACP) (\s :: CopyObject
s@CopyObject' {} Maybe Text
a -> CopyObject
s {$sel:grantWriteACP:CopyObject' :: Maybe Text
grantWriteACP = Maybe Text
a} :: CopyObject)
copyObject_metadata :: Lens.Lens' CopyObject (Prelude.HashMap Prelude.Text Prelude.Text)
copyObject_metadata :: Lens' CopyObject (HashMap Text Text)
copyObject_metadata = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\CopyObject' {HashMap Text Text
metadata :: HashMap Text Text
$sel:metadata:CopyObject' :: CopyObject -> HashMap Text Text
metadata} -> HashMap Text Text
metadata) (\s :: CopyObject
s@CopyObject' {} HashMap Text Text
a -> CopyObject
s {$sel:metadata:CopyObject' :: HashMap Text Text
metadata = HashMap Text Text
a} :: CopyObject) forall b c a. (b -> c) -> (a -> b) -> a -> c
Prelude.. forall s t a b. (Coercible s a, Coercible t b) => Iso s t a b
Lens.coerced
copyObject_metadataDirective :: Lens.Lens' CopyObject (Prelude.Maybe MetadataDirective)
copyObject_metadataDirective :: Lens' CopyObject (Maybe MetadataDirective)
copyObject_metadataDirective = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\CopyObject' {Maybe MetadataDirective
metadataDirective :: Maybe MetadataDirective
$sel:metadataDirective:CopyObject' :: CopyObject -> Maybe MetadataDirective
metadataDirective} -> Maybe MetadataDirective
metadataDirective) (\s :: CopyObject
s@CopyObject' {} Maybe MetadataDirective
a -> CopyObject
s {$sel:metadataDirective:CopyObject' :: Maybe MetadataDirective
metadataDirective = Maybe MetadataDirective
a} :: CopyObject)
copyObject_objectLockLegalHoldStatus :: Lens.Lens' CopyObject (Prelude.Maybe ObjectLockLegalHoldStatus)
copyObject_objectLockLegalHoldStatus :: Lens' CopyObject (Maybe ObjectLockLegalHoldStatus)
copyObject_objectLockLegalHoldStatus = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\CopyObject' {Maybe ObjectLockLegalHoldStatus
objectLockLegalHoldStatus :: Maybe ObjectLockLegalHoldStatus
$sel:objectLockLegalHoldStatus:CopyObject' :: CopyObject -> Maybe ObjectLockLegalHoldStatus
objectLockLegalHoldStatus} -> Maybe ObjectLockLegalHoldStatus
objectLockLegalHoldStatus) (\s :: CopyObject
s@CopyObject' {} Maybe ObjectLockLegalHoldStatus
a -> CopyObject
s {$sel:objectLockLegalHoldStatus:CopyObject' :: Maybe ObjectLockLegalHoldStatus
objectLockLegalHoldStatus = Maybe ObjectLockLegalHoldStatus
a} :: CopyObject)
copyObject_objectLockMode :: Lens.Lens' CopyObject (Prelude.Maybe ObjectLockMode)
copyObject_objectLockMode :: Lens' CopyObject (Maybe ObjectLockMode)
copyObject_objectLockMode = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\CopyObject' {Maybe ObjectLockMode
objectLockMode :: Maybe ObjectLockMode
$sel:objectLockMode:CopyObject' :: CopyObject -> Maybe ObjectLockMode
objectLockMode} -> Maybe ObjectLockMode
objectLockMode) (\s :: CopyObject
s@CopyObject' {} Maybe ObjectLockMode
a -> CopyObject
s {$sel:objectLockMode:CopyObject' :: Maybe ObjectLockMode
objectLockMode = Maybe ObjectLockMode
a} :: CopyObject)
copyObject_objectLockRetainUntilDate :: Lens.Lens' CopyObject (Prelude.Maybe Prelude.UTCTime)
copyObject_objectLockRetainUntilDate :: Lens' CopyObject (Maybe UTCTime)
copyObject_objectLockRetainUntilDate = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\CopyObject' {Maybe ISO8601
objectLockRetainUntilDate :: Maybe ISO8601
$sel:objectLockRetainUntilDate:CopyObject' :: CopyObject -> Maybe ISO8601
objectLockRetainUntilDate} -> Maybe ISO8601
objectLockRetainUntilDate) (\s :: CopyObject
s@CopyObject' {} Maybe ISO8601
a -> CopyObject
s {$sel:objectLockRetainUntilDate:CopyObject' :: Maybe ISO8601
objectLockRetainUntilDate = Maybe ISO8601
a} :: CopyObject) forall b c a. (b -> c) -> (a -> b) -> a -> c
Prelude.. forall (f :: * -> *) (g :: * -> *) s t a b.
(Functor f, Functor g) =>
AnIso s t a b -> Iso (f s) (g t) (f a) (g b)
Lens.mapping forall (a :: Format). Iso' (Time a) UTCTime
Data._Time
copyObject_requestPayer :: Lens.Lens' CopyObject (Prelude.Maybe RequestPayer)
copyObject_requestPayer :: Lens' CopyObject (Maybe RequestPayer)
copyObject_requestPayer = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\CopyObject' {Maybe RequestPayer
requestPayer :: Maybe RequestPayer
$sel:requestPayer:CopyObject' :: CopyObject -> Maybe RequestPayer
requestPayer} -> Maybe RequestPayer
requestPayer) (\s :: CopyObject
s@CopyObject' {} Maybe RequestPayer
a -> CopyObject
s {$sel:requestPayer:CopyObject' :: Maybe RequestPayer
requestPayer = Maybe RequestPayer
a} :: CopyObject)
copyObject_sSECustomerAlgorithm :: Lens.Lens' CopyObject (Prelude.Maybe Prelude.Text)
copyObject_sSECustomerAlgorithm :: Lens' CopyObject (Maybe Text)
copyObject_sSECustomerAlgorithm = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\CopyObject' {Maybe Text
sSECustomerAlgorithm :: Maybe Text
$sel:sSECustomerAlgorithm:CopyObject' :: CopyObject -> Maybe Text
sSECustomerAlgorithm} -> Maybe Text
sSECustomerAlgorithm) (\s :: CopyObject
s@CopyObject' {} Maybe Text
a -> CopyObject
s {$sel:sSECustomerAlgorithm:CopyObject' :: Maybe Text
sSECustomerAlgorithm = Maybe Text
a} :: CopyObject)
copyObject_sSECustomerKey :: Lens.Lens' CopyObject (Prelude.Maybe Prelude.Text)
copyObject_sSECustomerKey :: Lens' CopyObject (Maybe Text)
copyObject_sSECustomerKey = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\CopyObject' {Maybe (Sensitive Text)
sSECustomerKey :: Maybe (Sensitive Text)
$sel:sSECustomerKey:CopyObject' :: CopyObject -> Maybe (Sensitive Text)
sSECustomerKey} -> Maybe (Sensitive Text)
sSECustomerKey) (\s :: CopyObject
s@CopyObject' {} Maybe (Sensitive Text)
a -> CopyObject
s {$sel:sSECustomerKey:CopyObject' :: Maybe (Sensitive Text)
sSECustomerKey = Maybe (Sensitive Text)
a} :: CopyObject) forall b c a. (b -> c) -> (a -> b) -> a -> c
Prelude.. forall (f :: * -> *) (g :: * -> *) s t a b.
(Functor f, Functor g) =>
AnIso s t a b -> Iso (f s) (g t) (f a) (g b)
Lens.mapping forall a. Iso' (Sensitive a) a
Data._Sensitive
copyObject_sSECustomerKeyMD5 :: Lens.Lens' CopyObject (Prelude.Maybe Prelude.Text)
copyObject_sSECustomerKeyMD5 :: Lens' CopyObject (Maybe Text)
copyObject_sSECustomerKeyMD5 = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\CopyObject' {Maybe Text
sSECustomerKeyMD5 :: Maybe Text
$sel:sSECustomerKeyMD5:CopyObject' :: CopyObject -> Maybe Text
sSECustomerKeyMD5} -> Maybe Text
sSECustomerKeyMD5) (\s :: CopyObject
s@CopyObject' {} Maybe Text
a -> CopyObject
s {$sel:sSECustomerKeyMD5:CopyObject' :: Maybe Text
sSECustomerKeyMD5 = Maybe Text
a} :: CopyObject)
copyObject_sSEKMSEncryptionContext :: Lens.Lens' CopyObject (Prelude.Maybe Prelude.Text)
copyObject_sSEKMSEncryptionContext :: Lens' CopyObject (Maybe Text)
copyObject_sSEKMSEncryptionContext = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\CopyObject' {Maybe (Sensitive Text)
sSEKMSEncryptionContext :: Maybe (Sensitive Text)
$sel:sSEKMSEncryptionContext:CopyObject' :: CopyObject -> Maybe (Sensitive Text)
sSEKMSEncryptionContext} -> Maybe (Sensitive Text)
sSEKMSEncryptionContext) (\s :: CopyObject
s@CopyObject' {} Maybe (Sensitive Text)
a -> CopyObject
s {$sel:sSEKMSEncryptionContext:CopyObject' :: Maybe (Sensitive Text)
sSEKMSEncryptionContext = Maybe (Sensitive Text)
a} :: CopyObject) forall b c a. (b -> c) -> (a -> b) -> a -> c
Prelude.. forall (f :: * -> *) (g :: * -> *) s t a b.
(Functor f, Functor g) =>
AnIso s t a b -> Iso (f s) (g t) (f a) (g b)
Lens.mapping forall a. Iso' (Sensitive a) a
Data._Sensitive
copyObject_sSEKMSKeyId :: Lens.Lens' CopyObject (Prelude.Maybe Prelude.Text)
copyObject_sSEKMSKeyId :: Lens' CopyObject (Maybe Text)
copyObject_sSEKMSKeyId = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\CopyObject' {Maybe (Sensitive Text)
sSEKMSKeyId :: Maybe (Sensitive Text)
$sel:sSEKMSKeyId:CopyObject' :: CopyObject -> Maybe (Sensitive Text)
sSEKMSKeyId} -> Maybe (Sensitive Text)
sSEKMSKeyId) (\s :: CopyObject
s@CopyObject' {} Maybe (Sensitive Text)
a -> CopyObject
s {$sel:sSEKMSKeyId:CopyObject' :: Maybe (Sensitive Text)
sSEKMSKeyId = Maybe (Sensitive Text)
a} :: CopyObject) forall b c a. (b -> c) -> (a -> b) -> a -> c
Prelude.. forall (f :: * -> *) (g :: * -> *) s t a b.
(Functor f, Functor g) =>
AnIso s t a b -> Iso (f s) (g t) (f a) (g b)
Lens.mapping forall a. Iso' (Sensitive a) a
Data._Sensitive
copyObject_serverSideEncryption :: Lens.Lens' CopyObject (Prelude.Maybe ServerSideEncryption)
copyObject_serverSideEncryption :: Lens' CopyObject (Maybe ServerSideEncryption)
copyObject_serverSideEncryption = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\CopyObject' {Maybe ServerSideEncryption
serverSideEncryption :: Maybe ServerSideEncryption
$sel:serverSideEncryption:CopyObject' :: CopyObject -> Maybe ServerSideEncryption
serverSideEncryption} -> Maybe ServerSideEncryption
serverSideEncryption) (\s :: CopyObject
s@CopyObject' {} Maybe ServerSideEncryption
a -> CopyObject
s {$sel:serverSideEncryption:CopyObject' :: Maybe ServerSideEncryption
serverSideEncryption = Maybe ServerSideEncryption
a} :: CopyObject)
copyObject_storageClass :: Lens.Lens' CopyObject (Prelude.Maybe StorageClass)
copyObject_storageClass :: Lens' CopyObject (Maybe StorageClass)
copyObject_storageClass = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\CopyObject' {Maybe StorageClass
storageClass :: Maybe StorageClass
$sel:storageClass:CopyObject' :: CopyObject -> Maybe StorageClass
storageClass} -> Maybe StorageClass
storageClass) (\s :: CopyObject
s@CopyObject' {} Maybe StorageClass
a -> CopyObject
s {$sel:storageClass:CopyObject' :: Maybe StorageClass
storageClass = Maybe StorageClass
a} :: CopyObject)
copyObject_tagging :: Lens.Lens' CopyObject (Prelude.Maybe Prelude.Text)
copyObject_tagging :: Lens' CopyObject (Maybe Text)
copyObject_tagging = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\CopyObject' {Maybe Text
tagging :: Maybe Text
$sel:tagging:CopyObject' :: CopyObject -> Maybe Text
tagging} -> Maybe Text
tagging) (\s :: CopyObject
s@CopyObject' {} Maybe Text
a -> CopyObject
s {$sel:tagging:CopyObject' :: Maybe Text
tagging = Maybe Text
a} :: CopyObject)
copyObject_taggingDirective :: Lens.Lens' CopyObject (Prelude.Maybe TaggingDirective)
copyObject_taggingDirective :: Lens' CopyObject (Maybe TaggingDirective)
copyObject_taggingDirective = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\CopyObject' {Maybe TaggingDirective
taggingDirective :: Maybe TaggingDirective
$sel:taggingDirective:CopyObject' :: CopyObject -> Maybe TaggingDirective
taggingDirective} -> Maybe TaggingDirective
taggingDirective) (\s :: CopyObject
s@CopyObject' {} Maybe TaggingDirective
a -> CopyObject
s {$sel:taggingDirective:CopyObject' :: Maybe TaggingDirective
taggingDirective = Maybe TaggingDirective
a} :: CopyObject)
copyObject_websiteRedirectLocation :: Lens.Lens' CopyObject (Prelude.Maybe Prelude.Text)
copyObject_websiteRedirectLocation :: Lens' CopyObject (Maybe Text)
copyObject_websiteRedirectLocation = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\CopyObject' {Maybe Text
websiteRedirectLocation :: Maybe Text
$sel:websiteRedirectLocation:CopyObject' :: CopyObject -> Maybe Text
websiteRedirectLocation} -> Maybe Text
websiteRedirectLocation) (\s :: CopyObject
s@CopyObject' {} Maybe Text
a -> CopyObject
s {$sel:websiteRedirectLocation:CopyObject' :: Maybe Text
websiteRedirectLocation = Maybe Text
a} :: CopyObject)
copyObject_bucket :: Lens.Lens' CopyObject BucketName
copyObject_bucket :: Lens' CopyObject BucketName
copyObject_bucket = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\CopyObject' {BucketName
bucket :: BucketName
$sel:bucket:CopyObject' :: CopyObject -> BucketName
bucket} -> BucketName
bucket) (\s :: CopyObject
s@CopyObject' {} BucketName
a -> CopyObject
s {$sel:bucket:CopyObject' :: BucketName
bucket = BucketName
a} :: CopyObject)
copyObject_copySource :: Lens.Lens' CopyObject Prelude.Text
copyObject_copySource :: Lens' CopyObject Text
copyObject_copySource = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\CopyObject' {Text
copySource :: Text
$sel:copySource:CopyObject' :: CopyObject -> Text
copySource} -> Text
copySource) (\s :: CopyObject
s@CopyObject' {} Text
a -> CopyObject
s {$sel:copySource:CopyObject' :: Text
copySource = Text
a} :: CopyObject)
copyObject_key :: Lens.Lens' CopyObject ObjectKey
copyObject_key :: Lens' CopyObject ObjectKey
copyObject_key = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\CopyObject' {ObjectKey
key :: ObjectKey
$sel:key:CopyObject' :: CopyObject -> ObjectKey
key} -> ObjectKey
key) (\s :: CopyObject
s@CopyObject' {} ObjectKey
a -> CopyObject
s {$sel:key:CopyObject' :: ObjectKey
key = ObjectKey
a} :: CopyObject)
instance Core.AWSRequest CopyObject where
  type AWSResponse CopyObject = CopyObjectResponse
  request :: (Service -> Service) -> CopyObject -> Request CopyObject
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.put (Service -> Service
overrides Service
defaultService)
  response :: forall (m :: * -> *).
MonadResource m =>
(ByteStringLazy -> IO ByteStringLazy)
-> Service
-> Proxy CopyObject
-> ClientResponse ClientBody
-> m (Either Error (ClientResponse (AWSResponse CopyObject)))
response =
    forall (m :: * -> *) a.
MonadResource m =>
(Int -> ResponseHeaders -> [Node] -> Either String (AWSResponse a))
-> (ByteStringLazy -> IO ByteStringLazy)
-> Service
-> Proxy a
-> ClientResponse ClientBody
-> m (Either Error (ClientResponse (AWSResponse a)))
Response.receiveXML
      ( \Int
s ResponseHeaders
h [Node]
x ->
          Maybe Bool
-> Maybe CopyObjectResult
-> Maybe Text
-> Maybe Text
-> Maybe RequestCharged
-> Maybe Text
-> Maybe Text
-> Maybe (Sensitive Text)
-> Maybe (Sensitive Text)
-> Maybe ServerSideEncryption
-> Maybe ObjectVersionId
-> Int
-> CopyObjectResponse
CopyObjectResponse'
            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-server-side-encryption-bucket-key-enabled"
                        )
            forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
Prelude.<*> (forall a. FromXML a => [Node] -> Either String a
Data.parseXML [Node]
x)
            forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
Prelude.<*> (ResponseHeaders
h forall a.
FromText a =>
ResponseHeaders -> HeaderName -> Either String (Maybe a)
Data..#? HeaderName
"x-amz-copy-source-version-id")
            forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
Prelude.<*> (ResponseHeaders
h forall a.
FromText a =>
ResponseHeaders -> HeaderName -> Either String (Maybe a)
Data..#? HeaderName
"x-amz-expiration")
            forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
Prelude.<*> (ResponseHeaders
h forall a.
FromText a =>
ResponseHeaders -> HeaderName -> Either String (Maybe a)
Data..#? HeaderName
"x-amz-request-charged")
            forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
Prelude.<*> ( ResponseHeaders
h
                            forall a.
FromText a =>
ResponseHeaders -> HeaderName -> Either String (Maybe a)
Data..#? HeaderName
"x-amz-server-side-encryption-customer-algorithm"
                        )
            forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
Prelude.<*> ( ResponseHeaders
h
                            forall a.
FromText a =>
ResponseHeaders -> HeaderName -> Either String (Maybe a)
Data..#? HeaderName
"x-amz-server-side-encryption-customer-key-MD5"
                        )
            forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
Prelude.<*> (ResponseHeaders
h forall a.
FromText a =>
ResponseHeaders -> HeaderName -> Either String (Maybe a)
Data..#? HeaderName
"x-amz-server-side-encryption-context")
            forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
Prelude.<*> ( ResponseHeaders
h
                            forall a.
FromText a =>
ResponseHeaders -> HeaderName -> Either String (Maybe a)
Data..#? HeaderName
"x-amz-server-side-encryption-aws-kms-key-id"
                        )
            forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
Prelude.<*> (ResponseHeaders
h forall a.
FromText a =>
ResponseHeaders -> HeaderName -> Either String (Maybe a)
Data..#? HeaderName
"x-amz-server-side-encryption")
            forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
Prelude.<*> (ResponseHeaders
h forall a.
FromText a =>
ResponseHeaders -> HeaderName -> Either String (Maybe a)
Data..#? HeaderName
"x-amz-version-id")
            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 CopyObject where
  hashWithSalt :: Int -> CopyObject -> Int
hashWithSalt Int
_salt CopyObject' {Maybe Bool
Maybe Text
Maybe (Sensitive Text)
Maybe ISO8601
Maybe RFC822
Maybe ChecksumAlgorithm
Maybe MetadataDirective
Maybe ObjectCannedACL
Maybe ObjectLockLegalHoldStatus
Maybe ObjectLockMode
Maybe RequestPayer
Maybe ServerSideEncryption
Maybe StorageClass
Maybe TaggingDirective
Text
HashMap Text Text
ObjectKey
BucketName
key :: ObjectKey
copySource :: Text
bucket :: BucketName
websiteRedirectLocation :: Maybe Text
taggingDirective :: Maybe TaggingDirective
tagging :: Maybe Text
storageClass :: Maybe StorageClass
serverSideEncryption :: Maybe ServerSideEncryption
sSEKMSKeyId :: Maybe (Sensitive Text)
sSEKMSEncryptionContext :: Maybe (Sensitive Text)
sSECustomerKeyMD5 :: Maybe Text
sSECustomerKey :: Maybe (Sensitive Text)
sSECustomerAlgorithm :: Maybe Text
requestPayer :: Maybe RequestPayer
objectLockRetainUntilDate :: Maybe ISO8601
objectLockMode :: Maybe ObjectLockMode
objectLockLegalHoldStatus :: Maybe ObjectLockLegalHoldStatus
metadataDirective :: Maybe MetadataDirective
metadata :: HashMap Text Text
grantWriteACP :: Maybe Text
grantReadACP :: Maybe Text
grantRead :: Maybe Text
grantFullControl :: Maybe Text
expires :: Maybe RFC822
expectedSourceBucketOwner :: Maybe Text
expectedBucketOwner :: Maybe Text
copySourceSSECustomerKeyMD5 :: Maybe Text
copySourceSSECustomerKey :: Maybe (Sensitive Text)
copySourceSSECustomerAlgorithm :: Maybe Text
copySourceIfUnmodifiedSince :: Maybe RFC822
copySourceIfNoneMatch :: Maybe Text
copySourceIfModifiedSince :: Maybe RFC822
copySourceIfMatch :: Maybe Text
contentType :: Maybe Text
contentLanguage :: Maybe Text
contentEncoding :: Maybe Text
contentDisposition :: Maybe Text
checksumAlgorithm :: Maybe ChecksumAlgorithm
cacheControl :: Maybe Text
bucketKeyEnabled :: Maybe Bool
acl :: Maybe ObjectCannedACL
$sel:key:CopyObject' :: CopyObject -> ObjectKey
$sel:copySource:CopyObject' :: CopyObject -> Text
$sel:bucket:CopyObject' :: CopyObject -> BucketName
$sel:websiteRedirectLocation:CopyObject' :: CopyObject -> Maybe Text
$sel:taggingDirective:CopyObject' :: CopyObject -> Maybe TaggingDirective
$sel:tagging:CopyObject' :: CopyObject -> Maybe Text
$sel:storageClass:CopyObject' :: CopyObject -> Maybe StorageClass
$sel:serverSideEncryption:CopyObject' :: CopyObject -> Maybe ServerSideEncryption
$sel:sSEKMSKeyId:CopyObject' :: CopyObject -> Maybe (Sensitive Text)
$sel:sSEKMSEncryptionContext:CopyObject' :: CopyObject -> Maybe (Sensitive Text)
$sel:sSECustomerKeyMD5:CopyObject' :: CopyObject -> Maybe Text
$sel:sSECustomerKey:CopyObject' :: CopyObject -> Maybe (Sensitive Text)
$sel:sSECustomerAlgorithm:CopyObject' :: CopyObject -> Maybe Text
$sel:requestPayer:CopyObject' :: CopyObject -> Maybe RequestPayer
$sel:objectLockRetainUntilDate:CopyObject' :: CopyObject -> Maybe ISO8601
$sel:objectLockMode:CopyObject' :: CopyObject -> Maybe ObjectLockMode
$sel:objectLockLegalHoldStatus:CopyObject' :: CopyObject -> Maybe ObjectLockLegalHoldStatus
$sel:metadataDirective:CopyObject' :: CopyObject -> Maybe MetadataDirective
$sel:metadata:CopyObject' :: CopyObject -> HashMap Text Text
$sel:grantWriteACP:CopyObject' :: CopyObject -> Maybe Text
$sel:grantReadACP:CopyObject' :: CopyObject -> Maybe Text
$sel:grantRead:CopyObject' :: CopyObject -> Maybe Text
$sel:grantFullControl:CopyObject' :: CopyObject -> Maybe Text
$sel:expires:CopyObject' :: CopyObject -> Maybe RFC822
$sel:expectedSourceBucketOwner:CopyObject' :: CopyObject -> Maybe Text
$sel:expectedBucketOwner:CopyObject' :: CopyObject -> Maybe Text
$sel:copySourceSSECustomerKeyMD5:CopyObject' :: CopyObject -> Maybe Text
$sel:copySourceSSECustomerKey:CopyObject' :: CopyObject -> Maybe (Sensitive Text)
$sel:copySourceSSECustomerAlgorithm:CopyObject' :: CopyObject -> Maybe Text
$sel:copySourceIfUnmodifiedSince:CopyObject' :: CopyObject -> Maybe RFC822
$sel:copySourceIfNoneMatch:CopyObject' :: CopyObject -> Maybe Text
$sel:copySourceIfModifiedSince:CopyObject' :: CopyObject -> Maybe RFC822
$sel:copySourceIfMatch:CopyObject' :: CopyObject -> Maybe Text
$sel:contentType:CopyObject' :: CopyObject -> Maybe Text
$sel:contentLanguage:CopyObject' :: CopyObject -> Maybe Text
$sel:contentEncoding:CopyObject' :: CopyObject -> Maybe Text
$sel:contentDisposition:CopyObject' :: CopyObject -> Maybe Text
$sel:checksumAlgorithm:CopyObject' :: CopyObject -> Maybe ChecksumAlgorithm
$sel:cacheControl:CopyObject' :: CopyObject -> Maybe Text
$sel:bucketKeyEnabled:CopyObject' :: CopyObject -> Maybe Bool
$sel:acl:CopyObject' :: CopyObject -> Maybe ObjectCannedACL
..} =
    Int
_salt
      forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Maybe ObjectCannedACL
acl
      forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Maybe Bool
bucketKeyEnabled
      forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Maybe Text
cacheControl
      forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Maybe ChecksumAlgorithm
checksumAlgorithm
      forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Maybe Text
contentDisposition
      forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Maybe Text
contentEncoding
      forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Maybe Text
contentLanguage
      forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Maybe Text
contentType
      forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Maybe Text
copySourceIfMatch
      forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Maybe RFC822
copySourceIfModifiedSince
      forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Maybe Text
copySourceIfNoneMatch
      forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Maybe RFC822
copySourceIfUnmodifiedSince
      forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Maybe Text
copySourceSSECustomerAlgorithm
      forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Maybe (Sensitive Text)
copySourceSSECustomerKey
      forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Maybe Text
copySourceSSECustomerKeyMD5
      forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Maybe Text
expectedBucketOwner
      forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Maybe Text
expectedSourceBucketOwner
      forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Maybe RFC822
expires
      forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Maybe Text
grantFullControl
      forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Maybe Text
grantRead
      forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Maybe Text
grantReadACP
      forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Maybe Text
grantWriteACP
      forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` HashMap Text Text
metadata
      forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Maybe MetadataDirective
metadataDirective
      forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Maybe ObjectLockLegalHoldStatus
objectLockLegalHoldStatus
      forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Maybe ObjectLockMode
objectLockMode
      forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Maybe ISO8601
objectLockRetainUntilDate
      forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Maybe RequestPayer
requestPayer
      forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Maybe Text
sSECustomerAlgorithm
      forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Maybe (Sensitive Text)
sSECustomerKey
      forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Maybe Text
sSECustomerKeyMD5
      forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Maybe (Sensitive Text)
sSEKMSEncryptionContext
      forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Maybe (Sensitive Text)
sSEKMSKeyId
      forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Maybe ServerSideEncryption
serverSideEncryption
      forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Maybe StorageClass
storageClass
      forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Maybe Text
tagging
      forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Maybe TaggingDirective
taggingDirective
      forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Maybe Text
websiteRedirectLocation
      forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` BucketName
bucket
      forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Text
copySource
      forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` ObjectKey
key
instance Prelude.NFData CopyObject where
  rnf :: CopyObject -> ()
rnf CopyObject' {Maybe Bool
Maybe Text
Maybe (Sensitive Text)
Maybe ISO8601
Maybe RFC822
Maybe ChecksumAlgorithm
Maybe MetadataDirective
Maybe ObjectCannedACL
Maybe ObjectLockLegalHoldStatus
Maybe ObjectLockMode
Maybe RequestPayer
Maybe ServerSideEncryption
Maybe StorageClass
Maybe TaggingDirective
Text
HashMap Text Text
ObjectKey
BucketName
key :: ObjectKey
copySource :: Text
bucket :: BucketName
websiteRedirectLocation :: Maybe Text
taggingDirective :: Maybe TaggingDirective
tagging :: Maybe Text
storageClass :: Maybe StorageClass
serverSideEncryption :: Maybe ServerSideEncryption
sSEKMSKeyId :: Maybe (Sensitive Text)
sSEKMSEncryptionContext :: Maybe (Sensitive Text)
sSECustomerKeyMD5 :: Maybe Text
sSECustomerKey :: Maybe (Sensitive Text)
sSECustomerAlgorithm :: Maybe Text
requestPayer :: Maybe RequestPayer
objectLockRetainUntilDate :: Maybe ISO8601
objectLockMode :: Maybe ObjectLockMode
objectLockLegalHoldStatus :: Maybe ObjectLockLegalHoldStatus
metadataDirective :: Maybe MetadataDirective
metadata :: HashMap Text Text
grantWriteACP :: Maybe Text
grantReadACP :: Maybe Text
grantRead :: Maybe Text
grantFullControl :: Maybe Text
expires :: Maybe RFC822
expectedSourceBucketOwner :: Maybe Text
expectedBucketOwner :: Maybe Text
copySourceSSECustomerKeyMD5 :: Maybe Text
copySourceSSECustomerKey :: Maybe (Sensitive Text)
copySourceSSECustomerAlgorithm :: Maybe Text
copySourceIfUnmodifiedSince :: Maybe RFC822
copySourceIfNoneMatch :: Maybe Text
copySourceIfModifiedSince :: Maybe RFC822
copySourceIfMatch :: Maybe Text
contentType :: Maybe Text
contentLanguage :: Maybe Text
contentEncoding :: Maybe Text
contentDisposition :: Maybe Text
checksumAlgorithm :: Maybe ChecksumAlgorithm
cacheControl :: Maybe Text
bucketKeyEnabled :: Maybe Bool
acl :: Maybe ObjectCannedACL
$sel:key:CopyObject' :: CopyObject -> ObjectKey
$sel:copySource:CopyObject' :: CopyObject -> Text
$sel:bucket:CopyObject' :: CopyObject -> BucketName
$sel:websiteRedirectLocation:CopyObject' :: CopyObject -> Maybe Text
$sel:taggingDirective:CopyObject' :: CopyObject -> Maybe TaggingDirective
$sel:tagging:CopyObject' :: CopyObject -> Maybe Text
$sel:storageClass:CopyObject' :: CopyObject -> Maybe StorageClass
$sel:serverSideEncryption:CopyObject' :: CopyObject -> Maybe ServerSideEncryption
$sel:sSEKMSKeyId:CopyObject' :: CopyObject -> Maybe (Sensitive Text)
$sel:sSEKMSEncryptionContext:CopyObject' :: CopyObject -> Maybe (Sensitive Text)
$sel:sSECustomerKeyMD5:CopyObject' :: CopyObject -> Maybe Text
$sel:sSECustomerKey:CopyObject' :: CopyObject -> Maybe (Sensitive Text)
$sel:sSECustomerAlgorithm:CopyObject' :: CopyObject -> Maybe Text
$sel:requestPayer:CopyObject' :: CopyObject -> Maybe RequestPayer
$sel:objectLockRetainUntilDate:CopyObject' :: CopyObject -> Maybe ISO8601
$sel:objectLockMode:CopyObject' :: CopyObject -> Maybe ObjectLockMode
$sel:objectLockLegalHoldStatus:CopyObject' :: CopyObject -> Maybe ObjectLockLegalHoldStatus
$sel:metadataDirective:CopyObject' :: CopyObject -> Maybe MetadataDirective
$sel:metadata:CopyObject' :: CopyObject -> HashMap Text Text
$sel:grantWriteACP:CopyObject' :: CopyObject -> Maybe Text
$sel:grantReadACP:CopyObject' :: CopyObject -> Maybe Text
$sel:grantRead:CopyObject' :: CopyObject -> Maybe Text
$sel:grantFullControl:CopyObject' :: CopyObject -> Maybe Text
$sel:expires:CopyObject' :: CopyObject -> Maybe RFC822
$sel:expectedSourceBucketOwner:CopyObject' :: CopyObject -> Maybe Text
$sel:expectedBucketOwner:CopyObject' :: CopyObject -> Maybe Text
$sel:copySourceSSECustomerKeyMD5:CopyObject' :: CopyObject -> Maybe Text
$sel:copySourceSSECustomerKey:CopyObject' :: CopyObject -> Maybe (Sensitive Text)
$sel:copySourceSSECustomerAlgorithm:CopyObject' :: CopyObject -> Maybe Text
$sel:copySourceIfUnmodifiedSince:CopyObject' :: CopyObject -> Maybe RFC822
$sel:copySourceIfNoneMatch:CopyObject' :: CopyObject -> Maybe Text
$sel:copySourceIfModifiedSince:CopyObject' :: CopyObject -> Maybe RFC822
$sel:copySourceIfMatch:CopyObject' :: CopyObject -> Maybe Text
$sel:contentType:CopyObject' :: CopyObject -> Maybe Text
$sel:contentLanguage:CopyObject' :: CopyObject -> Maybe Text
$sel:contentEncoding:CopyObject' :: CopyObject -> Maybe Text
$sel:contentDisposition:CopyObject' :: CopyObject -> Maybe Text
$sel:checksumAlgorithm:CopyObject' :: CopyObject -> Maybe ChecksumAlgorithm
$sel:cacheControl:CopyObject' :: CopyObject -> Maybe Text
$sel:bucketKeyEnabled:CopyObject' :: CopyObject -> Maybe Bool
$sel:acl:CopyObject' :: CopyObject -> Maybe ObjectCannedACL
..} =
    forall a. NFData a => a -> ()
Prelude.rnf Maybe ObjectCannedACL
acl
      seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf Maybe Bool
bucketKeyEnabled
      seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf Maybe Text
cacheControl
      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
contentDisposition
      seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf Maybe Text
contentEncoding
      seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf Maybe Text
contentLanguage
      seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf Maybe Text
contentType
      seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf Maybe Text
copySourceIfMatch
      seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf Maybe RFC822
copySourceIfModifiedSince
      seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf Maybe Text
copySourceIfNoneMatch
      seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf Maybe RFC822
copySourceIfUnmodifiedSince
      seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf Maybe Text
copySourceSSECustomerAlgorithm
      seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf Maybe (Sensitive Text)
copySourceSSECustomerKey
      seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf Maybe Text
copySourceSSECustomerKeyMD5
      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
expectedSourceBucketOwner
      seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf Maybe RFC822
expires
      seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf Maybe Text
grantFullControl
      seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf Maybe Text
grantRead
      seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf Maybe Text
grantReadACP
      seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf Maybe Text
grantWriteACP
      seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf HashMap Text Text
metadata
      seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf
        Maybe MetadataDirective
metadataDirective
      seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf
        Maybe ObjectLockLegalHoldStatus
objectLockLegalHoldStatus
      seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf
        Maybe ObjectLockMode
objectLockMode
      seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf
        Maybe ISO8601
objectLockRetainUntilDate
      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 Text
sSECustomerAlgorithm
      seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf
        Maybe (Sensitive Text)
sSECustomerKey
      seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf
        Maybe Text
sSECustomerKeyMD5
      seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf
        Maybe (Sensitive Text)
sSEKMSEncryptionContext
      seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf
        Maybe (Sensitive Text)
sSEKMSKeyId
      seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf
        Maybe ServerSideEncryption
serverSideEncryption
      seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf
        Maybe StorageClass
storageClass
      seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf
        Maybe Text
tagging
      seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf
        Maybe TaggingDirective
taggingDirective
      seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf
        Maybe Text
websiteRedirectLocation
      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
        Text
copySource
      seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf
        ObjectKey
key
instance Data.ToHeaders CopyObject where
  toHeaders :: CopyObject -> ResponseHeaders
toHeaders CopyObject' {Maybe Bool
Maybe Text
Maybe (Sensitive Text)
Maybe ISO8601
Maybe RFC822
Maybe ChecksumAlgorithm
Maybe MetadataDirective
Maybe ObjectCannedACL
Maybe ObjectLockLegalHoldStatus
Maybe ObjectLockMode
Maybe RequestPayer
Maybe ServerSideEncryption
Maybe StorageClass
Maybe TaggingDirective
Text
HashMap Text Text
ObjectKey
BucketName
key :: ObjectKey
copySource :: Text
bucket :: BucketName
websiteRedirectLocation :: Maybe Text
taggingDirective :: Maybe TaggingDirective
tagging :: Maybe Text
storageClass :: Maybe StorageClass
serverSideEncryption :: Maybe ServerSideEncryption
sSEKMSKeyId :: Maybe (Sensitive Text)
sSEKMSEncryptionContext :: Maybe (Sensitive Text)
sSECustomerKeyMD5 :: Maybe Text
sSECustomerKey :: Maybe (Sensitive Text)
sSECustomerAlgorithm :: Maybe Text
requestPayer :: Maybe RequestPayer
objectLockRetainUntilDate :: Maybe ISO8601
objectLockMode :: Maybe ObjectLockMode
objectLockLegalHoldStatus :: Maybe ObjectLockLegalHoldStatus
metadataDirective :: Maybe MetadataDirective
metadata :: HashMap Text Text
grantWriteACP :: Maybe Text
grantReadACP :: Maybe Text
grantRead :: Maybe Text
grantFullControl :: Maybe Text
expires :: Maybe RFC822
expectedSourceBucketOwner :: Maybe Text
expectedBucketOwner :: Maybe Text
copySourceSSECustomerKeyMD5 :: Maybe Text
copySourceSSECustomerKey :: Maybe (Sensitive Text)
copySourceSSECustomerAlgorithm :: Maybe Text
copySourceIfUnmodifiedSince :: Maybe RFC822
copySourceIfNoneMatch :: Maybe Text
copySourceIfModifiedSince :: Maybe RFC822
copySourceIfMatch :: Maybe Text
contentType :: Maybe Text
contentLanguage :: Maybe Text
contentEncoding :: Maybe Text
contentDisposition :: Maybe Text
checksumAlgorithm :: Maybe ChecksumAlgorithm
cacheControl :: Maybe Text
bucketKeyEnabled :: Maybe Bool
acl :: Maybe ObjectCannedACL
$sel:key:CopyObject' :: CopyObject -> ObjectKey
$sel:copySource:CopyObject' :: CopyObject -> Text
$sel:bucket:CopyObject' :: CopyObject -> BucketName
$sel:websiteRedirectLocation:CopyObject' :: CopyObject -> Maybe Text
$sel:taggingDirective:CopyObject' :: CopyObject -> Maybe TaggingDirective
$sel:tagging:CopyObject' :: CopyObject -> Maybe Text
$sel:storageClass:CopyObject' :: CopyObject -> Maybe StorageClass
$sel:serverSideEncryption:CopyObject' :: CopyObject -> Maybe ServerSideEncryption
$sel:sSEKMSKeyId:CopyObject' :: CopyObject -> Maybe (Sensitive Text)
$sel:sSEKMSEncryptionContext:CopyObject' :: CopyObject -> Maybe (Sensitive Text)
$sel:sSECustomerKeyMD5:CopyObject' :: CopyObject -> Maybe Text
$sel:sSECustomerKey:CopyObject' :: CopyObject -> Maybe (Sensitive Text)
$sel:sSECustomerAlgorithm:CopyObject' :: CopyObject -> Maybe Text
$sel:requestPayer:CopyObject' :: CopyObject -> Maybe RequestPayer
$sel:objectLockRetainUntilDate:CopyObject' :: CopyObject -> Maybe ISO8601
$sel:objectLockMode:CopyObject' :: CopyObject -> Maybe ObjectLockMode
$sel:objectLockLegalHoldStatus:CopyObject' :: CopyObject -> Maybe ObjectLockLegalHoldStatus
$sel:metadataDirective:CopyObject' :: CopyObject -> Maybe MetadataDirective
$sel:metadata:CopyObject' :: CopyObject -> HashMap Text Text
$sel:grantWriteACP:CopyObject' :: CopyObject -> Maybe Text
$sel:grantReadACP:CopyObject' :: CopyObject -> Maybe Text
$sel:grantRead:CopyObject' :: CopyObject -> Maybe Text
$sel:grantFullControl:CopyObject' :: CopyObject -> Maybe Text
$sel:expires:CopyObject' :: CopyObject -> Maybe RFC822
$sel:expectedSourceBucketOwner:CopyObject' :: CopyObject -> Maybe Text
$sel:expectedBucketOwner:CopyObject' :: CopyObject -> Maybe Text
$sel:copySourceSSECustomerKeyMD5:CopyObject' :: CopyObject -> Maybe Text
$sel:copySourceSSECustomerKey:CopyObject' :: CopyObject -> Maybe (Sensitive Text)
$sel:copySourceSSECustomerAlgorithm:CopyObject' :: CopyObject -> Maybe Text
$sel:copySourceIfUnmodifiedSince:CopyObject' :: CopyObject -> Maybe RFC822
$sel:copySourceIfNoneMatch:CopyObject' :: CopyObject -> Maybe Text
$sel:copySourceIfModifiedSince:CopyObject' :: CopyObject -> Maybe RFC822
$sel:copySourceIfMatch:CopyObject' :: CopyObject -> Maybe Text
$sel:contentType:CopyObject' :: CopyObject -> Maybe Text
$sel:contentLanguage:CopyObject' :: CopyObject -> Maybe Text
$sel:contentEncoding:CopyObject' :: CopyObject -> Maybe Text
$sel:contentDisposition:CopyObject' :: CopyObject -> Maybe Text
$sel:checksumAlgorithm:CopyObject' :: CopyObject -> Maybe ChecksumAlgorithm
$sel:cacheControl:CopyObject' :: CopyObject -> Maybe Text
$sel:bucketKeyEnabled:CopyObject' :: CopyObject -> Maybe Bool
$sel:acl:CopyObject' :: CopyObject -> Maybe ObjectCannedACL
..} =
    forall a. Monoid a => [a] -> a
Prelude.mconcat
      [ HeaderName
"x-amz-acl" forall a. ToHeader a => HeaderName -> a -> ResponseHeaders
Data.=# Maybe ObjectCannedACL
acl,
        HeaderName
"x-amz-server-side-encryption-bucket-key-enabled"
          forall a. ToHeader a => HeaderName -> a -> ResponseHeaders
Data.=# Maybe Bool
bucketKeyEnabled,
        HeaderName
"Cache-Control" forall a. ToHeader a => HeaderName -> a -> ResponseHeaders
Data.=# Maybe Text
cacheControl,
        HeaderName
"x-amz-checksum-algorithm" forall a. ToHeader a => HeaderName -> a -> ResponseHeaders
Data.=# Maybe ChecksumAlgorithm
checksumAlgorithm,
        HeaderName
"Content-Disposition" forall a. ToHeader a => HeaderName -> a -> ResponseHeaders
Data.=# Maybe Text
contentDisposition,
        HeaderName
"Content-Encoding" forall a. ToHeader a => HeaderName -> a -> ResponseHeaders
Data.=# Maybe Text
contentEncoding,
        HeaderName
"Content-Language" forall a. ToHeader a => HeaderName -> a -> ResponseHeaders
Data.=# Maybe Text
contentLanguage,
        HeaderName
"Content-Type" forall a. ToHeader a => HeaderName -> a -> ResponseHeaders
Data.=# Maybe Text
contentType,
        HeaderName
"x-amz-copy-source-if-match"
          forall a. ToHeader a => HeaderName -> a -> ResponseHeaders
Data.=# Maybe Text
copySourceIfMatch,
        HeaderName
"x-amz-copy-source-if-modified-since"
          forall a. ToHeader a => HeaderName -> a -> ResponseHeaders
Data.=# Maybe RFC822
copySourceIfModifiedSince,
        HeaderName
"x-amz-copy-source-if-none-match"
          forall a. ToHeader a => HeaderName -> a -> ResponseHeaders
Data.=# Maybe Text
copySourceIfNoneMatch,
        HeaderName
"x-amz-copy-source-if-unmodified-since"
          forall a. ToHeader a => HeaderName -> a -> ResponseHeaders
Data.=# Maybe RFC822
copySourceIfUnmodifiedSince,
        HeaderName
"x-amz-copy-source-server-side-encryption-customer-algorithm"
          forall a. ToHeader a => HeaderName -> a -> ResponseHeaders
Data.=# Maybe Text
copySourceSSECustomerAlgorithm,
        HeaderName
"x-amz-copy-source-server-side-encryption-customer-key"
          forall a. ToHeader a => HeaderName -> a -> ResponseHeaders
Data.=# Maybe (Sensitive Text)
copySourceSSECustomerKey,
        HeaderName
"x-amz-copy-source-server-side-encryption-customer-key-MD5"
          forall a. ToHeader a => HeaderName -> a -> ResponseHeaders
Data.=# Maybe Text
copySourceSSECustomerKeyMD5,
        HeaderName
"x-amz-expected-bucket-owner"
          forall a. ToHeader a => HeaderName -> a -> ResponseHeaders
Data.=# Maybe Text
expectedBucketOwner,
        HeaderName
"x-amz-source-expected-bucket-owner"
          forall a. ToHeader a => HeaderName -> a -> ResponseHeaders
Data.=# Maybe Text
expectedSourceBucketOwner,
        HeaderName
"Expires" forall a. ToHeader a => HeaderName -> a -> ResponseHeaders
Data.=# Maybe RFC822
expires,
        HeaderName
"x-amz-grant-full-control" forall a. ToHeader a => HeaderName -> a -> ResponseHeaders
Data.=# Maybe Text
grantFullControl,
        HeaderName
"x-amz-grant-read" forall a. ToHeader a => HeaderName -> a -> ResponseHeaders
Data.=# Maybe Text
grantRead,
        HeaderName
"x-amz-grant-read-acp" forall a. ToHeader a => HeaderName -> a -> ResponseHeaders
Data.=# Maybe Text
grantReadACP,
        HeaderName
"x-amz-grant-write-acp" forall a. ToHeader a => HeaderName -> a -> ResponseHeaders
Data.=# Maybe Text
grantWriteACP,
        HeaderName
"x-amz-meta-" forall a. ToHeader a => HeaderName -> a -> ResponseHeaders
Data.=# HashMap Text Text
metadata,
        HeaderName
"x-amz-metadata-directive" forall a. ToHeader a => HeaderName -> a -> ResponseHeaders
Data.=# Maybe MetadataDirective
metadataDirective,
        HeaderName
"x-amz-object-lock-legal-hold"
          forall a. ToHeader a => HeaderName -> a -> ResponseHeaders
Data.=# Maybe ObjectLockLegalHoldStatus
objectLockLegalHoldStatus,
        HeaderName
"x-amz-object-lock-mode" forall a. ToHeader a => HeaderName -> a -> ResponseHeaders
Data.=# Maybe ObjectLockMode
objectLockMode,
        HeaderName
"x-amz-object-lock-retain-until-date"
          forall a. ToHeader a => HeaderName -> a -> ResponseHeaders
Data.=# Maybe ISO8601
objectLockRetainUntilDate,
        HeaderName
"x-amz-request-payer" forall a. ToHeader a => HeaderName -> a -> ResponseHeaders
Data.=# Maybe RequestPayer
requestPayer,
        HeaderName
"x-amz-server-side-encryption-customer-algorithm"
          forall a. ToHeader a => HeaderName -> a -> ResponseHeaders
Data.=# Maybe Text
sSECustomerAlgorithm,
        HeaderName
"x-amz-server-side-encryption-customer-key"
          forall a. ToHeader a => HeaderName -> a -> ResponseHeaders
Data.=# Maybe (Sensitive Text)
sSECustomerKey,
        HeaderName
"x-amz-server-side-encryption-customer-key-MD5"
          forall a. ToHeader a => HeaderName -> a -> ResponseHeaders
Data.=# Maybe Text
sSECustomerKeyMD5,
        HeaderName
"x-amz-server-side-encryption-context"
          forall a. ToHeader a => HeaderName -> a -> ResponseHeaders
Data.=# Maybe (Sensitive Text)
sSEKMSEncryptionContext,
        HeaderName
"x-amz-server-side-encryption-aws-kms-key-id"
          forall a. ToHeader a => HeaderName -> a -> ResponseHeaders
Data.=# Maybe (Sensitive Text)
sSEKMSKeyId,
        HeaderName
"x-amz-server-side-encryption"
          forall a. ToHeader a => HeaderName -> a -> ResponseHeaders
Data.=# Maybe ServerSideEncryption
serverSideEncryption,
        HeaderName
"x-amz-storage-class" forall a. ToHeader a => HeaderName -> a -> ResponseHeaders
Data.=# Maybe StorageClass
storageClass,
        HeaderName
"x-amz-tagging" forall a. ToHeader a => HeaderName -> a -> ResponseHeaders
Data.=# Maybe Text
tagging,
        HeaderName
"x-amz-tagging-directive" forall a. ToHeader a => HeaderName -> a -> ResponseHeaders
Data.=# Maybe TaggingDirective
taggingDirective,
        HeaderName
"x-amz-website-redirect-location"
          forall a. ToHeader a => HeaderName -> a -> ResponseHeaders
Data.=# Maybe Text
websiteRedirectLocation,
        HeaderName
"x-amz-copy-source" forall a. ToHeader a => HeaderName -> a -> ResponseHeaders
Data.=# Text
copySource
      ]
instance Data.ToPath CopyObject where
  toPath :: CopyObject -> ByteString
toPath CopyObject' {Maybe Bool
Maybe Text
Maybe (Sensitive Text)
Maybe ISO8601
Maybe RFC822
Maybe ChecksumAlgorithm
Maybe MetadataDirective
Maybe ObjectCannedACL
Maybe ObjectLockLegalHoldStatus
Maybe ObjectLockMode
Maybe RequestPayer
Maybe ServerSideEncryption
Maybe StorageClass
Maybe TaggingDirective
Text
HashMap Text Text
ObjectKey
BucketName
key :: ObjectKey
copySource :: Text
bucket :: BucketName
websiteRedirectLocation :: Maybe Text
taggingDirective :: Maybe TaggingDirective
tagging :: Maybe Text
storageClass :: Maybe StorageClass
serverSideEncryption :: Maybe ServerSideEncryption
sSEKMSKeyId :: Maybe (Sensitive Text)
sSEKMSEncryptionContext :: Maybe (Sensitive Text)
sSECustomerKeyMD5 :: Maybe Text
sSECustomerKey :: Maybe (Sensitive Text)
sSECustomerAlgorithm :: Maybe Text
requestPayer :: Maybe RequestPayer
objectLockRetainUntilDate :: Maybe ISO8601
objectLockMode :: Maybe ObjectLockMode
objectLockLegalHoldStatus :: Maybe ObjectLockLegalHoldStatus
metadataDirective :: Maybe MetadataDirective
metadata :: HashMap Text Text
grantWriteACP :: Maybe Text
grantReadACP :: Maybe Text
grantRead :: Maybe Text
grantFullControl :: Maybe Text
expires :: Maybe RFC822
expectedSourceBucketOwner :: Maybe Text
expectedBucketOwner :: Maybe Text
copySourceSSECustomerKeyMD5 :: Maybe Text
copySourceSSECustomerKey :: Maybe (Sensitive Text)
copySourceSSECustomerAlgorithm :: Maybe Text
copySourceIfUnmodifiedSince :: Maybe RFC822
copySourceIfNoneMatch :: Maybe Text
copySourceIfModifiedSince :: Maybe RFC822
copySourceIfMatch :: Maybe Text
contentType :: Maybe Text
contentLanguage :: Maybe Text
contentEncoding :: Maybe Text
contentDisposition :: Maybe Text
checksumAlgorithm :: Maybe ChecksumAlgorithm
cacheControl :: Maybe Text
bucketKeyEnabled :: Maybe Bool
acl :: Maybe ObjectCannedACL
$sel:key:CopyObject' :: CopyObject -> ObjectKey
$sel:copySource:CopyObject' :: CopyObject -> Text
$sel:bucket:CopyObject' :: CopyObject -> BucketName
$sel:websiteRedirectLocation:CopyObject' :: CopyObject -> Maybe Text
$sel:taggingDirective:CopyObject' :: CopyObject -> Maybe TaggingDirective
$sel:tagging:CopyObject' :: CopyObject -> Maybe Text
$sel:storageClass:CopyObject' :: CopyObject -> Maybe StorageClass
$sel:serverSideEncryption:CopyObject' :: CopyObject -> Maybe ServerSideEncryption
$sel:sSEKMSKeyId:CopyObject' :: CopyObject -> Maybe (Sensitive Text)
$sel:sSEKMSEncryptionContext:CopyObject' :: CopyObject -> Maybe (Sensitive Text)
$sel:sSECustomerKeyMD5:CopyObject' :: CopyObject -> Maybe Text
$sel:sSECustomerKey:CopyObject' :: CopyObject -> Maybe (Sensitive Text)
$sel:sSECustomerAlgorithm:CopyObject' :: CopyObject -> Maybe Text
$sel:requestPayer:CopyObject' :: CopyObject -> Maybe RequestPayer
$sel:objectLockRetainUntilDate:CopyObject' :: CopyObject -> Maybe ISO8601
$sel:objectLockMode:CopyObject' :: CopyObject -> Maybe ObjectLockMode
$sel:objectLockLegalHoldStatus:CopyObject' :: CopyObject -> Maybe ObjectLockLegalHoldStatus
$sel:metadataDirective:CopyObject' :: CopyObject -> Maybe MetadataDirective
$sel:metadata:CopyObject' :: CopyObject -> HashMap Text Text
$sel:grantWriteACP:CopyObject' :: CopyObject -> Maybe Text
$sel:grantReadACP:CopyObject' :: CopyObject -> Maybe Text
$sel:grantRead:CopyObject' :: CopyObject -> Maybe Text
$sel:grantFullControl:CopyObject' :: CopyObject -> Maybe Text
$sel:expires:CopyObject' :: CopyObject -> Maybe RFC822
$sel:expectedSourceBucketOwner:CopyObject' :: CopyObject -> Maybe Text
$sel:expectedBucketOwner:CopyObject' :: CopyObject -> Maybe Text
$sel:copySourceSSECustomerKeyMD5:CopyObject' :: CopyObject -> Maybe Text
$sel:copySourceSSECustomerKey:CopyObject' :: CopyObject -> Maybe (Sensitive Text)
$sel:copySourceSSECustomerAlgorithm:CopyObject' :: CopyObject -> Maybe Text
$sel:copySourceIfUnmodifiedSince:CopyObject' :: CopyObject -> Maybe RFC822
$sel:copySourceIfNoneMatch:CopyObject' :: CopyObject -> Maybe Text
$sel:copySourceIfModifiedSince:CopyObject' :: CopyObject -> Maybe RFC822
$sel:copySourceIfMatch:CopyObject' :: CopyObject -> Maybe Text
$sel:contentType:CopyObject' :: CopyObject -> Maybe Text
$sel:contentLanguage:CopyObject' :: CopyObject -> Maybe Text
$sel:contentEncoding:CopyObject' :: CopyObject -> Maybe Text
$sel:contentDisposition:CopyObject' :: CopyObject -> Maybe Text
$sel:checksumAlgorithm:CopyObject' :: CopyObject -> Maybe ChecksumAlgorithm
$sel:cacheControl:CopyObject' :: CopyObject -> Maybe Text
$sel:bucketKeyEnabled:CopyObject' :: CopyObject -> Maybe Bool
$sel:acl:CopyObject' :: CopyObject -> Maybe ObjectCannedACL
..} =
    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 CopyObject where
  toQuery :: CopyObject -> QueryString
toQuery = forall a b. a -> b -> a
Prelude.const forall a. Monoid a => a
Prelude.mempty
data CopyObjectResponse = CopyObjectResponse'
  { 
    
    CopyObjectResponse -> Maybe Bool
bucketKeyEnabled :: Prelude.Maybe Prelude.Bool,
    
    CopyObjectResponse -> Maybe CopyObjectResult
copyObjectResult :: Prelude.Maybe CopyObjectResult,
    
    CopyObjectResponse -> Maybe Text
copySourceVersionId :: Prelude.Maybe Prelude.Text,
    
    
    CopyObjectResponse -> Maybe Text
expiration :: Prelude.Maybe Prelude.Text,
    CopyObjectResponse -> Maybe RequestCharged
requestCharged :: Prelude.Maybe RequestCharged,
    
    
    
    CopyObjectResponse -> Maybe Text
sSECustomerAlgorithm :: Prelude.Maybe Prelude.Text,
    
    
    
    CopyObjectResponse -> Maybe Text
sSECustomerKeyMD5 :: Prelude.Maybe Prelude.Text,
    
    
    
    CopyObjectResponse -> Maybe (Sensitive Text)
sSEKMSEncryptionContext :: Prelude.Maybe (Data.Sensitive Prelude.Text),
    
    
    
    CopyObjectResponse -> Maybe (Sensitive Text)
sSEKMSKeyId :: Prelude.Maybe (Data.Sensitive Prelude.Text),
    
    
    CopyObjectResponse -> Maybe ServerSideEncryption
serverSideEncryption :: Prelude.Maybe ServerSideEncryption,
    
    CopyObjectResponse -> Maybe ObjectVersionId
versionId :: Prelude.Maybe ObjectVersionId,
    
    CopyObjectResponse -> Int
httpStatus :: Prelude.Int
  }
  deriving (CopyObjectResponse -> CopyObjectResponse -> Bool
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: CopyObjectResponse -> CopyObjectResponse -> Bool
$c/= :: CopyObjectResponse -> CopyObjectResponse -> Bool
== :: CopyObjectResponse -> CopyObjectResponse -> Bool
$c== :: CopyObjectResponse -> CopyObjectResponse -> Bool
Prelude.Eq, Int -> CopyObjectResponse -> ShowS
[CopyObjectResponse] -> ShowS
CopyObjectResponse -> String
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [CopyObjectResponse] -> ShowS
$cshowList :: [CopyObjectResponse] -> ShowS
show :: CopyObjectResponse -> String
$cshow :: CopyObjectResponse -> String
showsPrec :: Int -> CopyObjectResponse -> ShowS
$cshowsPrec :: Int -> CopyObjectResponse -> ShowS
Prelude.Show, forall x. Rep CopyObjectResponse x -> CopyObjectResponse
forall x. CopyObjectResponse -> Rep CopyObjectResponse x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cto :: forall x. Rep CopyObjectResponse x -> CopyObjectResponse
$cfrom :: forall x. CopyObjectResponse -> Rep CopyObjectResponse x
Prelude.Generic)
newCopyObjectResponse ::
  
  Prelude.Int ->
  CopyObjectResponse
newCopyObjectResponse :: Int -> CopyObjectResponse
newCopyObjectResponse Int
pHttpStatus_ =
  CopyObjectResponse'
    { $sel:bucketKeyEnabled:CopyObjectResponse' :: Maybe Bool
bucketKeyEnabled =
        forall a. Maybe a
Prelude.Nothing,
      $sel:copyObjectResult:CopyObjectResponse' :: Maybe CopyObjectResult
copyObjectResult = forall a. Maybe a
Prelude.Nothing,
      $sel:copySourceVersionId:CopyObjectResponse' :: Maybe Text
copySourceVersionId = forall a. Maybe a
Prelude.Nothing,
      $sel:expiration:CopyObjectResponse' :: Maybe Text
expiration = forall a. Maybe a
Prelude.Nothing,
      $sel:requestCharged:CopyObjectResponse' :: Maybe RequestCharged
requestCharged = forall a. Maybe a
Prelude.Nothing,
      $sel:sSECustomerAlgorithm:CopyObjectResponse' :: Maybe Text
sSECustomerAlgorithm = forall a. Maybe a
Prelude.Nothing,
      $sel:sSECustomerKeyMD5:CopyObjectResponse' :: Maybe Text
sSECustomerKeyMD5 = forall a. Maybe a
Prelude.Nothing,
      $sel:sSEKMSEncryptionContext:CopyObjectResponse' :: Maybe (Sensitive Text)
sSEKMSEncryptionContext = forall a. Maybe a
Prelude.Nothing,
      $sel:sSEKMSKeyId:CopyObjectResponse' :: Maybe (Sensitive Text)
sSEKMSKeyId = forall a. Maybe a
Prelude.Nothing,
      $sel:serverSideEncryption:CopyObjectResponse' :: Maybe ServerSideEncryption
serverSideEncryption = forall a. Maybe a
Prelude.Nothing,
      $sel:versionId:CopyObjectResponse' :: Maybe ObjectVersionId
versionId = forall a. Maybe a
Prelude.Nothing,
      $sel:httpStatus:CopyObjectResponse' :: Int
httpStatus = Int
pHttpStatus_
    }
copyObjectResponse_bucketKeyEnabled :: Lens.Lens' CopyObjectResponse (Prelude.Maybe Prelude.Bool)
copyObjectResponse_bucketKeyEnabled :: Lens' CopyObjectResponse (Maybe Bool)
copyObjectResponse_bucketKeyEnabled = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\CopyObjectResponse' {Maybe Bool
bucketKeyEnabled :: Maybe Bool
$sel:bucketKeyEnabled:CopyObjectResponse' :: CopyObjectResponse -> Maybe Bool
bucketKeyEnabled} -> Maybe Bool
bucketKeyEnabled) (\s :: CopyObjectResponse
s@CopyObjectResponse' {} Maybe Bool
a -> CopyObjectResponse
s {$sel:bucketKeyEnabled:CopyObjectResponse' :: Maybe Bool
bucketKeyEnabled = Maybe Bool
a} :: CopyObjectResponse)
copyObjectResponse_copyObjectResult :: Lens.Lens' CopyObjectResponse (Prelude.Maybe CopyObjectResult)
copyObjectResponse_copyObjectResult :: Lens' CopyObjectResponse (Maybe CopyObjectResult)
copyObjectResponse_copyObjectResult = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\CopyObjectResponse' {Maybe CopyObjectResult
copyObjectResult :: Maybe CopyObjectResult
$sel:copyObjectResult:CopyObjectResponse' :: CopyObjectResponse -> Maybe CopyObjectResult
copyObjectResult} -> Maybe CopyObjectResult
copyObjectResult) (\s :: CopyObjectResponse
s@CopyObjectResponse' {} Maybe CopyObjectResult
a -> CopyObjectResponse
s {$sel:copyObjectResult:CopyObjectResponse' :: Maybe CopyObjectResult
copyObjectResult = Maybe CopyObjectResult
a} :: CopyObjectResponse)
copyObjectResponse_copySourceVersionId :: Lens.Lens' CopyObjectResponse (Prelude.Maybe Prelude.Text)
copyObjectResponse_copySourceVersionId :: Lens' CopyObjectResponse (Maybe Text)
copyObjectResponse_copySourceVersionId = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\CopyObjectResponse' {Maybe Text
copySourceVersionId :: Maybe Text
$sel:copySourceVersionId:CopyObjectResponse' :: CopyObjectResponse -> Maybe Text
copySourceVersionId} -> Maybe Text
copySourceVersionId) (\s :: CopyObjectResponse
s@CopyObjectResponse' {} Maybe Text
a -> CopyObjectResponse
s {$sel:copySourceVersionId:CopyObjectResponse' :: Maybe Text
copySourceVersionId = Maybe Text
a} :: CopyObjectResponse)
copyObjectResponse_expiration :: Lens.Lens' CopyObjectResponse (Prelude.Maybe Prelude.Text)
copyObjectResponse_expiration :: Lens' CopyObjectResponse (Maybe Text)
copyObjectResponse_expiration = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\CopyObjectResponse' {Maybe Text
expiration :: Maybe Text
$sel:expiration:CopyObjectResponse' :: CopyObjectResponse -> Maybe Text
expiration} -> Maybe Text
expiration) (\s :: CopyObjectResponse
s@CopyObjectResponse' {} Maybe Text
a -> CopyObjectResponse
s {$sel:expiration:CopyObjectResponse' :: Maybe Text
expiration = Maybe Text
a} :: CopyObjectResponse)
copyObjectResponse_requestCharged :: Lens.Lens' CopyObjectResponse (Prelude.Maybe RequestCharged)
copyObjectResponse_requestCharged :: Lens' CopyObjectResponse (Maybe RequestCharged)
copyObjectResponse_requestCharged = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\CopyObjectResponse' {Maybe RequestCharged
requestCharged :: Maybe RequestCharged
$sel:requestCharged:CopyObjectResponse' :: CopyObjectResponse -> Maybe RequestCharged
requestCharged} -> Maybe RequestCharged
requestCharged) (\s :: CopyObjectResponse
s@CopyObjectResponse' {} Maybe RequestCharged
a -> CopyObjectResponse
s {$sel:requestCharged:CopyObjectResponse' :: Maybe RequestCharged
requestCharged = Maybe RequestCharged
a} :: CopyObjectResponse)
copyObjectResponse_sSECustomerAlgorithm :: Lens.Lens' CopyObjectResponse (Prelude.Maybe Prelude.Text)
copyObjectResponse_sSECustomerAlgorithm :: Lens' CopyObjectResponse (Maybe Text)
copyObjectResponse_sSECustomerAlgorithm = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\CopyObjectResponse' {Maybe Text
sSECustomerAlgorithm :: Maybe Text
$sel:sSECustomerAlgorithm:CopyObjectResponse' :: CopyObjectResponse -> Maybe Text
sSECustomerAlgorithm} -> Maybe Text
sSECustomerAlgorithm) (\s :: CopyObjectResponse
s@CopyObjectResponse' {} Maybe Text
a -> CopyObjectResponse
s {$sel:sSECustomerAlgorithm:CopyObjectResponse' :: Maybe Text
sSECustomerAlgorithm = Maybe Text
a} :: CopyObjectResponse)
copyObjectResponse_sSECustomerKeyMD5 :: Lens.Lens' CopyObjectResponse (Prelude.Maybe Prelude.Text)
copyObjectResponse_sSECustomerKeyMD5 :: Lens' CopyObjectResponse (Maybe Text)
copyObjectResponse_sSECustomerKeyMD5 = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\CopyObjectResponse' {Maybe Text
sSECustomerKeyMD5 :: Maybe Text
$sel:sSECustomerKeyMD5:CopyObjectResponse' :: CopyObjectResponse -> Maybe Text
sSECustomerKeyMD5} -> Maybe Text
sSECustomerKeyMD5) (\s :: CopyObjectResponse
s@CopyObjectResponse' {} Maybe Text
a -> CopyObjectResponse
s {$sel:sSECustomerKeyMD5:CopyObjectResponse' :: Maybe Text
sSECustomerKeyMD5 = Maybe Text
a} :: CopyObjectResponse)
copyObjectResponse_sSEKMSEncryptionContext :: Lens.Lens' CopyObjectResponse (Prelude.Maybe Prelude.Text)
copyObjectResponse_sSEKMSEncryptionContext :: Lens' CopyObjectResponse (Maybe Text)
copyObjectResponse_sSEKMSEncryptionContext = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\CopyObjectResponse' {Maybe (Sensitive Text)
sSEKMSEncryptionContext :: Maybe (Sensitive Text)
$sel:sSEKMSEncryptionContext:CopyObjectResponse' :: CopyObjectResponse -> Maybe (Sensitive Text)
sSEKMSEncryptionContext} -> Maybe (Sensitive Text)
sSEKMSEncryptionContext) (\s :: CopyObjectResponse
s@CopyObjectResponse' {} Maybe (Sensitive Text)
a -> CopyObjectResponse
s {$sel:sSEKMSEncryptionContext:CopyObjectResponse' :: Maybe (Sensitive Text)
sSEKMSEncryptionContext = Maybe (Sensitive Text)
a} :: CopyObjectResponse) forall b c a. (b -> c) -> (a -> b) -> a -> c
Prelude.. forall (f :: * -> *) (g :: * -> *) s t a b.
(Functor f, Functor g) =>
AnIso s t a b -> Iso (f s) (g t) (f a) (g b)
Lens.mapping forall a. Iso' (Sensitive a) a
Data._Sensitive
copyObjectResponse_sSEKMSKeyId :: Lens.Lens' CopyObjectResponse (Prelude.Maybe Prelude.Text)
copyObjectResponse_sSEKMSKeyId :: Lens' CopyObjectResponse (Maybe Text)
copyObjectResponse_sSEKMSKeyId = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\CopyObjectResponse' {Maybe (Sensitive Text)
sSEKMSKeyId :: Maybe (Sensitive Text)
$sel:sSEKMSKeyId:CopyObjectResponse' :: CopyObjectResponse -> Maybe (Sensitive Text)
sSEKMSKeyId} -> Maybe (Sensitive Text)
sSEKMSKeyId) (\s :: CopyObjectResponse
s@CopyObjectResponse' {} Maybe (Sensitive Text)
a -> CopyObjectResponse
s {$sel:sSEKMSKeyId:CopyObjectResponse' :: Maybe (Sensitive Text)
sSEKMSKeyId = Maybe (Sensitive Text)
a} :: CopyObjectResponse) forall b c a. (b -> c) -> (a -> b) -> a -> c
Prelude.. forall (f :: * -> *) (g :: * -> *) s t a b.
(Functor f, Functor g) =>
AnIso s t a b -> Iso (f s) (g t) (f a) (g b)
Lens.mapping forall a. Iso' (Sensitive a) a
Data._Sensitive
copyObjectResponse_serverSideEncryption :: Lens.Lens' CopyObjectResponse (Prelude.Maybe ServerSideEncryption)
copyObjectResponse_serverSideEncryption :: Lens' CopyObjectResponse (Maybe ServerSideEncryption)
copyObjectResponse_serverSideEncryption = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\CopyObjectResponse' {Maybe ServerSideEncryption
serverSideEncryption :: Maybe ServerSideEncryption
$sel:serverSideEncryption:CopyObjectResponse' :: CopyObjectResponse -> Maybe ServerSideEncryption
serverSideEncryption} -> Maybe ServerSideEncryption
serverSideEncryption) (\s :: CopyObjectResponse
s@CopyObjectResponse' {} Maybe ServerSideEncryption
a -> CopyObjectResponse
s {$sel:serverSideEncryption:CopyObjectResponse' :: Maybe ServerSideEncryption
serverSideEncryption = Maybe ServerSideEncryption
a} :: CopyObjectResponse)
copyObjectResponse_versionId :: Lens.Lens' CopyObjectResponse (Prelude.Maybe ObjectVersionId)
copyObjectResponse_versionId :: Lens' CopyObjectResponse (Maybe ObjectVersionId)
copyObjectResponse_versionId = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\CopyObjectResponse' {Maybe ObjectVersionId
versionId :: Maybe ObjectVersionId
$sel:versionId:CopyObjectResponse' :: CopyObjectResponse -> Maybe ObjectVersionId
versionId} -> Maybe ObjectVersionId
versionId) (\s :: CopyObjectResponse
s@CopyObjectResponse' {} Maybe ObjectVersionId
a -> CopyObjectResponse
s {$sel:versionId:CopyObjectResponse' :: Maybe ObjectVersionId
versionId = Maybe ObjectVersionId
a} :: CopyObjectResponse)
copyObjectResponse_httpStatus :: Lens.Lens' CopyObjectResponse Prelude.Int
copyObjectResponse_httpStatus :: Lens' CopyObjectResponse Int
copyObjectResponse_httpStatus = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\CopyObjectResponse' {Int
httpStatus :: Int
$sel:httpStatus:CopyObjectResponse' :: CopyObjectResponse -> Int
httpStatus} -> Int
httpStatus) (\s :: CopyObjectResponse
s@CopyObjectResponse' {} Int
a -> CopyObjectResponse
s {$sel:httpStatus:CopyObjectResponse' :: Int
httpStatus = Int
a} :: CopyObjectResponse)
instance Prelude.NFData CopyObjectResponse where
  rnf :: CopyObjectResponse -> ()
rnf CopyObjectResponse' {Int
Maybe Bool
Maybe Text
Maybe (Sensitive Text)
Maybe ObjectVersionId
Maybe CopyObjectResult
Maybe RequestCharged
Maybe ServerSideEncryption
httpStatus :: Int
versionId :: Maybe ObjectVersionId
serverSideEncryption :: Maybe ServerSideEncryption
sSEKMSKeyId :: Maybe (Sensitive Text)
sSEKMSEncryptionContext :: Maybe (Sensitive Text)
sSECustomerKeyMD5 :: Maybe Text
sSECustomerAlgorithm :: Maybe Text
requestCharged :: Maybe RequestCharged
expiration :: Maybe Text
copySourceVersionId :: Maybe Text
copyObjectResult :: Maybe CopyObjectResult
bucketKeyEnabled :: Maybe Bool
$sel:httpStatus:CopyObjectResponse' :: CopyObjectResponse -> Int
$sel:versionId:CopyObjectResponse' :: CopyObjectResponse -> Maybe ObjectVersionId
$sel:serverSideEncryption:CopyObjectResponse' :: CopyObjectResponse -> Maybe ServerSideEncryption
$sel:sSEKMSKeyId:CopyObjectResponse' :: CopyObjectResponse -> Maybe (Sensitive Text)
$sel:sSEKMSEncryptionContext:CopyObjectResponse' :: CopyObjectResponse -> Maybe (Sensitive Text)
$sel:sSECustomerKeyMD5:CopyObjectResponse' :: CopyObjectResponse -> Maybe Text
$sel:sSECustomerAlgorithm:CopyObjectResponse' :: CopyObjectResponse -> Maybe Text
$sel:requestCharged:CopyObjectResponse' :: CopyObjectResponse -> Maybe RequestCharged
$sel:expiration:CopyObjectResponse' :: CopyObjectResponse -> Maybe Text
$sel:copySourceVersionId:CopyObjectResponse' :: CopyObjectResponse -> Maybe Text
$sel:copyObjectResult:CopyObjectResponse' :: CopyObjectResponse -> Maybe CopyObjectResult
$sel:bucketKeyEnabled:CopyObjectResponse' :: CopyObjectResponse -> Maybe Bool
..} =
    forall a. NFData a => a -> ()
Prelude.rnf Maybe Bool
bucketKeyEnabled
      seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf Maybe CopyObjectResult
copyObjectResult
      seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf Maybe Text
copySourceVersionId
      seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf Maybe Text
expiration
      seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf Maybe RequestCharged
requestCharged
      seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf Maybe Text
sSECustomerAlgorithm
      seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf Maybe Text
sSECustomerKeyMD5
      seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf Maybe (Sensitive Text)
sSEKMSEncryptionContext
      seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf Maybe (Sensitive Text)
sSEKMSKeyId
      seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf Maybe ServerSideEncryption
serverSideEncryption
      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 Int
httpStatus