{-# 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.HoneyCode.QueryTableRows
-- Copyright   : (c) 2013-2023 Brendan Hay
-- License     : Mozilla Public License, v. 2.0.
-- Maintainer  : Brendan Hay
-- Stability   : auto-generated
-- Portability : non-portable (GHC extensions)
--
-- The QueryTableRows API allows you to use a filter formula to query for
-- specific rows in a table.
--
-- This operation returns paginated results.
module Amazonka.HoneyCode.QueryTableRows
  ( -- * Creating a Request
    QueryTableRows (..),
    newQueryTableRows,

    -- * Request Lenses
    queryTableRows_maxResults,
    queryTableRows_nextToken,
    queryTableRows_workbookId,
    queryTableRows_tableId,
    queryTableRows_filterFormula,

    -- * Destructuring the Response
    QueryTableRowsResponse (..),
    newQueryTableRowsResponse,

    -- * Response Lenses
    queryTableRowsResponse_nextToken,
    queryTableRowsResponse_httpStatus,
    queryTableRowsResponse_columnIds,
    queryTableRowsResponse_rows,
    queryTableRowsResponse_workbookCursor,
  )
where

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

-- | /See:/ 'newQueryTableRows' smart constructor.
data QueryTableRows = QueryTableRows'
  { -- | The maximum number of rows to return in each page of the results.
    QueryTableRows -> Maybe Natural
maxResults :: Prelude.Maybe Prelude.Natural,
    -- | This parameter is optional. If a nextToken is not specified, the API
    -- returns the first page of data.
    --
    -- Pagination tokens expire after 1 hour. If you use a token that was
    -- returned more than an hour back, the API will throw ValidationException.
    QueryTableRows -> Maybe Text
nextToken :: Prelude.Maybe Prelude.Text,
    -- | The ID of the workbook whose table rows are being queried.
    --
    -- If a workbook with the specified id could not be found, this API throws
    -- ResourceNotFoundException.
    QueryTableRows -> Text
workbookId :: Prelude.Text,
    -- | The ID of the table whose rows are being queried.
    --
    -- If a table with the specified id could not be found, this API throws
    -- ResourceNotFoundException.
    QueryTableRows -> Text
tableId :: Prelude.Text,
    -- | An object that represents a filter formula along with the id of the
    -- context row under which the filter function needs to evaluate.
    QueryTableRows -> Filter
filterFormula :: Filter
  }
  deriving (QueryTableRows -> QueryTableRows -> Bool
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: QueryTableRows -> QueryTableRows -> Bool
$c/= :: QueryTableRows -> QueryTableRows -> Bool
== :: QueryTableRows -> QueryTableRows -> Bool
$c== :: QueryTableRows -> QueryTableRows -> Bool
Prelude.Eq, Int -> QueryTableRows -> ShowS
[QueryTableRows] -> ShowS
QueryTableRows -> String
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [QueryTableRows] -> ShowS
$cshowList :: [QueryTableRows] -> ShowS
show :: QueryTableRows -> String
$cshow :: QueryTableRows -> String
showsPrec :: Int -> QueryTableRows -> ShowS
$cshowsPrec :: Int -> QueryTableRows -> ShowS
Prelude.Show, forall x. Rep QueryTableRows x -> QueryTableRows
forall x. QueryTableRows -> Rep QueryTableRows x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cto :: forall x. Rep QueryTableRows x -> QueryTableRows
$cfrom :: forall x. QueryTableRows -> Rep QueryTableRows x
Prelude.Generic)

-- |
-- Create a value of 'QueryTableRows' 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', 'queryTableRows_maxResults' - The maximum number of rows to return in each page of the results.
--
-- 'nextToken', 'queryTableRows_nextToken' - This parameter is optional. If a nextToken is not specified, the API
-- returns the first page of data.
--
-- Pagination tokens expire after 1 hour. If you use a token that was
-- returned more than an hour back, the API will throw ValidationException.
--
-- 'workbookId', 'queryTableRows_workbookId' - The ID of the workbook whose table rows are being queried.
--
-- If a workbook with the specified id could not be found, this API throws
-- ResourceNotFoundException.
--
-- 'tableId', 'queryTableRows_tableId' - The ID of the table whose rows are being queried.
--
-- If a table with the specified id could not be found, this API throws
-- ResourceNotFoundException.
--
-- 'filterFormula', 'queryTableRows_filterFormula' - An object that represents a filter formula along with the id of the
-- context row under which the filter function needs to evaluate.
newQueryTableRows ::
  -- | 'workbookId'
  Prelude.Text ->
  -- | 'tableId'
  Prelude.Text ->
  -- | 'filterFormula'
  Filter ->
  QueryTableRows
newQueryTableRows :: Text -> Text -> Filter -> QueryTableRows
newQueryTableRows
  Text
pWorkbookId_
  Text
pTableId_
  Filter
pFilterFormula_ =
    QueryTableRows'
      { $sel:maxResults:QueryTableRows' :: Maybe Natural
maxResults = forall a. Maybe a
Prelude.Nothing,
        $sel:nextToken:QueryTableRows' :: Maybe Text
nextToken = forall a. Maybe a
Prelude.Nothing,
        $sel:workbookId:QueryTableRows' :: Text
workbookId = Text
pWorkbookId_,
        $sel:tableId:QueryTableRows' :: Text
tableId = Text
pTableId_,
        $sel:filterFormula:QueryTableRows' :: Filter
filterFormula = Filter
pFilterFormula_
      }

-- | The maximum number of rows to return in each page of the results.
queryTableRows_maxResults :: Lens.Lens' QueryTableRows (Prelude.Maybe Prelude.Natural)
queryTableRows_maxResults :: Lens' QueryTableRows (Maybe Natural)
queryTableRows_maxResults = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\QueryTableRows' {Maybe Natural
maxResults :: Maybe Natural
$sel:maxResults:QueryTableRows' :: QueryTableRows -> Maybe Natural
maxResults} -> Maybe Natural
maxResults) (\s :: QueryTableRows
s@QueryTableRows' {} Maybe Natural
a -> QueryTableRows
s {$sel:maxResults:QueryTableRows' :: Maybe Natural
maxResults = Maybe Natural
a} :: QueryTableRows)

-- | This parameter is optional. If a nextToken is not specified, the API
-- returns the first page of data.
--
-- Pagination tokens expire after 1 hour. If you use a token that was
-- returned more than an hour back, the API will throw ValidationException.
queryTableRows_nextToken :: Lens.Lens' QueryTableRows (Prelude.Maybe Prelude.Text)
queryTableRows_nextToken :: Lens' QueryTableRows (Maybe Text)
queryTableRows_nextToken = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\QueryTableRows' {Maybe Text
nextToken :: Maybe Text
$sel:nextToken:QueryTableRows' :: QueryTableRows -> Maybe Text
nextToken} -> Maybe Text
nextToken) (\s :: QueryTableRows
s@QueryTableRows' {} Maybe Text
a -> QueryTableRows
s {$sel:nextToken:QueryTableRows' :: Maybe Text
nextToken = Maybe Text
a} :: QueryTableRows)

-- | The ID of the workbook whose table rows are being queried.
--
-- If a workbook with the specified id could not be found, this API throws
-- ResourceNotFoundException.
queryTableRows_workbookId :: Lens.Lens' QueryTableRows Prelude.Text
queryTableRows_workbookId :: Lens' QueryTableRows Text
queryTableRows_workbookId = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\QueryTableRows' {Text
workbookId :: Text
$sel:workbookId:QueryTableRows' :: QueryTableRows -> Text
workbookId} -> Text
workbookId) (\s :: QueryTableRows
s@QueryTableRows' {} Text
a -> QueryTableRows
s {$sel:workbookId:QueryTableRows' :: Text
workbookId = Text
a} :: QueryTableRows)

-- | The ID of the table whose rows are being queried.
--
-- If a table with the specified id could not be found, this API throws
-- ResourceNotFoundException.
queryTableRows_tableId :: Lens.Lens' QueryTableRows Prelude.Text
queryTableRows_tableId :: Lens' QueryTableRows Text
queryTableRows_tableId = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\QueryTableRows' {Text
tableId :: Text
$sel:tableId:QueryTableRows' :: QueryTableRows -> Text
tableId} -> Text
tableId) (\s :: QueryTableRows
s@QueryTableRows' {} Text
a -> QueryTableRows
s {$sel:tableId:QueryTableRows' :: Text
tableId = Text
a} :: QueryTableRows)

-- | An object that represents a filter formula along with the id of the
-- context row under which the filter function needs to evaluate.
queryTableRows_filterFormula :: Lens.Lens' QueryTableRows Filter
queryTableRows_filterFormula :: Lens' QueryTableRows Filter
queryTableRows_filterFormula = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\QueryTableRows' {Filter
filterFormula :: Filter
$sel:filterFormula:QueryTableRows' :: QueryTableRows -> Filter
filterFormula} -> Filter
filterFormula) (\s :: QueryTableRows
s@QueryTableRows' {} Filter
a -> QueryTableRows
s {$sel:filterFormula:QueryTableRows' :: Filter
filterFormula = Filter
a} :: QueryTableRows)

instance Core.AWSPager QueryTableRows where
  page :: QueryTableRows
-> AWSResponse QueryTableRows -> Maybe QueryTableRows
page QueryTableRows
rq AWSResponse QueryTableRows
rs
    | forall a. AWSTruncated a => a -> Bool
Core.stop
        ( AWSResponse QueryTableRows
rs
            forall s a. s -> Getting (First a) s a -> Maybe a
Lens.^? Lens' QueryTableRowsResponse (Maybe Text)
queryTableRowsResponse_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 QueryTableRows
rs forall s a. s -> Getting a s a -> a
Lens.^. Lens' QueryTableRowsResponse [TableRow]
queryTableRowsResponse_rows) =
        forall a. Maybe a
Prelude.Nothing
    | Bool
Prelude.otherwise =
        forall a. a -> Maybe a
Prelude.Just
          forall a b. (a -> b) -> a -> b
Prelude.$ QueryTableRows
rq
          forall a b. a -> (a -> b) -> b
Prelude.& Lens' QueryTableRows (Maybe Text)
queryTableRows_nextToken
          forall s t a b. ASetter s t a b -> b -> s -> t
Lens..~ AWSResponse QueryTableRows
rs
          forall s a. s -> Getting (First a) s a -> Maybe a
Lens.^? Lens' QueryTableRowsResponse (Maybe Text)
queryTableRowsResponse_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 QueryTableRows where
  type
    AWSResponse QueryTableRows =
      QueryTableRowsResponse
  request :: (Service -> Service) -> QueryTableRows -> Request QueryTableRows
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 QueryTableRows
-> ClientResponse ClientBody
-> m (Either Error (ClientResponse (AWSResponse QueryTableRows)))
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
-> Int
-> NonEmpty Text
-> [TableRow]
-> Integer
-> QueryTableRowsResponse
QueryTableRowsResponse'
            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.<*> (forall (f :: * -> *) a. Applicative f => a -> f a
Prelude.pure (forall a. Enum a => a -> Int
Prelude.fromEnum Int
s))
            forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
Prelude.<*> (Object
x forall a. FromJSON a => Object -> Key -> Either String a
Data..:> Key
"columnIds")
            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
"rows" 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 a
Data..:> Key
"workbookCursor")
      )

instance Prelude.Hashable QueryTableRows where
  hashWithSalt :: Int -> QueryTableRows -> Int
hashWithSalt Int
_salt QueryTableRows' {Maybe Natural
Maybe Text
Text
Filter
filterFormula :: Filter
tableId :: Text
workbookId :: Text
nextToken :: Maybe Text
maxResults :: Maybe Natural
$sel:filterFormula:QueryTableRows' :: QueryTableRows -> Filter
$sel:tableId:QueryTableRows' :: QueryTableRows -> Text
$sel:workbookId:QueryTableRows' :: QueryTableRows -> Text
$sel:nextToken:QueryTableRows' :: QueryTableRows -> Maybe Text
$sel:maxResults:QueryTableRows' :: QueryTableRows -> 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
workbookId
      forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Text
tableId
      forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Filter
filterFormula

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

instance Data.ToHeaders QueryTableRows where
  toHeaders :: QueryTableRows -> 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.ToJSON QueryTableRows where
  toJSON :: QueryTableRows -> Value
toJSON QueryTableRows' {Maybe Natural
Maybe Text
Text
Filter
filterFormula :: Filter
tableId :: Text
workbookId :: Text
nextToken :: Maybe Text
maxResults :: Maybe Natural
$sel:filterFormula:QueryTableRows' :: QueryTableRows -> Filter
$sel:tableId:QueryTableRows' :: QueryTableRows -> Text
$sel:workbookId:QueryTableRows' :: QueryTableRows -> Text
$sel:nextToken:QueryTableRows' :: QueryTableRows -> Maybe Text
$sel:maxResults:QueryTableRows' :: QueryTableRows -> Maybe Natural
..} =
    [Pair] -> Value
Data.object
      ( forall a. [Maybe a] -> [a]
Prelude.catMaybes
          [ (Key
"maxResults" 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 Natural
maxResults,
            (Key
"nextToken" 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
nextToken,
            forall a. a -> Maybe a
Prelude.Just
              (Key
"filterFormula" forall kv v. (KeyValue kv, ToJSON v) => Key -> v -> kv
Data..= Filter
filterFormula)
          ]
      )

instance Data.ToPath QueryTableRows where
  toPath :: QueryTableRows -> ByteString
toPath QueryTableRows' {Maybe Natural
Maybe Text
Text
Filter
filterFormula :: Filter
tableId :: Text
workbookId :: Text
nextToken :: Maybe Text
maxResults :: Maybe Natural
$sel:filterFormula:QueryTableRows' :: QueryTableRows -> Filter
$sel:tableId:QueryTableRows' :: QueryTableRows -> Text
$sel:workbookId:QueryTableRows' :: QueryTableRows -> Text
$sel:nextToken:QueryTableRows' :: QueryTableRows -> Maybe Text
$sel:maxResults:QueryTableRows' :: QueryTableRows -> Maybe Natural
..} =
    forall a. Monoid a => [a] -> a
Prelude.mconcat
      [ ByteString
"/workbooks/",
        forall a. ToByteString a => a -> ByteString
Data.toBS Text
workbookId,
        ByteString
"/tables/",
        forall a. ToByteString a => a -> ByteString
Data.toBS Text
tableId,
        ByteString
"/rows/query"
      ]

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

-- | /See:/ 'newQueryTableRowsResponse' smart constructor.
data QueryTableRowsResponse = QueryTableRowsResponse'
  { -- | Provides the pagination token to load the next page if there are more
    -- results matching the request. If a pagination token is not present in
    -- the response, it means that all data matching the request has been
    -- loaded.
    QueryTableRowsResponse -> Maybe Text
nextToken :: Prelude.Maybe Prelude.Text,
    -- | The response's http status code.
    QueryTableRowsResponse -> Int
httpStatus :: Prelude.Int,
    -- | The list of columns in the table whose row data is returned in the
    -- result.
    QueryTableRowsResponse -> NonEmpty Text
columnIds :: Prelude.NonEmpty Prelude.Text,
    -- | The list of rows in the table that match the query filter.
    QueryTableRowsResponse -> [TableRow]
rows :: [TableRow],
    -- | Indicates the cursor of the workbook at which the data returned by this
    -- request is read. Workbook cursor keeps increasing with every update and
    -- the increments are not sequential.
    QueryTableRowsResponse -> Integer
workbookCursor :: Prelude.Integer
  }
  deriving (QueryTableRowsResponse -> QueryTableRowsResponse -> Bool
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: QueryTableRowsResponse -> QueryTableRowsResponse -> Bool
$c/= :: QueryTableRowsResponse -> QueryTableRowsResponse -> Bool
== :: QueryTableRowsResponse -> QueryTableRowsResponse -> Bool
$c== :: QueryTableRowsResponse -> QueryTableRowsResponse -> Bool
Prelude.Eq, Int -> QueryTableRowsResponse -> ShowS
[QueryTableRowsResponse] -> ShowS
QueryTableRowsResponse -> String
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [QueryTableRowsResponse] -> ShowS
$cshowList :: [QueryTableRowsResponse] -> ShowS
show :: QueryTableRowsResponse -> String
$cshow :: QueryTableRowsResponse -> String
showsPrec :: Int -> QueryTableRowsResponse -> ShowS
$cshowsPrec :: Int -> QueryTableRowsResponse -> ShowS
Prelude.Show, forall x. Rep QueryTableRowsResponse x -> QueryTableRowsResponse
forall x. QueryTableRowsResponse -> Rep QueryTableRowsResponse x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cto :: forall x. Rep QueryTableRowsResponse x -> QueryTableRowsResponse
$cfrom :: forall x. QueryTableRowsResponse -> Rep QueryTableRowsResponse x
Prelude.Generic)

-- |
-- Create a value of 'QueryTableRowsResponse' 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', 'queryTableRowsResponse_nextToken' - Provides the pagination token to load the next page if there are more
-- results matching the request. If a pagination token is not present in
-- the response, it means that all data matching the request has been
-- loaded.
--
-- 'httpStatus', 'queryTableRowsResponse_httpStatus' - The response's http status code.
--
-- 'columnIds', 'queryTableRowsResponse_columnIds' - The list of columns in the table whose row data is returned in the
-- result.
--
-- 'rows', 'queryTableRowsResponse_rows' - The list of rows in the table that match the query filter.
--
-- 'workbookCursor', 'queryTableRowsResponse_workbookCursor' - Indicates the cursor of the workbook at which the data returned by this
-- request is read. Workbook cursor keeps increasing with every update and
-- the increments are not sequential.
newQueryTableRowsResponse ::
  -- | 'httpStatus'
  Prelude.Int ->
  -- | 'columnIds'
  Prelude.NonEmpty Prelude.Text ->
  -- | 'workbookCursor'
  Prelude.Integer ->
  QueryTableRowsResponse
newQueryTableRowsResponse :: Int -> NonEmpty Text -> Integer -> QueryTableRowsResponse
newQueryTableRowsResponse
  Int
pHttpStatus_
  NonEmpty Text
pColumnIds_
  Integer
pWorkbookCursor_ =
    QueryTableRowsResponse'
      { $sel:nextToken:QueryTableRowsResponse' :: Maybe Text
nextToken =
          forall a. Maybe a
Prelude.Nothing,
        $sel:httpStatus:QueryTableRowsResponse' :: Int
httpStatus = Int
pHttpStatus_,
        $sel:columnIds:QueryTableRowsResponse' :: NonEmpty Text
columnIds = forall s t a b. (Coercible s a, Coercible t b) => Iso s t a b
Lens.coerced forall t b. AReview t b -> b -> t
Lens.# NonEmpty Text
pColumnIds_,
        $sel:rows:QueryTableRowsResponse' :: [TableRow]
rows = forall a. Monoid a => a
Prelude.mempty,
        $sel:workbookCursor:QueryTableRowsResponse' :: Integer
workbookCursor = Integer
pWorkbookCursor_
      }

-- | Provides the pagination token to load the next page if there are more
-- results matching the request. If a pagination token is not present in
-- the response, it means that all data matching the request has been
-- loaded.
queryTableRowsResponse_nextToken :: Lens.Lens' QueryTableRowsResponse (Prelude.Maybe Prelude.Text)
queryTableRowsResponse_nextToken :: Lens' QueryTableRowsResponse (Maybe Text)
queryTableRowsResponse_nextToken = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\QueryTableRowsResponse' {Maybe Text
nextToken :: Maybe Text
$sel:nextToken:QueryTableRowsResponse' :: QueryTableRowsResponse -> Maybe Text
nextToken} -> Maybe Text
nextToken) (\s :: QueryTableRowsResponse
s@QueryTableRowsResponse' {} Maybe Text
a -> QueryTableRowsResponse
s {$sel:nextToken:QueryTableRowsResponse' :: Maybe Text
nextToken = Maybe Text
a} :: QueryTableRowsResponse)

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

-- | The list of columns in the table whose row data is returned in the
-- result.
queryTableRowsResponse_columnIds :: Lens.Lens' QueryTableRowsResponse (Prelude.NonEmpty Prelude.Text)
queryTableRowsResponse_columnIds :: Lens' QueryTableRowsResponse (NonEmpty Text)
queryTableRowsResponse_columnIds = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\QueryTableRowsResponse' {NonEmpty Text
columnIds :: NonEmpty Text
$sel:columnIds:QueryTableRowsResponse' :: QueryTableRowsResponse -> NonEmpty Text
columnIds} -> NonEmpty Text
columnIds) (\s :: QueryTableRowsResponse
s@QueryTableRowsResponse' {} NonEmpty Text
a -> QueryTableRowsResponse
s {$sel:columnIds:QueryTableRowsResponse' :: NonEmpty Text
columnIds = NonEmpty Text
a} :: QueryTableRowsResponse) forall b c a. (b -> c) -> (a -> b) -> a -> c
Prelude.. forall s t a b. (Coercible s a, Coercible t b) => Iso s t a b
Lens.coerced

-- | The list of rows in the table that match the query filter.
queryTableRowsResponse_rows :: Lens.Lens' QueryTableRowsResponse [TableRow]
queryTableRowsResponse_rows :: Lens' QueryTableRowsResponse [TableRow]
queryTableRowsResponse_rows = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\QueryTableRowsResponse' {[TableRow]
rows :: [TableRow]
$sel:rows:QueryTableRowsResponse' :: QueryTableRowsResponse -> [TableRow]
rows} -> [TableRow]
rows) (\s :: QueryTableRowsResponse
s@QueryTableRowsResponse' {} [TableRow]
a -> QueryTableRowsResponse
s {$sel:rows:QueryTableRowsResponse' :: [TableRow]
rows = [TableRow]
a} :: QueryTableRowsResponse) forall b c a. (b -> c) -> (a -> b) -> a -> c
Prelude.. forall s t a b. (Coercible s a, Coercible t b) => Iso s t a b
Lens.coerced

-- | Indicates the cursor of the workbook at which the data returned by this
-- request is read. Workbook cursor keeps increasing with every update and
-- the increments are not sequential.
queryTableRowsResponse_workbookCursor :: Lens.Lens' QueryTableRowsResponse Prelude.Integer
queryTableRowsResponse_workbookCursor :: Lens' QueryTableRowsResponse Integer
queryTableRowsResponse_workbookCursor = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\QueryTableRowsResponse' {Integer
workbookCursor :: Integer
$sel:workbookCursor:QueryTableRowsResponse' :: QueryTableRowsResponse -> Integer
workbookCursor} -> Integer
workbookCursor) (\s :: QueryTableRowsResponse
s@QueryTableRowsResponse' {} Integer
a -> QueryTableRowsResponse
s {$sel:workbookCursor:QueryTableRowsResponse' :: Integer
workbookCursor = Integer
a} :: QueryTableRowsResponse)

instance Prelude.NFData QueryTableRowsResponse where
  rnf :: QueryTableRowsResponse -> ()
rnf QueryTableRowsResponse' {Int
Integer
[TableRow]
Maybe Text
NonEmpty Text
workbookCursor :: Integer
rows :: [TableRow]
columnIds :: NonEmpty Text
httpStatus :: Int
nextToken :: Maybe Text
$sel:workbookCursor:QueryTableRowsResponse' :: QueryTableRowsResponse -> Integer
$sel:rows:QueryTableRowsResponse' :: QueryTableRowsResponse -> [TableRow]
$sel:columnIds:QueryTableRowsResponse' :: QueryTableRowsResponse -> NonEmpty Text
$sel:httpStatus:QueryTableRowsResponse' :: QueryTableRowsResponse -> Int
$sel:nextToken:QueryTableRowsResponse' :: QueryTableRowsResponse -> 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 Int
httpStatus
      seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf NonEmpty Text
columnIds
      seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf [TableRow]
rows
      seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf Integer
workbookCursor