{-# 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.Outposts.ListAssets
-- Copyright   : (c) 2013-2023 Brendan Hay
-- License     : Mozilla Public License, v. 2.0.
-- Maintainer  : Brendan Hay
-- Stability   : auto-generated
-- Portability : non-portable (GHC extensions)
--
-- Lists the hardware assets for the specified Outpost.
--
-- Use filters to return specific results. If you specify multiple filters,
-- the results include only the resources that match all of the specified
-- filters. For a filter where you can specify multiple values, the results
-- include items that match any of the values that you specify for the
-- filter.
module Amazonka.Outposts.ListAssets
  ( -- * Creating a Request
    ListAssets (..),
    newListAssets,

    -- * Request Lenses
    listAssets_hostIdFilter,
    listAssets_maxResults,
    listAssets_nextToken,
    listAssets_statusFilter,
    listAssets_outpostIdentifier,

    -- * Destructuring the Response
    ListAssetsResponse (..),
    newListAssetsResponse,

    -- * Response Lenses
    listAssetsResponse_assets,
    listAssetsResponse_nextToken,
    listAssetsResponse_httpStatus,
  )
where

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

-- | /See:/ 'newListAssets' smart constructor.
data ListAssets = ListAssets'
  { -- | Filters the results by the host ID of a Dedicated Host.
    ListAssets -> Maybe [Text]
hostIdFilter :: Prelude.Maybe [Prelude.Text],
    ListAssets -> Maybe Natural
maxResults :: Prelude.Maybe Prelude.Natural,
    ListAssets -> Maybe Text
nextToken :: Prelude.Maybe Prelude.Text,
    -- | Filters the results by state.
    ListAssets -> Maybe (NonEmpty AssetState)
statusFilter :: Prelude.Maybe (Prelude.NonEmpty AssetState),
    -- | The ID or the Amazon Resource Name (ARN) of the Outpost.
    ListAssets -> Text
outpostIdentifier :: Prelude.Text
  }
  deriving (ListAssets -> ListAssets -> Bool
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: ListAssets -> ListAssets -> Bool
$c/= :: ListAssets -> ListAssets -> Bool
== :: ListAssets -> ListAssets -> Bool
$c== :: ListAssets -> ListAssets -> Bool
Prelude.Eq, ReadPrec [ListAssets]
ReadPrec ListAssets
Int -> ReadS ListAssets
ReadS [ListAssets]
forall a.
(Int -> ReadS a)
-> ReadS [a] -> ReadPrec a -> ReadPrec [a] -> Read a
readListPrec :: ReadPrec [ListAssets]
$creadListPrec :: ReadPrec [ListAssets]
readPrec :: ReadPrec ListAssets
$creadPrec :: ReadPrec ListAssets
readList :: ReadS [ListAssets]
$creadList :: ReadS [ListAssets]
readsPrec :: Int -> ReadS ListAssets
$creadsPrec :: Int -> ReadS ListAssets
Prelude.Read, Int -> ListAssets -> ShowS
[ListAssets] -> ShowS
ListAssets -> String
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [ListAssets] -> ShowS
$cshowList :: [ListAssets] -> ShowS
show :: ListAssets -> String
$cshow :: ListAssets -> String
showsPrec :: Int -> ListAssets -> ShowS
$cshowsPrec :: Int -> ListAssets -> ShowS
Prelude.Show, forall x. Rep ListAssets x -> ListAssets
forall x. ListAssets -> Rep ListAssets x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cto :: forall x. Rep ListAssets x -> ListAssets
$cfrom :: forall x. ListAssets -> Rep ListAssets x
Prelude.Generic)

-- |
-- Create a value of 'ListAssets' 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:
--
-- 'hostIdFilter', 'listAssets_hostIdFilter' - Filters the results by the host ID of a Dedicated Host.
--
-- 'maxResults', 'listAssets_maxResults' - Undocumented member.
--
-- 'nextToken', 'listAssets_nextToken' - Undocumented member.
--
-- 'statusFilter', 'listAssets_statusFilter' - Filters the results by state.
--
-- 'outpostIdentifier', 'listAssets_outpostIdentifier' - The ID or the Amazon Resource Name (ARN) of the Outpost.
newListAssets ::
  -- | 'outpostIdentifier'
  Prelude.Text ->
  ListAssets
newListAssets :: Text -> ListAssets
newListAssets Text
pOutpostIdentifier_ =
  ListAssets'
    { $sel:hostIdFilter:ListAssets' :: Maybe [Text]
hostIdFilter = forall a. Maybe a
Prelude.Nothing,
      $sel:maxResults:ListAssets' :: Maybe Natural
maxResults = forall a. Maybe a
Prelude.Nothing,
      $sel:nextToken:ListAssets' :: Maybe Text
nextToken = forall a. Maybe a
Prelude.Nothing,
      $sel:statusFilter:ListAssets' :: Maybe (NonEmpty AssetState)
statusFilter = forall a. Maybe a
Prelude.Nothing,
      $sel:outpostIdentifier:ListAssets' :: Text
outpostIdentifier = Text
pOutpostIdentifier_
    }

-- | Filters the results by the host ID of a Dedicated Host.
listAssets_hostIdFilter :: Lens.Lens' ListAssets (Prelude.Maybe [Prelude.Text])
listAssets_hostIdFilter :: Lens' ListAssets (Maybe [Text])
listAssets_hostIdFilter = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\ListAssets' {Maybe [Text]
hostIdFilter :: Maybe [Text]
$sel:hostIdFilter:ListAssets' :: ListAssets -> Maybe [Text]
hostIdFilter} -> Maybe [Text]
hostIdFilter) (\s :: ListAssets
s@ListAssets' {} Maybe [Text]
a -> ListAssets
s {$sel:hostIdFilter:ListAssets' :: Maybe [Text]
hostIdFilter = Maybe [Text]
a} :: ListAssets) 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

-- | Undocumented member.
listAssets_maxResults :: Lens.Lens' ListAssets (Prelude.Maybe Prelude.Natural)
listAssets_maxResults :: Lens' ListAssets (Maybe Natural)
listAssets_maxResults = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\ListAssets' {Maybe Natural
maxResults :: Maybe Natural
$sel:maxResults:ListAssets' :: ListAssets -> Maybe Natural
maxResults} -> Maybe Natural
maxResults) (\s :: ListAssets
s@ListAssets' {} Maybe Natural
a -> ListAssets
s {$sel:maxResults:ListAssets' :: Maybe Natural
maxResults = Maybe Natural
a} :: ListAssets)

-- | Undocumented member.
listAssets_nextToken :: Lens.Lens' ListAssets (Prelude.Maybe Prelude.Text)
listAssets_nextToken :: Lens' ListAssets (Maybe Text)
listAssets_nextToken = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\ListAssets' {Maybe Text
nextToken :: Maybe Text
$sel:nextToken:ListAssets' :: ListAssets -> Maybe Text
nextToken} -> Maybe Text
nextToken) (\s :: ListAssets
s@ListAssets' {} Maybe Text
a -> ListAssets
s {$sel:nextToken:ListAssets' :: Maybe Text
nextToken = Maybe Text
a} :: ListAssets)

-- | Filters the results by state.
listAssets_statusFilter :: Lens.Lens' ListAssets (Prelude.Maybe (Prelude.NonEmpty AssetState))
listAssets_statusFilter :: Lens' ListAssets (Maybe (NonEmpty AssetState))
listAssets_statusFilter = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\ListAssets' {Maybe (NonEmpty AssetState)
statusFilter :: Maybe (NonEmpty AssetState)
$sel:statusFilter:ListAssets' :: ListAssets -> Maybe (NonEmpty AssetState)
statusFilter} -> Maybe (NonEmpty AssetState)
statusFilter) (\s :: ListAssets
s@ListAssets' {} Maybe (NonEmpty AssetState)
a -> ListAssets
s {$sel:statusFilter:ListAssets' :: Maybe (NonEmpty AssetState)
statusFilter = Maybe (NonEmpty AssetState)
a} :: ListAssets) 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 ID or the Amazon Resource Name (ARN) of the Outpost.
listAssets_outpostIdentifier :: Lens.Lens' ListAssets Prelude.Text
listAssets_outpostIdentifier :: Lens' ListAssets Text
listAssets_outpostIdentifier = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\ListAssets' {Text
outpostIdentifier :: Text
$sel:outpostIdentifier:ListAssets' :: ListAssets -> Text
outpostIdentifier} -> Text
outpostIdentifier) (\s :: ListAssets
s@ListAssets' {} Text
a -> ListAssets
s {$sel:outpostIdentifier:ListAssets' :: Text
outpostIdentifier = Text
a} :: ListAssets)

instance Core.AWSRequest ListAssets where
  type AWSResponse ListAssets = ListAssetsResponse
  request :: (Service -> Service) -> ListAssets -> Request ListAssets
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 ListAssets
-> ClientResponse ClientBody
-> m (Either Error (ClientResponse (AWSResponse ListAssets)))
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 [AssetInfo] -> Maybe Text -> Int -> ListAssetsResponse
ListAssetsResponse'
            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
"Assets" 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 ListAssets where
  hashWithSalt :: Int -> ListAssets -> Int
hashWithSalt Int
_salt ListAssets' {Maybe Natural
Maybe [Text]
Maybe (NonEmpty AssetState)
Maybe Text
Text
outpostIdentifier :: Text
statusFilter :: Maybe (NonEmpty AssetState)
nextToken :: Maybe Text
maxResults :: Maybe Natural
hostIdFilter :: Maybe [Text]
$sel:outpostIdentifier:ListAssets' :: ListAssets -> Text
$sel:statusFilter:ListAssets' :: ListAssets -> Maybe (NonEmpty AssetState)
$sel:nextToken:ListAssets' :: ListAssets -> Maybe Text
$sel:maxResults:ListAssets' :: ListAssets -> Maybe Natural
$sel:hostIdFilter:ListAssets' :: ListAssets -> Maybe [Text]
..} =
    Int
_salt
      forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Maybe [Text]
hostIdFilter
      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 (NonEmpty AssetState)
statusFilter
      forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Text
outpostIdentifier

instance Prelude.NFData ListAssets where
  rnf :: ListAssets -> ()
rnf ListAssets' {Maybe Natural
Maybe [Text]
Maybe (NonEmpty AssetState)
Maybe Text
Text
outpostIdentifier :: Text
statusFilter :: Maybe (NonEmpty AssetState)
nextToken :: Maybe Text
maxResults :: Maybe Natural
hostIdFilter :: Maybe [Text]
$sel:outpostIdentifier:ListAssets' :: ListAssets -> Text
$sel:statusFilter:ListAssets' :: ListAssets -> Maybe (NonEmpty AssetState)
$sel:nextToken:ListAssets' :: ListAssets -> Maybe Text
$sel:maxResults:ListAssets' :: ListAssets -> Maybe Natural
$sel:hostIdFilter:ListAssets' :: ListAssets -> Maybe [Text]
..} =
    forall a. NFData a => a -> ()
Prelude.rnf Maybe [Text]
hostIdFilter
      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 (NonEmpty AssetState)
statusFilter
      seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf Text
outpostIdentifier

instance Data.ToHeaders ListAssets where
  toHeaders :: ListAssets -> 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 ListAssets where
  toPath :: ListAssets -> ByteString
toPath ListAssets' {Maybe Natural
Maybe [Text]
Maybe (NonEmpty AssetState)
Maybe Text
Text
outpostIdentifier :: Text
statusFilter :: Maybe (NonEmpty AssetState)
nextToken :: Maybe Text
maxResults :: Maybe Natural
hostIdFilter :: Maybe [Text]
$sel:outpostIdentifier:ListAssets' :: ListAssets -> Text
$sel:statusFilter:ListAssets' :: ListAssets -> Maybe (NonEmpty AssetState)
$sel:nextToken:ListAssets' :: ListAssets -> Maybe Text
$sel:maxResults:ListAssets' :: ListAssets -> Maybe Natural
$sel:hostIdFilter:ListAssets' :: ListAssets -> Maybe [Text]
..} =
    forall a. Monoid a => [a] -> a
Prelude.mconcat
      [ ByteString
"/outposts/",
        forall a. ToByteString a => a -> ByteString
Data.toBS Text
outpostIdentifier,
        ByteString
"/assets"
      ]

instance Data.ToQuery ListAssets where
  toQuery :: ListAssets -> QueryString
toQuery ListAssets' {Maybe Natural
Maybe [Text]
Maybe (NonEmpty AssetState)
Maybe Text
Text
outpostIdentifier :: Text
statusFilter :: Maybe (NonEmpty AssetState)
nextToken :: Maybe Text
maxResults :: Maybe Natural
hostIdFilter :: Maybe [Text]
$sel:outpostIdentifier:ListAssets' :: ListAssets -> Text
$sel:statusFilter:ListAssets' :: ListAssets -> Maybe (NonEmpty AssetState)
$sel:nextToken:ListAssets' :: ListAssets -> Maybe Text
$sel:maxResults:ListAssets' :: ListAssets -> Maybe Natural
$sel:hostIdFilter:ListAssets' :: ListAssets -> Maybe [Text]
..} =
    forall a. Monoid a => [a] -> a
Prelude.mconcat
      [ ByteString
"HostIdFilter"
          forall a. ToQuery a => ByteString -> a -> QueryString
Data.=: forall a. ToQuery a => a -> QueryString
Data.toQuery
            (forall a.
(IsList a, ToQuery (Item a)) =>
ByteString -> a -> QueryString
Data.toQueryList ByteString
"member" forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
Prelude.<$> Maybe [Text]
hostIdFilter),
        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
"StatusFilter"
          forall a. ToQuery a => ByteString -> a -> QueryString
Data.=: forall a. ToQuery a => a -> QueryString
Data.toQuery
            (forall a.
(IsList a, ToQuery (Item a)) =>
ByteString -> a -> QueryString
Data.toQueryList ByteString
"member" forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
Prelude.<$> Maybe (NonEmpty AssetState)
statusFilter)
      ]

-- | /See:/ 'newListAssetsResponse' smart constructor.
data ListAssetsResponse = ListAssetsResponse'
  { -- | Information about the hardware assets.
    ListAssetsResponse -> Maybe [AssetInfo]
assets :: Prelude.Maybe [AssetInfo],
    ListAssetsResponse -> Maybe Text
nextToken :: Prelude.Maybe Prelude.Text,
    -- | The response's http status code.
    ListAssetsResponse -> Int
httpStatus :: Prelude.Int
  }
  deriving (ListAssetsResponse -> ListAssetsResponse -> Bool
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: ListAssetsResponse -> ListAssetsResponse -> Bool
$c/= :: ListAssetsResponse -> ListAssetsResponse -> Bool
== :: ListAssetsResponse -> ListAssetsResponse -> Bool
$c== :: ListAssetsResponse -> ListAssetsResponse -> Bool
Prelude.Eq, ReadPrec [ListAssetsResponse]
ReadPrec ListAssetsResponse
Int -> ReadS ListAssetsResponse
ReadS [ListAssetsResponse]
forall a.
(Int -> ReadS a)
-> ReadS [a] -> ReadPrec a -> ReadPrec [a] -> Read a
readListPrec :: ReadPrec [ListAssetsResponse]
$creadListPrec :: ReadPrec [ListAssetsResponse]
readPrec :: ReadPrec ListAssetsResponse
$creadPrec :: ReadPrec ListAssetsResponse
readList :: ReadS [ListAssetsResponse]
$creadList :: ReadS [ListAssetsResponse]
readsPrec :: Int -> ReadS ListAssetsResponse
$creadsPrec :: Int -> ReadS ListAssetsResponse
Prelude.Read, Int -> ListAssetsResponse -> ShowS
[ListAssetsResponse] -> ShowS
ListAssetsResponse -> String
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [ListAssetsResponse] -> ShowS
$cshowList :: [ListAssetsResponse] -> ShowS
show :: ListAssetsResponse -> String
$cshow :: ListAssetsResponse -> String
showsPrec :: Int -> ListAssetsResponse -> ShowS
$cshowsPrec :: Int -> ListAssetsResponse -> ShowS
Prelude.Show, forall x. Rep ListAssetsResponse x -> ListAssetsResponse
forall x. ListAssetsResponse -> Rep ListAssetsResponse x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cto :: forall x. Rep ListAssetsResponse x -> ListAssetsResponse
$cfrom :: forall x. ListAssetsResponse -> Rep ListAssetsResponse x
Prelude.Generic)

-- |
-- Create a value of 'ListAssetsResponse' 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:
--
-- 'assets', 'listAssetsResponse_assets' - Information about the hardware assets.
--
-- 'nextToken', 'listAssetsResponse_nextToken' - Undocumented member.
--
-- 'httpStatus', 'listAssetsResponse_httpStatus' - The response's http status code.
newListAssetsResponse ::
  -- | 'httpStatus'
  Prelude.Int ->
  ListAssetsResponse
newListAssetsResponse :: Int -> ListAssetsResponse
newListAssetsResponse Int
pHttpStatus_ =
  ListAssetsResponse'
    { $sel:assets:ListAssetsResponse' :: Maybe [AssetInfo]
assets = forall a. Maybe a
Prelude.Nothing,
      $sel:nextToken:ListAssetsResponse' :: Maybe Text
nextToken = forall a. Maybe a
Prelude.Nothing,
      $sel:httpStatus:ListAssetsResponse' :: Int
httpStatus = Int
pHttpStatus_
    }

-- | Information about the hardware assets.
listAssetsResponse_assets :: Lens.Lens' ListAssetsResponse (Prelude.Maybe [AssetInfo])
listAssetsResponse_assets :: Lens' ListAssetsResponse (Maybe [AssetInfo])
listAssetsResponse_assets = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\ListAssetsResponse' {Maybe [AssetInfo]
assets :: Maybe [AssetInfo]
$sel:assets:ListAssetsResponse' :: ListAssetsResponse -> Maybe [AssetInfo]
assets} -> Maybe [AssetInfo]
assets) (\s :: ListAssetsResponse
s@ListAssetsResponse' {} Maybe [AssetInfo]
a -> ListAssetsResponse
s {$sel:assets:ListAssetsResponse' :: Maybe [AssetInfo]
assets = Maybe [AssetInfo]
a} :: ListAssetsResponse) 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

-- | Undocumented member.
listAssetsResponse_nextToken :: Lens.Lens' ListAssetsResponse (Prelude.Maybe Prelude.Text)
listAssetsResponse_nextToken :: Lens' ListAssetsResponse (Maybe Text)
listAssetsResponse_nextToken = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\ListAssetsResponse' {Maybe Text
nextToken :: Maybe Text
$sel:nextToken:ListAssetsResponse' :: ListAssetsResponse -> Maybe Text
nextToken} -> Maybe Text
nextToken) (\s :: ListAssetsResponse
s@ListAssetsResponse' {} Maybe Text
a -> ListAssetsResponse
s {$sel:nextToken:ListAssetsResponse' :: Maybe Text
nextToken = Maybe Text
a} :: ListAssetsResponse)

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

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