{-# 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.SageMakerGeoSpatial.ListVectorEnrichmentJobs
-- Copyright   : (c) 2013-2023 Brendan Hay
-- License     : Mozilla Public License, v. 2.0.
-- Maintainer  : Brendan Hay
-- Stability   : auto-generated
-- Portability : non-portable (GHC extensions)
--
-- Retrieves a list of vector enrichment jobs.
--
-- This operation returns paginated results.
module Amazonka.SageMakerGeoSpatial.ListVectorEnrichmentJobs
  ( -- * Creating a Request
    ListVectorEnrichmentJobs (..),
    newListVectorEnrichmentJobs,

    -- * Request Lenses
    listVectorEnrichmentJobs_maxResults,
    listVectorEnrichmentJobs_nextToken,
    listVectorEnrichmentJobs_sortBy,
    listVectorEnrichmentJobs_sortOrder,
    listVectorEnrichmentJobs_statusEquals,

    -- * Destructuring the Response
    ListVectorEnrichmentJobsResponse (..),
    newListVectorEnrichmentJobsResponse,

    -- * Response Lenses
    listVectorEnrichmentJobsResponse_nextToken,
    listVectorEnrichmentJobsResponse_httpStatus,
    listVectorEnrichmentJobsResponse_vectorEnrichmentJobSummaries,
  )
where

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
import Amazonka.SageMakerGeoSpatial.Types

-- | /See:/ 'newListVectorEnrichmentJobs' smart constructor.
data ListVectorEnrichmentJobs = ListVectorEnrichmentJobs'
  { -- | The maximum number of items to return.
    ListVectorEnrichmentJobs -> Maybe Natural
maxResults :: Prelude.Maybe Prelude.Natural,
    -- | If the previous response was truncated, you receive this token. Use it
    -- in your next request to receive the next set of results.
    ListVectorEnrichmentJobs -> Maybe (Sensitive Text)
nextToken :: Prelude.Maybe (Data.Sensitive Prelude.Text),
    -- | The parameter by which to sort the results.
    ListVectorEnrichmentJobs -> Maybe Text
sortBy :: Prelude.Maybe Prelude.Text,
    -- | An optional value that specifies whether you want the results sorted in
    -- @Ascending@ or @Descending@ order.
    ListVectorEnrichmentJobs -> Maybe SortOrder
sortOrder :: Prelude.Maybe SortOrder,
    -- | A filter that retrieves only jobs with a specific status.
    ListVectorEnrichmentJobs -> Maybe Text
statusEquals :: Prelude.Maybe Prelude.Text
  }
  deriving (ListVectorEnrichmentJobs -> ListVectorEnrichmentJobs -> Bool
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: ListVectorEnrichmentJobs -> ListVectorEnrichmentJobs -> Bool
$c/= :: ListVectorEnrichmentJobs -> ListVectorEnrichmentJobs -> Bool
== :: ListVectorEnrichmentJobs -> ListVectorEnrichmentJobs -> Bool
$c== :: ListVectorEnrichmentJobs -> ListVectorEnrichmentJobs -> Bool
Prelude.Eq, Int -> ListVectorEnrichmentJobs -> ShowS
[ListVectorEnrichmentJobs] -> ShowS
ListVectorEnrichmentJobs -> String
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [ListVectorEnrichmentJobs] -> ShowS
$cshowList :: [ListVectorEnrichmentJobs] -> ShowS
show :: ListVectorEnrichmentJobs -> String
$cshow :: ListVectorEnrichmentJobs -> String
showsPrec :: Int -> ListVectorEnrichmentJobs -> ShowS
$cshowsPrec :: Int -> ListVectorEnrichmentJobs -> ShowS
Prelude.Show, forall x.
Rep ListVectorEnrichmentJobs x -> ListVectorEnrichmentJobs
forall x.
ListVectorEnrichmentJobs -> Rep ListVectorEnrichmentJobs x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cto :: forall x.
Rep ListVectorEnrichmentJobs x -> ListVectorEnrichmentJobs
$cfrom :: forall x.
ListVectorEnrichmentJobs -> Rep ListVectorEnrichmentJobs x
Prelude.Generic)

-- |
-- Create a value of 'ListVectorEnrichmentJobs' 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', 'listVectorEnrichmentJobs_maxResults' - The maximum number of items to return.
--
-- 'nextToken', 'listVectorEnrichmentJobs_nextToken' - If the previous response was truncated, you receive this token. Use it
-- in your next request to receive the next set of results.
--
-- 'sortBy', 'listVectorEnrichmentJobs_sortBy' - The parameter by which to sort the results.
--
-- 'sortOrder', 'listVectorEnrichmentJobs_sortOrder' - An optional value that specifies whether you want the results sorted in
-- @Ascending@ or @Descending@ order.
--
-- 'statusEquals', 'listVectorEnrichmentJobs_statusEquals' - A filter that retrieves only jobs with a specific status.
newListVectorEnrichmentJobs ::
  ListVectorEnrichmentJobs
newListVectorEnrichmentJobs :: ListVectorEnrichmentJobs
newListVectorEnrichmentJobs =
  ListVectorEnrichmentJobs'
    { $sel:maxResults:ListVectorEnrichmentJobs' :: Maybe Natural
maxResults =
        forall a. Maybe a
Prelude.Nothing,
      $sel:nextToken:ListVectorEnrichmentJobs' :: Maybe (Sensitive Text)
nextToken = forall a. Maybe a
Prelude.Nothing,
      $sel:sortBy:ListVectorEnrichmentJobs' :: Maybe Text
sortBy = forall a. Maybe a
Prelude.Nothing,
      $sel:sortOrder:ListVectorEnrichmentJobs' :: Maybe SortOrder
sortOrder = forall a. Maybe a
Prelude.Nothing,
      $sel:statusEquals:ListVectorEnrichmentJobs' :: Maybe Text
statusEquals = forall a. Maybe a
Prelude.Nothing
    }

-- | The maximum number of items to return.
listVectorEnrichmentJobs_maxResults :: Lens.Lens' ListVectorEnrichmentJobs (Prelude.Maybe Prelude.Natural)
listVectorEnrichmentJobs_maxResults :: Lens' ListVectorEnrichmentJobs (Maybe Natural)
listVectorEnrichmentJobs_maxResults = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\ListVectorEnrichmentJobs' {Maybe Natural
maxResults :: Maybe Natural
$sel:maxResults:ListVectorEnrichmentJobs' :: ListVectorEnrichmentJobs -> Maybe Natural
maxResults} -> Maybe Natural
maxResults) (\s :: ListVectorEnrichmentJobs
s@ListVectorEnrichmentJobs' {} Maybe Natural
a -> ListVectorEnrichmentJobs
s {$sel:maxResults:ListVectorEnrichmentJobs' :: Maybe Natural
maxResults = Maybe Natural
a} :: ListVectorEnrichmentJobs)

-- | If the previous response was truncated, you receive this token. Use it
-- in your next request to receive the next set of results.
listVectorEnrichmentJobs_nextToken :: Lens.Lens' ListVectorEnrichmentJobs (Prelude.Maybe Prelude.Text)
listVectorEnrichmentJobs_nextToken :: Lens' ListVectorEnrichmentJobs (Maybe Text)
listVectorEnrichmentJobs_nextToken = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\ListVectorEnrichmentJobs' {Maybe (Sensitive Text)
nextToken :: Maybe (Sensitive Text)
$sel:nextToken:ListVectorEnrichmentJobs' :: ListVectorEnrichmentJobs -> Maybe (Sensitive Text)
nextToken} -> Maybe (Sensitive Text)
nextToken) (\s :: ListVectorEnrichmentJobs
s@ListVectorEnrichmentJobs' {} Maybe (Sensitive Text)
a -> ListVectorEnrichmentJobs
s {$sel:nextToken:ListVectorEnrichmentJobs' :: Maybe (Sensitive Text)
nextToken = Maybe (Sensitive Text)
a} :: ListVectorEnrichmentJobs) 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 a. Iso' (Sensitive a) a
Data._Sensitive

-- | The parameter by which to sort the results.
listVectorEnrichmentJobs_sortBy :: Lens.Lens' ListVectorEnrichmentJobs (Prelude.Maybe Prelude.Text)
listVectorEnrichmentJobs_sortBy :: Lens' ListVectorEnrichmentJobs (Maybe Text)
listVectorEnrichmentJobs_sortBy = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\ListVectorEnrichmentJobs' {Maybe Text
sortBy :: Maybe Text
$sel:sortBy:ListVectorEnrichmentJobs' :: ListVectorEnrichmentJobs -> Maybe Text
sortBy} -> Maybe Text
sortBy) (\s :: ListVectorEnrichmentJobs
s@ListVectorEnrichmentJobs' {} Maybe Text
a -> ListVectorEnrichmentJobs
s {$sel:sortBy:ListVectorEnrichmentJobs' :: Maybe Text
sortBy = Maybe Text
a} :: ListVectorEnrichmentJobs)

-- | An optional value that specifies whether you want the results sorted in
-- @Ascending@ or @Descending@ order.
listVectorEnrichmentJobs_sortOrder :: Lens.Lens' ListVectorEnrichmentJobs (Prelude.Maybe SortOrder)
listVectorEnrichmentJobs_sortOrder :: Lens' ListVectorEnrichmentJobs (Maybe SortOrder)
listVectorEnrichmentJobs_sortOrder = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\ListVectorEnrichmentJobs' {Maybe SortOrder
sortOrder :: Maybe SortOrder
$sel:sortOrder:ListVectorEnrichmentJobs' :: ListVectorEnrichmentJobs -> Maybe SortOrder
sortOrder} -> Maybe SortOrder
sortOrder) (\s :: ListVectorEnrichmentJobs
s@ListVectorEnrichmentJobs' {} Maybe SortOrder
a -> ListVectorEnrichmentJobs
s {$sel:sortOrder:ListVectorEnrichmentJobs' :: Maybe SortOrder
sortOrder = Maybe SortOrder
a} :: ListVectorEnrichmentJobs)

-- | A filter that retrieves only jobs with a specific status.
listVectorEnrichmentJobs_statusEquals :: Lens.Lens' ListVectorEnrichmentJobs (Prelude.Maybe Prelude.Text)
listVectorEnrichmentJobs_statusEquals :: Lens' ListVectorEnrichmentJobs (Maybe Text)
listVectorEnrichmentJobs_statusEquals = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\ListVectorEnrichmentJobs' {Maybe Text
statusEquals :: Maybe Text
$sel:statusEquals:ListVectorEnrichmentJobs' :: ListVectorEnrichmentJobs -> Maybe Text
statusEquals} -> Maybe Text
statusEquals) (\s :: ListVectorEnrichmentJobs
s@ListVectorEnrichmentJobs' {} Maybe Text
a -> ListVectorEnrichmentJobs
s {$sel:statusEquals:ListVectorEnrichmentJobs' :: Maybe Text
statusEquals = Maybe Text
a} :: ListVectorEnrichmentJobs)

instance Core.AWSPager ListVectorEnrichmentJobs where
  page :: ListVectorEnrichmentJobs
-> AWSResponse ListVectorEnrichmentJobs
-> Maybe ListVectorEnrichmentJobs
page ListVectorEnrichmentJobs
rq AWSResponse ListVectorEnrichmentJobs
rs
    | forall a. AWSTruncated a => a -> Bool
Core.stop
        ( AWSResponse ListVectorEnrichmentJobs
rs
            forall s a. s -> Getting (First a) s a -> Maybe a
Lens.^? Lens' ListVectorEnrichmentJobsResponse (Maybe Text)
listVectorEnrichmentJobsResponse_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 ListVectorEnrichmentJobs
rs
            forall s a. s -> Getting a s a -> a
Lens.^. Lens'
  ListVectorEnrichmentJobsResponse
  [ListVectorEnrichmentJobOutputConfig]
listVectorEnrichmentJobsResponse_vectorEnrichmentJobSummaries
        ) =
        forall a. Maybe a
Prelude.Nothing
    | Bool
Prelude.otherwise =
        forall a. a -> Maybe a
Prelude.Just
          forall a b. (a -> b) -> a -> b
Prelude.$ ListVectorEnrichmentJobs
rq
          forall a b. a -> (a -> b) -> b
Prelude.& Lens' ListVectorEnrichmentJobs (Maybe Text)
listVectorEnrichmentJobs_nextToken
          forall s t a b. ASetter s t a b -> b -> s -> t
Lens..~ AWSResponse ListVectorEnrichmentJobs
rs
          forall s a. s -> Getting (First a) s a -> Maybe a
Lens.^? Lens' ListVectorEnrichmentJobsResponse (Maybe Text)
listVectorEnrichmentJobsResponse_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 ListVectorEnrichmentJobs where
  type
    AWSResponse ListVectorEnrichmentJobs =
      ListVectorEnrichmentJobsResponse
  request :: (Service -> Service)
-> ListVectorEnrichmentJobs -> Request ListVectorEnrichmentJobs
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 ListVectorEnrichmentJobs
-> ClientResponse ClientBody
-> m (Either
        Error (ClientResponse (AWSResponse ListVectorEnrichmentJobs)))
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 (Sensitive Text)
-> Int
-> [ListVectorEnrichmentJobOutputConfig]
-> ListVectorEnrichmentJobsResponse
ListVectorEnrichmentJobsResponse'
            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
"VectorEnrichmentJobSummaries"
                            forall (f :: * -> *) a. Functor f => f (Maybe a) -> a -> f a
Core..!@ forall a. Monoid a => a
Prelude.mempty
                        )
      )

instance Prelude.Hashable ListVectorEnrichmentJobs where
  hashWithSalt :: Int -> ListVectorEnrichmentJobs -> Int
hashWithSalt Int
_salt ListVectorEnrichmentJobs' {Maybe Natural
Maybe Text
Maybe (Sensitive Text)
Maybe SortOrder
statusEquals :: Maybe Text
sortOrder :: Maybe SortOrder
sortBy :: Maybe Text
nextToken :: Maybe (Sensitive Text)
maxResults :: Maybe Natural
$sel:statusEquals:ListVectorEnrichmentJobs' :: ListVectorEnrichmentJobs -> Maybe Text
$sel:sortOrder:ListVectorEnrichmentJobs' :: ListVectorEnrichmentJobs -> Maybe SortOrder
$sel:sortBy:ListVectorEnrichmentJobs' :: ListVectorEnrichmentJobs -> Maybe Text
$sel:nextToken:ListVectorEnrichmentJobs' :: ListVectorEnrichmentJobs -> Maybe (Sensitive Text)
$sel:maxResults:ListVectorEnrichmentJobs' :: ListVectorEnrichmentJobs -> 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 (Sensitive Text)
nextToken
      forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Maybe Text
sortBy
      forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Maybe SortOrder
sortOrder
      forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Maybe Text
statusEquals

instance Prelude.NFData ListVectorEnrichmentJobs where
  rnf :: ListVectorEnrichmentJobs -> ()
rnf ListVectorEnrichmentJobs' {Maybe Natural
Maybe Text
Maybe (Sensitive Text)
Maybe SortOrder
statusEquals :: Maybe Text
sortOrder :: Maybe SortOrder
sortBy :: Maybe Text
nextToken :: Maybe (Sensitive Text)
maxResults :: Maybe Natural
$sel:statusEquals:ListVectorEnrichmentJobs' :: ListVectorEnrichmentJobs -> Maybe Text
$sel:sortOrder:ListVectorEnrichmentJobs' :: ListVectorEnrichmentJobs -> Maybe SortOrder
$sel:sortBy:ListVectorEnrichmentJobs' :: ListVectorEnrichmentJobs -> Maybe Text
$sel:nextToken:ListVectorEnrichmentJobs' :: ListVectorEnrichmentJobs -> Maybe (Sensitive Text)
$sel:maxResults:ListVectorEnrichmentJobs' :: ListVectorEnrichmentJobs -> 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 (Sensitive Text)
nextToken
      seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf Maybe Text
sortBy
      seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf Maybe SortOrder
sortOrder
      seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf Maybe Text
statusEquals

instance Data.ToHeaders ListVectorEnrichmentJobs where
  toHeaders :: ListVectorEnrichmentJobs -> 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 ListVectorEnrichmentJobs where
  toJSON :: ListVectorEnrichmentJobs -> Value
toJSON ListVectorEnrichmentJobs' {Maybe Natural
Maybe Text
Maybe (Sensitive Text)
Maybe SortOrder
statusEquals :: Maybe Text
sortOrder :: Maybe SortOrder
sortBy :: Maybe Text
nextToken :: Maybe (Sensitive Text)
maxResults :: Maybe Natural
$sel:statusEquals:ListVectorEnrichmentJobs' :: ListVectorEnrichmentJobs -> Maybe Text
$sel:sortOrder:ListVectorEnrichmentJobs' :: ListVectorEnrichmentJobs -> Maybe SortOrder
$sel:sortBy:ListVectorEnrichmentJobs' :: ListVectorEnrichmentJobs -> Maybe Text
$sel:nextToken:ListVectorEnrichmentJobs' :: ListVectorEnrichmentJobs -> Maybe (Sensitive Text)
$sel:maxResults:ListVectorEnrichmentJobs' :: ListVectorEnrichmentJobs -> 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 (Sensitive Text)
nextToken,
            (Key
"SortBy" 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
sortBy,
            (Key
"SortOrder" 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 SortOrder
sortOrder,
            (Key
"StatusEquals" 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
statusEquals
          ]
      )

instance Data.ToPath ListVectorEnrichmentJobs where
  toPath :: ListVectorEnrichmentJobs -> ByteString
toPath = forall a b. a -> b -> a
Prelude.const ByteString
"/list-vector-enrichment-jobs"

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

-- | /See:/ 'newListVectorEnrichmentJobsResponse' smart constructor.
data ListVectorEnrichmentJobsResponse = ListVectorEnrichmentJobsResponse'
  { -- | If the previous response was truncated, you receive this token. Use it
    -- in your next request to receive the next set of results.
    ListVectorEnrichmentJobsResponse -> Maybe (Sensitive Text)
nextToken :: Prelude.Maybe (Data.Sensitive Prelude.Text),
    -- | The response's http status code.
    ListVectorEnrichmentJobsResponse -> Int
httpStatus :: Prelude.Int,
    -- | Contains summary information about the Vector Enrichment jobs.
    ListVectorEnrichmentJobsResponse
-> [ListVectorEnrichmentJobOutputConfig]
vectorEnrichmentJobSummaries :: [ListVectorEnrichmentJobOutputConfig]
  }
  deriving (ListVectorEnrichmentJobsResponse
-> ListVectorEnrichmentJobsResponse -> Bool
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: ListVectorEnrichmentJobsResponse
-> ListVectorEnrichmentJobsResponse -> Bool
$c/= :: ListVectorEnrichmentJobsResponse
-> ListVectorEnrichmentJobsResponse -> Bool
== :: ListVectorEnrichmentJobsResponse
-> ListVectorEnrichmentJobsResponse -> Bool
$c== :: ListVectorEnrichmentJobsResponse
-> ListVectorEnrichmentJobsResponse -> Bool
Prelude.Eq, Int -> ListVectorEnrichmentJobsResponse -> ShowS
[ListVectorEnrichmentJobsResponse] -> ShowS
ListVectorEnrichmentJobsResponse -> String
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [ListVectorEnrichmentJobsResponse] -> ShowS
$cshowList :: [ListVectorEnrichmentJobsResponse] -> ShowS
show :: ListVectorEnrichmentJobsResponse -> String
$cshow :: ListVectorEnrichmentJobsResponse -> String
showsPrec :: Int -> ListVectorEnrichmentJobsResponse -> ShowS
$cshowsPrec :: Int -> ListVectorEnrichmentJobsResponse -> ShowS
Prelude.Show, forall x.
Rep ListVectorEnrichmentJobsResponse x
-> ListVectorEnrichmentJobsResponse
forall x.
ListVectorEnrichmentJobsResponse
-> Rep ListVectorEnrichmentJobsResponse x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cto :: forall x.
Rep ListVectorEnrichmentJobsResponse x
-> ListVectorEnrichmentJobsResponse
$cfrom :: forall x.
ListVectorEnrichmentJobsResponse
-> Rep ListVectorEnrichmentJobsResponse x
Prelude.Generic)

-- |
-- Create a value of 'ListVectorEnrichmentJobsResponse' 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', 'listVectorEnrichmentJobsResponse_nextToken' - If the previous response was truncated, you receive this token. Use it
-- in your next request to receive the next set of results.
--
-- 'httpStatus', 'listVectorEnrichmentJobsResponse_httpStatus' - The response's http status code.
--
-- 'vectorEnrichmentJobSummaries', 'listVectorEnrichmentJobsResponse_vectorEnrichmentJobSummaries' - Contains summary information about the Vector Enrichment jobs.
newListVectorEnrichmentJobsResponse ::
  -- | 'httpStatus'
  Prelude.Int ->
  ListVectorEnrichmentJobsResponse
newListVectorEnrichmentJobsResponse :: Int -> ListVectorEnrichmentJobsResponse
newListVectorEnrichmentJobsResponse Int
pHttpStatus_ =
  ListVectorEnrichmentJobsResponse'
    { $sel:nextToken:ListVectorEnrichmentJobsResponse' :: Maybe (Sensitive Text)
nextToken =
        forall a. Maybe a
Prelude.Nothing,
      $sel:httpStatus:ListVectorEnrichmentJobsResponse' :: Int
httpStatus = Int
pHttpStatus_,
      $sel:vectorEnrichmentJobSummaries:ListVectorEnrichmentJobsResponse' :: [ListVectorEnrichmentJobOutputConfig]
vectorEnrichmentJobSummaries =
        forall a. Monoid a => a
Prelude.mempty
    }

-- | If the previous response was truncated, you receive this token. Use it
-- in your next request to receive the next set of results.
listVectorEnrichmentJobsResponse_nextToken :: Lens.Lens' ListVectorEnrichmentJobsResponse (Prelude.Maybe Prelude.Text)
listVectorEnrichmentJobsResponse_nextToken :: Lens' ListVectorEnrichmentJobsResponse (Maybe Text)
listVectorEnrichmentJobsResponse_nextToken = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\ListVectorEnrichmentJobsResponse' {Maybe (Sensitive Text)
nextToken :: Maybe (Sensitive Text)
$sel:nextToken:ListVectorEnrichmentJobsResponse' :: ListVectorEnrichmentJobsResponse -> Maybe (Sensitive Text)
nextToken} -> Maybe (Sensitive Text)
nextToken) (\s :: ListVectorEnrichmentJobsResponse
s@ListVectorEnrichmentJobsResponse' {} Maybe (Sensitive Text)
a -> ListVectorEnrichmentJobsResponse
s {$sel:nextToken:ListVectorEnrichmentJobsResponse' :: Maybe (Sensitive Text)
nextToken = Maybe (Sensitive Text)
a} :: ListVectorEnrichmentJobsResponse) 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 a. Iso' (Sensitive a) a
Data._Sensitive

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

-- | Contains summary information about the Vector Enrichment jobs.
listVectorEnrichmentJobsResponse_vectorEnrichmentJobSummaries :: Lens.Lens' ListVectorEnrichmentJobsResponse [ListVectorEnrichmentJobOutputConfig]
listVectorEnrichmentJobsResponse_vectorEnrichmentJobSummaries :: Lens'
  ListVectorEnrichmentJobsResponse
  [ListVectorEnrichmentJobOutputConfig]
listVectorEnrichmentJobsResponse_vectorEnrichmentJobSummaries = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\ListVectorEnrichmentJobsResponse' {[ListVectorEnrichmentJobOutputConfig]
vectorEnrichmentJobSummaries :: [ListVectorEnrichmentJobOutputConfig]
$sel:vectorEnrichmentJobSummaries:ListVectorEnrichmentJobsResponse' :: ListVectorEnrichmentJobsResponse
-> [ListVectorEnrichmentJobOutputConfig]
vectorEnrichmentJobSummaries} -> [ListVectorEnrichmentJobOutputConfig]
vectorEnrichmentJobSummaries) (\s :: ListVectorEnrichmentJobsResponse
s@ListVectorEnrichmentJobsResponse' {} [ListVectorEnrichmentJobOutputConfig]
a -> ListVectorEnrichmentJobsResponse
s {$sel:vectorEnrichmentJobSummaries:ListVectorEnrichmentJobsResponse' :: [ListVectorEnrichmentJobOutputConfig]
vectorEnrichmentJobSummaries = [ListVectorEnrichmentJobOutputConfig]
a} :: ListVectorEnrichmentJobsResponse) 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
    ListVectorEnrichmentJobsResponse
  where
  rnf :: ListVectorEnrichmentJobsResponse -> ()
rnf ListVectorEnrichmentJobsResponse' {Int
[ListVectorEnrichmentJobOutputConfig]
Maybe (Sensitive Text)
vectorEnrichmentJobSummaries :: [ListVectorEnrichmentJobOutputConfig]
httpStatus :: Int
nextToken :: Maybe (Sensitive Text)
$sel:vectorEnrichmentJobSummaries:ListVectorEnrichmentJobsResponse' :: ListVectorEnrichmentJobsResponse
-> [ListVectorEnrichmentJobOutputConfig]
$sel:httpStatus:ListVectorEnrichmentJobsResponse' :: ListVectorEnrichmentJobsResponse -> Int
$sel:nextToken:ListVectorEnrichmentJobsResponse' :: ListVectorEnrichmentJobsResponse -> Maybe (Sensitive Text)
..} =
    forall a. NFData a => a -> ()
Prelude.rnf Maybe (Sensitive 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 [ListVectorEnrichmentJobOutputConfig]
vectorEnrichmentJobSummaries