{-# 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.Pinpoint.UpdateSmsChannel
(
updateSmsChannel
, UpdateSmsChannel
, uscApplicationId
, uscSMSChannelRequest
, updateSmsChannelResponse
, UpdateSmsChannelResponse
, uscrsResponseStatus
, uscrsSMSChannelResponse
) where
import Network.AWS.Lens
import Network.AWS.Pinpoint.Types
import Network.AWS.Pinpoint.Types.Product
import Network.AWS.Prelude
import Network.AWS.Request
import Network.AWS.Response
data UpdateSmsChannel = UpdateSmsChannel'
{ _uscApplicationId :: !Text
, _uscSMSChannelRequest :: !SMSChannelRequest
} deriving (Eq, Read, Show, Data, Typeable, Generic)
updateSmsChannel
:: Text
-> SMSChannelRequest
-> UpdateSmsChannel
updateSmsChannel pApplicationId_ pSMSChannelRequest_ =
UpdateSmsChannel'
{ _uscApplicationId = pApplicationId_
, _uscSMSChannelRequest = pSMSChannelRequest_
}
uscApplicationId :: Lens' UpdateSmsChannel Text
uscApplicationId = lens _uscApplicationId (\ s a -> s{_uscApplicationId = a})
uscSMSChannelRequest :: Lens' UpdateSmsChannel SMSChannelRequest
uscSMSChannelRequest = lens _uscSMSChannelRequest (\ s a -> s{_uscSMSChannelRequest = a})
instance AWSRequest UpdateSmsChannel where
type Rs UpdateSmsChannel = UpdateSmsChannelResponse
request = putJSON pinpoint
response
= receiveJSON
(\ s h x ->
UpdateSmsChannelResponse' <$>
(pure (fromEnum s)) <*> (eitherParseJSON x))
instance Hashable UpdateSmsChannel where
instance NFData UpdateSmsChannel where
instance ToHeaders UpdateSmsChannel where
toHeaders
= const
(mconcat
["Content-Type" =#
("application/x-amz-json-1.1" :: ByteString)])
instance ToJSON UpdateSmsChannel where
toJSON UpdateSmsChannel'{..}
= object
(catMaybes
[Just
("SMSChannelRequest" .= _uscSMSChannelRequest)])
instance ToPath UpdateSmsChannel where
toPath UpdateSmsChannel'{..}
= mconcat
["/v1/apps/", toBS _uscApplicationId,
"/channels/sms"]
instance ToQuery UpdateSmsChannel where
toQuery = const mempty
data UpdateSmsChannelResponse = UpdateSmsChannelResponse'
{ _uscrsResponseStatus :: !Int
, _uscrsSMSChannelResponse :: !SMSChannelResponse
} deriving (Eq, Read, Show, Data, Typeable, Generic)
updateSmsChannelResponse
:: Int
-> SMSChannelResponse
-> UpdateSmsChannelResponse
updateSmsChannelResponse pResponseStatus_ pSMSChannelResponse_ =
UpdateSmsChannelResponse'
{ _uscrsResponseStatus = pResponseStatus_
, _uscrsSMSChannelResponse = pSMSChannelResponse_
}
uscrsResponseStatus :: Lens' UpdateSmsChannelResponse Int
uscrsResponseStatus = lens _uscrsResponseStatus (\ s a -> s{_uscrsResponseStatus = a})
uscrsSMSChannelResponse :: Lens' UpdateSmsChannelResponse SMSChannelResponse
uscrsSMSChannelResponse = lens _uscrsSMSChannelResponse (\ s a -> s{_uscrsSMSChannelResponse = a})
instance NFData UpdateSmsChannelResponse where