{-# 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.GetObjectTagging
(
getObjectTagging
, GetObjectTagging
, gotoVersionId
, gotoBucket
, gotoKey
, getObjectTaggingResponse
, GetObjectTaggingResponse
, gotrsVersionId
, gotrsResponseStatus
, gotrsTagSet
) 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 GetObjectTagging = GetObjectTagging'
{ _gotoVersionId :: !(Maybe ObjectVersionId)
, _gotoBucket :: !BucketName
, _gotoKey :: !ObjectKey
} deriving (Eq, Read, Show, Data, Typeable, Generic)
getObjectTagging
:: BucketName
-> ObjectKey
-> GetObjectTagging
getObjectTagging pBucket_ pKey_ =
GetObjectTagging'
{_gotoVersionId = Nothing, _gotoBucket = pBucket_, _gotoKey = pKey_}
gotoVersionId :: Lens' GetObjectTagging (Maybe ObjectVersionId)
gotoVersionId = lens _gotoVersionId (\ s a -> s{_gotoVersionId = a})
gotoBucket :: Lens' GetObjectTagging BucketName
gotoBucket = lens _gotoBucket (\ s a -> s{_gotoBucket = a})
gotoKey :: Lens' GetObjectTagging ObjectKey
gotoKey = lens _gotoKey (\ s a -> s{_gotoKey = a})
instance AWSRequest GetObjectTagging where
type Rs GetObjectTagging = GetObjectTaggingResponse
request = get s3
response
= receiveXML
(\ s h x ->
GetObjectTaggingResponse' <$>
(h .#? "x-amz-version-id") <*> (pure (fromEnum s))
<*>
(x .@? "TagSet" .!@ mempty >>= parseXMLList "Tag"))
instance Hashable GetObjectTagging where
instance NFData GetObjectTagging where
instance ToHeaders GetObjectTagging where
toHeaders = const mempty
instance ToPath GetObjectTagging where
toPath GetObjectTagging'{..}
= mconcat ["/", toBS _gotoBucket, "/", toBS _gotoKey]
instance ToQuery GetObjectTagging where
toQuery GetObjectTagging'{..}
= mconcat ["versionId" =: _gotoVersionId, "tagging"]
data GetObjectTaggingResponse = GetObjectTaggingResponse'
{ _gotrsVersionId :: !(Maybe ObjectVersionId)
, _gotrsResponseStatus :: !Int
, _gotrsTagSet :: ![Tag]
} deriving (Eq, Read, Show, Data, Typeable, Generic)
getObjectTaggingResponse
:: Int
-> GetObjectTaggingResponse
getObjectTaggingResponse pResponseStatus_ =
GetObjectTaggingResponse'
{ _gotrsVersionId = Nothing
, _gotrsResponseStatus = pResponseStatus_
, _gotrsTagSet = mempty
}
gotrsVersionId :: Lens' GetObjectTaggingResponse (Maybe ObjectVersionId)
gotrsVersionId = lens _gotrsVersionId (\ s a -> s{_gotrsVersionId = a})
gotrsResponseStatus :: Lens' GetObjectTaggingResponse Int
gotrsResponseStatus = lens _gotrsResponseStatus (\ s a -> s{_gotrsResponseStatus = a})
gotrsTagSet :: Lens' GetObjectTaggingResponse [Tag]
gotrsTagSet = lens _gotrsTagSet (\ s a -> s{_gotrsTagSet = a}) . _Coerce
instance NFData GetObjectTaggingResponse where