module Network.AWS.S3.GetBucketNotification
    (
    
      GetBucketNotification
    
    , getBucketNotification
    
    , gbnBucket
    
    , GetBucketNotificationResponse
    
    , getBucketNotificationResponse
    
    , gbnrCloudFunctionConfiguration
    , gbnrQueueConfiguration
    , gbnrTopicConfiguration
    ) where
import Network.AWS.Prelude
import Network.AWS.Request.S3
import Network.AWS.S3.Types
import qualified GHC.Exts
newtype GetBucketNotification = GetBucketNotification
    { _gbnBucket :: Text
    } deriving (Eq, Ord, Show, Monoid, IsString)
getBucketNotification :: Text 
                      -> GetBucketNotification
getBucketNotification p1 = GetBucketNotification
    { _gbnBucket = p1
    }
gbnBucket :: Lens' GetBucketNotification Text
gbnBucket = lens _gbnBucket (\s a -> s { _gbnBucket = a })
data GetBucketNotificationResponse = GetBucketNotificationResponse
    { _gbnrCloudFunctionConfiguration :: Maybe CloudFunctionConfiguration
    , _gbnrQueueConfiguration         :: Maybe QueueConfiguration
    , _gbnrTopicConfiguration         :: Maybe TopicConfiguration
    } deriving (Eq, Show)
getBucketNotificationResponse :: GetBucketNotificationResponse
getBucketNotificationResponse = GetBucketNotificationResponse
    { _gbnrTopicConfiguration         = Nothing
    , _gbnrQueueConfiguration         = Nothing
    , _gbnrCloudFunctionConfiguration = Nothing
    }
gbnrCloudFunctionConfiguration :: Lens' GetBucketNotificationResponse (Maybe CloudFunctionConfiguration)
gbnrCloudFunctionConfiguration =
    lens _gbnrCloudFunctionConfiguration
        (\s a -> s { _gbnrCloudFunctionConfiguration = a })
gbnrQueueConfiguration :: Lens' GetBucketNotificationResponse (Maybe QueueConfiguration)
gbnrQueueConfiguration =
    lens _gbnrQueueConfiguration (\s a -> s { _gbnrQueueConfiguration = a })
gbnrTopicConfiguration :: Lens' GetBucketNotificationResponse (Maybe TopicConfiguration)
gbnrTopicConfiguration =
    lens _gbnrTopicConfiguration (\s a -> s { _gbnrTopicConfiguration = a })
instance ToPath GetBucketNotification where
    toPath GetBucketNotification{..} = mconcat
        [ "/"
        , toText _gbnBucket
        ]
instance ToQuery GetBucketNotification where
    toQuery = const "notification"
instance ToHeaders GetBucketNotification
instance ToXMLRoot GetBucketNotification where
    toXMLRoot = const (namespaced ns "GetBucketNotification" [])
instance ToXML GetBucketNotification
instance AWSRequest GetBucketNotification where
    type Sv GetBucketNotification = S3
    type Rs GetBucketNotification = GetBucketNotificationResponse
    request  = get
    response = xmlResponse
instance FromXML GetBucketNotificationResponse where
    parseXML x = GetBucketNotificationResponse
        <$> x .@? "CloudFunctionConfiguration"
        <*> x .@? "QueueConfiguration"
        <*> x .@? "TopicConfiguration"