{-# 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.IoTSiteWise.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)
--
-- Retrieves a paginated list of asset summaries.
--
-- You can use this operation to do the following:
--
-- -   List assets based on a specific asset model.
--
-- -   List top-level assets.
--
-- You can\'t use this operation to list all assets. To retrieve summaries
-- for all of your assets, use
-- <https://docs.aws.amazon.com/iot-sitewise/latest/APIReference/API_ListAssetModels.html ListAssetModels>
-- to get all of your asset model IDs. Then, use ListAssets to get all
-- assets for each asset model.
--
-- This operation returns paginated results.
module Amazonka.IoTSiteWise.ListAssets
  ( -- * Creating a Request
    ListAssets (..),
    newListAssets,

    -- * Request Lenses
    listAssets_assetModelId,
    listAssets_filter,
    listAssets_maxResults,
    listAssets_nextToken,

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

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

import qualified Amazonka.Core as Core
import qualified Amazonka.Core.Lens.Internal as Lens
import qualified Amazonka.Data as Data
import Amazonka.IoTSiteWise.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'
  { -- | The ID of the asset model by which to filter the list of assets. This
    -- parameter is required if you choose @ALL@ for @filter@.
    ListAssets -> Maybe Text
assetModelId :: Prelude.Maybe Prelude.Text,
    -- | The filter for the requested list of assets. Choose one of the following
    -- options:
    --
    -- -   @ALL@ – The list includes all assets for a given asset model ID. The
    --     @assetModelId@ parameter is required if you filter by @ALL@.
    --
    -- -   @TOP_LEVEL@ – The list includes only top-level assets in the asset
    --     hierarchy tree.
    --
    -- Default: @ALL@
    ListAssets -> Maybe ListAssetsFilter
filter' :: Prelude.Maybe ListAssetsFilter,
    -- | The maximum number of results to return for each paginated request.
    --
    -- Default: 50
    ListAssets -> Maybe Natural
maxResults :: Prelude.Maybe Prelude.Natural,
    -- | The token to be used for the next set of paginated results.
    ListAssets -> Maybe Text
nextToken :: Prelude.Maybe 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:
--
-- 'assetModelId', 'listAssets_assetModelId' - The ID of the asset model by which to filter the list of assets. This
-- parameter is required if you choose @ALL@ for @filter@.
--
-- 'filter'', 'listAssets_filter' - The filter for the requested list of assets. Choose one of the following
-- options:
--
-- -   @ALL@ – The list includes all assets for a given asset model ID. The
--     @assetModelId@ parameter is required if you filter by @ALL@.
--
-- -   @TOP_LEVEL@ – The list includes only top-level assets in the asset
--     hierarchy tree.
--
-- Default: @ALL@
--
-- 'maxResults', 'listAssets_maxResults' - The maximum number of results to return for each paginated request.
--
-- Default: 50
--
-- 'nextToken', 'listAssets_nextToken' - The token to be used for the next set of paginated results.
newListAssets ::
  ListAssets
newListAssets :: ListAssets
newListAssets =
  ListAssets'
    { $sel:assetModelId:ListAssets' :: Maybe Text
assetModelId = forall a. Maybe a
Prelude.Nothing,
      $sel:filter':ListAssets' :: Maybe ListAssetsFilter
filter' = 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
    }

-- | The ID of the asset model by which to filter the list of assets. This
-- parameter is required if you choose @ALL@ for @filter@.
listAssets_assetModelId :: Lens.Lens' ListAssets (Prelude.Maybe Prelude.Text)
listAssets_assetModelId :: Lens' ListAssets (Maybe Text)
listAssets_assetModelId = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\ListAssets' {Maybe Text
assetModelId :: Maybe Text
$sel:assetModelId:ListAssets' :: ListAssets -> Maybe Text
assetModelId} -> Maybe Text
assetModelId) (\s :: ListAssets
s@ListAssets' {} Maybe Text
a -> ListAssets
s {$sel:assetModelId:ListAssets' :: Maybe Text
assetModelId = Maybe Text
a} :: ListAssets)

-- | The filter for the requested list of assets. Choose one of the following
-- options:
--
-- -   @ALL@ – The list includes all assets for a given asset model ID. The
--     @assetModelId@ parameter is required if you filter by @ALL@.
--
-- -   @TOP_LEVEL@ – The list includes only top-level assets in the asset
--     hierarchy tree.
--
-- Default: @ALL@
listAssets_filter :: Lens.Lens' ListAssets (Prelude.Maybe ListAssetsFilter)
listAssets_filter :: Lens' ListAssets (Maybe ListAssetsFilter)
listAssets_filter = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\ListAssets' {Maybe ListAssetsFilter
filter' :: Maybe ListAssetsFilter
$sel:filter':ListAssets' :: ListAssets -> Maybe ListAssetsFilter
filter'} -> Maybe ListAssetsFilter
filter') (\s :: ListAssets
s@ListAssets' {} Maybe ListAssetsFilter
a -> ListAssets
s {$sel:filter':ListAssets' :: Maybe ListAssetsFilter
filter' = Maybe ListAssetsFilter
a} :: ListAssets)

-- | The maximum number of results to return for each paginated request.
--
-- Default: 50
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)

-- | The token to be used for the next set of paginated results.
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)

instance Core.AWSPager ListAssets where
  page :: ListAssets -> AWSResponse ListAssets -> Maybe ListAssets
page ListAssets
rq AWSResponse ListAssets
rs
    | forall a. AWSTruncated a => a -> Bool
Core.stop
        ( AWSResponse ListAssets
rs
            forall s a. s -> Getting (First a) s a -> Maybe a
Lens.^? Lens' ListAssetsResponse (Maybe Text)
listAssetsResponse_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 ListAssets
rs forall s a. s -> Getting a s a -> a
Lens.^. Lens' ListAssetsResponse [AssetSummary]
listAssetsResponse_assetSummaries) =
        forall a. Maybe a
Prelude.Nothing
    | Bool
Prelude.otherwise =
        forall a. a -> Maybe a
Prelude.Just
          forall a b. (a -> b) -> a -> b
Prelude.$ ListAssets
rq
          forall a b. a -> (a -> b) -> b
Prelude.& Lens' ListAssets (Maybe Text)
listAssets_nextToken
          forall s t a b. ASetter s t a b -> b -> s -> t
Lens..~ AWSResponse ListAssets
rs
          forall s a. s -> Getting (First a) s a -> Maybe a
Lens.^? Lens' ListAssetsResponse (Maybe Text)
listAssetsResponse_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 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 Text -> Int -> [AssetSummary] -> 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
"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
"assetSummaries"
                            forall (f :: * -> *) a. Functor f => f (Maybe a) -> a -> f a
Core..!@ forall a. Monoid a => a
Prelude.mempty
                        )
      )

instance Prelude.Hashable ListAssets where
  hashWithSalt :: Int -> ListAssets -> Int
hashWithSalt Int
_salt ListAssets' {Maybe Natural
Maybe Text
Maybe ListAssetsFilter
nextToken :: Maybe Text
maxResults :: Maybe Natural
filter' :: Maybe ListAssetsFilter
assetModelId :: Maybe Text
$sel:nextToken:ListAssets' :: ListAssets -> Maybe Text
$sel:maxResults:ListAssets' :: ListAssets -> Maybe Natural
$sel:filter':ListAssets' :: ListAssets -> Maybe ListAssetsFilter
$sel:assetModelId:ListAssets' :: ListAssets -> Maybe Text
..} =
    Int
_salt
      forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Maybe Text
assetModelId
      forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Maybe ListAssetsFilter
filter'
      forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Maybe Natural
maxResults
      forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Maybe Text
nextToken

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

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 = forall a b. a -> b -> a
Prelude.const ByteString
"/assets"

instance Data.ToQuery ListAssets where
  toQuery :: ListAssets -> QueryString
toQuery ListAssets' {Maybe Natural
Maybe Text
Maybe ListAssetsFilter
nextToken :: Maybe Text
maxResults :: Maybe Natural
filter' :: Maybe ListAssetsFilter
assetModelId :: Maybe Text
$sel:nextToken:ListAssets' :: ListAssets -> Maybe Text
$sel:maxResults:ListAssets' :: ListAssets -> Maybe Natural
$sel:filter':ListAssets' :: ListAssets -> Maybe ListAssetsFilter
$sel:assetModelId:ListAssets' :: ListAssets -> Maybe Text
..} =
    forall a. Monoid a => [a] -> a
Prelude.mconcat
      [ ByteString
"assetModelId" forall a. ToQuery a => ByteString -> a -> QueryString
Data.=: Maybe Text
assetModelId,
        ByteString
"filter" forall a. ToQuery a => ByteString -> a -> QueryString
Data.=: Maybe ListAssetsFilter
filter',
        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
      ]

-- | /See:/ 'newListAssetsResponse' smart constructor.
data ListAssetsResponse = ListAssetsResponse'
  { -- | The token for the next set of results, or null if there are no
    -- additional results.
    ListAssetsResponse -> Maybe Text
nextToken :: Prelude.Maybe Prelude.Text,
    -- | The response's http status code.
    ListAssetsResponse -> Int
httpStatus :: Prelude.Int,
    -- | A list that summarizes each asset.
    ListAssetsResponse -> [AssetSummary]
assetSummaries :: [AssetSummary]
  }
  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:
--
-- 'nextToken', 'listAssetsResponse_nextToken' - The token for the next set of results, or null if there are no
-- additional results.
--
-- 'httpStatus', 'listAssetsResponse_httpStatus' - The response's http status code.
--
-- 'assetSummaries', 'listAssetsResponse_assetSummaries' - A list that summarizes each asset.
newListAssetsResponse ::
  -- | 'httpStatus'
  Prelude.Int ->
  ListAssetsResponse
newListAssetsResponse :: Int -> ListAssetsResponse
newListAssetsResponse Int
pHttpStatus_ =
  ListAssetsResponse'
    { $sel:nextToken:ListAssetsResponse' :: Maybe Text
nextToken = forall a. Maybe a
Prelude.Nothing,
      $sel:httpStatus:ListAssetsResponse' :: Int
httpStatus = Int
pHttpStatus_,
      $sel:assetSummaries:ListAssetsResponse' :: [AssetSummary]
assetSummaries = forall a. Monoid a => a
Prelude.mempty
    }

-- | The token for the next set of results, or null if there are no
-- additional results.
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)

-- | A list that summarizes each asset.
listAssetsResponse_assetSummaries :: Lens.Lens' ListAssetsResponse [AssetSummary]
listAssetsResponse_assetSummaries :: Lens' ListAssetsResponse [AssetSummary]
listAssetsResponse_assetSummaries = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\ListAssetsResponse' {[AssetSummary]
assetSummaries :: [AssetSummary]
$sel:assetSummaries:ListAssetsResponse' :: ListAssetsResponse -> [AssetSummary]
assetSummaries} -> [AssetSummary]
assetSummaries) (\s :: ListAssetsResponse
s@ListAssetsResponse' {} [AssetSummary]
a -> ListAssetsResponse
s {$sel:assetSummaries:ListAssetsResponse' :: [AssetSummary]
assetSummaries = [AssetSummary]
a} :: ListAssetsResponse) 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 ListAssetsResponse where
  rnf :: ListAssetsResponse -> ()
rnf ListAssetsResponse' {Int
[AssetSummary]
Maybe Text
assetSummaries :: [AssetSummary]
httpStatus :: Int
nextToken :: Maybe Text
$sel:assetSummaries:ListAssetsResponse' :: ListAssetsResponse -> [AssetSummary]
$sel:httpStatus:ListAssetsResponse' :: ListAssetsResponse -> Int
$sel:nextToken:ListAssetsResponse' :: ListAssetsResponse -> 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 [AssetSummary]
assetSummaries