module Network.AWS.S3.CopyObject
    (
    
      CopyObject
    
    , copyObject
    
    , coACL
    , coBucket
    , coCacheControl
    , coContentDisposition
    , coContentEncoding
    , coContentLanguage
    , coContentType
    , coCopySource
    , coCopySourceIfMatch
    , coCopySourceIfModifiedSince
    , coCopySourceIfNoneMatch
    , coCopySourceIfUnmodifiedSince
    , coCopySourceSSECustomerAlgorithm
    , coCopySourceSSECustomerKey
    , coCopySourceSSECustomerKeyMD5
    , coCopySourceSSEKMSKeyId
    , coExpires
    , coGrantFullControl
    , coGrantRead
    , coGrantReadACP
    , coGrantWriteACP
    , coKey
    , coMetadata
    , coMetadataDirective
    , coSSECustomerAlgorithm
    , coSSECustomerKey
    , coSSECustomerKeyMD5
    , coServerSideEncryption
    , coStorageClass
    , coWebsiteRedirectLocation
    
    , CopyObjectResponse
    
    , copyObjectResponse
    
    , corCopyObjectResult
    , corCopySourceVersionId
    , corExpiration
    , corSSECustomerAlgorithm
    , corSSECustomerKeyMD5
    , corSSEKMSKeyId
    , corServerSideEncryption
    ) where
import Network.AWS.Prelude
import Network.AWS.Request.S3
import Network.AWS.S3.Types
import qualified GHC.Exts
data CopyObject = CopyObject
    { _coACL                            :: Maybe ObjectCannedACL
    , _coBucket                         :: Text
    , _coCacheControl                   :: Maybe Text
    , _coContentDisposition             :: Maybe Text
    , _coContentEncoding                :: Maybe Text
    , _coContentLanguage                :: Maybe Text
    , _coContentType                    :: Maybe Text
    , _coCopySource                     :: Text
    , _coCopySourceIfMatch              :: Maybe Text
    , _coCopySourceIfModifiedSince      :: Maybe RFC822
    , _coCopySourceIfNoneMatch          :: Maybe Text
    , _coCopySourceIfUnmodifiedSince    :: Maybe RFC822
    , _coCopySourceSSECustomerAlgorithm :: Maybe Text
    , _coCopySourceSSECustomerKey       :: Maybe (Sensitive Text)
    , _coCopySourceSSECustomerKeyMD5    :: Maybe Text
    , _coCopySourceSSEKMSKeyId          :: Maybe (Sensitive Text)
    , _coExpires                        :: Maybe RFC822
    , _coGrantFullControl               :: Maybe Text
    , _coGrantRead                      :: Maybe Text
    , _coGrantReadACP                   :: Maybe Text
    , _coGrantWriteACP                  :: Maybe Text
    , _coKey                            :: Text
    , _coMetadata                       :: Map (CI Text) Text
    , _coMetadataDirective              :: Maybe MetadataDirective
    , _coSSECustomerAlgorithm           :: Maybe Text
    , _coSSECustomerKey                 :: Maybe (Sensitive Text)
    , _coSSECustomerKeyMD5              :: Maybe Text
    , _coServerSideEncryption           :: Maybe ServerSideEncryption
    , _coStorageClass                   :: Maybe StorageClass
    , _coWebsiteRedirectLocation        :: Maybe Text
    } deriving (Eq, Show)
copyObject :: Text 
           -> Text 
           -> Text 
           -> CopyObject
copyObject p1 p2 p3 = CopyObject
    { _coBucket                         = p1
    , _coCopySource                     = p2
    , _coKey                            = p3
    , _coACL                            = Nothing
    , _coCacheControl                   = Nothing
    , _coContentDisposition             = Nothing
    , _coContentEncoding                = Nothing
    , _coContentLanguage                = Nothing
    , _coContentType                    = Nothing
    , _coCopySourceIfMatch              = Nothing
    , _coCopySourceIfModifiedSince      = Nothing
    , _coCopySourceIfNoneMatch          = Nothing
    , _coCopySourceIfUnmodifiedSince    = Nothing
    , _coExpires                        = Nothing
    , _coGrantFullControl               = Nothing
    , _coGrantRead                      = Nothing
    , _coGrantReadACP                   = Nothing
    , _coGrantWriteACP                  = Nothing
    , _coMetadata                       = mempty
    , _coMetadataDirective              = Nothing
    , _coServerSideEncryption           = Nothing
    , _coStorageClass                   = Nothing
    , _coWebsiteRedirectLocation        = Nothing
    , _coSSECustomerAlgorithm           = Nothing
    , _coSSECustomerKey                 = Nothing
    , _coSSECustomerKeyMD5              = Nothing
    , _coCopySourceSSECustomerAlgorithm = Nothing
    , _coCopySourceSSECustomerKey       = Nothing
    , _coCopySourceSSECustomerKeyMD5    = Nothing
    , _coCopySourceSSEKMSKeyId          = Nothing
    }
coACL :: Lens' CopyObject (Maybe ObjectCannedACL)
coACL = lens _coACL (\s a -> s { _coACL = a })
coBucket :: Lens' CopyObject Text
coBucket = lens _coBucket (\s a -> s { _coBucket = a })
coCacheControl :: Lens' CopyObject (Maybe Text)
coCacheControl = lens _coCacheControl (\s a -> s { _coCacheControl = a })
coContentDisposition :: Lens' CopyObject (Maybe Text)
coContentDisposition =
    lens _coContentDisposition (\s a -> s { _coContentDisposition = a })
coContentEncoding :: Lens' CopyObject (Maybe Text)
coContentEncoding =
    lens _coContentEncoding (\s a -> s { _coContentEncoding = a })
coContentLanguage :: Lens' CopyObject (Maybe Text)
coContentLanguage =
    lens _coContentLanguage (\s a -> s { _coContentLanguage = a })
coContentType :: Lens' CopyObject (Maybe Text)
coContentType = lens _coContentType (\s a -> s { _coContentType = a })
coCopySource :: Lens' CopyObject Text
coCopySource = lens _coCopySource (\s a -> s { _coCopySource = a })
coCopySourceIfMatch :: Lens' CopyObject (Maybe Text)
coCopySourceIfMatch =
    lens _coCopySourceIfMatch (\s a -> s { _coCopySourceIfMatch = a })
coCopySourceIfModifiedSince :: Lens' CopyObject (Maybe UTCTime)
coCopySourceIfModifiedSince =
    lens _coCopySourceIfModifiedSince
        (\s a -> s { _coCopySourceIfModifiedSince = a })
            . mapping _Time
coCopySourceIfNoneMatch :: Lens' CopyObject (Maybe Text)
coCopySourceIfNoneMatch =
    lens _coCopySourceIfNoneMatch (\s a -> s { _coCopySourceIfNoneMatch = a })
coCopySourceIfUnmodifiedSince :: Lens' CopyObject (Maybe UTCTime)
coCopySourceIfUnmodifiedSince =
    lens _coCopySourceIfUnmodifiedSince
        (\s a -> s { _coCopySourceIfUnmodifiedSince = a })
            . mapping _Time
coCopySourceSSECustomerAlgorithm :: Lens' CopyObject (Maybe Text)
coCopySourceSSECustomerAlgorithm =
    lens _coCopySourceSSECustomerAlgorithm
        (\s a -> s { _coCopySourceSSECustomerAlgorithm = a })
coCopySourceSSECustomerKey :: Lens' CopyObject (Maybe Text)
coCopySourceSSECustomerKey =
    lens _coCopySourceSSECustomerKey
        (\s a -> s { _coCopySourceSSECustomerKey = a })
            . mapping _Sensitive
coCopySourceSSECustomerKeyMD5 :: Lens' CopyObject (Maybe Text)
coCopySourceSSECustomerKeyMD5 =
    lens _coCopySourceSSECustomerKeyMD5
        (\s a -> s { _coCopySourceSSECustomerKeyMD5 = a })
coCopySourceSSEKMSKeyId :: Lens' CopyObject (Maybe Text)
coCopySourceSSEKMSKeyId =
    lens _coCopySourceSSEKMSKeyId (\s a -> s { _coCopySourceSSEKMSKeyId = a })
        . mapping _Sensitive
coExpires :: Lens' CopyObject (Maybe UTCTime)
coExpires = lens _coExpires (\s a -> s { _coExpires = a }) . mapping _Time
coGrantFullControl :: Lens' CopyObject (Maybe Text)
coGrantFullControl =
    lens _coGrantFullControl (\s a -> s { _coGrantFullControl = a })
coGrantRead :: Lens' CopyObject (Maybe Text)
coGrantRead = lens _coGrantRead (\s a -> s { _coGrantRead = a })
coGrantReadACP :: Lens' CopyObject (Maybe Text)
coGrantReadACP = lens _coGrantReadACP (\s a -> s { _coGrantReadACP = a })
coGrantWriteACP :: Lens' CopyObject (Maybe Text)
coGrantWriteACP = lens _coGrantWriteACP (\s a -> s { _coGrantWriteACP = a })
coKey :: Lens' CopyObject Text
coKey = lens _coKey (\s a -> s { _coKey = a })
coMetadata :: Lens' CopyObject (HashMap (CI Text) Text)
coMetadata = lens _coMetadata (\s a -> s { _coMetadata = a }) . _Map
coMetadataDirective :: Lens' CopyObject (Maybe MetadataDirective)
coMetadataDirective =
    lens _coMetadataDirective (\s a -> s { _coMetadataDirective = 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
coSSECustomerKeyMD5 :: Lens' CopyObject (Maybe Text)
coSSECustomerKeyMD5 =
    lens _coSSECustomerKeyMD5 (\s a -> s { _coSSECustomerKeyMD5 = a })
coServerSideEncryption :: Lens' CopyObject (Maybe ServerSideEncryption)
coServerSideEncryption =
    lens _coServerSideEncryption (\s a -> s { _coServerSideEncryption = a })
coStorageClass :: Lens' CopyObject (Maybe StorageClass)
coStorageClass = lens _coStorageClass (\s a -> s { _coStorageClass = a })
coWebsiteRedirectLocation :: Lens' CopyObject (Maybe Text)
coWebsiteRedirectLocation =
    lens _coWebsiteRedirectLocation
        (\s a -> s { _coWebsiteRedirectLocation = a })
data CopyObjectResponse = CopyObjectResponse
    { _corCopyObjectResult     :: Maybe CopyObjectResult
    , _corCopySourceVersionId  :: Maybe Text
    , _corExpiration           :: Maybe RFC822
    , _corSSECustomerAlgorithm :: Maybe Text
    , _corSSECustomerKeyMD5    :: Maybe Text
    , _corSSEKMSKeyId          :: Maybe (Sensitive Text)
    , _corServerSideEncryption :: Maybe ServerSideEncryption
    } deriving (Eq, Show)
copyObjectResponse :: CopyObjectResponse
copyObjectResponse = CopyObjectResponse
    { _corCopyObjectResult     = Nothing
    , _corExpiration           = Nothing
    , _corCopySourceVersionId  = Nothing
    , _corServerSideEncryption = Nothing
    , _corSSECustomerAlgorithm = Nothing
    , _corSSECustomerKeyMD5    = Nothing
    , _corSSEKMSKeyId          = Nothing
    }
corCopyObjectResult :: Lens' CopyObjectResponse (Maybe CopyObjectResult)
corCopyObjectResult =
    lens _corCopyObjectResult (\s a -> s { _corCopyObjectResult = a })
corCopySourceVersionId :: Lens' CopyObjectResponse (Maybe Text)
corCopySourceVersionId =
    lens _corCopySourceVersionId (\s a -> s { _corCopySourceVersionId = a })
corExpiration :: Lens' CopyObjectResponse (Maybe UTCTime)
corExpiration = lens _corExpiration (\s a -> s { _corExpiration = a }) . mapping _Time
corSSECustomerAlgorithm :: Lens' CopyObjectResponse (Maybe Text)
corSSECustomerAlgorithm =
    lens _corSSECustomerAlgorithm (\s a -> s { _corSSECustomerAlgorithm = a })
corSSECustomerKeyMD5 :: Lens' CopyObjectResponse (Maybe Text)
corSSECustomerKeyMD5 =
    lens _corSSECustomerKeyMD5 (\s a -> s { _corSSECustomerKeyMD5 = a })
corSSEKMSKeyId :: Lens' CopyObjectResponse (Maybe Text)
corSSEKMSKeyId = lens _corSSEKMSKeyId (\s a -> s { _corSSEKMSKeyId = a }) . mapping _Sensitive
corServerSideEncryption :: Lens' CopyObjectResponse (Maybe ServerSideEncryption)
corServerSideEncryption =
    lens _corServerSideEncryption (\s a -> s { _corServerSideEncryption = a })
instance ToPath CopyObject where
    toPath CopyObject{..} = mconcat
        [ "/"
        , toText _coBucket
        , "/"
        , toText _coKey
        ]
instance ToQuery CopyObject where
    toQuery = const mempty
instance ToHeaders CopyObject where
    toHeaders CopyObject{..} = mconcat
        [ "x-amz-acl"                                                   =: _coACL
        , "Cache-Control"                                               =: _coCacheControl
        , "Content-Disposition"                                         =: _coContentDisposition
        , "Content-Encoding"                                            =: _coContentEncoding
        , "Content-Language"                                            =: _coContentLanguage
        , "Content-Type"                                                =: _coContentType
        , "x-amz-copy-source"                                           =: _coCopySource
        , "x-amz-copy-source-if-match"                                  =: _coCopySourceIfMatch
        , "x-amz-copy-source-if-modified-since"                         =: _coCopySourceIfModifiedSince
        , "x-amz-copy-source-if-none-match"                             =: _coCopySourceIfNoneMatch
        , "x-amz-copy-source-if-unmodified-since"                       =: _coCopySourceIfUnmodifiedSince
        , "Expires"                                                     =: _coExpires
        , "x-amz-grant-full-control"                                    =: _coGrantFullControl
        , "x-amz-grant-read"                                            =: _coGrantRead
        , "x-amz-grant-read-acp"                                        =: _coGrantReadACP
        , "x-amz-grant-write-acp"                                       =: _coGrantWriteACP
        , "x-amz-meta-"                                                 =: _coMetadata
        , "x-amz-metadata-directive"                                    =: _coMetadataDirective
        , "x-amz-server-side-encryption"                                =: _coServerSideEncryption
        , "x-amz-storage-class"                                         =: _coStorageClass
        , "x-amz-website-redirect-location"                             =: _coWebsiteRedirectLocation
        , "x-amz-server-side-encryption-customer-algorithm"             =: _coSSECustomerAlgorithm
        , "x-amz-server-side-encryption-customer-key"                   =: _coSSECustomerKey
        , "x-amz-server-side-encryption-customer-key-MD5"               =: _coSSECustomerKeyMD5
        , "x-amz-copy-source-server-side-encryption-customer-algorithm" =: _coCopySourceSSECustomerAlgorithm
        , "x-amz-copy-source-server-side-encryption-customer-key"       =: _coCopySourceSSECustomerKey
        , "x-amz-copy-source-server-side-encryption-customer-key-MD5"   =: _coCopySourceSSECustomerKeyMD5
        , "x-amz-copy-source-server-side-encryption-aws-kms-key-id"     =: _coCopySourceSSEKMSKeyId
        ]
instance ToXMLRoot CopyObject where
    toXMLRoot = const (namespaced ns "CopyObject" [])
instance ToXML CopyObject
instance AWSRequest CopyObject where
    type Sv CopyObject = S3
    type Rs CopyObject = CopyObjectResponse
    request  = put
    response = xmlHeaderResponse $ \h x -> CopyObjectResponse
        <$> x .@? "CopyObjectResult"
        <*> h ~:? "x-amz-copy-source-version-id"
        <*> h ~:? "x-amz-expiration"
        <*> h ~:? "x-amz-server-side-encryption-customer-algorithm"
        <*> 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"