{-# 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.BackupStorage.ListObjects
-- Copyright   : (c) 2013-2023 Brendan Hay
-- License     : Mozilla Public License, v. 2.0.
-- Maintainer  : Brendan Hay
-- Stability   : auto-generated
-- Portability : non-portable (GHC extensions)
--
-- List all Objects in a given Backup.
module Amazonka.BackupStorage.ListObjects
  ( -- * Creating a Request
    ListObjects (..),
    newListObjects,

    -- * Request Lenses
    listObjects_createdAfter,
    listObjects_createdBefore,
    listObjects_maxResults,
    listObjects_nextToken,
    listObjects_startingObjectName,
    listObjects_startingObjectPrefix,
    listObjects_storageJobId,

    -- * Destructuring the Response
    ListObjectsResponse (..),
    newListObjectsResponse,

    -- * Response Lenses
    listObjectsResponse_nextToken,
    listObjectsResponse_httpStatus,
    listObjectsResponse_objectList,
  )
where

import Amazonka.BackupStorage.Types
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

-- | /See:/ 'newListObjects' smart constructor.
data ListObjects = ListObjects'
  { -- | (Optional) Created after filter
    ListObjects -> Maybe POSIX
createdAfter :: Prelude.Maybe Data.POSIX,
    -- | (Optional) Created before filter
    ListObjects -> Maybe POSIX
createdBefore :: Prelude.Maybe Data.POSIX,
    -- | Maximum objects count
    ListObjects -> Maybe Natural
maxResults :: Prelude.Maybe Prelude.Natural,
    -- | Pagination token
    ListObjects -> Maybe Text
nextToken :: Prelude.Maybe Prelude.Text,
    -- | Optional, specifies the starting Object name to list from. Ignored if
    -- NextToken is not NULL
    ListObjects -> Maybe Text
startingObjectName :: Prelude.Maybe Prelude.Text,
    -- | Optional, specifies the starting Object prefix to list from. Ignored if
    -- NextToken is not NULL
    ListObjects -> Maybe Text
startingObjectPrefix :: Prelude.Maybe Prelude.Text,
    -- | Storage job id
    ListObjects -> Text
storageJobId :: Prelude.Text
  }
  deriving (ListObjects -> ListObjects -> Bool
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: ListObjects -> ListObjects -> Bool
$c/= :: ListObjects -> ListObjects -> Bool
== :: ListObjects -> ListObjects -> Bool
$c== :: ListObjects -> ListObjects -> Bool
Prelude.Eq, ReadPrec [ListObjects]
ReadPrec ListObjects
Int -> ReadS ListObjects
ReadS [ListObjects]
forall a.
(Int -> ReadS a)
-> ReadS [a] -> ReadPrec a -> ReadPrec [a] -> Read a
readListPrec :: ReadPrec [ListObjects]
$creadListPrec :: ReadPrec [ListObjects]
readPrec :: ReadPrec ListObjects
$creadPrec :: ReadPrec ListObjects
readList :: ReadS [ListObjects]
$creadList :: ReadS [ListObjects]
readsPrec :: Int -> ReadS ListObjects
$creadsPrec :: Int -> ReadS ListObjects
Prelude.Read, Int -> ListObjects -> ShowS
[ListObjects] -> ShowS
ListObjects -> String
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [ListObjects] -> ShowS
$cshowList :: [ListObjects] -> ShowS
show :: ListObjects -> String
$cshow :: ListObjects -> String
showsPrec :: Int -> ListObjects -> ShowS
$cshowsPrec :: Int -> ListObjects -> ShowS
Prelude.Show, forall x. Rep ListObjects x -> ListObjects
forall x. ListObjects -> Rep ListObjects x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cto :: forall x. Rep ListObjects x -> ListObjects
$cfrom :: forall x. ListObjects -> Rep ListObjects x
Prelude.Generic)

-- |
-- Create a value of 'ListObjects' 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:
--
-- 'createdAfter', 'listObjects_createdAfter' - (Optional) Created after filter
--
-- 'createdBefore', 'listObjects_createdBefore' - (Optional) Created before filter
--
-- 'maxResults', 'listObjects_maxResults' - Maximum objects count
--
-- 'nextToken', 'listObjects_nextToken' - Pagination token
--
-- 'startingObjectName', 'listObjects_startingObjectName' - Optional, specifies the starting Object name to list from. Ignored if
-- NextToken is not NULL
--
-- 'startingObjectPrefix', 'listObjects_startingObjectPrefix' - Optional, specifies the starting Object prefix to list from. Ignored if
-- NextToken is not NULL
--
-- 'storageJobId', 'listObjects_storageJobId' - Storage job id
newListObjects ::
  -- | 'storageJobId'
  Prelude.Text ->
  ListObjects
newListObjects :: Text -> ListObjects
newListObjects Text
pStorageJobId_ =
  ListObjects'
    { $sel:createdAfter:ListObjects' :: Maybe POSIX
createdAfter = forall a. Maybe a
Prelude.Nothing,
      $sel:createdBefore:ListObjects' :: Maybe POSIX
createdBefore = forall a. Maybe a
Prelude.Nothing,
      $sel:maxResults:ListObjects' :: Maybe Natural
maxResults = forall a. Maybe a
Prelude.Nothing,
      $sel:nextToken:ListObjects' :: Maybe Text
nextToken = forall a. Maybe a
Prelude.Nothing,
      $sel:startingObjectName:ListObjects' :: Maybe Text
startingObjectName = forall a. Maybe a
Prelude.Nothing,
      $sel:startingObjectPrefix:ListObjects' :: Maybe Text
startingObjectPrefix = forall a. Maybe a
Prelude.Nothing,
      $sel:storageJobId:ListObjects' :: Text
storageJobId = Text
pStorageJobId_
    }

-- | (Optional) Created after filter
listObjects_createdAfter :: Lens.Lens' ListObjects (Prelude.Maybe Prelude.UTCTime)
listObjects_createdAfter :: Lens' ListObjects (Maybe UTCTime)
listObjects_createdAfter = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\ListObjects' {Maybe POSIX
createdAfter :: Maybe POSIX
$sel:createdAfter:ListObjects' :: ListObjects -> Maybe POSIX
createdAfter} -> Maybe POSIX
createdAfter) (\s :: ListObjects
s@ListObjects' {} Maybe POSIX
a -> ListObjects
s {$sel:createdAfter:ListObjects' :: Maybe POSIX
createdAfter = Maybe POSIX
a} :: ListObjects) 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 (a :: Format). Iso' (Time a) UTCTime
Data._Time

-- | (Optional) Created before filter
listObjects_createdBefore :: Lens.Lens' ListObjects (Prelude.Maybe Prelude.UTCTime)
listObjects_createdBefore :: Lens' ListObjects (Maybe UTCTime)
listObjects_createdBefore = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\ListObjects' {Maybe POSIX
createdBefore :: Maybe POSIX
$sel:createdBefore:ListObjects' :: ListObjects -> Maybe POSIX
createdBefore} -> Maybe POSIX
createdBefore) (\s :: ListObjects
s@ListObjects' {} Maybe POSIX
a -> ListObjects
s {$sel:createdBefore:ListObjects' :: Maybe POSIX
createdBefore = Maybe POSIX
a} :: ListObjects) 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 (a :: Format). Iso' (Time a) UTCTime
Data._Time

-- | Maximum objects count
listObjects_maxResults :: Lens.Lens' ListObjects (Prelude.Maybe Prelude.Natural)
listObjects_maxResults :: Lens' ListObjects (Maybe Natural)
listObjects_maxResults = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\ListObjects' {Maybe Natural
maxResults :: Maybe Natural
$sel:maxResults:ListObjects' :: ListObjects -> Maybe Natural
maxResults} -> Maybe Natural
maxResults) (\s :: ListObjects
s@ListObjects' {} Maybe Natural
a -> ListObjects
s {$sel:maxResults:ListObjects' :: Maybe Natural
maxResults = Maybe Natural
a} :: ListObjects)

-- | Pagination token
listObjects_nextToken :: Lens.Lens' ListObjects (Prelude.Maybe Prelude.Text)
listObjects_nextToken :: Lens' ListObjects (Maybe Text)
listObjects_nextToken = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\ListObjects' {Maybe Text
nextToken :: Maybe Text
$sel:nextToken:ListObjects' :: ListObjects -> Maybe Text
nextToken} -> Maybe Text
nextToken) (\s :: ListObjects
s@ListObjects' {} Maybe Text
a -> ListObjects
s {$sel:nextToken:ListObjects' :: Maybe Text
nextToken = Maybe Text
a} :: ListObjects)

-- | Optional, specifies the starting Object name to list from. Ignored if
-- NextToken is not NULL
listObjects_startingObjectName :: Lens.Lens' ListObjects (Prelude.Maybe Prelude.Text)
listObjects_startingObjectName :: Lens' ListObjects (Maybe Text)
listObjects_startingObjectName = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\ListObjects' {Maybe Text
startingObjectName :: Maybe Text
$sel:startingObjectName:ListObjects' :: ListObjects -> Maybe Text
startingObjectName} -> Maybe Text
startingObjectName) (\s :: ListObjects
s@ListObjects' {} Maybe Text
a -> ListObjects
s {$sel:startingObjectName:ListObjects' :: Maybe Text
startingObjectName = Maybe Text
a} :: ListObjects)

-- | Optional, specifies the starting Object prefix to list from. Ignored if
-- NextToken is not NULL
listObjects_startingObjectPrefix :: Lens.Lens' ListObjects (Prelude.Maybe Prelude.Text)
listObjects_startingObjectPrefix :: Lens' ListObjects (Maybe Text)
listObjects_startingObjectPrefix = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\ListObjects' {Maybe Text
startingObjectPrefix :: Maybe Text
$sel:startingObjectPrefix:ListObjects' :: ListObjects -> Maybe Text
startingObjectPrefix} -> Maybe Text
startingObjectPrefix) (\s :: ListObjects
s@ListObjects' {} Maybe Text
a -> ListObjects
s {$sel:startingObjectPrefix:ListObjects' :: Maybe Text
startingObjectPrefix = Maybe Text
a} :: ListObjects)

-- | Storage job id
listObjects_storageJobId :: Lens.Lens' ListObjects Prelude.Text
listObjects_storageJobId :: Lens' ListObjects Text
listObjects_storageJobId = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\ListObjects' {Text
storageJobId :: Text
$sel:storageJobId:ListObjects' :: ListObjects -> Text
storageJobId} -> Text
storageJobId) (\s :: ListObjects
s@ListObjects' {} Text
a -> ListObjects
s {$sel:storageJobId:ListObjects' :: Text
storageJobId = Text
a} :: ListObjects)

instance Core.AWSRequest ListObjects where
  type AWSResponse ListObjects = ListObjectsResponse
  request :: (Service -> Service) -> ListObjects -> Request ListObjects
request Service -> Service
overrides =
    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 ListObjects
-> ClientResponse ClientBody
-> m (Either Error (ClientResponse (AWSResponse ListObjects)))
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 -> Int -> [BackupObject] -> ListObjectsResponse
ListObjectsResponse'
            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
"NextToken")
            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.<*> (Object
x forall a. FromJSON a => Object -> Key -> Either String (Maybe a)
Data..?> Key
"ObjectList" forall (f :: * -> *) a. Functor f => f (Maybe a) -> a -> f a
Core..!@ forall a. Monoid a => a
Prelude.mempty)
      )

instance Prelude.Hashable ListObjects where
  hashWithSalt :: Int -> ListObjects -> Int
hashWithSalt Int
_salt ListObjects' {Maybe Natural
Maybe Text
Maybe POSIX
Text
storageJobId :: Text
startingObjectPrefix :: Maybe Text
startingObjectName :: Maybe Text
nextToken :: Maybe Text
maxResults :: Maybe Natural
createdBefore :: Maybe POSIX
createdAfter :: Maybe POSIX
$sel:storageJobId:ListObjects' :: ListObjects -> Text
$sel:startingObjectPrefix:ListObjects' :: ListObjects -> Maybe Text
$sel:startingObjectName:ListObjects' :: ListObjects -> Maybe Text
$sel:nextToken:ListObjects' :: ListObjects -> Maybe Text
$sel:maxResults:ListObjects' :: ListObjects -> Maybe Natural
$sel:createdBefore:ListObjects' :: ListObjects -> Maybe POSIX
$sel:createdAfter:ListObjects' :: ListObjects -> Maybe POSIX
..} =
    Int
_salt
      forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Maybe POSIX
createdAfter
      forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Maybe POSIX
createdBefore
      forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Maybe Natural
maxResults
      forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Maybe Text
nextToken
      forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Maybe Text
startingObjectName
      forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Maybe Text
startingObjectPrefix
      forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Text
storageJobId

instance Prelude.NFData ListObjects where
  rnf :: ListObjects -> ()
rnf ListObjects' {Maybe Natural
Maybe Text
Maybe POSIX
Text
storageJobId :: Text
startingObjectPrefix :: Maybe Text
startingObjectName :: Maybe Text
nextToken :: Maybe Text
maxResults :: Maybe Natural
createdBefore :: Maybe POSIX
createdAfter :: Maybe POSIX
$sel:storageJobId:ListObjects' :: ListObjects -> Text
$sel:startingObjectPrefix:ListObjects' :: ListObjects -> Maybe Text
$sel:startingObjectName:ListObjects' :: ListObjects -> Maybe Text
$sel:nextToken:ListObjects' :: ListObjects -> Maybe Text
$sel:maxResults:ListObjects' :: ListObjects -> Maybe Natural
$sel:createdBefore:ListObjects' :: ListObjects -> Maybe POSIX
$sel:createdAfter:ListObjects' :: ListObjects -> Maybe POSIX
..} =
    forall a. NFData a => a -> ()
Prelude.rnf Maybe POSIX
createdAfter
      seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf Maybe POSIX
createdBefore
      seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf Maybe Natural
maxResults
      seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf Maybe Text
nextToken
      seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf Maybe Text
startingObjectName
      seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf Maybe Text
startingObjectPrefix
      seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf Text
storageJobId

instance Data.ToHeaders ListObjects where
  toHeaders :: ListObjects -> ResponseHeaders
toHeaders =
    forall a b. a -> b -> a
Prelude.const
      ( forall a. Monoid a => [a] -> a
Prelude.mconcat
          [ HeaderName
"Content-Type"
              forall a. ToHeader a => HeaderName -> a -> ResponseHeaders
Data.=# ( ByteString
"application/x-amz-json-1.1" ::
                          Prelude.ByteString
                      )
          ]
      )

instance Data.ToPath ListObjects where
  toPath :: ListObjects -> ByteString
toPath ListObjects' {Maybe Natural
Maybe Text
Maybe POSIX
Text
storageJobId :: Text
startingObjectPrefix :: Maybe Text
startingObjectName :: Maybe Text
nextToken :: Maybe Text
maxResults :: Maybe Natural
createdBefore :: Maybe POSIX
createdAfter :: Maybe POSIX
$sel:storageJobId:ListObjects' :: ListObjects -> Text
$sel:startingObjectPrefix:ListObjects' :: ListObjects -> Maybe Text
$sel:startingObjectName:ListObjects' :: ListObjects -> Maybe Text
$sel:nextToken:ListObjects' :: ListObjects -> Maybe Text
$sel:maxResults:ListObjects' :: ListObjects -> Maybe Natural
$sel:createdBefore:ListObjects' :: ListObjects -> Maybe POSIX
$sel:createdAfter:ListObjects' :: ListObjects -> Maybe POSIX
..} =
    forall a. Monoid a => [a] -> a
Prelude.mconcat
      [ ByteString
"/restore-jobs/",
        forall a. ToByteString a => a -> ByteString
Data.toBS Text
storageJobId,
        ByteString
"/objects/list"
      ]

instance Data.ToQuery ListObjects where
  toQuery :: ListObjects -> QueryString
toQuery ListObjects' {Maybe Natural
Maybe Text
Maybe POSIX
Text
storageJobId :: Text
startingObjectPrefix :: Maybe Text
startingObjectName :: Maybe Text
nextToken :: Maybe Text
maxResults :: Maybe Natural
createdBefore :: Maybe POSIX
createdAfter :: Maybe POSIX
$sel:storageJobId:ListObjects' :: ListObjects -> Text
$sel:startingObjectPrefix:ListObjects' :: ListObjects -> Maybe Text
$sel:startingObjectName:ListObjects' :: ListObjects -> Maybe Text
$sel:nextToken:ListObjects' :: ListObjects -> Maybe Text
$sel:maxResults:ListObjects' :: ListObjects -> Maybe Natural
$sel:createdBefore:ListObjects' :: ListObjects -> Maybe POSIX
$sel:createdAfter:ListObjects' :: ListObjects -> Maybe POSIX
..} =
    forall a. Monoid a => [a] -> a
Prelude.mconcat
      [ ByteString
"created-after" forall a. ToQuery a => ByteString -> a -> QueryString
Data.=: Maybe POSIX
createdAfter,
        ByteString
"created-before" forall a. ToQuery a => ByteString -> a -> QueryString
Data.=: Maybe POSIX
createdBefore,
        ByteString
"max-results" forall a. ToQuery a => ByteString -> a -> QueryString
Data.=: Maybe Natural
maxResults,
        ByteString
"next-token" forall a. ToQuery a => ByteString -> a -> QueryString
Data.=: Maybe Text
nextToken,
        ByteString
"starting-object-name" forall a. ToQuery a => ByteString -> a -> QueryString
Data.=: Maybe Text
startingObjectName,
        ByteString
"starting-object-prefix"
          forall a. ToQuery a => ByteString -> a -> QueryString
Data.=: Maybe Text
startingObjectPrefix
      ]

-- | /See:/ 'newListObjectsResponse' smart constructor.
data ListObjectsResponse = ListObjectsResponse'
  { -- | Pagination token
    ListObjectsResponse -> Maybe Text
nextToken :: Prelude.Maybe Prelude.Text,
    -- | The response's http status code.
    ListObjectsResponse -> Int
httpStatus :: Prelude.Int,
    -- | Object list
    ListObjectsResponse -> [BackupObject]
objectList :: [BackupObject]
  }
  deriving (ListObjectsResponse -> ListObjectsResponse -> Bool
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: ListObjectsResponse -> ListObjectsResponse -> Bool
$c/= :: ListObjectsResponse -> ListObjectsResponse -> Bool
== :: ListObjectsResponse -> ListObjectsResponse -> Bool
$c== :: ListObjectsResponse -> ListObjectsResponse -> Bool
Prelude.Eq, ReadPrec [ListObjectsResponse]
ReadPrec ListObjectsResponse
Int -> ReadS ListObjectsResponse
ReadS [ListObjectsResponse]
forall a.
(Int -> ReadS a)
-> ReadS [a] -> ReadPrec a -> ReadPrec [a] -> Read a
readListPrec :: ReadPrec [ListObjectsResponse]
$creadListPrec :: ReadPrec [ListObjectsResponse]
readPrec :: ReadPrec ListObjectsResponse
$creadPrec :: ReadPrec ListObjectsResponse
readList :: ReadS [ListObjectsResponse]
$creadList :: ReadS [ListObjectsResponse]
readsPrec :: Int -> ReadS ListObjectsResponse
$creadsPrec :: Int -> ReadS ListObjectsResponse
Prelude.Read, Int -> ListObjectsResponse -> ShowS
[ListObjectsResponse] -> ShowS
ListObjectsResponse -> String
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [ListObjectsResponse] -> ShowS
$cshowList :: [ListObjectsResponse] -> ShowS
show :: ListObjectsResponse -> String
$cshow :: ListObjectsResponse -> String
showsPrec :: Int -> ListObjectsResponse -> ShowS
$cshowsPrec :: Int -> ListObjectsResponse -> ShowS
Prelude.Show, forall x. Rep ListObjectsResponse x -> ListObjectsResponse
forall x. ListObjectsResponse -> Rep ListObjectsResponse x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cto :: forall x. Rep ListObjectsResponse x -> ListObjectsResponse
$cfrom :: forall x. ListObjectsResponse -> Rep ListObjectsResponse x
Prelude.Generic)

-- |
-- Create a value of 'ListObjectsResponse' 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:
--
-- 'nextToken', 'listObjectsResponse_nextToken' - Pagination token
--
-- 'httpStatus', 'listObjectsResponse_httpStatus' - The response's http status code.
--
-- 'objectList', 'listObjectsResponse_objectList' - Object list
newListObjectsResponse ::
  -- | 'httpStatus'
  Prelude.Int ->
  ListObjectsResponse
newListObjectsResponse :: Int -> ListObjectsResponse
newListObjectsResponse Int
pHttpStatus_ =
  ListObjectsResponse'
    { $sel:nextToken:ListObjectsResponse' :: Maybe Text
nextToken = forall a. Maybe a
Prelude.Nothing,
      $sel:httpStatus:ListObjectsResponse' :: Int
httpStatus = Int
pHttpStatus_,
      $sel:objectList:ListObjectsResponse' :: [BackupObject]
objectList = forall a. Monoid a => a
Prelude.mempty
    }

-- | Pagination token
listObjectsResponse_nextToken :: Lens.Lens' ListObjectsResponse (Prelude.Maybe Prelude.Text)
listObjectsResponse_nextToken :: Lens' ListObjectsResponse (Maybe Text)
listObjectsResponse_nextToken = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\ListObjectsResponse' {Maybe Text
nextToken :: Maybe Text
$sel:nextToken:ListObjectsResponse' :: ListObjectsResponse -> Maybe Text
nextToken} -> Maybe Text
nextToken) (\s :: ListObjectsResponse
s@ListObjectsResponse' {} Maybe Text
a -> ListObjectsResponse
s {$sel:nextToken:ListObjectsResponse' :: Maybe Text
nextToken = Maybe Text
a} :: ListObjectsResponse)

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

-- | Object list
listObjectsResponse_objectList :: Lens.Lens' ListObjectsResponse [BackupObject]
listObjectsResponse_objectList :: Lens' ListObjectsResponse [BackupObject]
listObjectsResponse_objectList = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\ListObjectsResponse' {[BackupObject]
objectList :: [BackupObject]
$sel:objectList:ListObjectsResponse' :: ListObjectsResponse -> [BackupObject]
objectList} -> [BackupObject]
objectList) (\s :: ListObjectsResponse
s@ListObjectsResponse' {} [BackupObject]
a -> ListObjectsResponse
s {$sel:objectList:ListObjectsResponse' :: [BackupObject]
objectList = [BackupObject]
a} :: ListObjectsResponse) forall b c a. (b -> c) -> (a -> b) -> a -> c
Prelude.. forall s t a b. (Coercible s a, Coercible t b) => Iso s t a b
Lens.coerced

instance Prelude.NFData ListObjectsResponse where
  rnf :: ListObjectsResponse -> ()
rnf ListObjectsResponse' {Int
[BackupObject]
Maybe Text
objectList :: [BackupObject]
httpStatus :: Int
nextToken :: Maybe Text
$sel:objectList:ListObjectsResponse' :: ListObjectsResponse -> [BackupObject]
$sel:httpStatus:ListObjectsResponse' :: ListObjectsResponse -> Int
$sel:nextToken:ListObjectsResponse' :: ListObjectsResponse -> Maybe Text
..} =
    forall a. NFData a => a -> ()
Prelude.rnf Maybe Text
nextToken
      seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf Int
httpStatus
      seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf [BackupObject]
objectList