{-# 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.ListSubscriptionsByTopic
(
listSubscriptionsByTopic
, ListSubscriptionsByTopic
, lsbtNextToken
, lsbtTopicARN
, listSubscriptionsByTopicResponse
, ListSubscriptionsByTopicResponse
, lsbtrsNextToken
, lsbtrsSubscriptions
, lsbtrsResponseStatus
) where
import Network.AWS.Lens
import Network.AWS.Pager
import Network.AWS.Prelude
import Network.AWS.Request
import Network.AWS.Response
import Network.AWS.SNS.Types
import Network.AWS.SNS.Types.Product
data ListSubscriptionsByTopic = ListSubscriptionsByTopic'
{ _lsbtNextToken :: !(Maybe Text)
, _lsbtTopicARN :: !Text
} deriving (Eq, Read, Show, Data, Typeable, Generic)
listSubscriptionsByTopic
:: Text
-> ListSubscriptionsByTopic
listSubscriptionsByTopic pTopicARN_ =
ListSubscriptionsByTopic'
{_lsbtNextToken = Nothing, _lsbtTopicARN = pTopicARN_}
lsbtNextToken :: Lens' ListSubscriptionsByTopic (Maybe Text)
lsbtNextToken = lens _lsbtNextToken (\ s a -> s{_lsbtNextToken = a})
lsbtTopicARN :: Lens' ListSubscriptionsByTopic Text
lsbtTopicARN = lens _lsbtTopicARN (\ s a -> s{_lsbtTopicARN = a})
instance AWSPager ListSubscriptionsByTopic where
page rq rs
| stop (rs ^. lsbtrsNextToken) = Nothing
| stop (rs ^. lsbtrsSubscriptions) = Nothing
| otherwise =
Just $ rq & lsbtNextToken .~ rs ^. lsbtrsNextToken
instance AWSRequest ListSubscriptionsByTopic where
type Rs ListSubscriptionsByTopic =
ListSubscriptionsByTopicResponse
request = postQuery sns
response
= receiveXMLWrapper "ListSubscriptionsByTopicResult"
(\ s h x ->
ListSubscriptionsByTopicResponse' <$>
(x .@? "NextToken") <*>
(x .@? "Subscriptions" .!@ mempty >>=
may (parseXMLList "member"))
<*> (pure (fromEnum s)))
instance Hashable ListSubscriptionsByTopic where
instance NFData ListSubscriptionsByTopic where
instance ToHeaders ListSubscriptionsByTopic where
toHeaders = const mempty
instance ToPath ListSubscriptionsByTopic where
toPath = const "/"
instance ToQuery ListSubscriptionsByTopic where
toQuery ListSubscriptionsByTopic'{..}
= mconcat
["Action" =:
("ListSubscriptionsByTopic" :: ByteString),
"Version" =: ("2010-03-31" :: ByteString),
"NextToken" =: _lsbtNextToken,
"TopicArn" =: _lsbtTopicARN]
data ListSubscriptionsByTopicResponse = ListSubscriptionsByTopicResponse'
{ _lsbtrsNextToken :: !(Maybe Text)
, _lsbtrsSubscriptions :: !(Maybe [Subscription])
, _lsbtrsResponseStatus :: !Int
} deriving (Eq, Read, Show, Data, Typeable, Generic)
listSubscriptionsByTopicResponse
:: Int
-> ListSubscriptionsByTopicResponse
listSubscriptionsByTopicResponse pResponseStatus_ =
ListSubscriptionsByTopicResponse'
{ _lsbtrsNextToken = Nothing
, _lsbtrsSubscriptions = Nothing
, _lsbtrsResponseStatus = pResponseStatus_
}
lsbtrsNextToken :: Lens' ListSubscriptionsByTopicResponse (Maybe Text)
lsbtrsNextToken = lens _lsbtrsNextToken (\ s a -> s{_lsbtrsNextToken = a})
lsbtrsSubscriptions :: Lens' ListSubscriptionsByTopicResponse [Subscription]
lsbtrsSubscriptions = lens _lsbtrsSubscriptions (\ s a -> s{_lsbtrsSubscriptions = a}) . _Default . _Coerce
lsbtrsResponseStatus :: Lens' ListSubscriptionsByTopicResponse Int
lsbtrsResponseStatus = lens _lsbtrsResponseStatus (\ s a -> s{_lsbtrsResponseStatus = a})
instance NFData ListSubscriptionsByTopicResponse
where