{-# 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.DynamoDB.UpdateTimeToLive
    (
    
      updateTimeToLive
    , UpdateTimeToLive
    
    , uttlTableName
    , uttlTimeToLiveSpecification
    
    , updateTimeToLiveResponse
    , UpdateTimeToLiveResponse
    
    , uttlrsTimeToLiveSpecification
    , uttlrsResponseStatus
    ) where
import Network.AWS.DynamoDB.Types
import Network.AWS.DynamoDB.Types.Product
import Network.AWS.Lens
import Network.AWS.Prelude
import Network.AWS.Request
import Network.AWS.Response
data UpdateTimeToLive = UpdateTimeToLive'
  { _uttlTableName               :: !Text
  , _uttlTimeToLiveSpecification :: !TimeToLiveSpecification
  } deriving (Eq, Read, Show, Data, Typeable, Generic)
updateTimeToLive
    :: Text 
    -> TimeToLiveSpecification 
    -> UpdateTimeToLive
updateTimeToLive pTableName_ pTimeToLiveSpecification_ =
  UpdateTimeToLive'
    { _uttlTableName = pTableName_
    , _uttlTimeToLiveSpecification = pTimeToLiveSpecification_
    }
uttlTableName :: Lens' UpdateTimeToLive Text
uttlTableName = lens _uttlTableName (\ s a -> s{_uttlTableName = a})
uttlTimeToLiveSpecification :: Lens' UpdateTimeToLive TimeToLiveSpecification
uttlTimeToLiveSpecification = lens _uttlTimeToLiveSpecification (\ s a -> s{_uttlTimeToLiveSpecification = a})
instance AWSRequest UpdateTimeToLive where
        type Rs UpdateTimeToLive = UpdateTimeToLiveResponse
        request = postJSON dynamoDB
        response
          = receiveJSON
              (\ s h x ->
                 UpdateTimeToLiveResponse' <$>
                   (x .?> "TimeToLiveSpecification") <*>
                     (pure (fromEnum s)))
instance Hashable UpdateTimeToLive where
instance NFData UpdateTimeToLive where
instance ToHeaders UpdateTimeToLive where
        toHeaders
          = const
              (mconcat
                 ["X-Amz-Target" =#
                    ("DynamoDB_20120810.UpdateTimeToLive" :: ByteString),
                  "Content-Type" =#
                    ("application/x-amz-json-1.0" :: ByteString)])
instance ToJSON UpdateTimeToLive where
        toJSON UpdateTimeToLive'{..}
          = object
              (catMaybes
                 [Just ("TableName" .= _uttlTableName),
                  Just
                    ("TimeToLiveSpecification" .=
                       _uttlTimeToLiveSpecification)])
instance ToPath UpdateTimeToLive where
        toPath = const "/"
instance ToQuery UpdateTimeToLive where
        toQuery = const mempty
data UpdateTimeToLiveResponse = UpdateTimeToLiveResponse'
  { _uttlrsTimeToLiveSpecification :: !(Maybe TimeToLiveSpecification)
  , _uttlrsResponseStatus          :: !Int
  } deriving (Eq, Read, Show, Data, Typeable, Generic)
updateTimeToLiveResponse
    :: Int 
    -> UpdateTimeToLiveResponse
updateTimeToLiveResponse pResponseStatus_ =
  UpdateTimeToLiveResponse'
    { _uttlrsTimeToLiveSpecification = Nothing
    , _uttlrsResponseStatus = pResponseStatus_
    }
uttlrsTimeToLiveSpecification :: Lens' UpdateTimeToLiveResponse (Maybe TimeToLiveSpecification)
uttlrsTimeToLiveSpecification = lens _uttlrsTimeToLiveSpecification (\ s a -> s{_uttlrsTimeToLiveSpecification = a})
uttlrsResponseStatus :: Lens' UpdateTimeToLiveResponse Int
uttlrsResponseStatus = lens _uttlrsResponseStatus (\ s a -> s{_uttlrsResponseStatus = a})
instance NFData UpdateTimeToLiveResponse where