{-# 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.SnowDeviceManagement.ListDeviceResources
-- Copyright   : (c) 2013-2023 Brendan Hay
-- License     : Mozilla Public License, v. 2.0.
-- Maintainer  : Brendan Hay
-- Stability   : auto-generated
-- Portability : non-portable (GHC extensions)
--
-- Returns a list of the Amazon Web Services resources available for a
-- device. Currently, Amazon EC2 instances are the only supported resource
-- type.
--
-- This operation returns paginated results.
module Amazonka.SnowDeviceManagement.ListDeviceResources
  ( -- * Creating a Request
    ListDeviceResources (..),
    newListDeviceResources,

    -- * Request Lenses
    listDeviceResources_maxResults,
    listDeviceResources_nextToken,
    listDeviceResources_type,
    listDeviceResources_managedDeviceId,

    -- * Destructuring the Response
    ListDeviceResourcesResponse (..),
    newListDeviceResourcesResponse,

    -- * Response Lenses
    listDeviceResourcesResponse_nextToken,
    listDeviceResourcesResponse_resources,
    listDeviceResourcesResponse_httpStatus,
  )
where

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

-- | /See:/ 'newListDeviceResources' smart constructor.
data ListDeviceResources = ListDeviceResources'
  { -- | The maximum number of resources per page.
    ListDeviceResources -> Maybe Natural
maxResults :: Prelude.Maybe Prelude.Natural,
    -- | A pagination token to continue to the next page of results.
    ListDeviceResources -> Maybe Text
nextToken :: Prelude.Maybe Prelude.Text,
    -- | A structure used to filter the results by type of resource.
    ListDeviceResources -> Maybe Text
type' :: Prelude.Maybe Prelude.Text,
    -- | The ID of the managed device that you are listing the resources of.
    ListDeviceResources -> Text
managedDeviceId :: Prelude.Text
  }
  deriving (ListDeviceResources -> ListDeviceResources -> Bool
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: ListDeviceResources -> ListDeviceResources -> Bool
$c/= :: ListDeviceResources -> ListDeviceResources -> Bool
== :: ListDeviceResources -> ListDeviceResources -> Bool
$c== :: ListDeviceResources -> ListDeviceResources -> Bool
Prelude.Eq, ReadPrec [ListDeviceResources]
ReadPrec ListDeviceResources
Int -> ReadS ListDeviceResources
ReadS [ListDeviceResources]
forall a.
(Int -> ReadS a)
-> ReadS [a] -> ReadPrec a -> ReadPrec [a] -> Read a
readListPrec :: ReadPrec [ListDeviceResources]
$creadListPrec :: ReadPrec [ListDeviceResources]
readPrec :: ReadPrec ListDeviceResources
$creadPrec :: ReadPrec ListDeviceResources
readList :: ReadS [ListDeviceResources]
$creadList :: ReadS [ListDeviceResources]
readsPrec :: Int -> ReadS ListDeviceResources
$creadsPrec :: Int -> ReadS ListDeviceResources
Prelude.Read, Int -> ListDeviceResources -> ShowS
[ListDeviceResources] -> ShowS
ListDeviceResources -> String
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [ListDeviceResources] -> ShowS
$cshowList :: [ListDeviceResources] -> ShowS
show :: ListDeviceResources -> String
$cshow :: ListDeviceResources -> String
showsPrec :: Int -> ListDeviceResources -> ShowS
$cshowsPrec :: Int -> ListDeviceResources -> ShowS
Prelude.Show, forall x. Rep ListDeviceResources x -> ListDeviceResources
forall x. ListDeviceResources -> Rep ListDeviceResources x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cto :: forall x. Rep ListDeviceResources x -> ListDeviceResources
$cfrom :: forall x. ListDeviceResources -> Rep ListDeviceResources x
Prelude.Generic)

-- |
-- Create a value of 'ListDeviceResources' 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', 'listDeviceResources_maxResults' - The maximum number of resources per page.
--
-- 'nextToken', 'listDeviceResources_nextToken' - A pagination token to continue to the next page of results.
--
-- 'type'', 'listDeviceResources_type' - A structure used to filter the results by type of resource.
--
-- 'managedDeviceId', 'listDeviceResources_managedDeviceId' - The ID of the managed device that you are listing the resources of.
newListDeviceResources ::
  -- | 'managedDeviceId'
  Prelude.Text ->
  ListDeviceResources
newListDeviceResources :: Text -> ListDeviceResources
newListDeviceResources Text
pManagedDeviceId_ =
  ListDeviceResources'
    { $sel:maxResults:ListDeviceResources' :: Maybe Natural
maxResults = forall a. Maybe a
Prelude.Nothing,
      $sel:nextToken:ListDeviceResources' :: Maybe Text
nextToken = forall a. Maybe a
Prelude.Nothing,
      $sel:type':ListDeviceResources' :: Maybe Text
type' = forall a. Maybe a
Prelude.Nothing,
      $sel:managedDeviceId:ListDeviceResources' :: Text
managedDeviceId = Text
pManagedDeviceId_
    }

-- | The maximum number of resources per page.
listDeviceResources_maxResults :: Lens.Lens' ListDeviceResources (Prelude.Maybe Prelude.Natural)
listDeviceResources_maxResults :: Lens' ListDeviceResources (Maybe Natural)
listDeviceResources_maxResults = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\ListDeviceResources' {Maybe Natural
maxResults :: Maybe Natural
$sel:maxResults:ListDeviceResources' :: ListDeviceResources -> Maybe Natural
maxResults} -> Maybe Natural
maxResults) (\s :: ListDeviceResources
s@ListDeviceResources' {} Maybe Natural
a -> ListDeviceResources
s {$sel:maxResults:ListDeviceResources' :: Maybe Natural
maxResults = Maybe Natural
a} :: ListDeviceResources)

-- | A pagination token to continue to the next page of results.
listDeviceResources_nextToken :: Lens.Lens' ListDeviceResources (Prelude.Maybe Prelude.Text)
listDeviceResources_nextToken :: Lens' ListDeviceResources (Maybe Text)
listDeviceResources_nextToken = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\ListDeviceResources' {Maybe Text
nextToken :: Maybe Text
$sel:nextToken:ListDeviceResources' :: ListDeviceResources -> Maybe Text
nextToken} -> Maybe Text
nextToken) (\s :: ListDeviceResources
s@ListDeviceResources' {} Maybe Text
a -> ListDeviceResources
s {$sel:nextToken:ListDeviceResources' :: Maybe Text
nextToken = Maybe Text
a} :: ListDeviceResources)

-- | A structure used to filter the results by type of resource.
listDeviceResources_type :: Lens.Lens' ListDeviceResources (Prelude.Maybe Prelude.Text)
listDeviceResources_type :: Lens' ListDeviceResources (Maybe Text)
listDeviceResources_type = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\ListDeviceResources' {Maybe Text
type' :: Maybe Text
$sel:type':ListDeviceResources' :: ListDeviceResources -> Maybe Text
type'} -> Maybe Text
type') (\s :: ListDeviceResources
s@ListDeviceResources' {} Maybe Text
a -> ListDeviceResources
s {$sel:type':ListDeviceResources' :: Maybe Text
type' = Maybe Text
a} :: ListDeviceResources)

-- | The ID of the managed device that you are listing the resources of.
listDeviceResources_managedDeviceId :: Lens.Lens' ListDeviceResources Prelude.Text
listDeviceResources_managedDeviceId :: Lens' ListDeviceResources Text
listDeviceResources_managedDeviceId = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\ListDeviceResources' {Text
managedDeviceId :: Text
$sel:managedDeviceId:ListDeviceResources' :: ListDeviceResources -> Text
managedDeviceId} -> Text
managedDeviceId) (\s :: ListDeviceResources
s@ListDeviceResources' {} Text
a -> ListDeviceResources
s {$sel:managedDeviceId:ListDeviceResources' :: Text
managedDeviceId = Text
a} :: ListDeviceResources)

instance Core.AWSPager ListDeviceResources where
  page :: ListDeviceResources
-> AWSResponse ListDeviceResources -> Maybe ListDeviceResources
page ListDeviceResources
rq AWSResponse ListDeviceResources
rs
    | forall a. AWSTruncated a => a -> Bool
Core.stop
        ( AWSResponse ListDeviceResources
rs
            forall s a. s -> Getting (First a) s a -> Maybe a
Lens.^? Lens' ListDeviceResourcesResponse (Maybe Text)
listDeviceResourcesResponse_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 ListDeviceResources
rs
            forall s a. s -> Getting (First a) s a -> Maybe a
Lens.^? Lens' ListDeviceResourcesResponse (Maybe [ResourceSummary])
listDeviceResourcesResponse_resources
            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.$ ListDeviceResources
rq
          forall a b. a -> (a -> b) -> b
Prelude.& Lens' ListDeviceResources (Maybe Text)
listDeviceResources_nextToken
          forall s t a b. ASetter s t a b -> b -> s -> t
Lens..~ AWSResponse ListDeviceResources
rs
          forall s a. s -> Getting (First a) s a -> Maybe a
Lens.^? Lens' ListDeviceResourcesResponse (Maybe Text)
listDeviceResourcesResponse_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 ListDeviceResources where
  type
    AWSResponse ListDeviceResources =
      ListDeviceResourcesResponse
  request :: (Service -> Service)
-> ListDeviceResources -> Request ListDeviceResources
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 ListDeviceResources
-> ClientResponse ClientBody
-> m (Either
        Error (ClientResponse (AWSResponse ListDeviceResources)))
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
-> Maybe [ResourceSummary] -> Int -> ListDeviceResourcesResponse
ListDeviceResourcesResponse'
            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.<*> (Object
x forall a. FromJSON a => Object -> Key -> Either String (Maybe a)
Data..?> Key
"resources" 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.<*> (forall (f :: * -> *) a. Applicative f => a -> f a
Prelude.pure (forall a. Enum a => a -> Int
Prelude.fromEnum Int
s))
      )

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

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

instance Data.ToHeaders ListDeviceResources where
  toHeaders :: ListDeviceResources -> 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 ListDeviceResources where
  toPath :: ListDeviceResources -> ByteString
toPath ListDeviceResources' {Maybe Natural
Maybe Text
Text
managedDeviceId :: Text
type' :: Maybe Text
nextToken :: Maybe Text
maxResults :: Maybe Natural
$sel:managedDeviceId:ListDeviceResources' :: ListDeviceResources -> Text
$sel:type':ListDeviceResources' :: ListDeviceResources -> Maybe Text
$sel:nextToken:ListDeviceResources' :: ListDeviceResources -> Maybe Text
$sel:maxResults:ListDeviceResources' :: ListDeviceResources -> Maybe Natural
..} =
    forall a. Monoid a => [a] -> a
Prelude.mconcat
      [ ByteString
"/managed-device/",
        forall a. ToByteString a => a -> ByteString
Data.toBS Text
managedDeviceId,
        ByteString
"/resources"
      ]

instance Data.ToQuery ListDeviceResources where
  toQuery :: ListDeviceResources -> QueryString
toQuery ListDeviceResources' {Maybe Natural
Maybe Text
Text
managedDeviceId :: Text
type' :: Maybe Text
nextToken :: Maybe Text
maxResults :: Maybe Natural
$sel:managedDeviceId:ListDeviceResources' :: ListDeviceResources -> Text
$sel:type':ListDeviceResources' :: ListDeviceResources -> Maybe Text
$sel:nextToken:ListDeviceResources' :: ListDeviceResources -> Maybe Text
$sel:maxResults:ListDeviceResources' :: ListDeviceResources -> 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
"type" forall a. ToQuery a => ByteString -> a -> QueryString
Data.=: Maybe Text
type'
      ]

-- | /See:/ 'newListDeviceResourcesResponse' smart constructor.
data ListDeviceResourcesResponse = ListDeviceResourcesResponse'
  { -- | A pagination token to continue to the next page of results.
    ListDeviceResourcesResponse -> Maybe Text
nextToken :: Prelude.Maybe Prelude.Text,
    -- | A structure defining the resource\'s type, Amazon Resource Name (ARN),
    -- and ID.
    ListDeviceResourcesResponse -> Maybe [ResourceSummary]
resources :: Prelude.Maybe [ResourceSummary],
    -- | The response's http status code.
    ListDeviceResourcesResponse -> Int
httpStatus :: Prelude.Int
  }
  deriving (ListDeviceResourcesResponse -> ListDeviceResourcesResponse -> Bool
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: ListDeviceResourcesResponse -> ListDeviceResourcesResponse -> Bool
$c/= :: ListDeviceResourcesResponse -> ListDeviceResourcesResponse -> Bool
== :: ListDeviceResourcesResponse -> ListDeviceResourcesResponse -> Bool
$c== :: ListDeviceResourcesResponse -> ListDeviceResourcesResponse -> Bool
Prelude.Eq, ReadPrec [ListDeviceResourcesResponse]
ReadPrec ListDeviceResourcesResponse
Int -> ReadS ListDeviceResourcesResponse
ReadS [ListDeviceResourcesResponse]
forall a.
(Int -> ReadS a)
-> ReadS [a] -> ReadPrec a -> ReadPrec [a] -> Read a
readListPrec :: ReadPrec [ListDeviceResourcesResponse]
$creadListPrec :: ReadPrec [ListDeviceResourcesResponse]
readPrec :: ReadPrec ListDeviceResourcesResponse
$creadPrec :: ReadPrec ListDeviceResourcesResponse
readList :: ReadS [ListDeviceResourcesResponse]
$creadList :: ReadS [ListDeviceResourcesResponse]
readsPrec :: Int -> ReadS ListDeviceResourcesResponse
$creadsPrec :: Int -> ReadS ListDeviceResourcesResponse
Prelude.Read, Int -> ListDeviceResourcesResponse -> ShowS
[ListDeviceResourcesResponse] -> ShowS
ListDeviceResourcesResponse -> String
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [ListDeviceResourcesResponse] -> ShowS
$cshowList :: [ListDeviceResourcesResponse] -> ShowS
show :: ListDeviceResourcesResponse -> String
$cshow :: ListDeviceResourcesResponse -> String
showsPrec :: Int -> ListDeviceResourcesResponse -> ShowS
$cshowsPrec :: Int -> ListDeviceResourcesResponse -> ShowS
Prelude.Show, forall x.
Rep ListDeviceResourcesResponse x -> ListDeviceResourcesResponse
forall x.
ListDeviceResourcesResponse -> Rep ListDeviceResourcesResponse x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cto :: forall x.
Rep ListDeviceResourcesResponse x -> ListDeviceResourcesResponse
$cfrom :: forall x.
ListDeviceResourcesResponse -> Rep ListDeviceResourcesResponse x
Prelude.Generic)

-- |
-- Create a value of 'ListDeviceResourcesResponse' 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', 'listDeviceResourcesResponse_nextToken' - A pagination token to continue to the next page of results.
--
-- 'resources', 'listDeviceResourcesResponse_resources' - A structure defining the resource\'s type, Amazon Resource Name (ARN),
-- and ID.
--
-- 'httpStatus', 'listDeviceResourcesResponse_httpStatus' - The response's http status code.
newListDeviceResourcesResponse ::
  -- | 'httpStatus'
  Prelude.Int ->
  ListDeviceResourcesResponse
newListDeviceResourcesResponse :: Int -> ListDeviceResourcesResponse
newListDeviceResourcesResponse Int
pHttpStatus_ =
  ListDeviceResourcesResponse'
    { $sel:nextToken:ListDeviceResourcesResponse' :: Maybe Text
nextToken =
        forall a. Maybe a
Prelude.Nothing,
      $sel:resources:ListDeviceResourcesResponse' :: Maybe [ResourceSummary]
resources = forall a. Maybe a
Prelude.Nothing,
      $sel:httpStatus:ListDeviceResourcesResponse' :: Int
httpStatus = Int
pHttpStatus_
    }

-- | A pagination token to continue to the next page of results.
listDeviceResourcesResponse_nextToken :: Lens.Lens' ListDeviceResourcesResponse (Prelude.Maybe Prelude.Text)
listDeviceResourcesResponse_nextToken :: Lens' ListDeviceResourcesResponse (Maybe Text)
listDeviceResourcesResponse_nextToken = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\ListDeviceResourcesResponse' {Maybe Text
nextToken :: Maybe Text
$sel:nextToken:ListDeviceResourcesResponse' :: ListDeviceResourcesResponse -> Maybe Text
nextToken} -> Maybe Text
nextToken) (\s :: ListDeviceResourcesResponse
s@ListDeviceResourcesResponse' {} Maybe Text
a -> ListDeviceResourcesResponse
s {$sel:nextToken:ListDeviceResourcesResponse' :: Maybe Text
nextToken = Maybe Text
a} :: ListDeviceResourcesResponse)

-- | A structure defining the resource\'s type, Amazon Resource Name (ARN),
-- and ID.
listDeviceResourcesResponse_resources :: Lens.Lens' ListDeviceResourcesResponse (Prelude.Maybe [ResourceSummary])
listDeviceResourcesResponse_resources :: Lens' ListDeviceResourcesResponse (Maybe [ResourceSummary])
listDeviceResourcesResponse_resources = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\ListDeviceResourcesResponse' {Maybe [ResourceSummary]
resources :: Maybe [ResourceSummary]
$sel:resources:ListDeviceResourcesResponse' :: ListDeviceResourcesResponse -> Maybe [ResourceSummary]
resources} -> Maybe [ResourceSummary]
resources) (\s :: ListDeviceResourcesResponse
s@ListDeviceResourcesResponse' {} Maybe [ResourceSummary]
a -> ListDeviceResourcesResponse
s {$sel:resources:ListDeviceResourcesResponse' :: Maybe [ResourceSummary]
resources = Maybe [ResourceSummary]
a} :: ListDeviceResourcesResponse) 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 response's http status code.
listDeviceResourcesResponse_httpStatus :: Lens.Lens' ListDeviceResourcesResponse Prelude.Int
listDeviceResourcesResponse_httpStatus :: Lens' ListDeviceResourcesResponse Int
listDeviceResourcesResponse_httpStatus = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\ListDeviceResourcesResponse' {Int
httpStatus :: Int
$sel:httpStatus:ListDeviceResourcesResponse' :: ListDeviceResourcesResponse -> Int
httpStatus} -> Int
httpStatus) (\s :: ListDeviceResourcesResponse
s@ListDeviceResourcesResponse' {} Int
a -> ListDeviceResourcesResponse
s {$sel:httpStatus:ListDeviceResourcesResponse' :: Int
httpStatus = Int
a} :: ListDeviceResourcesResponse)

instance Prelude.NFData ListDeviceResourcesResponse where
  rnf :: ListDeviceResourcesResponse -> ()
rnf ListDeviceResourcesResponse' {Int
Maybe [ResourceSummary]
Maybe Text
httpStatus :: Int
resources :: Maybe [ResourceSummary]
nextToken :: Maybe Text
$sel:httpStatus:ListDeviceResourcesResponse' :: ListDeviceResourcesResponse -> Int
$sel:resources:ListDeviceResourcesResponse' :: ListDeviceResourcesResponse -> Maybe [ResourceSummary]
$sel:nextToken:ListDeviceResourcesResponse' :: ListDeviceResourcesResponse -> 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 Maybe [ResourceSummary]
resources
      seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf Int
httpStatus