{-# 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.GetBucketReplication
(
getBucketReplication
, GetBucketReplication
, gbrBucket
, getBucketReplicationResponse
, GetBucketReplicationResponse
, gbrrsReplicationConfiguration
, gbrrsResponseStatus
) 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
newtype GetBucketReplication = GetBucketReplication'
{ _gbrBucket :: BucketName
} deriving (Eq, Read, Show, Data, Typeable, Generic)
getBucketReplication
:: BucketName
-> GetBucketReplication
getBucketReplication pBucket_ = GetBucketReplication' {_gbrBucket = pBucket_}
gbrBucket :: Lens' GetBucketReplication BucketName
gbrBucket = lens _gbrBucket (\ s a -> s{_gbrBucket = a})
instance AWSRequest GetBucketReplication where
type Rs GetBucketReplication =
GetBucketReplicationResponse
request = get s3
response
= receiveXML
(\ s h x ->
GetBucketReplicationResponse' <$>
(parseXML x) <*> (pure (fromEnum s)))
instance Hashable GetBucketReplication where
instance NFData GetBucketReplication where
instance ToHeaders GetBucketReplication where
toHeaders = const mempty
instance ToPath GetBucketReplication where
toPath GetBucketReplication'{..}
= mconcat ["/", toBS _gbrBucket]
instance ToQuery GetBucketReplication where
toQuery = const (mconcat ["replication"])
data GetBucketReplicationResponse = GetBucketReplicationResponse'
{ _gbrrsReplicationConfiguration :: !(Maybe ReplicationConfiguration)
, _gbrrsResponseStatus :: !Int
} deriving (Eq, Read, Show, Data, Typeable, Generic)
getBucketReplicationResponse
:: Int
-> GetBucketReplicationResponse
getBucketReplicationResponse pResponseStatus_ =
GetBucketReplicationResponse'
{ _gbrrsReplicationConfiguration = Nothing
, _gbrrsResponseStatus = pResponseStatus_
}
gbrrsReplicationConfiguration :: Lens' GetBucketReplicationResponse (Maybe ReplicationConfiguration)
gbrrsReplicationConfiguration = lens _gbrrsReplicationConfiguration (\ s a -> s{_gbrrsReplicationConfiguration = a})
gbrrsResponseStatus :: Lens' GetBucketReplicationResponse Int
gbrrsResponseStatus = lens _gbrrsResponseStatus (\ s a -> s{_gbrrsResponseStatus = a})
instance NFData GetBucketReplicationResponse where