{-# 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.SetTopicAttributes
(
setTopicAttributes
, SetTopicAttributes
, staAttributeValue
, staTopicARN
, staAttributeName
, setTopicAttributesResponse
, SetTopicAttributesResponse
) 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 SetTopicAttributes = SetTopicAttributes'
{ _staAttributeValue :: !(Maybe Text)
, _staTopicARN :: !Text
, _staAttributeName :: !Text
} deriving (Eq, Read, Show, Data, Typeable, Generic)
setTopicAttributes
:: Text
-> Text
-> SetTopicAttributes
setTopicAttributes pTopicARN_ pAttributeName_ =
SetTopicAttributes'
{ _staAttributeValue = Nothing
, _staTopicARN = pTopicARN_
, _staAttributeName = pAttributeName_
}
staAttributeValue :: Lens' SetTopicAttributes (Maybe Text)
staAttributeValue = lens _staAttributeValue (\ s a -> s{_staAttributeValue = a})
staTopicARN :: Lens' SetTopicAttributes Text
staTopicARN = lens _staTopicARN (\ s a -> s{_staTopicARN = a})
staAttributeName :: Lens' SetTopicAttributes Text
staAttributeName = lens _staAttributeName (\ s a -> s{_staAttributeName = a})
instance AWSRequest SetTopicAttributes where
type Rs SetTopicAttributes =
SetTopicAttributesResponse
request = postQuery sns
response = receiveNull SetTopicAttributesResponse'
instance Hashable SetTopicAttributes where
instance NFData SetTopicAttributes where
instance ToHeaders SetTopicAttributes where
toHeaders = const mempty
instance ToPath SetTopicAttributes where
toPath = const "/"
instance ToQuery SetTopicAttributes where
toQuery SetTopicAttributes'{..}
= mconcat
["Action" =: ("SetTopicAttributes" :: ByteString),
"Version" =: ("2010-03-31" :: ByteString),
"AttributeValue" =: _staAttributeValue,
"TopicArn" =: _staTopicARN,
"AttributeName" =: _staAttributeName]
data SetTopicAttributesResponse =
SetTopicAttributesResponse'
deriving (Eq, Read, Show, Data, Typeable, Generic)
setTopicAttributesResponse
:: SetTopicAttributesResponse
setTopicAttributesResponse = SetTopicAttributesResponse'
instance NFData SetTopicAttributesResponse where