{-# 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.GetObject
(
getObject
, GetObject
, goIfMatch
, goVersionId
, goResponseContentType
, goResponseContentDisposition
, goResponseContentLanguage
, goSSECustomerAlgorithm
, goSSECustomerKey
, goRequestPayer
, goResponseContentEncoding
, goIfModifiedSince
, goPartNumber
, goRange
, goIfUnmodifiedSince
, goSSECustomerKeyMD5
, goResponseCacheControl
, goResponseExpires
, goIfNoneMatch
, goBucket
, goKey
, getObjectResponse
, GetObjectResponse
, gorsRequestCharged
, gorsPartsCount
, gorsETag
, gorsVersionId
, gorsContentLength
, gorsExpires
, gorsRestore
, gorsExpiration
, gorsDeleteMarker
, gorsSSECustomerAlgorithm
, gorsTagCount
, gorsMissingMeta
, gorsWebsiteRedirectLocation
, gorsAcceptRanges
, gorsStorageClass
, gorsSSECustomerKeyMD5
, gorsSSEKMSKeyId
, gorsContentEncoding
, gorsMetadata
, gorsReplicationStatus
, gorsCacheControl
, gorsContentLanguage
, gorsLastModified
, gorsContentDisposition
, gorsContentRange
, gorsServerSideEncryption
, gorsContentType
, gorsResponseStatus
, gorsBody
) 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 GetObject = GetObject'
{ _goIfMatch :: !(Maybe Text)
, _goVersionId :: !(Maybe ObjectVersionId)
, _goResponseContentType :: !(Maybe Text)
, _goResponseContentDisposition :: !(Maybe Text)
, _goResponseContentLanguage :: !(Maybe Text)
, _goSSECustomerAlgorithm :: !(Maybe Text)
, _goSSECustomerKey :: !(Maybe (Sensitive Text))
, _goRequestPayer :: !(Maybe RequestPayer)
, _goResponseContentEncoding :: !(Maybe Text)
, _goIfModifiedSince :: !(Maybe RFC822)
, _goPartNumber :: !(Maybe Int)
, _goRange :: !(Maybe Text)
, _goIfUnmodifiedSince :: !(Maybe RFC822)
, _goSSECustomerKeyMD5 :: !(Maybe Text)
, _goResponseCacheControl :: !(Maybe Text)
, _goResponseExpires :: !(Maybe RFC822)
, _goIfNoneMatch :: !(Maybe Text)
, _goBucket :: !BucketName
, _goKey :: !ObjectKey
} deriving (Eq, Show, Data, Typeable, Generic)
getObject
:: BucketName
-> ObjectKey
-> GetObject
getObject pBucket_ pKey_ =
GetObject'
{ _goIfMatch = Nothing
, _goVersionId = Nothing
, _goResponseContentType = Nothing
, _goResponseContentDisposition = Nothing
, _goResponseContentLanguage = Nothing
, _goSSECustomerAlgorithm = Nothing
, _goSSECustomerKey = Nothing
, _goRequestPayer = Nothing
, _goResponseContentEncoding = Nothing
, _goIfModifiedSince = Nothing
, _goPartNumber = Nothing
, _goRange = Nothing
, _goIfUnmodifiedSince = Nothing
, _goSSECustomerKeyMD5 = Nothing
, _goResponseCacheControl = Nothing
, _goResponseExpires = Nothing
, _goIfNoneMatch = Nothing
, _goBucket = pBucket_
, _goKey = pKey_
}
goIfMatch :: Lens' GetObject (Maybe Text)
goIfMatch = lens _goIfMatch (\ s a -> s{_goIfMatch = a})
goVersionId :: Lens' GetObject (Maybe ObjectVersionId)
goVersionId = lens _goVersionId (\ s a -> s{_goVersionId = a})
goResponseContentType :: Lens' GetObject (Maybe Text)
goResponseContentType = lens _goResponseContentType (\ s a -> s{_goResponseContentType = a})
goResponseContentDisposition :: Lens' GetObject (Maybe Text)
goResponseContentDisposition = lens _goResponseContentDisposition (\ s a -> s{_goResponseContentDisposition = a})
goResponseContentLanguage :: Lens' GetObject (Maybe Text)
goResponseContentLanguage = lens _goResponseContentLanguage (\ s a -> s{_goResponseContentLanguage = a})
goSSECustomerAlgorithm :: Lens' GetObject (Maybe Text)
goSSECustomerAlgorithm = lens _goSSECustomerAlgorithm (\ s a -> s{_goSSECustomerAlgorithm = a})
goSSECustomerKey :: Lens' GetObject (Maybe Text)
goSSECustomerKey = lens _goSSECustomerKey (\ s a -> s{_goSSECustomerKey = a}) . mapping _Sensitive
goRequestPayer :: Lens' GetObject (Maybe RequestPayer)
goRequestPayer = lens _goRequestPayer (\ s a -> s{_goRequestPayer = a})
goResponseContentEncoding :: Lens' GetObject (Maybe Text)
goResponseContentEncoding = lens _goResponseContentEncoding (\ s a -> s{_goResponseContentEncoding = a})
goIfModifiedSince :: Lens' GetObject (Maybe UTCTime)
goIfModifiedSince = lens _goIfModifiedSince (\ s a -> s{_goIfModifiedSince = a}) . mapping _Time
goPartNumber :: Lens' GetObject (Maybe Int)
goPartNumber = lens _goPartNumber (\ s a -> s{_goPartNumber = a})
goRange :: Lens' GetObject (Maybe Text)
goRange = lens _goRange (\ s a -> s{_goRange = a})
goIfUnmodifiedSince :: Lens' GetObject (Maybe UTCTime)
goIfUnmodifiedSince = lens _goIfUnmodifiedSince (\ s a -> s{_goIfUnmodifiedSince = a}) . mapping _Time
goSSECustomerKeyMD5 :: Lens' GetObject (Maybe Text)
goSSECustomerKeyMD5 = lens _goSSECustomerKeyMD5 (\ s a -> s{_goSSECustomerKeyMD5 = a})
goResponseCacheControl :: Lens' GetObject (Maybe Text)
goResponseCacheControl = lens _goResponseCacheControl (\ s a -> s{_goResponseCacheControl = a})
goResponseExpires :: Lens' GetObject (Maybe UTCTime)
goResponseExpires = lens _goResponseExpires (\ s a -> s{_goResponseExpires = a}) . mapping _Time
goIfNoneMatch :: Lens' GetObject (Maybe Text)
goIfNoneMatch = lens _goIfNoneMatch (\ s a -> s{_goIfNoneMatch = a})
goBucket :: Lens' GetObject BucketName
goBucket = lens _goBucket (\ s a -> s{_goBucket = a})
goKey :: Lens' GetObject ObjectKey
goKey = lens _goKey (\ s a -> s{_goKey = a})
instance AWSRequest GetObject where
type Rs GetObject = GetObjectResponse
request = get s3
response
= receiveBody
(\ s h x ->
GetObjectResponse' <$>
(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-tagging-count")
<*> (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 .#? "Content-Range")
<*> (h .#? "x-amz-server-side-encryption")
<*> (h .#? "Content-Type")
<*> (pure (fromEnum s))
<*> (pure x))
instance Hashable GetObject where
instance NFData GetObject where
instance ToHeaders GetObject where
toHeaders GetObject'{..}
= mconcat
["If-Match" =# _goIfMatch,
"x-amz-server-side-encryption-customer-algorithm" =#
_goSSECustomerAlgorithm,
"x-amz-server-side-encryption-customer-key" =#
_goSSECustomerKey,
"x-amz-request-payer" =# _goRequestPayer,
"If-Modified-Since" =# _goIfModifiedSince,
"Range" =# _goRange,
"If-Unmodified-Since" =# _goIfUnmodifiedSince,
"x-amz-server-side-encryption-customer-key-MD5" =#
_goSSECustomerKeyMD5,
"If-None-Match" =# _goIfNoneMatch]
instance ToPath GetObject where
toPath GetObject'{..}
= mconcat ["/", toBS _goBucket, "/", toBS _goKey]
instance ToQuery GetObject where
toQuery GetObject'{..}
= mconcat
["versionId" =: _goVersionId,
"response-content-type" =: _goResponseContentType,
"response-content-disposition" =:
_goResponseContentDisposition,
"response-content-language" =:
_goResponseContentLanguage,
"response-content-encoding" =:
_goResponseContentEncoding,
"partNumber" =: _goPartNumber,
"response-cache-control" =: _goResponseCacheControl,
"response-expires" =: _goResponseExpires]
data GetObjectResponse = GetObjectResponse'
{ _gorsRequestCharged :: !(Maybe RequestCharged)
, _gorsPartsCount :: !(Maybe Int)
, _gorsETag :: !(Maybe ETag)
, _gorsVersionId :: !(Maybe ObjectVersionId)
, _gorsContentLength :: !(Maybe Integer)
, _gorsExpires :: !(Maybe RFC822)
, _gorsRestore :: !(Maybe Text)
, _gorsExpiration :: !(Maybe Text)
, _gorsDeleteMarker :: !(Maybe Bool)
, _gorsSSECustomerAlgorithm :: !(Maybe Text)
, _gorsTagCount :: !(Maybe Int)
, _gorsMissingMeta :: !(Maybe Int)
, _gorsWebsiteRedirectLocation :: !(Maybe Text)
, _gorsAcceptRanges :: !(Maybe Text)
, _gorsStorageClass :: !(Maybe StorageClass)
, _gorsSSECustomerKeyMD5 :: !(Maybe Text)
, _gorsSSEKMSKeyId :: !(Maybe (Sensitive Text))
, _gorsContentEncoding :: !(Maybe Text)
, _gorsMetadata :: !(Map Text Text)
, _gorsReplicationStatus :: !(Maybe ReplicationStatus)
, _gorsCacheControl :: !(Maybe Text)
, _gorsContentLanguage :: !(Maybe Text)
, _gorsLastModified :: !(Maybe RFC822)
, _gorsContentDisposition :: !(Maybe Text)
, _gorsContentRange :: !(Maybe Text)
, _gorsServerSideEncryption :: !(Maybe ServerSideEncryption)
, _gorsContentType :: !(Maybe Text)
, _gorsResponseStatus :: !Int
, _gorsBody :: !RsBody
} deriving (Show, Generic)
getObjectResponse
:: Int
-> RsBody
-> GetObjectResponse
getObjectResponse pResponseStatus_ pBody_ =
GetObjectResponse'
{ _gorsRequestCharged = Nothing
, _gorsPartsCount = Nothing
, _gorsETag = Nothing
, _gorsVersionId = Nothing
, _gorsContentLength = Nothing
, _gorsExpires = Nothing
, _gorsRestore = Nothing
, _gorsExpiration = Nothing
, _gorsDeleteMarker = Nothing
, _gorsSSECustomerAlgorithm = Nothing
, _gorsTagCount = Nothing
, _gorsMissingMeta = Nothing
, _gorsWebsiteRedirectLocation = Nothing
, _gorsAcceptRanges = Nothing
, _gorsStorageClass = Nothing
, _gorsSSECustomerKeyMD5 = Nothing
, _gorsSSEKMSKeyId = Nothing
, _gorsContentEncoding = Nothing
, _gorsMetadata = mempty
, _gorsReplicationStatus = Nothing
, _gorsCacheControl = Nothing
, _gorsContentLanguage = Nothing
, _gorsLastModified = Nothing
, _gorsContentDisposition = Nothing
, _gorsContentRange = Nothing
, _gorsServerSideEncryption = Nothing
, _gorsContentType = Nothing
, _gorsResponseStatus = pResponseStatus_
, _gorsBody = pBody_
}
gorsRequestCharged :: Lens' GetObjectResponse (Maybe RequestCharged)
gorsRequestCharged = lens _gorsRequestCharged (\ s a -> s{_gorsRequestCharged = a})
gorsPartsCount :: Lens' GetObjectResponse (Maybe Int)
gorsPartsCount = lens _gorsPartsCount (\ s a -> s{_gorsPartsCount = a})
gorsETag :: Lens' GetObjectResponse (Maybe ETag)
gorsETag = lens _gorsETag (\ s a -> s{_gorsETag = a})
gorsVersionId :: Lens' GetObjectResponse (Maybe ObjectVersionId)
gorsVersionId = lens _gorsVersionId (\ s a -> s{_gorsVersionId = a})
gorsContentLength :: Lens' GetObjectResponse (Maybe Integer)
gorsContentLength = lens _gorsContentLength (\ s a -> s{_gorsContentLength = a})
gorsExpires :: Lens' GetObjectResponse (Maybe UTCTime)
gorsExpires = lens _gorsExpires (\ s a -> s{_gorsExpires = a}) . mapping _Time
gorsRestore :: Lens' GetObjectResponse (Maybe Text)
gorsRestore = lens _gorsRestore (\ s a -> s{_gorsRestore = a})
gorsExpiration :: Lens' GetObjectResponse (Maybe Text)
gorsExpiration = lens _gorsExpiration (\ s a -> s{_gorsExpiration = a})
gorsDeleteMarker :: Lens' GetObjectResponse (Maybe Bool)
gorsDeleteMarker = lens _gorsDeleteMarker (\ s a -> s{_gorsDeleteMarker = a})
gorsSSECustomerAlgorithm :: Lens' GetObjectResponse (Maybe Text)
gorsSSECustomerAlgorithm = lens _gorsSSECustomerAlgorithm (\ s a -> s{_gorsSSECustomerAlgorithm = a})
gorsTagCount :: Lens' GetObjectResponse (Maybe Int)
gorsTagCount = lens _gorsTagCount (\ s a -> s{_gorsTagCount = a})
gorsMissingMeta :: Lens' GetObjectResponse (Maybe Int)
gorsMissingMeta = lens _gorsMissingMeta (\ s a -> s{_gorsMissingMeta = a})
gorsWebsiteRedirectLocation :: Lens' GetObjectResponse (Maybe Text)
gorsWebsiteRedirectLocation = lens _gorsWebsiteRedirectLocation (\ s a -> s{_gorsWebsiteRedirectLocation = a})
gorsAcceptRanges :: Lens' GetObjectResponse (Maybe Text)
gorsAcceptRanges = lens _gorsAcceptRanges (\ s a -> s{_gorsAcceptRanges = a})
gorsStorageClass :: Lens' GetObjectResponse (Maybe StorageClass)
gorsStorageClass = lens _gorsStorageClass (\ s a -> s{_gorsStorageClass = a})
gorsSSECustomerKeyMD5 :: Lens' GetObjectResponse (Maybe Text)
gorsSSECustomerKeyMD5 = lens _gorsSSECustomerKeyMD5 (\ s a -> s{_gorsSSECustomerKeyMD5 = a})
gorsSSEKMSKeyId :: Lens' GetObjectResponse (Maybe Text)
gorsSSEKMSKeyId = lens _gorsSSEKMSKeyId (\ s a -> s{_gorsSSEKMSKeyId = a}) . mapping _Sensitive
gorsContentEncoding :: Lens' GetObjectResponse (Maybe Text)
gorsContentEncoding = lens _gorsContentEncoding (\ s a -> s{_gorsContentEncoding = a})
gorsMetadata :: Lens' GetObjectResponse (HashMap Text Text)
gorsMetadata = lens _gorsMetadata (\ s a -> s{_gorsMetadata = a}) . _Map
gorsReplicationStatus :: Lens' GetObjectResponse (Maybe ReplicationStatus)
gorsReplicationStatus = lens _gorsReplicationStatus (\ s a -> s{_gorsReplicationStatus = a})
gorsCacheControl :: Lens' GetObjectResponse (Maybe Text)
gorsCacheControl = lens _gorsCacheControl (\ s a -> s{_gorsCacheControl = a})
gorsContentLanguage :: Lens' GetObjectResponse (Maybe Text)
gorsContentLanguage = lens _gorsContentLanguage (\ s a -> s{_gorsContentLanguage = a})
gorsLastModified :: Lens' GetObjectResponse (Maybe UTCTime)
gorsLastModified = lens _gorsLastModified (\ s a -> s{_gorsLastModified = a}) . mapping _Time
gorsContentDisposition :: Lens' GetObjectResponse (Maybe Text)
gorsContentDisposition = lens _gorsContentDisposition (\ s a -> s{_gorsContentDisposition = a})
gorsContentRange :: Lens' GetObjectResponse (Maybe Text)
gorsContentRange = lens _gorsContentRange (\ s a -> s{_gorsContentRange = a})
gorsServerSideEncryption :: Lens' GetObjectResponse (Maybe ServerSideEncryption)
gorsServerSideEncryption = lens _gorsServerSideEncryption (\ s a -> s{_gorsServerSideEncryption = a})
gorsContentType :: Lens' GetObjectResponse (Maybe Text)
gorsContentType = lens _gorsContentType (\ s a -> s{_gorsContentType = a})
gorsResponseStatus :: Lens' GetObjectResponse Int
gorsResponseStatus = lens _gorsResponseStatus (\ s a -> s{_gorsResponseStatus = a})
gorsBody :: Lens' GetObjectResponse RsBody
gorsBody = lens _gorsBody (\ s a -> s{_gorsBody = a})