{-# 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.Glacier.ListMultipartUploads
-- Copyright   : (c) 2013-2023 Brendan Hay
-- License     : Mozilla Public License, v. 2.0.
-- Maintainer  : Brendan Hay
-- Stability   : auto-generated
-- Portability : non-portable (GHC extensions)
--
-- This operation lists in-progress multipart uploads for the specified
-- vault. An in-progress multipart upload is a multipart upload that has
-- been initiated by an InitiateMultipartUpload request, but has not yet
-- been completed or aborted. The list returned in the List Multipart
-- Upload response has no guaranteed order.
--
-- The List Multipart Uploads operation supports pagination. By default,
-- this operation returns up to 50 multipart uploads in the response. You
-- should always check the response for a @marker@ at which to continue the
-- list; if there are no more items the @marker@ is @null@. To return a
-- list of multipart uploads that begins at a specific upload, set the
-- @marker@ request parameter to the value you obtained from a previous
-- List Multipart Upload request. You can also limit the number of uploads
-- returned in the response by specifying the @limit@ parameter in the
-- request.
--
-- Note the difference between this operation and listing parts
-- (ListParts). The List Multipart Uploads operation lists all multipart
-- uploads for a vault and does not require a multipart upload ID. The List
-- Parts operation requires a multipart upload ID since parts are
-- associated with a single upload.
--
-- An AWS account has full permission to perform all operations (actions).
-- However, AWS Identity and Access Management (IAM) users don\'t have any
-- permissions by default. You must grant them explicit permission to
-- perform specific actions. For more information, see
-- <https://docs.aws.amazon.com/amazonglacier/latest/dev/using-iam-with-amazon-glacier.html Access Control Using AWS Identity and Access Management (IAM)>.
--
-- For conceptual information and the underlying REST API, see
-- <https://docs.aws.amazon.com/amazonglacier/latest/dev/working-with-archives.html Working with Archives in Amazon S3 Glacier>
-- and
-- <https://docs.aws.amazon.com/amazonglacier/latest/dev/api-multipart-list-uploads.html List Multipart Uploads>
-- in the /Amazon Glacier Developer Guide/.
--
-- This operation returns paginated results.
module Amazonka.Glacier.ListMultipartUploads
  ( -- * Creating a Request
    ListMultipartUploads (..),
    newListMultipartUploads,

    -- * Request Lenses
    listMultipartUploads_limit,
    listMultipartUploads_marker,
    listMultipartUploads_accountId,
    listMultipartUploads_vaultName,

    -- * Destructuring the Response
    ListMultipartUploadsResponse (..),
    newListMultipartUploadsResponse,

    -- * Response Lenses
    listMultipartUploadsResponse_marker,
    listMultipartUploadsResponse_uploadsList,
    listMultipartUploadsResponse_httpStatus,
  )
where

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

-- | Provides options for retrieving list of in-progress multipart uploads
-- for an Amazon Glacier vault.
--
-- /See:/ 'newListMultipartUploads' smart constructor.
data ListMultipartUploads = ListMultipartUploads'
  { -- | Specifies the maximum number of uploads returned in the response body.
    -- If this value is not specified, the List Uploads operation returns up to
    -- 50 uploads.
    ListMultipartUploads -> Maybe Text
limit :: Prelude.Maybe Prelude.Text,
    -- | An opaque string used for pagination. This value specifies the upload at
    -- which the listing of uploads should begin. Get the marker value from a
    -- previous List Uploads response. You need only include the marker if you
    -- are continuing the pagination of results started in a previous List
    -- Uploads request.
    ListMultipartUploads -> Maybe Text
marker :: Prelude.Maybe Prelude.Text,
    -- | The @AccountId@ value is the AWS account ID of the account that owns the
    -- vault. You can either specify an AWS account ID or optionally a single
    -- \'@-@\' (hyphen), in which case Amazon S3 Glacier uses the AWS account
    -- ID associated with the credentials used to sign the request. If you use
    -- an account ID, do not include any hyphens (\'-\') in the ID.
    ListMultipartUploads -> Text
accountId :: Prelude.Text,
    -- | The name of the vault.
    ListMultipartUploads -> Text
vaultName :: Prelude.Text
  }
  deriving (ListMultipartUploads -> ListMultipartUploads -> Bool
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: ListMultipartUploads -> ListMultipartUploads -> Bool
$c/= :: ListMultipartUploads -> ListMultipartUploads -> Bool
== :: ListMultipartUploads -> ListMultipartUploads -> Bool
$c== :: ListMultipartUploads -> ListMultipartUploads -> Bool
Prelude.Eq, ReadPrec [ListMultipartUploads]
ReadPrec ListMultipartUploads
Int -> ReadS ListMultipartUploads
ReadS [ListMultipartUploads]
forall a.
(Int -> ReadS a)
-> ReadS [a] -> ReadPrec a -> ReadPrec [a] -> Read a
readListPrec :: ReadPrec [ListMultipartUploads]
$creadListPrec :: ReadPrec [ListMultipartUploads]
readPrec :: ReadPrec ListMultipartUploads
$creadPrec :: ReadPrec ListMultipartUploads
readList :: ReadS [ListMultipartUploads]
$creadList :: ReadS [ListMultipartUploads]
readsPrec :: Int -> ReadS ListMultipartUploads
$creadsPrec :: Int -> ReadS ListMultipartUploads
Prelude.Read, Int -> ListMultipartUploads -> ShowS
[ListMultipartUploads] -> ShowS
ListMultipartUploads -> String
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [ListMultipartUploads] -> ShowS
$cshowList :: [ListMultipartUploads] -> ShowS
show :: ListMultipartUploads -> String
$cshow :: ListMultipartUploads -> String
showsPrec :: Int -> ListMultipartUploads -> ShowS
$cshowsPrec :: Int -> ListMultipartUploads -> ShowS
Prelude.Show, forall x. Rep ListMultipartUploads x -> ListMultipartUploads
forall x. ListMultipartUploads -> Rep ListMultipartUploads x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cto :: forall x. Rep ListMultipartUploads x -> ListMultipartUploads
$cfrom :: forall x. ListMultipartUploads -> Rep ListMultipartUploads x
Prelude.Generic)

-- |
-- Create a value of 'ListMultipartUploads' 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:
--
-- 'limit', 'listMultipartUploads_limit' - Specifies the maximum number of uploads returned in the response body.
-- If this value is not specified, the List Uploads operation returns up to
-- 50 uploads.
--
-- 'marker', 'listMultipartUploads_marker' - An opaque string used for pagination. This value specifies the upload at
-- which the listing of uploads should begin. Get the marker value from a
-- previous List Uploads response. You need only include the marker if you
-- are continuing the pagination of results started in a previous List
-- Uploads request.
--
-- 'accountId', 'listMultipartUploads_accountId' - The @AccountId@ value is the AWS account ID of the account that owns the
-- vault. You can either specify an AWS account ID or optionally a single
-- \'@-@\' (hyphen), in which case Amazon S3 Glacier uses the AWS account
-- ID associated with the credentials used to sign the request. If you use
-- an account ID, do not include any hyphens (\'-\') in the ID.
--
-- 'vaultName', 'listMultipartUploads_vaultName' - The name of the vault.
newListMultipartUploads ::
  -- | 'accountId'
  Prelude.Text ->
  -- | 'vaultName'
  Prelude.Text ->
  ListMultipartUploads
newListMultipartUploads :: Text -> Text -> ListMultipartUploads
newListMultipartUploads Text
pAccountId_ Text
pVaultName_ =
  ListMultipartUploads'
    { $sel:limit:ListMultipartUploads' :: Maybe Text
limit = forall a. Maybe a
Prelude.Nothing,
      $sel:marker:ListMultipartUploads' :: Maybe Text
marker = forall a. Maybe a
Prelude.Nothing,
      $sel:accountId:ListMultipartUploads' :: Text
accountId = Text
pAccountId_,
      $sel:vaultName:ListMultipartUploads' :: Text
vaultName = Text
pVaultName_
    }

-- | Specifies the maximum number of uploads returned in the response body.
-- If this value is not specified, the List Uploads operation returns up to
-- 50 uploads.
listMultipartUploads_limit :: Lens.Lens' ListMultipartUploads (Prelude.Maybe Prelude.Text)
listMultipartUploads_limit :: Lens' ListMultipartUploads (Maybe Text)
listMultipartUploads_limit = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\ListMultipartUploads' {Maybe Text
limit :: Maybe Text
$sel:limit:ListMultipartUploads' :: ListMultipartUploads -> Maybe Text
limit} -> Maybe Text
limit) (\s :: ListMultipartUploads
s@ListMultipartUploads' {} Maybe Text
a -> ListMultipartUploads
s {$sel:limit:ListMultipartUploads' :: Maybe Text
limit = Maybe Text
a} :: ListMultipartUploads)

-- | An opaque string used for pagination. This value specifies the upload at
-- which the listing of uploads should begin. Get the marker value from a
-- previous List Uploads response. You need only include the marker if you
-- are continuing the pagination of results started in a previous List
-- Uploads request.
listMultipartUploads_marker :: Lens.Lens' ListMultipartUploads (Prelude.Maybe Prelude.Text)
listMultipartUploads_marker :: Lens' ListMultipartUploads (Maybe Text)
listMultipartUploads_marker = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\ListMultipartUploads' {Maybe Text
marker :: Maybe Text
$sel:marker:ListMultipartUploads' :: ListMultipartUploads -> Maybe Text
marker} -> Maybe Text
marker) (\s :: ListMultipartUploads
s@ListMultipartUploads' {} Maybe Text
a -> ListMultipartUploads
s {$sel:marker:ListMultipartUploads' :: Maybe Text
marker = Maybe Text
a} :: ListMultipartUploads)

-- | The @AccountId@ value is the AWS account ID of the account that owns the
-- vault. You can either specify an AWS account ID or optionally a single
-- \'@-@\' (hyphen), in which case Amazon S3 Glacier uses the AWS account
-- ID associated with the credentials used to sign the request. If you use
-- an account ID, do not include any hyphens (\'-\') in the ID.
listMultipartUploads_accountId :: Lens.Lens' ListMultipartUploads Prelude.Text
listMultipartUploads_accountId :: Lens' ListMultipartUploads Text
listMultipartUploads_accountId = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\ListMultipartUploads' {Text
accountId :: Text
$sel:accountId:ListMultipartUploads' :: ListMultipartUploads -> Text
accountId} -> Text
accountId) (\s :: ListMultipartUploads
s@ListMultipartUploads' {} Text
a -> ListMultipartUploads
s {$sel:accountId:ListMultipartUploads' :: Text
accountId = Text
a} :: ListMultipartUploads)

-- | The name of the vault.
listMultipartUploads_vaultName :: Lens.Lens' ListMultipartUploads Prelude.Text
listMultipartUploads_vaultName :: Lens' ListMultipartUploads Text
listMultipartUploads_vaultName = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\ListMultipartUploads' {Text
vaultName :: Text
$sel:vaultName:ListMultipartUploads' :: ListMultipartUploads -> Text
vaultName} -> Text
vaultName) (\s :: ListMultipartUploads
s@ListMultipartUploads' {} Text
a -> ListMultipartUploads
s {$sel:vaultName:ListMultipartUploads' :: Text
vaultName = Text
a} :: ListMultipartUploads)

instance Core.AWSPager ListMultipartUploads where
  page :: ListMultipartUploads
-> AWSResponse ListMultipartUploads -> Maybe ListMultipartUploads
page ListMultipartUploads
rq AWSResponse ListMultipartUploads
rs
    | forall a. AWSTruncated a => a -> Bool
Core.stop
        ( AWSResponse ListMultipartUploads
rs
            forall s a. s -> Getting (First a) s a -> Maybe a
Lens.^? Lens' ListMultipartUploadsResponse (Maybe Text)
listMultipartUploadsResponse_marker
            forall b c a. (b -> c) -> (a -> b) -> a -> c
Prelude.. forall a b. Prism (Maybe a) (Maybe b) a b
Lens._Just
        ) =
        forall a. Maybe a
Prelude.Nothing
    | forall a. AWSTruncated a => a -> Bool
Core.stop
        ( AWSResponse ListMultipartUploads
rs
            forall s a. s -> Getting (First a) s a -> Maybe a
Lens.^? Lens' ListMultipartUploadsResponse (Maybe [UploadListElement])
listMultipartUploadsResponse_uploadsList
            forall b c a. (b -> c) -> (a -> b) -> a -> c
Prelude.. forall a b. Prism (Maybe a) (Maybe b) a b
Lens._Just
        ) =
        forall a. Maybe a
Prelude.Nothing
    | Bool
Prelude.otherwise =
        forall a. a -> Maybe a
Prelude.Just
          forall a b. (a -> b) -> a -> b
Prelude.$ ListMultipartUploads
rq
          forall a b. a -> (a -> b) -> b
Prelude.& Lens' ListMultipartUploads (Maybe Text)
listMultipartUploads_marker
          forall s t a b. ASetter s t a b -> b -> s -> t
Lens..~ AWSResponse ListMultipartUploads
rs
          forall s a. s -> Getting (First a) s a -> Maybe a
Lens.^? Lens' ListMultipartUploadsResponse (Maybe Text)
listMultipartUploadsResponse_marker
          forall b c a. (b -> c) -> (a -> b) -> a -> c
Prelude.. forall a b. Prism (Maybe a) (Maybe b) a b
Lens._Just

instance Core.AWSRequest ListMultipartUploads where
  type
    AWSResponse ListMultipartUploads =
      ListMultipartUploadsResponse
  request :: (Service -> Service)
-> ListMultipartUploads -> Request ListMultipartUploads
request Service -> Service
overrides =
    forall a. ByteString -> Request a -> Request a
Request.glacierVersionHeader (Service -> ByteString
Core.version Service
defaultService)
      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 ListMultipartUploads
-> ClientResponse ClientBody
-> m (Either
        Error (ClientResponse (AWSResponse ListMultipartUploads)))
response =
    forall (m :: * -> *) a.
MonadResource m =>
(Int -> ResponseHeaders -> Object -> Either String (AWSResponse a))
-> (ByteStringLazy -> IO ByteStringLazy)
-> Service
-> Proxy a
-> ClientResponse ClientBody
-> m (Either Error (ClientResponse (AWSResponse a)))
Response.receiveJSON
      ( \Int
s ResponseHeaders
h Object
x ->
          Maybe Text
-> Maybe [UploadListElement] -> Int -> ListMultipartUploadsResponse
ListMultipartUploadsResponse'
            forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
Prelude.<$> (Object
x forall a. FromJSON a => Object -> Key -> Either String (Maybe a)
Data..?> Key
"Marker")
            forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
Prelude.<*> (Object
x forall a. FromJSON a => Object -> Key -> Either String (Maybe a)
Data..?> Key
"UploadsList" forall (f :: * -> *) a. Functor f => f (Maybe a) -> a -> f a
Core..!@ forall a. Monoid a => a
Prelude.mempty)
            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))
      )

instance Prelude.Hashable ListMultipartUploads where
  hashWithSalt :: Int -> ListMultipartUploads -> Int
hashWithSalt Int
_salt ListMultipartUploads' {Maybe Text
Text
vaultName :: Text
accountId :: Text
marker :: Maybe Text
limit :: Maybe Text
$sel:vaultName:ListMultipartUploads' :: ListMultipartUploads -> Text
$sel:accountId:ListMultipartUploads' :: ListMultipartUploads -> Text
$sel:marker:ListMultipartUploads' :: ListMultipartUploads -> Maybe Text
$sel:limit:ListMultipartUploads' :: ListMultipartUploads -> Maybe Text
..} =
    Int
_salt
      forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Maybe Text
limit
      forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Maybe Text
marker
      forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Text
accountId
      forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Text
vaultName

instance Prelude.NFData ListMultipartUploads where
  rnf :: ListMultipartUploads -> ()
rnf ListMultipartUploads' {Maybe Text
Text
vaultName :: Text
accountId :: Text
marker :: Maybe Text
limit :: Maybe Text
$sel:vaultName:ListMultipartUploads' :: ListMultipartUploads -> Text
$sel:accountId:ListMultipartUploads' :: ListMultipartUploads -> Text
$sel:marker:ListMultipartUploads' :: ListMultipartUploads -> Maybe Text
$sel:limit:ListMultipartUploads' :: ListMultipartUploads -> Maybe Text
..} =
    forall a. NFData a => a -> ()
Prelude.rnf Maybe Text
limit
      seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf Maybe Text
marker
      seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf Text
accountId
      seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf Text
vaultName

instance Data.ToHeaders ListMultipartUploads where
  toHeaders :: ListMultipartUploads -> ResponseHeaders
toHeaders = forall a b. a -> b -> a
Prelude.const forall a. Monoid a => a
Prelude.mempty

instance Data.ToPath ListMultipartUploads where
  toPath :: ListMultipartUploads -> ByteString
toPath ListMultipartUploads' {Maybe Text
Text
vaultName :: Text
accountId :: Text
marker :: Maybe Text
limit :: Maybe Text
$sel:vaultName:ListMultipartUploads' :: ListMultipartUploads -> Text
$sel:accountId:ListMultipartUploads' :: ListMultipartUploads -> Text
$sel:marker:ListMultipartUploads' :: ListMultipartUploads -> Maybe Text
$sel:limit:ListMultipartUploads' :: ListMultipartUploads -> Maybe Text
..} =
    forall a. Monoid a => [a] -> a
Prelude.mconcat
      [ ByteString
"/",
        forall a. ToByteString a => a -> ByteString
Data.toBS Text
accountId,
        ByteString
"/vaults/",
        forall a. ToByteString a => a -> ByteString
Data.toBS Text
vaultName,
        ByteString
"/multipart-uploads"
      ]

instance Data.ToQuery ListMultipartUploads where
  toQuery :: ListMultipartUploads -> QueryString
toQuery ListMultipartUploads' {Maybe Text
Text
vaultName :: Text
accountId :: Text
marker :: Maybe Text
limit :: Maybe Text
$sel:vaultName:ListMultipartUploads' :: ListMultipartUploads -> Text
$sel:accountId:ListMultipartUploads' :: ListMultipartUploads -> Text
$sel:marker:ListMultipartUploads' :: ListMultipartUploads -> Maybe Text
$sel:limit:ListMultipartUploads' :: ListMultipartUploads -> Maybe Text
..} =
    forall a. Monoid a => [a] -> a
Prelude.mconcat
      [ByteString
"limit" forall a. ToQuery a => ByteString -> a -> QueryString
Data.=: Maybe Text
limit, ByteString
"marker" forall a. ToQuery a => ByteString -> a -> QueryString
Data.=: Maybe Text
marker]

-- | Contains the Amazon S3 Glacier response to your request.
--
-- /See:/ 'newListMultipartUploadsResponse' smart constructor.
data ListMultipartUploadsResponse = ListMultipartUploadsResponse'
  { -- | An opaque string that represents where to continue pagination of the
    -- results. You use the marker in a new List Multipart Uploads request to
    -- obtain more uploads in the list. If there are no more uploads, this
    -- value is @null@.
    ListMultipartUploadsResponse -> Maybe Text
marker :: Prelude.Maybe Prelude.Text,
    -- | A list of in-progress multipart uploads.
    ListMultipartUploadsResponse -> Maybe [UploadListElement]
uploadsList :: Prelude.Maybe [UploadListElement],
    -- | The response's http status code.
    ListMultipartUploadsResponse -> Int
httpStatus :: Prelude.Int
  }
  deriving (ListMultipartUploadsResponse
-> ListMultipartUploadsResponse -> Bool
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: ListMultipartUploadsResponse
-> ListMultipartUploadsResponse -> Bool
$c/= :: ListMultipartUploadsResponse
-> ListMultipartUploadsResponse -> Bool
== :: ListMultipartUploadsResponse
-> ListMultipartUploadsResponse -> Bool
$c== :: ListMultipartUploadsResponse
-> ListMultipartUploadsResponse -> Bool
Prelude.Eq, ReadPrec [ListMultipartUploadsResponse]
ReadPrec ListMultipartUploadsResponse
Int -> ReadS ListMultipartUploadsResponse
ReadS [ListMultipartUploadsResponse]
forall a.
(Int -> ReadS a)
-> ReadS [a] -> ReadPrec a -> ReadPrec [a] -> Read a
readListPrec :: ReadPrec [ListMultipartUploadsResponse]
$creadListPrec :: ReadPrec [ListMultipartUploadsResponse]
readPrec :: ReadPrec ListMultipartUploadsResponse
$creadPrec :: ReadPrec ListMultipartUploadsResponse
readList :: ReadS [ListMultipartUploadsResponse]
$creadList :: ReadS [ListMultipartUploadsResponse]
readsPrec :: Int -> ReadS ListMultipartUploadsResponse
$creadsPrec :: Int -> ReadS ListMultipartUploadsResponse
Prelude.Read, Int -> ListMultipartUploadsResponse -> ShowS
[ListMultipartUploadsResponse] -> ShowS
ListMultipartUploadsResponse -> String
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [ListMultipartUploadsResponse] -> ShowS
$cshowList :: [ListMultipartUploadsResponse] -> ShowS
show :: ListMultipartUploadsResponse -> String
$cshow :: ListMultipartUploadsResponse -> String
showsPrec :: Int -> ListMultipartUploadsResponse -> ShowS
$cshowsPrec :: Int -> ListMultipartUploadsResponse -> ShowS
Prelude.Show, forall x.
Rep ListMultipartUploadsResponse x -> ListMultipartUploadsResponse
forall x.
ListMultipartUploadsResponse -> Rep ListMultipartUploadsResponse x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cto :: forall x.
Rep ListMultipartUploadsResponse x -> ListMultipartUploadsResponse
$cfrom :: forall x.
ListMultipartUploadsResponse -> Rep ListMultipartUploadsResponse x
Prelude.Generic)

-- |
-- Create a value of 'ListMultipartUploadsResponse' 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:
--
-- 'marker', 'listMultipartUploadsResponse_marker' - An opaque string that represents where to continue pagination of the
-- results. You use the marker in a new List Multipart Uploads request to
-- obtain more uploads in the list. If there are no more uploads, this
-- value is @null@.
--
-- 'uploadsList', 'listMultipartUploadsResponse_uploadsList' - A list of in-progress multipart uploads.
--
-- 'httpStatus', 'listMultipartUploadsResponse_httpStatus' - The response's http status code.
newListMultipartUploadsResponse ::
  -- | 'httpStatus'
  Prelude.Int ->
  ListMultipartUploadsResponse
newListMultipartUploadsResponse :: Int -> ListMultipartUploadsResponse
newListMultipartUploadsResponse Int
pHttpStatus_ =
  ListMultipartUploadsResponse'
    { $sel:marker:ListMultipartUploadsResponse' :: Maybe Text
marker =
        forall a. Maybe a
Prelude.Nothing,
      $sel:uploadsList:ListMultipartUploadsResponse' :: Maybe [UploadListElement]
uploadsList = forall a. Maybe a
Prelude.Nothing,
      $sel:httpStatus:ListMultipartUploadsResponse' :: Int
httpStatus = Int
pHttpStatus_
    }

-- | An opaque string that represents where to continue pagination of the
-- results. You use the marker in a new List Multipart Uploads request to
-- obtain more uploads in the list. If there are no more uploads, this
-- value is @null@.
listMultipartUploadsResponse_marker :: Lens.Lens' ListMultipartUploadsResponse (Prelude.Maybe Prelude.Text)
listMultipartUploadsResponse_marker :: Lens' ListMultipartUploadsResponse (Maybe Text)
listMultipartUploadsResponse_marker = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\ListMultipartUploadsResponse' {Maybe Text
marker :: Maybe Text
$sel:marker:ListMultipartUploadsResponse' :: ListMultipartUploadsResponse -> Maybe Text
marker} -> Maybe Text
marker) (\s :: ListMultipartUploadsResponse
s@ListMultipartUploadsResponse' {} Maybe Text
a -> ListMultipartUploadsResponse
s {$sel:marker:ListMultipartUploadsResponse' :: Maybe Text
marker = Maybe Text
a} :: ListMultipartUploadsResponse)

-- | A list of in-progress multipart uploads.
listMultipartUploadsResponse_uploadsList :: Lens.Lens' ListMultipartUploadsResponse (Prelude.Maybe [UploadListElement])
listMultipartUploadsResponse_uploadsList :: Lens' ListMultipartUploadsResponse (Maybe [UploadListElement])
listMultipartUploadsResponse_uploadsList = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\ListMultipartUploadsResponse' {Maybe [UploadListElement]
uploadsList :: Maybe [UploadListElement]
$sel:uploadsList:ListMultipartUploadsResponse' :: ListMultipartUploadsResponse -> Maybe [UploadListElement]
uploadsList} -> Maybe [UploadListElement]
uploadsList) (\s :: ListMultipartUploadsResponse
s@ListMultipartUploadsResponse' {} Maybe [UploadListElement]
a -> ListMultipartUploadsResponse
s {$sel:uploadsList:ListMultipartUploadsResponse' :: Maybe [UploadListElement]
uploadsList = Maybe [UploadListElement]
a} :: ListMultipartUploadsResponse) forall b c a. (b -> c) -> (a -> b) -> a -> c
Prelude.. forall (f :: * -> *) (g :: * -> *) s t a b.
(Functor f, Functor g) =>
AnIso s t a b -> Iso (f s) (g t) (f a) (g b)
Lens.mapping forall s t a b. (Coercible s a, Coercible t b) => Iso s t a b
Lens.coerced

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

instance Prelude.NFData ListMultipartUploadsResponse where
  rnf :: ListMultipartUploadsResponse -> ()
rnf ListMultipartUploadsResponse' {Int
Maybe [UploadListElement]
Maybe Text
httpStatus :: Int
uploadsList :: Maybe [UploadListElement]
marker :: Maybe Text
$sel:httpStatus:ListMultipartUploadsResponse' :: ListMultipartUploadsResponse -> Int
$sel:uploadsList:ListMultipartUploadsResponse' :: ListMultipartUploadsResponse -> Maybe [UploadListElement]
$sel:marker:ListMultipartUploadsResponse' :: ListMultipartUploadsResponse -> Maybe Text
..} =
    forall a. NFData a => a -> ()
Prelude.rnf Maybe Text
marker
      seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf Maybe [UploadListElement]
uploadsList
      seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf Int
httpStatus