{-# 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.MediaStoreData.ListItems
-- Copyright   : (c) 2013-2023 Brendan Hay
-- License     : Mozilla Public License, v. 2.0.
-- Maintainer  : Brendan Hay
-- Stability   : auto-generated
-- Portability : non-portable (GHC extensions)
--
-- Provides a list of metadata entries about folders and objects in the
-- specified folder.
--
-- This operation returns paginated results.
module Amazonka.MediaStoreData.ListItems
  ( -- * Creating a Request
    ListItems (..),
    newListItems,

    -- * Request Lenses
    listItems_maxResults,
    listItems_nextToken,
    listItems_path,

    -- * Destructuring the Response
    ListItemsResponse (..),
    newListItemsResponse,

    -- * Response Lenses
    listItemsResponse_items,
    listItemsResponse_nextToken,
    listItemsResponse_httpStatus,
  )
where

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

-- | /See:/ 'newListItems' smart constructor.
data ListItems = ListItems'
  { -- | The maximum number of results to return per API request. For example,
    -- you submit a @ListItems@ request with @MaxResults@ set at 500. Although
    -- 2,000 items match your request, the service returns no more than the
    -- first 500 items. (The service also returns a @NextToken@ value that you
    -- can use to fetch the next batch of results.) The service might return
    -- fewer results than the @MaxResults@ value.
    --
    -- If @MaxResults@ is not included in the request, the service defaults to
    -- pagination with a maximum of 1,000 results per page.
    ListItems -> Maybe Natural
maxResults :: Prelude.Maybe Prelude.Natural,
    -- | The token that identifies which batch of results that you want to see.
    -- For example, you submit a @ListItems@ request with @MaxResults@ set at
    -- 500. The service returns the first batch of results (up to 500) and a
    -- @NextToken@ value. To see the next batch of results, you can submit the
    -- @ListItems@ request a second time and specify the @NextToken@ value.
    --
    -- Tokens expire after 15 minutes.
    ListItems -> Maybe Text
nextToken :: Prelude.Maybe Prelude.Text,
    -- | The path in the container from which to retrieve items. Format: \<folder
    -- name>\/\<folder name>\/\<file name>
    ListItems -> Maybe Text
path :: Prelude.Maybe Prelude.Text
  }
  deriving (ListItems -> ListItems -> Bool
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: ListItems -> ListItems -> Bool
$c/= :: ListItems -> ListItems -> Bool
== :: ListItems -> ListItems -> Bool
$c== :: ListItems -> ListItems -> Bool
Prelude.Eq, ReadPrec [ListItems]
ReadPrec ListItems
Int -> ReadS ListItems
ReadS [ListItems]
forall a.
(Int -> ReadS a)
-> ReadS [a] -> ReadPrec a -> ReadPrec [a] -> Read a
readListPrec :: ReadPrec [ListItems]
$creadListPrec :: ReadPrec [ListItems]
readPrec :: ReadPrec ListItems
$creadPrec :: ReadPrec ListItems
readList :: ReadS [ListItems]
$creadList :: ReadS [ListItems]
readsPrec :: Int -> ReadS ListItems
$creadsPrec :: Int -> ReadS ListItems
Prelude.Read, Int -> ListItems -> ShowS
[ListItems] -> ShowS
ListItems -> String
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [ListItems] -> ShowS
$cshowList :: [ListItems] -> ShowS
show :: ListItems -> String
$cshow :: ListItems -> String
showsPrec :: Int -> ListItems -> ShowS
$cshowsPrec :: Int -> ListItems -> ShowS
Prelude.Show, forall x. Rep ListItems x -> ListItems
forall x. ListItems -> Rep ListItems x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cto :: forall x. Rep ListItems x -> ListItems
$cfrom :: forall x. ListItems -> Rep ListItems x
Prelude.Generic)

-- |
-- Create a value of 'ListItems' 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', 'listItems_maxResults' - The maximum number of results to return per API request. For example,
-- you submit a @ListItems@ request with @MaxResults@ set at 500. Although
-- 2,000 items match your request, the service returns no more than the
-- first 500 items. (The service also returns a @NextToken@ value that you
-- can use to fetch the next batch of results.) The service might return
-- fewer results than the @MaxResults@ value.
--
-- If @MaxResults@ is not included in the request, the service defaults to
-- pagination with a maximum of 1,000 results per page.
--
-- 'nextToken', 'listItems_nextToken' - The token that identifies which batch of results that you want to see.
-- For example, you submit a @ListItems@ request with @MaxResults@ set at
-- 500. The service returns the first batch of results (up to 500) and a
-- @NextToken@ value. To see the next batch of results, you can submit the
-- @ListItems@ request a second time and specify the @NextToken@ value.
--
-- Tokens expire after 15 minutes.
--
-- 'path', 'listItems_path' - The path in the container from which to retrieve items. Format: \<folder
-- name>\/\<folder name>\/\<file name>
newListItems ::
  ListItems
newListItems :: ListItems
newListItems =
  ListItems'
    { $sel:maxResults:ListItems' :: Maybe Natural
maxResults = forall a. Maybe a
Prelude.Nothing,
      $sel:nextToken:ListItems' :: Maybe Text
nextToken = forall a. Maybe a
Prelude.Nothing,
      $sel:path:ListItems' :: Maybe Text
path = forall a. Maybe a
Prelude.Nothing
    }

-- | The maximum number of results to return per API request. For example,
-- you submit a @ListItems@ request with @MaxResults@ set at 500. Although
-- 2,000 items match your request, the service returns no more than the
-- first 500 items. (The service also returns a @NextToken@ value that you
-- can use to fetch the next batch of results.) The service might return
-- fewer results than the @MaxResults@ value.
--
-- If @MaxResults@ is not included in the request, the service defaults to
-- pagination with a maximum of 1,000 results per page.
listItems_maxResults :: Lens.Lens' ListItems (Prelude.Maybe Prelude.Natural)
listItems_maxResults :: Lens' ListItems (Maybe Natural)
listItems_maxResults = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\ListItems' {Maybe Natural
maxResults :: Maybe Natural
$sel:maxResults:ListItems' :: ListItems -> Maybe Natural
maxResults} -> Maybe Natural
maxResults) (\s :: ListItems
s@ListItems' {} Maybe Natural
a -> ListItems
s {$sel:maxResults:ListItems' :: Maybe Natural
maxResults = Maybe Natural
a} :: ListItems)

-- | The token that identifies which batch of results that you want to see.
-- For example, you submit a @ListItems@ request with @MaxResults@ set at
-- 500. The service returns the first batch of results (up to 500) and a
-- @NextToken@ value. To see the next batch of results, you can submit the
-- @ListItems@ request a second time and specify the @NextToken@ value.
--
-- Tokens expire after 15 minutes.
listItems_nextToken :: Lens.Lens' ListItems (Prelude.Maybe Prelude.Text)
listItems_nextToken :: Lens' ListItems (Maybe Text)
listItems_nextToken = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\ListItems' {Maybe Text
nextToken :: Maybe Text
$sel:nextToken:ListItems' :: ListItems -> Maybe Text
nextToken} -> Maybe Text
nextToken) (\s :: ListItems
s@ListItems' {} Maybe Text
a -> ListItems
s {$sel:nextToken:ListItems' :: Maybe Text
nextToken = Maybe Text
a} :: ListItems)

-- | The path in the container from which to retrieve items. Format: \<folder
-- name>\/\<folder name>\/\<file name>
listItems_path :: Lens.Lens' ListItems (Prelude.Maybe Prelude.Text)
listItems_path :: Lens' ListItems (Maybe Text)
listItems_path = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\ListItems' {Maybe Text
path :: Maybe Text
$sel:path:ListItems' :: ListItems -> Maybe Text
path} -> Maybe Text
path) (\s :: ListItems
s@ListItems' {} Maybe Text
a -> ListItems
s {$sel:path:ListItems' :: Maybe Text
path = Maybe Text
a} :: ListItems)

instance Core.AWSPager ListItems where
  page :: ListItems -> AWSResponse ListItems -> Maybe ListItems
page ListItems
rq AWSResponse ListItems
rs
    | forall a. AWSTruncated a => a -> Bool
Core.stop
        ( AWSResponse ListItems
rs
            forall s a. s -> Getting (First a) s a -> Maybe a
Lens.^? Lens' ListItemsResponse (Maybe Text)
listItemsResponse_nextToken
            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 ListItems
rs
            forall s a. s -> Getting (First a) s a -> Maybe a
Lens.^? Lens' ListItemsResponse (Maybe [Item])
listItemsResponse_items
            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.$ ListItems
rq
          forall a b. a -> (a -> b) -> b
Prelude.& Lens' ListItems (Maybe Text)
listItems_nextToken
          forall s t a b. ASetter s t a b -> b -> s -> t
Lens..~ AWSResponse ListItems
rs
          forall s a. s -> Getting (First a) s a -> Maybe a
Lens.^? Lens' ListItemsResponse (Maybe Text)
listItemsResponse_nextToken
          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 ListItems where
  type AWSResponse ListItems = ListItemsResponse
  request :: (Service -> Service) -> ListItems -> Request ListItems
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 ListItems
-> ClientResponse ClientBody
-> m (Either Error (ClientResponse (AWSResponse ListItems)))
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 [Item] -> Maybe Text -> Int -> ListItemsResponse
ListItemsResponse'
            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
"Items" 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.<*> (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))
      )

instance Prelude.Hashable ListItems where
  hashWithSalt :: Int -> ListItems -> Int
hashWithSalt Int
_salt ListItems' {Maybe Natural
Maybe Text
path :: Maybe Text
nextToken :: Maybe Text
maxResults :: Maybe Natural
$sel:path:ListItems' :: ListItems -> Maybe Text
$sel:nextToken:ListItems' :: ListItems -> Maybe Text
$sel:maxResults:ListItems' :: ListItems -> 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` Maybe Text
path

instance Prelude.NFData ListItems where
  rnf :: ListItems -> ()
rnf ListItems' {Maybe Natural
Maybe Text
path :: Maybe Text
nextToken :: Maybe Text
maxResults :: Maybe Natural
$sel:path:ListItems' :: ListItems -> Maybe Text
$sel:nextToken:ListItems' :: ListItems -> Maybe Text
$sel:maxResults:ListItems' :: ListItems -> 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 Maybe Text
path

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

instance Data.ToPath ListItems where
  toPath :: ListItems -> ByteString
toPath = forall a b. a -> b -> a
Prelude.const ByteString
"/"

instance Data.ToQuery ListItems where
  toQuery :: ListItems -> QueryString
toQuery ListItems' {Maybe Natural
Maybe Text
path :: Maybe Text
nextToken :: Maybe Text
maxResults :: Maybe Natural
$sel:path:ListItems' :: ListItems -> Maybe Text
$sel:nextToken:ListItems' :: ListItems -> Maybe Text
$sel:maxResults:ListItems' :: ListItems -> Maybe Natural
..} =
    forall a. Monoid a => [a] -> a
Prelude.mconcat
      [ ByteString
"MaxResults" forall a. ToQuery a => ByteString -> a -> QueryString
Data.=: Maybe Natural
maxResults,
        ByteString
"NextToken" forall a. ToQuery a => ByteString -> a -> QueryString
Data.=: Maybe Text
nextToken,
        ByteString
"Path" forall a. ToQuery a => ByteString -> a -> QueryString
Data.=: Maybe Text
path
      ]

-- | /See:/ 'newListItemsResponse' smart constructor.
data ListItemsResponse = ListItemsResponse'
  { -- | The metadata entries for the folders and objects at the requested path.
    ListItemsResponse -> Maybe [Item]
items :: Prelude.Maybe [Item],
    -- | The token that can be used in a request to view the next set of results.
    -- For example, you submit a @ListItems@ request that matches 2,000 items
    -- with @MaxResults@ set at 500. The service returns the first batch of
    -- results (up to 500) and a @NextToken@ value that can be used to fetch
    -- the next batch of results.
    ListItemsResponse -> Maybe Text
nextToken :: Prelude.Maybe Prelude.Text,
    -- | The response's http status code.
    ListItemsResponse -> Int
httpStatus :: Prelude.Int
  }
  deriving (ListItemsResponse -> ListItemsResponse -> Bool
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: ListItemsResponse -> ListItemsResponse -> Bool
$c/= :: ListItemsResponse -> ListItemsResponse -> Bool
== :: ListItemsResponse -> ListItemsResponse -> Bool
$c== :: ListItemsResponse -> ListItemsResponse -> Bool
Prelude.Eq, ReadPrec [ListItemsResponse]
ReadPrec ListItemsResponse
Int -> ReadS ListItemsResponse
ReadS [ListItemsResponse]
forall a.
(Int -> ReadS a)
-> ReadS [a] -> ReadPrec a -> ReadPrec [a] -> Read a
readListPrec :: ReadPrec [ListItemsResponse]
$creadListPrec :: ReadPrec [ListItemsResponse]
readPrec :: ReadPrec ListItemsResponse
$creadPrec :: ReadPrec ListItemsResponse
readList :: ReadS [ListItemsResponse]
$creadList :: ReadS [ListItemsResponse]
readsPrec :: Int -> ReadS ListItemsResponse
$creadsPrec :: Int -> ReadS ListItemsResponse
Prelude.Read, Int -> ListItemsResponse -> ShowS
[ListItemsResponse] -> ShowS
ListItemsResponse -> String
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [ListItemsResponse] -> ShowS
$cshowList :: [ListItemsResponse] -> ShowS
show :: ListItemsResponse -> String
$cshow :: ListItemsResponse -> String
showsPrec :: Int -> ListItemsResponse -> ShowS
$cshowsPrec :: Int -> ListItemsResponse -> ShowS
Prelude.Show, forall x. Rep ListItemsResponse x -> ListItemsResponse
forall x. ListItemsResponse -> Rep ListItemsResponse x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cto :: forall x. Rep ListItemsResponse x -> ListItemsResponse
$cfrom :: forall x. ListItemsResponse -> Rep ListItemsResponse x
Prelude.Generic)

-- |
-- Create a value of 'ListItemsResponse' 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:
--
-- 'items', 'listItemsResponse_items' - The metadata entries for the folders and objects at the requested path.
--
-- 'nextToken', 'listItemsResponse_nextToken' - The token that can be used in a request to view the next set of results.
-- For example, you submit a @ListItems@ request that matches 2,000 items
-- with @MaxResults@ set at 500. The service returns the first batch of
-- results (up to 500) and a @NextToken@ value that can be used to fetch
-- the next batch of results.
--
-- 'httpStatus', 'listItemsResponse_httpStatus' - The response's http status code.
newListItemsResponse ::
  -- | 'httpStatus'
  Prelude.Int ->
  ListItemsResponse
newListItemsResponse :: Int -> ListItemsResponse
newListItemsResponse Int
pHttpStatus_ =
  ListItemsResponse'
    { $sel:items:ListItemsResponse' :: Maybe [Item]
items = forall a. Maybe a
Prelude.Nothing,
      $sel:nextToken:ListItemsResponse' :: Maybe Text
nextToken = forall a. Maybe a
Prelude.Nothing,
      $sel:httpStatus:ListItemsResponse' :: Int
httpStatus = Int
pHttpStatus_
    }

-- | The metadata entries for the folders and objects at the requested path.
listItemsResponse_items :: Lens.Lens' ListItemsResponse (Prelude.Maybe [Item])
listItemsResponse_items :: Lens' ListItemsResponse (Maybe [Item])
listItemsResponse_items = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\ListItemsResponse' {Maybe [Item]
items :: Maybe [Item]
$sel:items:ListItemsResponse' :: ListItemsResponse -> Maybe [Item]
items} -> Maybe [Item]
items) (\s :: ListItemsResponse
s@ListItemsResponse' {} Maybe [Item]
a -> ListItemsResponse
s {$sel:items:ListItemsResponse' :: Maybe [Item]
items = Maybe [Item]
a} :: ListItemsResponse) 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 token that can be used in a request to view the next set of results.
-- For example, you submit a @ListItems@ request that matches 2,000 items
-- with @MaxResults@ set at 500. The service returns the first batch of
-- results (up to 500) and a @NextToken@ value that can be used to fetch
-- the next batch of results.
listItemsResponse_nextToken :: Lens.Lens' ListItemsResponse (Prelude.Maybe Prelude.Text)
listItemsResponse_nextToken :: Lens' ListItemsResponse (Maybe Text)
listItemsResponse_nextToken = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\ListItemsResponse' {Maybe Text
nextToken :: Maybe Text
$sel:nextToken:ListItemsResponse' :: ListItemsResponse -> Maybe Text
nextToken} -> Maybe Text
nextToken) (\s :: ListItemsResponse
s@ListItemsResponse' {} Maybe Text
a -> ListItemsResponse
s {$sel:nextToken:ListItemsResponse' :: Maybe Text
nextToken = Maybe Text
a} :: ListItemsResponse)

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

instance Prelude.NFData ListItemsResponse where
  rnf :: ListItemsResponse -> ()
rnf ListItemsResponse' {Int
Maybe [Item]
Maybe Text
httpStatus :: Int
nextToken :: Maybe Text
items :: Maybe [Item]
$sel:httpStatus:ListItemsResponse' :: ListItemsResponse -> Int
$sel:nextToken:ListItemsResponse' :: ListItemsResponse -> Maybe Text
$sel:items:ListItemsResponse' :: ListItemsResponse -> Maybe [Item]
..} =
    forall a. NFData a => a -> ()
Prelude.rnf Maybe [Item]
items
      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 Int
httpStatus