{-# 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.PutBucketInventoryConfiguration
(
putBucketInventoryConfiguration
, PutBucketInventoryConfiguration
, pbicBucket
, pbicId
, pbicInventoryConfiguration
, putBucketInventoryConfigurationResponse
, PutBucketInventoryConfigurationResponse
) 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 PutBucketInventoryConfiguration = PutBucketInventoryConfiguration'
{ _pbicBucket :: !BucketName
, _pbicId :: !Text
, _pbicInventoryConfiguration :: !InventoryConfiguration
} deriving (Eq, Show, Data, Typeable, Generic)
putBucketInventoryConfiguration
:: BucketName
-> Text
-> InventoryConfiguration
-> PutBucketInventoryConfiguration
putBucketInventoryConfiguration pBucket_ pId_ pInventoryConfiguration_ =
PutBucketInventoryConfiguration'
{ _pbicBucket = pBucket_
, _pbicId = pId_
, _pbicInventoryConfiguration = pInventoryConfiguration_
}
pbicBucket :: Lens' PutBucketInventoryConfiguration BucketName
pbicBucket = lens _pbicBucket (\ s a -> s{_pbicBucket = a})
pbicId :: Lens' PutBucketInventoryConfiguration Text
pbicId = lens _pbicId (\ s a -> s{_pbicId = a})
pbicInventoryConfiguration :: Lens' PutBucketInventoryConfiguration InventoryConfiguration
pbicInventoryConfiguration = lens _pbicInventoryConfiguration (\ s a -> s{_pbicInventoryConfiguration = a})
instance AWSRequest PutBucketInventoryConfiguration
where
type Rs PutBucketInventoryConfiguration =
PutBucketInventoryConfigurationResponse
request = putXML s3
response
= receiveNull
PutBucketInventoryConfigurationResponse'
instance Hashable PutBucketInventoryConfiguration
where
instance NFData PutBucketInventoryConfiguration where
instance ToElement PutBucketInventoryConfiguration
where
toElement
= mkElement
"{http://s3.amazonaws.com/doc/2006-03-01/}InventoryConfiguration"
.
_pbicInventoryConfiguration
instance ToHeaders PutBucketInventoryConfiguration
where
toHeaders = const mempty
instance ToPath PutBucketInventoryConfiguration where
toPath PutBucketInventoryConfiguration'{..}
= mconcat ["/", toBS _pbicBucket]
instance ToQuery PutBucketInventoryConfiguration
where
toQuery PutBucketInventoryConfiguration'{..}
= mconcat ["id" =: _pbicId, "inventory"]
data PutBucketInventoryConfigurationResponse =
PutBucketInventoryConfigurationResponse'
deriving (Eq, Read, Show, Data, Typeable, Generic)
putBucketInventoryConfigurationResponse
:: PutBucketInventoryConfigurationResponse
putBucketInventoryConfigurationResponse =
PutBucketInventoryConfigurationResponse'
instance NFData
PutBucketInventoryConfigurationResponse
where