{-# 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.CreateTopic
(
createTopic
, CreateTopic
, ctName
, createTopicResponse
, CreateTopicResponse
, ctrsTopicARN
, ctrsResponseStatus
) 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 CreateTopic = CreateTopic'
{ _ctName :: Text
} deriving (Eq, Read, Show, Data, Typeable, Generic)
createTopic
:: Text
-> CreateTopic
createTopic pName_ = CreateTopic' {_ctName = pName_}
ctName :: Lens' CreateTopic Text
ctName = lens _ctName (\ s a -> s{_ctName = a})
instance AWSRequest CreateTopic where
type Rs CreateTopic = CreateTopicResponse
request = postQuery sns
response
= receiveXMLWrapper "CreateTopicResult"
(\ s h x ->
CreateTopicResponse' <$>
(x .@? "TopicArn") <*> (pure (fromEnum s)))
instance Hashable CreateTopic where
instance NFData CreateTopic where
instance ToHeaders CreateTopic where
toHeaders = const mempty
instance ToPath CreateTopic where
toPath = const "/"
instance ToQuery CreateTopic where
toQuery CreateTopic'{..}
= mconcat
["Action" =: ("CreateTopic" :: ByteString),
"Version" =: ("2010-03-31" :: ByteString),
"Name" =: _ctName]
data CreateTopicResponse = CreateTopicResponse'
{ _ctrsTopicARN :: !(Maybe Text)
, _ctrsResponseStatus :: !Int
} deriving (Eq, Read, Show, Data, Typeable, Generic)
createTopicResponse
:: Int
-> CreateTopicResponse
createTopicResponse pResponseStatus_ =
CreateTopicResponse'
{_ctrsTopicARN = Nothing, _ctrsResponseStatus = pResponseStatus_}
ctrsTopicARN :: Lens' CreateTopicResponse (Maybe Text)
ctrsTopicARN = lens _ctrsTopicARN (\ s a -> s{_ctrsTopicARN = a})
ctrsResponseStatus :: Lens' CreateTopicResponse Int
ctrsResponseStatus = lens _ctrsResponseStatus (\ s a -> s{_ctrsResponseStatus = a})
instance NFData CreateTopicResponse where