{-# 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.Lightsail.GetBlueprints
-- 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 the list of available instance images, or /blueprints/. You can
-- use a blueprint to create a new instance already running a specific
-- operating system, as well as a preinstalled app or development stack.
-- The software each instance is running depends on the blueprint image you
-- choose.
--
-- Use active blueprints when creating new instances. Inactive blueprints
-- are listed to support customers with existing instances and are not
-- necessarily available to create new instances. Blueprints are marked
-- inactive when they become outdated due to operating system updates or
-- new application releases.
--
-- This operation returns paginated results.
module Amazonka.Lightsail.GetBlueprints
  ( -- * Creating a Request
    GetBlueprints (..),
    newGetBlueprints,

    -- * Request Lenses
    getBlueprints_includeInactive,
    getBlueprints_pageToken,

    -- * Destructuring the Response
    GetBlueprintsResponse (..),
    newGetBlueprintsResponse,

    -- * Response Lenses
    getBlueprintsResponse_blueprints,
    getBlueprintsResponse_nextPageToken,
    getBlueprintsResponse_httpStatus,
  )
where

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

-- | /See:/ 'newGetBlueprints' smart constructor.
data GetBlueprints = GetBlueprints'
  { -- | A Boolean value that indicates whether to include inactive (unavailable)
    -- blueprints in the response of your request.
    GetBlueprints -> Maybe Bool
includeInactive :: Prelude.Maybe Prelude.Bool,
    -- | The token to advance to the next page of results from your request.
    --
    -- To get a page token, perform an initial @GetBlueprints@ request. If your
    -- results are paginated, the response will return a next page token that
    -- you can specify as the page token in a subsequent request.
    GetBlueprints -> Maybe Text
pageToken :: Prelude.Maybe Prelude.Text
  }
  deriving (GetBlueprints -> GetBlueprints -> Bool
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: GetBlueprints -> GetBlueprints -> Bool
$c/= :: GetBlueprints -> GetBlueprints -> Bool
== :: GetBlueprints -> GetBlueprints -> Bool
$c== :: GetBlueprints -> GetBlueprints -> Bool
Prelude.Eq, ReadPrec [GetBlueprints]
ReadPrec GetBlueprints
Int -> ReadS GetBlueprints
ReadS [GetBlueprints]
forall a.
(Int -> ReadS a)
-> ReadS [a] -> ReadPrec a -> ReadPrec [a] -> Read a
readListPrec :: ReadPrec [GetBlueprints]
$creadListPrec :: ReadPrec [GetBlueprints]
readPrec :: ReadPrec GetBlueprints
$creadPrec :: ReadPrec GetBlueprints
readList :: ReadS [GetBlueprints]
$creadList :: ReadS [GetBlueprints]
readsPrec :: Int -> ReadS GetBlueprints
$creadsPrec :: Int -> ReadS GetBlueprints
Prelude.Read, Int -> GetBlueprints -> ShowS
[GetBlueprints] -> ShowS
GetBlueprints -> String
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [GetBlueprints] -> ShowS
$cshowList :: [GetBlueprints] -> ShowS
show :: GetBlueprints -> String
$cshow :: GetBlueprints -> String
showsPrec :: Int -> GetBlueprints -> ShowS
$cshowsPrec :: Int -> GetBlueprints -> ShowS
Prelude.Show, forall x. Rep GetBlueprints x -> GetBlueprints
forall x. GetBlueprints -> Rep GetBlueprints x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cto :: forall x. Rep GetBlueprints x -> GetBlueprints
$cfrom :: forall x. GetBlueprints -> Rep GetBlueprints x
Prelude.Generic)

-- |
-- Create a value of 'GetBlueprints' 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:
--
-- 'includeInactive', 'getBlueprints_includeInactive' - A Boolean value that indicates whether to include inactive (unavailable)
-- blueprints in the response of your request.
--
-- 'pageToken', 'getBlueprints_pageToken' - The token to advance to the next page of results from your request.
--
-- To get a page token, perform an initial @GetBlueprints@ request. If your
-- results are paginated, the response will return a next page token that
-- you can specify as the page token in a subsequent request.
newGetBlueprints ::
  GetBlueprints
newGetBlueprints :: GetBlueprints
newGetBlueprints =
  GetBlueprints'
    { $sel:includeInactive:GetBlueprints' :: Maybe Bool
includeInactive = forall a. Maybe a
Prelude.Nothing,
      $sel:pageToken:GetBlueprints' :: Maybe Text
pageToken = forall a. Maybe a
Prelude.Nothing
    }

-- | A Boolean value that indicates whether to include inactive (unavailable)
-- blueprints in the response of your request.
getBlueprints_includeInactive :: Lens.Lens' GetBlueprints (Prelude.Maybe Prelude.Bool)
getBlueprints_includeInactive :: Lens' GetBlueprints (Maybe Bool)
getBlueprints_includeInactive = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\GetBlueprints' {Maybe Bool
includeInactive :: Maybe Bool
$sel:includeInactive:GetBlueprints' :: GetBlueprints -> Maybe Bool
includeInactive} -> Maybe Bool
includeInactive) (\s :: GetBlueprints
s@GetBlueprints' {} Maybe Bool
a -> GetBlueprints
s {$sel:includeInactive:GetBlueprints' :: Maybe Bool
includeInactive = Maybe Bool
a} :: GetBlueprints)

-- | The token to advance to the next page of results from your request.
--
-- To get a page token, perform an initial @GetBlueprints@ request. If your
-- results are paginated, the response will return a next page token that
-- you can specify as the page token in a subsequent request.
getBlueprints_pageToken :: Lens.Lens' GetBlueprints (Prelude.Maybe Prelude.Text)
getBlueprints_pageToken :: Lens' GetBlueprints (Maybe Text)
getBlueprints_pageToken = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\GetBlueprints' {Maybe Text
pageToken :: Maybe Text
$sel:pageToken:GetBlueprints' :: GetBlueprints -> Maybe Text
pageToken} -> Maybe Text
pageToken) (\s :: GetBlueprints
s@GetBlueprints' {} Maybe Text
a -> GetBlueprints
s {$sel:pageToken:GetBlueprints' :: Maybe Text
pageToken = Maybe Text
a} :: GetBlueprints)

instance Core.AWSPager GetBlueprints where
  page :: GetBlueprints -> AWSResponse GetBlueprints -> Maybe GetBlueprints
page GetBlueprints
rq AWSResponse GetBlueprints
rs
    | forall a. AWSTruncated a => a -> Bool
Core.stop
        ( AWSResponse GetBlueprints
rs
            forall s a. s -> Getting (First a) s a -> Maybe a
Lens.^? Lens' GetBlueprintsResponse (Maybe Text)
getBlueprintsResponse_nextPageToken
            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 GetBlueprints
rs
            forall s a. s -> Getting (First a) s a -> Maybe a
Lens.^? Lens' GetBlueprintsResponse (Maybe [Blueprint])
getBlueprintsResponse_blueprints
            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.$ GetBlueprints
rq
          forall a b. a -> (a -> b) -> b
Prelude.& Lens' GetBlueprints (Maybe Text)
getBlueprints_pageToken
          forall s t a b. ASetter s t a b -> b -> s -> t
Lens..~ AWSResponse GetBlueprints
rs
          forall s a. s -> Getting (First a) s a -> Maybe a
Lens.^? Lens' GetBlueprintsResponse (Maybe Text)
getBlueprintsResponse_nextPageToken
          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 GetBlueprints where
  type
    AWSResponse GetBlueprints =
      GetBlueprintsResponse
  request :: (Service -> Service) -> GetBlueprints -> Request GetBlueprints
request Service -> Service
overrides =
    forall a. (ToRequest a, ToJSON a) => Service -> a -> Request a
Request.postJSON (Service -> Service
overrides Service
defaultService)
  response :: forall (m :: * -> *).
MonadResource m =>
(ByteStringLazy -> IO ByteStringLazy)
-> Service
-> Proxy GetBlueprints
-> ClientResponse ClientBody
-> m (Either Error (ClientResponse (AWSResponse GetBlueprints)))
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 [Blueprint] -> Maybe Text -> Int -> GetBlueprintsResponse
GetBlueprintsResponse'
            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
"blueprints" 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
"nextPageToken")
            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 GetBlueprints where
  hashWithSalt :: Int -> GetBlueprints -> Int
hashWithSalt Int
_salt GetBlueprints' {Maybe Bool
Maybe Text
pageToken :: Maybe Text
includeInactive :: Maybe Bool
$sel:pageToken:GetBlueprints' :: GetBlueprints -> Maybe Text
$sel:includeInactive:GetBlueprints' :: GetBlueprints -> Maybe Bool
..} =
    Int
_salt
      forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Maybe Bool
includeInactive
      forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Maybe Text
pageToken

instance Prelude.NFData GetBlueprints where
  rnf :: GetBlueprints -> ()
rnf GetBlueprints' {Maybe Bool
Maybe Text
pageToken :: Maybe Text
includeInactive :: Maybe Bool
$sel:pageToken:GetBlueprints' :: GetBlueprints -> Maybe Text
$sel:includeInactive:GetBlueprints' :: GetBlueprints -> Maybe Bool
..} =
    forall a. NFData a => a -> ()
Prelude.rnf Maybe Bool
includeInactive
      seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf Maybe Text
pageToken

instance Data.ToHeaders GetBlueprints where
  toHeaders :: GetBlueprints -> ResponseHeaders
toHeaders =
    forall a b. a -> b -> a
Prelude.const
      ( forall a. Monoid a => [a] -> a
Prelude.mconcat
          [ HeaderName
"X-Amz-Target"
              forall a. ToHeader a => HeaderName -> a -> ResponseHeaders
Data.=# ( ByteString
"Lightsail_20161128.GetBlueprints" ::
                          Prelude.ByteString
                      ),
            HeaderName
"Content-Type"
              forall a. ToHeader a => HeaderName -> a -> ResponseHeaders
Data.=# ( ByteString
"application/x-amz-json-1.1" ::
                          Prelude.ByteString
                      )
          ]
      )

instance Data.ToJSON GetBlueprints where
  toJSON :: GetBlueprints -> Value
toJSON GetBlueprints' {Maybe Bool
Maybe Text
pageToken :: Maybe Text
includeInactive :: Maybe Bool
$sel:pageToken:GetBlueprints' :: GetBlueprints -> Maybe Text
$sel:includeInactive:GetBlueprints' :: GetBlueprints -> Maybe Bool
..} =
    [Pair] -> Value
Data.object
      ( forall a. [Maybe a] -> [a]
Prelude.catMaybes
          [ (Key
"includeInactive" forall kv v. (KeyValue kv, ToJSON v) => Key -> v -> kv
Data..=)
              forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
Prelude.<$> Maybe Bool
includeInactive,
            (Key
"pageToken" forall kv v. (KeyValue kv, ToJSON v) => Key -> v -> kv
Data..=) forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
Prelude.<$> Maybe Text
pageToken
          ]
      )

instance Data.ToPath GetBlueprints where
  toPath :: GetBlueprints -> ByteString
toPath = forall a b. a -> b -> a
Prelude.const ByteString
"/"

instance Data.ToQuery GetBlueprints where
  toQuery :: GetBlueprints -> QueryString
toQuery = forall a b. a -> b -> a
Prelude.const forall a. Monoid a => a
Prelude.mempty

-- | /See:/ 'newGetBlueprintsResponse' smart constructor.
data GetBlueprintsResponse = GetBlueprintsResponse'
  { -- | An array of key-value pairs that contains information about the
    -- available blueprints.
    GetBlueprintsResponse -> Maybe [Blueprint]
blueprints :: Prelude.Maybe [Blueprint],
    -- | The token to advance to the next page of results from your request.
    --
    -- A next page token is not returned if there are no more results to
    -- display.
    --
    -- To get the next page of results, perform another @GetBlueprints@ request
    -- and specify the next page token using the @pageToken@ parameter.
    GetBlueprintsResponse -> Maybe Text
nextPageToken :: Prelude.Maybe Prelude.Text,
    -- | The response's http status code.
    GetBlueprintsResponse -> Int
httpStatus :: Prelude.Int
  }
  deriving (GetBlueprintsResponse -> GetBlueprintsResponse -> Bool
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: GetBlueprintsResponse -> GetBlueprintsResponse -> Bool
$c/= :: GetBlueprintsResponse -> GetBlueprintsResponse -> Bool
== :: GetBlueprintsResponse -> GetBlueprintsResponse -> Bool
$c== :: GetBlueprintsResponse -> GetBlueprintsResponse -> Bool
Prelude.Eq, ReadPrec [GetBlueprintsResponse]
ReadPrec GetBlueprintsResponse
Int -> ReadS GetBlueprintsResponse
ReadS [GetBlueprintsResponse]
forall a.
(Int -> ReadS a)
-> ReadS [a] -> ReadPrec a -> ReadPrec [a] -> Read a
readListPrec :: ReadPrec [GetBlueprintsResponse]
$creadListPrec :: ReadPrec [GetBlueprintsResponse]
readPrec :: ReadPrec GetBlueprintsResponse
$creadPrec :: ReadPrec GetBlueprintsResponse
readList :: ReadS [GetBlueprintsResponse]
$creadList :: ReadS [GetBlueprintsResponse]
readsPrec :: Int -> ReadS GetBlueprintsResponse
$creadsPrec :: Int -> ReadS GetBlueprintsResponse
Prelude.Read, Int -> GetBlueprintsResponse -> ShowS
[GetBlueprintsResponse] -> ShowS
GetBlueprintsResponse -> String
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [GetBlueprintsResponse] -> ShowS
$cshowList :: [GetBlueprintsResponse] -> ShowS
show :: GetBlueprintsResponse -> String
$cshow :: GetBlueprintsResponse -> String
showsPrec :: Int -> GetBlueprintsResponse -> ShowS
$cshowsPrec :: Int -> GetBlueprintsResponse -> ShowS
Prelude.Show, forall x. Rep GetBlueprintsResponse x -> GetBlueprintsResponse
forall x. GetBlueprintsResponse -> Rep GetBlueprintsResponse x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cto :: forall x. Rep GetBlueprintsResponse x -> GetBlueprintsResponse
$cfrom :: forall x. GetBlueprintsResponse -> Rep GetBlueprintsResponse x
Prelude.Generic)

-- |
-- Create a value of 'GetBlueprintsResponse' 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:
--
-- 'blueprints', 'getBlueprintsResponse_blueprints' - An array of key-value pairs that contains information about the
-- available blueprints.
--
-- 'nextPageToken', 'getBlueprintsResponse_nextPageToken' - The token to advance to the next page of results from your request.
--
-- A next page token is not returned if there are no more results to
-- display.
--
-- To get the next page of results, perform another @GetBlueprints@ request
-- and specify the next page token using the @pageToken@ parameter.
--
-- 'httpStatus', 'getBlueprintsResponse_httpStatus' - The response's http status code.
newGetBlueprintsResponse ::
  -- | 'httpStatus'
  Prelude.Int ->
  GetBlueprintsResponse
newGetBlueprintsResponse :: Int -> GetBlueprintsResponse
newGetBlueprintsResponse Int
pHttpStatus_ =
  GetBlueprintsResponse'
    { $sel:blueprints:GetBlueprintsResponse' :: Maybe [Blueprint]
blueprints =
        forall a. Maybe a
Prelude.Nothing,
      $sel:nextPageToken:GetBlueprintsResponse' :: Maybe Text
nextPageToken = forall a. Maybe a
Prelude.Nothing,
      $sel:httpStatus:GetBlueprintsResponse' :: Int
httpStatus = Int
pHttpStatus_
    }

-- | An array of key-value pairs that contains information about the
-- available blueprints.
getBlueprintsResponse_blueprints :: Lens.Lens' GetBlueprintsResponse (Prelude.Maybe [Blueprint])
getBlueprintsResponse_blueprints :: Lens' GetBlueprintsResponse (Maybe [Blueprint])
getBlueprintsResponse_blueprints = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\GetBlueprintsResponse' {Maybe [Blueprint]
blueprints :: Maybe [Blueprint]
$sel:blueprints:GetBlueprintsResponse' :: GetBlueprintsResponse -> Maybe [Blueprint]
blueprints} -> Maybe [Blueprint]
blueprints) (\s :: GetBlueprintsResponse
s@GetBlueprintsResponse' {} Maybe [Blueprint]
a -> GetBlueprintsResponse
s {$sel:blueprints:GetBlueprintsResponse' :: Maybe [Blueprint]
blueprints = Maybe [Blueprint]
a} :: GetBlueprintsResponse) 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 to advance to the next page of results from your request.
--
-- A next page token is not returned if there are no more results to
-- display.
--
-- To get the next page of results, perform another @GetBlueprints@ request
-- and specify the next page token using the @pageToken@ parameter.
getBlueprintsResponse_nextPageToken :: Lens.Lens' GetBlueprintsResponse (Prelude.Maybe Prelude.Text)
getBlueprintsResponse_nextPageToken :: Lens' GetBlueprintsResponse (Maybe Text)
getBlueprintsResponse_nextPageToken = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\GetBlueprintsResponse' {Maybe Text
nextPageToken :: Maybe Text
$sel:nextPageToken:GetBlueprintsResponse' :: GetBlueprintsResponse -> Maybe Text
nextPageToken} -> Maybe Text
nextPageToken) (\s :: GetBlueprintsResponse
s@GetBlueprintsResponse' {} Maybe Text
a -> GetBlueprintsResponse
s {$sel:nextPageToken:GetBlueprintsResponse' :: Maybe Text
nextPageToken = Maybe Text
a} :: GetBlueprintsResponse)

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

instance Prelude.NFData GetBlueprintsResponse where
  rnf :: GetBlueprintsResponse -> ()
rnf GetBlueprintsResponse' {Int
Maybe [Blueprint]
Maybe Text
httpStatus :: Int
nextPageToken :: Maybe Text
blueprints :: Maybe [Blueprint]
$sel:httpStatus:GetBlueprintsResponse' :: GetBlueprintsResponse -> Int
$sel:nextPageToken:GetBlueprintsResponse' :: GetBlueprintsResponse -> Maybe Text
$sel:blueprints:GetBlueprintsResponse' :: GetBlueprintsResponse -> Maybe [Blueprint]
..} =
    forall a. NFData a => a -> ()
Prelude.rnf Maybe [Blueprint]
blueprints
      seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf Maybe Text
nextPageToken
      seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf Int
httpStatus