{-# 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.GetBucketLocation
(
getBucketLocation
, GetBucketLocation
, gblBucket
, getBucketLocationResponse
, GetBucketLocationResponse
, gblbrsResponseStatus
, gblbrsLocationConstraint
) 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 GetBucketLocation = GetBucketLocation'
{ _gblBucket :: BucketName
} deriving (Eq, Read, Show, Data, Typeable, Generic)
getBucketLocation
:: BucketName
-> GetBucketLocation
getBucketLocation pBucket_ = GetBucketLocation' {_gblBucket = pBucket_}
gblBucket :: Lens' GetBucketLocation BucketName
gblBucket = lens _gblBucket (\ s a -> s{_gblBucket = a})
instance AWSRequest GetBucketLocation where
type Rs GetBucketLocation = GetBucketLocationResponse
request = get s3
response
= receiveXML
(\ s h x ->
GetBucketLocationResponse' <$>
(pure (fromEnum s)) <*> (parseXML x))
instance Hashable GetBucketLocation where
instance NFData GetBucketLocation where
instance ToHeaders GetBucketLocation where
toHeaders = const mempty
instance ToPath GetBucketLocation where
toPath GetBucketLocation'{..}
= mconcat ["/", toBS _gblBucket]
instance ToQuery GetBucketLocation where
toQuery = const (mconcat ["location"])
data GetBucketLocationResponse = GetBucketLocationResponse'
{ _gblbrsResponseStatus :: !Int
, _gblbrsLocationConstraint :: !LocationConstraint
} deriving (Eq, Read, Show, Data, Typeable, Generic)
getBucketLocationResponse
:: Int
-> LocationConstraint
-> GetBucketLocationResponse
getBucketLocationResponse pResponseStatus_ pLocationConstraint_ =
GetBucketLocationResponse'
{ _gblbrsResponseStatus = pResponseStatus_
, _gblbrsLocationConstraint = pLocationConstraint_
}
gblbrsResponseStatus :: Lens' GetBucketLocationResponse Int
gblbrsResponseStatus = lens _gblbrsResponseStatus (\ s a -> s{_gblbrsResponseStatus = a})
gblbrsLocationConstraint :: Lens' GetBucketLocationResponse LocationConstraint
gblbrsLocationConstraint = lens _gblbrsLocationConstraint (\ s a -> s{_gblbrsLocationConstraint = a})
instance NFData GetBucketLocationResponse where