{-# 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.GetSMSAttributes
(
getSMSAttributes
, GetSMSAttributes
, gsmsaAttributes
, getSMSAttributesResponse
, GetSMSAttributesResponse
, gsmsarsAttributes
, gsmsarsResponseStatus
) 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 GetSMSAttributes = GetSMSAttributes'
{ _gsmsaAttributes :: Maybe [Text]
} deriving (Eq, Read, Show, Data, Typeable, Generic)
getSMSAttributes
:: GetSMSAttributes
getSMSAttributes = GetSMSAttributes' {_gsmsaAttributes = Nothing}
gsmsaAttributes :: Lens' GetSMSAttributes [Text]
gsmsaAttributes = lens _gsmsaAttributes (\ s a -> s{_gsmsaAttributes = a}) . _Default . _Coerce
instance AWSRequest GetSMSAttributes where
type Rs GetSMSAttributes = GetSMSAttributesResponse
request = postQuery sns
response
= receiveXMLWrapper "GetSMSAttributesResult"
(\ s h x ->
GetSMSAttributesResponse' <$>
(x .@? "attributes" .!@ mempty >>=
may (parseXMLMap "entry" "key" "value"))
<*> (pure (fromEnum s)))
instance Hashable GetSMSAttributes where
instance NFData GetSMSAttributes where
instance ToHeaders GetSMSAttributes where
toHeaders = const mempty
instance ToPath GetSMSAttributes where
toPath = const "/"
instance ToQuery GetSMSAttributes where
toQuery GetSMSAttributes'{..}
= mconcat
["Action" =: ("GetSMSAttributes" :: ByteString),
"Version" =: ("2010-03-31" :: ByteString),
"attributes" =:
toQuery (toQueryList "member" <$> _gsmsaAttributes)]
data GetSMSAttributesResponse = GetSMSAttributesResponse'
{ _gsmsarsAttributes :: !(Maybe (Map Text Text))
, _gsmsarsResponseStatus :: !Int
} deriving (Eq, Read, Show, Data, Typeable, Generic)
getSMSAttributesResponse
:: Int
-> GetSMSAttributesResponse
getSMSAttributesResponse pResponseStatus_ =
GetSMSAttributesResponse'
{_gsmsarsAttributes = Nothing, _gsmsarsResponseStatus = pResponseStatus_}
gsmsarsAttributes :: Lens' GetSMSAttributesResponse (HashMap Text Text)
gsmsarsAttributes = lens _gsmsarsAttributes (\ s a -> s{_gsmsarsAttributes = a}) . _Default . _Map
gsmsarsResponseStatus :: Lens' GetSMSAttributesResponse Int
gsmsarsResponseStatus = lens _gsmsarsResponseStatus (\ s a -> s{_gsmsarsResponseStatus = a})
instance NFData GetSMSAttributesResponse where