{-# LANGUAGE DeriveGeneric #-}
{-# LANGUAGE DuplicateRecordFields #-}
{-# LANGUAGE NamedFieldPuns #-}
{-# LANGUAGE OverloadedStrings #-}
{-# LANGUAGE RecordWildCards #-}
{-# LANGUAGE StrictData #-}
{-# LANGUAGE TypeFamilies #-}
{-# LANGUAGE NoImplicitPrelude #-}
{-# OPTIONS_GHC -fno-warn-unused-binds #-}
{-# OPTIONS_GHC -fno-warn-unused-imports #-}
{-# OPTIONS_GHC -fno-warn-unused-matches #-}

-- Derived from AWS service descriptions, licensed under Apache 2.0.

-- |
-- Module      : Amazonka.S3.GetObjectTorrent
-- Copyright   : (c) 2013-2023 Brendan Hay
-- License     : Mozilla Public License, v. 2.0.
-- Maintainer  : Brendan Hay
-- Stability   : auto-generated
-- Portability : non-portable (GHC extensions)
--
-- Returns torrent files from a bucket. BitTorrent can save you bandwidth
-- when you\'re distributing large files. For more information about
-- BitTorrent, see
-- <https://docs.aws.amazon.com/AmazonS3/latest/dev/S3Torrent.html Using BitTorrent with Amazon S3>.
--
-- You can get torrent only for objects that are less than 5 GB in size,
-- and that are not encrypted using server-side encryption with a
-- customer-provided encryption key.
--
-- To use GET, you must have READ access to the object.
--
-- This action is not supported by Amazon S3 on Outposts.
--
-- The following action is related to @GetObjectTorrent@:
--
-- -   <https://docs.aws.amazon.com/AmazonS3/latest/API/API_GetObject.html GetObject>
module Amazonka.S3.GetObjectTorrent
  ( -- * Creating a Request
    GetObjectTorrent (..),
    newGetObjectTorrent,

    -- * Request Lenses
    getObjectTorrent_expectedBucketOwner,
    getObjectTorrent_requestPayer,
    getObjectTorrent_bucket,
    getObjectTorrent_key,

    -- * Destructuring the Response
    GetObjectTorrentResponse (..),
    newGetObjectTorrentResponse,

    -- * Response Lenses
    getObjectTorrentResponse_requestCharged,
    getObjectTorrentResponse_httpStatus,
    getObjectTorrentResponse_body,
  )
where

import qualified Amazonka.Core as Core
import qualified Amazonka.Core.Lens.Internal as Lens
import qualified Amazonka.Data as Data
import qualified Amazonka.Prelude as Prelude
import qualified Amazonka.Request as Request
import qualified Amazonka.Response as Response
import Amazonka.S3.Types

-- | /See:/ 'newGetObjectTorrent' smart constructor.
data GetObjectTorrent = GetObjectTorrent'
  { -- | The account ID of the expected bucket owner. If the bucket is owned by a
    -- different account, the request fails with the HTTP status code
    -- @403 Forbidden@ (access denied).
    GetObjectTorrent -> Maybe Text
expectedBucketOwner :: Prelude.Maybe Prelude.Text,
    GetObjectTorrent -> Maybe RequestPayer
requestPayer :: Prelude.Maybe RequestPayer,
    -- | The name of the bucket containing the object for which to get the
    -- torrent files.
    GetObjectTorrent -> BucketName
bucket :: BucketName,
    -- | The object key for which to get the information.
    GetObjectTorrent -> ObjectKey
key :: ObjectKey
  }
  deriving (GetObjectTorrent -> GetObjectTorrent -> Bool
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: GetObjectTorrent -> GetObjectTorrent -> Bool
$c/= :: GetObjectTorrent -> GetObjectTorrent -> Bool
== :: GetObjectTorrent -> GetObjectTorrent -> Bool
$c== :: GetObjectTorrent -> GetObjectTorrent -> Bool
Prelude.Eq, ReadPrec [GetObjectTorrent]
ReadPrec GetObjectTorrent
Int -> ReadS GetObjectTorrent
ReadS [GetObjectTorrent]
forall a.
(Int -> ReadS a)
-> ReadS [a] -> ReadPrec a -> ReadPrec [a] -> Read a
readListPrec :: ReadPrec [GetObjectTorrent]
$creadListPrec :: ReadPrec [GetObjectTorrent]
readPrec :: ReadPrec GetObjectTorrent
$creadPrec :: ReadPrec GetObjectTorrent
readList :: ReadS [GetObjectTorrent]
$creadList :: ReadS [GetObjectTorrent]
readsPrec :: Int -> ReadS GetObjectTorrent
$creadsPrec :: Int -> ReadS GetObjectTorrent
Prelude.Read, Int -> GetObjectTorrent -> ShowS
[GetObjectTorrent] -> ShowS
GetObjectTorrent -> String
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [GetObjectTorrent] -> ShowS
$cshowList :: [GetObjectTorrent] -> ShowS
show :: GetObjectTorrent -> String
$cshow :: GetObjectTorrent -> String
showsPrec :: Int -> GetObjectTorrent -> ShowS
$cshowsPrec :: Int -> GetObjectTorrent -> ShowS
Prelude.Show, forall x. Rep GetObjectTorrent x -> GetObjectTorrent
forall x. GetObjectTorrent -> Rep GetObjectTorrent x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cto :: forall x. Rep GetObjectTorrent x -> GetObjectTorrent
$cfrom :: forall x. GetObjectTorrent -> Rep GetObjectTorrent x
Prelude.Generic)

-- |
-- Create a value of 'GetObjectTorrent' with all optional fields omitted.
--
-- Use <https://hackage.haskell.org/package/generic-lens generic-lens> or <https://hackage.haskell.org/package/optics optics> to modify other optional fields.
--
-- The following record fields are available, with the corresponding lenses provided
-- for backwards compatibility:
--
-- 'expectedBucketOwner', 'getObjectTorrent_expectedBucketOwner' - The account ID of the expected bucket owner. If the bucket is owned by a
-- different account, the request fails with the HTTP status code
-- @403 Forbidden@ (access denied).
--
-- 'requestPayer', 'getObjectTorrent_requestPayer' - Undocumented member.
--
-- 'bucket', 'getObjectTorrent_bucket' - The name of the bucket containing the object for which to get the
-- torrent files.
--
-- 'key', 'getObjectTorrent_key' - The object key for which to get the information.
newGetObjectTorrent ::
  -- | 'bucket'
  BucketName ->
  -- | 'key'
  ObjectKey ->
  GetObjectTorrent
newGetObjectTorrent :: BucketName -> ObjectKey -> GetObjectTorrent
newGetObjectTorrent BucketName
pBucket_ ObjectKey
pKey_ =
  GetObjectTorrent'
    { $sel:expectedBucketOwner:GetObjectTorrent' :: Maybe Text
expectedBucketOwner =
        forall a. Maybe a
Prelude.Nothing,
      $sel:requestPayer:GetObjectTorrent' :: Maybe RequestPayer
requestPayer = forall a. Maybe a
Prelude.Nothing,
      $sel:bucket:GetObjectTorrent' :: BucketName
bucket = BucketName
pBucket_,
      $sel:key:GetObjectTorrent' :: ObjectKey
key = ObjectKey
pKey_
    }

-- | The account ID of the expected bucket owner. If the bucket is owned by a
-- different account, the request fails with the HTTP status code
-- @403 Forbidden@ (access denied).
getObjectTorrent_expectedBucketOwner :: Lens.Lens' GetObjectTorrent (Prelude.Maybe Prelude.Text)
getObjectTorrent_expectedBucketOwner :: Lens' GetObjectTorrent (Maybe Text)
getObjectTorrent_expectedBucketOwner = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\GetObjectTorrent' {Maybe Text
expectedBucketOwner :: Maybe Text
$sel:expectedBucketOwner:GetObjectTorrent' :: GetObjectTorrent -> Maybe Text
expectedBucketOwner} -> Maybe Text
expectedBucketOwner) (\s :: GetObjectTorrent
s@GetObjectTorrent' {} Maybe Text
a -> GetObjectTorrent
s {$sel:expectedBucketOwner:GetObjectTorrent' :: Maybe Text
expectedBucketOwner = Maybe Text
a} :: GetObjectTorrent)

-- | Undocumented member.
getObjectTorrent_requestPayer :: Lens.Lens' GetObjectTorrent (Prelude.Maybe RequestPayer)
getObjectTorrent_requestPayer :: Lens' GetObjectTorrent (Maybe RequestPayer)
getObjectTorrent_requestPayer = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\GetObjectTorrent' {Maybe RequestPayer
requestPayer :: Maybe RequestPayer
$sel:requestPayer:GetObjectTorrent' :: GetObjectTorrent -> Maybe RequestPayer
requestPayer} -> Maybe RequestPayer
requestPayer) (\s :: GetObjectTorrent
s@GetObjectTorrent' {} Maybe RequestPayer
a -> GetObjectTorrent
s {$sel:requestPayer:GetObjectTorrent' :: Maybe RequestPayer
requestPayer = Maybe RequestPayer
a} :: GetObjectTorrent)

-- | The name of the bucket containing the object for which to get the
-- torrent files.
getObjectTorrent_bucket :: Lens.Lens' GetObjectTorrent BucketName
getObjectTorrent_bucket :: Lens' GetObjectTorrent BucketName
getObjectTorrent_bucket = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\GetObjectTorrent' {BucketName
bucket :: BucketName
$sel:bucket:GetObjectTorrent' :: GetObjectTorrent -> BucketName
bucket} -> BucketName
bucket) (\s :: GetObjectTorrent
s@GetObjectTorrent' {} BucketName
a -> GetObjectTorrent
s {$sel:bucket:GetObjectTorrent' :: BucketName
bucket = BucketName
a} :: GetObjectTorrent)

-- | The object key for which to get the information.
getObjectTorrent_key :: Lens.Lens' GetObjectTorrent ObjectKey
getObjectTorrent_key :: Lens' GetObjectTorrent ObjectKey
getObjectTorrent_key = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\GetObjectTorrent' {ObjectKey
key :: ObjectKey
$sel:key:GetObjectTorrent' :: GetObjectTorrent -> ObjectKey
key} -> ObjectKey
key) (\s :: GetObjectTorrent
s@GetObjectTorrent' {} ObjectKey
a -> GetObjectTorrent
s {$sel:key:GetObjectTorrent' :: ObjectKey
key = ObjectKey
a} :: GetObjectTorrent)

instance Core.AWSRequest GetObjectTorrent where
  type
    AWSResponse GetObjectTorrent =
      GetObjectTorrentResponse
  request :: (Service -> Service)
-> GetObjectTorrent -> Request GetObjectTorrent
request Service -> Service
overrides =
    forall a. Request a -> Request a
Request.s3vhost
      forall b c a. (b -> c) -> (a -> b) -> a -> c
Prelude.. forall a. ToRequest a => Service -> a -> Request a
Request.get (Service -> Service
overrides Service
defaultService)
  response :: forall (m :: * -> *).
MonadResource m =>
(ByteStringLazy -> IO ByteStringLazy)
-> Service
-> Proxy GetObjectTorrent
-> ClientResponse ClientBody
-> m (Either Error (ClientResponse (AWSResponse GetObjectTorrent)))
response =
    forall (m :: * -> *) a.
MonadResource m =>
(Int
 -> ResponseHeaders
 -> ResponseBody
 -> Either String (AWSResponse a))
-> (ByteStringLazy -> IO ByteStringLazy)
-> Service
-> Proxy a
-> ClientResponse ClientBody
-> m (Either Error (ClientResponse (AWSResponse a)))
Response.receiveBody
      ( \Int
s ResponseHeaders
h ResponseBody
x ->
          Maybe RequestCharged
-> Int -> ResponseBody -> GetObjectTorrentResponse
GetObjectTorrentResponse'
            forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
Prelude.<$> (ResponseHeaders
h forall a.
FromText a =>
ResponseHeaders -> HeaderName -> Either String (Maybe a)
Data..#? HeaderName
"x-amz-request-charged")
            forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
Prelude.<*> (forall (f :: * -> *) a. Applicative f => a -> f a
Prelude.pure (forall a. Enum a => a -> Int
Prelude.fromEnum Int
s))
            forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
Prelude.<*> (forall (f :: * -> *) a. Applicative f => a -> f a
Prelude.pure ResponseBody
x)
      )

instance Prelude.Hashable GetObjectTorrent where
  hashWithSalt :: Int -> GetObjectTorrent -> Int
hashWithSalt Int
_salt GetObjectTorrent' {Maybe Text
Maybe RequestPayer
ObjectKey
BucketName
key :: ObjectKey
bucket :: BucketName
requestPayer :: Maybe RequestPayer
expectedBucketOwner :: Maybe Text
$sel:key:GetObjectTorrent' :: GetObjectTorrent -> ObjectKey
$sel:bucket:GetObjectTorrent' :: GetObjectTorrent -> BucketName
$sel:requestPayer:GetObjectTorrent' :: GetObjectTorrent -> Maybe RequestPayer
$sel:expectedBucketOwner:GetObjectTorrent' :: GetObjectTorrent -> Maybe Text
..} =
    Int
_salt
      forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Maybe Text
expectedBucketOwner
      forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Maybe RequestPayer
requestPayer
      forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` BucketName
bucket
      forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` ObjectKey
key

instance Prelude.NFData GetObjectTorrent where
  rnf :: GetObjectTorrent -> ()
rnf GetObjectTorrent' {Maybe Text
Maybe RequestPayer
ObjectKey
BucketName
key :: ObjectKey
bucket :: BucketName
requestPayer :: Maybe RequestPayer
expectedBucketOwner :: Maybe Text
$sel:key:GetObjectTorrent' :: GetObjectTorrent -> ObjectKey
$sel:bucket:GetObjectTorrent' :: GetObjectTorrent -> BucketName
$sel:requestPayer:GetObjectTorrent' :: GetObjectTorrent -> Maybe RequestPayer
$sel:expectedBucketOwner:GetObjectTorrent' :: GetObjectTorrent -> Maybe Text
..} =
    forall a. NFData a => a -> ()
Prelude.rnf Maybe Text
expectedBucketOwner
      seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf Maybe RequestPayer
requestPayer
      seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf BucketName
bucket
      seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf ObjectKey
key

instance Data.ToHeaders GetObjectTorrent where
  toHeaders :: GetObjectTorrent -> ResponseHeaders
toHeaders GetObjectTorrent' {Maybe Text
Maybe RequestPayer
ObjectKey
BucketName
key :: ObjectKey
bucket :: BucketName
requestPayer :: Maybe RequestPayer
expectedBucketOwner :: Maybe Text
$sel:key:GetObjectTorrent' :: GetObjectTorrent -> ObjectKey
$sel:bucket:GetObjectTorrent' :: GetObjectTorrent -> BucketName
$sel:requestPayer:GetObjectTorrent' :: GetObjectTorrent -> Maybe RequestPayer
$sel:expectedBucketOwner:GetObjectTorrent' :: GetObjectTorrent -> Maybe Text
..} =
    forall a. Monoid a => [a] -> a
Prelude.mconcat
      [ HeaderName
"x-amz-expected-bucket-owner"
          forall a. ToHeader a => HeaderName -> a -> ResponseHeaders
Data.=# Maybe Text
expectedBucketOwner,
        HeaderName
"x-amz-request-payer" forall a. ToHeader a => HeaderName -> a -> ResponseHeaders
Data.=# Maybe RequestPayer
requestPayer
      ]

instance Data.ToPath GetObjectTorrent where
  toPath :: GetObjectTorrent -> ByteString
toPath GetObjectTorrent' {Maybe Text
Maybe RequestPayer
ObjectKey
BucketName
key :: ObjectKey
bucket :: BucketName
requestPayer :: Maybe RequestPayer
expectedBucketOwner :: Maybe Text
$sel:key:GetObjectTorrent' :: GetObjectTorrent -> ObjectKey
$sel:bucket:GetObjectTorrent' :: GetObjectTorrent -> BucketName
$sel:requestPayer:GetObjectTorrent' :: GetObjectTorrent -> Maybe RequestPayer
$sel:expectedBucketOwner:GetObjectTorrent' :: GetObjectTorrent -> Maybe Text
..} =
    forall a. Monoid a => [a] -> a
Prelude.mconcat
      [ByteString
"/", forall a. ToByteString a => a -> ByteString
Data.toBS BucketName
bucket, ByteString
"/", forall a. ToByteString a => a -> ByteString
Data.toBS ObjectKey
key]

instance Data.ToQuery GetObjectTorrent where
  toQuery :: GetObjectTorrent -> QueryString
toQuery = forall a b. a -> b -> a
Prelude.const (forall a. Monoid a => [a] -> a
Prelude.mconcat [QueryString
"torrent"])

-- | /See:/ 'newGetObjectTorrentResponse' smart constructor.
data GetObjectTorrentResponse = GetObjectTorrentResponse'
  { GetObjectTorrentResponse -> Maybe RequestCharged
requestCharged :: Prelude.Maybe RequestCharged,
    -- | The response's http status code.
    GetObjectTorrentResponse -> Int
httpStatus :: Prelude.Int,
    -- | A Bencoded dictionary as defined by the BitTorrent specification
    GetObjectTorrentResponse -> ResponseBody
body :: Data.ResponseBody
  }
  deriving (Int -> GetObjectTorrentResponse -> ShowS
[GetObjectTorrentResponse] -> ShowS
GetObjectTorrentResponse -> String
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [GetObjectTorrentResponse] -> ShowS
$cshowList :: [GetObjectTorrentResponse] -> ShowS
show :: GetObjectTorrentResponse -> String
$cshow :: GetObjectTorrentResponse -> String
showsPrec :: Int -> GetObjectTorrentResponse -> ShowS
$cshowsPrec :: Int -> GetObjectTorrentResponse -> ShowS
Prelude.Show, forall x.
Rep GetObjectTorrentResponse x -> GetObjectTorrentResponse
forall x.
GetObjectTorrentResponse -> Rep GetObjectTorrentResponse x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cto :: forall x.
Rep GetObjectTorrentResponse x -> GetObjectTorrentResponse
$cfrom :: forall x.
GetObjectTorrentResponse -> Rep GetObjectTorrentResponse x
Prelude.Generic)

-- |
-- Create a value of 'GetObjectTorrentResponse' with all optional fields omitted.
--
-- Use <https://hackage.haskell.org/package/generic-lens generic-lens> or <https://hackage.haskell.org/package/optics optics> to modify other optional fields.
--
-- The following record fields are available, with the corresponding lenses provided
-- for backwards compatibility:
--
-- 'requestCharged', 'getObjectTorrentResponse_requestCharged' - Undocumented member.
--
-- 'httpStatus', 'getObjectTorrentResponse_httpStatus' - The response's http status code.
--
-- 'body', 'getObjectTorrentResponse_body' - A Bencoded dictionary as defined by the BitTorrent specification
newGetObjectTorrentResponse ::
  -- | 'httpStatus'
  Prelude.Int ->
  -- | 'body'
  Data.ResponseBody ->
  GetObjectTorrentResponse
newGetObjectTorrentResponse :: Int -> ResponseBody -> GetObjectTorrentResponse
newGetObjectTorrentResponse Int
pHttpStatus_ ResponseBody
pBody_ =
  GetObjectTorrentResponse'
    { $sel:requestCharged:GetObjectTorrentResponse' :: Maybe RequestCharged
requestCharged =
        forall a. Maybe a
Prelude.Nothing,
      $sel:httpStatus:GetObjectTorrentResponse' :: Int
httpStatus = Int
pHttpStatus_,
      $sel:body:GetObjectTorrentResponse' :: ResponseBody
body = ResponseBody
pBody_
    }

-- | Undocumented member.
getObjectTorrentResponse_requestCharged :: Lens.Lens' GetObjectTorrentResponse (Prelude.Maybe RequestCharged)
getObjectTorrentResponse_requestCharged :: Lens' GetObjectTorrentResponse (Maybe RequestCharged)
getObjectTorrentResponse_requestCharged = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\GetObjectTorrentResponse' {Maybe RequestCharged
requestCharged :: Maybe RequestCharged
$sel:requestCharged:GetObjectTorrentResponse' :: GetObjectTorrentResponse -> Maybe RequestCharged
requestCharged} -> Maybe RequestCharged
requestCharged) (\s :: GetObjectTorrentResponse
s@GetObjectTorrentResponse' {} Maybe RequestCharged
a -> GetObjectTorrentResponse
s {$sel:requestCharged:GetObjectTorrentResponse' :: Maybe RequestCharged
requestCharged = Maybe RequestCharged
a} :: GetObjectTorrentResponse)

-- | The response's http status code.
getObjectTorrentResponse_httpStatus :: Lens.Lens' GetObjectTorrentResponse Prelude.Int
getObjectTorrentResponse_httpStatus :: Lens' GetObjectTorrentResponse Int
getObjectTorrentResponse_httpStatus = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\GetObjectTorrentResponse' {Int
httpStatus :: Int
$sel:httpStatus:GetObjectTorrentResponse' :: GetObjectTorrentResponse -> Int
httpStatus} -> Int
httpStatus) (\s :: GetObjectTorrentResponse
s@GetObjectTorrentResponse' {} Int
a -> GetObjectTorrentResponse
s {$sel:httpStatus:GetObjectTorrentResponse' :: Int
httpStatus = Int
a} :: GetObjectTorrentResponse)

-- | A Bencoded dictionary as defined by the BitTorrent specification
getObjectTorrentResponse_body :: Lens.Lens' GetObjectTorrentResponse Data.ResponseBody
getObjectTorrentResponse_body :: Lens' GetObjectTorrentResponse ResponseBody
getObjectTorrentResponse_body = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\GetObjectTorrentResponse' {ResponseBody
body :: ResponseBody
$sel:body:GetObjectTorrentResponse' :: GetObjectTorrentResponse -> ResponseBody
body} -> ResponseBody
body) (\s :: GetObjectTorrentResponse
s@GetObjectTorrentResponse' {} ResponseBody
a -> GetObjectTorrentResponse
s {$sel:body:GetObjectTorrentResponse' :: ResponseBody
body = ResponseBody
a} :: GetObjectTorrentResponse)