{-# 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.S3.RestoreObject
(
restoreObject
, RestoreObject
, roVersionId
, roRequestPayer
, roRestoreRequest
, roBucket
, roKey
, restoreObjectResponse
, RestoreObjectResponse
, rorsRequestCharged
, rorsRestoreOutputPath
, rorsResponseStatus
) where
import Network.AWS.Lens
import Network.AWS.Prelude
import Network.AWS.Request
import Network.AWS.Response
import Network.AWS.S3.Types
import Network.AWS.S3.Types.Product
data RestoreObject = RestoreObject'
{ _roVersionId :: !(Maybe ObjectVersionId)
, _roRequestPayer :: !(Maybe RequestPayer)
, _roRestoreRequest :: !(Maybe RestoreRequest)
, _roBucket :: !BucketName
, _roKey :: !ObjectKey
} deriving (Eq, Show, Data, Typeable, Generic)
restoreObject
:: BucketName
-> ObjectKey
-> RestoreObject
restoreObject pBucket_ pKey_ =
RestoreObject'
{ _roVersionId = Nothing
, _roRequestPayer = Nothing
, _roRestoreRequest = Nothing
, _roBucket = pBucket_
, _roKey = pKey_
}
roVersionId :: Lens' RestoreObject (Maybe ObjectVersionId)
roVersionId = lens _roVersionId (\ s a -> s{_roVersionId = a})
roRequestPayer :: Lens' RestoreObject (Maybe RequestPayer)
roRequestPayer = lens _roRequestPayer (\ s a -> s{_roRequestPayer = a})
roRestoreRequest :: Lens' RestoreObject (Maybe RestoreRequest)
roRestoreRequest = lens _roRestoreRequest (\ s a -> s{_roRestoreRequest = a})
roBucket :: Lens' RestoreObject BucketName
roBucket = lens _roBucket (\ s a -> s{_roBucket = a})
roKey :: Lens' RestoreObject ObjectKey
roKey = lens _roKey (\ s a -> s{_roKey = a})
instance AWSRequest RestoreObject where
type Rs RestoreObject = RestoreObjectResponse
request = postXML s3
response
= receiveEmpty
(\ s h x ->
RestoreObjectResponse' <$>
(h .#? "x-amz-request-charged") <*>
(h .#? "x-amz-restore-output-path")
<*> (pure (fromEnum s)))
instance Hashable RestoreObject where
instance NFData RestoreObject where
instance ToElement RestoreObject where
toElement
= mkElement
"{http://s3.amazonaws.com/doc/2006-03-01/}RestoreRequest"
.
_roRestoreRequest
instance ToHeaders RestoreObject where
toHeaders RestoreObject'{..}
= mconcat ["x-amz-request-payer" =# _roRequestPayer]
instance ToPath RestoreObject where
toPath RestoreObject'{..}
= mconcat ["/", toBS _roBucket, "/", toBS _roKey]
instance ToQuery RestoreObject where
toQuery RestoreObject'{..}
= mconcat ["versionId" =: _roVersionId, "restore"]
data RestoreObjectResponse = RestoreObjectResponse'
{ _rorsRequestCharged :: !(Maybe RequestCharged)
, _rorsRestoreOutputPath :: !(Maybe Text)
, _rorsResponseStatus :: !Int
} deriving (Eq, Read, Show, Data, Typeable, Generic)
restoreObjectResponse
:: Int
-> RestoreObjectResponse
restoreObjectResponse pResponseStatus_ =
RestoreObjectResponse'
{ _rorsRequestCharged = Nothing
, _rorsRestoreOutputPath = Nothing
, _rorsResponseStatus = pResponseStatus_
}
rorsRequestCharged :: Lens' RestoreObjectResponse (Maybe RequestCharged)
rorsRequestCharged = lens _rorsRequestCharged (\ s a -> s{_rorsRequestCharged = a})
rorsRestoreOutputPath :: Lens' RestoreObjectResponse (Maybe Text)
rorsRestoreOutputPath = lens _rorsRestoreOutputPath (\ s a -> s{_rorsRestoreOutputPath = a})
rorsResponseStatus :: Lens' RestoreObjectResponse Int
rorsResponseStatus = lens _rorsResponseStatus (\ s a -> s{_rorsResponseStatus = a})
instance NFData RestoreObjectResponse where