{-# 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.SetSubscriptionAttributes
(
setSubscriptionAttributes
, SetSubscriptionAttributes
, ssaAttributeValue
, ssaSubscriptionARN
, ssaAttributeName
, setSubscriptionAttributesResponse
, SetSubscriptionAttributesResponse
) 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
data SetSubscriptionAttributes = SetSubscriptionAttributes'
{ _ssaAttributeValue :: !(Maybe Text)
, _ssaSubscriptionARN :: !Text
, _ssaAttributeName :: !Text
} deriving (Eq, Read, Show, Data, Typeable, Generic)
setSubscriptionAttributes
:: Text
-> Text
-> SetSubscriptionAttributes
setSubscriptionAttributes pSubscriptionARN_ pAttributeName_ =
SetSubscriptionAttributes'
{ _ssaAttributeValue = Nothing
, _ssaSubscriptionARN = pSubscriptionARN_
, _ssaAttributeName = pAttributeName_
}
ssaAttributeValue :: Lens' SetSubscriptionAttributes (Maybe Text)
ssaAttributeValue = lens _ssaAttributeValue (\ s a -> s{_ssaAttributeValue = a})
ssaSubscriptionARN :: Lens' SetSubscriptionAttributes Text
ssaSubscriptionARN = lens _ssaSubscriptionARN (\ s a -> s{_ssaSubscriptionARN = a})
ssaAttributeName :: Lens' SetSubscriptionAttributes Text
ssaAttributeName = lens _ssaAttributeName (\ s a -> s{_ssaAttributeName = a})
instance AWSRequest SetSubscriptionAttributes where
type Rs SetSubscriptionAttributes =
SetSubscriptionAttributesResponse
request = postQuery sns
response
= receiveNull SetSubscriptionAttributesResponse'
instance Hashable SetSubscriptionAttributes where
instance NFData SetSubscriptionAttributes where
instance ToHeaders SetSubscriptionAttributes where
toHeaders = const mempty
instance ToPath SetSubscriptionAttributes where
toPath = const "/"
instance ToQuery SetSubscriptionAttributes where
toQuery SetSubscriptionAttributes'{..}
= mconcat
["Action" =:
("SetSubscriptionAttributes" :: ByteString),
"Version" =: ("2010-03-31" :: ByteString),
"AttributeValue" =: _ssaAttributeValue,
"SubscriptionArn" =: _ssaSubscriptionARN,
"AttributeName" =: _ssaAttributeName]
data SetSubscriptionAttributesResponse =
SetSubscriptionAttributesResponse'
deriving (Eq, Read, Show, Data, Typeable, Generic)
setSubscriptionAttributesResponse
:: SetSubscriptionAttributesResponse
setSubscriptionAttributesResponse = SetSubscriptionAttributesResponse'
instance NFData SetSubscriptionAttributesResponse
where