{-# 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.DeleteTopic
(
deleteTopic
, DeleteTopic
, dtTopicARN
, deleteTopicResponse
, DeleteTopicResponse
) 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 DeleteTopic = DeleteTopic'
{ _dtTopicARN :: Text
} deriving (Eq, Read, Show, Data, Typeable, Generic)
deleteTopic
:: Text
-> DeleteTopic
deleteTopic pTopicARN_ = DeleteTopic' {_dtTopicARN = pTopicARN_}
dtTopicARN :: Lens' DeleteTopic Text
dtTopicARN = lens _dtTopicARN (\ s a -> s{_dtTopicARN = a})
instance AWSRequest DeleteTopic where
type Rs DeleteTopic = DeleteTopicResponse
request = postQuery sns
response = receiveNull DeleteTopicResponse'
instance Hashable DeleteTopic where
instance NFData DeleteTopic where
instance ToHeaders DeleteTopic where
toHeaders = const mempty
instance ToPath DeleteTopic where
toPath = const "/"
instance ToQuery DeleteTopic where
toQuery DeleteTopic'{..}
= mconcat
["Action" =: ("DeleteTopic" :: ByteString),
"Version" =: ("2010-03-31" :: ByteString),
"TopicArn" =: _dtTopicARN]
data DeleteTopicResponse =
DeleteTopicResponse'
deriving (Eq, Read, Show, Data, Typeable, Generic)
deleteTopicResponse
:: DeleteTopicResponse
deleteTopicResponse = DeleteTopicResponse'
instance NFData DeleteTopicResponse where