{-# 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.Glue.SearchTables
-- Copyright   : (c) 2013-2023 Brendan Hay
-- License     : Mozilla Public License, v. 2.0.
-- Maintainer  : Brendan Hay
-- Stability   : auto-generated
-- Portability : non-portable (GHC extensions)
--
-- Searches a set of tables based on properties in the table metadata as
-- well as on the parent database. You can search against text or filter
-- conditions.
--
-- You can only get tables that you have access to based on the security
-- policies defined in Lake Formation. You need at least a read-only access
-- to the table for it to be returned. If you do not have access to all the
-- columns in the table, these columns will not be searched against when
-- returning the list of tables back to you. If you have access to the
-- columns but not the data in the columns, those columns and the
-- associated metadata for those columns will be included in the search.
module Amazonka.Glue.SearchTables
  ( -- * Creating a Request
    SearchTables (..),
    newSearchTables,

    -- * Request Lenses
    searchTables_catalogId,
    searchTables_filters,
    searchTables_maxResults,
    searchTables_nextToken,
    searchTables_resourceShareType,
    searchTables_searchText,
    searchTables_sortCriteria,

    -- * Destructuring the Response
    SearchTablesResponse (..),
    newSearchTablesResponse,

    -- * Response Lenses
    searchTablesResponse_nextToken,
    searchTablesResponse_tableList,
    searchTablesResponse_httpStatus,
  )
where

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

-- | /See:/ 'newSearchTables' smart constructor.
data SearchTables = SearchTables'
  { -- | A unique identifier, consisting of @ @/@account_id@/@ @.
    SearchTables -> Maybe Text
catalogId :: Prelude.Maybe Prelude.Text,
    -- | A list of key-value pairs, and a comparator used to filter the search
    -- results. Returns all entities matching the predicate.
    --
    -- The @Comparator@ member of the @PropertyPredicate@ struct is used only
    -- for time fields, and can be omitted for other field types. Also, when
    -- comparing string values, such as when @Key=Name@, a fuzzy match
    -- algorithm is used. The @Key@ field (for example, the value of the @Name@
    -- field) is split on certain punctuation characters, for example, -, :, #,
    -- etc. into tokens. Then each token is exact-match compared with the
    -- @Value@ member of @PropertyPredicate@. For example, if @Key=Name@ and
    -- @Value=link@, tables named @customer-link@ and @xx-link-yy@ are
    -- returned, but @xxlinkyy@ is not returned.
    SearchTables -> Maybe [PropertyPredicate]
filters :: Prelude.Maybe [PropertyPredicate],
    -- | The maximum number of tables to return in a single response.
    SearchTables -> Maybe Natural
maxResults :: Prelude.Maybe Prelude.Natural,
    -- | A continuation token, included if this is a continuation call.
    SearchTables -> Maybe Text
nextToken :: Prelude.Maybe Prelude.Text,
    -- | Allows you to specify that you want to search the tables shared with
    -- your account. The allowable values are @FOREIGN@ or @ALL@.
    --
    -- -   If set to @FOREIGN@, will search the tables shared with your
    --     account.
    --
    -- -   If set to @ALL@, will search the tables shared with your account, as
    --     well as the tables in yor local account.
    SearchTables -> Maybe ResourceShareType
resourceShareType :: Prelude.Maybe ResourceShareType,
    -- | A string used for a text search.
    --
    -- Specifying a value in quotes filters based on an exact match to the
    -- value.
    SearchTables -> Maybe Text
searchText :: Prelude.Maybe Prelude.Text,
    -- | A list of criteria for sorting the results by a field name, in an
    -- ascending or descending order.
    SearchTables -> Maybe [SortCriterion]
sortCriteria :: Prelude.Maybe [SortCriterion]
  }
  deriving (SearchTables -> SearchTables -> Bool
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: SearchTables -> SearchTables -> Bool
$c/= :: SearchTables -> SearchTables -> Bool
== :: SearchTables -> SearchTables -> Bool
$c== :: SearchTables -> SearchTables -> Bool
Prelude.Eq, ReadPrec [SearchTables]
ReadPrec SearchTables
Int -> ReadS SearchTables
ReadS [SearchTables]
forall a.
(Int -> ReadS a)
-> ReadS [a] -> ReadPrec a -> ReadPrec [a] -> Read a
readListPrec :: ReadPrec [SearchTables]
$creadListPrec :: ReadPrec [SearchTables]
readPrec :: ReadPrec SearchTables
$creadPrec :: ReadPrec SearchTables
readList :: ReadS [SearchTables]
$creadList :: ReadS [SearchTables]
readsPrec :: Int -> ReadS SearchTables
$creadsPrec :: Int -> ReadS SearchTables
Prelude.Read, Int -> SearchTables -> ShowS
[SearchTables] -> ShowS
SearchTables -> String
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [SearchTables] -> ShowS
$cshowList :: [SearchTables] -> ShowS
show :: SearchTables -> String
$cshow :: SearchTables -> String
showsPrec :: Int -> SearchTables -> ShowS
$cshowsPrec :: Int -> SearchTables -> ShowS
Prelude.Show, forall x. Rep SearchTables x -> SearchTables
forall x. SearchTables -> Rep SearchTables x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cto :: forall x. Rep SearchTables x -> SearchTables
$cfrom :: forall x. SearchTables -> Rep SearchTables x
Prelude.Generic)

-- |
-- Create a value of 'SearchTables' 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:
--
-- 'catalogId', 'searchTables_catalogId' - A unique identifier, consisting of @ @/@account_id@/@ @.
--
-- 'filters', 'searchTables_filters' - A list of key-value pairs, and a comparator used to filter the search
-- results. Returns all entities matching the predicate.
--
-- The @Comparator@ member of the @PropertyPredicate@ struct is used only
-- for time fields, and can be omitted for other field types. Also, when
-- comparing string values, such as when @Key=Name@, a fuzzy match
-- algorithm is used. The @Key@ field (for example, the value of the @Name@
-- field) is split on certain punctuation characters, for example, -, :, #,
-- etc. into tokens. Then each token is exact-match compared with the
-- @Value@ member of @PropertyPredicate@. For example, if @Key=Name@ and
-- @Value=link@, tables named @customer-link@ and @xx-link-yy@ are
-- returned, but @xxlinkyy@ is not returned.
--
-- 'maxResults', 'searchTables_maxResults' - The maximum number of tables to return in a single response.
--
-- 'nextToken', 'searchTables_nextToken' - A continuation token, included if this is a continuation call.
--
-- 'resourceShareType', 'searchTables_resourceShareType' - Allows you to specify that you want to search the tables shared with
-- your account. The allowable values are @FOREIGN@ or @ALL@.
--
-- -   If set to @FOREIGN@, will search the tables shared with your
--     account.
--
-- -   If set to @ALL@, will search the tables shared with your account, as
--     well as the tables in yor local account.
--
-- 'searchText', 'searchTables_searchText' - A string used for a text search.
--
-- Specifying a value in quotes filters based on an exact match to the
-- value.
--
-- 'sortCriteria', 'searchTables_sortCriteria' - A list of criteria for sorting the results by a field name, in an
-- ascending or descending order.
newSearchTables ::
  SearchTables
newSearchTables :: SearchTables
newSearchTables =
  SearchTables'
    { $sel:catalogId:SearchTables' :: Maybe Text
catalogId = forall a. Maybe a
Prelude.Nothing,
      $sel:filters:SearchTables' :: Maybe [PropertyPredicate]
filters = forall a. Maybe a
Prelude.Nothing,
      $sel:maxResults:SearchTables' :: Maybe Natural
maxResults = forall a. Maybe a
Prelude.Nothing,
      $sel:nextToken:SearchTables' :: Maybe Text
nextToken = forall a. Maybe a
Prelude.Nothing,
      $sel:resourceShareType:SearchTables' :: Maybe ResourceShareType
resourceShareType = forall a. Maybe a
Prelude.Nothing,
      $sel:searchText:SearchTables' :: Maybe Text
searchText = forall a. Maybe a
Prelude.Nothing,
      $sel:sortCriteria:SearchTables' :: Maybe [SortCriterion]
sortCriteria = forall a. Maybe a
Prelude.Nothing
    }

-- | A unique identifier, consisting of @ @/@account_id@/@ @.
searchTables_catalogId :: Lens.Lens' SearchTables (Prelude.Maybe Prelude.Text)
searchTables_catalogId :: Lens' SearchTables (Maybe Text)
searchTables_catalogId = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\SearchTables' {Maybe Text
catalogId :: Maybe Text
$sel:catalogId:SearchTables' :: SearchTables -> Maybe Text
catalogId} -> Maybe Text
catalogId) (\s :: SearchTables
s@SearchTables' {} Maybe Text
a -> SearchTables
s {$sel:catalogId:SearchTables' :: Maybe Text
catalogId = Maybe Text
a} :: SearchTables)

-- | A list of key-value pairs, and a comparator used to filter the search
-- results. Returns all entities matching the predicate.
--
-- The @Comparator@ member of the @PropertyPredicate@ struct is used only
-- for time fields, and can be omitted for other field types. Also, when
-- comparing string values, such as when @Key=Name@, a fuzzy match
-- algorithm is used. The @Key@ field (for example, the value of the @Name@
-- field) is split on certain punctuation characters, for example, -, :, #,
-- etc. into tokens. Then each token is exact-match compared with the
-- @Value@ member of @PropertyPredicate@. For example, if @Key=Name@ and
-- @Value=link@, tables named @customer-link@ and @xx-link-yy@ are
-- returned, but @xxlinkyy@ is not returned.
searchTables_filters :: Lens.Lens' SearchTables (Prelude.Maybe [PropertyPredicate])
searchTables_filters :: Lens' SearchTables (Maybe [PropertyPredicate])
searchTables_filters = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\SearchTables' {Maybe [PropertyPredicate]
filters :: Maybe [PropertyPredicate]
$sel:filters:SearchTables' :: SearchTables -> Maybe [PropertyPredicate]
filters} -> Maybe [PropertyPredicate]
filters) (\s :: SearchTables
s@SearchTables' {} Maybe [PropertyPredicate]
a -> SearchTables
s {$sel:filters:SearchTables' :: Maybe [PropertyPredicate]
filters = Maybe [PropertyPredicate]
a} :: SearchTables) 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 maximum number of tables to return in a single response.
searchTables_maxResults :: Lens.Lens' SearchTables (Prelude.Maybe Prelude.Natural)
searchTables_maxResults :: Lens' SearchTables (Maybe Natural)
searchTables_maxResults = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\SearchTables' {Maybe Natural
maxResults :: Maybe Natural
$sel:maxResults:SearchTables' :: SearchTables -> Maybe Natural
maxResults} -> Maybe Natural
maxResults) (\s :: SearchTables
s@SearchTables' {} Maybe Natural
a -> SearchTables
s {$sel:maxResults:SearchTables' :: Maybe Natural
maxResults = Maybe Natural
a} :: SearchTables)

-- | A continuation token, included if this is a continuation call.
searchTables_nextToken :: Lens.Lens' SearchTables (Prelude.Maybe Prelude.Text)
searchTables_nextToken :: Lens' SearchTables (Maybe Text)
searchTables_nextToken = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\SearchTables' {Maybe Text
nextToken :: Maybe Text
$sel:nextToken:SearchTables' :: SearchTables -> Maybe Text
nextToken} -> Maybe Text
nextToken) (\s :: SearchTables
s@SearchTables' {} Maybe Text
a -> SearchTables
s {$sel:nextToken:SearchTables' :: Maybe Text
nextToken = Maybe Text
a} :: SearchTables)

-- | Allows you to specify that you want to search the tables shared with
-- your account. The allowable values are @FOREIGN@ or @ALL@.
--
-- -   If set to @FOREIGN@, will search the tables shared with your
--     account.
--
-- -   If set to @ALL@, will search the tables shared with your account, as
--     well as the tables in yor local account.
searchTables_resourceShareType :: Lens.Lens' SearchTables (Prelude.Maybe ResourceShareType)
searchTables_resourceShareType :: Lens' SearchTables (Maybe ResourceShareType)
searchTables_resourceShareType = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\SearchTables' {Maybe ResourceShareType
resourceShareType :: Maybe ResourceShareType
$sel:resourceShareType:SearchTables' :: SearchTables -> Maybe ResourceShareType
resourceShareType} -> Maybe ResourceShareType
resourceShareType) (\s :: SearchTables
s@SearchTables' {} Maybe ResourceShareType
a -> SearchTables
s {$sel:resourceShareType:SearchTables' :: Maybe ResourceShareType
resourceShareType = Maybe ResourceShareType
a} :: SearchTables)

-- | A string used for a text search.
--
-- Specifying a value in quotes filters based on an exact match to the
-- value.
searchTables_searchText :: Lens.Lens' SearchTables (Prelude.Maybe Prelude.Text)
searchTables_searchText :: Lens' SearchTables (Maybe Text)
searchTables_searchText = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\SearchTables' {Maybe Text
searchText :: Maybe Text
$sel:searchText:SearchTables' :: SearchTables -> Maybe Text
searchText} -> Maybe Text
searchText) (\s :: SearchTables
s@SearchTables' {} Maybe Text
a -> SearchTables
s {$sel:searchText:SearchTables' :: Maybe Text
searchText = Maybe Text
a} :: SearchTables)

-- | A list of criteria for sorting the results by a field name, in an
-- ascending or descending order.
searchTables_sortCriteria :: Lens.Lens' SearchTables (Prelude.Maybe [SortCriterion])
searchTables_sortCriteria :: Lens' SearchTables (Maybe [SortCriterion])
searchTables_sortCriteria = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\SearchTables' {Maybe [SortCriterion]
sortCriteria :: Maybe [SortCriterion]
$sel:sortCriteria:SearchTables' :: SearchTables -> Maybe [SortCriterion]
sortCriteria} -> Maybe [SortCriterion]
sortCriteria) (\s :: SearchTables
s@SearchTables' {} Maybe [SortCriterion]
a -> SearchTables
s {$sel:sortCriteria:SearchTables' :: Maybe [SortCriterion]
sortCriteria = Maybe [SortCriterion]
a} :: SearchTables) 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

instance Core.AWSRequest SearchTables where
  type AWSResponse SearchTables = SearchTablesResponse
  request :: (Service -> Service) -> SearchTables -> Request SearchTables
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 SearchTables
-> ClientResponse ClientBody
-> m (Either Error (ClientResponse (AWSResponse SearchTables)))
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 [Table] -> Int -> SearchTablesResponse
SearchTablesResponse'
            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
"TableList" forall (f :: * -> *) a. Functor f => f (Maybe a) -> a -> f a
Core..!@ forall a. Monoid a => a
Prelude.mempty)
            forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
Prelude.<*> (forall (f :: * -> *) a. Applicative f => a -> f a
Prelude.pure (forall a. Enum a => a -> Int
Prelude.fromEnum Int
s))
      )

instance Prelude.Hashable SearchTables where
  hashWithSalt :: Int -> SearchTables -> Int
hashWithSalt Int
_salt SearchTables' {Maybe Natural
Maybe [PropertyPredicate]
Maybe [SortCriterion]
Maybe Text
Maybe ResourceShareType
sortCriteria :: Maybe [SortCriterion]
searchText :: Maybe Text
resourceShareType :: Maybe ResourceShareType
nextToken :: Maybe Text
maxResults :: Maybe Natural
filters :: Maybe [PropertyPredicate]
catalogId :: Maybe Text
$sel:sortCriteria:SearchTables' :: SearchTables -> Maybe [SortCriterion]
$sel:searchText:SearchTables' :: SearchTables -> Maybe Text
$sel:resourceShareType:SearchTables' :: SearchTables -> Maybe ResourceShareType
$sel:nextToken:SearchTables' :: SearchTables -> Maybe Text
$sel:maxResults:SearchTables' :: SearchTables -> Maybe Natural
$sel:filters:SearchTables' :: SearchTables -> Maybe [PropertyPredicate]
$sel:catalogId:SearchTables' :: SearchTables -> Maybe Text
..} =
    Int
_salt
      forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Maybe Text
catalogId
      forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Maybe [PropertyPredicate]
filters
      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` Maybe ResourceShareType
resourceShareType
      forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Maybe Text
searchText
      forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Maybe [SortCriterion]
sortCriteria

instance Prelude.NFData SearchTables where
  rnf :: SearchTables -> ()
rnf SearchTables' {Maybe Natural
Maybe [PropertyPredicate]
Maybe [SortCriterion]
Maybe Text
Maybe ResourceShareType
sortCriteria :: Maybe [SortCriterion]
searchText :: Maybe Text
resourceShareType :: Maybe ResourceShareType
nextToken :: Maybe Text
maxResults :: Maybe Natural
filters :: Maybe [PropertyPredicate]
catalogId :: Maybe Text
$sel:sortCriteria:SearchTables' :: SearchTables -> Maybe [SortCriterion]
$sel:searchText:SearchTables' :: SearchTables -> Maybe Text
$sel:resourceShareType:SearchTables' :: SearchTables -> Maybe ResourceShareType
$sel:nextToken:SearchTables' :: SearchTables -> Maybe Text
$sel:maxResults:SearchTables' :: SearchTables -> Maybe Natural
$sel:filters:SearchTables' :: SearchTables -> Maybe [PropertyPredicate]
$sel:catalogId:SearchTables' :: SearchTables -> Maybe Text
..} =
    forall a. NFData a => a -> ()
Prelude.rnf Maybe Text
catalogId
      seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf Maybe [PropertyPredicate]
filters
      seq :: forall a b. a -> b -> b
`Prelude.seq` 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 Maybe ResourceShareType
resourceShareType
      seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf Maybe Text
searchText
      seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf Maybe [SortCriterion]
sortCriteria

instance Data.ToHeaders SearchTables where
  toHeaders :: SearchTables -> 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
"AWSGlue.SearchTables" :: 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 SearchTables where
  toJSON :: SearchTables -> Value
toJSON SearchTables' {Maybe Natural
Maybe [PropertyPredicate]
Maybe [SortCriterion]
Maybe Text
Maybe ResourceShareType
sortCriteria :: Maybe [SortCriterion]
searchText :: Maybe Text
resourceShareType :: Maybe ResourceShareType
nextToken :: Maybe Text
maxResults :: Maybe Natural
filters :: Maybe [PropertyPredicate]
catalogId :: Maybe Text
$sel:sortCriteria:SearchTables' :: SearchTables -> Maybe [SortCriterion]
$sel:searchText:SearchTables' :: SearchTables -> Maybe Text
$sel:resourceShareType:SearchTables' :: SearchTables -> Maybe ResourceShareType
$sel:nextToken:SearchTables' :: SearchTables -> Maybe Text
$sel:maxResults:SearchTables' :: SearchTables -> Maybe Natural
$sel:filters:SearchTables' :: SearchTables -> Maybe [PropertyPredicate]
$sel:catalogId:SearchTables' :: SearchTables -> Maybe Text
..} =
    [Pair] -> Value
Data.object
      ( forall a. [Maybe a] -> [a]
Prelude.catMaybes
          [ (Key
"CatalogId" 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
catalogId,
            (Key
"Filters" 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 [PropertyPredicate]
filters,
            (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,
            (Key
"ResourceShareType" 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 ResourceShareType
resourceShareType,
            (Key
"SearchText" 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
searchText,
            (Key
"SortCriteria" 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 [SortCriterion]
sortCriteria
          ]
      )

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

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

-- | /See:/ 'newSearchTablesResponse' smart constructor.
data SearchTablesResponse = SearchTablesResponse'
  { -- | A continuation token, present if the current list segment is not the
    -- last.
    SearchTablesResponse -> Maybe Text
nextToken :: Prelude.Maybe Prelude.Text,
    -- | A list of the requested @Table@ objects. The @SearchTables@ response
    -- returns only the tables that you have access to.
    SearchTablesResponse -> Maybe [Table]
tableList :: Prelude.Maybe [Table],
    -- | The response's http status code.
    SearchTablesResponse -> Int
httpStatus :: Prelude.Int
  }
  deriving (SearchTablesResponse -> SearchTablesResponse -> Bool
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: SearchTablesResponse -> SearchTablesResponse -> Bool
$c/= :: SearchTablesResponse -> SearchTablesResponse -> Bool
== :: SearchTablesResponse -> SearchTablesResponse -> Bool
$c== :: SearchTablesResponse -> SearchTablesResponse -> Bool
Prelude.Eq, ReadPrec [SearchTablesResponse]
ReadPrec SearchTablesResponse
Int -> ReadS SearchTablesResponse
ReadS [SearchTablesResponse]
forall a.
(Int -> ReadS a)
-> ReadS [a] -> ReadPrec a -> ReadPrec [a] -> Read a
readListPrec :: ReadPrec [SearchTablesResponse]
$creadListPrec :: ReadPrec [SearchTablesResponse]
readPrec :: ReadPrec SearchTablesResponse
$creadPrec :: ReadPrec SearchTablesResponse
readList :: ReadS [SearchTablesResponse]
$creadList :: ReadS [SearchTablesResponse]
readsPrec :: Int -> ReadS SearchTablesResponse
$creadsPrec :: Int -> ReadS SearchTablesResponse
Prelude.Read, Int -> SearchTablesResponse -> ShowS
[SearchTablesResponse] -> ShowS
SearchTablesResponse -> String
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [SearchTablesResponse] -> ShowS
$cshowList :: [SearchTablesResponse] -> ShowS
show :: SearchTablesResponse -> String
$cshow :: SearchTablesResponse -> String
showsPrec :: Int -> SearchTablesResponse -> ShowS
$cshowsPrec :: Int -> SearchTablesResponse -> ShowS
Prelude.Show, forall x. Rep SearchTablesResponse x -> SearchTablesResponse
forall x. SearchTablesResponse -> Rep SearchTablesResponse x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cto :: forall x. Rep SearchTablesResponse x -> SearchTablesResponse
$cfrom :: forall x. SearchTablesResponse -> Rep SearchTablesResponse x
Prelude.Generic)

-- |
-- Create a value of 'SearchTablesResponse' 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', 'searchTablesResponse_nextToken' - A continuation token, present if the current list segment is not the
-- last.
--
-- 'tableList', 'searchTablesResponse_tableList' - A list of the requested @Table@ objects. The @SearchTables@ response
-- returns only the tables that you have access to.
--
-- 'httpStatus', 'searchTablesResponse_httpStatus' - The response's http status code.
newSearchTablesResponse ::
  -- | 'httpStatus'
  Prelude.Int ->
  SearchTablesResponse
newSearchTablesResponse :: Int -> SearchTablesResponse
newSearchTablesResponse Int
pHttpStatus_ =
  SearchTablesResponse'
    { $sel:nextToken:SearchTablesResponse' :: Maybe Text
nextToken = forall a. Maybe a
Prelude.Nothing,
      $sel:tableList:SearchTablesResponse' :: Maybe [Table]
tableList = forall a. Maybe a
Prelude.Nothing,
      $sel:httpStatus:SearchTablesResponse' :: Int
httpStatus = Int
pHttpStatus_
    }

-- | A continuation token, present if the current list segment is not the
-- last.
searchTablesResponse_nextToken :: Lens.Lens' SearchTablesResponse (Prelude.Maybe Prelude.Text)
searchTablesResponse_nextToken :: Lens' SearchTablesResponse (Maybe Text)
searchTablesResponse_nextToken = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\SearchTablesResponse' {Maybe Text
nextToken :: Maybe Text
$sel:nextToken:SearchTablesResponse' :: SearchTablesResponse -> Maybe Text
nextToken} -> Maybe Text
nextToken) (\s :: SearchTablesResponse
s@SearchTablesResponse' {} Maybe Text
a -> SearchTablesResponse
s {$sel:nextToken:SearchTablesResponse' :: Maybe Text
nextToken = Maybe Text
a} :: SearchTablesResponse)

-- | A list of the requested @Table@ objects. The @SearchTables@ response
-- returns only the tables that you have access to.
searchTablesResponse_tableList :: Lens.Lens' SearchTablesResponse (Prelude.Maybe [Table])
searchTablesResponse_tableList :: Lens' SearchTablesResponse (Maybe [Table])
searchTablesResponse_tableList = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\SearchTablesResponse' {Maybe [Table]
tableList :: Maybe [Table]
$sel:tableList:SearchTablesResponse' :: SearchTablesResponse -> Maybe [Table]
tableList} -> Maybe [Table]
tableList) (\s :: SearchTablesResponse
s@SearchTablesResponse' {} Maybe [Table]
a -> SearchTablesResponse
s {$sel:tableList:SearchTablesResponse' :: Maybe [Table]
tableList = Maybe [Table]
a} :: SearchTablesResponse) forall b c a. (b -> c) -> (a -> b) -> a -> c
Prelude.. forall (f :: * -> *) (g :: * -> *) s t a b.
(Functor f, Functor g) =>
AnIso s t a b -> Iso (f s) (g t) (f a) (g b)
Lens.mapping forall s t a b. (Coercible s a, Coercible t b) => Iso s t a b
Lens.coerced

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

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