module Network.AWS.S3.UploadPartCopy
    (
    
      UploadPartCopy
    
    , uploadPartCopy
    
    , upcBucket
    , upcCopySource
    , upcCopySourceIfMatch
    , upcCopySourceIfModifiedSince
    , upcCopySourceIfNoneMatch
    , upcCopySourceIfUnmodifiedSince
    , upcCopySourceRange
    , upcCopySourceSSECustomerAlgorithm
    , upcCopySourceSSECustomerKey
    , upcCopySourceSSECustomerKeyMD5
    , upcCopySourceSSEKMSKeyId
    , upcKey
    , upcPartNumber
    , upcSSECustomerAlgorithm
    , upcSSECustomerKey
    , upcSSECustomerKeyMD5
    , upcUploadId
    
    , UploadPartCopyResponse
    
    , uploadPartCopyResponse
    
    , upcrCopyPartResult
    , upcrCopySourceVersionId
    , upcrSSECustomerAlgorithm
    , upcrSSECustomerKeyMD5
    , upcrSSEKMSKeyId
    , upcrServerSideEncryption
    ) where
import Network.AWS.Prelude
import Network.AWS.Request.S3
import Network.AWS.S3.Types
import qualified GHC.Exts
data UploadPartCopy = UploadPartCopy
    { _upcBucket                         :: Text
    , _upcCopySource                     :: Text
    , _upcCopySourceIfMatch              :: Maybe Text
    , _upcCopySourceIfModifiedSince      :: Maybe RFC822
    , _upcCopySourceIfNoneMatch          :: Maybe Text
    , _upcCopySourceIfUnmodifiedSince    :: Maybe RFC822
    , _upcCopySourceRange                :: Maybe Text
    , _upcCopySourceSSECustomerAlgorithm :: Maybe Text
    , _upcCopySourceSSECustomerKey       :: Maybe (Sensitive Text)
    , _upcCopySourceSSECustomerKeyMD5    :: Maybe Text
    , _upcCopySourceSSEKMSKeyId          :: Maybe (Sensitive Text)
    , _upcKey                            :: Text
    , _upcPartNumber                     :: Int
    , _upcSSECustomerAlgorithm           :: Maybe Text
    , _upcSSECustomerKey                 :: Maybe (Sensitive Text)
    , _upcSSECustomerKeyMD5              :: Maybe Text
    , _upcUploadId                       :: Text
    } deriving (Eq, Ord, Show)
uploadPartCopy :: Text 
               -> Text 
               -> Text 
               -> Int 
               -> Text 
               -> UploadPartCopy
uploadPartCopy p1 p2 p3 p4 p5 = UploadPartCopy
    { _upcBucket                         = p1
    , _upcCopySource                     = p2
    , _upcKey                            = p3
    , _upcPartNumber                     = p4
    , _upcUploadId                       = p5
    , _upcCopySourceIfMatch              = Nothing
    , _upcCopySourceIfModifiedSince      = Nothing
    , _upcCopySourceIfNoneMatch          = Nothing
    , _upcCopySourceIfUnmodifiedSince    = Nothing
    , _upcCopySourceRange                = Nothing
    , _upcSSECustomerAlgorithm           = Nothing
    , _upcSSECustomerKey                 = Nothing
    , _upcSSECustomerKeyMD5              = Nothing
    , _upcCopySourceSSECustomerAlgorithm = Nothing
    , _upcCopySourceSSECustomerKey       = Nothing
    , _upcCopySourceSSECustomerKeyMD5    = Nothing
    , _upcCopySourceSSEKMSKeyId          = Nothing
    }
upcBucket :: Lens' UploadPartCopy Text
upcBucket = lens _upcBucket (\s a -> s { _upcBucket = a })
upcCopySource :: Lens' UploadPartCopy Text
upcCopySource = lens _upcCopySource (\s a -> s { _upcCopySource = a })
upcCopySourceIfMatch :: Lens' UploadPartCopy (Maybe Text)
upcCopySourceIfMatch =
    lens _upcCopySourceIfMatch (\s a -> s { _upcCopySourceIfMatch = a })
upcCopySourceIfModifiedSince :: Lens' UploadPartCopy (Maybe UTCTime)
upcCopySourceIfModifiedSince =
    lens _upcCopySourceIfModifiedSince
        (\s a -> s { _upcCopySourceIfModifiedSince = a })
            . mapping _Time
upcCopySourceIfNoneMatch :: Lens' UploadPartCopy (Maybe Text)
upcCopySourceIfNoneMatch =
    lens _upcCopySourceIfNoneMatch
        (\s a -> s { _upcCopySourceIfNoneMatch = a })
upcCopySourceIfUnmodifiedSince :: Lens' UploadPartCopy (Maybe UTCTime)
upcCopySourceIfUnmodifiedSince =
    lens _upcCopySourceIfUnmodifiedSince
        (\s a -> s { _upcCopySourceIfUnmodifiedSince = a })
            . mapping _Time
upcCopySourceRange :: Lens' UploadPartCopy (Maybe Text)
upcCopySourceRange =
    lens _upcCopySourceRange (\s a -> s { _upcCopySourceRange = a })
upcCopySourceSSECustomerAlgorithm :: Lens' UploadPartCopy (Maybe Text)
upcCopySourceSSECustomerAlgorithm =
    lens _upcCopySourceSSECustomerAlgorithm
        (\s a -> s { _upcCopySourceSSECustomerAlgorithm = a })
upcCopySourceSSECustomerKey :: Lens' UploadPartCopy (Maybe Text)
upcCopySourceSSECustomerKey =
    lens _upcCopySourceSSECustomerKey
        (\s a -> s { _upcCopySourceSSECustomerKey = a })
            . mapping _Sensitive
upcCopySourceSSECustomerKeyMD5 :: Lens' UploadPartCopy (Maybe Text)
upcCopySourceSSECustomerKeyMD5 =
    lens _upcCopySourceSSECustomerKeyMD5
        (\s a -> s { _upcCopySourceSSECustomerKeyMD5 = a })
upcCopySourceSSEKMSKeyId :: Lens' UploadPartCopy (Maybe Text)
upcCopySourceSSEKMSKeyId =
    lens _upcCopySourceSSEKMSKeyId
        (\s a -> s { _upcCopySourceSSEKMSKeyId = a })
            . mapping _Sensitive
upcKey :: Lens' UploadPartCopy Text
upcKey = lens _upcKey (\s a -> s { _upcKey = a })
upcPartNumber :: Lens' UploadPartCopy Int
upcPartNumber = lens _upcPartNumber (\s a -> s { _upcPartNumber = a })
upcSSECustomerAlgorithm :: Lens' UploadPartCopy (Maybe Text)
upcSSECustomerAlgorithm =
    lens _upcSSECustomerAlgorithm (\s a -> s { _upcSSECustomerAlgorithm = a })
upcSSECustomerKey :: Lens' UploadPartCopy (Maybe Text)
upcSSECustomerKey =
    lens _upcSSECustomerKey (\s a -> s { _upcSSECustomerKey = a })
        . mapping _Sensitive
upcSSECustomerKeyMD5 :: Lens' UploadPartCopy (Maybe Text)
upcSSECustomerKeyMD5 =
    lens _upcSSECustomerKeyMD5 (\s a -> s { _upcSSECustomerKeyMD5 = a })
upcUploadId :: Lens' UploadPartCopy Text
upcUploadId = lens _upcUploadId (\s a -> s { _upcUploadId = a })
data UploadPartCopyResponse = UploadPartCopyResponse
    { _upcrCopyPartResult       :: Maybe CopyPartResult
    , _upcrCopySourceVersionId  :: Maybe Text
    , _upcrSSECustomerAlgorithm :: Maybe Text
    , _upcrSSECustomerKeyMD5    :: Maybe Text
    , _upcrSSEKMSKeyId          :: Maybe (Sensitive Text)
    , _upcrServerSideEncryption :: Maybe ServerSideEncryption
    } deriving (Eq, Show)
uploadPartCopyResponse :: UploadPartCopyResponse
uploadPartCopyResponse = UploadPartCopyResponse
    { _upcrCopySourceVersionId  = Nothing
    , _upcrCopyPartResult       = Nothing
    , _upcrServerSideEncryption = Nothing
    , _upcrSSECustomerAlgorithm = Nothing
    , _upcrSSECustomerKeyMD5    = Nothing
    , _upcrSSEKMSKeyId          = Nothing
    }
upcrCopyPartResult :: Lens' UploadPartCopyResponse (Maybe CopyPartResult)
upcrCopyPartResult =
    lens _upcrCopyPartResult (\s a -> s { _upcrCopyPartResult = a })
upcrCopySourceVersionId :: Lens' UploadPartCopyResponse (Maybe Text)
upcrCopySourceVersionId =
    lens _upcrCopySourceVersionId (\s a -> s { _upcrCopySourceVersionId = a })
upcrSSECustomerAlgorithm :: Lens' UploadPartCopyResponse (Maybe Text)
upcrSSECustomerAlgorithm =
    lens _upcrSSECustomerAlgorithm
        (\s a -> s { _upcrSSECustomerAlgorithm = a })
upcrSSECustomerKeyMD5 :: Lens' UploadPartCopyResponse (Maybe Text)
upcrSSECustomerKeyMD5 =
    lens _upcrSSECustomerKeyMD5 (\s a -> s { _upcrSSECustomerKeyMD5 = a })
upcrSSEKMSKeyId :: Lens' UploadPartCopyResponse (Maybe Text)
upcrSSEKMSKeyId = lens _upcrSSEKMSKeyId (\s a -> s { _upcrSSEKMSKeyId = a }) . mapping _Sensitive
upcrServerSideEncryption :: Lens' UploadPartCopyResponse (Maybe ServerSideEncryption)
upcrServerSideEncryption =
    lens _upcrServerSideEncryption
        (\s a -> s { _upcrServerSideEncryption = a })
instance ToPath UploadPartCopy where
    toPath UploadPartCopy{..} = mconcat
        [ "/"
        , toText _upcBucket
        , "/"
        , toText _upcKey
        ]
instance ToQuery UploadPartCopy where
    toQuery UploadPartCopy{..} = mconcat
        [ "partNumber" =? _upcPartNumber
        , "uploadId"   =? _upcUploadId
        ]
instance ToHeaders UploadPartCopy where
    toHeaders UploadPartCopy{..} = mconcat
        [ "x-amz-copy-source"                                           =: _upcCopySource
        , "x-amz-copy-source-if-match"                                  =: _upcCopySourceIfMatch
        , "x-amz-copy-source-if-modified-since"                         =: _upcCopySourceIfModifiedSince
        , "x-amz-copy-source-if-none-match"                             =: _upcCopySourceIfNoneMatch
        , "x-amz-copy-source-if-unmodified-since"                       =: _upcCopySourceIfUnmodifiedSince
        , "x-amz-copy-source-range"                                     =: _upcCopySourceRange
        , "x-amz-server-side-encryption-customer-algorithm"             =: _upcSSECustomerAlgorithm
        , "x-amz-server-side-encryption-customer-key"                   =: _upcSSECustomerKey
        , "x-amz-server-side-encryption-customer-key-MD5"               =: _upcSSECustomerKeyMD5
        , "x-amz-copy-source-server-side-encryption-customer-algorithm" =: _upcCopySourceSSECustomerAlgorithm
        , "x-amz-copy-source-server-side-encryption-customer-key"       =: _upcCopySourceSSECustomerKey
        , "x-amz-copy-source-server-side-encryption-customer-key-MD5"   =: _upcCopySourceSSECustomerKeyMD5
        , "x-amz-server-side-encryption-aws-kms-key-id"                 =: _upcCopySourceSSEKMSKeyId
        ]
instance ToXMLRoot UploadPartCopy where
    toXMLRoot = const (namespaced ns "UploadPartCopy" [])
instance ToXML UploadPartCopy
instance AWSRequest UploadPartCopy where
    type Sv UploadPartCopy = S3
    type Rs UploadPartCopy = UploadPartCopyResponse
    request  = put
    response = xmlHeaderResponse $ \h x -> UploadPartCopyResponse
        <$> x .@? "CopyPartResult"
        <*> h ~:? "x-amz-copy-source-version-id"
        <*> 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"