{-# 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.ListEarthObservationJobs
-- Copyright   : (c) 2013-2023 Brendan Hay
-- License     : Mozilla Public License, v. 2.0.
-- Maintainer  : Brendan Hay
-- Stability   : auto-generated
-- Portability : non-portable (GHC extensions)
--
-- Use this operation to get a list of the Earth Observation jobs
-- associated with the calling Amazon Web Services account.
--
-- This operation returns paginated results.
module Amazonka.SageMakerGeoSpatial.ListEarthObservationJobs
  ( -- * Creating a Request
    ListEarthObservationJobs (..),
    newListEarthObservationJobs,

    -- * Request Lenses
    listEarthObservationJobs_maxResults,
    listEarthObservationJobs_nextToken,
    listEarthObservationJobs_sortBy,
    listEarthObservationJobs_sortOrder,
    listEarthObservationJobs_statusEquals,

    -- * Destructuring the Response
    ListEarthObservationJobsResponse (..),
    newListEarthObservationJobsResponse,

    -- * Response Lenses
    listEarthObservationJobsResponse_nextToken,
    listEarthObservationJobsResponse_httpStatus,
    listEarthObservationJobsResponse_earthObservationJobSummaries,
  )
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:/ 'newListEarthObservationJobs' smart constructor.
data ListEarthObservationJobs = ListEarthObservationJobs'
  { -- | The total number of items to return.
    ListEarthObservationJobs -> 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.
    ListEarthObservationJobs -> Maybe (Sensitive Text)
nextToken :: Prelude.Maybe (Data.Sensitive Prelude.Text),
    -- | The parameter by which to sort the results.
    ListEarthObservationJobs -> Maybe Text
sortBy :: Prelude.Maybe Prelude.Text,
    -- | An optional value that specifies whether you want the results sorted in
    -- @Ascending@ or @Descending@ order.
    ListEarthObservationJobs -> Maybe SortOrder
sortOrder :: Prelude.Maybe SortOrder,
    -- | A filter that retrieves only jobs with a specific status.
    ListEarthObservationJobs -> Maybe EarthObservationJobStatus
statusEquals :: Prelude.Maybe EarthObservationJobStatus
  }
  deriving (ListEarthObservationJobs -> ListEarthObservationJobs -> Bool
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: ListEarthObservationJobs -> ListEarthObservationJobs -> Bool
$c/= :: ListEarthObservationJobs -> ListEarthObservationJobs -> Bool
== :: ListEarthObservationJobs -> ListEarthObservationJobs -> Bool
$c== :: ListEarthObservationJobs -> ListEarthObservationJobs -> Bool
Prelude.Eq, Int -> ListEarthObservationJobs -> ShowS
[ListEarthObservationJobs] -> ShowS
ListEarthObservationJobs -> String
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [ListEarthObservationJobs] -> ShowS
$cshowList :: [ListEarthObservationJobs] -> ShowS
show :: ListEarthObservationJobs -> String
$cshow :: ListEarthObservationJobs -> String
showsPrec :: Int -> ListEarthObservationJobs -> ShowS
$cshowsPrec :: Int -> ListEarthObservationJobs -> ShowS
Prelude.Show, forall x.
Rep ListEarthObservationJobs x -> ListEarthObservationJobs
forall x.
ListEarthObservationJobs -> Rep ListEarthObservationJobs x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cto :: forall x.
Rep ListEarthObservationJobs x -> ListEarthObservationJobs
$cfrom :: forall x.
ListEarthObservationJobs -> Rep ListEarthObservationJobs x
Prelude.Generic)

-- |
-- Create a value of 'ListEarthObservationJobs' 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', 'listEarthObservationJobs_maxResults' - The total number of items to return.
--
-- 'nextToken', 'listEarthObservationJobs_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', 'listEarthObservationJobs_sortBy' - The parameter by which to sort the results.
--
-- 'sortOrder', 'listEarthObservationJobs_sortOrder' - An optional value that specifies whether you want the results sorted in
-- @Ascending@ or @Descending@ order.
--
-- 'statusEquals', 'listEarthObservationJobs_statusEquals' - A filter that retrieves only jobs with a specific status.
newListEarthObservationJobs ::
  ListEarthObservationJobs
newListEarthObservationJobs :: ListEarthObservationJobs
newListEarthObservationJobs =
  ListEarthObservationJobs'
    { $sel:maxResults:ListEarthObservationJobs' :: Maybe Natural
maxResults =
        forall a. Maybe a
Prelude.Nothing,
      $sel:nextToken:ListEarthObservationJobs' :: Maybe (Sensitive Text)
nextToken = forall a. Maybe a
Prelude.Nothing,
      $sel:sortBy:ListEarthObservationJobs' :: Maybe Text
sortBy = forall a. Maybe a
Prelude.Nothing,
      $sel:sortOrder:ListEarthObservationJobs' :: Maybe SortOrder
sortOrder = forall a. Maybe a
Prelude.Nothing,
      $sel:statusEquals:ListEarthObservationJobs' :: Maybe EarthObservationJobStatus
statusEquals = forall a. Maybe a
Prelude.Nothing
    }

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

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

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

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

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

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

instance Prelude.NFData ListEarthObservationJobs where
  rnf :: ListEarthObservationJobs -> ()
rnf ListEarthObservationJobs' {Maybe Natural
Maybe Text
Maybe (Sensitive Text)
Maybe EarthObservationJobStatus
Maybe SortOrder
statusEquals :: Maybe EarthObservationJobStatus
sortOrder :: Maybe SortOrder
sortBy :: Maybe Text
nextToken :: Maybe (Sensitive Text)
maxResults :: Maybe Natural
$sel:statusEquals:ListEarthObservationJobs' :: ListEarthObservationJobs -> Maybe EarthObservationJobStatus
$sel:sortOrder:ListEarthObservationJobs' :: ListEarthObservationJobs -> Maybe SortOrder
$sel:sortBy:ListEarthObservationJobs' :: ListEarthObservationJobs -> Maybe Text
$sel:nextToken:ListEarthObservationJobs' :: ListEarthObservationJobs -> Maybe (Sensitive Text)
$sel:maxResults:ListEarthObservationJobs' :: ListEarthObservationJobs -> 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 EarthObservationJobStatus
statusEquals

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

instance Data.ToPath ListEarthObservationJobs where
  toPath :: ListEarthObservationJobs -> ByteString
toPath = forall a b. a -> b -> a
Prelude.const ByteString
"/list-earth-observation-jobs"

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

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

-- |
-- Create a value of 'ListEarthObservationJobsResponse' 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', 'listEarthObservationJobsResponse_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', 'listEarthObservationJobsResponse_httpStatus' - The response's http status code.
--
-- 'earthObservationJobSummaries', 'listEarthObservationJobsResponse_earthObservationJobSummaries' - Contains summary information about the Earth Observation jobs.
newListEarthObservationJobsResponse ::
  -- | 'httpStatus'
  Prelude.Int ->
  ListEarthObservationJobsResponse
newListEarthObservationJobsResponse :: Int -> ListEarthObservationJobsResponse
newListEarthObservationJobsResponse Int
pHttpStatus_ =
  ListEarthObservationJobsResponse'
    { $sel:nextToken:ListEarthObservationJobsResponse' :: Maybe (Sensitive Text)
nextToken =
        forall a. Maybe a
Prelude.Nothing,
      $sel:httpStatus:ListEarthObservationJobsResponse' :: Int
httpStatus = Int
pHttpStatus_,
      $sel:earthObservationJobSummaries:ListEarthObservationJobsResponse' :: [ListEarthObservationJobOutputConfig]
earthObservationJobSummaries =
        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.
listEarthObservationJobsResponse_nextToken :: Lens.Lens' ListEarthObservationJobsResponse (Prelude.Maybe Prelude.Text)
listEarthObservationJobsResponse_nextToken :: Lens' ListEarthObservationJobsResponse (Maybe Text)
listEarthObservationJobsResponse_nextToken = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\ListEarthObservationJobsResponse' {Maybe (Sensitive Text)
nextToken :: Maybe (Sensitive Text)
$sel:nextToken:ListEarthObservationJobsResponse' :: ListEarthObservationJobsResponse -> Maybe (Sensitive Text)
nextToken} -> Maybe (Sensitive Text)
nextToken) (\s :: ListEarthObservationJobsResponse
s@ListEarthObservationJobsResponse' {} Maybe (Sensitive Text)
a -> ListEarthObservationJobsResponse
s {$sel:nextToken:ListEarthObservationJobsResponse' :: Maybe (Sensitive Text)
nextToken = Maybe (Sensitive Text)
a} :: ListEarthObservationJobsResponse) 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.
listEarthObservationJobsResponse_httpStatus :: Lens.Lens' ListEarthObservationJobsResponse Prelude.Int
listEarthObservationJobsResponse_httpStatus :: Lens' ListEarthObservationJobsResponse Int
listEarthObservationJobsResponse_httpStatus = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\ListEarthObservationJobsResponse' {Int
httpStatus :: Int
$sel:httpStatus:ListEarthObservationJobsResponse' :: ListEarthObservationJobsResponse -> Int
httpStatus} -> Int
httpStatus) (\s :: ListEarthObservationJobsResponse
s@ListEarthObservationJobsResponse' {} Int
a -> ListEarthObservationJobsResponse
s {$sel:httpStatus:ListEarthObservationJobsResponse' :: Int
httpStatus = Int
a} :: ListEarthObservationJobsResponse)

-- | Contains summary information about the Earth Observation jobs.
listEarthObservationJobsResponse_earthObservationJobSummaries :: Lens.Lens' ListEarthObservationJobsResponse [ListEarthObservationJobOutputConfig]
listEarthObservationJobsResponse_earthObservationJobSummaries :: Lens'
  ListEarthObservationJobsResponse
  [ListEarthObservationJobOutputConfig]
listEarthObservationJobsResponse_earthObservationJobSummaries = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\ListEarthObservationJobsResponse' {[ListEarthObservationJobOutputConfig]
earthObservationJobSummaries :: [ListEarthObservationJobOutputConfig]
$sel:earthObservationJobSummaries:ListEarthObservationJobsResponse' :: ListEarthObservationJobsResponse
-> [ListEarthObservationJobOutputConfig]
earthObservationJobSummaries} -> [ListEarthObservationJobOutputConfig]
earthObservationJobSummaries) (\s :: ListEarthObservationJobsResponse
s@ListEarthObservationJobsResponse' {} [ListEarthObservationJobOutputConfig]
a -> ListEarthObservationJobsResponse
s {$sel:earthObservationJobSummaries:ListEarthObservationJobsResponse' :: [ListEarthObservationJobOutputConfig]
earthObservationJobSummaries = [ListEarthObservationJobOutputConfig]
a} :: ListEarthObservationJobsResponse) 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
    ListEarthObservationJobsResponse
  where
  rnf :: ListEarthObservationJobsResponse -> ()
rnf ListEarthObservationJobsResponse' {Int
[ListEarthObservationJobOutputConfig]
Maybe (Sensitive Text)
earthObservationJobSummaries :: [ListEarthObservationJobOutputConfig]
httpStatus :: Int
nextToken :: Maybe (Sensitive Text)
$sel:earthObservationJobSummaries:ListEarthObservationJobsResponse' :: ListEarthObservationJobsResponse
-> [ListEarthObservationJobOutputConfig]
$sel:httpStatus:ListEarthObservationJobsResponse' :: ListEarthObservationJobsResponse -> Int
$sel:nextToken:ListEarthObservationJobsResponse' :: ListEarthObservationJobsResponse -> 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 [ListEarthObservationJobOutputConfig]
earthObservationJobSummaries