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

    -- * Request Lenses
    listEdgePackagingJobs_creationTimeAfter,
    listEdgePackagingJobs_creationTimeBefore,
    listEdgePackagingJobs_lastModifiedTimeAfter,
    listEdgePackagingJobs_lastModifiedTimeBefore,
    listEdgePackagingJobs_maxResults,
    listEdgePackagingJobs_modelNameContains,
    listEdgePackagingJobs_nameContains,
    listEdgePackagingJobs_nextToken,
    listEdgePackagingJobs_sortBy,
    listEdgePackagingJobs_sortOrder,
    listEdgePackagingJobs_statusEquals,

    -- * Destructuring the Response
    ListEdgePackagingJobsResponse (..),
    newListEdgePackagingJobsResponse,

    -- * Response Lenses
    listEdgePackagingJobsResponse_nextToken,
    listEdgePackagingJobsResponse_httpStatus,
    listEdgePackagingJobsResponse_edgePackagingJobSummaries,
  )
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.SageMaker.Types

-- | /See:/ 'newListEdgePackagingJobs' smart constructor.
data ListEdgePackagingJobs = ListEdgePackagingJobs'
  { -- | Select jobs where the job was created after specified time.
    ListEdgePackagingJobs -> Maybe POSIX
creationTimeAfter :: Prelude.Maybe Data.POSIX,
    -- | Select jobs where the job was created before specified time.
    ListEdgePackagingJobs -> Maybe POSIX
creationTimeBefore :: Prelude.Maybe Data.POSIX,
    -- | Select jobs where the job was updated after specified time.
    ListEdgePackagingJobs -> Maybe POSIX
lastModifiedTimeAfter :: Prelude.Maybe Data.POSIX,
    -- | Select jobs where the job was updated before specified time.
    ListEdgePackagingJobs -> Maybe POSIX
lastModifiedTimeBefore :: Prelude.Maybe Data.POSIX,
    -- | Maximum number of results to select.
    ListEdgePackagingJobs -> Maybe Int
maxResults :: Prelude.Maybe Prelude.Int,
    -- | Filter for jobs where the model name contains this string.
    ListEdgePackagingJobs -> Maybe Text
modelNameContains :: Prelude.Maybe Prelude.Text,
    -- | Filter for jobs containing this name in their packaging job name.
    ListEdgePackagingJobs -> Maybe Text
nameContains :: Prelude.Maybe Prelude.Text,
    -- | The response from the last list when returning a list large enough to
    -- need tokening.
    ListEdgePackagingJobs -> Maybe Text
nextToken :: Prelude.Maybe Prelude.Text,
    -- | Use to specify what column to sort by.
    ListEdgePackagingJobs -> Maybe ListEdgePackagingJobsSortBy
sortBy :: Prelude.Maybe ListEdgePackagingJobsSortBy,
    -- | What direction to sort by.
    ListEdgePackagingJobs -> Maybe SortOrder
sortOrder :: Prelude.Maybe SortOrder,
    -- | The job status to filter for.
    ListEdgePackagingJobs -> Maybe EdgePackagingJobStatus
statusEquals :: Prelude.Maybe EdgePackagingJobStatus
  }
  deriving (ListEdgePackagingJobs -> ListEdgePackagingJobs -> Bool
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: ListEdgePackagingJobs -> ListEdgePackagingJobs -> Bool
$c/= :: ListEdgePackagingJobs -> ListEdgePackagingJobs -> Bool
== :: ListEdgePackagingJobs -> ListEdgePackagingJobs -> Bool
$c== :: ListEdgePackagingJobs -> ListEdgePackagingJobs -> Bool
Prelude.Eq, ReadPrec [ListEdgePackagingJobs]
ReadPrec ListEdgePackagingJobs
Int -> ReadS ListEdgePackagingJobs
ReadS [ListEdgePackagingJobs]
forall a.
(Int -> ReadS a)
-> ReadS [a] -> ReadPrec a -> ReadPrec [a] -> Read a
readListPrec :: ReadPrec [ListEdgePackagingJobs]
$creadListPrec :: ReadPrec [ListEdgePackagingJobs]
readPrec :: ReadPrec ListEdgePackagingJobs
$creadPrec :: ReadPrec ListEdgePackagingJobs
readList :: ReadS [ListEdgePackagingJobs]
$creadList :: ReadS [ListEdgePackagingJobs]
readsPrec :: Int -> ReadS ListEdgePackagingJobs
$creadsPrec :: Int -> ReadS ListEdgePackagingJobs
Prelude.Read, Int -> ListEdgePackagingJobs -> ShowS
[ListEdgePackagingJobs] -> ShowS
ListEdgePackagingJobs -> String
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [ListEdgePackagingJobs] -> ShowS
$cshowList :: [ListEdgePackagingJobs] -> ShowS
show :: ListEdgePackagingJobs -> String
$cshow :: ListEdgePackagingJobs -> String
showsPrec :: Int -> ListEdgePackagingJobs -> ShowS
$cshowsPrec :: Int -> ListEdgePackagingJobs -> ShowS
Prelude.Show, forall x. Rep ListEdgePackagingJobs x -> ListEdgePackagingJobs
forall x. ListEdgePackagingJobs -> Rep ListEdgePackagingJobs x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cto :: forall x. Rep ListEdgePackagingJobs x -> ListEdgePackagingJobs
$cfrom :: forall x. ListEdgePackagingJobs -> Rep ListEdgePackagingJobs x
Prelude.Generic)

-- |
-- Create a value of 'ListEdgePackagingJobs' 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:
--
-- 'creationTimeAfter', 'listEdgePackagingJobs_creationTimeAfter' - Select jobs where the job was created after specified time.
--
-- 'creationTimeBefore', 'listEdgePackagingJobs_creationTimeBefore' - Select jobs where the job was created before specified time.
--
-- 'lastModifiedTimeAfter', 'listEdgePackagingJobs_lastModifiedTimeAfter' - Select jobs where the job was updated after specified time.
--
-- 'lastModifiedTimeBefore', 'listEdgePackagingJobs_lastModifiedTimeBefore' - Select jobs where the job was updated before specified time.
--
-- 'maxResults', 'listEdgePackagingJobs_maxResults' - Maximum number of results to select.
--
-- 'modelNameContains', 'listEdgePackagingJobs_modelNameContains' - Filter for jobs where the model name contains this string.
--
-- 'nameContains', 'listEdgePackagingJobs_nameContains' - Filter for jobs containing this name in their packaging job name.
--
-- 'nextToken', 'listEdgePackagingJobs_nextToken' - The response from the last list when returning a list large enough to
-- need tokening.
--
-- 'sortBy', 'listEdgePackagingJobs_sortBy' - Use to specify what column to sort by.
--
-- 'sortOrder', 'listEdgePackagingJobs_sortOrder' - What direction to sort by.
--
-- 'statusEquals', 'listEdgePackagingJobs_statusEquals' - The job status to filter for.
newListEdgePackagingJobs ::
  ListEdgePackagingJobs
newListEdgePackagingJobs :: ListEdgePackagingJobs
newListEdgePackagingJobs =
  ListEdgePackagingJobs'
    { $sel:creationTimeAfter:ListEdgePackagingJobs' :: Maybe POSIX
creationTimeAfter =
        forall a. Maybe a
Prelude.Nothing,
      $sel:creationTimeBefore:ListEdgePackagingJobs' :: Maybe POSIX
creationTimeBefore = forall a. Maybe a
Prelude.Nothing,
      $sel:lastModifiedTimeAfter:ListEdgePackagingJobs' :: Maybe POSIX
lastModifiedTimeAfter = forall a. Maybe a
Prelude.Nothing,
      $sel:lastModifiedTimeBefore:ListEdgePackagingJobs' :: Maybe POSIX
lastModifiedTimeBefore = forall a. Maybe a
Prelude.Nothing,
      $sel:maxResults:ListEdgePackagingJobs' :: Maybe Int
maxResults = forall a. Maybe a
Prelude.Nothing,
      $sel:modelNameContains:ListEdgePackagingJobs' :: Maybe Text
modelNameContains = forall a. Maybe a
Prelude.Nothing,
      $sel:nameContains:ListEdgePackagingJobs' :: Maybe Text
nameContains = forall a. Maybe a
Prelude.Nothing,
      $sel:nextToken:ListEdgePackagingJobs' :: Maybe Text
nextToken = forall a. Maybe a
Prelude.Nothing,
      $sel:sortBy:ListEdgePackagingJobs' :: Maybe ListEdgePackagingJobsSortBy
sortBy = forall a. Maybe a
Prelude.Nothing,
      $sel:sortOrder:ListEdgePackagingJobs' :: Maybe SortOrder
sortOrder = forall a. Maybe a
Prelude.Nothing,
      $sel:statusEquals:ListEdgePackagingJobs' :: Maybe EdgePackagingJobStatus
statusEquals = forall a. Maybe a
Prelude.Nothing
    }

-- | Select jobs where the job was created after specified time.
listEdgePackagingJobs_creationTimeAfter :: Lens.Lens' ListEdgePackagingJobs (Prelude.Maybe Prelude.UTCTime)
listEdgePackagingJobs_creationTimeAfter :: Lens' ListEdgePackagingJobs (Maybe UTCTime)
listEdgePackagingJobs_creationTimeAfter = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\ListEdgePackagingJobs' {Maybe POSIX
creationTimeAfter :: Maybe POSIX
$sel:creationTimeAfter:ListEdgePackagingJobs' :: ListEdgePackagingJobs -> Maybe POSIX
creationTimeAfter} -> Maybe POSIX
creationTimeAfter) (\s :: ListEdgePackagingJobs
s@ListEdgePackagingJobs' {} Maybe POSIX
a -> ListEdgePackagingJobs
s {$sel:creationTimeAfter:ListEdgePackagingJobs' :: Maybe POSIX
creationTimeAfter = Maybe POSIX
a} :: ListEdgePackagingJobs) 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 :: Format). Iso' (Time a) UTCTime
Data._Time

-- | Select jobs where the job was created before specified time.
listEdgePackagingJobs_creationTimeBefore :: Lens.Lens' ListEdgePackagingJobs (Prelude.Maybe Prelude.UTCTime)
listEdgePackagingJobs_creationTimeBefore :: Lens' ListEdgePackagingJobs (Maybe UTCTime)
listEdgePackagingJobs_creationTimeBefore = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\ListEdgePackagingJobs' {Maybe POSIX
creationTimeBefore :: Maybe POSIX
$sel:creationTimeBefore:ListEdgePackagingJobs' :: ListEdgePackagingJobs -> Maybe POSIX
creationTimeBefore} -> Maybe POSIX
creationTimeBefore) (\s :: ListEdgePackagingJobs
s@ListEdgePackagingJobs' {} Maybe POSIX
a -> ListEdgePackagingJobs
s {$sel:creationTimeBefore:ListEdgePackagingJobs' :: Maybe POSIX
creationTimeBefore = Maybe POSIX
a} :: ListEdgePackagingJobs) 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 :: Format). Iso' (Time a) UTCTime
Data._Time

-- | Select jobs where the job was updated after specified time.
listEdgePackagingJobs_lastModifiedTimeAfter :: Lens.Lens' ListEdgePackagingJobs (Prelude.Maybe Prelude.UTCTime)
listEdgePackagingJobs_lastModifiedTimeAfter :: Lens' ListEdgePackagingJobs (Maybe UTCTime)
listEdgePackagingJobs_lastModifiedTimeAfter = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\ListEdgePackagingJobs' {Maybe POSIX
lastModifiedTimeAfter :: Maybe POSIX
$sel:lastModifiedTimeAfter:ListEdgePackagingJobs' :: ListEdgePackagingJobs -> Maybe POSIX
lastModifiedTimeAfter} -> Maybe POSIX
lastModifiedTimeAfter) (\s :: ListEdgePackagingJobs
s@ListEdgePackagingJobs' {} Maybe POSIX
a -> ListEdgePackagingJobs
s {$sel:lastModifiedTimeAfter:ListEdgePackagingJobs' :: Maybe POSIX
lastModifiedTimeAfter = Maybe POSIX
a} :: ListEdgePackagingJobs) 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 :: Format). Iso' (Time a) UTCTime
Data._Time

-- | Select jobs where the job was updated before specified time.
listEdgePackagingJobs_lastModifiedTimeBefore :: Lens.Lens' ListEdgePackagingJobs (Prelude.Maybe Prelude.UTCTime)
listEdgePackagingJobs_lastModifiedTimeBefore :: Lens' ListEdgePackagingJobs (Maybe UTCTime)
listEdgePackagingJobs_lastModifiedTimeBefore = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\ListEdgePackagingJobs' {Maybe POSIX
lastModifiedTimeBefore :: Maybe POSIX
$sel:lastModifiedTimeBefore:ListEdgePackagingJobs' :: ListEdgePackagingJobs -> Maybe POSIX
lastModifiedTimeBefore} -> Maybe POSIX
lastModifiedTimeBefore) (\s :: ListEdgePackagingJobs
s@ListEdgePackagingJobs' {} Maybe POSIX
a -> ListEdgePackagingJobs
s {$sel:lastModifiedTimeBefore:ListEdgePackagingJobs' :: Maybe POSIX
lastModifiedTimeBefore = Maybe POSIX
a} :: ListEdgePackagingJobs) 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 :: Format). Iso' (Time a) UTCTime
Data._Time

-- | Maximum number of results to select.
listEdgePackagingJobs_maxResults :: Lens.Lens' ListEdgePackagingJobs (Prelude.Maybe Prelude.Int)
listEdgePackagingJobs_maxResults :: Lens' ListEdgePackagingJobs (Maybe Int)
listEdgePackagingJobs_maxResults = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\ListEdgePackagingJobs' {Maybe Int
maxResults :: Maybe Int
$sel:maxResults:ListEdgePackagingJobs' :: ListEdgePackagingJobs -> Maybe Int
maxResults} -> Maybe Int
maxResults) (\s :: ListEdgePackagingJobs
s@ListEdgePackagingJobs' {} Maybe Int
a -> ListEdgePackagingJobs
s {$sel:maxResults:ListEdgePackagingJobs' :: Maybe Int
maxResults = Maybe Int
a} :: ListEdgePackagingJobs)

-- | Filter for jobs where the model name contains this string.
listEdgePackagingJobs_modelNameContains :: Lens.Lens' ListEdgePackagingJobs (Prelude.Maybe Prelude.Text)
listEdgePackagingJobs_modelNameContains :: Lens' ListEdgePackagingJobs (Maybe Text)
listEdgePackagingJobs_modelNameContains = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\ListEdgePackagingJobs' {Maybe Text
modelNameContains :: Maybe Text
$sel:modelNameContains:ListEdgePackagingJobs' :: ListEdgePackagingJobs -> Maybe Text
modelNameContains} -> Maybe Text
modelNameContains) (\s :: ListEdgePackagingJobs
s@ListEdgePackagingJobs' {} Maybe Text
a -> ListEdgePackagingJobs
s {$sel:modelNameContains:ListEdgePackagingJobs' :: Maybe Text
modelNameContains = Maybe Text
a} :: ListEdgePackagingJobs)

-- | Filter for jobs containing this name in their packaging job name.
listEdgePackagingJobs_nameContains :: Lens.Lens' ListEdgePackagingJobs (Prelude.Maybe Prelude.Text)
listEdgePackagingJobs_nameContains :: Lens' ListEdgePackagingJobs (Maybe Text)
listEdgePackagingJobs_nameContains = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\ListEdgePackagingJobs' {Maybe Text
nameContains :: Maybe Text
$sel:nameContains:ListEdgePackagingJobs' :: ListEdgePackagingJobs -> Maybe Text
nameContains} -> Maybe Text
nameContains) (\s :: ListEdgePackagingJobs
s@ListEdgePackagingJobs' {} Maybe Text
a -> ListEdgePackagingJobs
s {$sel:nameContains:ListEdgePackagingJobs' :: Maybe Text
nameContains = Maybe Text
a} :: ListEdgePackagingJobs)

-- | The response from the last list when returning a list large enough to
-- need tokening.
listEdgePackagingJobs_nextToken :: Lens.Lens' ListEdgePackagingJobs (Prelude.Maybe Prelude.Text)
listEdgePackagingJobs_nextToken :: Lens' ListEdgePackagingJobs (Maybe Text)
listEdgePackagingJobs_nextToken = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\ListEdgePackagingJobs' {Maybe Text
nextToken :: Maybe Text
$sel:nextToken:ListEdgePackagingJobs' :: ListEdgePackagingJobs -> Maybe Text
nextToken} -> Maybe Text
nextToken) (\s :: ListEdgePackagingJobs
s@ListEdgePackagingJobs' {} Maybe Text
a -> ListEdgePackagingJobs
s {$sel:nextToken:ListEdgePackagingJobs' :: Maybe Text
nextToken = Maybe Text
a} :: ListEdgePackagingJobs)

-- | Use to specify what column to sort by.
listEdgePackagingJobs_sortBy :: Lens.Lens' ListEdgePackagingJobs (Prelude.Maybe ListEdgePackagingJobsSortBy)
listEdgePackagingJobs_sortBy :: Lens' ListEdgePackagingJobs (Maybe ListEdgePackagingJobsSortBy)
listEdgePackagingJobs_sortBy = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\ListEdgePackagingJobs' {Maybe ListEdgePackagingJobsSortBy
sortBy :: Maybe ListEdgePackagingJobsSortBy
$sel:sortBy:ListEdgePackagingJobs' :: ListEdgePackagingJobs -> Maybe ListEdgePackagingJobsSortBy
sortBy} -> Maybe ListEdgePackagingJobsSortBy
sortBy) (\s :: ListEdgePackagingJobs
s@ListEdgePackagingJobs' {} Maybe ListEdgePackagingJobsSortBy
a -> ListEdgePackagingJobs
s {$sel:sortBy:ListEdgePackagingJobs' :: Maybe ListEdgePackagingJobsSortBy
sortBy = Maybe ListEdgePackagingJobsSortBy
a} :: ListEdgePackagingJobs)

-- | What direction to sort by.
listEdgePackagingJobs_sortOrder :: Lens.Lens' ListEdgePackagingJobs (Prelude.Maybe SortOrder)
listEdgePackagingJobs_sortOrder :: Lens' ListEdgePackagingJobs (Maybe SortOrder)
listEdgePackagingJobs_sortOrder = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\ListEdgePackagingJobs' {Maybe SortOrder
sortOrder :: Maybe SortOrder
$sel:sortOrder:ListEdgePackagingJobs' :: ListEdgePackagingJobs -> Maybe SortOrder
sortOrder} -> Maybe SortOrder
sortOrder) (\s :: ListEdgePackagingJobs
s@ListEdgePackagingJobs' {} Maybe SortOrder
a -> ListEdgePackagingJobs
s {$sel:sortOrder:ListEdgePackagingJobs' :: Maybe SortOrder
sortOrder = Maybe SortOrder
a} :: ListEdgePackagingJobs)

-- | The job status to filter for.
listEdgePackagingJobs_statusEquals :: Lens.Lens' ListEdgePackagingJobs (Prelude.Maybe EdgePackagingJobStatus)
listEdgePackagingJobs_statusEquals :: Lens' ListEdgePackagingJobs (Maybe EdgePackagingJobStatus)
listEdgePackagingJobs_statusEquals = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\ListEdgePackagingJobs' {Maybe EdgePackagingJobStatus
statusEquals :: Maybe EdgePackagingJobStatus
$sel:statusEquals:ListEdgePackagingJobs' :: ListEdgePackagingJobs -> Maybe EdgePackagingJobStatus
statusEquals} -> Maybe EdgePackagingJobStatus
statusEquals) (\s :: ListEdgePackagingJobs
s@ListEdgePackagingJobs' {} Maybe EdgePackagingJobStatus
a -> ListEdgePackagingJobs
s {$sel:statusEquals:ListEdgePackagingJobs' :: Maybe EdgePackagingJobStatus
statusEquals = Maybe EdgePackagingJobStatus
a} :: ListEdgePackagingJobs)

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

instance Prelude.Hashable ListEdgePackagingJobs where
  hashWithSalt :: Int -> ListEdgePackagingJobs -> Int
hashWithSalt Int
_salt ListEdgePackagingJobs' {Maybe Int
Maybe Text
Maybe POSIX
Maybe EdgePackagingJobStatus
Maybe ListEdgePackagingJobsSortBy
Maybe SortOrder
statusEquals :: Maybe EdgePackagingJobStatus
sortOrder :: Maybe SortOrder
sortBy :: Maybe ListEdgePackagingJobsSortBy
nextToken :: Maybe Text
nameContains :: Maybe Text
modelNameContains :: Maybe Text
maxResults :: Maybe Int
lastModifiedTimeBefore :: Maybe POSIX
lastModifiedTimeAfter :: Maybe POSIX
creationTimeBefore :: Maybe POSIX
creationTimeAfter :: Maybe POSIX
$sel:statusEquals:ListEdgePackagingJobs' :: ListEdgePackagingJobs -> Maybe EdgePackagingJobStatus
$sel:sortOrder:ListEdgePackagingJobs' :: ListEdgePackagingJobs -> Maybe SortOrder
$sel:sortBy:ListEdgePackagingJobs' :: ListEdgePackagingJobs -> Maybe ListEdgePackagingJobsSortBy
$sel:nextToken:ListEdgePackagingJobs' :: ListEdgePackagingJobs -> Maybe Text
$sel:nameContains:ListEdgePackagingJobs' :: ListEdgePackagingJobs -> Maybe Text
$sel:modelNameContains:ListEdgePackagingJobs' :: ListEdgePackagingJobs -> Maybe Text
$sel:maxResults:ListEdgePackagingJobs' :: ListEdgePackagingJobs -> Maybe Int
$sel:lastModifiedTimeBefore:ListEdgePackagingJobs' :: ListEdgePackagingJobs -> Maybe POSIX
$sel:lastModifiedTimeAfter:ListEdgePackagingJobs' :: ListEdgePackagingJobs -> Maybe POSIX
$sel:creationTimeBefore:ListEdgePackagingJobs' :: ListEdgePackagingJobs -> Maybe POSIX
$sel:creationTimeAfter:ListEdgePackagingJobs' :: ListEdgePackagingJobs -> Maybe POSIX
..} =
    Int
_salt
      forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Maybe POSIX
creationTimeAfter
      forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Maybe POSIX
creationTimeBefore
      forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Maybe POSIX
lastModifiedTimeAfter
      forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Maybe POSIX
lastModifiedTimeBefore
      forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Maybe Int
maxResults
      forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Maybe Text
modelNameContains
      forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Maybe Text
nameContains
      forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Maybe Text
nextToken
      forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Maybe ListEdgePackagingJobsSortBy
sortBy
      forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Maybe SortOrder
sortOrder
      forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Maybe EdgePackagingJobStatus
statusEquals

instance Prelude.NFData ListEdgePackagingJobs where
  rnf :: ListEdgePackagingJobs -> ()
rnf ListEdgePackagingJobs' {Maybe Int
Maybe Text
Maybe POSIX
Maybe EdgePackagingJobStatus
Maybe ListEdgePackagingJobsSortBy
Maybe SortOrder
statusEquals :: Maybe EdgePackagingJobStatus
sortOrder :: Maybe SortOrder
sortBy :: Maybe ListEdgePackagingJobsSortBy
nextToken :: Maybe Text
nameContains :: Maybe Text
modelNameContains :: Maybe Text
maxResults :: Maybe Int
lastModifiedTimeBefore :: Maybe POSIX
lastModifiedTimeAfter :: Maybe POSIX
creationTimeBefore :: Maybe POSIX
creationTimeAfter :: Maybe POSIX
$sel:statusEquals:ListEdgePackagingJobs' :: ListEdgePackagingJobs -> Maybe EdgePackagingJobStatus
$sel:sortOrder:ListEdgePackagingJobs' :: ListEdgePackagingJobs -> Maybe SortOrder
$sel:sortBy:ListEdgePackagingJobs' :: ListEdgePackagingJobs -> Maybe ListEdgePackagingJobsSortBy
$sel:nextToken:ListEdgePackagingJobs' :: ListEdgePackagingJobs -> Maybe Text
$sel:nameContains:ListEdgePackagingJobs' :: ListEdgePackagingJobs -> Maybe Text
$sel:modelNameContains:ListEdgePackagingJobs' :: ListEdgePackagingJobs -> Maybe Text
$sel:maxResults:ListEdgePackagingJobs' :: ListEdgePackagingJobs -> Maybe Int
$sel:lastModifiedTimeBefore:ListEdgePackagingJobs' :: ListEdgePackagingJobs -> Maybe POSIX
$sel:lastModifiedTimeAfter:ListEdgePackagingJobs' :: ListEdgePackagingJobs -> Maybe POSIX
$sel:creationTimeBefore:ListEdgePackagingJobs' :: ListEdgePackagingJobs -> Maybe POSIX
$sel:creationTimeAfter:ListEdgePackagingJobs' :: ListEdgePackagingJobs -> Maybe POSIX
..} =
    forall a. NFData a => a -> ()
Prelude.rnf Maybe POSIX
creationTimeAfter
      seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf Maybe POSIX
creationTimeBefore
      seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf Maybe POSIX
lastModifiedTimeAfter
      seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf Maybe POSIX
lastModifiedTimeBefore
      seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf Maybe Int
maxResults
      seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf Maybe Text
modelNameContains
      seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf Maybe Text
nameContains
      seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf Maybe Text
nextToken
      seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf Maybe ListEdgePackagingJobsSortBy
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 EdgePackagingJobStatus
statusEquals

instance Data.ToHeaders ListEdgePackagingJobs where
  toHeaders :: ListEdgePackagingJobs -> 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
"SageMaker.ListEdgePackagingJobs" ::
                          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 ListEdgePackagingJobs where
  toJSON :: ListEdgePackagingJobs -> Value
toJSON ListEdgePackagingJobs' {Maybe Int
Maybe Text
Maybe POSIX
Maybe EdgePackagingJobStatus
Maybe ListEdgePackagingJobsSortBy
Maybe SortOrder
statusEquals :: Maybe EdgePackagingJobStatus
sortOrder :: Maybe SortOrder
sortBy :: Maybe ListEdgePackagingJobsSortBy
nextToken :: Maybe Text
nameContains :: Maybe Text
modelNameContains :: Maybe Text
maxResults :: Maybe Int
lastModifiedTimeBefore :: Maybe POSIX
lastModifiedTimeAfter :: Maybe POSIX
creationTimeBefore :: Maybe POSIX
creationTimeAfter :: Maybe POSIX
$sel:statusEquals:ListEdgePackagingJobs' :: ListEdgePackagingJobs -> Maybe EdgePackagingJobStatus
$sel:sortOrder:ListEdgePackagingJobs' :: ListEdgePackagingJobs -> Maybe SortOrder
$sel:sortBy:ListEdgePackagingJobs' :: ListEdgePackagingJobs -> Maybe ListEdgePackagingJobsSortBy
$sel:nextToken:ListEdgePackagingJobs' :: ListEdgePackagingJobs -> Maybe Text
$sel:nameContains:ListEdgePackagingJobs' :: ListEdgePackagingJobs -> Maybe Text
$sel:modelNameContains:ListEdgePackagingJobs' :: ListEdgePackagingJobs -> Maybe Text
$sel:maxResults:ListEdgePackagingJobs' :: ListEdgePackagingJobs -> Maybe Int
$sel:lastModifiedTimeBefore:ListEdgePackagingJobs' :: ListEdgePackagingJobs -> Maybe POSIX
$sel:lastModifiedTimeAfter:ListEdgePackagingJobs' :: ListEdgePackagingJobs -> Maybe POSIX
$sel:creationTimeBefore:ListEdgePackagingJobs' :: ListEdgePackagingJobs -> Maybe POSIX
$sel:creationTimeAfter:ListEdgePackagingJobs' :: ListEdgePackagingJobs -> Maybe POSIX
..} =
    [Pair] -> Value
Data.object
      ( forall a. [Maybe a] -> [a]
Prelude.catMaybes
          [ (Key
"CreationTimeAfter" 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 POSIX
creationTimeAfter,
            (Key
"CreationTimeBefore" 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 POSIX
creationTimeBefore,
            (Key
"LastModifiedTimeAfter" 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 POSIX
lastModifiedTimeAfter,
            (Key
"LastModifiedTimeBefore" 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 POSIX
lastModifiedTimeBefore,
            (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 Int
maxResults,
            (Key
"ModelNameContains" 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
modelNameContains,
            (Key
"NameContains" 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
nameContains,
            (Key
"NextToken" forall kv v. (KeyValue kv, ToJSON v) => Key -> v -> kv
Data..=) forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
Prelude.<$> Maybe Text
nextToken,
            (Key
"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 ListEdgePackagingJobsSortBy
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 EdgePackagingJobStatus
statusEquals
          ]
      )

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

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

-- | /See:/ 'newListEdgePackagingJobsResponse' smart constructor.
data ListEdgePackagingJobsResponse = ListEdgePackagingJobsResponse'
  { -- | Token to use when calling the next page of results.
    ListEdgePackagingJobsResponse -> Maybe Text
nextToken :: Prelude.Maybe Prelude.Text,
    -- | The response's http status code.
    ListEdgePackagingJobsResponse -> Int
httpStatus :: Prelude.Int,
    -- | Summaries of edge packaging jobs.
    ListEdgePackagingJobsResponse -> [EdgePackagingJobSummary]
edgePackagingJobSummaries :: [EdgePackagingJobSummary]
  }
  deriving (ListEdgePackagingJobsResponse
-> ListEdgePackagingJobsResponse -> Bool
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: ListEdgePackagingJobsResponse
-> ListEdgePackagingJobsResponse -> Bool
$c/= :: ListEdgePackagingJobsResponse
-> ListEdgePackagingJobsResponse -> Bool
== :: ListEdgePackagingJobsResponse
-> ListEdgePackagingJobsResponse -> Bool
$c== :: ListEdgePackagingJobsResponse
-> ListEdgePackagingJobsResponse -> Bool
Prelude.Eq, ReadPrec [ListEdgePackagingJobsResponse]
ReadPrec ListEdgePackagingJobsResponse
Int -> ReadS ListEdgePackagingJobsResponse
ReadS [ListEdgePackagingJobsResponse]
forall a.
(Int -> ReadS a)
-> ReadS [a] -> ReadPrec a -> ReadPrec [a] -> Read a
readListPrec :: ReadPrec [ListEdgePackagingJobsResponse]
$creadListPrec :: ReadPrec [ListEdgePackagingJobsResponse]
readPrec :: ReadPrec ListEdgePackagingJobsResponse
$creadPrec :: ReadPrec ListEdgePackagingJobsResponse
readList :: ReadS [ListEdgePackagingJobsResponse]
$creadList :: ReadS [ListEdgePackagingJobsResponse]
readsPrec :: Int -> ReadS ListEdgePackagingJobsResponse
$creadsPrec :: Int -> ReadS ListEdgePackagingJobsResponse
Prelude.Read, Int -> ListEdgePackagingJobsResponse -> ShowS
[ListEdgePackagingJobsResponse] -> ShowS
ListEdgePackagingJobsResponse -> String
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [ListEdgePackagingJobsResponse] -> ShowS
$cshowList :: [ListEdgePackagingJobsResponse] -> ShowS
show :: ListEdgePackagingJobsResponse -> String
$cshow :: ListEdgePackagingJobsResponse -> String
showsPrec :: Int -> ListEdgePackagingJobsResponse -> ShowS
$cshowsPrec :: Int -> ListEdgePackagingJobsResponse -> ShowS
Prelude.Show, forall x.
Rep ListEdgePackagingJobsResponse x
-> ListEdgePackagingJobsResponse
forall x.
ListEdgePackagingJobsResponse
-> Rep ListEdgePackagingJobsResponse x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cto :: forall x.
Rep ListEdgePackagingJobsResponse x
-> ListEdgePackagingJobsResponse
$cfrom :: forall x.
ListEdgePackagingJobsResponse
-> Rep ListEdgePackagingJobsResponse x
Prelude.Generic)

-- |
-- Create a value of 'ListEdgePackagingJobsResponse' 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', 'listEdgePackagingJobsResponse_nextToken' - Token to use when calling the next page of results.
--
-- 'httpStatus', 'listEdgePackagingJobsResponse_httpStatus' - The response's http status code.
--
-- 'edgePackagingJobSummaries', 'listEdgePackagingJobsResponse_edgePackagingJobSummaries' - Summaries of edge packaging jobs.
newListEdgePackagingJobsResponse ::
  -- | 'httpStatus'
  Prelude.Int ->
  ListEdgePackagingJobsResponse
newListEdgePackagingJobsResponse :: Int -> ListEdgePackagingJobsResponse
newListEdgePackagingJobsResponse Int
pHttpStatus_ =
  ListEdgePackagingJobsResponse'
    { $sel:nextToken:ListEdgePackagingJobsResponse' :: Maybe Text
nextToken =
        forall a. Maybe a
Prelude.Nothing,
      $sel:httpStatus:ListEdgePackagingJobsResponse' :: Int
httpStatus = Int
pHttpStatus_,
      $sel:edgePackagingJobSummaries:ListEdgePackagingJobsResponse' :: [EdgePackagingJobSummary]
edgePackagingJobSummaries = forall a. Monoid a => a
Prelude.mempty
    }

-- | Token to use when calling the next page of results.
listEdgePackagingJobsResponse_nextToken :: Lens.Lens' ListEdgePackagingJobsResponse (Prelude.Maybe Prelude.Text)
listEdgePackagingJobsResponse_nextToken :: Lens' ListEdgePackagingJobsResponse (Maybe Text)
listEdgePackagingJobsResponse_nextToken = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\ListEdgePackagingJobsResponse' {Maybe Text
nextToken :: Maybe Text
$sel:nextToken:ListEdgePackagingJobsResponse' :: ListEdgePackagingJobsResponse -> Maybe Text
nextToken} -> Maybe Text
nextToken) (\s :: ListEdgePackagingJobsResponse
s@ListEdgePackagingJobsResponse' {} Maybe Text
a -> ListEdgePackagingJobsResponse
s {$sel:nextToken:ListEdgePackagingJobsResponse' :: Maybe Text
nextToken = Maybe Text
a} :: ListEdgePackagingJobsResponse)

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

-- | Summaries of edge packaging jobs.
listEdgePackagingJobsResponse_edgePackagingJobSummaries :: Lens.Lens' ListEdgePackagingJobsResponse [EdgePackagingJobSummary]
listEdgePackagingJobsResponse_edgePackagingJobSummaries :: Lens' ListEdgePackagingJobsResponse [EdgePackagingJobSummary]
listEdgePackagingJobsResponse_edgePackagingJobSummaries = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\ListEdgePackagingJobsResponse' {[EdgePackagingJobSummary]
edgePackagingJobSummaries :: [EdgePackagingJobSummary]
$sel:edgePackagingJobSummaries:ListEdgePackagingJobsResponse' :: ListEdgePackagingJobsResponse -> [EdgePackagingJobSummary]
edgePackagingJobSummaries} -> [EdgePackagingJobSummary]
edgePackagingJobSummaries) (\s :: ListEdgePackagingJobsResponse
s@ListEdgePackagingJobsResponse' {} [EdgePackagingJobSummary]
a -> ListEdgePackagingJobsResponse
s {$sel:edgePackagingJobSummaries:ListEdgePackagingJobsResponse' :: [EdgePackagingJobSummary]
edgePackagingJobSummaries = [EdgePackagingJobSummary]
a} :: ListEdgePackagingJobsResponse) 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 ListEdgePackagingJobsResponse where
  rnf :: ListEdgePackagingJobsResponse -> ()
rnf ListEdgePackagingJobsResponse' {Int
[EdgePackagingJobSummary]
Maybe Text
edgePackagingJobSummaries :: [EdgePackagingJobSummary]
httpStatus :: Int
nextToken :: Maybe Text
$sel:edgePackagingJobSummaries:ListEdgePackagingJobsResponse' :: ListEdgePackagingJobsResponse -> [EdgePackagingJobSummary]
$sel:httpStatus:ListEdgePackagingJobsResponse' :: ListEdgePackagingJobsResponse -> Int
$sel:nextToken:ListEdgePackagingJobsResponse' :: ListEdgePackagingJobsResponse -> 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 [EdgePackagingJobSummary]
edgePackagingJobSummaries