{-# 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.AddPermission
(
addPermission
, AddPermission
, apTopicARN
, apLabel
, apAWSAccountId
, apActionName
, addPermissionResponse
, AddPermissionResponse
) 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 AddPermission = AddPermission'
{ _apTopicARN :: !Text
, _apLabel :: !Text
, _apAWSAccountId :: ![Text]
, _apActionName :: ![Text]
} deriving (Eq, Read, Show, Data, Typeable, Generic)
addPermission
:: Text
-> Text
-> AddPermission
addPermission pTopicARN_ pLabel_ =
AddPermission'
{ _apTopicARN = pTopicARN_
, _apLabel = pLabel_
, _apAWSAccountId = mempty
, _apActionName = mempty
}
apTopicARN :: Lens' AddPermission Text
apTopicARN = lens _apTopicARN (\ s a -> s{_apTopicARN = a})
apLabel :: Lens' AddPermission Text
apLabel = lens _apLabel (\ s a -> s{_apLabel = a})
apAWSAccountId :: Lens' AddPermission [Text]
apAWSAccountId = lens _apAWSAccountId (\ s a -> s{_apAWSAccountId = a}) . _Coerce
apActionName :: Lens' AddPermission [Text]
apActionName = lens _apActionName (\ s a -> s{_apActionName = a}) . _Coerce
instance AWSRequest AddPermission where
type Rs AddPermission = AddPermissionResponse
request = postQuery sns
response = receiveNull AddPermissionResponse'
instance Hashable AddPermission where
instance NFData AddPermission where
instance ToHeaders AddPermission where
toHeaders = const mempty
instance ToPath AddPermission where
toPath = const "/"
instance ToQuery AddPermission where
toQuery AddPermission'{..}
= mconcat
["Action" =: ("AddPermission" :: ByteString),
"Version" =: ("2010-03-31" :: ByteString),
"TopicArn" =: _apTopicARN, "Label" =: _apLabel,
"AWSAccountId" =:
toQueryList "member" _apAWSAccountId,
"ActionName" =: toQueryList "member" _apActionName]
data AddPermissionResponse =
AddPermissionResponse'
deriving (Eq, Read, Show, Data, Typeable, Generic)
addPermissionResponse
:: AddPermissionResponse
addPermissionResponse = AddPermissionResponse'
instance NFData AddPermissionResponse where