{-# 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.PutObjectTagging
(
putObjectTagging
, PutObjectTagging
, potVersionId
, potContentMD5
, potBucket
, potKey
, potTagging
, putObjectTaggingResponse
, PutObjectTaggingResponse
, potrsVersionId
, potrsResponseStatus
) 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 PutObjectTagging = PutObjectTagging'
{ _potVersionId :: !(Maybe ObjectVersionId)
, _potContentMD5 :: !(Maybe Text)
, _potBucket :: !BucketName
, _potKey :: !ObjectKey
, _potTagging :: !Tagging
} deriving (Eq, Read, Show, Data, Typeable, Generic)
putObjectTagging
:: BucketName
-> ObjectKey
-> Tagging
-> PutObjectTagging
putObjectTagging pBucket_ pKey_ pTagging_ =
PutObjectTagging'
{ _potVersionId = Nothing
, _potContentMD5 = Nothing
, _potBucket = pBucket_
, _potKey = pKey_
, _potTagging = pTagging_
}
potVersionId :: Lens' PutObjectTagging (Maybe ObjectVersionId)
potVersionId = lens _potVersionId (\ s a -> s{_potVersionId = a})
potContentMD5 :: Lens' PutObjectTagging (Maybe Text)
potContentMD5 = lens _potContentMD5 (\ s a -> s{_potContentMD5 = a})
potBucket :: Lens' PutObjectTagging BucketName
potBucket = lens _potBucket (\ s a -> s{_potBucket = a})
potKey :: Lens' PutObjectTagging ObjectKey
potKey = lens _potKey (\ s a -> s{_potKey = a})
potTagging :: Lens' PutObjectTagging Tagging
potTagging = lens _potTagging (\ s a -> s{_potTagging = a})
instance AWSRequest PutObjectTagging where
type Rs PutObjectTagging = PutObjectTaggingResponse
request = putXML s3
response
= receiveEmpty
(\ s h x ->
PutObjectTaggingResponse' <$>
(h .#? "x-amz-version-id") <*> (pure (fromEnum s)))
instance Hashable PutObjectTagging where
instance NFData PutObjectTagging where
instance ToElement PutObjectTagging where
toElement
= mkElement
"{http://s3.amazonaws.com/doc/2006-03-01/}Tagging"
.
_potTagging
instance ToHeaders PutObjectTagging where
toHeaders PutObjectTagging'{..}
= mconcat ["Content-MD5" =# _potContentMD5]
instance ToPath PutObjectTagging where
toPath PutObjectTagging'{..}
= mconcat ["/", toBS _potBucket, "/", toBS _potKey]
instance ToQuery PutObjectTagging where
toQuery PutObjectTagging'{..}
= mconcat ["versionId" =: _potVersionId, "tagging"]
data PutObjectTaggingResponse = PutObjectTaggingResponse'
{ _potrsVersionId :: !(Maybe ObjectVersionId)
, _potrsResponseStatus :: !Int
} deriving (Eq, Read, Show, Data, Typeable, Generic)
putObjectTaggingResponse
:: Int
-> PutObjectTaggingResponse
putObjectTaggingResponse pResponseStatus_ =
PutObjectTaggingResponse'
{_potrsVersionId = Nothing, _potrsResponseStatus = pResponseStatus_}
potrsVersionId :: Lens' PutObjectTaggingResponse (Maybe ObjectVersionId)
potrsVersionId = lens _potrsVersionId (\ s a -> s{_potrsVersionId = a})
potrsResponseStatus :: Lens' PutObjectTaggingResponse Int
potrsResponseStatus = lens _potrsResponseStatus (\ s a -> s{_potrsResponseStatus = a})
instance NFData PutObjectTaggingResponse where