{-# 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.DataPipeline.QueryObjects
-- Copyright   : (c) 2013-2023 Brendan Hay
-- License     : Mozilla Public License, v. 2.0.
-- Maintainer  : Brendan Hay
-- Stability   : auto-generated
-- Portability : non-portable (GHC extensions)
--
-- Queries the specified pipeline for the names of objects that match the
-- specified set of conditions.
--
-- This operation returns paginated results.
module Amazonka.DataPipeline.QueryObjects
  ( -- * Creating a Request
    QueryObjects (..),
    newQueryObjects,

    -- * Request Lenses
    queryObjects_limit,
    queryObjects_marker,
    queryObjects_query,
    queryObjects_pipelineId,
    queryObjects_sphere,

    -- * Destructuring the Response
    QueryObjectsResponse (..),
    newQueryObjectsResponse,

    -- * Response Lenses
    queryObjectsResponse_hasMoreResults,
    queryObjectsResponse_ids,
    queryObjectsResponse_marker,
    queryObjectsResponse_httpStatus,
  )
where

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

-- | Contains the parameters for QueryObjects.
--
-- /See:/ 'newQueryObjects' smart constructor.
data QueryObjects = QueryObjects'
  { -- | The maximum number of object names that @QueryObjects@ will return in a
    -- single call. The default value is 100.
    QueryObjects -> Maybe Int
limit :: Prelude.Maybe Prelude.Int,
    -- | The starting point for the results to be returned. For the first call,
    -- this value should be empty. As long as there are more results, continue
    -- to call @QueryObjects@ with the marker value from the previous call to
    -- retrieve the next set of results.
    QueryObjects -> Maybe Text
marker :: Prelude.Maybe Prelude.Text,
    -- | The query that defines the objects to be returned. The @Query@ object
    -- can contain a maximum of ten selectors. The conditions in the query are
    -- limited to top-level String fields in the object. These filters can be
    -- applied to components, instances, and attempts.
    QueryObjects -> Maybe Query
query :: Prelude.Maybe Query,
    -- | The ID of the pipeline.
    QueryObjects -> Text
pipelineId :: Prelude.Text,
    -- | Indicates whether the query applies to components or instances. The
    -- possible values are: @COMPONENT@, @INSTANCE@, and @ATTEMPT@.
    QueryObjects -> Text
sphere :: Prelude.Text
  }
  deriving (QueryObjects -> QueryObjects -> Bool
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: QueryObjects -> QueryObjects -> Bool
$c/= :: QueryObjects -> QueryObjects -> Bool
== :: QueryObjects -> QueryObjects -> Bool
$c== :: QueryObjects -> QueryObjects -> Bool
Prelude.Eq, ReadPrec [QueryObjects]
ReadPrec QueryObjects
Int -> ReadS QueryObjects
ReadS [QueryObjects]
forall a.
(Int -> ReadS a)
-> ReadS [a] -> ReadPrec a -> ReadPrec [a] -> Read a
readListPrec :: ReadPrec [QueryObjects]
$creadListPrec :: ReadPrec [QueryObjects]
readPrec :: ReadPrec QueryObjects
$creadPrec :: ReadPrec QueryObjects
readList :: ReadS [QueryObjects]
$creadList :: ReadS [QueryObjects]
readsPrec :: Int -> ReadS QueryObjects
$creadsPrec :: Int -> ReadS QueryObjects
Prelude.Read, Int -> QueryObjects -> ShowS
[QueryObjects] -> ShowS
QueryObjects -> String
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [QueryObjects] -> ShowS
$cshowList :: [QueryObjects] -> ShowS
show :: QueryObjects -> String
$cshow :: QueryObjects -> String
showsPrec :: Int -> QueryObjects -> ShowS
$cshowsPrec :: Int -> QueryObjects -> ShowS
Prelude.Show, forall x. Rep QueryObjects x -> QueryObjects
forall x. QueryObjects -> Rep QueryObjects x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cto :: forall x. Rep QueryObjects x -> QueryObjects
$cfrom :: forall x. QueryObjects -> Rep QueryObjects x
Prelude.Generic)

-- |
-- Create a value of 'QueryObjects' 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:
--
-- 'limit', 'queryObjects_limit' - The maximum number of object names that @QueryObjects@ will return in a
-- single call. The default value is 100.
--
-- 'marker', 'queryObjects_marker' - The starting point for the results to be returned. For the first call,
-- this value should be empty. As long as there are more results, continue
-- to call @QueryObjects@ with the marker value from the previous call to
-- retrieve the next set of results.
--
-- 'query', 'queryObjects_query' - The query that defines the objects to be returned. The @Query@ object
-- can contain a maximum of ten selectors. The conditions in the query are
-- limited to top-level String fields in the object. These filters can be
-- applied to components, instances, and attempts.
--
-- 'pipelineId', 'queryObjects_pipelineId' - The ID of the pipeline.
--
-- 'sphere', 'queryObjects_sphere' - Indicates whether the query applies to components or instances. The
-- possible values are: @COMPONENT@, @INSTANCE@, and @ATTEMPT@.
newQueryObjects ::
  -- | 'pipelineId'
  Prelude.Text ->
  -- | 'sphere'
  Prelude.Text ->
  QueryObjects
newQueryObjects :: Text -> Text -> QueryObjects
newQueryObjects Text
pPipelineId_ Text
pSphere_ =
  QueryObjects'
    { $sel:limit:QueryObjects' :: Maybe Int
limit = forall a. Maybe a
Prelude.Nothing,
      $sel:marker:QueryObjects' :: Maybe Text
marker = forall a. Maybe a
Prelude.Nothing,
      $sel:query:QueryObjects' :: Maybe Query
query = forall a. Maybe a
Prelude.Nothing,
      $sel:pipelineId:QueryObjects' :: Text
pipelineId = Text
pPipelineId_,
      $sel:sphere:QueryObjects' :: Text
sphere = Text
pSphere_
    }

-- | The maximum number of object names that @QueryObjects@ will return in a
-- single call. The default value is 100.
queryObjects_limit :: Lens.Lens' QueryObjects (Prelude.Maybe Prelude.Int)
queryObjects_limit :: Lens' QueryObjects (Maybe Int)
queryObjects_limit = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\QueryObjects' {Maybe Int
limit :: Maybe Int
$sel:limit:QueryObjects' :: QueryObjects -> Maybe Int
limit} -> Maybe Int
limit) (\s :: QueryObjects
s@QueryObjects' {} Maybe Int
a -> QueryObjects
s {$sel:limit:QueryObjects' :: Maybe Int
limit = Maybe Int
a} :: QueryObjects)

-- | The starting point for the results to be returned. For the first call,
-- this value should be empty. As long as there are more results, continue
-- to call @QueryObjects@ with the marker value from the previous call to
-- retrieve the next set of results.
queryObjects_marker :: Lens.Lens' QueryObjects (Prelude.Maybe Prelude.Text)
queryObjects_marker :: Lens' QueryObjects (Maybe Text)
queryObjects_marker = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\QueryObjects' {Maybe Text
marker :: Maybe Text
$sel:marker:QueryObjects' :: QueryObjects -> Maybe Text
marker} -> Maybe Text
marker) (\s :: QueryObjects
s@QueryObjects' {} Maybe Text
a -> QueryObjects
s {$sel:marker:QueryObjects' :: Maybe Text
marker = Maybe Text
a} :: QueryObjects)

-- | The query that defines the objects to be returned. The @Query@ object
-- can contain a maximum of ten selectors. The conditions in the query are
-- limited to top-level String fields in the object. These filters can be
-- applied to components, instances, and attempts.
queryObjects_query :: Lens.Lens' QueryObjects (Prelude.Maybe Query)
queryObjects_query :: Lens' QueryObjects (Maybe Query)
queryObjects_query = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\QueryObjects' {Maybe Query
query :: Maybe Query
$sel:query:QueryObjects' :: QueryObjects -> Maybe Query
query} -> Maybe Query
query) (\s :: QueryObjects
s@QueryObjects' {} Maybe Query
a -> QueryObjects
s {$sel:query:QueryObjects' :: Maybe Query
query = Maybe Query
a} :: QueryObjects)

-- | The ID of the pipeline.
queryObjects_pipelineId :: Lens.Lens' QueryObjects Prelude.Text
queryObjects_pipelineId :: Lens' QueryObjects Text
queryObjects_pipelineId = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\QueryObjects' {Text
pipelineId :: Text
$sel:pipelineId:QueryObjects' :: QueryObjects -> Text
pipelineId} -> Text
pipelineId) (\s :: QueryObjects
s@QueryObjects' {} Text
a -> QueryObjects
s {$sel:pipelineId:QueryObjects' :: Text
pipelineId = Text
a} :: QueryObjects)

-- | Indicates whether the query applies to components or instances. The
-- possible values are: @COMPONENT@, @INSTANCE@, and @ATTEMPT@.
queryObjects_sphere :: Lens.Lens' QueryObjects Prelude.Text
queryObjects_sphere :: Lens' QueryObjects Text
queryObjects_sphere = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\QueryObjects' {Text
sphere :: Text
$sel:sphere:QueryObjects' :: QueryObjects -> Text
sphere} -> Text
sphere) (\s :: QueryObjects
s@QueryObjects' {} Text
a -> QueryObjects
s {$sel:sphere:QueryObjects' :: Text
sphere = Text
a} :: QueryObjects)

instance Core.AWSPager QueryObjects where
  page :: QueryObjects -> AWSResponse QueryObjects -> Maybe QueryObjects
page QueryObjects
rq AWSResponse QueryObjects
rs
    | forall a. AWSTruncated a => a -> Bool
Core.stop
        ( AWSResponse QueryObjects
rs
            forall s a. s -> Getting (First a) s a -> Maybe a
Lens.^? Lens' QueryObjectsResponse (Maybe Bool)
queryObjectsResponse_hasMoreResults
            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. Maybe a -> Bool
Prelude.isNothing
        ( AWSResponse QueryObjects
rs
            forall s a. s -> Getting (First a) s a -> Maybe a
Lens.^? Lens' QueryObjectsResponse (Maybe Text)
queryObjectsResponse_marker
            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.$ QueryObjects
rq
          forall a b. a -> (a -> b) -> b
Prelude.& Lens' QueryObjects (Maybe Text)
queryObjects_marker
          forall s t a b. ASetter s t a b -> b -> s -> t
Lens..~ AWSResponse QueryObjects
rs
          forall s a. s -> Getting (First a) s a -> Maybe a
Lens.^? Lens' QueryObjectsResponse (Maybe Text)
queryObjectsResponse_marker
          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 QueryObjects where
  type AWSResponse QueryObjects = QueryObjectsResponse
  request :: (Service -> Service) -> QueryObjects -> Request QueryObjects
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 QueryObjects
-> ClientResponse ClientBody
-> m (Either Error (ClientResponse (AWSResponse QueryObjects)))
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 Bool
-> Maybe [Text] -> Maybe Text -> Int -> QueryObjectsResponse
QueryObjectsResponse'
            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
"hasMoreResults")
            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
"ids" 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
"marker")
            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 QueryObjects where
  hashWithSalt :: Int -> QueryObjects -> Int
hashWithSalt Int
_salt QueryObjects' {Maybe Int
Maybe Text
Maybe Query
Text
sphere :: Text
pipelineId :: Text
query :: Maybe Query
marker :: Maybe Text
limit :: Maybe Int
$sel:sphere:QueryObjects' :: QueryObjects -> Text
$sel:pipelineId:QueryObjects' :: QueryObjects -> Text
$sel:query:QueryObjects' :: QueryObjects -> Maybe Query
$sel:marker:QueryObjects' :: QueryObjects -> Maybe Text
$sel:limit:QueryObjects' :: QueryObjects -> Maybe Int
..} =
    Int
_salt
      forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Maybe Int
limit
      forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Maybe Text
marker
      forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Maybe Query
query
      forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Text
pipelineId
      forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Text
sphere

instance Prelude.NFData QueryObjects where
  rnf :: QueryObjects -> ()
rnf QueryObjects' {Maybe Int
Maybe Text
Maybe Query
Text
sphere :: Text
pipelineId :: Text
query :: Maybe Query
marker :: Maybe Text
limit :: Maybe Int
$sel:sphere:QueryObjects' :: QueryObjects -> Text
$sel:pipelineId:QueryObjects' :: QueryObjects -> Text
$sel:query:QueryObjects' :: QueryObjects -> Maybe Query
$sel:marker:QueryObjects' :: QueryObjects -> Maybe Text
$sel:limit:QueryObjects' :: QueryObjects -> Maybe Int
..} =
    forall a. NFData a => a -> ()
Prelude.rnf Maybe Int
limit
      seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf Maybe Text
marker
      seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf Maybe Query
query
      seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf Text
pipelineId
      seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf Text
sphere

instance Data.ToHeaders QueryObjects where
  toHeaders :: QueryObjects -> 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
"DataPipeline.QueryObjects" :: 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 QueryObjects where
  toJSON :: QueryObjects -> Value
toJSON QueryObjects' {Maybe Int
Maybe Text
Maybe Query
Text
sphere :: Text
pipelineId :: Text
query :: Maybe Query
marker :: Maybe Text
limit :: Maybe Int
$sel:sphere:QueryObjects' :: QueryObjects -> Text
$sel:pipelineId:QueryObjects' :: QueryObjects -> Text
$sel:query:QueryObjects' :: QueryObjects -> Maybe Query
$sel:marker:QueryObjects' :: QueryObjects -> Maybe Text
$sel:limit:QueryObjects' :: QueryObjects -> Maybe Int
..} =
    [Pair] -> Value
Data.object
      ( forall a. [Maybe a] -> [a]
Prelude.catMaybes
          [ (Key
"limit" 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 Int
limit,
            (Key
"marker" 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
marker,
            (Key
"query" 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 Query
query,
            forall a. a -> Maybe a
Prelude.Just (Key
"pipelineId" forall kv v. (KeyValue kv, ToJSON v) => Key -> v -> kv
Data..= Text
pipelineId),
            forall a. a -> Maybe a
Prelude.Just (Key
"sphere" forall kv v. (KeyValue kv, ToJSON v) => Key -> v -> kv
Data..= Text
sphere)
          ]
      )

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

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

-- | Contains the output of QueryObjects.
--
-- /See:/ 'newQueryObjectsResponse' smart constructor.
data QueryObjectsResponse = QueryObjectsResponse'
  { -- | Indicates whether there are more results that can be obtained by a
    -- subsequent call.
    QueryObjectsResponse -> Maybe Bool
hasMoreResults :: Prelude.Maybe Prelude.Bool,
    -- | The identifiers that match the query selectors.
    QueryObjectsResponse -> Maybe [Text]
ids :: Prelude.Maybe [Prelude.Text],
    -- | The starting point for the next page of results. To view the next page
    -- of results, call @QueryObjects@ again with this marker value. If the
    -- value is null, there are no more results.
    QueryObjectsResponse -> Maybe Text
marker :: Prelude.Maybe Prelude.Text,
    -- | The response's http status code.
    QueryObjectsResponse -> Int
httpStatus :: Prelude.Int
  }
  deriving (QueryObjectsResponse -> QueryObjectsResponse -> Bool
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: QueryObjectsResponse -> QueryObjectsResponse -> Bool
$c/= :: QueryObjectsResponse -> QueryObjectsResponse -> Bool
== :: QueryObjectsResponse -> QueryObjectsResponse -> Bool
$c== :: QueryObjectsResponse -> QueryObjectsResponse -> Bool
Prelude.Eq, ReadPrec [QueryObjectsResponse]
ReadPrec QueryObjectsResponse
Int -> ReadS QueryObjectsResponse
ReadS [QueryObjectsResponse]
forall a.
(Int -> ReadS a)
-> ReadS [a] -> ReadPrec a -> ReadPrec [a] -> Read a
readListPrec :: ReadPrec [QueryObjectsResponse]
$creadListPrec :: ReadPrec [QueryObjectsResponse]
readPrec :: ReadPrec QueryObjectsResponse
$creadPrec :: ReadPrec QueryObjectsResponse
readList :: ReadS [QueryObjectsResponse]
$creadList :: ReadS [QueryObjectsResponse]
readsPrec :: Int -> ReadS QueryObjectsResponse
$creadsPrec :: Int -> ReadS QueryObjectsResponse
Prelude.Read, Int -> QueryObjectsResponse -> ShowS
[QueryObjectsResponse] -> ShowS
QueryObjectsResponse -> String
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [QueryObjectsResponse] -> ShowS
$cshowList :: [QueryObjectsResponse] -> ShowS
show :: QueryObjectsResponse -> String
$cshow :: QueryObjectsResponse -> String
showsPrec :: Int -> QueryObjectsResponse -> ShowS
$cshowsPrec :: Int -> QueryObjectsResponse -> ShowS
Prelude.Show, forall x. Rep QueryObjectsResponse x -> QueryObjectsResponse
forall x. QueryObjectsResponse -> Rep QueryObjectsResponse x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cto :: forall x. Rep QueryObjectsResponse x -> QueryObjectsResponse
$cfrom :: forall x. QueryObjectsResponse -> Rep QueryObjectsResponse x
Prelude.Generic)

-- |
-- Create a value of 'QueryObjectsResponse' 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:
--
-- 'hasMoreResults', 'queryObjectsResponse_hasMoreResults' - Indicates whether there are more results that can be obtained by a
-- subsequent call.
--
-- 'ids', 'queryObjectsResponse_ids' - The identifiers that match the query selectors.
--
-- 'marker', 'queryObjectsResponse_marker' - The starting point for the next page of results. To view the next page
-- of results, call @QueryObjects@ again with this marker value. If the
-- value is null, there are no more results.
--
-- 'httpStatus', 'queryObjectsResponse_httpStatus' - The response's http status code.
newQueryObjectsResponse ::
  -- | 'httpStatus'
  Prelude.Int ->
  QueryObjectsResponse
newQueryObjectsResponse :: Int -> QueryObjectsResponse
newQueryObjectsResponse Int
pHttpStatus_ =
  QueryObjectsResponse'
    { $sel:hasMoreResults:QueryObjectsResponse' :: Maybe Bool
hasMoreResults =
        forall a. Maybe a
Prelude.Nothing,
      $sel:ids:QueryObjectsResponse' :: Maybe [Text]
ids = forall a. Maybe a
Prelude.Nothing,
      $sel:marker:QueryObjectsResponse' :: Maybe Text
marker = forall a. Maybe a
Prelude.Nothing,
      $sel:httpStatus:QueryObjectsResponse' :: Int
httpStatus = Int
pHttpStatus_
    }

-- | Indicates whether there are more results that can be obtained by a
-- subsequent call.
queryObjectsResponse_hasMoreResults :: Lens.Lens' QueryObjectsResponse (Prelude.Maybe Prelude.Bool)
queryObjectsResponse_hasMoreResults :: Lens' QueryObjectsResponse (Maybe Bool)
queryObjectsResponse_hasMoreResults = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\QueryObjectsResponse' {Maybe Bool
hasMoreResults :: Maybe Bool
$sel:hasMoreResults:QueryObjectsResponse' :: QueryObjectsResponse -> Maybe Bool
hasMoreResults} -> Maybe Bool
hasMoreResults) (\s :: QueryObjectsResponse
s@QueryObjectsResponse' {} Maybe Bool
a -> QueryObjectsResponse
s {$sel:hasMoreResults:QueryObjectsResponse' :: Maybe Bool
hasMoreResults = Maybe Bool
a} :: QueryObjectsResponse)

-- | The identifiers that match the query selectors.
queryObjectsResponse_ids :: Lens.Lens' QueryObjectsResponse (Prelude.Maybe [Prelude.Text])
queryObjectsResponse_ids :: Lens' QueryObjectsResponse (Maybe [Text])
queryObjectsResponse_ids = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\QueryObjectsResponse' {Maybe [Text]
ids :: Maybe [Text]
$sel:ids:QueryObjectsResponse' :: QueryObjectsResponse -> Maybe [Text]
ids} -> Maybe [Text]
ids) (\s :: QueryObjectsResponse
s@QueryObjectsResponse' {} Maybe [Text]
a -> QueryObjectsResponse
s {$sel:ids:QueryObjectsResponse' :: Maybe [Text]
ids = Maybe [Text]
a} :: QueryObjectsResponse) 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 starting point for the next page of results. To view the next page
-- of results, call @QueryObjects@ again with this marker value. If the
-- value is null, there are no more results.
queryObjectsResponse_marker :: Lens.Lens' QueryObjectsResponse (Prelude.Maybe Prelude.Text)
queryObjectsResponse_marker :: Lens' QueryObjectsResponse (Maybe Text)
queryObjectsResponse_marker = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\QueryObjectsResponse' {Maybe Text
marker :: Maybe Text
$sel:marker:QueryObjectsResponse' :: QueryObjectsResponse -> Maybe Text
marker} -> Maybe Text
marker) (\s :: QueryObjectsResponse
s@QueryObjectsResponse' {} Maybe Text
a -> QueryObjectsResponse
s {$sel:marker:QueryObjectsResponse' :: Maybe Text
marker = Maybe Text
a} :: QueryObjectsResponse)

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

instance Prelude.NFData QueryObjectsResponse where
  rnf :: QueryObjectsResponse -> ()
rnf QueryObjectsResponse' {Int
Maybe Bool
Maybe [Text]
Maybe Text
httpStatus :: Int
marker :: Maybe Text
ids :: Maybe [Text]
hasMoreResults :: Maybe Bool
$sel:httpStatus:QueryObjectsResponse' :: QueryObjectsResponse -> Int
$sel:marker:QueryObjectsResponse' :: QueryObjectsResponse -> Maybe Text
$sel:ids:QueryObjectsResponse' :: QueryObjectsResponse -> Maybe [Text]
$sel:hasMoreResults:QueryObjectsResponse' :: QueryObjectsResponse -> Maybe Bool
..} =
    forall a. NFData a => a -> ()
Prelude.rnf Maybe Bool
hasMoreResults
      seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf Maybe [Text]
ids
      seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf Maybe Text
marker
      seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf Int
httpStatus