{-# 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.Panorama.ListApplicationInstanceNodeInstances
-- 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 application node instances.
module Amazonka.Panorama.ListApplicationInstanceNodeInstances
  ( -- * Creating a Request
    ListApplicationInstanceNodeInstances (..),
    newListApplicationInstanceNodeInstances,

    -- * Request Lenses
    listApplicationInstanceNodeInstances_maxResults,
    listApplicationInstanceNodeInstances_nextToken,
    listApplicationInstanceNodeInstances_applicationInstanceId,

    -- * Destructuring the Response
    ListApplicationInstanceNodeInstancesResponse (..),
    newListApplicationInstanceNodeInstancesResponse,

    -- * Response Lenses
    listApplicationInstanceNodeInstancesResponse_nextToken,
    listApplicationInstanceNodeInstancesResponse_nodeInstances,
    listApplicationInstanceNodeInstancesResponse_httpStatus,
  )
where

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

-- | /See:/ 'newListApplicationInstanceNodeInstances' smart constructor.
data ListApplicationInstanceNodeInstances = ListApplicationInstanceNodeInstances'
  { -- | The maximum number of node instances to return in one page of results.
    ListApplicationInstanceNodeInstances -> Maybe Natural
maxResults :: Prelude.Maybe Prelude.Natural,
    -- | Specify the pagination token from a previous request to retrieve the
    -- next page of results.
    ListApplicationInstanceNodeInstances -> Maybe Text
nextToken :: Prelude.Maybe Prelude.Text,
    -- | The node instances\' application instance ID.
    ListApplicationInstanceNodeInstances -> Text
applicationInstanceId :: Prelude.Text
  }
  deriving (ListApplicationInstanceNodeInstances
-> ListApplicationInstanceNodeInstances -> Bool
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: ListApplicationInstanceNodeInstances
-> ListApplicationInstanceNodeInstances -> Bool
$c/= :: ListApplicationInstanceNodeInstances
-> ListApplicationInstanceNodeInstances -> Bool
== :: ListApplicationInstanceNodeInstances
-> ListApplicationInstanceNodeInstances -> Bool
$c== :: ListApplicationInstanceNodeInstances
-> ListApplicationInstanceNodeInstances -> Bool
Prelude.Eq, ReadPrec [ListApplicationInstanceNodeInstances]
ReadPrec ListApplicationInstanceNodeInstances
Int -> ReadS ListApplicationInstanceNodeInstances
ReadS [ListApplicationInstanceNodeInstances]
forall a.
(Int -> ReadS a)
-> ReadS [a] -> ReadPrec a -> ReadPrec [a] -> Read a
readListPrec :: ReadPrec [ListApplicationInstanceNodeInstances]
$creadListPrec :: ReadPrec [ListApplicationInstanceNodeInstances]
readPrec :: ReadPrec ListApplicationInstanceNodeInstances
$creadPrec :: ReadPrec ListApplicationInstanceNodeInstances
readList :: ReadS [ListApplicationInstanceNodeInstances]
$creadList :: ReadS [ListApplicationInstanceNodeInstances]
readsPrec :: Int -> ReadS ListApplicationInstanceNodeInstances
$creadsPrec :: Int -> ReadS ListApplicationInstanceNodeInstances
Prelude.Read, Int -> ListApplicationInstanceNodeInstances -> ShowS
[ListApplicationInstanceNodeInstances] -> ShowS
ListApplicationInstanceNodeInstances -> String
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [ListApplicationInstanceNodeInstances] -> ShowS
$cshowList :: [ListApplicationInstanceNodeInstances] -> ShowS
show :: ListApplicationInstanceNodeInstances -> String
$cshow :: ListApplicationInstanceNodeInstances -> String
showsPrec :: Int -> ListApplicationInstanceNodeInstances -> ShowS
$cshowsPrec :: Int -> ListApplicationInstanceNodeInstances -> ShowS
Prelude.Show, forall x.
Rep ListApplicationInstanceNodeInstances x
-> ListApplicationInstanceNodeInstances
forall x.
ListApplicationInstanceNodeInstances
-> Rep ListApplicationInstanceNodeInstances x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cto :: forall x.
Rep ListApplicationInstanceNodeInstances x
-> ListApplicationInstanceNodeInstances
$cfrom :: forall x.
ListApplicationInstanceNodeInstances
-> Rep ListApplicationInstanceNodeInstances x
Prelude.Generic)

-- |
-- Create a value of 'ListApplicationInstanceNodeInstances' 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', 'listApplicationInstanceNodeInstances_maxResults' - The maximum number of node instances to return in one page of results.
--
-- 'nextToken', 'listApplicationInstanceNodeInstances_nextToken' - Specify the pagination token from a previous request to retrieve the
-- next page of results.
--
-- 'applicationInstanceId', 'listApplicationInstanceNodeInstances_applicationInstanceId' - The node instances\' application instance ID.
newListApplicationInstanceNodeInstances ::
  -- | 'applicationInstanceId'
  Prelude.Text ->
  ListApplicationInstanceNodeInstances
newListApplicationInstanceNodeInstances :: Text -> ListApplicationInstanceNodeInstances
newListApplicationInstanceNodeInstances
  Text
pApplicationInstanceId_ =
    ListApplicationInstanceNodeInstances'
      { $sel:maxResults:ListApplicationInstanceNodeInstances' :: Maybe Natural
maxResults =
          forall a. Maybe a
Prelude.Nothing,
        $sel:nextToken:ListApplicationInstanceNodeInstances' :: Maybe Text
nextToken = forall a. Maybe a
Prelude.Nothing,
        $sel:applicationInstanceId:ListApplicationInstanceNodeInstances' :: Text
applicationInstanceId =
          Text
pApplicationInstanceId_
      }

-- | The maximum number of node instances to return in one page of results.
listApplicationInstanceNodeInstances_maxResults :: Lens.Lens' ListApplicationInstanceNodeInstances (Prelude.Maybe Prelude.Natural)
listApplicationInstanceNodeInstances_maxResults :: Lens' ListApplicationInstanceNodeInstances (Maybe Natural)
listApplicationInstanceNodeInstances_maxResults = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\ListApplicationInstanceNodeInstances' {Maybe Natural
maxResults :: Maybe Natural
$sel:maxResults:ListApplicationInstanceNodeInstances' :: ListApplicationInstanceNodeInstances -> Maybe Natural
maxResults} -> Maybe Natural
maxResults) (\s :: ListApplicationInstanceNodeInstances
s@ListApplicationInstanceNodeInstances' {} Maybe Natural
a -> ListApplicationInstanceNodeInstances
s {$sel:maxResults:ListApplicationInstanceNodeInstances' :: Maybe Natural
maxResults = Maybe Natural
a} :: ListApplicationInstanceNodeInstances)

-- | Specify the pagination token from a previous request to retrieve the
-- next page of results.
listApplicationInstanceNodeInstances_nextToken :: Lens.Lens' ListApplicationInstanceNodeInstances (Prelude.Maybe Prelude.Text)
listApplicationInstanceNodeInstances_nextToken :: Lens' ListApplicationInstanceNodeInstances (Maybe Text)
listApplicationInstanceNodeInstances_nextToken = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\ListApplicationInstanceNodeInstances' {Maybe Text
nextToken :: Maybe Text
$sel:nextToken:ListApplicationInstanceNodeInstances' :: ListApplicationInstanceNodeInstances -> Maybe Text
nextToken} -> Maybe Text
nextToken) (\s :: ListApplicationInstanceNodeInstances
s@ListApplicationInstanceNodeInstances' {} Maybe Text
a -> ListApplicationInstanceNodeInstances
s {$sel:nextToken:ListApplicationInstanceNodeInstances' :: Maybe Text
nextToken = Maybe Text
a} :: ListApplicationInstanceNodeInstances)

-- | The node instances\' application instance ID.
listApplicationInstanceNodeInstances_applicationInstanceId :: Lens.Lens' ListApplicationInstanceNodeInstances Prelude.Text
listApplicationInstanceNodeInstances_applicationInstanceId :: Lens' ListApplicationInstanceNodeInstances Text
listApplicationInstanceNodeInstances_applicationInstanceId = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\ListApplicationInstanceNodeInstances' {Text
applicationInstanceId :: Text
$sel:applicationInstanceId:ListApplicationInstanceNodeInstances' :: ListApplicationInstanceNodeInstances -> Text
applicationInstanceId} -> Text
applicationInstanceId) (\s :: ListApplicationInstanceNodeInstances
s@ListApplicationInstanceNodeInstances' {} Text
a -> ListApplicationInstanceNodeInstances
s {$sel:applicationInstanceId:ListApplicationInstanceNodeInstances' :: Text
applicationInstanceId = Text
a} :: ListApplicationInstanceNodeInstances)

instance
  Core.AWSRequest
    ListApplicationInstanceNodeInstances
  where
  type
    AWSResponse ListApplicationInstanceNodeInstances =
      ListApplicationInstanceNodeInstancesResponse
  request :: (Service -> Service)
-> ListApplicationInstanceNodeInstances
-> Request ListApplicationInstanceNodeInstances
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 ListApplicationInstanceNodeInstances
-> ClientResponse ClientBody
-> m (Either
        Error
        (ClientResponse
           (AWSResponse ListApplicationInstanceNodeInstances)))
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 [NodeInstance]
-> Int
-> ListApplicationInstanceNodeInstancesResponse
ListApplicationInstanceNodeInstancesResponse'
            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
"NodeInstances" 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
    ListApplicationInstanceNodeInstances
  where
  hashWithSalt :: Int -> ListApplicationInstanceNodeInstances -> Int
hashWithSalt
    Int
_salt
    ListApplicationInstanceNodeInstances' {Maybe Natural
Maybe Text
Text
applicationInstanceId :: Text
nextToken :: Maybe Text
maxResults :: Maybe Natural
$sel:applicationInstanceId:ListApplicationInstanceNodeInstances' :: ListApplicationInstanceNodeInstances -> Text
$sel:nextToken:ListApplicationInstanceNodeInstances' :: ListApplicationInstanceNodeInstances -> Maybe Text
$sel:maxResults:ListApplicationInstanceNodeInstances' :: ListApplicationInstanceNodeInstances -> 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
applicationInstanceId

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

instance
  Data.ToHeaders
    ListApplicationInstanceNodeInstances
  where
  toHeaders :: ListApplicationInstanceNodeInstances -> 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
    ListApplicationInstanceNodeInstances
  where
  toPath :: ListApplicationInstanceNodeInstances -> ByteString
toPath ListApplicationInstanceNodeInstances' {Maybe Natural
Maybe Text
Text
applicationInstanceId :: Text
nextToken :: Maybe Text
maxResults :: Maybe Natural
$sel:applicationInstanceId:ListApplicationInstanceNodeInstances' :: ListApplicationInstanceNodeInstances -> Text
$sel:nextToken:ListApplicationInstanceNodeInstances' :: ListApplicationInstanceNodeInstances -> Maybe Text
$sel:maxResults:ListApplicationInstanceNodeInstances' :: ListApplicationInstanceNodeInstances -> Maybe Natural
..} =
    forall a. Monoid a => [a] -> a
Prelude.mconcat
      [ ByteString
"/application-instances/",
        forall a. ToByteString a => a -> ByteString
Data.toBS Text
applicationInstanceId,
        ByteString
"/node-instances"
      ]

instance
  Data.ToQuery
    ListApplicationInstanceNodeInstances
  where
  toQuery :: ListApplicationInstanceNodeInstances -> QueryString
toQuery ListApplicationInstanceNodeInstances' {Maybe Natural
Maybe Text
Text
applicationInstanceId :: Text
nextToken :: Maybe Text
maxResults :: Maybe Natural
$sel:applicationInstanceId:ListApplicationInstanceNodeInstances' :: ListApplicationInstanceNodeInstances -> Text
$sel:nextToken:ListApplicationInstanceNodeInstances' :: ListApplicationInstanceNodeInstances -> Maybe Text
$sel:maxResults:ListApplicationInstanceNodeInstances' :: ListApplicationInstanceNodeInstances -> 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
      ]

-- | /See:/ 'newListApplicationInstanceNodeInstancesResponse' smart constructor.
data ListApplicationInstanceNodeInstancesResponse = ListApplicationInstanceNodeInstancesResponse'
  { -- | A pagination token that\'s included if more results are available.
    ListApplicationInstanceNodeInstancesResponse -> Maybe Text
nextToken :: Prelude.Maybe Prelude.Text,
    -- | A list of node instances.
    ListApplicationInstanceNodeInstancesResponse
-> Maybe [NodeInstance]
nodeInstances :: Prelude.Maybe [NodeInstance],
    -- | The response's http status code.
    ListApplicationInstanceNodeInstancesResponse -> Int
httpStatus :: Prelude.Int
  }
  deriving (ListApplicationInstanceNodeInstancesResponse
-> ListApplicationInstanceNodeInstancesResponse -> Bool
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: ListApplicationInstanceNodeInstancesResponse
-> ListApplicationInstanceNodeInstancesResponse -> Bool
$c/= :: ListApplicationInstanceNodeInstancesResponse
-> ListApplicationInstanceNodeInstancesResponse -> Bool
== :: ListApplicationInstanceNodeInstancesResponse
-> ListApplicationInstanceNodeInstancesResponse -> Bool
$c== :: ListApplicationInstanceNodeInstancesResponse
-> ListApplicationInstanceNodeInstancesResponse -> Bool
Prelude.Eq, ReadPrec [ListApplicationInstanceNodeInstancesResponse]
ReadPrec ListApplicationInstanceNodeInstancesResponse
Int -> ReadS ListApplicationInstanceNodeInstancesResponse
ReadS [ListApplicationInstanceNodeInstancesResponse]
forall a.
(Int -> ReadS a)
-> ReadS [a] -> ReadPrec a -> ReadPrec [a] -> Read a
readListPrec :: ReadPrec [ListApplicationInstanceNodeInstancesResponse]
$creadListPrec :: ReadPrec [ListApplicationInstanceNodeInstancesResponse]
readPrec :: ReadPrec ListApplicationInstanceNodeInstancesResponse
$creadPrec :: ReadPrec ListApplicationInstanceNodeInstancesResponse
readList :: ReadS [ListApplicationInstanceNodeInstancesResponse]
$creadList :: ReadS [ListApplicationInstanceNodeInstancesResponse]
readsPrec :: Int -> ReadS ListApplicationInstanceNodeInstancesResponse
$creadsPrec :: Int -> ReadS ListApplicationInstanceNodeInstancesResponse
Prelude.Read, Int -> ListApplicationInstanceNodeInstancesResponse -> ShowS
[ListApplicationInstanceNodeInstancesResponse] -> ShowS
ListApplicationInstanceNodeInstancesResponse -> String
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [ListApplicationInstanceNodeInstancesResponse] -> ShowS
$cshowList :: [ListApplicationInstanceNodeInstancesResponse] -> ShowS
show :: ListApplicationInstanceNodeInstancesResponse -> String
$cshow :: ListApplicationInstanceNodeInstancesResponse -> String
showsPrec :: Int -> ListApplicationInstanceNodeInstancesResponse -> ShowS
$cshowsPrec :: Int -> ListApplicationInstanceNodeInstancesResponse -> ShowS
Prelude.Show, forall x.
Rep ListApplicationInstanceNodeInstancesResponse x
-> ListApplicationInstanceNodeInstancesResponse
forall x.
ListApplicationInstanceNodeInstancesResponse
-> Rep ListApplicationInstanceNodeInstancesResponse x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cto :: forall x.
Rep ListApplicationInstanceNodeInstancesResponse x
-> ListApplicationInstanceNodeInstancesResponse
$cfrom :: forall x.
ListApplicationInstanceNodeInstancesResponse
-> Rep ListApplicationInstanceNodeInstancesResponse x
Prelude.Generic)

-- |
-- Create a value of 'ListApplicationInstanceNodeInstancesResponse' 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', 'listApplicationInstanceNodeInstancesResponse_nextToken' - A pagination token that\'s included if more results are available.
--
-- 'nodeInstances', 'listApplicationInstanceNodeInstancesResponse_nodeInstances' - A list of node instances.
--
-- 'httpStatus', 'listApplicationInstanceNodeInstancesResponse_httpStatus' - The response's http status code.
newListApplicationInstanceNodeInstancesResponse ::
  -- | 'httpStatus'
  Prelude.Int ->
  ListApplicationInstanceNodeInstancesResponse
newListApplicationInstanceNodeInstancesResponse :: Int -> ListApplicationInstanceNodeInstancesResponse
newListApplicationInstanceNodeInstancesResponse
  Int
pHttpStatus_ =
    ListApplicationInstanceNodeInstancesResponse'
      { $sel:nextToken:ListApplicationInstanceNodeInstancesResponse' :: Maybe Text
nextToken =
          forall a. Maybe a
Prelude.Nothing,
        $sel:nodeInstances:ListApplicationInstanceNodeInstancesResponse' :: Maybe [NodeInstance]
nodeInstances =
          forall a. Maybe a
Prelude.Nothing,
        $sel:httpStatus:ListApplicationInstanceNodeInstancesResponse' :: Int
httpStatus = Int
pHttpStatus_
      }

-- | A pagination token that\'s included if more results are available.
listApplicationInstanceNodeInstancesResponse_nextToken :: Lens.Lens' ListApplicationInstanceNodeInstancesResponse (Prelude.Maybe Prelude.Text)
listApplicationInstanceNodeInstancesResponse_nextToken :: Lens' ListApplicationInstanceNodeInstancesResponse (Maybe Text)
listApplicationInstanceNodeInstancesResponse_nextToken = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\ListApplicationInstanceNodeInstancesResponse' {Maybe Text
nextToken :: Maybe Text
$sel:nextToken:ListApplicationInstanceNodeInstancesResponse' :: ListApplicationInstanceNodeInstancesResponse -> Maybe Text
nextToken} -> Maybe Text
nextToken) (\s :: ListApplicationInstanceNodeInstancesResponse
s@ListApplicationInstanceNodeInstancesResponse' {} Maybe Text
a -> ListApplicationInstanceNodeInstancesResponse
s {$sel:nextToken:ListApplicationInstanceNodeInstancesResponse' :: Maybe Text
nextToken = Maybe Text
a} :: ListApplicationInstanceNodeInstancesResponse)

-- | A list of node instances.
listApplicationInstanceNodeInstancesResponse_nodeInstances :: Lens.Lens' ListApplicationInstanceNodeInstancesResponse (Prelude.Maybe [NodeInstance])
listApplicationInstanceNodeInstancesResponse_nodeInstances :: Lens'
  ListApplicationInstanceNodeInstancesResponse (Maybe [NodeInstance])
listApplicationInstanceNodeInstancesResponse_nodeInstances = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\ListApplicationInstanceNodeInstancesResponse' {Maybe [NodeInstance]
nodeInstances :: Maybe [NodeInstance]
$sel:nodeInstances:ListApplicationInstanceNodeInstancesResponse' :: ListApplicationInstanceNodeInstancesResponse
-> Maybe [NodeInstance]
nodeInstances} -> Maybe [NodeInstance]
nodeInstances) (\s :: ListApplicationInstanceNodeInstancesResponse
s@ListApplicationInstanceNodeInstancesResponse' {} Maybe [NodeInstance]
a -> ListApplicationInstanceNodeInstancesResponse
s {$sel:nodeInstances:ListApplicationInstanceNodeInstancesResponse' :: Maybe [NodeInstance]
nodeInstances = Maybe [NodeInstance]
a} :: ListApplicationInstanceNodeInstancesResponse) 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.
listApplicationInstanceNodeInstancesResponse_httpStatus :: Lens.Lens' ListApplicationInstanceNodeInstancesResponse Prelude.Int
listApplicationInstanceNodeInstancesResponse_httpStatus :: Lens' ListApplicationInstanceNodeInstancesResponse Int
listApplicationInstanceNodeInstancesResponse_httpStatus = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\ListApplicationInstanceNodeInstancesResponse' {Int
httpStatus :: Int
$sel:httpStatus:ListApplicationInstanceNodeInstancesResponse' :: ListApplicationInstanceNodeInstancesResponse -> Int
httpStatus} -> Int
httpStatus) (\s :: ListApplicationInstanceNodeInstancesResponse
s@ListApplicationInstanceNodeInstancesResponse' {} Int
a -> ListApplicationInstanceNodeInstancesResponse
s {$sel:httpStatus:ListApplicationInstanceNodeInstancesResponse' :: Int
httpStatus = Int
a} :: ListApplicationInstanceNodeInstancesResponse)

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