{-# 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.GetObjectTorrent
(
getObjectTorrent
, GetObjectTorrent
, gotRequestPayer
, gotBucket
, gotKey
, getObjectTorrentResponse
, GetObjectTorrentResponse
, getrsRequestCharged
, getrsResponseStatus
, getrsBody
) 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 GetObjectTorrent = GetObjectTorrent'
{ _gotRequestPayer :: !(Maybe RequestPayer)
, _gotBucket :: !BucketName
, _gotKey :: !ObjectKey
} deriving (Eq, Read, Show, Data, Typeable, Generic)
getObjectTorrent
:: BucketName
-> ObjectKey
-> GetObjectTorrent
getObjectTorrent pBucket_ pKey_ =
GetObjectTorrent'
{_gotRequestPayer = Nothing, _gotBucket = pBucket_, _gotKey = pKey_}
gotRequestPayer :: Lens' GetObjectTorrent (Maybe RequestPayer)
gotRequestPayer = lens _gotRequestPayer (\ s a -> s{_gotRequestPayer = a})
gotBucket :: Lens' GetObjectTorrent BucketName
gotBucket = lens _gotBucket (\ s a -> s{_gotBucket = a})
gotKey :: Lens' GetObjectTorrent ObjectKey
gotKey = lens _gotKey (\ s a -> s{_gotKey = a})
instance AWSRequest GetObjectTorrent where
type Rs GetObjectTorrent = GetObjectTorrentResponse
request = get s3
response
= receiveBody
(\ s h x ->
GetObjectTorrentResponse' <$>
(h .#? "x-amz-request-charged") <*>
(pure (fromEnum s))
<*> (pure x))
instance Hashable GetObjectTorrent where
instance NFData GetObjectTorrent where
instance ToHeaders GetObjectTorrent where
toHeaders GetObjectTorrent'{..}
= mconcat ["x-amz-request-payer" =# _gotRequestPayer]
instance ToPath GetObjectTorrent where
toPath GetObjectTorrent'{..}
= mconcat ["/", toBS _gotBucket, "/", toBS _gotKey]
instance ToQuery GetObjectTorrent where
toQuery = const (mconcat ["torrent"])
data GetObjectTorrentResponse = GetObjectTorrentResponse'
{ _getrsRequestCharged :: !(Maybe RequestCharged)
, _getrsResponseStatus :: !Int
, _getrsBody :: !RsBody
} deriving (Show, Generic)
getObjectTorrentResponse
:: Int
-> RsBody
-> GetObjectTorrentResponse
getObjectTorrentResponse pResponseStatus_ pBody_ =
GetObjectTorrentResponse'
{ _getrsRequestCharged = Nothing
, _getrsResponseStatus = pResponseStatus_
, _getrsBody = pBody_
}
getrsRequestCharged :: Lens' GetObjectTorrentResponse (Maybe RequestCharged)
getrsRequestCharged = lens _getrsRequestCharged (\ s a -> s{_getrsRequestCharged = a})
getrsResponseStatus :: Lens' GetObjectTorrentResponse Int
getrsResponseStatus = lens _getrsResponseStatus (\ s a -> s{_getrsResponseStatus = a})
getrsBody :: Lens' GetObjectTorrentResponse RsBody
getrsBody = lens _getrsBody (\ s a -> s{_getrsBody = a})