{-# 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.DeleteEndpoint
(
deleteEndpoint
, DeleteEndpoint
, deEndpointARN
, deleteEndpointResponse
, DeleteEndpointResponse
) 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 DeleteEndpoint = DeleteEndpoint'
{ _deEndpointARN :: Text
} deriving (Eq, Read, Show, Data, Typeable, Generic)
deleteEndpoint
:: Text
-> DeleteEndpoint
deleteEndpoint pEndpointARN_ = DeleteEndpoint' {_deEndpointARN = pEndpointARN_}
deEndpointARN :: Lens' DeleteEndpoint Text
deEndpointARN = lens _deEndpointARN (\ s a -> s{_deEndpointARN = a})
instance AWSRequest DeleteEndpoint where
type Rs DeleteEndpoint = DeleteEndpointResponse
request = postQuery sns
response = receiveNull DeleteEndpointResponse'
instance Hashable DeleteEndpoint where
instance NFData DeleteEndpoint where
instance ToHeaders DeleteEndpoint where
toHeaders = const mempty
instance ToPath DeleteEndpoint where
toPath = const "/"
instance ToQuery DeleteEndpoint where
toQuery DeleteEndpoint'{..}
= mconcat
["Action" =: ("DeleteEndpoint" :: ByteString),
"Version" =: ("2010-03-31" :: ByteString),
"EndpointArn" =: _deEndpointARN]
data DeleteEndpointResponse =
DeleteEndpointResponse'
deriving (Eq, Read, Show, Data, Typeable, Generic)
deleteEndpointResponse
:: DeleteEndpointResponse
deleteEndpointResponse = DeleteEndpointResponse'
instance NFData DeleteEndpointResponse where