{-# 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.GetBucketCORS
(
getBucketCORS
, GetBucketCORS
, gbcBucket
, getBucketCORSResponse
, GetBucketCORSResponse
, gbcrsCORSRules
, gbcrsResponseStatus
) 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 GetBucketCORS = GetBucketCORS'
{ _gbcBucket :: BucketName
} deriving (Eq, Read, Show, Data, Typeable, Generic)
getBucketCORS
:: BucketName
-> GetBucketCORS
getBucketCORS pBucket_ = GetBucketCORS' {_gbcBucket = pBucket_}
gbcBucket :: Lens' GetBucketCORS BucketName
gbcBucket = lens _gbcBucket (\ s a -> s{_gbcBucket = a})
instance AWSRequest GetBucketCORS where
type Rs GetBucketCORS = GetBucketCORSResponse
request = get s3
response
= receiveXML
(\ s h x ->
GetBucketCORSResponse' <$>
(may (parseXMLList "CORSRule") x) <*>
(pure (fromEnum s)))
instance Hashable GetBucketCORS where
instance NFData GetBucketCORS where
instance ToHeaders GetBucketCORS where
toHeaders = const mempty
instance ToPath GetBucketCORS where
toPath GetBucketCORS'{..}
= mconcat ["/", toBS _gbcBucket]
instance ToQuery GetBucketCORS where
toQuery = const (mconcat ["cors"])
data GetBucketCORSResponse = GetBucketCORSResponse'
{ _gbcrsCORSRules :: !(Maybe [CORSRule])
, _gbcrsResponseStatus :: !Int
} deriving (Eq, Read, Show, Data, Typeable, Generic)
getBucketCORSResponse
:: Int
-> GetBucketCORSResponse
getBucketCORSResponse pResponseStatus_ =
GetBucketCORSResponse'
{_gbcrsCORSRules = Nothing, _gbcrsResponseStatus = pResponseStatus_}
gbcrsCORSRules :: Lens' GetBucketCORSResponse [CORSRule]
gbcrsCORSRules = lens _gbcrsCORSRules (\ s a -> s{_gbcrsCORSRules = a}) . _Default . _Coerce
gbcrsResponseStatus :: Lens' GetBucketCORSResponse Int
gbcrsResponseStatus = lens _gbcrsResponseStatus (\ s a -> s{_gbcrsResponseStatus = a})
instance NFData GetBucketCORSResponse where