module Network.AWS.S3.GetObjectTorrent
    (
    
      GetObjectTorrent
    
    , getObjectTorrent
    
    , gotBucket
    , gotKey
    
    , GetObjectTorrentResponse
    
    , getObjectTorrentResponse
    
    , gotrBody
    ) where
import Network.AWS.Prelude
import Network.AWS.Request.S3
import Network.AWS.S3.Types
import qualified GHC.Exts
data GetObjectTorrent = GetObjectTorrent
    { _gotBucket :: Text
    , _gotKey    :: Text
    } deriving (Eq, Ord, Show)
getObjectTorrent :: Text 
                 -> Text 
                 -> GetObjectTorrent
getObjectTorrent p1 p2 = GetObjectTorrent
    { _gotBucket = p1
    , _gotKey    = p2
    }
gotBucket :: Lens' GetObjectTorrent Text
gotBucket = lens _gotBucket (\s a -> s { _gotBucket = a })
gotKey :: Lens' GetObjectTorrent Text
gotKey = lens _gotKey (\s a -> s { _gotKey = a })
newtype GetObjectTorrentResponse = GetObjectTorrentResponse
    { _gotrBody :: RsBody
    } deriving (Show)
getObjectTorrentResponse :: RsBody 
                         -> GetObjectTorrentResponse
getObjectTorrentResponse p1 = GetObjectTorrentResponse
    { _gotrBody = p1
    }
gotrBody :: Lens' GetObjectTorrentResponse RsBody
gotrBody = lens _gotrBody (\s a -> s { _gotrBody = a })
instance ToPath GetObjectTorrent where
    toPath GetObjectTorrent{..} = mconcat
        [ "/"
        , toText _gotBucket
        , "/"
        , toText _gotKey
        ]
instance ToQuery GetObjectTorrent where
    toQuery = const "torrent"
instance ToHeaders GetObjectTorrent
instance ToXMLRoot GetObjectTorrent where
    toXMLRoot = const (namespaced ns "GetObjectTorrent" [])
instance ToXML GetObjectTorrent
instance AWSRequest GetObjectTorrent where
    type Sv GetObjectTorrent = S3
    type Rs GetObjectTorrent = GetObjectTorrentResponse
    request  = get
    response = bodyResponse . const $ \b -> GetObjectTorrentResponse
        <$> pure (RsBody b)