{-# 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.ListBucketInventoryConfigurations
(
listBucketInventoryConfigurations
, ListBucketInventoryConfigurations
, lbicContinuationToken
, lbicBucket
, listBucketInventoryConfigurationsResponse
, ListBucketInventoryConfigurationsResponse
, lbicrsContinuationToken
, lbicrsInventoryConfigurationList
, lbicrsNextContinuationToken
, lbicrsIsTruncated
, lbicrsResponseStatus
) 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 ListBucketInventoryConfigurations = ListBucketInventoryConfigurations'
{ _lbicContinuationToken :: !(Maybe Text)
, _lbicBucket :: !BucketName
} deriving (Eq, Read, Show, Data, Typeable, Generic)
listBucketInventoryConfigurations
:: BucketName
-> ListBucketInventoryConfigurations
listBucketInventoryConfigurations pBucket_ =
ListBucketInventoryConfigurations'
{_lbicContinuationToken = Nothing, _lbicBucket = pBucket_}
lbicContinuationToken :: Lens' ListBucketInventoryConfigurations (Maybe Text)
lbicContinuationToken = lens _lbicContinuationToken (\ s a -> s{_lbicContinuationToken = a})
lbicBucket :: Lens' ListBucketInventoryConfigurations BucketName
lbicBucket = lens _lbicBucket (\ s a -> s{_lbicBucket = a})
instance AWSRequest ListBucketInventoryConfigurations
where
type Rs ListBucketInventoryConfigurations =
ListBucketInventoryConfigurationsResponse
request = get s3
response
= receiveXML
(\ s h x ->
ListBucketInventoryConfigurationsResponse' <$>
(x .@? "ContinuationToken") <*>
(may (parseXMLList "InventoryConfiguration") x)
<*> (x .@? "NextContinuationToken")
<*> (x .@? "IsTruncated")
<*> (pure (fromEnum s)))
instance Hashable ListBucketInventoryConfigurations
where
instance NFData ListBucketInventoryConfigurations
where
instance ToHeaders ListBucketInventoryConfigurations
where
toHeaders = const mempty
instance ToPath ListBucketInventoryConfigurations
where
toPath ListBucketInventoryConfigurations'{..}
= mconcat ["/", toBS _lbicBucket]
instance ToQuery ListBucketInventoryConfigurations
where
toQuery ListBucketInventoryConfigurations'{..}
= mconcat
["continuation-token" =: _lbicContinuationToken,
"inventory"]
data ListBucketInventoryConfigurationsResponse = ListBucketInventoryConfigurationsResponse'
{ _lbicrsContinuationToken :: !(Maybe Text)
, _lbicrsInventoryConfigurationList :: !(Maybe [InventoryConfiguration])
, _lbicrsNextContinuationToken :: !(Maybe Text)
, _lbicrsIsTruncated :: !(Maybe Bool)
, _lbicrsResponseStatus :: !Int
} deriving (Eq, Show, Data, Typeable, Generic)
listBucketInventoryConfigurationsResponse
:: Int
-> ListBucketInventoryConfigurationsResponse
listBucketInventoryConfigurationsResponse pResponseStatus_ =
ListBucketInventoryConfigurationsResponse'
{ _lbicrsContinuationToken = Nothing
, _lbicrsInventoryConfigurationList = Nothing
, _lbicrsNextContinuationToken = Nothing
, _lbicrsIsTruncated = Nothing
, _lbicrsResponseStatus = pResponseStatus_
}
lbicrsContinuationToken :: Lens' ListBucketInventoryConfigurationsResponse (Maybe Text)
lbicrsContinuationToken = lens _lbicrsContinuationToken (\ s a -> s{_lbicrsContinuationToken = a})
lbicrsInventoryConfigurationList :: Lens' ListBucketInventoryConfigurationsResponse [InventoryConfiguration]
lbicrsInventoryConfigurationList = lens _lbicrsInventoryConfigurationList (\ s a -> s{_lbicrsInventoryConfigurationList = a}) . _Default . _Coerce
lbicrsNextContinuationToken :: Lens' ListBucketInventoryConfigurationsResponse (Maybe Text)
lbicrsNextContinuationToken = lens _lbicrsNextContinuationToken (\ s a -> s{_lbicrsNextContinuationToken = a})
lbicrsIsTruncated :: Lens' ListBucketInventoryConfigurationsResponse (Maybe Bool)
lbicrsIsTruncated = lens _lbicrsIsTruncated (\ s a -> s{_lbicrsIsTruncated = a})
lbicrsResponseStatus :: Lens' ListBucketInventoryConfigurationsResponse Int
lbicrsResponseStatus = lens _lbicrsResponseStatus (\ s a -> s{_lbicrsResponseStatus = a})
instance NFData
ListBucketInventoryConfigurationsResponse
where