{-# 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.RemovePermission
(
removePermission
, RemovePermission
, rpTopicARN
, rpLabel
, removePermissionResponse
, RemovePermissionResponse
) 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 RemovePermission = RemovePermission'
{ _rpTopicARN :: !Text
, _rpLabel :: !Text
} deriving (Eq, Read, Show, Data, Typeable, Generic)
removePermission
:: Text
-> Text
-> RemovePermission
removePermission pTopicARN_ pLabel_ =
RemovePermission' {_rpTopicARN = pTopicARN_, _rpLabel = pLabel_}
rpTopicARN :: Lens' RemovePermission Text
rpTopicARN = lens _rpTopicARN (\ s a -> s{_rpTopicARN = a})
rpLabel :: Lens' RemovePermission Text
rpLabel = lens _rpLabel (\ s a -> s{_rpLabel = a})
instance AWSRequest RemovePermission where
type Rs RemovePermission = RemovePermissionResponse
request = postQuery sns
response = receiveNull RemovePermissionResponse'
instance Hashable RemovePermission where
instance NFData RemovePermission where
instance ToHeaders RemovePermission where
toHeaders = const mempty
instance ToPath RemovePermission where
toPath = const "/"
instance ToQuery RemovePermission where
toQuery RemovePermission'{..}
= mconcat
["Action" =: ("RemovePermission" :: ByteString),
"Version" =: ("2010-03-31" :: ByteString),
"TopicArn" =: _rpTopicARN, "Label" =: _rpLabel]
data RemovePermissionResponse =
RemovePermissionResponse'
deriving (Eq, Read, Show, Data, Typeable, Generic)
removePermissionResponse
:: RemovePermissionResponse
removePermissionResponse = RemovePermissionResponse'
instance NFData RemovePermissionResponse where