{-# 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.ListTableColumns
-- 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 ListTableColumns API allows you to retrieve a list of all the
-- columns in a table in a workbook.
--
-- This operation returns paginated results.
module Amazonka.HoneyCode.ListTableColumns
  ( -- * Creating a Request
    ListTableColumns (..),
    newListTableColumns,

    -- * Request Lenses
    listTableColumns_nextToken,
    listTableColumns_workbookId,
    listTableColumns_tableId,

    -- * Destructuring the Response
    ListTableColumnsResponse (..),
    newListTableColumnsResponse,

    -- * Response Lenses
    listTableColumnsResponse_nextToken,
    listTableColumnsResponse_workbookCursor,
    listTableColumnsResponse_httpStatus,
    listTableColumnsResponse_tableColumns,
  )
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:/ 'newListTableColumns' smart constructor.
data ListTableColumns = ListTableColumns'
  { -- | 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.
    ListTableColumns -> Maybe Text
nextToken :: Prelude.Maybe Prelude.Text,
    -- | The ID of the workbook that contains the table whose columns are being
    -- retrieved.
    --
    -- If a workbook with the specified id could not be found, this API throws
    -- ResourceNotFoundException.
    ListTableColumns -> Text
workbookId :: Prelude.Text,
    -- | The ID of the table whose columns are being retrieved.
    --
    -- If a table with the specified id could not be found, this API throws
    -- ResourceNotFoundException.
    ListTableColumns -> Text
tableId :: Prelude.Text
  }
  deriving (ListTableColumns -> ListTableColumns -> Bool
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: ListTableColumns -> ListTableColumns -> Bool
$c/= :: ListTableColumns -> ListTableColumns -> Bool
== :: ListTableColumns -> ListTableColumns -> Bool
$c== :: ListTableColumns -> ListTableColumns -> Bool
Prelude.Eq, ReadPrec [ListTableColumns]
ReadPrec ListTableColumns
Int -> ReadS ListTableColumns
ReadS [ListTableColumns]
forall a.
(Int -> ReadS a)
-> ReadS [a] -> ReadPrec a -> ReadPrec [a] -> Read a
readListPrec :: ReadPrec [ListTableColumns]
$creadListPrec :: ReadPrec [ListTableColumns]
readPrec :: ReadPrec ListTableColumns
$creadPrec :: ReadPrec ListTableColumns
readList :: ReadS [ListTableColumns]
$creadList :: ReadS [ListTableColumns]
readsPrec :: Int -> ReadS ListTableColumns
$creadsPrec :: Int -> ReadS ListTableColumns
Prelude.Read, Int -> ListTableColumns -> ShowS
[ListTableColumns] -> ShowS
ListTableColumns -> String
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [ListTableColumns] -> ShowS
$cshowList :: [ListTableColumns] -> ShowS
show :: ListTableColumns -> String
$cshow :: ListTableColumns -> String
showsPrec :: Int -> ListTableColumns -> ShowS
$cshowsPrec :: Int -> ListTableColumns -> ShowS
Prelude.Show, forall x. Rep ListTableColumns x -> ListTableColumns
forall x. ListTableColumns -> Rep ListTableColumns x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cto :: forall x. Rep ListTableColumns x -> ListTableColumns
$cfrom :: forall x. ListTableColumns -> Rep ListTableColumns x
Prelude.Generic)

-- |
-- Create a value of 'ListTableColumns' 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', 'listTableColumns_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', 'listTableColumns_workbookId' - The ID of the workbook that contains the table whose columns are being
-- retrieved.
--
-- If a workbook with the specified id could not be found, this API throws
-- ResourceNotFoundException.
--
-- 'tableId', 'listTableColumns_tableId' - The ID of the table whose columns are being retrieved.
--
-- If a table with the specified id could not be found, this API throws
-- ResourceNotFoundException.
newListTableColumns ::
  -- | 'workbookId'
  Prelude.Text ->
  -- | 'tableId'
  Prelude.Text ->
  ListTableColumns
newListTableColumns :: Text -> Text -> ListTableColumns
newListTableColumns Text
pWorkbookId_ Text
pTableId_ =
  ListTableColumns'
    { $sel:nextToken:ListTableColumns' :: Maybe Text
nextToken = forall a. Maybe a
Prelude.Nothing,
      $sel:workbookId:ListTableColumns' :: Text
workbookId = Text
pWorkbookId_,
      $sel:tableId:ListTableColumns' :: Text
tableId = Text
pTableId_
    }

-- | 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.
listTableColumns_nextToken :: Lens.Lens' ListTableColumns (Prelude.Maybe Prelude.Text)
listTableColumns_nextToken :: Lens' ListTableColumns (Maybe Text)
listTableColumns_nextToken = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\ListTableColumns' {Maybe Text
nextToken :: Maybe Text
$sel:nextToken:ListTableColumns' :: ListTableColumns -> Maybe Text
nextToken} -> Maybe Text
nextToken) (\s :: ListTableColumns
s@ListTableColumns' {} Maybe Text
a -> ListTableColumns
s {$sel:nextToken:ListTableColumns' :: Maybe Text
nextToken = Maybe Text
a} :: ListTableColumns)

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

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

instance Core.AWSPager ListTableColumns where
  page :: ListTableColumns
-> AWSResponse ListTableColumns -> Maybe ListTableColumns
page ListTableColumns
rq AWSResponse ListTableColumns
rs
    | forall a. AWSTruncated a => a -> Bool
Core.stop
        ( AWSResponse ListTableColumns
rs
            forall s a. s -> Getting (First a) s a -> Maybe a
Lens.^? Lens' ListTableColumnsResponse (Maybe Text)
listTableColumnsResponse_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 ListTableColumns
rs forall s a. s -> Getting a s a -> a
Lens.^. Lens' ListTableColumnsResponse [TableColumn]
listTableColumnsResponse_tableColumns) =
        forall a. Maybe a
Prelude.Nothing
    | Bool
Prelude.otherwise =
        forall a. a -> Maybe a
Prelude.Just
          forall a b. (a -> b) -> a -> b
Prelude.$ ListTableColumns
rq
          forall a b. a -> (a -> b) -> b
Prelude.& Lens' ListTableColumns (Maybe Text)
listTableColumns_nextToken
          forall s t a b. ASetter s t a b -> b -> s -> t
Lens..~ AWSResponse ListTableColumns
rs
          forall s a. s -> Getting (First a) s a -> Maybe a
Lens.^? Lens' ListTableColumnsResponse (Maybe Text)
listTableColumnsResponse_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 ListTableColumns where
  type
    AWSResponse ListTableColumns =
      ListTableColumnsResponse
  request :: (Service -> Service)
-> ListTableColumns -> Request ListTableColumns
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 ListTableColumns
-> ClientResponse ClientBody
-> m (Either Error (ClientResponse (AWSResponse ListTableColumns)))
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 Integer
-> Int
-> [TableColumn]
-> ListTableColumnsResponse
ListTableColumnsResponse'
            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
"workbookCursor")
            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 (Maybe a)
Data..?> Key
"tableColumns" forall (f :: * -> *) a. Functor f => f (Maybe a) -> a -> f a
Core..!@ forall a. Monoid a => a
Prelude.mempty)
      )

instance Prelude.Hashable ListTableColumns where
  hashWithSalt :: Int -> ListTableColumns -> Int
hashWithSalt Int
_salt ListTableColumns' {Maybe Text
Text
tableId :: Text
workbookId :: Text
nextToken :: Maybe Text
$sel:tableId:ListTableColumns' :: ListTableColumns -> Text
$sel:workbookId:ListTableColumns' :: ListTableColumns -> Text
$sel:nextToken:ListTableColumns' :: ListTableColumns -> Maybe Text
..} =
    Int
_salt
      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

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

instance Data.ToHeaders ListTableColumns where
  toHeaders :: ListTableColumns -> 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 ListTableColumns where
  toPath :: ListTableColumns -> ByteString
toPath ListTableColumns' {Maybe Text
Text
tableId :: Text
workbookId :: Text
nextToken :: Maybe Text
$sel:tableId:ListTableColumns' :: ListTableColumns -> Text
$sel:workbookId:ListTableColumns' :: ListTableColumns -> Text
$sel:nextToken:ListTableColumns' :: ListTableColumns -> Maybe Text
..} =
    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
"/columns"
      ]

instance Data.ToQuery ListTableColumns where
  toQuery :: ListTableColumns -> QueryString
toQuery ListTableColumns' {Maybe Text
Text
tableId :: Text
workbookId :: Text
nextToken :: Maybe Text
$sel:tableId:ListTableColumns' :: ListTableColumns -> Text
$sel:workbookId:ListTableColumns' :: ListTableColumns -> Text
$sel:nextToken:ListTableColumns' :: ListTableColumns -> Maybe Text
..} =
    forall a. Monoid a => [a] -> a
Prelude.mconcat [ByteString
"nextToken" forall a. ToQuery a => ByteString -> a -> QueryString
Data.=: Maybe Text
nextToken]

-- | /See:/ 'newListTableColumnsResponse' smart constructor.
data ListTableColumnsResponse = ListTableColumnsResponse'
  { -- | 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.
    ListTableColumnsResponse -> Maybe Text
nextToken :: Prelude.Maybe Prelude.Text,
    -- | 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.
    ListTableColumnsResponse -> Maybe Integer
workbookCursor :: Prelude.Maybe Prelude.Integer,
    -- | The response's http status code.
    ListTableColumnsResponse -> Int
httpStatus :: Prelude.Int,
    -- | The list of columns in the table.
    ListTableColumnsResponse -> [TableColumn]
tableColumns :: [TableColumn]
  }
  deriving (ListTableColumnsResponse -> ListTableColumnsResponse -> Bool
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: ListTableColumnsResponse -> ListTableColumnsResponse -> Bool
$c/= :: ListTableColumnsResponse -> ListTableColumnsResponse -> Bool
== :: ListTableColumnsResponse -> ListTableColumnsResponse -> Bool
$c== :: ListTableColumnsResponse -> ListTableColumnsResponse -> Bool
Prelude.Eq, ReadPrec [ListTableColumnsResponse]
ReadPrec ListTableColumnsResponse
Int -> ReadS ListTableColumnsResponse
ReadS [ListTableColumnsResponse]
forall a.
(Int -> ReadS a)
-> ReadS [a] -> ReadPrec a -> ReadPrec [a] -> Read a
readListPrec :: ReadPrec [ListTableColumnsResponse]
$creadListPrec :: ReadPrec [ListTableColumnsResponse]
readPrec :: ReadPrec ListTableColumnsResponse
$creadPrec :: ReadPrec ListTableColumnsResponse
readList :: ReadS [ListTableColumnsResponse]
$creadList :: ReadS [ListTableColumnsResponse]
readsPrec :: Int -> ReadS ListTableColumnsResponse
$creadsPrec :: Int -> ReadS ListTableColumnsResponse
Prelude.Read, Int -> ListTableColumnsResponse -> ShowS
[ListTableColumnsResponse] -> ShowS
ListTableColumnsResponse -> String
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [ListTableColumnsResponse] -> ShowS
$cshowList :: [ListTableColumnsResponse] -> ShowS
show :: ListTableColumnsResponse -> String
$cshow :: ListTableColumnsResponse -> String
showsPrec :: Int -> ListTableColumnsResponse -> ShowS
$cshowsPrec :: Int -> ListTableColumnsResponse -> ShowS
Prelude.Show, forall x.
Rep ListTableColumnsResponse x -> ListTableColumnsResponse
forall x.
ListTableColumnsResponse -> Rep ListTableColumnsResponse x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cto :: forall x.
Rep ListTableColumnsResponse x -> ListTableColumnsResponse
$cfrom :: forall x.
ListTableColumnsResponse -> Rep ListTableColumnsResponse x
Prelude.Generic)

-- |
-- Create a value of 'ListTableColumnsResponse' 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', 'listTableColumnsResponse_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.
--
-- 'workbookCursor', 'listTableColumnsResponse_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.
--
-- 'httpStatus', 'listTableColumnsResponse_httpStatus' - The response's http status code.
--
-- 'tableColumns', 'listTableColumnsResponse_tableColumns' - The list of columns in the table.
newListTableColumnsResponse ::
  -- | 'httpStatus'
  Prelude.Int ->
  ListTableColumnsResponse
newListTableColumnsResponse :: Int -> ListTableColumnsResponse
newListTableColumnsResponse Int
pHttpStatus_ =
  ListTableColumnsResponse'
    { $sel:nextToken:ListTableColumnsResponse' :: Maybe Text
nextToken =
        forall a. Maybe a
Prelude.Nothing,
      $sel:workbookCursor:ListTableColumnsResponse' :: Maybe Integer
workbookCursor = forall a. Maybe a
Prelude.Nothing,
      $sel:httpStatus:ListTableColumnsResponse' :: Int
httpStatus = Int
pHttpStatus_,
      $sel:tableColumns:ListTableColumnsResponse' :: [TableColumn]
tableColumns = forall a. Monoid a => a
Prelude.mempty
    }

-- | 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.
listTableColumnsResponse_nextToken :: Lens.Lens' ListTableColumnsResponse (Prelude.Maybe Prelude.Text)
listTableColumnsResponse_nextToken :: Lens' ListTableColumnsResponse (Maybe Text)
listTableColumnsResponse_nextToken = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\ListTableColumnsResponse' {Maybe Text
nextToken :: Maybe Text
$sel:nextToken:ListTableColumnsResponse' :: ListTableColumnsResponse -> Maybe Text
nextToken} -> Maybe Text
nextToken) (\s :: ListTableColumnsResponse
s@ListTableColumnsResponse' {} Maybe Text
a -> ListTableColumnsResponse
s {$sel:nextToken:ListTableColumnsResponse' :: Maybe Text
nextToken = Maybe Text
a} :: ListTableColumnsResponse)

-- | 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.
listTableColumnsResponse_workbookCursor :: Lens.Lens' ListTableColumnsResponse (Prelude.Maybe Prelude.Integer)
listTableColumnsResponse_workbookCursor :: Lens' ListTableColumnsResponse (Maybe Integer)
listTableColumnsResponse_workbookCursor = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\ListTableColumnsResponse' {Maybe Integer
workbookCursor :: Maybe Integer
$sel:workbookCursor:ListTableColumnsResponse' :: ListTableColumnsResponse -> Maybe Integer
workbookCursor} -> Maybe Integer
workbookCursor) (\s :: ListTableColumnsResponse
s@ListTableColumnsResponse' {} Maybe Integer
a -> ListTableColumnsResponse
s {$sel:workbookCursor:ListTableColumnsResponse' :: Maybe Integer
workbookCursor = Maybe Integer
a} :: ListTableColumnsResponse)

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

-- | The list of columns in the table.
listTableColumnsResponse_tableColumns :: Lens.Lens' ListTableColumnsResponse [TableColumn]
listTableColumnsResponse_tableColumns :: Lens' ListTableColumnsResponse [TableColumn]
listTableColumnsResponse_tableColumns = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\ListTableColumnsResponse' {[TableColumn]
tableColumns :: [TableColumn]
$sel:tableColumns:ListTableColumnsResponse' :: ListTableColumnsResponse -> [TableColumn]
tableColumns} -> [TableColumn]
tableColumns) (\s :: ListTableColumnsResponse
s@ListTableColumnsResponse' {} [TableColumn]
a -> ListTableColumnsResponse
s {$sel:tableColumns:ListTableColumnsResponse' :: [TableColumn]
tableColumns = [TableColumn]
a} :: ListTableColumnsResponse) 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

instance Prelude.NFData ListTableColumnsResponse where
  rnf :: ListTableColumnsResponse -> ()
rnf ListTableColumnsResponse' {Int
[TableColumn]
Maybe Integer
Maybe Text
tableColumns :: [TableColumn]
httpStatus :: Int
workbookCursor :: Maybe Integer
nextToken :: Maybe Text
$sel:tableColumns:ListTableColumnsResponse' :: ListTableColumnsResponse -> [TableColumn]
$sel:httpStatus:ListTableColumnsResponse' :: ListTableColumnsResponse -> Int
$sel:workbookCursor:ListTableColumnsResponse' :: ListTableColumnsResponse -> Maybe Integer
$sel:nextToken:ListTableColumnsResponse' :: ListTableColumnsResponse -> 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 Integer
workbookCursor
      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 [TableColumn]
tableColumns