{-# LANGUAGE DeriveDataTypeable #-}
{-# LANGUAGE DeriveGeneric      #-}
{-# LANGUAGE OverloadedStrings  #-}
{-# LANGUAGE RecordWildCards    #-}
{-# LANGUAGE TypeFamilies       #-}
{-# OPTIONS_GHC -fno-warn-unused-imports #-}
{-# OPTIONS_GHC -fno-warn-unused-binds   #-}
{-# OPTIONS_GHC -fno-warn-unused-matches #-}
module Network.AWS.S3.CopyObject
    (
    
      copyObject
    , CopyObject
    
    , coCopySourceIfModifiedSince
    , coCopySourceIfUnmodifiedSince
    , coCopySourceSSECustomerKeyMD5
    , coTaggingDirective
    , coMetadataDirective
    , coExpires
    , coGrantReadACP
    , coCopySourceIfNoneMatch
    , coSSECustomerAlgorithm
    , coSSECustomerKey
    , coRequestPayer
    , coGrantWriteACP
    , coCopySourceIfMatch
    , coWebsiteRedirectLocation
    , coGrantRead
    , coStorageClass
    , coSSECustomerKeyMD5
    , coSSEKMSKeyId
    , coGrantFullControl
    , coContentEncoding
    , coTagging
    , coMetadata
    , coCacheControl
    , coContentLanguage
    , coCopySourceSSECustomerKey
    , coCopySourceSSECustomerAlgorithm
    , coACL
    , coContentDisposition
    , coServerSideEncryption
    , coContentType
    , coBucket
    , coCopySource
    , coKey
    
    , copyObjectResponse
    , CopyObjectResponse
    
    , corsRequestCharged
    , corsVersionId
    , corsExpiration
    , corsSSECustomerAlgorithm
    , corsCopySourceVersionId
    , corsSSECustomerKeyMD5
    , corsSSEKMSKeyId
    , corsServerSideEncryption
    , corsCopyObjectResult
    , corsResponseStatus
    ) where
import Network.AWS.Lens
import Network.AWS.Prelude
import Network.AWS.Request
import Network.AWS.Response
import Network.AWS.S3.Types
import Network.AWS.S3.Types.Product
data CopyObject = CopyObject'
  { _coCopySourceIfModifiedSince      :: !(Maybe RFC822)
  , _coCopySourceIfUnmodifiedSince    :: !(Maybe RFC822)
  , _coCopySourceSSECustomerKeyMD5    :: !(Maybe Text)
  , _coTaggingDirective               :: !(Maybe TaggingDirective)
  , _coMetadataDirective              :: !(Maybe MetadataDirective)
  , _coExpires                        :: !(Maybe RFC822)
  , _coGrantReadACP                   :: !(Maybe Text)
  , _coCopySourceIfNoneMatch          :: !(Maybe Text)
  , _coSSECustomerAlgorithm           :: !(Maybe Text)
  , _coSSECustomerKey                 :: !(Maybe (Sensitive Text))
  , _coRequestPayer                   :: !(Maybe RequestPayer)
  , _coGrantWriteACP                  :: !(Maybe Text)
  , _coCopySourceIfMatch              :: !(Maybe Text)
  , _coWebsiteRedirectLocation        :: !(Maybe Text)
  , _coGrantRead                      :: !(Maybe Text)
  , _coStorageClass                   :: !(Maybe StorageClass)
  , _coSSECustomerKeyMD5              :: !(Maybe Text)
  , _coSSEKMSKeyId                    :: !(Maybe (Sensitive Text))
  , _coGrantFullControl               :: !(Maybe Text)
  , _coContentEncoding                :: !(Maybe Text)
  , _coTagging                        :: !(Maybe Text)
  , _coMetadata                       :: !(Map Text Text)
  , _coCacheControl                   :: !(Maybe Text)
  , _coContentLanguage                :: !(Maybe Text)
  , _coCopySourceSSECustomerKey       :: !(Maybe (Sensitive Text))
  , _coCopySourceSSECustomerAlgorithm :: !(Maybe Text)
  , _coACL                            :: !(Maybe ObjectCannedACL)
  , _coContentDisposition             :: !(Maybe Text)
  , _coServerSideEncryption           :: !(Maybe ServerSideEncryption)
  , _coContentType                    :: !(Maybe Text)
  , _coBucket                         :: !BucketName
  , _coCopySource                     :: !Text
  , _coKey                            :: !ObjectKey
  } deriving (Eq, Show, Data, Typeable, Generic)
copyObject
    :: BucketName 
    -> Text 
    -> ObjectKey 
    -> CopyObject
copyObject pBucket_ pCopySource_ pKey_ =
  CopyObject'
    { _coCopySourceIfModifiedSince = Nothing
    , _coCopySourceIfUnmodifiedSince = Nothing
    , _coCopySourceSSECustomerKeyMD5 = Nothing
    , _coTaggingDirective = Nothing
    , _coMetadataDirective = Nothing
    , _coExpires = Nothing
    , _coGrantReadACP = Nothing
    , _coCopySourceIfNoneMatch = Nothing
    , _coSSECustomerAlgorithm = Nothing
    , _coSSECustomerKey = Nothing
    , _coRequestPayer = Nothing
    , _coGrantWriteACP = Nothing
    , _coCopySourceIfMatch = Nothing
    , _coWebsiteRedirectLocation = Nothing
    , _coGrantRead = Nothing
    , _coStorageClass = Nothing
    , _coSSECustomerKeyMD5 = Nothing
    , _coSSEKMSKeyId = Nothing
    , _coGrantFullControl = Nothing
    , _coContentEncoding = Nothing
    , _coTagging = Nothing
    , _coMetadata = mempty
    , _coCacheControl = Nothing
    , _coContentLanguage = Nothing
    , _coCopySourceSSECustomerKey = Nothing
    , _coCopySourceSSECustomerAlgorithm = Nothing
    , _coACL = Nothing
    , _coContentDisposition = Nothing
    , _coServerSideEncryption = Nothing
    , _coContentType = Nothing
    , _coBucket = pBucket_
    , _coCopySource = pCopySource_
    , _coKey = pKey_
    }
coCopySourceIfModifiedSince :: Lens' CopyObject (Maybe UTCTime)
coCopySourceIfModifiedSince = lens _coCopySourceIfModifiedSince (\ s a -> s{_coCopySourceIfModifiedSince = a}) . mapping _Time
coCopySourceIfUnmodifiedSince :: Lens' CopyObject (Maybe UTCTime)
coCopySourceIfUnmodifiedSince = lens _coCopySourceIfUnmodifiedSince (\ s a -> s{_coCopySourceIfUnmodifiedSince = a}) . mapping _Time
coCopySourceSSECustomerKeyMD5 :: Lens' CopyObject (Maybe Text)
coCopySourceSSECustomerKeyMD5 = lens _coCopySourceSSECustomerKeyMD5 (\ s a -> s{_coCopySourceSSECustomerKeyMD5 = a})
coTaggingDirective :: Lens' CopyObject (Maybe TaggingDirective)
coTaggingDirective = lens _coTaggingDirective (\ s a -> s{_coTaggingDirective = a})
coMetadataDirective :: Lens' CopyObject (Maybe MetadataDirective)
coMetadataDirective = lens _coMetadataDirective (\ s a -> s{_coMetadataDirective = a})
coExpires :: Lens' CopyObject (Maybe UTCTime)
coExpires = lens _coExpires (\ s a -> s{_coExpires = a}) . mapping _Time
coGrantReadACP :: Lens' CopyObject (Maybe Text)
coGrantReadACP = lens _coGrantReadACP (\ s a -> s{_coGrantReadACP = a})
coCopySourceIfNoneMatch :: Lens' CopyObject (Maybe Text)
coCopySourceIfNoneMatch = lens _coCopySourceIfNoneMatch (\ s a -> s{_coCopySourceIfNoneMatch = a})
coSSECustomerAlgorithm :: Lens' CopyObject (Maybe Text)
coSSECustomerAlgorithm = lens _coSSECustomerAlgorithm (\ s a -> s{_coSSECustomerAlgorithm = a})
coSSECustomerKey :: Lens' CopyObject (Maybe Text)
coSSECustomerKey = lens _coSSECustomerKey (\ s a -> s{_coSSECustomerKey = a}) . mapping _Sensitive
coRequestPayer :: Lens' CopyObject (Maybe RequestPayer)
coRequestPayer = lens _coRequestPayer (\ s a -> s{_coRequestPayer = a})
coGrantWriteACP :: Lens' CopyObject (Maybe Text)
coGrantWriteACP = lens _coGrantWriteACP (\ s a -> s{_coGrantWriteACP = a})
coCopySourceIfMatch :: Lens' CopyObject (Maybe Text)
coCopySourceIfMatch = lens _coCopySourceIfMatch (\ s a -> s{_coCopySourceIfMatch = a})
coWebsiteRedirectLocation :: Lens' CopyObject (Maybe Text)
coWebsiteRedirectLocation = lens _coWebsiteRedirectLocation (\ s a -> s{_coWebsiteRedirectLocation = a})
coGrantRead :: Lens' CopyObject (Maybe Text)
coGrantRead = lens _coGrantRead (\ s a -> s{_coGrantRead = a})
coStorageClass :: Lens' CopyObject (Maybe StorageClass)
coStorageClass = lens _coStorageClass (\ s a -> s{_coStorageClass = a})
coSSECustomerKeyMD5 :: Lens' CopyObject (Maybe Text)
coSSECustomerKeyMD5 = lens _coSSECustomerKeyMD5 (\ s a -> s{_coSSECustomerKeyMD5 = a})
coSSEKMSKeyId :: Lens' CopyObject (Maybe Text)
coSSEKMSKeyId = lens _coSSEKMSKeyId (\ s a -> s{_coSSEKMSKeyId = a}) . mapping _Sensitive
coGrantFullControl :: Lens' CopyObject (Maybe Text)
coGrantFullControl = lens _coGrantFullControl (\ s a -> s{_coGrantFullControl = a})
coContentEncoding :: Lens' CopyObject (Maybe Text)
coContentEncoding = lens _coContentEncoding (\ s a -> s{_coContentEncoding = a})
coTagging :: Lens' CopyObject (Maybe Text)
coTagging = lens _coTagging (\ s a -> s{_coTagging = a})
coMetadata :: Lens' CopyObject (HashMap Text Text)
coMetadata = lens _coMetadata (\ s a -> s{_coMetadata = a}) . _Map
coCacheControl :: Lens' CopyObject (Maybe Text)
coCacheControl = lens _coCacheControl (\ s a -> s{_coCacheControl = a})
coContentLanguage :: Lens' CopyObject (Maybe Text)
coContentLanguage = lens _coContentLanguage (\ s a -> s{_coContentLanguage = a})
coCopySourceSSECustomerKey :: Lens' CopyObject (Maybe Text)
coCopySourceSSECustomerKey = lens _coCopySourceSSECustomerKey (\ s a -> s{_coCopySourceSSECustomerKey = a}) . mapping _Sensitive
coCopySourceSSECustomerAlgorithm :: Lens' CopyObject (Maybe Text)
coCopySourceSSECustomerAlgorithm = lens _coCopySourceSSECustomerAlgorithm (\ s a -> s{_coCopySourceSSECustomerAlgorithm = a})
coACL :: Lens' CopyObject (Maybe ObjectCannedACL)
coACL = lens _coACL (\ s a -> s{_coACL = a})
coContentDisposition :: Lens' CopyObject (Maybe Text)
coContentDisposition = lens _coContentDisposition (\ s a -> s{_coContentDisposition = a})
coServerSideEncryption :: Lens' CopyObject (Maybe ServerSideEncryption)
coServerSideEncryption = lens _coServerSideEncryption (\ s a -> s{_coServerSideEncryption = a})
coContentType :: Lens' CopyObject (Maybe Text)
coContentType = lens _coContentType (\ s a -> s{_coContentType = a})
coBucket :: Lens' CopyObject BucketName
coBucket = lens _coBucket (\ s a -> s{_coBucket = a})
coCopySource :: Lens' CopyObject Text
coCopySource = lens _coCopySource (\ s a -> s{_coCopySource = a})
coKey :: Lens' CopyObject ObjectKey
coKey = lens _coKey (\ s a -> s{_coKey = a})
instance AWSRequest CopyObject where
        type Rs CopyObject = CopyObjectResponse
        request = put s3
        response
          = receiveXML
              (\ s h x ->
                 CopyObjectResponse' <$>
                   (h .#? "x-amz-request-charged") <*>
                     (h .#? "x-amz-version-id")
                     <*> (h .#? "x-amz-expiration")
                     <*>
                     (h .#?
                        "x-amz-server-side-encryption-customer-algorithm")
                     <*> (h .#? "x-amz-copy-source-version-id")
                     <*>
                     (h .#?
                        "x-amz-server-side-encryption-customer-key-MD5")
                     <*>
                     (h .#? "x-amz-server-side-encryption-aws-kms-key-id")
                     <*> (h .#? "x-amz-server-side-encryption")
                     <*> (parseXML x)
                     <*> (pure (fromEnum s)))
instance Hashable CopyObject where
instance NFData CopyObject where
instance ToHeaders CopyObject where
        toHeaders CopyObject'{..}
          = mconcat
              ["x-amz-copy-source-if-modified-since" =#
                 _coCopySourceIfModifiedSince,
               "x-amz-copy-source-if-unmodified-since" =#
                 _coCopySourceIfUnmodifiedSince,
               "x-amz-copy-source-server-side-encryption-customer-key-MD5"
                 =# _coCopySourceSSECustomerKeyMD5,
               "x-amz-tagging-directive" =# _coTaggingDirective,
               "x-amz-metadata-directive" =# _coMetadataDirective,
               "Expires" =# _coExpires,
               "x-amz-grant-read-acp" =# _coGrantReadACP,
               "x-amz-copy-source-if-none-match" =#
                 _coCopySourceIfNoneMatch,
               "x-amz-server-side-encryption-customer-algorithm" =#
                 _coSSECustomerAlgorithm,
               "x-amz-server-side-encryption-customer-key" =#
                 _coSSECustomerKey,
               "x-amz-request-payer" =# _coRequestPayer,
               "x-amz-grant-write-acp" =# _coGrantWriteACP,
               "x-amz-copy-source-if-match" =# _coCopySourceIfMatch,
               "x-amz-website-redirect-location" =#
                 _coWebsiteRedirectLocation,
               "x-amz-grant-read" =# _coGrantRead,
               "x-amz-storage-class" =# _coStorageClass,
               "x-amz-server-side-encryption-customer-key-MD5" =#
                 _coSSECustomerKeyMD5,
               "x-amz-server-side-encryption-aws-kms-key-id" =#
                 _coSSEKMSKeyId,
               "x-amz-grant-full-control" =# _coGrantFullControl,
               "Content-Encoding" =# _coContentEncoding,
               "x-amz-tagging" =# _coTagging,
               "x-amz-meta-" =# _coMetadata,
               "Cache-Control" =# _coCacheControl,
               "Content-Language" =# _coContentLanguage,
               "x-amz-copy-source-server-side-encryption-customer-key"
                 =# _coCopySourceSSECustomerKey,
               "x-amz-copy-source-server-side-encryption-customer-algorithm"
                 =# _coCopySourceSSECustomerAlgorithm,
               "x-amz-acl" =# _coACL,
               "Content-Disposition" =# _coContentDisposition,
               "x-amz-server-side-encryption" =#
                 _coServerSideEncryption,
               "Content-Type" =# _coContentType,
               "x-amz-copy-source" =# _coCopySource]
instance ToPath CopyObject where
        toPath CopyObject'{..}
          = mconcat ["/", toBS _coBucket, "/", toBS _coKey]
instance ToQuery CopyObject where
        toQuery = const mempty
data CopyObjectResponse = CopyObjectResponse'
  { _corsRequestCharged       :: !(Maybe RequestCharged)
  , _corsVersionId            :: !(Maybe ObjectVersionId)
  , _corsExpiration           :: !(Maybe Text)
  , _corsSSECustomerAlgorithm :: !(Maybe Text)
  , _corsCopySourceVersionId  :: !(Maybe Text)
  , _corsSSECustomerKeyMD5    :: !(Maybe Text)
  , _corsSSEKMSKeyId          :: !(Maybe (Sensitive Text))
  , _corsServerSideEncryption :: !(Maybe ServerSideEncryption)
  , _corsCopyObjectResult     :: !(Maybe CopyObjectResult)
  , _corsResponseStatus       :: !Int
  } deriving (Eq, Show, Data, Typeable, Generic)
copyObjectResponse
    :: Int 
    -> CopyObjectResponse
copyObjectResponse pResponseStatus_ =
  CopyObjectResponse'
    { _corsRequestCharged = Nothing
    , _corsVersionId = Nothing
    , _corsExpiration = Nothing
    , _corsSSECustomerAlgorithm = Nothing
    , _corsCopySourceVersionId = Nothing
    , _corsSSECustomerKeyMD5 = Nothing
    , _corsSSEKMSKeyId = Nothing
    , _corsServerSideEncryption = Nothing
    , _corsCopyObjectResult = Nothing
    , _corsResponseStatus = pResponseStatus_
    }
corsRequestCharged :: Lens' CopyObjectResponse (Maybe RequestCharged)
corsRequestCharged = lens _corsRequestCharged (\ s a -> s{_corsRequestCharged = a})
corsVersionId :: Lens' CopyObjectResponse (Maybe ObjectVersionId)
corsVersionId = lens _corsVersionId (\ s a -> s{_corsVersionId = a})
corsExpiration :: Lens' CopyObjectResponse (Maybe Text)
corsExpiration = lens _corsExpiration (\ s a -> s{_corsExpiration = a})
corsSSECustomerAlgorithm :: Lens' CopyObjectResponse (Maybe Text)
corsSSECustomerAlgorithm = lens _corsSSECustomerAlgorithm (\ s a -> s{_corsSSECustomerAlgorithm = a})
corsCopySourceVersionId :: Lens' CopyObjectResponse (Maybe Text)
corsCopySourceVersionId = lens _corsCopySourceVersionId (\ s a -> s{_corsCopySourceVersionId = a})
corsSSECustomerKeyMD5 :: Lens' CopyObjectResponse (Maybe Text)
corsSSECustomerKeyMD5 = lens _corsSSECustomerKeyMD5 (\ s a -> s{_corsSSECustomerKeyMD5 = a})
corsSSEKMSKeyId :: Lens' CopyObjectResponse (Maybe Text)
corsSSEKMSKeyId = lens _corsSSEKMSKeyId (\ s a -> s{_corsSSEKMSKeyId = a}) . mapping _Sensitive
corsServerSideEncryption :: Lens' CopyObjectResponse (Maybe ServerSideEncryption)
corsServerSideEncryption = lens _corsServerSideEncryption (\ s a -> s{_corsServerSideEncryption = a})
corsCopyObjectResult :: Lens' CopyObjectResponse (Maybe CopyObjectResult)
corsCopyObjectResult = lens _corsCopyObjectResult (\ s a -> s{_corsCopyObjectResult = a})
corsResponseStatus :: Lens' CopyObjectResponse Int
corsResponseStatus = lens _corsResponseStatus (\ s a -> s{_corsResponseStatus = a})
instance NFData CopyObjectResponse where