{-# 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.PutBucketPolicy
(
putBucketPolicy
, PutBucketPolicy
, pbpConfirmRemoveSelfBucketAccess
, pbpContentMD5
, pbpBucket
, pbpPolicy
, putBucketPolicyResponse
, PutBucketPolicyResponse
) 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 PutBucketPolicy = PutBucketPolicy'
{ _pbpConfirmRemoveSelfBucketAccess :: !(Maybe Bool)
, _pbpContentMD5 :: !(Maybe Text)
, _pbpBucket :: !BucketName
, _pbpPolicy :: !ByteString
} deriving (Eq, Show, Data, Typeable, Generic)
putBucketPolicy
:: BucketName
-> ByteString
-> PutBucketPolicy
putBucketPolicy pBucket_ pPolicy_ =
PutBucketPolicy'
{ _pbpConfirmRemoveSelfBucketAccess = Nothing
, _pbpContentMD5 = Nothing
, _pbpBucket = pBucket_
, _pbpPolicy = pPolicy_
}
pbpConfirmRemoveSelfBucketAccess :: Lens' PutBucketPolicy (Maybe Bool)
pbpConfirmRemoveSelfBucketAccess = lens _pbpConfirmRemoveSelfBucketAccess (\ s a -> s{_pbpConfirmRemoveSelfBucketAccess = a})
pbpContentMD5 :: Lens' PutBucketPolicy (Maybe Text)
pbpContentMD5 = lens _pbpContentMD5 (\ s a -> s{_pbpContentMD5 = a})
pbpBucket :: Lens' PutBucketPolicy BucketName
pbpBucket = lens _pbpBucket (\ s a -> s{_pbpBucket = a})
pbpPolicy :: Lens' PutBucketPolicy ByteString
pbpPolicy = lens _pbpPolicy (\ s a -> s{_pbpPolicy = a})
instance AWSRequest PutBucketPolicy where
type Rs PutBucketPolicy = PutBucketPolicyResponse
request = contentMD5Header . putBody s3
response = receiveNull PutBucketPolicyResponse'
instance Hashable PutBucketPolicy where
instance NFData PutBucketPolicy where
instance ToBody PutBucketPolicy where
toBody = toBody . _pbpPolicy
instance ToHeaders PutBucketPolicy where
toHeaders PutBucketPolicy'{..}
= mconcat
["x-amz-confirm-remove-self-bucket-access" =#
_pbpConfirmRemoveSelfBucketAccess,
"Content-MD5" =# _pbpContentMD5]
instance ToPath PutBucketPolicy where
toPath PutBucketPolicy'{..}
= mconcat ["/", toBS _pbpBucket]
instance ToQuery PutBucketPolicy where
toQuery = const (mconcat ["policy"])
data PutBucketPolicyResponse =
PutBucketPolicyResponse'
deriving (Eq, Read, Show, Data, Typeable, Generic)
putBucketPolicyResponse
:: PutBucketPolicyResponse
putBucketPolicyResponse = PutBucketPolicyResponse'
instance NFData PutBucketPolicyResponse where