{-# 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.ElasticTranscoder.ListJobsByPipeline
-- Copyright   : (c) 2013-2023 Brendan Hay
-- License     : Mozilla Public License, v. 2.0.
-- Maintainer  : Brendan Hay
-- Stability   : auto-generated
-- Portability : non-portable (GHC extensions)
--
-- The ListJobsByPipeline operation gets a list of the jobs currently in a
-- pipeline.
--
-- Elastic Transcoder returns all of the jobs currently in the specified
-- pipeline. The response body contains one element for each job that
-- satisfies the search criteria.
--
-- This operation returns paginated results.
module Amazonka.ElasticTranscoder.ListJobsByPipeline
  ( -- * Creating a Request
    ListJobsByPipeline (..),
    newListJobsByPipeline,

    -- * Request Lenses
    listJobsByPipeline_ascending,
    listJobsByPipeline_pageToken,
    listJobsByPipeline_pipelineId,

    -- * Destructuring the Response
    ListJobsByPipelineResponse (..),
    newListJobsByPipelineResponse,

    -- * Response Lenses
    listJobsByPipelineResponse_jobs,
    listJobsByPipelineResponse_nextPageToken,
    listJobsByPipelineResponse_httpStatus,
  )
where

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

-- | The @ListJobsByPipelineRequest@ structure.
--
-- /See:/ 'newListJobsByPipeline' smart constructor.
data ListJobsByPipeline = ListJobsByPipeline'
  { -- | To list jobs in chronological order by the date and time that they were
    -- submitted, enter @true@. To list jobs in reverse chronological order,
    -- enter @false@.
    ListJobsByPipeline -> Maybe Text
ascending :: Prelude.Maybe Prelude.Text,
    -- | When Elastic Transcoder returns more than one page of results, use
    -- @pageToken@ in subsequent @GET@ requests to get each successive page of
    -- results.
    ListJobsByPipeline -> Maybe Text
pageToken :: Prelude.Maybe Prelude.Text,
    -- | The ID of the pipeline for which you want to get job information.
    ListJobsByPipeline -> Text
pipelineId :: Prelude.Text
  }
  deriving (ListJobsByPipeline -> ListJobsByPipeline -> Bool
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: ListJobsByPipeline -> ListJobsByPipeline -> Bool
$c/= :: ListJobsByPipeline -> ListJobsByPipeline -> Bool
== :: ListJobsByPipeline -> ListJobsByPipeline -> Bool
$c== :: ListJobsByPipeline -> ListJobsByPipeline -> Bool
Prelude.Eq, ReadPrec [ListJobsByPipeline]
ReadPrec ListJobsByPipeline
Int -> ReadS ListJobsByPipeline
ReadS [ListJobsByPipeline]
forall a.
(Int -> ReadS a)
-> ReadS [a] -> ReadPrec a -> ReadPrec [a] -> Read a
readListPrec :: ReadPrec [ListJobsByPipeline]
$creadListPrec :: ReadPrec [ListJobsByPipeline]
readPrec :: ReadPrec ListJobsByPipeline
$creadPrec :: ReadPrec ListJobsByPipeline
readList :: ReadS [ListJobsByPipeline]
$creadList :: ReadS [ListJobsByPipeline]
readsPrec :: Int -> ReadS ListJobsByPipeline
$creadsPrec :: Int -> ReadS ListJobsByPipeline
Prelude.Read, Int -> ListJobsByPipeline -> ShowS
[ListJobsByPipeline] -> ShowS
ListJobsByPipeline -> String
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [ListJobsByPipeline] -> ShowS
$cshowList :: [ListJobsByPipeline] -> ShowS
show :: ListJobsByPipeline -> String
$cshow :: ListJobsByPipeline -> String
showsPrec :: Int -> ListJobsByPipeline -> ShowS
$cshowsPrec :: Int -> ListJobsByPipeline -> ShowS
Prelude.Show, forall x. Rep ListJobsByPipeline x -> ListJobsByPipeline
forall x. ListJobsByPipeline -> Rep ListJobsByPipeline x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cto :: forall x. Rep ListJobsByPipeline x -> ListJobsByPipeline
$cfrom :: forall x. ListJobsByPipeline -> Rep ListJobsByPipeline x
Prelude.Generic)

-- |
-- Create a value of 'ListJobsByPipeline' 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:
--
-- 'ascending', 'listJobsByPipeline_ascending' - To list jobs in chronological order by the date and time that they were
-- submitted, enter @true@. To list jobs in reverse chronological order,
-- enter @false@.
--
-- 'pageToken', 'listJobsByPipeline_pageToken' - When Elastic Transcoder returns more than one page of results, use
-- @pageToken@ in subsequent @GET@ requests to get each successive page of
-- results.
--
-- 'pipelineId', 'listJobsByPipeline_pipelineId' - The ID of the pipeline for which you want to get job information.
newListJobsByPipeline ::
  -- | 'pipelineId'
  Prelude.Text ->
  ListJobsByPipeline
newListJobsByPipeline :: Text -> ListJobsByPipeline
newListJobsByPipeline Text
pPipelineId_ =
  ListJobsByPipeline'
    { $sel:ascending:ListJobsByPipeline' :: Maybe Text
ascending = forall a. Maybe a
Prelude.Nothing,
      $sel:pageToken:ListJobsByPipeline' :: Maybe Text
pageToken = forall a. Maybe a
Prelude.Nothing,
      $sel:pipelineId:ListJobsByPipeline' :: Text
pipelineId = Text
pPipelineId_
    }

-- | To list jobs in chronological order by the date and time that they were
-- submitted, enter @true@. To list jobs in reverse chronological order,
-- enter @false@.
listJobsByPipeline_ascending :: Lens.Lens' ListJobsByPipeline (Prelude.Maybe Prelude.Text)
listJobsByPipeline_ascending :: Lens' ListJobsByPipeline (Maybe Text)
listJobsByPipeline_ascending = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\ListJobsByPipeline' {Maybe Text
ascending :: Maybe Text
$sel:ascending:ListJobsByPipeline' :: ListJobsByPipeline -> Maybe Text
ascending} -> Maybe Text
ascending) (\s :: ListJobsByPipeline
s@ListJobsByPipeline' {} Maybe Text
a -> ListJobsByPipeline
s {$sel:ascending:ListJobsByPipeline' :: Maybe Text
ascending = Maybe Text
a} :: ListJobsByPipeline)

-- | When Elastic Transcoder returns more than one page of results, use
-- @pageToken@ in subsequent @GET@ requests to get each successive page of
-- results.
listJobsByPipeline_pageToken :: Lens.Lens' ListJobsByPipeline (Prelude.Maybe Prelude.Text)
listJobsByPipeline_pageToken :: Lens' ListJobsByPipeline (Maybe Text)
listJobsByPipeline_pageToken = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\ListJobsByPipeline' {Maybe Text
pageToken :: Maybe Text
$sel:pageToken:ListJobsByPipeline' :: ListJobsByPipeline -> Maybe Text
pageToken} -> Maybe Text
pageToken) (\s :: ListJobsByPipeline
s@ListJobsByPipeline' {} Maybe Text
a -> ListJobsByPipeline
s {$sel:pageToken:ListJobsByPipeline' :: Maybe Text
pageToken = Maybe Text
a} :: ListJobsByPipeline)

-- | The ID of the pipeline for which you want to get job information.
listJobsByPipeline_pipelineId :: Lens.Lens' ListJobsByPipeline Prelude.Text
listJobsByPipeline_pipelineId :: Lens' ListJobsByPipeline Text
listJobsByPipeline_pipelineId = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\ListJobsByPipeline' {Text
pipelineId :: Text
$sel:pipelineId:ListJobsByPipeline' :: ListJobsByPipeline -> Text
pipelineId} -> Text
pipelineId) (\s :: ListJobsByPipeline
s@ListJobsByPipeline' {} Text
a -> ListJobsByPipeline
s {$sel:pipelineId:ListJobsByPipeline' :: Text
pipelineId = Text
a} :: ListJobsByPipeline)

instance Core.AWSPager ListJobsByPipeline where
  page :: ListJobsByPipeline
-> AWSResponse ListJobsByPipeline -> Maybe ListJobsByPipeline
page ListJobsByPipeline
rq AWSResponse ListJobsByPipeline
rs
    | forall a. AWSTruncated a => a -> Bool
Core.stop
        ( AWSResponse ListJobsByPipeline
rs
            forall s a. s -> Getting (First a) s a -> Maybe a
Lens.^? Lens' ListJobsByPipelineResponse (Maybe Text)
listJobsByPipelineResponse_nextPageToken
            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 ListJobsByPipeline
rs
            forall s a. s -> Getting (First a) s a -> Maybe a
Lens.^? Lens' ListJobsByPipelineResponse (Maybe [Job])
listJobsByPipelineResponse_jobs
            forall b c a. (b -> c) -> (a -> b) -> a -> c
Prelude.. forall a b. Prism (Maybe a) (Maybe b) a b
Lens._Just
        ) =
        forall a. Maybe a
Prelude.Nothing
    | Bool
Prelude.otherwise =
        forall a. a -> Maybe a
Prelude.Just
          forall a b. (a -> b) -> a -> b
Prelude.$ ListJobsByPipeline
rq
          forall a b. a -> (a -> b) -> b
Prelude.& Lens' ListJobsByPipeline (Maybe Text)
listJobsByPipeline_pageToken
          forall s t a b. ASetter s t a b -> b -> s -> t
Lens..~ AWSResponse ListJobsByPipeline
rs
          forall s a. s -> Getting (First a) s a -> Maybe a
Lens.^? Lens' ListJobsByPipelineResponse (Maybe Text)
listJobsByPipelineResponse_nextPageToken
          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 ListJobsByPipeline where
  type
    AWSResponse ListJobsByPipeline =
      ListJobsByPipelineResponse
  request :: (Service -> Service)
-> ListJobsByPipeline -> Request ListJobsByPipeline
request Service -> Service
overrides =
    forall a. ToRequest a => Service -> a -> Request a
Request.get (Service -> Service
overrides Service
defaultService)
  response :: forall (m :: * -> *).
MonadResource m =>
(ByteStringLazy -> IO ByteStringLazy)
-> Service
-> Proxy ListJobsByPipeline
-> ClientResponse ClientBody
-> m (Either
        Error (ClientResponse (AWSResponse ListJobsByPipeline)))
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 [Job] -> Maybe Text -> Int -> ListJobsByPipelineResponse
ListJobsByPipelineResponse'
            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
"Jobs" forall (f :: * -> *) a. Functor f => f (Maybe a) -> a -> f a
Core..!@ forall a. Monoid a => a
Prelude.mempty)
            forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
Prelude.<*> (Object
x forall a. FromJSON a => Object -> Key -> Either String (Maybe a)
Data..?> Key
"NextPageToken")
            forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
Prelude.<*> (forall (f :: * -> *) a. Applicative f => a -> f a
Prelude.pure (forall a. Enum a => a -> Int
Prelude.fromEnum Int
s))
      )

instance Prelude.Hashable ListJobsByPipeline where
  hashWithSalt :: Int -> ListJobsByPipeline -> Int
hashWithSalt Int
_salt ListJobsByPipeline' {Maybe Text
Text
pipelineId :: Text
pageToken :: Maybe Text
ascending :: Maybe Text
$sel:pipelineId:ListJobsByPipeline' :: ListJobsByPipeline -> Text
$sel:pageToken:ListJobsByPipeline' :: ListJobsByPipeline -> Maybe Text
$sel:ascending:ListJobsByPipeline' :: ListJobsByPipeline -> Maybe Text
..} =
    Int
_salt
      forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Maybe Text
ascending
      forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Maybe Text
pageToken
      forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Text
pipelineId

instance Prelude.NFData ListJobsByPipeline where
  rnf :: ListJobsByPipeline -> ()
rnf ListJobsByPipeline' {Maybe Text
Text
pipelineId :: Text
pageToken :: Maybe Text
ascending :: Maybe Text
$sel:pipelineId:ListJobsByPipeline' :: ListJobsByPipeline -> Text
$sel:pageToken:ListJobsByPipeline' :: ListJobsByPipeline -> Maybe Text
$sel:ascending:ListJobsByPipeline' :: ListJobsByPipeline -> Maybe Text
..} =
    forall a. NFData a => a -> ()
Prelude.rnf Maybe Text
ascending
      seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf Maybe Text
pageToken
      seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf Text
pipelineId

instance Data.ToHeaders ListJobsByPipeline where
  toHeaders :: ListJobsByPipeline -> ResponseHeaders
toHeaders = forall a b. a -> b -> a
Prelude.const forall a. Monoid a => a
Prelude.mempty

instance Data.ToPath ListJobsByPipeline where
  toPath :: ListJobsByPipeline -> ByteString
toPath ListJobsByPipeline' {Maybe Text
Text
pipelineId :: Text
pageToken :: Maybe Text
ascending :: Maybe Text
$sel:pipelineId:ListJobsByPipeline' :: ListJobsByPipeline -> Text
$sel:pageToken:ListJobsByPipeline' :: ListJobsByPipeline -> Maybe Text
$sel:ascending:ListJobsByPipeline' :: ListJobsByPipeline -> Maybe Text
..} =
    forall a. Monoid a => [a] -> a
Prelude.mconcat
      [ByteString
"/2012-09-25/jobsByPipeline/", forall a. ToByteString a => a -> ByteString
Data.toBS Text
pipelineId]

instance Data.ToQuery ListJobsByPipeline where
  toQuery :: ListJobsByPipeline -> QueryString
toQuery ListJobsByPipeline' {Maybe Text
Text
pipelineId :: Text
pageToken :: Maybe Text
ascending :: Maybe Text
$sel:pipelineId:ListJobsByPipeline' :: ListJobsByPipeline -> Text
$sel:pageToken:ListJobsByPipeline' :: ListJobsByPipeline -> Maybe Text
$sel:ascending:ListJobsByPipeline' :: ListJobsByPipeline -> Maybe Text
..} =
    forall a. Monoid a => [a] -> a
Prelude.mconcat
      [ ByteString
"Ascending" forall a. ToQuery a => ByteString -> a -> QueryString
Data.=: Maybe Text
ascending,
        ByteString
"PageToken" forall a. ToQuery a => ByteString -> a -> QueryString
Data.=: Maybe Text
pageToken
      ]

-- | The @ListJobsByPipelineResponse@ structure.
--
-- /See:/ 'newListJobsByPipelineResponse' smart constructor.
data ListJobsByPipelineResponse = ListJobsByPipelineResponse'
  { -- | An array of @Job@ objects that are in the specified pipeline.
    ListJobsByPipelineResponse -> Maybe [Job]
jobs :: Prelude.Maybe [Job],
    -- | A value that you use to access the second and subsequent pages of
    -- results, if any. When the jobs in the specified pipeline fit on one page
    -- or when you\'ve reached the last page of results, the value of
    -- @NextPageToken@ is @null@.
    ListJobsByPipelineResponse -> Maybe Text
nextPageToken :: Prelude.Maybe Prelude.Text,
    -- | The response's http status code.
    ListJobsByPipelineResponse -> Int
httpStatus :: Prelude.Int
  }
  deriving (ListJobsByPipelineResponse -> ListJobsByPipelineResponse -> Bool
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: ListJobsByPipelineResponse -> ListJobsByPipelineResponse -> Bool
$c/= :: ListJobsByPipelineResponse -> ListJobsByPipelineResponse -> Bool
== :: ListJobsByPipelineResponse -> ListJobsByPipelineResponse -> Bool
$c== :: ListJobsByPipelineResponse -> ListJobsByPipelineResponse -> Bool
Prelude.Eq, ReadPrec [ListJobsByPipelineResponse]
ReadPrec ListJobsByPipelineResponse
Int -> ReadS ListJobsByPipelineResponse
ReadS [ListJobsByPipelineResponse]
forall a.
(Int -> ReadS a)
-> ReadS [a] -> ReadPrec a -> ReadPrec [a] -> Read a
readListPrec :: ReadPrec [ListJobsByPipelineResponse]
$creadListPrec :: ReadPrec [ListJobsByPipelineResponse]
readPrec :: ReadPrec ListJobsByPipelineResponse
$creadPrec :: ReadPrec ListJobsByPipelineResponse
readList :: ReadS [ListJobsByPipelineResponse]
$creadList :: ReadS [ListJobsByPipelineResponse]
readsPrec :: Int -> ReadS ListJobsByPipelineResponse
$creadsPrec :: Int -> ReadS ListJobsByPipelineResponse
Prelude.Read, Int -> ListJobsByPipelineResponse -> ShowS
[ListJobsByPipelineResponse] -> ShowS
ListJobsByPipelineResponse -> String
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [ListJobsByPipelineResponse] -> ShowS
$cshowList :: [ListJobsByPipelineResponse] -> ShowS
show :: ListJobsByPipelineResponse -> String
$cshow :: ListJobsByPipelineResponse -> String
showsPrec :: Int -> ListJobsByPipelineResponse -> ShowS
$cshowsPrec :: Int -> ListJobsByPipelineResponse -> ShowS
Prelude.Show, forall x.
Rep ListJobsByPipelineResponse x -> ListJobsByPipelineResponse
forall x.
ListJobsByPipelineResponse -> Rep ListJobsByPipelineResponse x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cto :: forall x.
Rep ListJobsByPipelineResponse x -> ListJobsByPipelineResponse
$cfrom :: forall x.
ListJobsByPipelineResponse -> Rep ListJobsByPipelineResponse x
Prelude.Generic)

-- |
-- Create a value of 'ListJobsByPipelineResponse' 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:
--
-- 'jobs', 'listJobsByPipelineResponse_jobs' - An array of @Job@ objects that are in the specified pipeline.
--
-- 'nextPageToken', 'listJobsByPipelineResponse_nextPageToken' - A value that you use to access the second and subsequent pages of
-- results, if any. When the jobs in the specified pipeline fit on one page
-- or when you\'ve reached the last page of results, the value of
-- @NextPageToken@ is @null@.
--
-- 'httpStatus', 'listJobsByPipelineResponse_httpStatus' - The response's http status code.
newListJobsByPipelineResponse ::
  -- | 'httpStatus'
  Prelude.Int ->
  ListJobsByPipelineResponse
newListJobsByPipelineResponse :: Int -> ListJobsByPipelineResponse
newListJobsByPipelineResponse Int
pHttpStatus_ =
  ListJobsByPipelineResponse'
    { $sel:jobs:ListJobsByPipelineResponse' :: Maybe [Job]
jobs = forall a. Maybe a
Prelude.Nothing,
      $sel:nextPageToken:ListJobsByPipelineResponse' :: Maybe Text
nextPageToken = forall a. Maybe a
Prelude.Nothing,
      $sel:httpStatus:ListJobsByPipelineResponse' :: Int
httpStatus = Int
pHttpStatus_
    }

-- | An array of @Job@ objects that are in the specified pipeline.
listJobsByPipelineResponse_jobs :: Lens.Lens' ListJobsByPipelineResponse (Prelude.Maybe [Job])
listJobsByPipelineResponse_jobs :: Lens' ListJobsByPipelineResponse (Maybe [Job])
listJobsByPipelineResponse_jobs = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\ListJobsByPipelineResponse' {Maybe [Job]
jobs :: Maybe [Job]
$sel:jobs:ListJobsByPipelineResponse' :: ListJobsByPipelineResponse -> Maybe [Job]
jobs} -> Maybe [Job]
jobs) (\s :: ListJobsByPipelineResponse
s@ListJobsByPipelineResponse' {} Maybe [Job]
a -> ListJobsByPipelineResponse
s {$sel:jobs:ListJobsByPipelineResponse' :: Maybe [Job]
jobs = Maybe [Job]
a} :: ListJobsByPipelineResponse) forall b c a. (b -> c) -> (a -> b) -> a -> c
Prelude.. forall (f :: * -> *) (g :: * -> *) s t a b.
(Functor f, Functor g) =>
AnIso s t a b -> Iso (f s) (g t) (f a) (g b)
Lens.mapping forall s t a b. (Coercible s a, Coercible t b) => Iso s t a b
Lens.coerced

-- | A value that you use to access the second and subsequent pages of
-- results, if any. When the jobs in the specified pipeline fit on one page
-- or when you\'ve reached the last page of results, the value of
-- @NextPageToken@ is @null@.
listJobsByPipelineResponse_nextPageToken :: Lens.Lens' ListJobsByPipelineResponse (Prelude.Maybe Prelude.Text)
listJobsByPipelineResponse_nextPageToken :: Lens' ListJobsByPipelineResponse (Maybe Text)
listJobsByPipelineResponse_nextPageToken = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\ListJobsByPipelineResponse' {Maybe Text
nextPageToken :: Maybe Text
$sel:nextPageToken:ListJobsByPipelineResponse' :: ListJobsByPipelineResponse -> Maybe Text
nextPageToken} -> Maybe Text
nextPageToken) (\s :: ListJobsByPipelineResponse
s@ListJobsByPipelineResponse' {} Maybe Text
a -> ListJobsByPipelineResponse
s {$sel:nextPageToken:ListJobsByPipelineResponse' :: Maybe Text
nextPageToken = Maybe Text
a} :: ListJobsByPipelineResponse)

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

instance Prelude.NFData ListJobsByPipelineResponse where
  rnf :: ListJobsByPipelineResponse -> ()
rnf ListJobsByPipelineResponse' {Int
Maybe [Job]
Maybe Text
httpStatus :: Int
nextPageToken :: Maybe Text
jobs :: Maybe [Job]
$sel:httpStatus:ListJobsByPipelineResponse' :: ListJobsByPipelineResponse -> Int
$sel:nextPageToken:ListJobsByPipelineResponse' :: ListJobsByPipelineResponse -> Maybe Text
$sel:jobs:ListJobsByPipelineResponse' :: ListJobsByPipelineResponse -> Maybe [Job]
..} =
    forall a. NFData a => a -> ()
Prelude.rnf Maybe [Job]
jobs
      seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf Maybe Text
nextPageToken
      seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf Int
httpStatus