{-# 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.ListChunks
-- 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 chunks in a given Object
module Amazonka.BackupStorage.ListChunks
  ( -- * Creating a Request
    ListChunks (..),
    newListChunks,

    -- * Request Lenses
    listChunks_maxResults,
    listChunks_nextToken,
    listChunks_storageJobId,
    listChunks_objectToken,

    -- * Destructuring the Response
    ListChunksResponse (..),
    newListChunksResponse,

    -- * Response Lenses
    listChunksResponse_nextToken,
    listChunksResponse_httpStatus,
    listChunksResponse_chunkList,
  )
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:/ 'newListChunks' smart constructor.
data ListChunks = ListChunks'
  { -- | Maximum number of chunks
    ListChunks -> Maybe Natural
maxResults :: Prelude.Maybe Prelude.Natural,
    -- | Pagination token
    ListChunks -> Maybe Text
nextToken :: Prelude.Maybe Prelude.Text,
    -- | Storage job id
    ListChunks -> Text
storageJobId :: Prelude.Text,
    -- | Object token
    ListChunks -> Text
objectToken :: Prelude.Text
  }
  deriving (ListChunks -> ListChunks -> Bool
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: ListChunks -> ListChunks -> Bool
$c/= :: ListChunks -> ListChunks -> Bool
== :: ListChunks -> ListChunks -> Bool
$c== :: ListChunks -> ListChunks -> Bool
Prelude.Eq, ReadPrec [ListChunks]
ReadPrec ListChunks
Int -> ReadS ListChunks
ReadS [ListChunks]
forall a.
(Int -> ReadS a)
-> ReadS [a] -> ReadPrec a -> ReadPrec [a] -> Read a
readListPrec :: ReadPrec [ListChunks]
$creadListPrec :: ReadPrec [ListChunks]
readPrec :: ReadPrec ListChunks
$creadPrec :: ReadPrec ListChunks
readList :: ReadS [ListChunks]
$creadList :: ReadS [ListChunks]
readsPrec :: Int -> ReadS ListChunks
$creadsPrec :: Int -> ReadS ListChunks
Prelude.Read, Int -> ListChunks -> ShowS
[ListChunks] -> ShowS
ListChunks -> String
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [ListChunks] -> ShowS
$cshowList :: [ListChunks] -> ShowS
show :: ListChunks -> String
$cshow :: ListChunks -> String
showsPrec :: Int -> ListChunks -> ShowS
$cshowsPrec :: Int -> ListChunks -> ShowS
Prelude.Show, forall x. Rep ListChunks x -> ListChunks
forall x. ListChunks -> Rep ListChunks x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cto :: forall x. Rep ListChunks x -> ListChunks
$cfrom :: forall x. ListChunks -> Rep ListChunks x
Prelude.Generic)

-- |
-- Create a value of 'ListChunks' 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:
--
-- 'maxResults', 'listChunks_maxResults' - Maximum number of chunks
--
-- 'nextToken', 'listChunks_nextToken' - Pagination token
--
-- 'storageJobId', 'listChunks_storageJobId' - Storage job id
--
-- 'objectToken', 'listChunks_objectToken' - Object token
newListChunks ::
  -- | 'storageJobId'
  Prelude.Text ->
  -- | 'objectToken'
  Prelude.Text ->
  ListChunks
newListChunks :: Text -> Text -> ListChunks
newListChunks Text
pStorageJobId_ Text
pObjectToken_ =
  ListChunks'
    { $sel:maxResults:ListChunks' :: Maybe Natural
maxResults = forall a. Maybe a
Prelude.Nothing,
      $sel:nextToken:ListChunks' :: Maybe Text
nextToken = forall a. Maybe a
Prelude.Nothing,
      $sel:storageJobId:ListChunks' :: Text
storageJobId = Text
pStorageJobId_,
      $sel:objectToken:ListChunks' :: Text
objectToken = Text
pObjectToken_
    }

-- | Maximum number of chunks
listChunks_maxResults :: Lens.Lens' ListChunks (Prelude.Maybe Prelude.Natural)
listChunks_maxResults :: Lens' ListChunks (Maybe Natural)
listChunks_maxResults = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\ListChunks' {Maybe Natural
maxResults :: Maybe Natural
$sel:maxResults:ListChunks' :: ListChunks -> Maybe Natural
maxResults} -> Maybe Natural
maxResults) (\s :: ListChunks
s@ListChunks' {} Maybe Natural
a -> ListChunks
s {$sel:maxResults:ListChunks' :: Maybe Natural
maxResults = Maybe Natural
a} :: ListChunks)

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

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

-- | Object token
listChunks_objectToken :: Lens.Lens' ListChunks Prelude.Text
listChunks_objectToken :: Lens' ListChunks Text
listChunks_objectToken = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\ListChunks' {Text
objectToken :: Text
$sel:objectToken:ListChunks' :: ListChunks -> Text
objectToken} -> Text
objectToken) (\s :: ListChunks
s@ListChunks' {} Text
a -> ListChunks
s {$sel:objectToken:ListChunks' :: Text
objectToken = Text
a} :: ListChunks)

instance Core.AWSRequest ListChunks where
  type AWSResponse ListChunks = ListChunksResponse
  request :: (Service -> Service) -> ListChunks -> Request ListChunks
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 ListChunks
-> ClientResponse ClientBody
-> m (Either Error (ClientResponse (AWSResponse ListChunks)))
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 -> [Chunk] -> ListChunksResponse
ListChunksResponse'
            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
"ChunkList" forall (f :: * -> *) a. Functor f => f (Maybe a) -> a -> f a
Core..!@ forall a. Monoid a => a
Prelude.mempty)
      )

instance Prelude.Hashable ListChunks where
  hashWithSalt :: Int -> ListChunks -> Int
hashWithSalt Int
_salt ListChunks' {Maybe Natural
Maybe Text
Text
objectToken :: Text
storageJobId :: Text
nextToken :: Maybe Text
maxResults :: Maybe Natural
$sel:objectToken:ListChunks' :: ListChunks -> Text
$sel:storageJobId:ListChunks' :: ListChunks -> Text
$sel:nextToken:ListChunks' :: ListChunks -> Maybe Text
$sel:maxResults:ListChunks' :: ListChunks -> Maybe Natural
..} =
    Int
_salt
      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` Text
storageJobId
      forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Text
objectToken

instance Prelude.NFData ListChunks where
  rnf :: ListChunks -> ()
rnf ListChunks' {Maybe Natural
Maybe Text
Text
objectToken :: Text
storageJobId :: Text
nextToken :: Maybe Text
maxResults :: Maybe Natural
$sel:objectToken:ListChunks' :: ListChunks -> Text
$sel:storageJobId:ListChunks' :: ListChunks -> Text
$sel:nextToken:ListChunks' :: ListChunks -> Maybe Text
$sel:maxResults:ListChunks' :: ListChunks -> Maybe Natural
..} =
    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 Text
storageJobId
      seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf Text
objectToken

instance Data.ToHeaders ListChunks where
  toHeaders :: ListChunks -> 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 ListChunks where
  toPath :: ListChunks -> ByteString
toPath ListChunks' {Maybe Natural
Maybe Text
Text
objectToken :: Text
storageJobId :: Text
nextToken :: Maybe Text
maxResults :: Maybe Natural
$sel:objectToken:ListChunks' :: ListChunks -> Text
$sel:storageJobId:ListChunks' :: ListChunks -> Text
$sel:nextToken:ListChunks' :: ListChunks -> Maybe Text
$sel:maxResults:ListChunks' :: ListChunks -> Maybe Natural
..} =
    forall a. Monoid a => [a] -> a
Prelude.mconcat
      [ ByteString
"/restore-jobs/",
        forall a. ToByteString a => a -> ByteString
Data.toBS Text
storageJobId,
        ByteString
"/chunks/",
        forall a. ToByteString a => a -> ByteString
Data.toBS Text
objectToken,
        ByteString
"/list"
      ]

instance Data.ToQuery ListChunks where
  toQuery :: ListChunks -> QueryString
toQuery ListChunks' {Maybe Natural
Maybe Text
Text
objectToken :: Text
storageJobId :: Text
nextToken :: Maybe Text
maxResults :: Maybe Natural
$sel:objectToken:ListChunks' :: ListChunks -> Text
$sel:storageJobId:ListChunks' :: ListChunks -> Text
$sel:nextToken:ListChunks' :: ListChunks -> Maybe Text
$sel:maxResults:ListChunks' :: ListChunks -> Maybe Natural
..} =
    forall a. Monoid a => [a] -> a
Prelude.mconcat
      [ 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
      ]

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

-- |
-- Create a value of 'ListChunksResponse' 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', 'listChunksResponse_nextToken' - Pagination token
--
-- 'httpStatus', 'listChunksResponse_httpStatus' - The response's http status code.
--
-- 'chunkList', 'listChunksResponse_chunkList' - List of chunks
newListChunksResponse ::
  -- | 'httpStatus'
  Prelude.Int ->
  ListChunksResponse
newListChunksResponse :: Int -> ListChunksResponse
newListChunksResponse Int
pHttpStatus_ =
  ListChunksResponse'
    { $sel:nextToken:ListChunksResponse' :: Maybe Text
nextToken = forall a. Maybe a
Prelude.Nothing,
      $sel:httpStatus:ListChunksResponse' :: Int
httpStatus = Int
pHttpStatus_,
      $sel:chunkList:ListChunksResponse' :: [Chunk]
chunkList = forall a. Monoid a => a
Prelude.mempty
    }

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

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

-- | List of chunks
listChunksResponse_chunkList :: Lens.Lens' ListChunksResponse [Chunk]
listChunksResponse_chunkList :: Lens' ListChunksResponse [Chunk]
listChunksResponse_chunkList = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\ListChunksResponse' {[Chunk]
chunkList :: [Chunk]
$sel:chunkList:ListChunksResponse' :: ListChunksResponse -> [Chunk]
chunkList} -> [Chunk]
chunkList) (\s :: ListChunksResponse
s@ListChunksResponse' {} [Chunk]
a -> ListChunksResponse
s {$sel:chunkList:ListChunksResponse' :: [Chunk]
chunkList = [Chunk]
a} :: ListChunksResponse) 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 ListChunksResponse where
  rnf :: ListChunksResponse -> ()
rnf ListChunksResponse' {Int
[Chunk]
Maybe Text
chunkList :: [Chunk]
httpStatus :: Int
nextToken :: Maybe Text
$sel:chunkList:ListChunksResponse' :: ListChunksResponse -> [Chunk]
$sel:httpStatus:ListChunksResponse' :: ListChunksResponse -> Int
$sel:nextToken:ListChunksResponse' :: ListChunksResponse -> 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 [Chunk]
chunkList