{-# 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.Braket.SearchJobs
-- 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 for Amazon Braket jobs that match the specified filter values.
--
-- This operation returns paginated results.
module Amazonka.Braket.SearchJobs
  ( -- * Creating a Request
    SearchJobs (..),
    newSearchJobs,

    -- * Request Lenses
    searchJobs_maxResults,
    searchJobs_nextToken,
    searchJobs_filters,

    -- * Destructuring the Response
    SearchJobsResponse (..),
    newSearchJobsResponse,

    -- * Response Lenses
    searchJobsResponse_nextToken,
    searchJobsResponse_httpStatus,
    searchJobsResponse_jobs,
  )
where

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

-- | /See:/ 'newSearchJobs' smart constructor.
data SearchJobs = SearchJobs'
  { -- | The maximum number of results to return in the response.
    SearchJobs -> Maybe Natural
maxResults :: Prelude.Maybe Prelude.Natural,
    -- | A token used for pagination of results returned in the response. Use the
    -- token returned from the previous request to continue results where the
    -- previous request ended.
    SearchJobs -> Maybe Text
nextToken :: Prelude.Maybe Prelude.Text,
    -- | The filter values to use when searching for a job.
    SearchJobs -> [SearchJobsFilter]
filters :: [SearchJobsFilter]
  }
  deriving (SearchJobs -> SearchJobs -> Bool
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: SearchJobs -> SearchJobs -> Bool
$c/= :: SearchJobs -> SearchJobs -> Bool
== :: SearchJobs -> SearchJobs -> Bool
$c== :: SearchJobs -> SearchJobs -> Bool
Prelude.Eq, ReadPrec [SearchJobs]
ReadPrec SearchJobs
Int -> ReadS SearchJobs
ReadS [SearchJobs]
forall a.
(Int -> ReadS a)
-> ReadS [a] -> ReadPrec a -> ReadPrec [a] -> Read a
readListPrec :: ReadPrec [SearchJobs]
$creadListPrec :: ReadPrec [SearchJobs]
readPrec :: ReadPrec SearchJobs
$creadPrec :: ReadPrec SearchJobs
readList :: ReadS [SearchJobs]
$creadList :: ReadS [SearchJobs]
readsPrec :: Int -> ReadS SearchJobs
$creadsPrec :: Int -> ReadS SearchJobs
Prelude.Read, Int -> SearchJobs -> ShowS
[SearchJobs] -> ShowS
SearchJobs -> String
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [SearchJobs] -> ShowS
$cshowList :: [SearchJobs] -> ShowS
show :: SearchJobs -> String
$cshow :: SearchJobs -> String
showsPrec :: Int -> SearchJobs -> ShowS
$cshowsPrec :: Int -> SearchJobs -> ShowS
Prelude.Show, forall x. Rep SearchJobs x -> SearchJobs
forall x. SearchJobs -> Rep SearchJobs x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cto :: forall x. Rep SearchJobs x -> SearchJobs
$cfrom :: forall x. SearchJobs -> Rep SearchJobs x
Prelude.Generic)

-- |
-- Create a value of 'SearchJobs' 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', 'searchJobs_maxResults' - The maximum number of results to return in the response.
--
-- 'nextToken', 'searchJobs_nextToken' - A token used for pagination of results returned in the response. Use the
-- token returned from the previous request to continue results where the
-- previous request ended.
--
-- 'filters', 'searchJobs_filters' - The filter values to use when searching for a job.
newSearchJobs ::
  SearchJobs
newSearchJobs :: SearchJobs
newSearchJobs =
  SearchJobs'
    { $sel:maxResults:SearchJobs' :: Maybe Natural
maxResults = forall a. Maybe a
Prelude.Nothing,
      $sel:nextToken:SearchJobs' :: Maybe Text
nextToken = forall a. Maybe a
Prelude.Nothing,
      $sel:filters:SearchJobs' :: [SearchJobsFilter]
filters = forall a. Monoid a => a
Prelude.mempty
    }

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

-- | A token used for pagination of results returned in the response. Use the
-- token returned from the previous request to continue results where the
-- previous request ended.
searchJobs_nextToken :: Lens.Lens' SearchJobs (Prelude.Maybe Prelude.Text)
searchJobs_nextToken :: Lens' SearchJobs (Maybe Text)
searchJobs_nextToken = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\SearchJobs' {Maybe Text
nextToken :: Maybe Text
$sel:nextToken:SearchJobs' :: SearchJobs -> Maybe Text
nextToken} -> Maybe Text
nextToken) (\s :: SearchJobs
s@SearchJobs' {} Maybe Text
a -> SearchJobs
s {$sel:nextToken:SearchJobs' :: Maybe Text
nextToken = Maybe Text
a} :: SearchJobs)

-- | The filter values to use when searching for a job.
searchJobs_filters :: Lens.Lens' SearchJobs [SearchJobsFilter]
searchJobs_filters :: Lens' SearchJobs [SearchJobsFilter]
searchJobs_filters = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\SearchJobs' {[SearchJobsFilter]
filters :: [SearchJobsFilter]
$sel:filters:SearchJobs' :: SearchJobs -> [SearchJobsFilter]
filters} -> [SearchJobsFilter]
filters) (\s :: SearchJobs
s@SearchJobs' {} [SearchJobsFilter]
a -> SearchJobs
s {$sel:filters:SearchJobs' :: [SearchJobsFilter]
filters = [SearchJobsFilter]
a} :: SearchJobs) 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 Core.AWSPager SearchJobs where
  page :: SearchJobs -> AWSResponse SearchJobs -> Maybe SearchJobs
page SearchJobs
rq AWSResponse SearchJobs
rs
    | forall a. AWSTruncated a => a -> Bool
Core.stop
        ( AWSResponse SearchJobs
rs
            forall s a. s -> Getting (First a) s a -> Maybe a
Lens.^? Lens' SearchJobsResponse (Maybe Text)
searchJobsResponse_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 SearchJobs
rs forall s a. s -> Getting a s a -> a
Lens.^. Lens' SearchJobsResponse [JobSummary]
searchJobsResponse_jobs) =
        forall a. Maybe a
Prelude.Nothing
    | Bool
Prelude.otherwise =
        forall a. a -> Maybe a
Prelude.Just
          forall a b. (a -> b) -> a -> b
Prelude.$ SearchJobs
rq
          forall a b. a -> (a -> b) -> b
Prelude.& Lens' SearchJobs (Maybe Text)
searchJobs_nextToken
          forall s t a b. ASetter s t a b -> b -> s -> t
Lens..~ AWSResponse SearchJobs
rs
          forall s a. s -> Getting (First a) s a -> Maybe a
Lens.^? Lens' SearchJobsResponse (Maybe Text)
searchJobsResponse_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 SearchJobs where
  type AWSResponse SearchJobs = SearchJobsResponse
  request :: (Service -> Service) -> SearchJobs -> Request SearchJobs
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 SearchJobs
-> ClientResponse ClientBody
-> m (Either Error (ClientResponse (AWSResponse SearchJobs)))
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 -> [JobSummary] -> SearchJobsResponse
SearchJobsResponse'
            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 (Maybe a)
Data..?> Key
"jobs" forall (f :: * -> *) a. Functor f => f (Maybe a) -> a -> f a
Core..!@ forall a. Monoid a => a
Prelude.mempty)
      )

instance Prelude.Hashable SearchJobs where
  hashWithSalt :: Int -> SearchJobs -> Int
hashWithSalt Int
_salt SearchJobs' {[SearchJobsFilter]
Maybe Natural
Maybe Text
filters :: [SearchJobsFilter]
nextToken :: Maybe Text
maxResults :: Maybe Natural
$sel:filters:SearchJobs' :: SearchJobs -> [SearchJobsFilter]
$sel:nextToken:SearchJobs' :: SearchJobs -> Maybe Text
$sel:maxResults:SearchJobs' :: SearchJobs -> 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` [SearchJobsFilter]
filters

instance Prelude.NFData SearchJobs where
  rnf :: SearchJobs -> ()
rnf SearchJobs' {[SearchJobsFilter]
Maybe Natural
Maybe Text
filters :: [SearchJobsFilter]
nextToken :: Maybe Text
maxResults :: Maybe Natural
$sel:filters:SearchJobs' :: SearchJobs -> [SearchJobsFilter]
$sel:nextToken:SearchJobs' :: SearchJobs -> Maybe Text
$sel:maxResults:SearchJobs' :: SearchJobs -> 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 [SearchJobsFilter]
filters

instance Data.ToHeaders SearchJobs where
  toHeaders :: SearchJobs -> 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 SearchJobs where
  toJSON :: SearchJobs -> Value
toJSON SearchJobs' {[SearchJobsFilter]
Maybe Natural
Maybe Text
filters :: [SearchJobsFilter]
nextToken :: Maybe Text
maxResults :: Maybe Natural
$sel:filters:SearchJobs' :: SearchJobs -> [SearchJobsFilter]
$sel:nextToken:SearchJobs' :: SearchJobs -> Maybe Text
$sel:maxResults:SearchJobs' :: SearchJobs -> 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
"filters" forall kv v. (KeyValue kv, ToJSON v) => Key -> v -> kv
Data..= [SearchJobsFilter]
filters)
          ]
      )

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

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

-- | /See:/ 'newSearchJobsResponse' smart constructor.
data SearchJobsResponse = SearchJobsResponse'
  { -- | A token used for pagination of results, or @null@ if there are no
    -- additional results. Use the token value in a subsequent request to
    -- continue results where the previous request ended.
    SearchJobsResponse -> Maybe Text
nextToken :: Prelude.Maybe Prelude.Text,
    -- | The response's http status code.
    SearchJobsResponse -> Int
httpStatus :: Prelude.Int,
    -- | An array of @JobSummary@ objects for devices that match the specified
    -- filter values.
    SearchJobsResponse -> [JobSummary]
jobs :: [JobSummary]
  }
  deriving (SearchJobsResponse -> SearchJobsResponse -> Bool
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: SearchJobsResponse -> SearchJobsResponse -> Bool
$c/= :: SearchJobsResponse -> SearchJobsResponse -> Bool
== :: SearchJobsResponse -> SearchJobsResponse -> Bool
$c== :: SearchJobsResponse -> SearchJobsResponse -> Bool
Prelude.Eq, ReadPrec [SearchJobsResponse]
ReadPrec SearchJobsResponse
Int -> ReadS SearchJobsResponse
ReadS [SearchJobsResponse]
forall a.
(Int -> ReadS a)
-> ReadS [a] -> ReadPrec a -> ReadPrec [a] -> Read a
readListPrec :: ReadPrec [SearchJobsResponse]
$creadListPrec :: ReadPrec [SearchJobsResponse]
readPrec :: ReadPrec SearchJobsResponse
$creadPrec :: ReadPrec SearchJobsResponse
readList :: ReadS [SearchJobsResponse]
$creadList :: ReadS [SearchJobsResponse]
readsPrec :: Int -> ReadS SearchJobsResponse
$creadsPrec :: Int -> ReadS SearchJobsResponse
Prelude.Read, Int -> SearchJobsResponse -> ShowS
[SearchJobsResponse] -> ShowS
SearchJobsResponse -> String
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [SearchJobsResponse] -> ShowS
$cshowList :: [SearchJobsResponse] -> ShowS
show :: SearchJobsResponse -> String
$cshow :: SearchJobsResponse -> String
showsPrec :: Int -> SearchJobsResponse -> ShowS
$cshowsPrec :: Int -> SearchJobsResponse -> ShowS
Prelude.Show, forall x. Rep SearchJobsResponse x -> SearchJobsResponse
forall x. SearchJobsResponse -> Rep SearchJobsResponse x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cto :: forall x. Rep SearchJobsResponse x -> SearchJobsResponse
$cfrom :: forall x. SearchJobsResponse -> Rep SearchJobsResponse x
Prelude.Generic)

-- |
-- Create a value of 'SearchJobsResponse' 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', 'searchJobsResponse_nextToken' - A token used for pagination of results, or @null@ if there are no
-- additional results. Use the token value in a subsequent request to
-- continue results where the previous request ended.
--
-- 'httpStatus', 'searchJobsResponse_httpStatus' - The response's http status code.
--
-- 'jobs', 'searchJobsResponse_jobs' - An array of @JobSummary@ objects for devices that match the specified
-- filter values.
newSearchJobsResponse ::
  -- | 'httpStatus'
  Prelude.Int ->
  SearchJobsResponse
newSearchJobsResponse :: Int -> SearchJobsResponse
newSearchJobsResponse Int
pHttpStatus_ =
  SearchJobsResponse'
    { $sel:nextToken:SearchJobsResponse' :: Maybe Text
nextToken = forall a. Maybe a
Prelude.Nothing,
      $sel:httpStatus:SearchJobsResponse' :: Int
httpStatus = Int
pHttpStatus_,
      $sel:jobs:SearchJobsResponse' :: [JobSummary]
jobs = forall a. Monoid a => a
Prelude.mempty
    }

-- | A token used for pagination of results, or @null@ if there are no
-- additional results. Use the token value in a subsequent request to
-- continue results where the previous request ended.
searchJobsResponse_nextToken :: Lens.Lens' SearchJobsResponse (Prelude.Maybe Prelude.Text)
searchJobsResponse_nextToken :: Lens' SearchJobsResponse (Maybe Text)
searchJobsResponse_nextToken = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\SearchJobsResponse' {Maybe Text
nextToken :: Maybe Text
$sel:nextToken:SearchJobsResponse' :: SearchJobsResponse -> Maybe Text
nextToken} -> Maybe Text
nextToken) (\s :: SearchJobsResponse
s@SearchJobsResponse' {} Maybe Text
a -> SearchJobsResponse
s {$sel:nextToken:SearchJobsResponse' :: Maybe Text
nextToken = Maybe Text
a} :: SearchJobsResponse)

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

-- | An array of @JobSummary@ objects for devices that match the specified
-- filter values.
searchJobsResponse_jobs :: Lens.Lens' SearchJobsResponse [JobSummary]
searchJobsResponse_jobs :: Lens' SearchJobsResponse [JobSummary]
searchJobsResponse_jobs = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\SearchJobsResponse' {[JobSummary]
jobs :: [JobSummary]
$sel:jobs:SearchJobsResponse' :: SearchJobsResponse -> [JobSummary]
jobs} -> [JobSummary]
jobs) (\s :: SearchJobsResponse
s@SearchJobsResponse' {} [JobSummary]
a -> SearchJobsResponse
s {$sel:jobs:SearchJobsResponse' :: [JobSummary]
jobs = [JobSummary]
a} :: SearchJobsResponse) 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 SearchJobsResponse where
  rnf :: SearchJobsResponse -> ()
rnf SearchJobsResponse' {Int
[JobSummary]
Maybe Text
jobs :: [JobSummary]
httpStatus :: Int
nextToken :: Maybe Text
$sel:jobs:SearchJobsResponse' :: SearchJobsResponse -> [JobSummary]
$sel:httpStatus:SearchJobsResponse' :: SearchJobsResponse -> Int
$sel:nextToken:SearchJobsResponse' :: SearchJobsResponse -> 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 [JobSummary]
jobs