{-# 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.GetBucketEncryption
(
getBucketEncryption
, GetBucketEncryption
, gbeBucket
, getBucketEncryptionResponse
, GetBucketEncryptionResponse
, gbersServerSideEncryptionConfiguration
, gbersResponseStatus
) 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 GetBucketEncryption = GetBucketEncryption'
{ _gbeBucket :: BucketName
} deriving (Eq, Read, Show, Data, Typeable, Generic)
getBucketEncryption
:: BucketName
-> GetBucketEncryption
getBucketEncryption pBucket_ = GetBucketEncryption' {_gbeBucket = pBucket_}
gbeBucket :: Lens' GetBucketEncryption BucketName
gbeBucket = lens _gbeBucket (\ s a -> s{_gbeBucket = a})
instance AWSRequest GetBucketEncryption where
type Rs GetBucketEncryption =
GetBucketEncryptionResponse
request = get s3
response
= receiveXML
(\ s h x ->
GetBucketEncryptionResponse' <$>
(parseXML x) <*> (pure (fromEnum s)))
instance Hashable GetBucketEncryption where
instance NFData GetBucketEncryption where
instance ToHeaders GetBucketEncryption where
toHeaders = const mempty
instance ToPath GetBucketEncryption where
toPath GetBucketEncryption'{..}
= mconcat ["/", toBS _gbeBucket]
instance ToQuery GetBucketEncryption where
toQuery = const (mconcat ["encryption"])
data GetBucketEncryptionResponse = GetBucketEncryptionResponse'
{ _gbersServerSideEncryptionConfiguration :: !(Maybe ServerSideEncryptionConfiguration)
, _gbersResponseStatus :: !Int
} deriving (Eq, Show, Data, Typeable, Generic)
getBucketEncryptionResponse
:: Int
-> GetBucketEncryptionResponse
getBucketEncryptionResponse pResponseStatus_ =
GetBucketEncryptionResponse'
{ _gbersServerSideEncryptionConfiguration = Nothing
, _gbersResponseStatus = pResponseStatus_
}
gbersServerSideEncryptionConfiguration :: Lens' GetBucketEncryptionResponse (Maybe ServerSideEncryptionConfiguration)
gbersServerSideEncryptionConfiguration = lens _gbersServerSideEncryptionConfiguration (\ s a -> s{_gbersServerSideEncryptionConfiguration = a})
gbersResponseStatus :: Lens' GetBucketEncryptionResponse Int
gbersResponseStatus = lens _gbersResponseStatus (\ s a -> s{_gbersResponseStatus = a})
instance NFData GetBucketEncryptionResponse where