{-# 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.PutBucketMetricsConfiguration
(
putBucketMetricsConfiguration
, PutBucketMetricsConfiguration
, pbmcBucket
, pbmcId
, pbmcMetricsConfiguration
, putBucketMetricsConfigurationResponse
, PutBucketMetricsConfigurationResponse
) 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 PutBucketMetricsConfiguration = PutBucketMetricsConfiguration'
{ _pbmcBucket :: !BucketName
, _pbmcId :: !Text
, _pbmcMetricsConfiguration :: !MetricsConfiguration
} deriving (Eq, Read, Show, Data, Typeable, Generic)
putBucketMetricsConfiguration
:: BucketName
-> Text
-> MetricsConfiguration
-> PutBucketMetricsConfiguration
putBucketMetricsConfiguration pBucket_ pId_ pMetricsConfiguration_ =
PutBucketMetricsConfiguration'
{ _pbmcBucket = pBucket_
, _pbmcId = pId_
, _pbmcMetricsConfiguration = pMetricsConfiguration_
}
pbmcBucket :: Lens' PutBucketMetricsConfiguration BucketName
pbmcBucket = lens _pbmcBucket (\ s a -> s{_pbmcBucket = a})
pbmcId :: Lens' PutBucketMetricsConfiguration Text
pbmcId = lens _pbmcId (\ s a -> s{_pbmcId = a})
pbmcMetricsConfiguration :: Lens' PutBucketMetricsConfiguration MetricsConfiguration
pbmcMetricsConfiguration = lens _pbmcMetricsConfiguration (\ s a -> s{_pbmcMetricsConfiguration = a})
instance AWSRequest PutBucketMetricsConfiguration
where
type Rs PutBucketMetricsConfiguration =
PutBucketMetricsConfigurationResponse
request = putXML s3
response
= receiveNull PutBucketMetricsConfigurationResponse'
instance Hashable PutBucketMetricsConfiguration where
instance NFData PutBucketMetricsConfiguration where
instance ToElement PutBucketMetricsConfiguration
where
toElement
= mkElement
"{http://s3.amazonaws.com/doc/2006-03-01/}MetricsConfiguration"
.
_pbmcMetricsConfiguration
instance ToHeaders PutBucketMetricsConfiguration
where
toHeaders = const mempty
instance ToPath PutBucketMetricsConfiguration where
toPath PutBucketMetricsConfiguration'{..}
= mconcat ["/", toBS _pbmcBucket]
instance ToQuery PutBucketMetricsConfiguration where
toQuery PutBucketMetricsConfiguration'{..}
= mconcat ["id" =: _pbmcId, "metrics"]
data PutBucketMetricsConfigurationResponse =
PutBucketMetricsConfigurationResponse'
deriving (Eq, Read, Show, Data, Typeable, Generic)
putBucketMetricsConfigurationResponse
:: PutBucketMetricsConfigurationResponse
putBucketMetricsConfigurationResponse = PutBucketMetricsConfigurationResponse'
instance NFData PutBucketMetricsConfigurationResponse
where