{-# 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.SelectObjectContent
(
selectObjectContent
, SelectObjectContent
, socSSECustomerAlgorithm
, socSSECustomerKey
, socRequestProgress
, socSSECustomerKeyMD5
, socBucket
, socKey
, socExpression
, socExpressionType
, socInputSerialization
, socOutputSerialization
, selectObjectContentResponse
, SelectObjectContentResponse
, socrsPayload
, socrsResponseStatus
) 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 SelectObjectContent = SelectObjectContent'
{ _socSSECustomerAlgorithm :: !(Maybe Text)
, _socSSECustomerKey :: !(Maybe (Sensitive Text))
, _socRequestProgress :: !(Maybe RequestProgress)
, _socSSECustomerKeyMD5 :: !(Maybe Text)
, _socBucket :: !BucketName
, _socKey :: !ObjectKey
, _socExpression :: !Text
, _socExpressionType :: !ExpressionType
, _socInputSerialization :: !InputSerialization
, _socOutputSerialization :: !OutputSerialization
} deriving (Eq, Show, Data, Typeable, Generic)
selectObjectContent
:: BucketName
-> ObjectKey
-> Text
-> ExpressionType
-> InputSerialization
-> OutputSerialization
-> SelectObjectContent
selectObjectContent pBucket_ pKey_ pExpression_ pExpressionType_ pInputSerialization_ pOutputSerialization_ =
SelectObjectContent'
{ _socSSECustomerAlgorithm = Nothing
, _socSSECustomerKey = Nothing
, _socRequestProgress = Nothing
, _socSSECustomerKeyMD5 = Nothing
, _socBucket = pBucket_
, _socKey = pKey_
, _socExpression = pExpression_
, _socExpressionType = pExpressionType_
, _socInputSerialization = pInputSerialization_
, _socOutputSerialization = pOutputSerialization_
}
socSSECustomerAlgorithm :: Lens' SelectObjectContent (Maybe Text)
socSSECustomerAlgorithm = lens _socSSECustomerAlgorithm (\ s a -> s{_socSSECustomerAlgorithm = a})
socSSECustomerKey :: Lens' SelectObjectContent (Maybe Text)
socSSECustomerKey = lens _socSSECustomerKey (\ s a -> s{_socSSECustomerKey = a}) . mapping _Sensitive
socRequestProgress :: Lens' SelectObjectContent (Maybe RequestProgress)
socRequestProgress = lens _socRequestProgress (\ s a -> s{_socRequestProgress = a})
socSSECustomerKeyMD5 :: Lens' SelectObjectContent (Maybe Text)
socSSECustomerKeyMD5 = lens _socSSECustomerKeyMD5 (\ s a -> s{_socSSECustomerKeyMD5 = a})
socBucket :: Lens' SelectObjectContent BucketName
socBucket = lens _socBucket (\ s a -> s{_socBucket = a})
socKey :: Lens' SelectObjectContent ObjectKey
socKey = lens _socKey (\ s a -> s{_socKey = a})
socExpression :: Lens' SelectObjectContent Text
socExpression = lens _socExpression (\ s a -> s{_socExpression = a})
socExpressionType :: Lens' SelectObjectContent ExpressionType
socExpressionType = lens _socExpressionType (\ s a -> s{_socExpressionType = a})
socInputSerialization :: Lens' SelectObjectContent InputSerialization
socInputSerialization = lens _socInputSerialization (\ s a -> s{_socInputSerialization = a})
socOutputSerialization :: Lens' SelectObjectContent OutputSerialization
socOutputSerialization = lens _socOutputSerialization (\ s a -> s{_socOutputSerialization = a})
instance AWSRequest SelectObjectContent where
type Rs SelectObjectContent =
SelectObjectContentResponse
request = postXML s3
response
= receiveXML
(\ s h x ->
SelectObjectContentResponse' <$>
(parseXML x) <*> (pure (fromEnum s)))
instance Hashable SelectObjectContent where
instance NFData SelectObjectContent where
instance ToElement SelectObjectContent where
toElement
= mkElement
"{http://s3.amazonaws.com/doc/2006-03-01/}SelectObjectContentRequest"
instance ToHeaders SelectObjectContent where
toHeaders SelectObjectContent'{..}
= mconcat
["x-amz-server-side-encryption-customer-algorithm" =#
_socSSECustomerAlgorithm,
"x-amz-server-side-encryption-customer-key" =#
_socSSECustomerKey,
"x-amz-server-side-encryption-customer-key-MD5" =#
_socSSECustomerKeyMD5]
instance ToPath SelectObjectContent where
toPath SelectObjectContent'{..}
= mconcat ["/", toBS _socBucket, "/", toBS _socKey]
instance ToQuery SelectObjectContent where
toQuery = const (mconcat ["select&select-type=2"])
instance ToXML SelectObjectContent where
toXML SelectObjectContent'{..}
= mconcat
["RequestProgress" @= _socRequestProgress,
"Expression" @= _socExpression,
"ExpressionType" @= _socExpressionType,
"InputSerialization" @= _socInputSerialization,
"OutputSerialization" @= _socOutputSerialization]
data SelectObjectContentResponse = SelectObjectContentResponse'
{ _socrsPayload :: !(Maybe SelectObjectContentEventStream)
, _socrsResponseStatus :: !Int
} deriving (Eq, Read, Show, Data, Typeable, Generic)
selectObjectContentResponse
:: Int
-> SelectObjectContentResponse
selectObjectContentResponse pResponseStatus_ =
SelectObjectContentResponse'
{_socrsPayload = Nothing, _socrsResponseStatus = pResponseStatus_}
socrsPayload :: Lens' SelectObjectContentResponse (Maybe SelectObjectContentEventStream)
socrsPayload = lens _socrsPayload (\ s a -> s{_socrsPayload = a})
socrsResponseStatus :: Lens' SelectObjectContentResponse Int
socrsResponseStatus = lens _socrsResponseStatus (\ s a -> s{_socrsResponseStatus = a})
instance NFData SelectObjectContentResponse where