{-# LANGUAGE DeriveGeneric #-}
{-# LANGUAGE DuplicateRecordFields #-}
{-# LANGUAGE NamedFieldPuns #-}
{-# LANGUAGE OverloadedStrings #-}
{-# LANGUAGE RecordWildCards #-}
{-# LANGUAGE StrictData #-}
{-# LANGUAGE NoImplicitPrelude #-}
{-# 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.Types.BuildBatch
-- Copyright   : (c) 2013-2023 Brendan Hay
-- License     : Mozilla Public License, v. 2.0.
-- Maintainer  : Brendan Hay
-- Stability   : auto-generated
-- Portability : non-portable (GHC extensions)
module Amazonka.CodeBuild.Types.BuildBatch where

import Amazonka.CodeBuild.Types.BuildArtifacts
import Amazonka.CodeBuild.Types.BuildBatchPhase
import Amazonka.CodeBuild.Types.BuildGroup
import Amazonka.CodeBuild.Types.LogsConfig
import Amazonka.CodeBuild.Types.ProjectBuildBatchConfig
import Amazonka.CodeBuild.Types.ProjectCache
import Amazonka.CodeBuild.Types.ProjectEnvironment
import Amazonka.CodeBuild.Types.ProjectFileSystemLocation
import Amazonka.CodeBuild.Types.ProjectSource
import Amazonka.CodeBuild.Types.ProjectSourceVersion
import Amazonka.CodeBuild.Types.StatusType
import Amazonka.CodeBuild.Types.VpcConfig
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

-- | Contains information about a batch build.
--
-- /See:/ 'newBuildBatch' smart constructor.
data BuildBatch = BuildBatch'
  { -- | The ARN of the batch build.
    BuildBatch -> Maybe Text
arn :: Prelude.Maybe Prelude.Text,
    -- | A @BuildArtifacts@ object the defines the build artifacts for this batch
    -- build.
    BuildBatch -> Maybe BuildArtifacts
artifacts :: Prelude.Maybe BuildArtifacts,
    BuildBatch -> Maybe ProjectBuildBatchConfig
buildBatchConfig :: Prelude.Maybe ProjectBuildBatchConfig,
    -- | The number of the batch build. For each project, the @buildBatchNumber@
    -- of its first batch build is @1@. The @buildBatchNumber@ of each
    -- subsequent batch build is incremented by @1@. If a batch build is
    -- deleted, the @buildBatchNumber@ of other batch builds does not change.
    BuildBatch -> Maybe Integer
buildBatchNumber :: Prelude.Maybe Prelude.Integer,
    -- | The status of the batch build.
    BuildBatch -> Maybe StatusType
buildBatchStatus :: Prelude.Maybe StatusType,
    -- | An array of @BuildGroup@ objects that define the build groups for the
    -- batch build.
    BuildBatch -> Maybe [BuildGroup]
buildGroups :: Prelude.Maybe [BuildGroup],
    -- | Specifies the maximum amount of time, in minutes, that the build in a
    -- batch must be completed in.
    BuildBatch -> Maybe Int
buildTimeoutInMinutes :: Prelude.Maybe Prelude.Int,
    BuildBatch -> Maybe ProjectCache
cache :: Prelude.Maybe ProjectCache,
    -- | Indicates if the batch build is complete.
    BuildBatch -> Maybe Bool
complete :: Prelude.Maybe Prelude.Bool,
    -- | The current phase of the batch build.
    BuildBatch -> Maybe Text
currentPhase :: Prelude.Maybe Prelude.Text,
    -- | Specifies if session debugging is enabled for this batch build. For more
    -- information, see
    -- <https://docs.aws.amazon.com/codebuild/latest/userguide/session-manager.html Viewing a running build in Session Manager>.
    -- Batch session debugging is not supported for matrix batch builds.
    BuildBatch -> Maybe Bool
debugSessionEnabled :: Prelude.Maybe Prelude.Bool,
    -- | The Key Management Service customer master key (CMK) to be used for
    -- encrypting the batch build output artifacts.
    --
    -- You can use a cross-account KMS key to encrypt the build output
    -- artifacts if your service role has permission to that key.
    --
    -- You can specify either the Amazon Resource Name (ARN) of the CMK or, if
    -- available, the CMK\'s alias (using the format @alias\/\<alias-name>@).
    BuildBatch -> Maybe Text
encryptionKey :: Prelude.Maybe Prelude.Text,
    -- | The date and time that the batch build ended.
    BuildBatch -> Maybe POSIX
endTime :: Prelude.Maybe Data.POSIX,
    BuildBatch -> Maybe ProjectEnvironment
environment :: Prelude.Maybe ProjectEnvironment,
    -- | An array of @ProjectFileSystemLocation@ objects for the batch build
    -- project. A @ProjectFileSystemLocation@ object specifies the
    -- @identifier@, @location@, @mountOptions@, @mountPoint@, and @type@ of a
    -- file system created using Amazon Elastic File System.
    BuildBatch -> Maybe [ProjectFileSystemLocation]
fileSystemLocations :: Prelude.Maybe [ProjectFileSystemLocation],
    -- | The identifier of the batch build.
    BuildBatch -> Maybe Text
id :: Prelude.Maybe Prelude.Text,
    -- | The entity that started the batch build. Valid values include:
    --
    -- -   If CodePipeline started the build, the pipeline\'s name (for
    --     example, @codepipeline\/my-demo-pipeline@).
    --
    -- -   If an IAM user started the build, the user\'s name.
    --
    -- -   If the Jenkins plugin for CodeBuild started the build, the string
    --     @CodeBuild-Jenkins-Plugin@.
    BuildBatch -> Maybe Text
initiator :: Prelude.Maybe Prelude.Text,
    BuildBatch -> Maybe LogsConfig
logConfig :: Prelude.Maybe LogsConfig,
    -- | An array of @BuildBatchPhase@ objects the specify the phases of the
    -- batch build.
    BuildBatch -> Maybe [BuildBatchPhase]
phases :: Prelude.Maybe [BuildBatchPhase],
    -- | The name of the batch build project.
    BuildBatch -> Maybe Text
projectName :: Prelude.Maybe Prelude.Text,
    -- | Specifies the amount of time, in minutes, that the batch build is
    -- allowed to be queued before it times out.
    BuildBatch -> Maybe Int
queuedTimeoutInMinutes :: Prelude.Maybe Prelude.Int,
    -- | The identifier of the resolved version of this batch build\'s source
    -- code.
    --
    -- -   For CodeCommit, GitHub, GitHub Enterprise, and BitBucket, the commit
    --     ID.
    --
    -- -   For CodePipeline, the source revision provided by CodePipeline.
    --
    -- -   For Amazon S3, this does not apply.
    BuildBatch -> Maybe Text
resolvedSourceVersion :: Prelude.Maybe Prelude.Text,
    -- | An array of @BuildArtifacts@ objects the define the build artifacts for
    -- this batch build.
    BuildBatch -> Maybe [BuildArtifacts]
secondaryArtifacts :: Prelude.Maybe [BuildArtifacts],
    -- | An array of @ProjectSourceVersion@ objects. Each @ProjectSourceVersion@
    -- must be one of:
    --
    -- -   For CodeCommit: the commit ID, branch, or Git tag to use.
    --
    -- -   For GitHub: the commit ID, pull request ID, branch name, or tag name
    --     that corresponds to the version of the source code you want to
    --     build. If a pull request ID is specified, it must use the format
    --     @pr\/pull-request-ID@ (for example, @pr\/25@). If a branch name is
    --     specified, the branch\'s HEAD commit ID is used. If not specified,
    --     the default branch\'s HEAD commit ID is used.
    --
    -- -   For Bitbucket: the commit ID, branch name, or tag name that
    --     corresponds to the version of the source code you want to build. If
    --     a branch name is specified, the branch\'s HEAD commit ID is used. If
    --     not specified, the default branch\'s HEAD commit ID is used.
    --
    -- -   For Amazon S3: the version ID of the object that represents the
    --     build input ZIP file to use.
    BuildBatch -> Maybe [ProjectSourceVersion]
secondarySourceVersions :: Prelude.Maybe [ProjectSourceVersion],
    -- | An array of @ProjectSource@ objects that define the sources for the
    -- batch build.
    BuildBatch -> Maybe [ProjectSource]
secondarySources :: Prelude.Maybe [ProjectSource],
    -- | The name of a service role used for builds in the batch.
    BuildBatch -> Maybe Text
serviceRole :: Prelude.Maybe Prelude.Text,
    BuildBatch -> Maybe ProjectSource
source :: Prelude.Maybe ProjectSource,
    -- | The identifier of the version of the source code to be built.
    BuildBatch -> Maybe Text
sourceVersion :: Prelude.Maybe Prelude.Text,
    -- | The date and time that the batch build started.
    BuildBatch -> Maybe POSIX
startTime :: Prelude.Maybe Data.POSIX,
    BuildBatch -> Maybe VpcConfig
vpcConfig :: Prelude.Maybe VpcConfig
  }
  deriving (BuildBatch -> BuildBatch -> Bool
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: BuildBatch -> BuildBatch -> Bool
$c/= :: BuildBatch -> BuildBatch -> Bool
== :: BuildBatch -> BuildBatch -> Bool
$c== :: BuildBatch -> BuildBatch -> Bool
Prelude.Eq, ReadPrec [BuildBatch]
ReadPrec BuildBatch
Int -> ReadS BuildBatch
ReadS [BuildBatch]
forall a.
(Int -> ReadS a)
-> ReadS [a] -> ReadPrec a -> ReadPrec [a] -> Read a
readListPrec :: ReadPrec [BuildBatch]
$creadListPrec :: ReadPrec [BuildBatch]
readPrec :: ReadPrec BuildBatch
$creadPrec :: ReadPrec BuildBatch
readList :: ReadS [BuildBatch]
$creadList :: ReadS [BuildBatch]
readsPrec :: Int -> ReadS BuildBatch
$creadsPrec :: Int -> ReadS BuildBatch
Prelude.Read, Int -> BuildBatch -> ShowS
[BuildBatch] -> ShowS
BuildBatch -> String
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [BuildBatch] -> ShowS
$cshowList :: [BuildBatch] -> ShowS
show :: BuildBatch -> String
$cshow :: BuildBatch -> String
showsPrec :: Int -> BuildBatch -> ShowS
$cshowsPrec :: Int -> BuildBatch -> ShowS
Prelude.Show, forall x. Rep BuildBatch x -> BuildBatch
forall x. BuildBatch -> Rep BuildBatch x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cto :: forall x. Rep BuildBatch x -> BuildBatch
$cfrom :: forall x. BuildBatch -> Rep BuildBatch x
Prelude.Generic)

-- |
-- Create a value of 'BuildBatch' 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:
--
-- 'arn', 'buildBatch_arn' - The ARN of the batch build.
--
-- 'artifacts', 'buildBatch_artifacts' - A @BuildArtifacts@ object the defines the build artifacts for this batch
-- build.
--
-- 'buildBatchConfig', 'buildBatch_buildBatchConfig' - Undocumented member.
--
-- 'buildBatchNumber', 'buildBatch_buildBatchNumber' - The number of the batch build. For each project, the @buildBatchNumber@
-- of its first batch build is @1@. The @buildBatchNumber@ of each
-- subsequent batch build is incremented by @1@. If a batch build is
-- deleted, the @buildBatchNumber@ of other batch builds does not change.
--
-- 'buildBatchStatus', 'buildBatch_buildBatchStatus' - The status of the batch build.
--
-- 'buildGroups', 'buildBatch_buildGroups' - An array of @BuildGroup@ objects that define the build groups for the
-- batch build.
--
-- 'buildTimeoutInMinutes', 'buildBatch_buildTimeoutInMinutes' - Specifies the maximum amount of time, in minutes, that the build in a
-- batch must be completed in.
--
-- 'cache', 'buildBatch_cache' - Undocumented member.
--
-- 'complete', 'buildBatch_complete' - Indicates if the batch build is complete.
--
-- 'currentPhase', 'buildBatch_currentPhase' - The current phase of the batch build.
--
-- 'debugSessionEnabled', 'buildBatch_debugSessionEnabled' - Specifies if session debugging is enabled for this batch build. For more
-- information, see
-- <https://docs.aws.amazon.com/codebuild/latest/userguide/session-manager.html Viewing a running build in Session Manager>.
-- Batch session debugging is not supported for matrix batch builds.
--
-- 'encryptionKey', 'buildBatch_encryptionKey' - The Key Management Service customer master key (CMK) to be used for
-- encrypting the batch build output artifacts.
--
-- You can use a cross-account KMS key to encrypt the build output
-- artifacts if your service role has permission to that key.
--
-- You can specify either the Amazon Resource Name (ARN) of the CMK or, if
-- available, the CMK\'s alias (using the format @alias\/\<alias-name>@).
--
-- 'endTime', 'buildBatch_endTime' - The date and time that the batch build ended.
--
-- 'environment', 'buildBatch_environment' - Undocumented member.
--
-- 'fileSystemLocations', 'buildBatch_fileSystemLocations' - An array of @ProjectFileSystemLocation@ objects for the batch build
-- project. A @ProjectFileSystemLocation@ object specifies the
-- @identifier@, @location@, @mountOptions@, @mountPoint@, and @type@ of a
-- file system created using Amazon Elastic File System.
--
-- 'id', 'buildBatch_id' - The identifier of the batch build.
--
-- 'initiator', 'buildBatch_initiator' - The entity that started the batch build. Valid values include:
--
-- -   If CodePipeline started the build, the pipeline\'s name (for
--     example, @codepipeline\/my-demo-pipeline@).
--
-- -   If an IAM user started the build, the user\'s name.
--
-- -   If the Jenkins plugin for CodeBuild started the build, the string
--     @CodeBuild-Jenkins-Plugin@.
--
-- 'logConfig', 'buildBatch_logConfig' - Undocumented member.
--
-- 'phases', 'buildBatch_phases' - An array of @BuildBatchPhase@ objects the specify the phases of the
-- batch build.
--
-- 'projectName', 'buildBatch_projectName' - The name of the batch build project.
--
-- 'queuedTimeoutInMinutes', 'buildBatch_queuedTimeoutInMinutes' - Specifies the amount of time, in minutes, that the batch build is
-- allowed to be queued before it times out.
--
-- 'resolvedSourceVersion', 'buildBatch_resolvedSourceVersion' - The identifier of the resolved version of this batch build\'s source
-- code.
--
-- -   For CodeCommit, GitHub, GitHub Enterprise, and BitBucket, the commit
--     ID.
--
-- -   For CodePipeline, the source revision provided by CodePipeline.
--
-- -   For Amazon S3, this does not apply.
--
-- 'secondaryArtifacts', 'buildBatch_secondaryArtifacts' - An array of @BuildArtifacts@ objects the define the build artifacts for
-- this batch build.
--
-- 'secondarySourceVersions', 'buildBatch_secondarySourceVersions' - An array of @ProjectSourceVersion@ objects. Each @ProjectSourceVersion@
-- must be one of:
--
-- -   For CodeCommit: the commit ID, branch, or Git tag to use.
--
-- -   For GitHub: the commit ID, pull request ID, branch name, or tag name
--     that corresponds to the version of the source code you want to
--     build. If a pull request ID is specified, it must use the format
--     @pr\/pull-request-ID@ (for example, @pr\/25@). If a branch name is
--     specified, the branch\'s HEAD commit ID is used. If not specified,
--     the default branch\'s HEAD commit ID is used.
--
-- -   For Bitbucket: the commit ID, branch name, or tag name that
--     corresponds to the version of the source code you want to build. If
--     a branch name is specified, the branch\'s HEAD commit ID is used. If
--     not specified, the default branch\'s HEAD commit ID is used.
--
-- -   For Amazon S3: the version ID of the object that represents the
--     build input ZIP file to use.
--
-- 'secondarySources', 'buildBatch_secondarySources' - An array of @ProjectSource@ objects that define the sources for the
-- batch build.
--
-- 'serviceRole', 'buildBatch_serviceRole' - The name of a service role used for builds in the batch.
--
-- 'source', 'buildBatch_source' - Undocumented member.
--
-- 'sourceVersion', 'buildBatch_sourceVersion' - The identifier of the version of the source code to be built.
--
-- 'startTime', 'buildBatch_startTime' - The date and time that the batch build started.
--
-- 'vpcConfig', 'buildBatch_vpcConfig' - Undocumented member.
newBuildBatch ::
  BuildBatch
newBuildBatch :: BuildBatch
newBuildBatch =
  BuildBatch'
    { $sel:arn:BuildBatch' :: Maybe Text
arn = forall a. Maybe a
Prelude.Nothing,
      $sel:artifacts:BuildBatch' :: Maybe BuildArtifacts
artifacts = forall a. Maybe a
Prelude.Nothing,
      $sel:buildBatchConfig:BuildBatch' :: Maybe ProjectBuildBatchConfig
buildBatchConfig = forall a. Maybe a
Prelude.Nothing,
      $sel:buildBatchNumber:BuildBatch' :: Maybe Integer
buildBatchNumber = forall a. Maybe a
Prelude.Nothing,
      $sel:buildBatchStatus:BuildBatch' :: Maybe StatusType
buildBatchStatus = forall a. Maybe a
Prelude.Nothing,
      $sel:buildGroups:BuildBatch' :: Maybe [BuildGroup]
buildGroups = forall a. Maybe a
Prelude.Nothing,
      $sel:buildTimeoutInMinutes:BuildBatch' :: Maybe Int
buildTimeoutInMinutes = forall a. Maybe a
Prelude.Nothing,
      $sel:cache:BuildBatch' :: Maybe ProjectCache
cache = forall a. Maybe a
Prelude.Nothing,
      $sel:complete:BuildBatch' :: Maybe Bool
complete = forall a. Maybe a
Prelude.Nothing,
      $sel:currentPhase:BuildBatch' :: Maybe Text
currentPhase = forall a. Maybe a
Prelude.Nothing,
      $sel:debugSessionEnabled:BuildBatch' :: Maybe Bool
debugSessionEnabled = forall a. Maybe a
Prelude.Nothing,
      $sel:encryptionKey:BuildBatch' :: Maybe Text
encryptionKey = forall a. Maybe a
Prelude.Nothing,
      $sel:endTime:BuildBatch' :: Maybe POSIX
endTime = forall a. Maybe a
Prelude.Nothing,
      $sel:environment:BuildBatch' :: Maybe ProjectEnvironment
environment = forall a. Maybe a
Prelude.Nothing,
      $sel:fileSystemLocations:BuildBatch' :: Maybe [ProjectFileSystemLocation]
fileSystemLocations = forall a. Maybe a
Prelude.Nothing,
      $sel:id:BuildBatch' :: Maybe Text
id = forall a. Maybe a
Prelude.Nothing,
      $sel:initiator:BuildBatch' :: Maybe Text
initiator = forall a. Maybe a
Prelude.Nothing,
      $sel:logConfig:BuildBatch' :: Maybe LogsConfig
logConfig = forall a. Maybe a
Prelude.Nothing,
      $sel:phases:BuildBatch' :: Maybe [BuildBatchPhase]
phases = forall a. Maybe a
Prelude.Nothing,
      $sel:projectName:BuildBatch' :: Maybe Text
projectName = forall a. Maybe a
Prelude.Nothing,
      $sel:queuedTimeoutInMinutes:BuildBatch' :: Maybe Int
queuedTimeoutInMinutes = forall a. Maybe a
Prelude.Nothing,
      $sel:resolvedSourceVersion:BuildBatch' :: Maybe Text
resolvedSourceVersion = forall a. Maybe a
Prelude.Nothing,
      $sel:secondaryArtifacts:BuildBatch' :: Maybe [BuildArtifacts]
secondaryArtifacts = forall a. Maybe a
Prelude.Nothing,
      $sel:secondarySourceVersions:BuildBatch' :: Maybe [ProjectSourceVersion]
secondarySourceVersions = forall a. Maybe a
Prelude.Nothing,
      $sel:secondarySources:BuildBatch' :: Maybe [ProjectSource]
secondarySources = forall a. Maybe a
Prelude.Nothing,
      $sel:serviceRole:BuildBatch' :: Maybe Text
serviceRole = forall a. Maybe a
Prelude.Nothing,
      $sel:source:BuildBatch' :: Maybe ProjectSource
source = forall a. Maybe a
Prelude.Nothing,
      $sel:sourceVersion:BuildBatch' :: Maybe Text
sourceVersion = forall a. Maybe a
Prelude.Nothing,
      $sel:startTime:BuildBatch' :: Maybe POSIX
startTime = forall a. Maybe a
Prelude.Nothing,
      $sel:vpcConfig:BuildBatch' :: Maybe VpcConfig
vpcConfig = forall a. Maybe a
Prelude.Nothing
    }

-- | The ARN of the batch build.
buildBatch_arn :: Lens.Lens' BuildBatch (Prelude.Maybe Prelude.Text)
buildBatch_arn :: Lens' BuildBatch (Maybe Text)
buildBatch_arn = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\BuildBatch' {Maybe Text
arn :: Maybe Text
$sel:arn:BuildBatch' :: BuildBatch -> Maybe Text
arn} -> Maybe Text
arn) (\s :: BuildBatch
s@BuildBatch' {} Maybe Text
a -> BuildBatch
s {$sel:arn:BuildBatch' :: Maybe Text
arn = Maybe Text
a} :: BuildBatch)

-- | A @BuildArtifacts@ object the defines the build artifacts for this batch
-- build.
buildBatch_artifacts :: Lens.Lens' BuildBatch (Prelude.Maybe BuildArtifacts)
buildBatch_artifacts :: Lens' BuildBatch (Maybe BuildArtifacts)
buildBatch_artifacts = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\BuildBatch' {Maybe BuildArtifacts
artifacts :: Maybe BuildArtifacts
$sel:artifacts:BuildBatch' :: BuildBatch -> Maybe BuildArtifacts
artifacts} -> Maybe BuildArtifacts
artifacts) (\s :: BuildBatch
s@BuildBatch' {} Maybe BuildArtifacts
a -> BuildBatch
s {$sel:artifacts:BuildBatch' :: Maybe BuildArtifacts
artifacts = Maybe BuildArtifacts
a} :: BuildBatch)

-- | Undocumented member.
buildBatch_buildBatchConfig :: Lens.Lens' BuildBatch (Prelude.Maybe ProjectBuildBatchConfig)
buildBatch_buildBatchConfig :: Lens' BuildBatch (Maybe ProjectBuildBatchConfig)
buildBatch_buildBatchConfig = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\BuildBatch' {Maybe ProjectBuildBatchConfig
buildBatchConfig :: Maybe ProjectBuildBatchConfig
$sel:buildBatchConfig:BuildBatch' :: BuildBatch -> Maybe ProjectBuildBatchConfig
buildBatchConfig} -> Maybe ProjectBuildBatchConfig
buildBatchConfig) (\s :: BuildBatch
s@BuildBatch' {} Maybe ProjectBuildBatchConfig
a -> BuildBatch
s {$sel:buildBatchConfig:BuildBatch' :: Maybe ProjectBuildBatchConfig
buildBatchConfig = Maybe ProjectBuildBatchConfig
a} :: BuildBatch)

-- | The number of the batch build. For each project, the @buildBatchNumber@
-- of its first batch build is @1@. The @buildBatchNumber@ of each
-- subsequent batch build is incremented by @1@. If a batch build is
-- deleted, the @buildBatchNumber@ of other batch builds does not change.
buildBatch_buildBatchNumber :: Lens.Lens' BuildBatch (Prelude.Maybe Prelude.Integer)
buildBatch_buildBatchNumber :: Lens' BuildBatch (Maybe Integer)
buildBatch_buildBatchNumber = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\BuildBatch' {Maybe Integer
buildBatchNumber :: Maybe Integer
$sel:buildBatchNumber:BuildBatch' :: BuildBatch -> Maybe Integer
buildBatchNumber} -> Maybe Integer
buildBatchNumber) (\s :: BuildBatch
s@BuildBatch' {} Maybe Integer
a -> BuildBatch
s {$sel:buildBatchNumber:BuildBatch' :: Maybe Integer
buildBatchNumber = Maybe Integer
a} :: BuildBatch)

-- | The status of the batch build.
buildBatch_buildBatchStatus :: Lens.Lens' BuildBatch (Prelude.Maybe StatusType)
buildBatch_buildBatchStatus :: Lens' BuildBatch (Maybe StatusType)
buildBatch_buildBatchStatus = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\BuildBatch' {Maybe StatusType
buildBatchStatus :: Maybe StatusType
$sel:buildBatchStatus:BuildBatch' :: BuildBatch -> Maybe StatusType
buildBatchStatus} -> Maybe StatusType
buildBatchStatus) (\s :: BuildBatch
s@BuildBatch' {} Maybe StatusType
a -> BuildBatch
s {$sel:buildBatchStatus:BuildBatch' :: Maybe StatusType
buildBatchStatus = Maybe StatusType
a} :: BuildBatch)

-- | An array of @BuildGroup@ objects that define the build groups for the
-- batch build.
buildBatch_buildGroups :: Lens.Lens' BuildBatch (Prelude.Maybe [BuildGroup])
buildBatch_buildGroups :: Lens' BuildBatch (Maybe [BuildGroup])
buildBatch_buildGroups = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\BuildBatch' {Maybe [BuildGroup]
buildGroups :: Maybe [BuildGroup]
$sel:buildGroups:BuildBatch' :: BuildBatch -> Maybe [BuildGroup]
buildGroups} -> Maybe [BuildGroup]
buildGroups) (\s :: BuildBatch
s@BuildBatch' {} Maybe [BuildGroup]
a -> BuildBatch
s {$sel:buildGroups:BuildBatch' :: Maybe [BuildGroup]
buildGroups = Maybe [BuildGroup]
a} :: BuildBatch) 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

-- | Specifies the maximum amount of time, in minutes, that the build in a
-- batch must be completed in.
buildBatch_buildTimeoutInMinutes :: Lens.Lens' BuildBatch (Prelude.Maybe Prelude.Int)
buildBatch_buildTimeoutInMinutes :: Lens' BuildBatch (Maybe Int)
buildBatch_buildTimeoutInMinutes = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\BuildBatch' {Maybe Int
buildTimeoutInMinutes :: Maybe Int
$sel:buildTimeoutInMinutes:BuildBatch' :: BuildBatch -> Maybe Int
buildTimeoutInMinutes} -> Maybe Int
buildTimeoutInMinutes) (\s :: BuildBatch
s@BuildBatch' {} Maybe Int
a -> BuildBatch
s {$sel:buildTimeoutInMinutes:BuildBatch' :: Maybe Int
buildTimeoutInMinutes = Maybe Int
a} :: BuildBatch)

-- | Undocumented member.
buildBatch_cache :: Lens.Lens' BuildBatch (Prelude.Maybe ProjectCache)
buildBatch_cache :: Lens' BuildBatch (Maybe ProjectCache)
buildBatch_cache = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\BuildBatch' {Maybe ProjectCache
cache :: Maybe ProjectCache
$sel:cache:BuildBatch' :: BuildBatch -> Maybe ProjectCache
cache} -> Maybe ProjectCache
cache) (\s :: BuildBatch
s@BuildBatch' {} Maybe ProjectCache
a -> BuildBatch
s {$sel:cache:BuildBatch' :: Maybe ProjectCache
cache = Maybe ProjectCache
a} :: BuildBatch)

-- | Indicates if the batch build is complete.
buildBatch_complete :: Lens.Lens' BuildBatch (Prelude.Maybe Prelude.Bool)
buildBatch_complete :: Lens' BuildBatch (Maybe Bool)
buildBatch_complete = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\BuildBatch' {Maybe Bool
complete :: Maybe Bool
$sel:complete:BuildBatch' :: BuildBatch -> Maybe Bool
complete} -> Maybe Bool
complete) (\s :: BuildBatch
s@BuildBatch' {} Maybe Bool
a -> BuildBatch
s {$sel:complete:BuildBatch' :: Maybe Bool
complete = Maybe Bool
a} :: BuildBatch)

-- | The current phase of the batch build.
buildBatch_currentPhase :: Lens.Lens' BuildBatch (Prelude.Maybe Prelude.Text)
buildBatch_currentPhase :: Lens' BuildBatch (Maybe Text)
buildBatch_currentPhase = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\BuildBatch' {Maybe Text
currentPhase :: Maybe Text
$sel:currentPhase:BuildBatch' :: BuildBatch -> Maybe Text
currentPhase} -> Maybe Text
currentPhase) (\s :: BuildBatch
s@BuildBatch' {} Maybe Text
a -> BuildBatch
s {$sel:currentPhase:BuildBatch' :: Maybe Text
currentPhase = Maybe Text
a} :: BuildBatch)

-- | Specifies if session debugging is enabled for this batch build. For more
-- information, see
-- <https://docs.aws.amazon.com/codebuild/latest/userguide/session-manager.html Viewing a running build in Session Manager>.
-- Batch session debugging is not supported for matrix batch builds.
buildBatch_debugSessionEnabled :: Lens.Lens' BuildBatch (Prelude.Maybe Prelude.Bool)
buildBatch_debugSessionEnabled :: Lens' BuildBatch (Maybe Bool)
buildBatch_debugSessionEnabled = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\BuildBatch' {Maybe Bool
debugSessionEnabled :: Maybe Bool
$sel:debugSessionEnabled:BuildBatch' :: BuildBatch -> Maybe Bool
debugSessionEnabled} -> Maybe Bool
debugSessionEnabled) (\s :: BuildBatch
s@BuildBatch' {} Maybe Bool
a -> BuildBatch
s {$sel:debugSessionEnabled:BuildBatch' :: Maybe Bool
debugSessionEnabled = Maybe Bool
a} :: BuildBatch)

-- | The Key Management Service customer master key (CMK) to be used for
-- encrypting the batch build output artifacts.
--
-- You can use a cross-account KMS key to encrypt the build output
-- artifacts if your service role has permission to that key.
--
-- You can specify either the Amazon Resource Name (ARN) of the CMK or, if
-- available, the CMK\'s alias (using the format @alias\/\<alias-name>@).
buildBatch_encryptionKey :: Lens.Lens' BuildBatch (Prelude.Maybe Prelude.Text)
buildBatch_encryptionKey :: Lens' BuildBatch (Maybe Text)
buildBatch_encryptionKey = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\BuildBatch' {Maybe Text
encryptionKey :: Maybe Text
$sel:encryptionKey:BuildBatch' :: BuildBatch -> Maybe Text
encryptionKey} -> Maybe Text
encryptionKey) (\s :: BuildBatch
s@BuildBatch' {} Maybe Text
a -> BuildBatch
s {$sel:encryptionKey:BuildBatch' :: Maybe Text
encryptionKey = Maybe Text
a} :: BuildBatch)

-- | The date and time that the batch build ended.
buildBatch_endTime :: Lens.Lens' BuildBatch (Prelude.Maybe Prelude.UTCTime)
buildBatch_endTime :: Lens' BuildBatch (Maybe UTCTime)
buildBatch_endTime = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\BuildBatch' {Maybe POSIX
endTime :: Maybe POSIX
$sel:endTime:BuildBatch' :: BuildBatch -> Maybe POSIX
endTime} -> Maybe POSIX
endTime) (\s :: BuildBatch
s@BuildBatch' {} Maybe POSIX
a -> BuildBatch
s {$sel:endTime:BuildBatch' :: Maybe POSIX
endTime = Maybe POSIX
a} :: BuildBatch) 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

-- | Undocumented member.
buildBatch_environment :: Lens.Lens' BuildBatch (Prelude.Maybe ProjectEnvironment)
buildBatch_environment :: Lens' BuildBatch (Maybe ProjectEnvironment)
buildBatch_environment = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\BuildBatch' {Maybe ProjectEnvironment
environment :: Maybe ProjectEnvironment
$sel:environment:BuildBatch' :: BuildBatch -> Maybe ProjectEnvironment
environment} -> Maybe ProjectEnvironment
environment) (\s :: BuildBatch
s@BuildBatch' {} Maybe ProjectEnvironment
a -> BuildBatch
s {$sel:environment:BuildBatch' :: Maybe ProjectEnvironment
environment = Maybe ProjectEnvironment
a} :: BuildBatch)

-- | An array of @ProjectFileSystemLocation@ objects for the batch build
-- project. A @ProjectFileSystemLocation@ object specifies the
-- @identifier@, @location@, @mountOptions@, @mountPoint@, and @type@ of a
-- file system created using Amazon Elastic File System.
buildBatch_fileSystemLocations :: Lens.Lens' BuildBatch (Prelude.Maybe [ProjectFileSystemLocation])
buildBatch_fileSystemLocations :: Lens' BuildBatch (Maybe [ProjectFileSystemLocation])
buildBatch_fileSystemLocations = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\BuildBatch' {Maybe [ProjectFileSystemLocation]
fileSystemLocations :: Maybe [ProjectFileSystemLocation]
$sel:fileSystemLocations:BuildBatch' :: BuildBatch -> Maybe [ProjectFileSystemLocation]
fileSystemLocations} -> Maybe [ProjectFileSystemLocation]
fileSystemLocations) (\s :: BuildBatch
s@BuildBatch' {} Maybe [ProjectFileSystemLocation]
a -> BuildBatch
s {$sel:fileSystemLocations:BuildBatch' :: Maybe [ProjectFileSystemLocation]
fileSystemLocations = Maybe [ProjectFileSystemLocation]
a} :: BuildBatch) 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

-- | The identifier of the batch build.
buildBatch_id :: Lens.Lens' BuildBatch (Prelude.Maybe Prelude.Text)
buildBatch_id :: Lens' BuildBatch (Maybe Text)
buildBatch_id = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\BuildBatch' {Maybe Text
id :: Maybe Text
$sel:id:BuildBatch' :: BuildBatch -> Maybe Text
id} -> Maybe Text
id) (\s :: BuildBatch
s@BuildBatch' {} Maybe Text
a -> BuildBatch
s {$sel:id:BuildBatch' :: Maybe Text
id = Maybe Text
a} :: BuildBatch)

-- | The entity that started the batch build. Valid values include:
--
-- -   If CodePipeline started the build, the pipeline\'s name (for
--     example, @codepipeline\/my-demo-pipeline@).
--
-- -   If an IAM user started the build, the user\'s name.
--
-- -   If the Jenkins plugin for CodeBuild started the build, the string
--     @CodeBuild-Jenkins-Plugin@.
buildBatch_initiator :: Lens.Lens' BuildBatch (Prelude.Maybe Prelude.Text)
buildBatch_initiator :: Lens' BuildBatch (Maybe Text)
buildBatch_initiator = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\BuildBatch' {Maybe Text
initiator :: Maybe Text
$sel:initiator:BuildBatch' :: BuildBatch -> Maybe Text
initiator} -> Maybe Text
initiator) (\s :: BuildBatch
s@BuildBatch' {} Maybe Text
a -> BuildBatch
s {$sel:initiator:BuildBatch' :: Maybe Text
initiator = Maybe Text
a} :: BuildBatch)

-- | Undocumented member.
buildBatch_logConfig :: Lens.Lens' BuildBatch (Prelude.Maybe LogsConfig)
buildBatch_logConfig :: Lens' BuildBatch (Maybe LogsConfig)
buildBatch_logConfig = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\BuildBatch' {Maybe LogsConfig
logConfig :: Maybe LogsConfig
$sel:logConfig:BuildBatch' :: BuildBatch -> Maybe LogsConfig
logConfig} -> Maybe LogsConfig
logConfig) (\s :: BuildBatch
s@BuildBatch' {} Maybe LogsConfig
a -> BuildBatch
s {$sel:logConfig:BuildBatch' :: Maybe LogsConfig
logConfig = Maybe LogsConfig
a} :: BuildBatch)

-- | An array of @BuildBatchPhase@ objects the specify the phases of the
-- batch build.
buildBatch_phases :: Lens.Lens' BuildBatch (Prelude.Maybe [BuildBatchPhase])
buildBatch_phases :: Lens' BuildBatch (Maybe [BuildBatchPhase])
buildBatch_phases = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\BuildBatch' {Maybe [BuildBatchPhase]
phases :: Maybe [BuildBatchPhase]
$sel:phases:BuildBatch' :: BuildBatch -> Maybe [BuildBatchPhase]
phases} -> Maybe [BuildBatchPhase]
phases) (\s :: BuildBatch
s@BuildBatch' {} Maybe [BuildBatchPhase]
a -> BuildBatch
s {$sel:phases:BuildBatch' :: Maybe [BuildBatchPhase]
phases = Maybe [BuildBatchPhase]
a} :: BuildBatch) 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

-- | The name of the batch build project.
buildBatch_projectName :: Lens.Lens' BuildBatch (Prelude.Maybe Prelude.Text)
buildBatch_projectName :: Lens' BuildBatch (Maybe Text)
buildBatch_projectName = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\BuildBatch' {Maybe Text
projectName :: Maybe Text
$sel:projectName:BuildBatch' :: BuildBatch -> Maybe Text
projectName} -> Maybe Text
projectName) (\s :: BuildBatch
s@BuildBatch' {} Maybe Text
a -> BuildBatch
s {$sel:projectName:BuildBatch' :: Maybe Text
projectName = Maybe Text
a} :: BuildBatch)

-- | Specifies the amount of time, in minutes, that the batch build is
-- allowed to be queued before it times out.
buildBatch_queuedTimeoutInMinutes :: Lens.Lens' BuildBatch (Prelude.Maybe Prelude.Int)
buildBatch_queuedTimeoutInMinutes :: Lens' BuildBatch (Maybe Int)
buildBatch_queuedTimeoutInMinutes = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\BuildBatch' {Maybe Int
queuedTimeoutInMinutes :: Maybe Int
$sel:queuedTimeoutInMinutes:BuildBatch' :: BuildBatch -> Maybe Int
queuedTimeoutInMinutes} -> Maybe Int
queuedTimeoutInMinutes) (\s :: BuildBatch
s@BuildBatch' {} Maybe Int
a -> BuildBatch
s {$sel:queuedTimeoutInMinutes:BuildBatch' :: Maybe Int
queuedTimeoutInMinutes = Maybe Int
a} :: BuildBatch)

-- | The identifier of the resolved version of this batch build\'s source
-- code.
--
-- -   For CodeCommit, GitHub, GitHub Enterprise, and BitBucket, the commit
--     ID.
--
-- -   For CodePipeline, the source revision provided by CodePipeline.
--
-- -   For Amazon S3, this does not apply.
buildBatch_resolvedSourceVersion :: Lens.Lens' BuildBatch (Prelude.Maybe Prelude.Text)
buildBatch_resolvedSourceVersion :: Lens' BuildBatch (Maybe Text)
buildBatch_resolvedSourceVersion = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\BuildBatch' {Maybe Text
resolvedSourceVersion :: Maybe Text
$sel:resolvedSourceVersion:BuildBatch' :: BuildBatch -> Maybe Text
resolvedSourceVersion} -> Maybe Text
resolvedSourceVersion) (\s :: BuildBatch
s@BuildBatch' {} Maybe Text
a -> BuildBatch
s {$sel:resolvedSourceVersion:BuildBatch' :: Maybe Text
resolvedSourceVersion = Maybe Text
a} :: BuildBatch)

-- | An array of @BuildArtifacts@ objects the define the build artifacts for
-- this batch build.
buildBatch_secondaryArtifacts :: Lens.Lens' BuildBatch (Prelude.Maybe [BuildArtifacts])
buildBatch_secondaryArtifacts :: Lens' BuildBatch (Maybe [BuildArtifacts])
buildBatch_secondaryArtifacts = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\BuildBatch' {Maybe [BuildArtifacts]
secondaryArtifacts :: Maybe [BuildArtifacts]
$sel:secondaryArtifacts:BuildBatch' :: BuildBatch -> Maybe [BuildArtifacts]
secondaryArtifacts} -> Maybe [BuildArtifacts]
secondaryArtifacts) (\s :: BuildBatch
s@BuildBatch' {} Maybe [BuildArtifacts]
a -> BuildBatch
s {$sel:secondaryArtifacts:BuildBatch' :: Maybe [BuildArtifacts]
secondaryArtifacts = Maybe [BuildArtifacts]
a} :: BuildBatch) 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

-- | An array of @ProjectSourceVersion@ objects. Each @ProjectSourceVersion@
-- must be one of:
--
-- -   For CodeCommit: the commit ID, branch, or Git tag to use.
--
-- -   For GitHub: the commit ID, pull request ID, branch name, or tag name
--     that corresponds to the version of the source code you want to
--     build. If a pull request ID is specified, it must use the format
--     @pr\/pull-request-ID@ (for example, @pr\/25@). If a branch name is
--     specified, the branch\'s HEAD commit ID is used. If not specified,
--     the default branch\'s HEAD commit ID is used.
--
-- -   For Bitbucket: the commit ID, branch name, or tag name that
--     corresponds to the version of the source code you want to build. If
--     a branch name is specified, the branch\'s HEAD commit ID is used. If
--     not specified, the default branch\'s HEAD commit ID is used.
--
-- -   For Amazon S3: the version ID of the object that represents the
--     build input ZIP file to use.
buildBatch_secondarySourceVersions :: Lens.Lens' BuildBatch (Prelude.Maybe [ProjectSourceVersion])
buildBatch_secondarySourceVersions :: Lens' BuildBatch (Maybe [ProjectSourceVersion])
buildBatch_secondarySourceVersions = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\BuildBatch' {Maybe [ProjectSourceVersion]
secondarySourceVersions :: Maybe [ProjectSourceVersion]
$sel:secondarySourceVersions:BuildBatch' :: BuildBatch -> Maybe [ProjectSourceVersion]
secondarySourceVersions} -> Maybe [ProjectSourceVersion]
secondarySourceVersions) (\s :: BuildBatch
s@BuildBatch' {} Maybe [ProjectSourceVersion]
a -> BuildBatch
s {$sel:secondarySourceVersions:BuildBatch' :: Maybe [ProjectSourceVersion]
secondarySourceVersions = Maybe [ProjectSourceVersion]
a} :: BuildBatch) 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

-- | An array of @ProjectSource@ objects that define the sources for the
-- batch build.
buildBatch_secondarySources :: Lens.Lens' BuildBatch (Prelude.Maybe [ProjectSource])
buildBatch_secondarySources :: Lens' BuildBatch (Maybe [ProjectSource])
buildBatch_secondarySources = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\BuildBatch' {Maybe [ProjectSource]
secondarySources :: Maybe [ProjectSource]
$sel:secondarySources:BuildBatch' :: BuildBatch -> Maybe [ProjectSource]
secondarySources} -> Maybe [ProjectSource]
secondarySources) (\s :: BuildBatch
s@BuildBatch' {} Maybe [ProjectSource]
a -> BuildBatch
s {$sel:secondarySources:BuildBatch' :: Maybe [ProjectSource]
secondarySources = Maybe [ProjectSource]
a} :: BuildBatch) 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

-- | The name of a service role used for builds in the batch.
buildBatch_serviceRole :: Lens.Lens' BuildBatch (Prelude.Maybe Prelude.Text)
buildBatch_serviceRole :: Lens' BuildBatch (Maybe Text)
buildBatch_serviceRole = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\BuildBatch' {Maybe Text
serviceRole :: Maybe Text
$sel:serviceRole:BuildBatch' :: BuildBatch -> Maybe Text
serviceRole} -> Maybe Text
serviceRole) (\s :: BuildBatch
s@BuildBatch' {} Maybe Text
a -> BuildBatch
s {$sel:serviceRole:BuildBatch' :: Maybe Text
serviceRole = Maybe Text
a} :: BuildBatch)

-- | Undocumented member.
buildBatch_source :: Lens.Lens' BuildBatch (Prelude.Maybe ProjectSource)
buildBatch_source :: Lens' BuildBatch (Maybe ProjectSource)
buildBatch_source = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\BuildBatch' {Maybe ProjectSource
source :: Maybe ProjectSource
$sel:source:BuildBatch' :: BuildBatch -> Maybe ProjectSource
source} -> Maybe ProjectSource
source) (\s :: BuildBatch
s@BuildBatch' {} Maybe ProjectSource
a -> BuildBatch
s {$sel:source:BuildBatch' :: Maybe ProjectSource
source = Maybe ProjectSource
a} :: BuildBatch)

-- | The identifier of the version of the source code to be built.
buildBatch_sourceVersion :: Lens.Lens' BuildBatch (Prelude.Maybe Prelude.Text)
buildBatch_sourceVersion :: Lens' BuildBatch (Maybe Text)
buildBatch_sourceVersion = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\BuildBatch' {Maybe Text
sourceVersion :: Maybe Text
$sel:sourceVersion:BuildBatch' :: BuildBatch -> Maybe Text
sourceVersion} -> Maybe Text
sourceVersion) (\s :: BuildBatch
s@BuildBatch' {} Maybe Text
a -> BuildBatch
s {$sel:sourceVersion:BuildBatch' :: Maybe Text
sourceVersion = Maybe Text
a} :: BuildBatch)

-- | The date and time that the batch build started.
buildBatch_startTime :: Lens.Lens' BuildBatch (Prelude.Maybe Prelude.UTCTime)
buildBatch_startTime :: Lens' BuildBatch (Maybe UTCTime)
buildBatch_startTime = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\BuildBatch' {Maybe POSIX
startTime :: Maybe POSIX
$sel:startTime:BuildBatch' :: BuildBatch -> Maybe POSIX
startTime} -> Maybe POSIX
startTime) (\s :: BuildBatch
s@BuildBatch' {} Maybe POSIX
a -> BuildBatch
s {$sel:startTime:BuildBatch' :: Maybe POSIX
startTime = Maybe POSIX
a} :: BuildBatch) 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

-- | Undocumented member.
buildBatch_vpcConfig :: Lens.Lens' BuildBatch (Prelude.Maybe VpcConfig)
buildBatch_vpcConfig :: Lens' BuildBatch (Maybe VpcConfig)
buildBatch_vpcConfig = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\BuildBatch' {Maybe VpcConfig
vpcConfig :: Maybe VpcConfig
$sel:vpcConfig:BuildBatch' :: BuildBatch -> Maybe VpcConfig
vpcConfig} -> Maybe VpcConfig
vpcConfig) (\s :: BuildBatch
s@BuildBatch' {} Maybe VpcConfig
a -> BuildBatch
s {$sel:vpcConfig:BuildBatch' :: Maybe VpcConfig
vpcConfig = Maybe VpcConfig
a} :: BuildBatch)

instance Data.FromJSON BuildBatch where
  parseJSON :: Value -> Parser BuildBatch
parseJSON =
    forall a. String -> (Object -> Parser a) -> Value -> Parser a
Data.withObject
      String
"BuildBatch"
      ( \Object
x ->
          Maybe Text
-> Maybe BuildArtifacts
-> Maybe ProjectBuildBatchConfig
-> Maybe Integer
-> Maybe StatusType
-> Maybe [BuildGroup]
-> Maybe Int
-> Maybe ProjectCache
-> Maybe Bool
-> Maybe Text
-> Maybe Bool
-> Maybe Text
-> Maybe POSIX
-> Maybe ProjectEnvironment
-> Maybe [ProjectFileSystemLocation]
-> Maybe Text
-> Maybe Text
-> Maybe LogsConfig
-> Maybe [BuildBatchPhase]
-> Maybe Text
-> Maybe Int
-> Maybe Text
-> Maybe [BuildArtifacts]
-> Maybe [ProjectSourceVersion]
-> Maybe [ProjectSource]
-> Maybe Text
-> Maybe ProjectSource
-> Maybe Text
-> Maybe POSIX
-> Maybe VpcConfig
-> BuildBatch
BuildBatch'
            forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
Prelude.<$> (Object
x forall a. FromJSON a => Object -> Key -> Parser (Maybe a)
Data..:? Key
"arn")
            forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
Prelude.<*> (Object
x forall a. FromJSON a => Object -> Key -> Parser (Maybe a)
Data..:? Key
"artifacts")
            forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
Prelude.<*> (Object
x forall a. FromJSON a => Object -> Key -> Parser (Maybe a)
Data..:? Key
"buildBatchConfig")
            forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
Prelude.<*> (Object
x forall a. FromJSON a => Object -> Key -> Parser (Maybe a)
Data..:? Key
"buildBatchNumber")
            forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
Prelude.<*> (Object
x forall a. FromJSON a => Object -> Key -> Parser (Maybe a)
Data..:? Key
"buildBatchStatus")
            forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
Prelude.<*> (Object
x forall a. FromJSON a => Object -> Key -> Parser (Maybe a)
Data..:? Key
"buildGroups" forall a. Parser (Maybe a) -> a -> Parser a
Data..!= 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 -> Parser (Maybe a)
Data..:? Key
"buildTimeoutInMinutes")
            forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
Prelude.<*> (Object
x forall a. FromJSON a => Object -> Key -> Parser (Maybe a)
Data..:? Key
"cache")
            forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
Prelude.<*> (Object
x forall a. FromJSON a => Object -> Key -> Parser (Maybe a)
Data..:? Key
"complete")
            forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
Prelude.<*> (Object
x forall a. FromJSON a => Object -> Key -> Parser (Maybe a)
Data..:? Key
"currentPhase")
            forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
Prelude.<*> (Object
x forall a. FromJSON a => Object -> Key -> Parser (Maybe a)
Data..:? Key
"debugSessionEnabled")
            forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
Prelude.<*> (Object
x forall a. FromJSON a => Object -> Key -> Parser (Maybe a)
Data..:? Key
"encryptionKey")
            forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
Prelude.<*> (Object
x forall a. FromJSON a => Object -> Key -> Parser (Maybe a)
Data..:? Key
"endTime")
            forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
Prelude.<*> (Object
x forall a. FromJSON a => Object -> Key -> Parser (Maybe a)
Data..:? Key
"environment")
            forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
Prelude.<*> ( Object
x
                            forall a. FromJSON a => Object -> Key -> Parser (Maybe a)
Data..:? Key
"fileSystemLocations"
                            forall a. Parser (Maybe a) -> a -> Parser a
Data..!= 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 -> Parser (Maybe a)
Data..:? Key
"id")
            forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
Prelude.<*> (Object
x forall a. FromJSON a => Object -> Key -> Parser (Maybe a)
Data..:? Key
"initiator")
            forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
Prelude.<*> (Object
x forall a. FromJSON a => Object -> Key -> Parser (Maybe a)
Data..:? Key
"logConfig")
            forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
Prelude.<*> (Object
x forall a. FromJSON a => Object -> Key -> Parser (Maybe a)
Data..:? Key
"phases" forall a. Parser (Maybe a) -> a -> Parser a
Data..!= 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 -> Parser (Maybe a)
Data..:? Key
"projectName")
            forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
Prelude.<*> (Object
x forall a. FromJSON a => Object -> Key -> Parser (Maybe a)
Data..:? Key
"queuedTimeoutInMinutes")
            forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
Prelude.<*> (Object
x forall a. FromJSON a => Object -> Key -> Parser (Maybe a)
Data..:? Key
"resolvedSourceVersion")
            forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
Prelude.<*> ( Object
x
                            forall a. FromJSON a => Object -> Key -> Parser (Maybe a)
Data..:? Key
"secondaryArtifacts"
                            forall a. Parser (Maybe a) -> a -> Parser a
Data..!= 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 -> Parser (Maybe a)
Data..:? Key
"secondarySourceVersions"
                            forall a. Parser (Maybe a) -> a -> Parser a
Data..!= 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 -> Parser (Maybe a)
Data..:? Key
"secondarySources"
                            forall a. Parser (Maybe a) -> a -> Parser a
Data..!= 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 -> Parser (Maybe a)
Data..:? Key
"serviceRole")
            forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
Prelude.<*> (Object
x forall a. FromJSON a => Object -> Key -> Parser (Maybe a)
Data..:? Key
"source")
            forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
Prelude.<*> (Object
x forall a. FromJSON a => Object -> Key -> Parser (Maybe a)
Data..:? Key
"sourceVersion")
            forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
Prelude.<*> (Object
x forall a. FromJSON a => Object -> Key -> Parser (Maybe a)
Data..:? Key
"startTime")
            forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
Prelude.<*> (Object
x forall a. FromJSON a => Object -> Key -> Parser (Maybe a)
Data..:? Key
"vpcConfig")
      )

instance Prelude.Hashable BuildBatch where
  hashWithSalt :: Int -> BuildBatch -> Int
hashWithSalt Int
_salt BuildBatch' {Maybe Bool
Maybe Int
Maybe Integer
Maybe [BuildArtifacts]
Maybe [ProjectFileSystemLocation]
Maybe [ProjectSourceVersion]
Maybe [ProjectSource]
Maybe [BuildGroup]
Maybe [BuildBatchPhase]
Maybe Text
Maybe POSIX
Maybe BuildArtifacts
Maybe ProjectBuildBatchConfig
Maybe ProjectCache
Maybe ProjectEnvironment
Maybe LogsConfig
Maybe ProjectSource
Maybe StatusType
Maybe VpcConfig
vpcConfig :: Maybe VpcConfig
startTime :: Maybe POSIX
sourceVersion :: Maybe Text
source :: Maybe ProjectSource
serviceRole :: Maybe Text
secondarySources :: Maybe [ProjectSource]
secondarySourceVersions :: Maybe [ProjectSourceVersion]
secondaryArtifacts :: Maybe [BuildArtifacts]
resolvedSourceVersion :: Maybe Text
queuedTimeoutInMinutes :: Maybe Int
projectName :: Maybe Text
phases :: Maybe [BuildBatchPhase]
logConfig :: Maybe LogsConfig
initiator :: Maybe Text
id :: Maybe Text
fileSystemLocations :: Maybe [ProjectFileSystemLocation]
environment :: Maybe ProjectEnvironment
endTime :: Maybe POSIX
encryptionKey :: Maybe Text
debugSessionEnabled :: Maybe Bool
currentPhase :: Maybe Text
complete :: Maybe Bool
cache :: Maybe ProjectCache
buildTimeoutInMinutes :: Maybe Int
buildGroups :: Maybe [BuildGroup]
buildBatchStatus :: Maybe StatusType
buildBatchNumber :: Maybe Integer
buildBatchConfig :: Maybe ProjectBuildBatchConfig
artifacts :: Maybe BuildArtifacts
arn :: Maybe Text
$sel:vpcConfig:BuildBatch' :: BuildBatch -> Maybe VpcConfig
$sel:startTime:BuildBatch' :: BuildBatch -> Maybe POSIX
$sel:sourceVersion:BuildBatch' :: BuildBatch -> Maybe Text
$sel:source:BuildBatch' :: BuildBatch -> Maybe ProjectSource
$sel:serviceRole:BuildBatch' :: BuildBatch -> Maybe Text
$sel:secondarySources:BuildBatch' :: BuildBatch -> Maybe [ProjectSource]
$sel:secondarySourceVersions:BuildBatch' :: BuildBatch -> Maybe [ProjectSourceVersion]
$sel:secondaryArtifacts:BuildBatch' :: BuildBatch -> Maybe [BuildArtifacts]
$sel:resolvedSourceVersion:BuildBatch' :: BuildBatch -> Maybe Text
$sel:queuedTimeoutInMinutes:BuildBatch' :: BuildBatch -> Maybe Int
$sel:projectName:BuildBatch' :: BuildBatch -> Maybe Text
$sel:phases:BuildBatch' :: BuildBatch -> Maybe [BuildBatchPhase]
$sel:logConfig:BuildBatch' :: BuildBatch -> Maybe LogsConfig
$sel:initiator:BuildBatch' :: BuildBatch -> Maybe Text
$sel:id:BuildBatch' :: BuildBatch -> Maybe Text
$sel:fileSystemLocations:BuildBatch' :: BuildBatch -> Maybe [ProjectFileSystemLocation]
$sel:environment:BuildBatch' :: BuildBatch -> Maybe ProjectEnvironment
$sel:endTime:BuildBatch' :: BuildBatch -> Maybe POSIX
$sel:encryptionKey:BuildBatch' :: BuildBatch -> Maybe Text
$sel:debugSessionEnabled:BuildBatch' :: BuildBatch -> Maybe Bool
$sel:currentPhase:BuildBatch' :: BuildBatch -> Maybe Text
$sel:complete:BuildBatch' :: BuildBatch -> Maybe Bool
$sel:cache:BuildBatch' :: BuildBatch -> Maybe ProjectCache
$sel:buildTimeoutInMinutes:BuildBatch' :: BuildBatch -> Maybe Int
$sel:buildGroups:BuildBatch' :: BuildBatch -> Maybe [BuildGroup]
$sel:buildBatchStatus:BuildBatch' :: BuildBatch -> Maybe StatusType
$sel:buildBatchNumber:BuildBatch' :: BuildBatch -> Maybe Integer
$sel:buildBatchConfig:BuildBatch' :: BuildBatch -> Maybe ProjectBuildBatchConfig
$sel:artifacts:BuildBatch' :: BuildBatch -> Maybe BuildArtifacts
$sel:arn:BuildBatch' :: BuildBatch -> Maybe Text
..} =
    Int
_salt
      forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Maybe Text
arn
      forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Maybe BuildArtifacts
artifacts
      forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Maybe ProjectBuildBatchConfig
buildBatchConfig
      forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Maybe Integer
buildBatchNumber
      forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Maybe StatusType
buildBatchStatus
      forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Maybe [BuildGroup]
buildGroups
      forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Maybe Int
buildTimeoutInMinutes
      forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Maybe ProjectCache
cache
      forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Maybe Bool
complete
      forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Maybe Text
currentPhase
      forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Maybe Bool
debugSessionEnabled
      forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Maybe Text
encryptionKey
      forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Maybe POSIX
endTime
      forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Maybe ProjectEnvironment
environment
      forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Maybe [ProjectFileSystemLocation]
fileSystemLocations
      forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Maybe Text
id
      forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Maybe Text
initiator
      forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Maybe LogsConfig
logConfig
      forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Maybe [BuildBatchPhase]
phases
      forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Maybe Text
projectName
      forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Maybe Int
queuedTimeoutInMinutes
      forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Maybe Text
resolvedSourceVersion
      forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Maybe [BuildArtifacts]
secondaryArtifacts
      forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Maybe [ProjectSourceVersion]
secondarySourceVersions
      forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Maybe [ProjectSource]
secondarySources
      forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Maybe Text
serviceRole
      forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Maybe ProjectSource
source
      forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Maybe Text
sourceVersion
      forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Maybe POSIX
startTime
      forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Maybe VpcConfig
vpcConfig

instance Prelude.NFData BuildBatch where
  rnf :: BuildBatch -> ()
rnf BuildBatch' {Maybe Bool
Maybe Int
Maybe Integer
Maybe [BuildArtifacts]
Maybe [ProjectFileSystemLocation]
Maybe [ProjectSourceVersion]
Maybe [ProjectSource]
Maybe [BuildGroup]
Maybe [BuildBatchPhase]
Maybe Text
Maybe POSIX
Maybe BuildArtifacts
Maybe ProjectBuildBatchConfig
Maybe ProjectCache
Maybe ProjectEnvironment
Maybe LogsConfig
Maybe ProjectSource
Maybe StatusType
Maybe VpcConfig
vpcConfig :: Maybe VpcConfig
startTime :: Maybe POSIX
sourceVersion :: Maybe Text
source :: Maybe ProjectSource
serviceRole :: Maybe Text
secondarySources :: Maybe [ProjectSource]
secondarySourceVersions :: Maybe [ProjectSourceVersion]
secondaryArtifacts :: Maybe [BuildArtifacts]
resolvedSourceVersion :: Maybe Text
queuedTimeoutInMinutes :: Maybe Int
projectName :: Maybe Text
phases :: Maybe [BuildBatchPhase]
logConfig :: Maybe LogsConfig
initiator :: Maybe Text
id :: Maybe Text
fileSystemLocations :: Maybe [ProjectFileSystemLocation]
environment :: Maybe ProjectEnvironment
endTime :: Maybe POSIX
encryptionKey :: Maybe Text
debugSessionEnabled :: Maybe Bool
currentPhase :: Maybe Text
complete :: Maybe Bool
cache :: Maybe ProjectCache
buildTimeoutInMinutes :: Maybe Int
buildGroups :: Maybe [BuildGroup]
buildBatchStatus :: Maybe StatusType
buildBatchNumber :: Maybe Integer
buildBatchConfig :: Maybe ProjectBuildBatchConfig
artifacts :: Maybe BuildArtifacts
arn :: Maybe Text
$sel:vpcConfig:BuildBatch' :: BuildBatch -> Maybe VpcConfig
$sel:startTime:BuildBatch' :: BuildBatch -> Maybe POSIX
$sel:sourceVersion:BuildBatch' :: BuildBatch -> Maybe Text
$sel:source:BuildBatch' :: BuildBatch -> Maybe ProjectSource
$sel:serviceRole:BuildBatch' :: BuildBatch -> Maybe Text
$sel:secondarySources:BuildBatch' :: BuildBatch -> Maybe [ProjectSource]
$sel:secondarySourceVersions:BuildBatch' :: BuildBatch -> Maybe [ProjectSourceVersion]
$sel:secondaryArtifacts:BuildBatch' :: BuildBatch -> Maybe [BuildArtifacts]
$sel:resolvedSourceVersion:BuildBatch' :: BuildBatch -> Maybe Text
$sel:queuedTimeoutInMinutes:BuildBatch' :: BuildBatch -> Maybe Int
$sel:projectName:BuildBatch' :: BuildBatch -> Maybe Text
$sel:phases:BuildBatch' :: BuildBatch -> Maybe [BuildBatchPhase]
$sel:logConfig:BuildBatch' :: BuildBatch -> Maybe LogsConfig
$sel:initiator:BuildBatch' :: BuildBatch -> Maybe Text
$sel:id:BuildBatch' :: BuildBatch -> Maybe Text
$sel:fileSystemLocations:BuildBatch' :: BuildBatch -> Maybe [ProjectFileSystemLocation]
$sel:environment:BuildBatch' :: BuildBatch -> Maybe ProjectEnvironment
$sel:endTime:BuildBatch' :: BuildBatch -> Maybe POSIX
$sel:encryptionKey:BuildBatch' :: BuildBatch -> Maybe Text
$sel:debugSessionEnabled:BuildBatch' :: BuildBatch -> Maybe Bool
$sel:currentPhase:BuildBatch' :: BuildBatch -> Maybe Text
$sel:complete:BuildBatch' :: BuildBatch -> Maybe Bool
$sel:cache:BuildBatch' :: BuildBatch -> Maybe ProjectCache
$sel:buildTimeoutInMinutes:BuildBatch' :: BuildBatch -> Maybe Int
$sel:buildGroups:BuildBatch' :: BuildBatch -> Maybe [BuildGroup]
$sel:buildBatchStatus:BuildBatch' :: BuildBatch -> Maybe StatusType
$sel:buildBatchNumber:BuildBatch' :: BuildBatch -> Maybe Integer
$sel:buildBatchConfig:BuildBatch' :: BuildBatch -> Maybe ProjectBuildBatchConfig
$sel:artifacts:BuildBatch' :: BuildBatch -> Maybe BuildArtifacts
$sel:arn:BuildBatch' :: BuildBatch -> Maybe Text
..} =
    forall a. NFData a => a -> ()
Prelude.rnf Maybe Text
arn
      seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf Maybe BuildArtifacts
artifacts
      seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf Maybe ProjectBuildBatchConfig
buildBatchConfig
      seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf Maybe Integer
buildBatchNumber
      seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf Maybe StatusType
buildBatchStatus
      seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf Maybe [BuildGroup]
buildGroups
      seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf Maybe Int
buildTimeoutInMinutes
      seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf Maybe ProjectCache
cache
      seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf Maybe Bool
complete
      seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf Maybe Text
currentPhase
      seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf Maybe Bool
debugSessionEnabled
      seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf Maybe Text
encryptionKey
      seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf Maybe POSIX
endTime
      seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf Maybe ProjectEnvironment
environment
      seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf Maybe [ProjectFileSystemLocation]
fileSystemLocations
      seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf Maybe Text
id
      seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf Maybe Text
initiator
      seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf Maybe LogsConfig
logConfig
      seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf Maybe [BuildBatchPhase]
phases
      seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf Maybe Text
projectName
      seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf
        Maybe Int
queuedTimeoutInMinutes
      seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf
        Maybe Text
resolvedSourceVersion
      seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf
        Maybe [BuildArtifacts]
secondaryArtifacts
      seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf
        Maybe [ProjectSourceVersion]
secondarySourceVersions
      seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf
        Maybe [ProjectSource]
secondarySources
      seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf
        Maybe Text
serviceRole
      seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf
        Maybe ProjectSource
source
      seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf
        Maybe Text
sourceVersion
      seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf
        Maybe POSIX
startTime
      seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf
        Maybe VpcConfig
vpcConfig