{-# 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.CodeBuild.ListBuildsForProject
-- Copyright   : (c) 2013-2023 Brendan Hay
-- License     : Mozilla Public License, v. 2.0.
-- Maintainer  : Brendan Hay
-- Stability   : auto-generated
-- Portability : non-portable (GHC extensions)
--
-- Gets a list of build identifiers for the specified build project, with
-- each build identifier representing a single build.
--
-- This operation returns paginated results.
module Amazonka.CodeBuild.ListBuildsForProject
  ( -- * Creating a Request
    ListBuildsForProject (..),
    newListBuildsForProject,

    -- * Request Lenses
    listBuildsForProject_nextToken,
    listBuildsForProject_sortOrder,
    listBuildsForProject_projectName,

    -- * Destructuring the Response
    ListBuildsForProjectResponse (..),
    newListBuildsForProjectResponse,

    -- * Response Lenses
    listBuildsForProjectResponse_ids,
    listBuildsForProjectResponse_nextToken,
    listBuildsForProjectResponse_httpStatus,
  )
where

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

-- | /See:/ 'newListBuildsForProject' smart constructor.
data ListBuildsForProject = ListBuildsForProject'
  { -- | During a previous call, if there are more than 100 items in the list,
    -- only the first 100 items are returned, along with a unique string called
    -- a /nextToken/. To get the next batch of items in the list, call this
    -- operation again, adding the next token to the call. To get all of the
    -- items in the list, keep calling this operation with each subsequent next
    -- token that is returned, until no more next tokens are returned.
    ListBuildsForProject -> Maybe Text
nextToken :: Prelude.Maybe Prelude.Text,
    -- | The order to sort the results in. The results are sorted by build
    -- number, not the build identifier. If this is not specified, the results
    -- are sorted in descending order.
    --
    -- Valid values include:
    --
    -- -   @ASCENDING@: List the build identifiers in ascending order, by build
    --     number.
    --
    -- -   @DESCENDING@: List the build identifiers in descending order, by
    --     build number.
    --
    -- If the project has more than 100 builds, setting the sort order will
    -- result in an error.
    ListBuildsForProject -> Maybe SortOrderType
sortOrder :: Prelude.Maybe SortOrderType,
    -- | The name of the CodeBuild project.
    ListBuildsForProject -> Text
projectName :: Prelude.Text
  }
  deriving (ListBuildsForProject -> ListBuildsForProject -> Bool
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: ListBuildsForProject -> ListBuildsForProject -> Bool
$c/= :: ListBuildsForProject -> ListBuildsForProject -> Bool
== :: ListBuildsForProject -> ListBuildsForProject -> Bool
$c== :: ListBuildsForProject -> ListBuildsForProject -> Bool
Prelude.Eq, ReadPrec [ListBuildsForProject]
ReadPrec ListBuildsForProject
Int -> ReadS ListBuildsForProject
ReadS [ListBuildsForProject]
forall a.
(Int -> ReadS a)
-> ReadS [a] -> ReadPrec a -> ReadPrec [a] -> Read a
readListPrec :: ReadPrec [ListBuildsForProject]
$creadListPrec :: ReadPrec [ListBuildsForProject]
readPrec :: ReadPrec ListBuildsForProject
$creadPrec :: ReadPrec ListBuildsForProject
readList :: ReadS [ListBuildsForProject]
$creadList :: ReadS [ListBuildsForProject]
readsPrec :: Int -> ReadS ListBuildsForProject
$creadsPrec :: Int -> ReadS ListBuildsForProject
Prelude.Read, Int -> ListBuildsForProject -> ShowS
[ListBuildsForProject] -> ShowS
ListBuildsForProject -> String
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [ListBuildsForProject] -> ShowS
$cshowList :: [ListBuildsForProject] -> ShowS
show :: ListBuildsForProject -> String
$cshow :: ListBuildsForProject -> String
showsPrec :: Int -> ListBuildsForProject -> ShowS
$cshowsPrec :: Int -> ListBuildsForProject -> ShowS
Prelude.Show, forall x. Rep ListBuildsForProject x -> ListBuildsForProject
forall x. ListBuildsForProject -> Rep ListBuildsForProject x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cto :: forall x. Rep ListBuildsForProject x -> ListBuildsForProject
$cfrom :: forall x. ListBuildsForProject -> Rep ListBuildsForProject x
Prelude.Generic)

-- |
-- Create a value of 'ListBuildsForProject' 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', 'listBuildsForProject_nextToken' - During a previous call, if there are more than 100 items in the list,
-- only the first 100 items are returned, along with a unique string called
-- a /nextToken/. To get the next batch of items in the list, call this
-- operation again, adding the next token to the call. To get all of the
-- items in the list, keep calling this operation with each subsequent next
-- token that is returned, until no more next tokens are returned.
--
-- 'sortOrder', 'listBuildsForProject_sortOrder' - The order to sort the results in. The results are sorted by build
-- number, not the build identifier. If this is not specified, the results
-- are sorted in descending order.
--
-- Valid values include:
--
-- -   @ASCENDING@: List the build identifiers in ascending order, by build
--     number.
--
-- -   @DESCENDING@: List the build identifiers in descending order, by
--     build number.
--
-- If the project has more than 100 builds, setting the sort order will
-- result in an error.
--
-- 'projectName', 'listBuildsForProject_projectName' - The name of the CodeBuild project.
newListBuildsForProject ::
  -- | 'projectName'
  Prelude.Text ->
  ListBuildsForProject
newListBuildsForProject :: Text -> ListBuildsForProject
newListBuildsForProject Text
pProjectName_ =
  ListBuildsForProject'
    { $sel:nextToken:ListBuildsForProject' :: Maybe Text
nextToken = forall a. Maybe a
Prelude.Nothing,
      $sel:sortOrder:ListBuildsForProject' :: Maybe SortOrderType
sortOrder = forall a. Maybe a
Prelude.Nothing,
      $sel:projectName:ListBuildsForProject' :: Text
projectName = Text
pProjectName_
    }

-- | During a previous call, if there are more than 100 items in the list,
-- only the first 100 items are returned, along with a unique string called
-- a /nextToken/. To get the next batch of items in the list, call this
-- operation again, adding the next token to the call. To get all of the
-- items in the list, keep calling this operation with each subsequent next
-- token that is returned, until no more next tokens are returned.
listBuildsForProject_nextToken :: Lens.Lens' ListBuildsForProject (Prelude.Maybe Prelude.Text)
listBuildsForProject_nextToken :: Lens' ListBuildsForProject (Maybe Text)
listBuildsForProject_nextToken = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\ListBuildsForProject' {Maybe Text
nextToken :: Maybe Text
$sel:nextToken:ListBuildsForProject' :: ListBuildsForProject -> Maybe Text
nextToken} -> Maybe Text
nextToken) (\s :: ListBuildsForProject
s@ListBuildsForProject' {} Maybe Text
a -> ListBuildsForProject
s {$sel:nextToken:ListBuildsForProject' :: Maybe Text
nextToken = Maybe Text
a} :: ListBuildsForProject)

-- | The order to sort the results in. The results are sorted by build
-- number, not the build identifier. If this is not specified, the results
-- are sorted in descending order.
--
-- Valid values include:
--
-- -   @ASCENDING@: List the build identifiers in ascending order, by build
--     number.
--
-- -   @DESCENDING@: List the build identifiers in descending order, by
--     build number.
--
-- If the project has more than 100 builds, setting the sort order will
-- result in an error.
listBuildsForProject_sortOrder :: Lens.Lens' ListBuildsForProject (Prelude.Maybe SortOrderType)
listBuildsForProject_sortOrder :: Lens' ListBuildsForProject (Maybe SortOrderType)
listBuildsForProject_sortOrder = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\ListBuildsForProject' {Maybe SortOrderType
sortOrder :: Maybe SortOrderType
$sel:sortOrder:ListBuildsForProject' :: ListBuildsForProject -> Maybe SortOrderType
sortOrder} -> Maybe SortOrderType
sortOrder) (\s :: ListBuildsForProject
s@ListBuildsForProject' {} Maybe SortOrderType
a -> ListBuildsForProject
s {$sel:sortOrder:ListBuildsForProject' :: Maybe SortOrderType
sortOrder = Maybe SortOrderType
a} :: ListBuildsForProject)

-- | The name of the CodeBuild project.
listBuildsForProject_projectName :: Lens.Lens' ListBuildsForProject Prelude.Text
listBuildsForProject_projectName :: Lens' ListBuildsForProject Text
listBuildsForProject_projectName = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\ListBuildsForProject' {Text
projectName :: Text
$sel:projectName:ListBuildsForProject' :: ListBuildsForProject -> Text
projectName} -> Text
projectName) (\s :: ListBuildsForProject
s@ListBuildsForProject' {} Text
a -> ListBuildsForProject
s {$sel:projectName:ListBuildsForProject' :: Text
projectName = Text
a} :: ListBuildsForProject)

instance Core.AWSPager ListBuildsForProject where
  page :: ListBuildsForProject
-> AWSResponse ListBuildsForProject -> Maybe ListBuildsForProject
page ListBuildsForProject
rq AWSResponse ListBuildsForProject
rs
    | forall a. AWSTruncated a => a -> Bool
Core.stop
        ( AWSResponse ListBuildsForProject
rs
            forall s a. s -> Getting (First a) s a -> Maybe a
Lens.^? Lens' ListBuildsForProjectResponse (Maybe Text)
listBuildsForProjectResponse_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 ListBuildsForProject
rs
            forall s a. s -> Getting (First a) s a -> Maybe a
Lens.^? Lens' ListBuildsForProjectResponse (Maybe (NonEmpty Text))
listBuildsForProjectResponse_ids
            forall b c a. (b -> c) -> (a -> b) -> a -> c
Prelude.. forall a b. Prism (Maybe a) (Maybe b) a b
Lens._Just
            forall b c a. (b -> c) -> (a -> b) -> a -> c
Prelude.. forall (p :: * -> * -> *) (f :: * -> *) s a.
(Profunctor p, Contravariant f) =>
(s -> a) -> Optic' p f s a
Lens.to forall l. IsList l => l -> [Item l]
Prelude.toList
        ) =
        forall a. Maybe a
Prelude.Nothing
    | Bool
Prelude.otherwise =
        forall a. a -> Maybe a
Prelude.Just
          forall a b. (a -> b) -> a -> b
Prelude.$ ListBuildsForProject
rq
          forall a b. a -> (a -> b) -> b
Prelude.& Lens' ListBuildsForProject (Maybe Text)
listBuildsForProject_nextToken
          forall s t a b. ASetter s t a b -> b -> s -> t
Lens..~ AWSResponse ListBuildsForProject
rs
          forall s a. s -> Getting (First a) s a -> Maybe a
Lens.^? Lens' ListBuildsForProjectResponse (Maybe Text)
listBuildsForProjectResponse_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 ListBuildsForProject where
  type
    AWSResponse ListBuildsForProject =
      ListBuildsForProjectResponse
  request :: (Service -> Service)
-> ListBuildsForProject -> Request ListBuildsForProject
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 ListBuildsForProject
-> ClientResponse ClientBody
-> m (Either
        Error (ClientResponse (AWSResponse ListBuildsForProject)))
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 (NonEmpty Text)
-> Maybe Text -> Int -> ListBuildsForProjectResponse
ListBuildsForProjectResponse'
            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
"ids")
            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
"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))
      )

instance Prelude.Hashable ListBuildsForProject where
  hashWithSalt :: Int -> ListBuildsForProject -> Int
hashWithSalt Int
_salt ListBuildsForProject' {Maybe Text
Maybe SortOrderType
Text
projectName :: Text
sortOrder :: Maybe SortOrderType
nextToken :: Maybe Text
$sel:projectName:ListBuildsForProject' :: ListBuildsForProject -> Text
$sel:sortOrder:ListBuildsForProject' :: ListBuildsForProject -> Maybe SortOrderType
$sel:nextToken:ListBuildsForProject' :: ListBuildsForProject -> Maybe Text
..} =
    Int
_salt
      forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Maybe Text
nextToken
      forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Maybe SortOrderType
sortOrder
      forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Text
projectName

instance Prelude.NFData ListBuildsForProject where
  rnf :: ListBuildsForProject -> ()
rnf ListBuildsForProject' {Maybe Text
Maybe SortOrderType
Text
projectName :: Text
sortOrder :: Maybe SortOrderType
nextToken :: Maybe Text
$sel:projectName:ListBuildsForProject' :: ListBuildsForProject -> Text
$sel:sortOrder:ListBuildsForProject' :: ListBuildsForProject -> Maybe SortOrderType
$sel:nextToken:ListBuildsForProject' :: ListBuildsForProject -> 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 Maybe SortOrderType
sortOrder
      seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf Text
projectName

instance Data.ToHeaders ListBuildsForProject where
  toHeaders :: ListBuildsForProject -> 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
"CodeBuild_20161006.ListBuildsForProject" ::
                          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 ListBuildsForProject where
  toJSON :: ListBuildsForProject -> Value
toJSON ListBuildsForProject' {Maybe Text
Maybe SortOrderType
Text
projectName :: Text
sortOrder :: Maybe SortOrderType
nextToken :: Maybe Text
$sel:projectName:ListBuildsForProject' :: ListBuildsForProject -> Text
$sel:sortOrder:ListBuildsForProject' :: ListBuildsForProject -> Maybe SortOrderType
$sel:nextToken:ListBuildsForProject' :: ListBuildsForProject -> Maybe Text
..} =
    [Pair] -> Value
Data.object
      ( forall a. [Maybe a] -> [a]
Prelude.catMaybes
          [ (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
"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 SortOrderType
sortOrder,
            forall a. a -> Maybe a
Prelude.Just (Key
"projectName" forall kv v. (KeyValue kv, ToJSON v) => Key -> v -> kv
Data..= Text
projectName)
          ]
      )

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

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

-- | /See:/ 'newListBuildsForProjectResponse' smart constructor.
data ListBuildsForProjectResponse = ListBuildsForProjectResponse'
  { -- | A list of build identifiers for the specified build project, with each
    -- build ID representing a single build.
    ListBuildsForProjectResponse -> Maybe (NonEmpty Text)
ids :: Prelude.Maybe (Prelude.NonEmpty Prelude.Text),
    -- | If there are more than 100 items in the list, only the first 100 items
    -- are returned, along with a unique string called a /nextToken/. To get
    -- the next batch of items in the list, call this operation again, adding
    -- the next token to the call.
    ListBuildsForProjectResponse -> Maybe Text
nextToken :: Prelude.Maybe Prelude.Text,
    -- | The response's http status code.
    ListBuildsForProjectResponse -> Int
httpStatus :: Prelude.Int
  }
  deriving (ListBuildsForProjectResponse
-> ListBuildsForProjectResponse -> Bool
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: ListBuildsForProjectResponse
-> ListBuildsForProjectResponse -> Bool
$c/= :: ListBuildsForProjectResponse
-> ListBuildsForProjectResponse -> Bool
== :: ListBuildsForProjectResponse
-> ListBuildsForProjectResponse -> Bool
$c== :: ListBuildsForProjectResponse
-> ListBuildsForProjectResponse -> Bool
Prelude.Eq, ReadPrec [ListBuildsForProjectResponse]
ReadPrec ListBuildsForProjectResponse
Int -> ReadS ListBuildsForProjectResponse
ReadS [ListBuildsForProjectResponse]
forall a.
(Int -> ReadS a)
-> ReadS [a] -> ReadPrec a -> ReadPrec [a] -> Read a
readListPrec :: ReadPrec [ListBuildsForProjectResponse]
$creadListPrec :: ReadPrec [ListBuildsForProjectResponse]
readPrec :: ReadPrec ListBuildsForProjectResponse
$creadPrec :: ReadPrec ListBuildsForProjectResponse
readList :: ReadS [ListBuildsForProjectResponse]
$creadList :: ReadS [ListBuildsForProjectResponse]
readsPrec :: Int -> ReadS ListBuildsForProjectResponse
$creadsPrec :: Int -> ReadS ListBuildsForProjectResponse
Prelude.Read, Int -> ListBuildsForProjectResponse -> ShowS
[ListBuildsForProjectResponse] -> ShowS
ListBuildsForProjectResponse -> String
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [ListBuildsForProjectResponse] -> ShowS
$cshowList :: [ListBuildsForProjectResponse] -> ShowS
show :: ListBuildsForProjectResponse -> String
$cshow :: ListBuildsForProjectResponse -> String
showsPrec :: Int -> ListBuildsForProjectResponse -> ShowS
$cshowsPrec :: Int -> ListBuildsForProjectResponse -> ShowS
Prelude.Show, forall x.
Rep ListBuildsForProjectResponse x -> ListBuildsForProjectResponse
forall x.
ListBuildsForProjectResponse -> Rep ListBuildsForProjectResponse x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cto :: forall x.
Rep ListBuildsForProjectResponse x -> ListBuildsForProjectResponse
$cfrom :: forall x.
ListBuildsForProjectResponse -> Rep ListBuildsForProjectResponse x
Prelude.Generic)

-- |
-- Create a value of 'ListBuildsForProjectResponse' 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:
--
-- 'ids', 'listBuildsForProjectResponse_ids' - A list of build identifiers for the specified build project, with each
-- build ID representing a single build.
--
-- 'nextToken', 'listBuildsForProjectResponse_nextToken' - If there are more than 100 items in the list, only the first 100 items
-- are returned, along with a unique string called a /nextToken/. To get
-- the next batch of items in the list, call this operation again, adding
-- the next token to the call.
--
-- 'httpStatus', 'listBuildsForProjectResponse_httpStatus' - The response's http status code.
newListBuildsForProjectResponse ::
  -- | 'httpStatus'
  Prelude.Int ->
  ListBuildsForProjectResponse
newListBuildsForProjectResponse :: Int -> ListBuildsForProjectResponse
newListBuildsForProjectResponse Int
pHttpStatus_ =
  ListBuildsForProjectResponse'
    { $sel:ids:ListBuildsForProjectResponse' :: Maybe (NonEmpty Text)
ids =
        forall a. Maybe a
Prelude.Nothing,
      $sel:nextToken:ListBuildsForProjectResponse' :: Maybe Text
nextToken = forall a. Maybe a
Prelude.Nothing,
      $sel:httpStatus:ListBuildsForProjectResponse' :: Int
httpStatus = Int
pHttpStatus_
    }

-- | A list of build identifiers for the specified build project, with each
-- build ID representing a single build.
listBuildsForProjectResponse_ids :: Lens.Lens' ListBuildsForProjectResponse (Prelude.Maybe (Prelude.NonEmpty Prelude.Text))
listBuildsForProjectResponse_ids :: Lens' ListBuildsForProjectResponse (Maybe (NonEmpty Text))
listBuildsForProjectResponse_ids = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\ListBuildsForProjectResponse' {Maybe (NonEmpty Text)
ids :: Maybe (NonEmpty Text)
$sel:ids:ListBuildsForProjectResponse' :: ListBuildsForProjectResponse -> Maybe (NonEmpty Text)
ids} -> Maybe (NonEmpty Text)
ids) (\s :: ListBuildsForProjectResponse
s@ListBuildsForProjectResponse' {} Maybe (NonEmpty Text)
a -> ListBuildsForProjectResponse
s {$sel:ids:ListBuildsForProjectResponse' :: Maybe (NonEmpty Text)
ids = Maybe (NonEmpty Text)
a} :: ListBuildsForProjectResponse) 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

-- | If there are more than 100 items in the list, only the first 100 items
-- are returned, along with a unique string called a /nextToken/. To get
-- the next batch of items in the list, call this operation again, adding
-- the next token to the call.
listBuildsForProjectResponse_nextToken :: Lens.Lens' ListBuildsForProjectResponse (Prelude.Maybe Prelude.Text)
listBuildsForProjectResponse_nextToken :: Lens' ListBuildsForProjectResponse (Maybe Text)
listBuildsForProjectResponse_nextToken = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\ListBuildsForProjectResponse' {Maybe Text
nextToken :: Maybe Text
$sel:nextToken:ListBuildsForProjectResponse' :: ListBuildsForProjectResponse -> Maybe Text
nextToken} -> Maybe Text
nextToken) (\s :: ListBuildsForProjectResponse
s@ListBuildsForProjectResponse' {} Maybe Text
a -> ListBuildsForProjectResponse
s {$sel:nextToken:ListBuildsForProjectResponse' :: Maybe Text
nextToken = Maybe Text
a} :: ListBuildsForProjectResponse)

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

instance Prelude.NFData ListBuildsForProjectResponse where
  rnf :: ListBuildsForProjectResponse -> ()
rnf ListBuildsForProjectResponse' {Int
Maybe (NonEmpty Text)
Maybe Text
httpStatus :: Int
nextToken :: Maybe Text
ids :: Maybe (NonEmpty Text)
$sel:httpStatus:ListBuildsForProjectResponse' :: ListBuildsForProjectResponse -> Int
$sel:nextToken:ListBuildsForProjectResponse' :: ListBuildsForProjectResponse -> Maybe Text
$sel:ids:ListBuildsForProjectResponse' :: ListBuildsForProjectResponse -> Maybe (NonEmpty Text)
..} =
    forall a. NFData a => a -> ()
Prelude.rnf Maybe (NonEmpty Text)
ids
      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 Int
httpStatus