{-# 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.Greengrass.ListFunctionDefinitions
-- 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 list of Lambda function definitions.
--
-- This operation returns paginated results.
module Amazonka.Greengrass.ListFunctionDefinitions
  ( -- * Creating a Request
    ListFunctionDefinitions (..),
    newListFunctionDefinitions,

    -- * Request Lenses
    listFunctionDefinitions_maxResults,
    listFunctionDefinitions_nextToken,

    -- * Destructuring the Response
    ListFunctionDefinitionsResponse (..),
    newListFunctionDefinitionsResponse,

    -- * Response Lenses
    listFunctionDefinitionsResponse_definitions,
    listFunctionDefinitionsResponse_nextToken,
    listFunctionDefinitionsResponse_httpStatus,
  )
where

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

-- | /See:/ 'newListFunctionDefinitions' smart constructor.
data ListFunctionDefinitions = ListFunctionDefinitions'
  { -- | The maximum number of results to be returned per request.
    ListFunctionDefinitions -> Maybe Text
maxResults :: Prelude.Maybe Prelude.Text,
    -- | The token for the next set of results, or \'\'null\'\' if there are no
    -- additional results.
    ListFunctionDefinitions -> Maybe Text
nextToken :: Prelude.Maybe Prelude.Text
  }
  deriving (ListFunctionDefinitions -> ListFunctionDefinitions -> Bool
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: ListFunctionDefinitions -> ListFunctionDefinitions -> Bool
$c/= :: ListFunctionDefinitions -> ListFunctionDefinitions -> Bool
== :: ListFunctionDefinitions -> ListFunctionDefinitions -> Bool
$c== :: ListFunctionDefinitions -> ListFunctionDefinitions -> Bool
Prelude.Eq, ReadPrec [ListFunctionDefinitions]
ReadPrec ListFunctionDefinitions
Int -> ReadS ListFunctionDefinitions
ReadS [ListFunctionDefinitions]
forall a.
(Int -> ReadS a)
-> ReadS [a] -> ReadPrec a -> ReadPrec [a] -> Read a
readListPrec :: ReadPrec [ListFunctionDefinitions]
$creadListPrec :: ReadPrec [ListFunctionDefinitions]
readPrec :: ReadPrec ListFunctionDefinitions
$creadPrec :: ReadPrec ListFunctionDefinitions
readList :: ReadS [ListFunctionDefinitions]
$creadList :: ReadS [ListFunctionDefinitions]
readsPrec :: Int -> ReadS ListFunctionDefinitions
$creadsPrec :: Int -> ReadS ListFunctionDefinitions
Prelude.Read, Int -> ListFunctionDefinitions -> ShowS
[ListFunctionDefinitions] -> ShowS
ListFunctionDefinitions -> String
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [ListFunctionDefinitions] -> ShowS
$cshowList :: [ListFunctionDefinitions] -> ShowS
show :: ListFunctionDefinitions -> String
$cshow :: ListFunctionDefinitions -> String
showsPrec :: Int -> ListFunctionDefinitions -> ShowS
$cshowsPrec :: Int -> ListFunctionDefinitions -> ShowS
Prelude.Show, forall x. Rep ListFunctionDefinitions x -> ListFunctionDefinitions
forall x. ListFunctionDefinitions -> Rep ListFunctionDefinitions x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cto :: forall x. Rep ListFunctionDefinitions x -> ListFunctionDefinitions
$cfrom :: forall x. ListFunctionDefinitions -> Rep ListFunctionDefinitions x
Prelude.Generic)

-- |
-- Create a value of 'ListFunctionDefinitions' 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', 'listFunctionDefinitions_maxResults' - The maximum number of results to be returned per request.
--
-- 'nextToken', 'listFunctionDefinitions_nextToken' - The token for the next set of results, or \'\'null\'\' if there are no
-- additional results.
newListFunctionDefinitions ::
  ListFunctionDefinitions
newListFunctionDefinitions :: ListFunctionDefinitions
newListFunctionDefinitions =
  ListFunctionDefinitions'
    { $sel:maxResults:ListFunctionDefinitions' :: Maybe Text
maxResults =
        forall a. Maybe a
Prelude.Nothing,
      $sel:nextToken:ListFunctionDefinitions' :: Maybe Text
nextToken = forall a. Maybe a
Prelude.Nothing
    }

-- | The maximum number of results to be returned per request.
listFunctionDefinitions_maxResults :: Lens.Lens' ListFunctionDefinitions (Prelude.Maybe Prelude.Text)
listFunctionDefinitions_maxResults :: Lens' ListFunctionDefinitions (Maybe Text)
listFunctionDefinitions_maxResults = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\ListFunctionDefinitions' {Maybe Text
maxResults :: Maybe Text
$sel:maxResults:ListFunctionDefinitions' :: ListFunctionDefinitions -> Maybe Text
maxResults} -> Maybe Text
maxResults) (\s :: ListFunctionDefinitions
s@ListFunctionDefinitions' {} Maybe Text
a -> ListFunctionDefinitions
s {$sel:maxResults:ListFunctionDefinitions' :: Maybe Text
maxResults = Maybe Text
a} :: ListFunctionDefinitions)

-- | The token for the next set of results, or \'\'null\'\' if there are no
-- additional results.
listFunctionDefinitions_nextToken :: Lens.Lens' ListFunctionDefinitions (Prelude.Maybe Prelude.Text)
listFunctionDefinitions_nextToken :: Lens' ListFunctionDefinitions (Maybe Text)
listFunctionDefinitions_nextToken = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\ListFunctionDefinitions' {Maybe Text
nextToken :: Maybe Text
$sel:nextToken:ListFunctionDefinitions' :: ListFunctionDefinitions -> Maybe Text
nextToken} -> Maybe Text
nextToken) (\s :: ListFunctionDefinitions
s@ListFunctionDefinitions' {} Maybe Text
a -> ListFunctionDefinitions
s {$sel:nextToken:ListFunctionDefinitions' :: Maybe Text
nextToken = Maybe Text
a} :: ListFunctionDefinitions)

instance Core.AWSPager ListFunctionDefinitions where
  page :: ListFunctionDefinitions
-> AWSResponse ListFunctionDefinitions
-> Maybe ListFunctionDefinitions
page ListFunctionDefinitions
rq AWSResponse ListFunctionDefinitions
rs
    | forall a. AWSTruncated a => a -> Bool
Core.stop
        ( AWSResponse ListFunctionDefinitions
rs
            forall s a. s -> Getting (First a) s a -> Maybe a
Lens.^? Lens' ListFunctionDefinitionsResponse (Maybe Text)
listFunctionDefinitionsResponse_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 ListFunctionDefinitions
rs
            forall s a. s -> Getting (First a) s a -> Maybe a
Lens.^? Lens'
  ListFunctionDefinitionsResponse (Maybe [DefinitionInformation])
listFunctionDefinitionsResponse_definitions
            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.$ ListFunctionDefinitions
rq
          forall a b. a -> (a -> b) -> b
Prelude.& Lens' ListFunctionDefinitions (Maybe Text)
listFunctionDefinitions_nextToken
          forall s t a b. ASetter s t a b -> b -> s -> t
Lens..~ AWSResponse ListFunctionDefinitions
rs
          forall s a. s -> Getting (First a) s a -> Maybe a
Lens.^? Lens' ListFunctionDefinitionsResponse (Maybe Text)
listFunctionDefinitionsResponse_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 ListFunctionDefinitions where
  type
    AWSResponse ListFunctionDefinitions =
      ListFunctionDefinitionsResponse
  request :: (Service -> Service)
-> ListFunctionDefinitions -> Request ListFunctionDefinitions
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 ListFunctionDefinitions
-> ClientResponse ClientBody
-> m (Either
        Error (ClientResponse (AWSResponse ListFunctionDefinitions)))
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 [DefinitionInformation]
-> Maybe Text -> Int -> ListFunctionDefinitionsResponse
ListFunctionDefinitionsResponse'
            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
"Definitions" 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 ListFunctionDefinitions where
  hashWithSalt :: Int -> ListFunctionDefinitions -> Int
hashWithSalt Int
_salt ListFunctionDefinitions' {Maybe Text
nextToken :: Maybe Text
maxResults :: Maybe Text
$sel:nextToken:ListFunctionDefinitions' :: ListFunctionDefinitions -> Maybe Text
$sel:maxResults:ListFunctionDefinitions' :: ListFunctionDefinitions -> Maybe Text
..} =
    Int
_salt
      forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Maybe Text
maxResults
      forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Maybe Text
nextToken

instance Prelude.NFData ListFunctionDefinitions where
  rnf :: ListFunctionDefinitions -> ()
rnf ListFunctionDefinitions' {Maybe Text
nextToken :: Maybe Text
maxResults :: Maybe Text
$sel:nextToken:ListFunctionDefinitions' :: ListFunctionDefinitions -> Maybe Text
$sel:maxResults:ListFunctionDefinitions' :: ListFunctionDefinitions -> Maybe Text
..} =
    forall a. NFData a => a -> ()
Prelude.rnf Maybe Text
maxResults
      seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf Maybe Text
nextToken

instance Data.ToHeaders ListFunctionDefinitions where
  toHeaders :: ListFunctionDefinitions -> 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 ListFunctionDefinitions where
  toPath :: ListFunctionDefinitions -> ByteString
toPath =
    forall a b. a -> b -> a
Prelude.const ByteString
"/greengrass/definition/functions"

instance Data.ToQuery ListFunctionDefinitions where
  toQuery :: ListFunctionDefinitions -> QueryString
toQuery ListFunctionDefinitions' {Maybe Text
nextToken :: Maybe Text
maxResults :: Maybe Text
$sel:nextToken:ListFunctionDefinitions' :: ListFunctionDefinitions -> Maybe Text
$sel:maxResults:ListFunctionDefinitions' :: ListFunctionDefinitions -> Maybe Text
..} =
    forall a. Monoid a => [a] -> a
Prelude.mconcat
      [ ByteString
"MaxResults" forall a. ToQuery a => ByteString -> a -> QueryString
Data.=: Maybe Text
maxResults,
        ByteString
"NextToken" forall a. ToQuery a => ByteString -> a -> QueryString
Data.=: Maybe Text
nextToken
      ]

-- | /See:/ 'newListFunctionDefinitionsResponse' smart constructor.
data ListFunctionDefinitionsResponse = ListFunctionDefinitionsResponse'
  { -- | Information about a definition.
    ListFunctionDefinitionsResponse -> Maybe [DefinitionInformation]
definitions :: Prelude.Maybe [DefinitionInformation],
    -- | The token for the next set of results, or \'\'null\'\' if there are no
    -- additional results.
    ListFunctionDefinitionsResponse -> Maybe Text
nextToken :: Prelude.Maybe Prelude.Text,
    -- | The response's http status code.
    ListFunctionDefinitionsResponse -> Int
httpStatus :: Prelude.Int
  }
  deriving (ListFunctionDefinitionsResponse
-> ListFunctionDefinitionsResponse -> Bool
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: ListFunctionDefinitionsResponse
-> ListFunctionDefinitionsResponse -> Bool
$c/= :: ListFunctionDefinitionsResponse
-> ListFunctionDefinitionsResponse -> Bool
== :: ListFunctionDefinitionsResponse
-> ListFunctionDefinitionsResponse -> Bool
$c== :: ListFunctionDefinitionsResponse
-> ListFunctionDefinitionsResponse -> Bool
Prelude.Eq, ReadPrec [ListFunctionDefinitionsResponse]
ReadPrec ListFunctionDefinitionsResponse
Int -> ReadS ListFunctionDefinitionsResponse
ReadS [ListFunctionDefinitionsResponse]
forall a.
(Int -> ReadS a)
-> ReadS [a] -> ReadPrec a -> ReadPrec [a] -> Read a
readListPrec :: ReadPrec [ListFunctionDefinitionsResponse]
$creadListPrec :: ReadPrec [ListFunctionDefinitionsResponse]
readPrec :: ReadPrec ListFunctionDefinitionsResponse
$creadPrec :: ReadPrec ListFunctionDefinitionsResponse
readList :: ReadS [ListFunctionDefinitionsResponse]
$creadList :: ReadS [ListFunctionDefinitionsResponse]
readsPrec :: Int -> ReadS ListFunctionDefinitionsResponse
$creadsPrec :: Int -> ReadS ListFunctionDefinitionsResponse
Prelude.Read, Int -> ListFunctionDefinitionsResponse -> ShowS
[ListFunctionDefinitionsResponse] -> ShowS
ListFunctionDefinitionsResponse -> String
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [ListFunctionDefinitionsResponse] -> ShowS
$cshowList :: [ListFunctionDefinitionsResponse] -> ShowS
show :: ListFunctionDefinitionsResponse -> String
$cshow :: ListFunctionDefinitionsResponse -> String
showsPrec :: Int -> ListFunctionDefinitionsResponse -> ShowS
$cshowsPrec :: Int -> ListFunctionDefinitionsResponse -> ShowS
Prelude.Show, forall x.
Rep ListFunctionDefinitionsResponse x
-> ListFunctionDefinitionsResponse
forall x.
ListFunctionDefinitionsResponse
-> Rep ListFunctionDefinitionsResponse x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cto :: forall x.
Rep ListFunctionDefinitionsResponse x
-> ListFunctionDefinitionsResponse
$cfrom :: forall x.
ListFunctionDefinitionsResponse
-> Rep ListFunctionDefinitionsResponse x
Prelude.Generic)

-- |
-- Create a value of 'ListFunctionDefinitionsResponse' 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:
--
-- 'definitions', 'listFunctionDefinitionsResponse_definitions' - Information about a definition.
--
-- 'nextToken', 'listFunctionDefinitionsResponse_nextToken' - The token for the next set of results, or \'\'null\'\' if there are no
-- additional results.
--
-- 'httpStatus', 'listFunctionDefinitionsResponse_httpStatus' - The response's http status code.
newListFunctionDefinitionsResponse ::
  -- | 'httpStatus'
  Prelude.Int ->
  ListFunctionDefinitionsResponse
newListFunctionDefinitionsResponse :: Int -> ListFunctionDefinitionsResponse
newListFunctionDefinitionsResponse Int
pHttpStatus_ =
  ListFunctionDefinitionsResponse'
    { $sel:definitions:ListFunctionDefinitionsResponse' :: Maybe [DefinitionInformation]
definitions =
        forall a. Maybe a
Prelude.Nothing,
      $sel:nextToken:ListFunctionDefinitionsResponse' :: Maybe Text
nextToken = forall a. Maybe a
Prelude.Nothing,
      $sel:httpStatus:ListFunctionDefinitionsResponse' :: Int
httpStatus = Int
pHttpStatus_
    }

-- | Information about a definition.
listFunctionDefinitionsResponse_definitions :: Lens.Lens' ListFunctionDefinitionsResponse (Prelude.Maybe [DefinitionInformation])
listFunctionDefinitionsResponse_definitions :: Lens'
  ListFunctionDefinitionsResponse (Maybe [DefinitionInformation])
listFunctionDefinitionsResponse_definitions = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\ListFunctionDefinitionsResponse' {Maybe [DefinitionInformation]
definitions :: Maybe [DefinitionInformation]
$sel:definitions:ListFunctionDefinitionsResponse' :: ListFunctionDefinitionsResponse -> Maybe [DefinitionInformation]
definitions} -> Maybe [DefinitionInformation]
definitions) (\s :: ListFunctionDefinitionsResponse
s@ListFunctionDefinitionsResponse' {} Maybe [DefinitionInformation]
a -> ListFunctionDefinitionsResponse
s {$sel:definitions:ListFunctionDefinitionsResponse' :: Maybe [DefinitionInformation]
definitions = Maybe [DefinitionInformation]
a} :: ListFunctionDefinitionsResponse) 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 token for the next set of results, or \'\'null\'\' if there are no
-- additional results.
listFunctionDefinitionsResponse_nextToken :: Lens.Lens' ListFunctionDefinitionsResponse (Prelude.Maybe Prelude.Text)
listFunctionDefinitionsResponse_nextToken :: Lens' ListFunctionDefinitionsResponse (Maybe Text)
listFunctionDefinitionsResponse_nextToken = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\ListFunctionDefinitionsResponse' {Maybe Text
nextToken :: Maybe Text
$sel:nextToken:ListFunctionDefinitionsResponse' :: ListFunctionDefinitionsResponse -> Maybe Text
nextToken} -> Maybe Text
nextToken) (\s :: ListFunctionDefinitionsResponse
s@ListFunctionDefinitionsResponse' {} Maybe Text
a -> ListFunctionDefinitionsResponse
s {$sel:nextToken:ListFunctionDefinitionsResponse' :: Maybe Text
nextToken = Maybe Text
a} :: ListFunctionDefinitionsResponse)

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

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