{-# 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.PutBucketLogging
(
putBucketLogging
, PutBucketLogging
, pblContentMD5
, pblBucket
, pblBucketLoggingStatus
, putBucketLoggingResponse
, PutBucketLoggingResponse
) 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 PutBucketLogging = PutBucketLogging'
{ _pblContentMD5 :: !(Maybe Text)
, _pblBucket :: !BucketName
, _pblBucketLoggingStatus :: !BucketLoggingStatus
} deriving (Eq, Read, Show, Data, Typeable, Generic)
putBucketLogging
:: BucketName
-> BucketLoggingStatus
-> PutBucketLogging
putBucketLogging pBucket_ pBucketLoggingStatus_ =
PutBucketLogging'
{ _pblContentMD5 = Nothing
, _pblBucket = pBucket_
, _pblBucketLoggingStatus = pBucketLoggingStatus_
}
pblContentMD5 :: Lens' PutBucketLogging (Maybe Text)
pblContentMD5 = lens _pblContentMD5 (\ s a -> s{_pblContentMD5 = a})
pblBucket :: Lens' PutBucketLogging BucketName
pblBucket = lens _pblBucket (\ s a -> s{_pblBucket = a})
pblBucketLoggingStatus :: Lens' PutBucketLogging BucketLoggingStatus
pblBucketLoggingStatus = lens _pblBucketLoggingStatus (\ s a -> s{_pblBucketLoggingStatus = a})
instance AWSRequest PutBucketLogging where
type Rs PutBucketLogging = PutBucketLoggingResponse
request = putXML s3
response = receiveNull PutBucketLoggingResponse'
instance Hashable PutBucketLogging where
instance NFData PutBucketLogging where
instance ToElement PutBucketLogging where
toElement
= mkElement
"{http://s3.amazonaws.com/doc/2006-03-01/}BucketLoggingStatus"
.
_pblBucketLoggingStatus
instance ToHeaders PutBucketLogging where
toHeaders PutBucketLogging'{..}
= mconcat ["Content-MD5" =# _pblContentMD5]
instance ToPath PutBucketLogging where
toPath PutBucketLogging'{..}
= mconcat ["/", toBS _pblBucket]
instance ToQuery PutBucketLogging where
toQuery = const (mconcat ["logging"])
data PutBucketLoggingResponse =
PutBucketLoggingResponse'
deriving (Eq, Read, Show, Data, Typeable, Generic)
putBucketLoggingResponse
:: PutBucketLoggingResponse
putBucketLoggingResponse = PutBucketLoggingResponse'
instance NFData PutBucketLoggingResponse where