module Aws.S3.Commands.DeleteObjectVersion
where
import Aws.Core
import Aws.S3.Core
import Data.ByteString.Char8 ()
import qualified Data.Text as T
import qualified Data.Text.Encoding as T
data DeleteObjectVersion = DeleteObjectVersion {
DeleteObjectVersion -> Text
dovObjectName :: T.Text,
DeleteObjectVersion -> Text
dovBucket :: Bucket,
DeleteObjectVersion -> Text
dovVersionId :: T.Text
} deriving (Int -> DeleteObjectVersion -> ShowS
[DeleteObjectVersion] -> ShowS
DeleteObjectVersion -> String
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [DeleteObjectVersion] -> ShowS
$cshowList :: [DeleteObjectVersion] -> ShowS
show :: DeleteObjectVersion -> String
$cshow :: DeleteObjectVersion -> String
showsPrec :: Int -> DeleteObjectVersion -> ShowS
$cshowsPrec :: Int -> DeleteObjectVersion -> ShowS
Show)
deleteObjectVersion :: Bucket -> T.Text -> T.Text -> DeleteObjectVersion
deleteObjectVersion :: Text -> Text -> Text -> DeleteObjectVersion
deleteObjectVersion Text
bucket Text
object Text
version
= DeleteObjectVersion {
dovObjectName :: Text
dovObjectName = Text
object
, dovBucket :: Text
dovBucket = Text
bucket
, dovVersionId :: Text
dovVersionId = Text
version
}
data DeleteObjectVersionResponse = DeleteObjectVersionResponse {
} deriving (Int -> DeleteObjectVersionResponse -> ShowS
[DeleteObjectVersionResponse] -> ShowS
DeleteObjectVersionResponse -> String
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [DeleteObjectVersionResponse] -> ShowS
$cshowList :: [DeleteObjectVersionResponse] -> ShowS
show :: DeleteObjectVersionResponse -> String
$cshow :: DeleteObjectVersionResponse -> String
showsPrec :: Int -> DeleteObjectVersionResponse -> ShowS
$cshowsPrec :: Int -> DeleteObjectVersionResponse -> ShowS
Show)
instance SignQuery DeleteObjectVersion where
type ServiceConfiguration DeleteObjectVersion = S3Configuration
signQuery :: forall queryType.
DeleteObjectVersion
-> ServiceConfiguration DeleteObjectVersion queryType
-> SignatureData
-> SignedQuery
signQuery DeleteObjectVersion {Text
dovVersionId :: Text
dovBucket :: Text
dovObjectName :: Text
dovVersionId :: DeleteObjectVersion -> Text
dovBucket :: DeleteObjectVersion -> Text
dovObjectName :: DeleteObjectVersion -> Text
..} = forall qt.
S3Query -> S3Configuration qt -> SignatureData -> SignedQuery
s3SignQuery S3Query {
s3QMethod :: Method
s3QMethod = Method
Delete
, s3QBucket :: Maybe ByteString
s3QBucket = forall a. a -> Maybe a
Just forall a b. (a -> b) -> a -> b
$ Text -> ByteString
T.encodeUtf8 Text
dovBucket
, s3QSubresources :: Query
s3QSubresources = [ (ByteString
"versionId", forall a. a -> Maybe a
Just forall a b. (a -> b) -> a -> b
$ Text -> ByteString
T.encodeUtf8 Text
dovVersionId) ]
, s3QQuery :: Query
s3QQuery = []
, s3QContentType :: Maybe ByteString
s3QContentType = forall a. Maybe a
Nothing
, s3QContentMd5 :: Maybe (Digest MD5)
s3QContentMd5 = forall a. Maybe a
Nothing
, s3QAmzHeaders :: RequestHeaders
s3QAmzHeaders = []
, s3QOtherHeaders :: RequestHeaders
s3QOtherHeaders = []
, s3QRequestBody :: Maybe RequestBody
s3QRequestBody = forall a. Maybe a
Nothing
, s3QObject :: Maybe ByteString
s3QObject = forall a. a -> Maybe a
Just forall a b. (a -> b) -> a -> b
$ Text -> ByteString
T.encodeUtf8 Text
dovObjectName
}
instance ResponseConsumer DeleteObjectVersion DeleteObjectVersionResponse where
type ResponseMetadata DeleteObjectVersionResponse = S3Metadata
responseConsumer :: Request
-> DeleteObjectVersion
-> IORef (ResponseMetadata DeleteObjectVersionResponse)
-> HTTPResponseConsumer DeleteObjectVersionResponse
responseConsumer Request
_ DeleteObjectVersion
_
= forall a.
HTTPResponseConsumer a
-> IORef S3Metadata -> HTTPResponseConsumer a
s3ResponseConsumer forall a b. (a -> b) -> a -> b
$ \Response (ConduitM () ByteString (ResourceT IO) ())
_ -> forall (m :: * -> *) a. Monad m => a -> m a
return DeleteObjectVersionResponse
DeleteObjectVersionResponse
instance Transaction DeleteObjectVersion DeleteObjectVersionResponse
instance AsMemoryResponse DeleteObjectVersionResponse where
type MemoryResponse DeleteObjectVersionResponse = DeleteObjectVersionResponse
loadToMemory :: DeleteObjectVersionResponse
-> ResourceT IO (MemoryResponse DeleteObjectVersionResponse)
loadToMemory = forall (m :: * -> *) a. Monad m => a -> m a
return