{-# 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.GetBucketInventoryConfiguration
(
getBucketInventoryConfiguration
, GetBucketInventoryConfiguration
, gbicBucket
, gbicId
, getBucketInventoryConfigurationResponse
, GetBucketInventoryConfigurationResponse
, gbicrsInventoryConfiguration
, gbicrsResponseStatus
) 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 GetBucketInventoryConfiguration = GetBucketInventoryConfiguration'
{ _gbicBucket :: !BucketName
, _gbicId :: !Text
} deriving (Eq, Read, Show, Data, Typeable, Generic)
getBucketInventoryConfiguration
:: BucketName
-> Text
-> GetBucketInventoryConfiguration
getBucketInventoryConfiguration pBucket_ pId_ =
GetBucketInventoryConfiguration' {_gbicBucket = pBucket_, _gbicId = pId_}
gbicBucket :: Lens' GetBucketInventoryConfiguration BucketName
gbicBucket = lens _gbicBucket (\ s a -> s{_gbicBucket = a})
gbicId :: Lens' GetBucketInventoryConfiguration Text
gbicId = lens _gbicId (\ s a -> s{_gbicId = a})
instance AWSRequest GetBucketInventoryConfiguration
where
type Rs GetBucketInventoryConfiguration =
GetBucketInventoryConfigurationResponse
request = get s3
response
= receiveXML
(\ s h x ->
GetBucketInventoryConfigurationResponse' <$>
(parseXML x) <*> (pure (fromEnum s)))
instance Hashable GetBucketInventoryConfiguration
where
instance NFData GetBucketInventoryConfiguration where
instance ToHeaders GetBucketInventoryConfiguration
where
toHeaders = const mempty
instance ToPath GetBucketInventoryConfiguration where
toPath GetBucketInventoryConfiguration'{..}
= mconcat ["/", toBS _gbicBucket]
instance ToQuery GetBucketInventoryConfiguration
where
toQuery GetBucketInventoryConfiguration'{..}
= mconcat ["id" =: _gbicId, "inventory"]
data GetBucketInventoryConfigurationResponse = GetBucketInventoryConfigurationResponse'
{ _gbicrsInventoryConfiguration :: !(Maybe InventoryConfiguration)
, _gbicrsResponseStatus :: !Int
} deriving (Eq, Show, Data, Typeable, Generic)
getBucketInventoryConfigurationResponse
:: Int
-> GetBucketInventoryConfigurationResponse
getBucketInventoryConfigurationResponse pResponseStatus_ =
GetBucketInventoryConfigurationResponse'
{ _gbicrsInventoryConfiguration = Nothing
, _gbicrsResponseStatus = pResponseStatus_
}
gbicrsInventoryConfiguration :: Lens' GetBucketInventoryConfigurationResponse (Maybe InventoryConfiguration)
gbicrsInventoryConfiguration = lens _gbicrsInventoryConfiguration (\ s a -> s{_gbicrsInventoryConfiguration = a})
gbicrsResponseStatus :: Lens' GetBucketInventoryConfigurationResponse Int
gbicrsResponseStatus = lens _gbicrsResponseStatus (\ s a -> s{_gbicrsResponseStatus = a})
instance NFData
GetBucketInventoryConfigurationResponse
where