{-# 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.GetBucketAnalyticsConfiguration
(
getBucketAnalyticsConfiguration
, GetBucketAnalyticsConfiguration
, getBucket
, getId
, getBucketAnalyticsConfigurationResponse
, GetBucketAnalyticsConfigurationResponse
, gbacrsAnalyticsConfiguration
, gbacrsResponseStatus
) 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 GetBucketAnalyticsConfiguration = GetBucketAnalyticsConfiguration'
{ _getBucket :: !BucketName
, _getId :: !Text
} deriving (Eq, Read, Show, Data, Typeable, Generic)
getBucketAnalyticsConfiguration
:: BucketName
-> Text
-> GetBucketAnalyticsConfiguration
getBucketAnalyticsConfiguration pBucket_ pId_ =
GetBucketAnalyticsConfiguration' {_getBucket = pBucket_, _getId = pId_}
getBucket :: Lens' GetBucketAnalyticsConfiguration BucketName
getBucket = lens _getBucket (\ s a -> s{_getBucket = a})
getId :: Lens' GetBucketAnalyticsConfiguration Text
getId = lens _getId (\ s a -> s{_getId = a})
instance AWSRequest GetBucketAnalyticsConfiguration
where
type Rs GetBucketAnalyticsConfiguration =
GetBucketAnalyticsConfigurationResponse
request = get s3
response
= receiveXML
(\ s h x ->
GetBucketAnalyticsConfigurationResponse' <$>
(parseXML x) <*> (pure (fromEnum s)))
instance Hashable GetBucketAnalyticsConfiguration
where
instance NFData GetBucketAnalyticsConfiguration where
instance ToHeaders GetBucketAnalyticsConfiguration
where
toHeaders = const mempty
instance ToPath GetBucketAnalyticsConfiguration where
toPath GetBucketAnalyticsConfiguration'{..}
= mconcat ["/", toBS _getBucket]
instance ToQuery GetBucketAnalyticsConfiguration
where
toQuery GetBucketAnalyticsConfiguration'{..}
= mconcat ["id" =: _getId, "analytics"]
data GetBucketAnalyticsConfigurationResponse = GetBucketAnalyticsConfigurationResponse'
{ _gbacrsAnalyticsConfiguration :: !(Maybe AnalyticsConfiguration)
, _gbacrsResponseStatus :: !Int
} deriving (Eq, Read, Show, Data, Typeable, Generic)
getBucketAnalyticsConfigurationResponse
:: Int
-> GetBucketAnalyticsConfigurationResponse
getBucketAnalyticsConfigurationResponse pResponseStatus_ =
GetBucketAnalyticsConfigurationResponse'
{ _gbacrsAnalyticsConfiguration = Nothing
, _gbacrsResponseStatus = pResponseStatus_
}
gbacrsAnalyticsConfiguration :: Lens' GetBucketAnalyticsConfigurationResponse (Maybe AnalyticsConfiguration)
gbacrsAnalyticsConfiguration = lens _gbacrsAnalyticsConfiguration (\ s a -> s{_gbacrsAnalyticsConfiguration = a})
gbacrsResponseStatus :: Lens' GetBucketAnalyticsConfigurationResponse Int
gbacrsResponseStatus = lens _gbacrsResponseStatus (\ s a -> s{_gbacrsResponseStatus = a})
instance NFData
GetBucketAnalyticsConfigurationResponse
where