{-# 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.HeadObject
(
headObject
, HeadObject
, hoIfMatch
, hoVersionId
, hoSSECustomerAlgorithm
, hoSSECustomerKey
, hoRequestPayer
, hoIfModifiedSince
, hoPartNumber
, hoRange
, hoIfUnmodifiedSince
, hoSSECustomerKeyMD5
, hoIfNoneMatch
, hoBucket
, hoKey
, headObjectResponse
, HeadObjectResponse
, horsRequestCharged
, horsPartsCount
, horsETag
, horsVersionId
, horsContentLength
, horsExpires
, horsRestore
, horsExpiration
, horsDeleteMarker
, horsSSECustomerAlgorithm
, horsMissingMeta
, horsWebsiteRedirectLocation
, horsAcceptRanges
, horsStorageClass
, horsSSECustomerKeyMD5
, horsSSEKMSKeyId
, horsContentEncoding
, horsMetadata
, horsReplicationStatus
, horsCacheControl
, horsContentLanguage
, horsLastModified
, horsContentDisposition
, horsServerSideEncryption
, horsContentType
, horsResponseStatus
) 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 HeadObject = HeadObject'
{ _hoIfMatch :: !(Maybe Text)
, _hoVersionId :: !(Maybe ObjectVersionId)
, _hoSSECustomerAlgorithm :: !(Maybe Text)
, _hoSSECustomerKey :: !(Maybe (Sensitive Text))
, _hoRequestPayer :: !(Maybe RequestPayer)
, _hoIfModifiedSince :: !(Maybe RFC822)
, _hoPartNumber :: !(Maybe Int)
, _hoRange :: !(Maybe Text)
, _hoIfUnmodifiedSince :: !(Maybe RFC822)
, _hoSSECustomerKeyMD5 :: !(Maybe Text)
, _hoIfNoneMatch :: !(Maybe Text)
, _hoBucket :: !BucketName
, _hoKey :: !ObjectKey
} deriving (Eq, Show, Data, Typeable, Generic)
headObject
:: BucketName
-> ObjectKey
-> HeadObject
headObject pBucket_ pKey_ =
HeadObject'
{ _hoIfMatch = Nothing
, _hoVersionId = Nothing
, _hoSSECustomerAlgorithm = Nothing
, _hoSSECustomerKey = Nothing
, _hoRequestPayer = Nothing
, _hoIfModifiedSince = Nothing
, _hoPartNumber = Nothing
, _hoRange = Nothing
, _hoIfUnmodifiedSince = Nothing
, _hoSSECustomerKeyMD5 = Nothing
, _hoIfNoneMatch = Nothing
, _hoBucket = pBucket_
, _hoKey = pKey_
}
hoIfMatch :: Lens' HeadObject (Maybe Text)
hoIfMatch = lens _hoIfMatch (\ s a -> s{_hoIfMatch = a})
hoVersionId :: Lens' HeadObject (Maybe ObjectVersionId)
hoVersionId = lens _hoVersionId (\ s a -> s{_hoVersionId = a})
hoSSECustomerAlgorithm :: Lens' HeadObject (Maybe Text)
hoSSECustomerAlgorithm = lens _hoSSECustomerAlgorithm (\ s a -> s{_hoSSECustomerAlgorithm = a})
hoSSECustomerKey :: Lens' HeadObject (Maybe Text)
hoSSECustomerKey = lens _hoSSECustomerKey (\ s a -> s{_hoSSECustomerKey = a}) . mapping _Sensitive
hoRequestPayer :: Lens' HeadObject (Maybe RequestPayer)
hoRequestPayer = lens _hoRequestPayer (\ s a -> s{_hoRequestPayer = a})
hoIfModifiedSince :: Lens' HeadObject (Maybe UTCTime)
hoIfModifiedSince = lens _hoIfModifiedSince (\ s a -> s{_hoIfModifiedSince = a}) . mapping _Time
hoPartNumber :: Lens' HeadObject (Maybe Int)
hoPartNumber = lens _hoPartNumber (\ s a -> s{_hoPartNumber = a})
hoRange :: Lens' HeadObject (Maybe Text)
hoRange = lens _hoRange (\ s a -> s{_hoRange = a})
hoIfUnmodifiedSince :: Lens' HeadObject (Maybe UTCTime)
hoIfUnmodifiedSince = lens _hoIfUnmodifiedSince (\ s a -> s{_hoIfUnmodifiedSince = a}) . mapping _Time
hoSSECustomerKeyMD5 :: Lens' HeadObject (Maybe Text)
hoSSECustomerKeyMD5 = lens _hoSSECustomerKeyMD5 (\ s a -> s{_hoSSECustomerKeyMD5 = a})
hoIfNoneMatch :: Lens' HeadObject (Maybe Text)
hoIfNoneMatch = lens _hoIfNoneMatch (\ s a -> s{_hoIfNoneMatch = a})
hoBucket :: Lens' HeadObject BucketName
hoBucket = lens _hoBucket (\ s a -> s{_hoBucket = a})
hoKey :: Lens' HeadObject ObjectKey
hoKey = lens _hoKey (\ s a -> s{_hoKey = a})
instance AWSRequest HeadObject where
type Rs HeadObject = HeadObjectResponse
request = head' s3
response
= receiveEmpty
(\ s h x ->
HeadObjectResponse' <$>
(h .#? "x-amz-request-charged") <*>
(h .#? "x-amz-mp-parts-count")
<*> (h .#? "ETag")
<*> (h .#? "x-amz-version-id")
<*> (h .#? "Content-Length")
<*> (h .#? "Expires")
<*> (h .#? "x-amz-restore")
<*> (h .#? "x-amz-expiration")
<*> (h .#? "x-amz-delete-marker")
<*>
(h .#?
"x-amz-server-side-encryption-customer-algorithm")
<*> (h .#? "x-amz-missing-meta")
<*> (h .#? "x-amz-website-redirect-location")
<*> (h .#? "accept-ranges")
<*> (h .#? "x-amz-storage-class")
<*>
(h .#?
"x-amz-server-side-encryption-customer-key-MD5")
<*>
(h .#? "x-amz-server-side-encryption-aws-kms-key-id")
<*> (h .#? "Content-Encoding")
<*> (parseHeadersMap "x-amz-meta-" h)
<*> (h .#? "x-amz-replication-status")
<*> (h .#? "Cache-Control")
<*> (h .#? "Content-Language")
<*> (h .#? "Last-Modified")
<*> (h .#? "Content-Disposition")
<*> (h .#? "x-amz-server-side-encryption")
<*> (h .#? "Content-Type")
<*> (pure (fromEnum s)))
instance Hashable HeadObject where
instance NFData HeadObject where
instance ToHeaders HeadObject where
toHeaders HeadObject'{..}
= mconcat
["If-Match" =# _hoIfMatch,
"x-amz-server-side-encryption-customer-algorithm" =#
_hoSSECustomerAlgorithm,
"x-amz-server-side-encryption-customer-key" =#
_hoSSECustomerKey,
"x-amz-request-payer" =# _hoRequestPayer,
"If-Modified-Since" =# _hoIfModifiedSince,
"Range" =# _hoRange,
"If-Unmodified-Since" =# _hoIfUnmodifiedSince,
"x-amz-server-side-encryption-customer-key-MD5" =#
_hoSSECustomerKeyMD5,
"If-None-Match" =# _hoIfNoneMatch]
instance ToPath HeadObject where
toPath HeadObject'{..}
= mconcat ["/", toBS _hoBucket, "/", toBS _hoKey]
instance ToQuery HeadObject where
toQuery HeadObject'{..}
= mconcat
["versionId" =: _hoVersionId,
"partNumber" =: _hoPartNumber]
data HeadObjectResponse = HeadObjectResponse'
{ _horsRequestCharged :: !(Maybe RequestCharged)
, _horsPartsCount :: !(Maybe Int)
, _horsETag :: !(Maybe ETag)
, _horsVersionId :: !(Maybe ObjectVersionId)
, _horsContentLength :: !(Maybe Integer)
, _horsExpires :: !(Maybe RFC822)
, _horsRestore :: !(Maybe Text)
, _horsExpiration :: !(Maybe Text)
, _horsDeleteMarker :: !(Maybe Bool)
, _horsSSECustomerAlgorithm :: !(Maybe Text)
, _horsMissingMeta :: !(Maybe Int)
, _horsWebsiteRedirectLocation :: !(Maybe Text)
, _horsAcceptRanges :: !(Maybe Text)
, _horsStorageClass :: !(Maybe StorageClass)
, _horsSSECustomerKeyMD5 :: !(Maybe Text)
, _horsSSEKMSKeyId :: !(Maybe (Sensitive Text))
, _horsContentEncoding :: !(Maybe Text)
, _horsMetadata :: !(Map Text Text)
, _horsReplicationStatus :: !(Maybe ReplicationStatus)
, _horsCacheControl :: !(Maybe Text)
, _horsContentLanguage :: !(Maybe Text)
, _horsLastModified :: !(Maybe RFC822)
, _horsContentDisposition :: !(Maybe Text)
, _horsServerSideEncryption :: !(Maybe ServerSideEncryption)
, _horsContentType :: !(Maybe Text)
, _horsResponseStatus :: !Int
} deriving (Eq, Show, Data, Typeable, Generic)
headObjectResponse
:: Int
-> HeadObjectResponse
headObjectResponse pResponseStatus_ =
HeadObjectResponse'
{ _horsRequestCharged = Nothing
, _horsPartsCount = Nothing
, _horsETag = Nothing
, _horsVersionId = Nothing
, _horsContentLength = Nothing
, _horsExpires = Nothing
, _horsRestore = Nothing
, _horsExpiration = Nothing
, _horsDeleteMarker = Nothing
, _horsSSECustomerAlgorithm = Nothing
, _horsMissingMeta = Nothing
, _horsWebsiteRedirectLocation = Nothing
, _horsAcceptRanges = Nothing
, _horsStorageClass = Nothing
, _horsSSECustomerKeyMD5 = Nothing
, _horsSSEKMSKeyId = Nothing
, _horsContentEncoding = Nothing
, _horsMetadata = mempty
, _horsReplicationStatus = Nothing
, _horsCacheControl = Nothing
, _horsContentLanguage = Nothing
, _horsLastModified = Nothing
, _horsContentDisposition = Nothing
, _horsServerSideEncryption = Nothing
, _horsContentType = Nothing
, _horsResponseStatus = pResponseStatus_
}
horsRequestCharged :: Lens' HeadObjectResponse (Maybe RequestCharged)
horsRequestCharged = lens _horsRequestCharged (\ s a -> s{_horsRequestCharged = a})
horsPartsCount :: Lens' HeadObjectResponse (Maybe Int)
horsPartsCount = lens _horsPartsCount (\ s a -> s{_horsPartsCount = a})
horsETag :: Lens' HeadObjectResponse (Maybe ETag)
horsETag = lens _horsETag (\ s a -> s{_horsETag = a})
horsVersionId :: Lens' HeadObjectResponse (Maybe ObjectVersionId)
horsVersionId = lens _horsVersionId (\ s a -> s{_horsVersionId = a})
horsContentLength :: Lens' HeadObjectResponse (Maybe Integer)
horsContentLength = lens _horsContentLength (\ s a -> s{_horsContentLength = a})
horsExpires :: Lens' HeadObjectResponse (Maybe UTCTime)
horsExpires = lens _horsExpires (\ s a -> s{_horsExpires = a}) . mapping _Time
horsRestore :: Lens' HeadObjectResponse (Maybe Text)
horsRestore = lens _horsRestore (\ s a -> s{_horsRestore = a})
horsExpiration :: Lens' HeadObjectResponse (Maybe Text)
horsExpiration = lens _horsExpiration (\ s a -> s{_horsExpiration = a})
horsDeleteMarker :: Lens' HeadObjectResponse (Maybe Bool)
horsDeleteMarker = lens _horsDeleteMarker (\ s a -> s{_horsDeleteMarker = a})
horsSSECustomerAlgorithm :: Lens' HeadObjectResponse (Maybe Text)
horsSSECustomerAlgorithm = lens _horsSSECustomerAlgorithm (\ s a -> s{_horsSSECustomerAlgorithm = a})
horsMissingMeta :: Lens' HeadObjectResponse (Maybe Int)
horsMissingMeta = lens _horsMissingMeta (\ s a -> s{_horsMissingMeta = a})
horsWebsiteRedirectLocation :: Lens' HeadObjectResponse (Maybe Text)
horsWebsiteRedirectLocation = lens _horsWebsiteRedirectLocation (\ s a -> s{_horsWebsiteRedirectLocation = a})
horsAcceptRanges :: Lens' HeadObjectResponse (Maybe Text)
horsAcceptRanges = lens _horsAcceptRanges (\ s a -> s{_horsAcceptRanges = a})
horsStorageClass :: Lens' HeadObjectResponse (Maybe StorageClass)
horsStorageClass = lens _horsStorageClass (\ s a -> s{_horsStorageClass = a})
horsSSECustomerKeyMD5 :: Lens' HeadObjectResponse (Maybe Text)
horsSSECustomerKeyMD5 = lens _horsSSECustomerKeyMD5 (\ s a -> s{_horsSSECustomerKeyMD5 = a})
horsSSEKMSKeyId :: Lens' HeadObjectResponse (Maybe Text)
horsSSEKMSKeyId = lens _horsSSEKMSKeyId (\ s a -> s{_horsSSEKMSKeyId = a}) . mapping _Sensitive
horsContentEncoding :: Lens' HeadObjectResponse (Maybe Text)
horsContentEncoding = lens _horsContentEncoding (\ s a -> s{_horsContentEncoding = a})
horsMetadata :: Lens' HeadObjectResponse (HashMap Text Text)
horsMetadata = lens _horsMetadata (\ s a -> s{_horsMetadata = a}) . _Map
horsReplicationStatus :: Lens' HeadObjectResponse (Maybe ReplicationStatus)
horsReplicationStatus = lens _horsReplicationStatus (\ s a -> s{_horsReplicationStatus = a})
horsCacheControl :: Lens' HeadObjectResponse (Maybe Text)
horsCacheControl = lens _horsCacheControl (\ s a -> s{_horsCacheControl = a})
horsContentLanguage :: Lens' HeadObjectResponse (Maybe Text)
horsContentLanguage = lens _horsContentLanguage (\ s a -> s{_horsContentLanguage = a})
horsLastModified :: Lens' HeadObjectResponse (Maybe UTCTime)
horsLastModified = lens _horsLastModified (\ s a -> s{_horsLastModified = a}) . mapping _Time
horsContentDisposition :: Lens' HeadObjectResponse (Maybe Text)
horsContentDisposition = lens _horsContentDisposition (\ s a -> s{_horsContentDisposition = a})
horsServerSideEncryption :: Lens' HeadObjectResponse (Maybe ServerSideEncryption)
horsServerSideEncryption = lens _horsServerSideEncryption (\ s a -> s{_horsServerSideEncryption = a})
horsContentType :: Lens' HeadObjectResponse (Maybe Text)
horsContentType = lens _horsContentType (\ s a -> s{_horsContentType = a})
horsResponseStatus :: Lens' HeadObjectResponse Int
horsResponseStatus = lens _horsResponseStatus (\ s a -> s{_horsResponseStatus = a})
instance NFData HeadObjectResponse where