{-# 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.SNS.GetSubscriptionAttributes
(
getSubscriptionAttributes
, GetSubscriptionAttributes
, gsaSubscriptionARN
, getSubscriptionAttributesResponse
, GetSubscriptionAttributesResponse
, gsarsAttributes
, gsarsResponseStatus
) where
import Network.AWS.Lens
import Network.AWS.Prelude
import Network.AWS.Request
import Network.AWS.Response
import Network.AWS.SNS.Types
import Network.AWS.SNS.Types.Product
newtype GetSubscriptionAttributes = GetSubscriptionAttributes'
{ _gsaSubscriptionARN :: Text
} deriving (Eq, Read, Show, Data, Typeable, Generic)
getSubscriptionAttributes
:: Text
-> GetSubscriptionAttributes
getSubscriptionAttributes pSubscriptionARN_ =
GetSubscriptionAttributes' {_gsaSubscriptionARN = pSubscriptionARN_}
gsaSubscriptionARN :: Lens' GetSubscriptionAttributes Text
gsaSubscriptionARN = lens _gsaSubscriptionARN (\ s a -> s{_gsaSubscriptionARN = a})
instance AWSRequest GetSubscriptionAttributes where
type Rs GetSubscriptionAttributes =
GetSubscriptionAttributesResponse
request = postQuery sns
response
= receiveXMLWrapper "GetSubscriptionAttributesResult"
(\ s h x ->
GetSubscriptionAttributesResponse' <$>
(x .@? "Attributes" .!@ mempty >>=
may (parseXMLMap "entry" "key" "value"))
<*> (pure (fromEnum s)))
instance Hashable GetSubscriptionAttributes where
instance NFData GetSubscriptionAttributes where
instance ToHeaders GetSubscriptionAttributes where
toHeaders = const mempty
instance ToPath GetSubscriptionAttributes where
toPath = const "/"
instance ToQuery GetSubscriptionAttributes where
toQuery GetSubscriptionAttributes'{..}
= mconcat
["Action" =:
("GetSubscriptionAttributes" :: ByteString),
"Version" =: ("2010-03-31" :: ByteString),
"SubscriptionArn" =: _gsaSubscriptionARN]
data GetSubscriptionAttributesResponse = GetSubscriptionAttributesResponse'
{ _gsarsAttributes :: !(Maybe (Map Text Text))
, _gsarsResponseStatus :: !Int
} deriving (Eq, Read, Show, Data, Typeable, Generic)
getSubscriptionAttributesResponse
:: Int
-> GetSubscriptionAttributesResponse
getSubscriptionAttributesResponse pResponseStatus_ =
GetSubscriptionAttributesResponse'
{_gsarsAttributes = Nothing, _gsarsResponseStatus = pResponseStatus_}
gsarsAttributes :: Lens' GetSubscriptionAttributesResponse (HashMap Text Text)
gsarsAttributes = lens _gsarsAttributes (\ s a -> s{_gsarsAttributes = a}) . _Default . _Map
gsarsResponseStatus :: Lens' GetSubscriptionAttributesResponse Int
gsarsResponseStatus = lens _gsarsResponseStatus (\ s a -> s{_gsarsResponseStatus = a})
instance NFData GetSubscriptionAttributesResponse
where