{-# 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.ManagedBlockChain.ListNodes
-- 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 information about the nodes within a network.
--
-- Applies to Hyperledger Fabric and Ethereum.
module Amazonka.ManagedBlockChain.ListNodes
  ( -- * Creating a Request
    ListNodes (..),
    newListNodes,

    -- * Request Lenses
    listNodes_maxResults,
    listNodes_memberId,
    listNodes_nextToken,
    listNodes_status,
    listNodes_networkId,

    -- * Destructuring the Response
    ListNodesResponse (..),
    newListNodesResponse,

    -- * Response Lenses
    listNodesResponse_nextToken,
    listNodesResponse_nodes,
    listNodesResponse_httpStatus,
  )
where

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

-- | /See:/ 'newListNodes' smart constructor.
data ListNodes = ListNodes'
  { -- | The maximum number of nodes to list.
    ListNodes -> Maybe Natural
maxResults :: Prelude.Maybe Prelude.Natural,
    -- | The unique identifier of the member who owns the nodes to list.
    --
    -- Applies only to Hyperledger Fabric and is required for Hyperledger
    -- Fabric.
    ListNodes -> Maybe Text
memberId :: Prelude.Maybe Prelude.Text,
    -- | The pagination token that indicates the next set of results to retrieve.
    ListNodes -> Maybe Text
nextToken :: Prelude.Maybe Prelude.Text,
    -- | An optional status specifier. If provided, only nodes currently in this
    -- status are listed.
    ListNodes -> Maybe NodeStatus
status :: Prelude.Maybe NodeStatus,
    -- | The unique identifier of the network for which to list nodes.
    ListNodes -> Text
networkId :: Prelude.Text
  }
  deriving (ListNodes -> ListNodes -> Bool
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: ListNodes -> ListNodes -> Bool
$c/= :: ListNodes -> ListNodes -> Bool
== :: ListNodes -> ListNodes -> Bool
$c== :: ListNodes -> ListNodes -> Bool
Prelude.Eq, ReadPrec [ListNodes]
ReadPrec ListNodes
Int -> ReadS ListNodes
ReadS [ListNodes]
forall a.
(Int -> ReadS a)
-> ReadS [a] -> ReadPrec a -> ReadPrec [a] -> Read a
readListPrec :: ReadPrec [ListNodes]
$creadListPrec :: ReadPrec [ListNodes]
readPrec :: ReadPrec ListNodes
$creadPrec :: ReadPrec ListNodes
readList :: ReadS [ListNodes]
$creadList :: ReadS [ListNodes]
readsPrec :: Int -> ReadS ListNodes
$creadsPrec :: Int -> ReadS ListNodes
Prelude.Read, Int -> ListNodes -> ShowS
[ListNodes] -> ShowS
ListNodes -> String
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [ListNodes] -> ShowS
$cshowList :: [ListNodes] -> ShowS
show :: ListNodes -> String
$cshow :: ListNodes -> String
showsPrec :: Int -> ListNodes -> ShowS
$cshowsPrec :: Int -> ListNodes -> ShowS
Prelude.Show, forall x. Rep ListNodes x -> ListNodes
forall x. ListNodes -> Rep ListNodes x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cto :: forall x. Rep ListNodes x -> ListNodes
$cfrom :: forall x. ListNodes -> Rep ListNodes x
Prelude.Generic)

-- |
-- Create a value of 'ListNodes' 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', 'listNodes_maxResults' - The maximum number of nodes to list.
--
-- 'memberId', 'listNodes_memberId' - The unique identifier of the member who owns the nodes to list.
--
-- Applies only to Hyperledger Fabric and is required for Hyperledger
-- Fabric.
--
-- 'nextToken', 'listNodes_nextToken' - The pagination token that indicates the next set of results to retrieve.
--
-- 'status', 'listNodes_status' - An optional status specifier. If provided, only nodes currently in this
-- status are listed.
--
-- 'networkId', 'listNodes_networkId' - The unique identifier of the network for which to list nodes.
newListNodes ::
  -- | 'networkId'
  Prelude.Text ->
  ListNodes
newListNodes :: Text -> ListNodes
newListNodes Text
pNetworkId_ =
  ListNodes'
    { $sel:maxResults:ListNodes' :: Maybe Natural
maxResults = forall a. Maybe a
Prelude.Nothing,
      $sel:memberId:ListNodes' :: Maybe Text
memberId = forall a. Maybe a
Prelude.Nothing,
      $sel:nextToken:ListNodes' :: Maybe Text
nextToken = forall a. Maybe a
Prelude.Nothing,
      $sel:status:ListNodes' :: Maybe NodeStatus
status = forall a. Maybe a
Prelude.Nothing,
      $sel:networkId:ListNodes' :: Text
networkId = Text
pNetworkId_
    }

-- | The maximum number of nodes to list.
listNodes_maxResults :: Lens.Lens' ListNodes (Prelude.Maybe Prelude.Natural)
listNodes_maxResults :: Lens' ListNodes (Maybe Natural)
listNodes_maxResults = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\ListNodes' {Maybe Natural
maxResults :: Maybe Natural
$sel:maxResults:ListNodes' :: ListNodes -> Maybe Natural
maxResults} -> Maybe Natural
maxResults) (\s :: ListNodes
s@ListNodes' {} Maybe Natural
a -> ListNodes
s {$sel:maxResults:ListNodes' :: Maybe Natural
maxResults = Maybe Natural
a} :: ListNodes)

-- | The unique identifier of the member who owns the nodes to list.
--
-- Applies only to Hyperledger Fabric and is required for Hyperledger
-- Fabric.
listNodes_memberId :: Lens.Lens' ListNodes (Prelude.Maybe Prelude.Text)
listNodes_memberId :: Lens' ListNodes (Maybe Text)
listNodes_memberId = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\ListNodes' {Maybe Text
memberId :: Maybe Text
$sel:memberId:ListNodes' :: ListNodes -> Maybe Text
memberId} -> Maybe Text
memberId) (\s :: ListNodes
s@ListNodes' {} Maybe Text
a -> ListNodes
s {$sel:memberId:ListNodes' :: Maybe Text
memberId = Maybe Text
a} :: ListNodes)

-- | The pagination token that indicates the next set of results to retrieve.
listNodes_nextToken :: Lens.Lens' ListNodes (Prelude.Maybe Prelude.Text)
listNodes_nextToken :: Lens' ListNodes (Maybe Text)
listNodes_nextToken = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\ListNodes' {Maybe Text
nextToken :: Maybe Text
$sel:nextToken:ListNodes' :: ListNodes -> Maybe Text
nextToken} -> Maybe Text
nextToken) (\s :: ListNodes
s@ListNodes' {} Maybe Text
a -> ListNodes
s {$sel:nextToken:ListNodes' :: Maybe Text
nextToken = Maybe Text
a} :: ListNodes)

-- | An optional status specifier. If provided, only nodes currently in this
-- status are listed.
listNodes_status :: Lens.Lens' ListNodes (Prelude.Maybe NodeStatus)
listNodes_status :: Lens' ListNodes (Maybe NodeStatus)
listNodes_status = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\ListNodes' {Maybe NodeStatus
status :: Maybe NodeStatus
$sel:status:ListNodes' :: ListNodes -> Maybe NodeStatus
status} -> Maybe NodeStatus
status) (\s :: ListNodes
s@ListNodes' {} Maybe NodeStatus
a -> ListNodes
s {$sel:status:ListNodes' :: Maybe NodeStatus
status = Maybe NodeStatus
a} :: ListNodes)

-- | The unique identifier of the network for which to list nodes.
listNodes_networkId :: Lens.Lens' ListNodes Prelude.Text
listNodes_networkId :: Lens' ListNodes Text
listNodes_networkId = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\ListNodes' {Text
networkId :: Text
$sel:networkId:ListNodes' :: ListNodes -> Text
networkId} -> Text
networkId) (\s :: ListNodes
s@ListNodes' {} Text
a -> ListNodes
s {$sel:networkId:ListNodes' :: Text
networkId = Text
a} :: ListNodes)

instance Core.AWSRequest ListNodes where
  type AWSResponse ListNodes = ListNodesResponse
  request :: (Service -> Service) -> ListNodes -> Request ListNodes
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 ListNodes
-> ClientResponse ClientBody
-> m (Either Error (ClientResponse (AWSResponse ListNodes)))
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 [NodeSummary] -> Int -> ListNodesResponse
ListNodesResponse'
            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
"Nodes" 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 ListNodes where
  hashWithSalt :: Int -> ListNodes -> Int
hashWithSalt Int
_salt ListNodes' {Maybe Natural
Maybe Text
Maybe NodeStatus
Text
networkId :: Text
status :: Maybe NodeStatus
nextToken :: Maybe Text
memberId :: Maybe Text
maxResults :: Maybe Natural
$sel:networkId:ListNodes' :: ListNodes -> Text
$sel:status:ListNodes' :: ListNodes -> Maybe NodeStatus
$sel:nextToken:ListNodes' :: ListNodes -> Maybe Text
$sel:memberId:ListNodes' :: ListNodes -> Maybe Text
$sel:maxResults:ListNodes' :: ListNodes -> 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
memberId
      forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Maybe Text
nextToken
      forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Maybe NodeStatus
status
      forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Text
networkId

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

instance Data.ToHeaders ListNodes where
  toHeaders :: ListNodes -> 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 ListNodes where
  toPath :: ListNodes -> ByteString
toPath ListNodes' {Maybe Natural
Maybe Text
Maybe NodeStatus
Text
networkId :: Text
status :: Maybe NodeStatus
nextToken :: Maybe Text
memberId :: Maybe Text
maxResults :: Maybe Natural
$sel:networkId:ListNodes' :: ListNodes -> Text
$sel:status:ListNodes' :: ListNodes -> Maybe NodeStatus
$sel:nextToken:ListNodes' :: ListNodes -> Maybe Text
$sel:memberId:ListNodes' :: ListNodes -> Maybe Text
$sel:maxResults:ListNodes' :: ListNodes -> Maybe Natural
..} =
    forall a. Monoid a => [a] -> a
Prelude.mconcat
      [ByteString
"/networks/", forall a. ToByteString a => a -> ByteString
Data.toBS Text
networkId, ByteString
"/nodes"]

instance Data.ToQuery ListNodes where
  toQuery :: ListNodes -> QueryString
toQuery ListNodes' {Maybe Natural
Maybe Text
Maybe NodeStatus
Text
networkId :: Text
status :: Maybe NodeStatus
nextToken :: Maybe Text
memberId :: Maybe Text
maxResults :: Maybe Natural
$sel:networkId:ListNodes' :: ListNodes -> Text
$sel:status:ListNodes' :: ListNodes -> Maybe NodeStatus
$sel:nextToken:ListNodes' :: ListNodes -> Maybe Text
$sel:memberId:ListNodes' :: ListNodes -> Maybe Text
$sel:maxResults:ListNodes' :: ListNodes -> Maybe Natural
..} =
    forall a. Monoid a => [a] -> a
Prelude.mconcat
      [ ByteString
"maxResults" forall a. ToQuery a => ByteString -> a -> QueryString
Data.=: Maybe Natural
maxResults,
        ByteString
"memberId" forall a. ToQuery a => ByteString -> a -> QueryString
Data.=: Maybe Text
memberId,
        ByteString
"nextToken" forall a. ToQuery a => ByteString -> a -> QueryString
Data.=: Maybe Text
nextToken,
        ByteString
"status" forall a. ToQuery a => ByteString -> a -> QueryString
Data.=: Maybe NodeStatus
status
      ]

-- | /See:/ 'newListNodesResponse' smart constructor.
data ListNodesResponse = ListNodesResponse'
  { -- | The pagination token that indicates the next set of results to retrieve.
    ListNodesResponse -> Maybe Text
nextToken :: Prelude.Maybe Prelude.Text,
    -- | An array of @NodeSummary@ objects that contain configuration properties
    -- for each node.
    ListNodesResponse -> Maybe [NodeSummary]
nodes :: Prelude.Maybe [NodeSummary],
    -- | The response's http status code.
    ListNodesResponse -> Int
httpStatus :: Prelude.Int
  }
  deriving (ListNodesResponse -> ListNodesResponse -> Bool
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: ListNodesResponse -> ListNodesResponse -> Bool
$c/= :: ListNodesResponse -> ListNodesResponse -> Bool
== :: ListNodesResponse -> ListNodesResponse -> Bool
$c== :: ListNodesResponse -> ListNodesResponse -> Bool
Prelude.Eq, ReadPrec [ListNodesResponse]
ReadPrec ListNodesResponse
Int -> ReadS ListNodesResponse
ReadS [ListNodesResponse]
forall a.
(Int -> ReadS a)
-> ReadS [a] -> ReadPrec a -> ReadPrec [a] -> Read a
readListPrec :: ReadPrec [ListNodesResponse]
$creadListPrec :: ReadPrec [ListNodesResponse]
readPrec :: ReadPrec ListNodesResponse
$creadPrec :: ReadPrec ListNodesResponse
readList :: ReadS [ListNodesResponse]
$creadList :: ReadS [ListNodesResponse]
readsPrec :: Int -> ReadS ListNodesResponse
$creadsPrec :: Int -> ReadS ListNodesResponse
Prelude.Read, Int -> ListNodesResponse -> ShowS
[ListNodesResponse] -> ShowS
ListNodesResponse -> String
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [ListNodesResponse] -> ShowS
$cshowList :: [ListNodesResponse] -> ShowS
show :: ListNodesResponse -> String
$cshow :: ListNodesResponse -> String
showsPrec :: Int -> ListNodesResponse -> ShowS
$cshowsPrec :: Int -> ListNodesResponse -> ShowS
Prelude.Show, forall x. Rep ListNodesResponse x -> ListNodesResponse
forall x. ListNodesResponse -> Rep ListNodesResponse x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cto :: forall x. Rep ListNodesResponse x -> ListNodesResponse
$cfrom :: forall x. ListNodesResponse -> Rep ListNodesResponse x
Prelude.Generic)

-- |
-- Create a value of 'ListNodesResponse' 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', 'listNodesResponse_nextToken' - The pagination token that indicates the next set of results to retrieve.
--
-- 'nodes', 'listNodesResponse_nodes' - An array of @NodeSummary@ objects that contain configuration properties
-- for each node.
--
-- 'httpStatus', 'listNodesResponse_httpStatus' - The response's http status code.
newListNodesResponse ::
  -- | 'httpStatus'
  Prelude.Int ->
  ListNodesResponse
newListNodesResponse :: Int -> ListNodesResponse
newListNodesResponse Int
pHttpStatus_ =
  ListNodesResponse'
    { $sel:nextToken:ListNodesResponse' :: Maybe Text
nextToken = forall a. Maybe a
Prelude.Nothing,
      $sel:nodes:ListNodesResponse' :: Maybe [NodeSummary]
nodes = forall a. Maybe a
Prelude.Nothing,
      $sel:httpStatus:ListNodesResponse' :: Int
httpStatus = Int
pHttpStatus_
    }

-- | The pagination token that indicates the next set of results to retrieve.
listNodesResponse_nextToken :: Lens.Lens' ListNodesResponse (Prelude.Maybe Prelude.Text)
listNodesResponse_nextToken :: Lens' ListNodesResponse (Maybe Text)
listNodesResponse_nextToken = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\ListNodesResponse' {Maybe Text
nextToken :: Maybe Text
$sel:nextToken:ListNodesResponse' :: ListNodesResponse -> Maybe Text
nextToken} -> Maybe Text
nextToken) (\s :: ListNodesResponse
s@ListNodesResponse' {} Maybe Text
a -> ListNodesResponse
s {$sel:nextToken:ListNodesResponse' :: Maybe Text
nextToken = Maybe Text
a} :: ListNodesResponse)

-- | An array of @NodeSummary@ objects that contain configuration properties
-- for each node.
listNodesResponse_nodes :: Lens.Lens' ListNodesResponse (Prelude.Maybe [NodeSummary])
listNodesResponse_nodes :: Lens' ListNodesResponse (Maybe [NodeSummary])
listNodesResponse_nodes = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\ListNodesResponse' {Maybe [NodeSummary]
nodes :: Maybe [NodeSummary]
$sel:nodes:ListNodesResponse' :: ListNodesResponse -> Maybe [NodeSummary]
nodes} -> Maybe [NodeSummary]
nodes) (\s :: ListNodesResponse
s@ListNodesResponse' {} Maybe [NodeSummary]
a -> ListNodesResponse
s {$sel:nodes:ListNodesResponse' :: Maybe [NodeSummary]
nodes = Maybe [NodeSummary]
a} :: ListNodesResponse) 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.
listNodesResponse_httpStatus :: Lens.Lens' ListNodesResponse Prelude.Int
listNodesResponse_httpStatus :: Lens' ListNodesResponse Int
listNodesResponse_httpStatus = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\ListNodesResponse' {Int
httpStatus :: Int
$sel:httpStatus:ListNodesResponse' :: ListNodesResponse -> Int
httpStatus} -> Int
httpStatus) (\s :: ListNodesResponse
s@ListNodesResponse' {} Int
a -> ListNodesResponse
s {$sel:httpStatus:ListNodesResponse' :: Int
httpStatus = Int
a} :: ListNodesResponse)

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