{-# 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.Build
-- 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.Build where

import Amazonka.CodeBuild.Types.BuildArtifacts
import Amazonka.CodeBuild.Types.BuildPhase
import Amazonka.CodeBuild.Types.DebugSession
import Amazonka.CodeBuild.Types.ExportedEnvironmentVariable
import Amazonka.CodeBuild.Types.LogsLocation
import Amazonka.CodeBuild.Types.NetworkInterface
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

-- | Information about a build.
--
-- /See:/ 'newBuild' smart constructor.
data Build = Build'
  { -- | The Amazon Resource Name (ARN) of the build.
    Build -> Maybe Text
arn :: Prelude.Maybe Prelude.Text,
    -- | Information about the output artifacts for the build.
    Build -> Maybe BuildArtifacts
artifacts :: Prelude.Maybe BuildArtifacts,
    -- | The ARN of the batch build that this build is a member of, if
    -- applicable.
    Build -> Maybe Text
buildBatchArn :: Prelude.Maybe Prelude.Text,
    -- | Whether the build is complete. True if complete; otherwise, false.
    Build -> Maybe Bool
buildComplete :: Prelude.Maybe Prelude.Bool,
    -- | The number of the build. For each project, the @buildNumber@ of its
    -- first build is @1@. The @buildNumber@ of each subsequent build is
    -- incremented by @1@. If a build is deleted, the @buildNumber@ of other
    -- builds does not change.
    Build -> Maybe Integer
buildNumber :: Prelude.Maybe Prelude.Integer,
    -- | The current status of the build. Valid values include:
    --
    -- -   @FAILED@: The build failed.
    --
    -- -   @FAULT@: The build faulted.
    --
    -- -   @IN_PROGRESS@: The build is still in progress.
    --
    -- -   @STOPPED@: The build stopped.
    --
    -- -   @SUCCEEDED@: The build succeeded.
    --
    -- -   @TIMED_OUT@: The build timed out.
    Build -> Maybe StatusType
buildStatus :: Prelude.Maybe StatusType,
    -- | Information about the cache for the build.
    Build -> Maybe ProjectCache
cache :: Prelude.Maybe ProjectCache,
    -- | The current build phase.
    Build -> Maybe Text
currentPhase :: Prelude.Maybe Prelude.Text,
    -- | Contains information about the debug session for this build.
    Build -> Maybe DebugSession
debugSession :: Prelude.Maybe DebugSession,
    -- | The Key Management Service customer master key (CMK) to be used for
    -- encrypting the 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>@).
    Build -> Maybe Text
encryptionKey :: Prelude.Maybe Prelude.Text,
    -- | When the build process ended, expressed in Unix time format.
    Build -> Maybe POSIX
endTime :: Prelude.Maybe Data.POSIX,
    -- | Information about the build environment for this build.
    Build -> Maybe ProjectEnvironment
environment :: Prelude.Maybe ProjectEnvironment,
    -- | A list of exported environment variables for this build.
    --
    -- Exported environment variables are used in conjunction with CodePipeline
    -- to export environment variables from the current build stage to
    -- subsequent stages in the pipeline. For more information, see
    -- <https://docs.aws.amazon.com/codepipeline/latest/userguide/actions-variables.html Working with variables>
    -- in the /CodePipeline User Guide/.
    Build -> Maybe [ExportedEnvironmentVariable]
exportedEnvironmentVariables :: Prelude.Maybe [ExportedEnvironmentVariable],
    -- | An array of @ProjectFileSystemLocation@ objects for a CodeBuild build
    -- project. A @ProjectFileSystemLocation@ object specifies the
    -- @identifier@, @location@, @mountOptions@, @mountPoint@, and @type@ of a
    -- file system created using Amazon Elastic File System.
    Build -> Maybe [ProjectFileSystemLocation]
fileSystemLocations :: Prelude.Maybe [ProjectFileSystemLocation],
    -- | The unique ID for the build.
    Build -> Maybe Text
id :: Prelude.Maybe Prelude.Text,
    -- | The entity that started the 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 (for example,
    --     @MyUserName@).
    --
    -- -   If the Jenkins plugin for CodeBuild started the build, the string
    --     @CodeBuild-Jenkins-Plugin@.
    Build -> Maybe Text
initiator :: Prelude.Maybe Prelude.Text,
    -- | Information about the build\'s logs in CloudWatch Logs.
    Build -> Maybe LogsLocation
logs :: Prelude.Maybe LogsLocation,
    -- | Describes a network interface.
    Build -> Maybe NetworkInterface
networkInterface :: Prelude.Maybe NetworkInterface,
    -- | Information about all previous build phases that are complete and
    -- information about any current build phase that is not yet complete.
    Build -> Maybe [BuildPhase]
phases :: Prelude.Maybe [BuildPhase],
    -- | The name of the CodeBuild project.
    Build -> Maybe Text
projectName :: Prelude.Maybe Prelude.Text,
    -- | The number of minutes a build is allowed to be queued before it times
    -- out.
    Build -> Maybe Int
queuedTimeoutInMinutes :: Prelude.Maybe Prelude.Int,
    -- | An array of the ARNs associated with this build\'s reports.
    Build -> Maybe [Text]
reportArns :: Prelude.Maybe [Prelude.Text],
    -- | An identifier for the version of this 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.
    Build -> Maybe Text
resolvedSourceVersion :: Prelude.Maybe Prelude.Text,
    -- | An array of @ProjectArtifacts@ objects.
    Build -> 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.
    Build -> Maybe [ProjectSourceVersion]
secondarySourceVersions :: Prelude.Maybe [ProjectSourceVersion],
    -- | An array of @ProjectSource@ objects.
    Build -> Maybe [ProjectSource]
secondarySources :: Prelude.Maybe [ProjectSource],
    -- | The name of a service role used for this build.
    Build -> Maybe Text
serviceRole :: Prelude.Maybe Prelude.Text,
    -- | Information about the source code to be built.
    Build -> Maybe ProjectSource
source :: Prelude.Maybe ProjectSource,
    -- | Any version identifier for the version of the source code to be built.
    -- If @sourceVersion@ is specified at the project level, then this
    -- @sourceVersion@ (at the build level) takes precedence.
    --
    -- For more information, see
    -- <https://docs.aws.amazon.com/codebuild/latest/userguide/sample-source-version.html Source Version Sample with CodeBuild>
    -- in the /CodeBuild User Guide/.
    Build -> Maybe Text
sourceVersion :: Prelude.Maybe Prelude.Text,
    -- | When the build process started, expressed in Unix time format.
    Build -> Maybe POSIX
startTime :: Prelude.Maybe Data.POSIX,
    -- | How long, in minutes, for CodeBuild to wait before timing out this build
    -- if it does not get marked as completed.
    Build -> Maybe Int
timeoutInMinutes :: Prelude.Maybe Prelude.Int,
    -- | If your CodeBuild project accesses resources in an Amazon VPC, you
    -- provide this parameter that identifies the VPC ID and the list of
    -- security group IDs and subnet IDs. The security groups and subnets must
    -- belong to the same VPC. You must provide at least one security group and
    -- one subnet ID.
    Build -> Maybe VpcConfig
vpcConfig :: Prelude.Maybe VpcConfig
  }
  deriving (Build -> Build -> Bool
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: Build -> Build -> Bool
$c/= :: Build -> Build -> Bool
== :: Build -> Build -> Bool
$c== :: Build -> Build -> Bool
Prelude.Eq, ReadPrec [Build]
ReadPrec Build
Int -> ReadS Build
ReadS [Build]
forall a.
(Int -> ReadS a)
-> ReadS [a] -> ReadPrec a -> ReadPrec [a] -> Read a
readListPrec :: ReadPrec [Build]
$creadListPrec :: ReadPrec [Build]
readPrec :: ReadPrec Build
$creadPrec :: ReadPrec Build
readList :: ReadS [Build]
$creadList :: ReadS [Build]
readsPrec :: Int -> ReadS Build
$creadsPrec :: Int -> ReadS Build
Prelude.Read, Int -> Build -> ShowS
[Build] -> ShowS
Build -> String
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [Build] -> ShowS
$cshowList :: [Build] -> ShowS
show :: Build -> String
$cshow :: Build -> String
showsPrec :: Int -> Build -> ShowS
$cshowsPrec :: Int -> Build -> ShowS
Prelude.Show, forall x. Rep Build x -> Build
forall x. Build -> Rep Build x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cto :: forall x. Rep Build x -> Build
$cfrom :: forall x. Build -> Rep Build x
Prelude.Generic)

-- |
-- Create a value of 'Build' 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', 'build_arn' - The Amazon Resource Name (ARN) of the build.
--
-- 'artifacts', 'build_artifacts' - Information about the output artifacts for the build.
--
-- 'buildBatchArn', 'build_buildBatchArn' - The ARN of the batch build that this build is a member of, if
-- applicable.
--
-- 'buildComplete', 'build_buildComplete' - Whether the build is complete. True if complete; otherwise, false.
--
-- 'buildNumber', 'build_buildNumber' - The number of the build. For each project, the @buildNumber@ of its
-- first build is @1@. The @buildNumber@ of each subsequent build is
-- incremented by @1@. If a build is deleted, the @buildNumber@ of other
-- builds does not change.
--
-- 'buildStatus', 'build_buildStatus' - The current status of the build. Valid values include:
--
-- -   @FAILED@: The build failed.
--
-- -   @FAULT@: The build faulted.
--
-- -   @IN_PROGRESS@: The build is still in progress.
--
-- -   @STOPPED@: The build stopped.
--
-- -   @SUCCEEDED@: The build succeeded.
--
-- -   @TIMED_OUT@: The build timed out.
--
-- 'cache', 'build_cache' - Information about the cache for the build.
--
-- 'currentPhase', 'build_currentPhase' - The current build phase.
--
-- 'debugSession', 'build_debugSession' - Contains information about the debug session for this build.
--
-- 'encryptionKey', 'build_encryptionKey' - The Key Management Service customer master key (CMK) to be used for
-- encrypting the 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', 'build_endTime' - When the build process ended, expressed in Unix time format.
--
-- 'environment', 'build_environment' - Information about the build environment for this build.
--
-- 'exportedEnvironmentVariables', 'build_exportedEnvironmentVariables' - A list of exported environment variables for this build.
--
-- Exported environment variables are used in conjunction with CodePipeline
-- to export environment variables from the current build stage to
-- subsequent stages in the pipeline. For more information, see
-- <https://docs.aws.amazon.com/codepipeline/latest/userguide/actions-variables.html Working with variables>
-- in the /CodePipeline User Guide/.
--
-- 'fileSystemLocations', 'build_fileSystemLocations' - An array of @ProjectFileSystemLocation@ objects for a CodeBuild build
-- project. A @ProjectFileSystemLocation@ object specifies the
-- @identifier@, @location@, @mountOptions@, @mountPoint@, and @type@ of a
-- file system created using Amazon Elastic File System.
--
-- 'id', 'build_id' - The unique ID for the build.
--
-- 'initiator', 'build_initiator' - The entity that started the 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 (for example,
--     @MyUserName@).
--
-- -   If the Jenkins plugin for CodeBuild started the build, the string
--     @CodeBuild-Jenkins-Plugin@.
--
-- 'logs', 'build_logs' - Information about the build\'s logs in CloudWatch Logs.
--
-- 'networkInterface', 'build_networkInterface' - Describes a network interface.
--
-- 'phases', 'build_phases' - Information about all previous build phases that are complete and
-- information about any current build phase that is not yet complete.
--
-- 'projectName', 'build_projectName' - The name of the CodeBuild project.
--
-- 'queuedTimeoutInMinutes', 'build_queuedTimeoutInMinutes' - The number of minutes a build is allowed to be queued before it times
-- out.
--
-- 'reportArns', 'build_reportArns' - An array of the ARNs associated with this build\'s reports.
--
-- 'resolvedSourceVersion', 'build_resolvedSourceVersion' - An identifier for the version of this 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', 'build_secondaryArtifacts' - An array of @ProjectArtifacts@ objects.
--
-- 'secondarySourceVersions', 'build_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', 'build_secondarySources' - An array of @ProjectSource@ objects.
--
-- 'serviceRole', 'build_serviceRole' - The name of a service role used for this build.
--
-- 'source', 'build_source' - Information about the source code to be built.
--
-- 'sourceVersion', 'build_sourceVersion' - Any version identifier for the version of the source code to be built.
-- If @sourceVersion@ is specified at the project level, then this
-- @sourceVersion@ (at the build level) takes precedence.
--
-- For more information, see
-- <https://docs.aws.amazon.com/codebuild/latest/userguide/sample-source-version.html Source Version Sample with CodeBuild>
-- in the /CodeBuild User Guide/.
--
-- 'startTime', 'build_startTime' - When the build process started, expressed in Unix time format.
--
-- 'timeoutInMinutes', 'build_timeoutInMinutes' - How long, in minutes, for CodeBuild to wait before timing out this build
-- if it does not get marked as completed.
--
-- 'vpcConfig', 'build_vpcConfig' - If your CodeBuild project accesses resources in an Amazon VPC, you
-- provide this parameter that identifies the VPC ID and the list of
-- security group IDs and subnet IDs. The security groups and subnets must
-- belong to the same VPC. You must provide at least one security group and
-- one subnet ID.
newBuild ::
  Build
newBuild :: Build
newBuild =
  Build'
    { $sel:arn:Build' :: Maybe Text
arn = forall a. Maybe a
Prelude.Nothing,
      $sel:artifacts:Build' :: Maybe BuildArtifacts
artifacts = forall a. Maybe a
Prelude.Nothing,
      $sel:buildBatchArn:Build' :: Maybe Text
buildBatchArn = forall a. Maybe a
Prelude.Nothing,
      $sel:buildComplete:Build' :: Maybe Bool
buildComplete = forall a. Maybe a
Prelude.Nothing,
      $sel:buildNumber:Build' :: Maybe Integer
buildNumber = forall a. Maybe a
Prelude.Nothing,
      $sel:buildStatus:Build' :: Maybe StatusType
buildStatus = forall a. Maybe a
Prelude.Nothing,
      $sel:cache:Build' :: Maybe ProjectCache
cache = forall a. Maybe a
Prelude.Nothing,
      $sel:currentPhase:Build' :: Maybe Text
currentPhase = forall a. Maybe a
Prelude.Nothing,
      $sel:debugSession:Build' :: Maybe DebugSession
debugSession = forall a. Maybe a
Prelude.Nothing,
      $sel:encryptionKey:Build' :: Maybe Text
encryptionKey = forall a. Maybe a
Prelude.Nothing,
      $sel:endTime:Build' :: Maybe POSIX
endTime = forall a. Maybe a
Prelude.Nothing,
      $sel:environment:Build' :: Maybe ProjectEnvironment
environment = forall a. Maybe a
Prelude.Nothing,
      $sel:exportedEnvironmentVariables:Build' :: Maybe [ExportedEnvironmentVariable]
exportedEnvironmentVariables = forall a. Maybe a
Prelude.Nothing,
      $sel:fileSystemLocations:Build' :: Maybe [ProjectFileSystemLocation]
fileSystemLocations = forall a. Maybe a
Prelude.Nothing,
      $sel:id:Build' :: Maybe Text
id = forall a. Maybe a
Prelude.Nothing,
      $sel:initiator:Build' :: Maybe Text
initiator = forall a. Maybe a
Prelude.Nothing,
      $sel:logs:Build' :: Maybe LogsLocation
logs = forall a. Maybe a
Prelude.Nothing,
      $sel:networkInterface:Build' :: Maybe NetworkInterface
networkInterface = forall a. Maybe a
Prelude.Nothing,
      $sel:phases:Build' :: Maybe [BuildPhase]
phases = forall a. Maybe a
Prelude.Nothing,
      $sel:projectName:Build' :: Maybe Text
projectName = forall a. Maybe a
Prelude.Nothing,
      $sel:queuedTimeoutInMinutes:Build' :: Maybe Int
queuedTimeoutInMinutes = forall a. Maybe a
Prelude.Nothing,
      $sel:reportArns:Build' :: Maybe [Text]
reportArns = forall a. Maybe a
Prelude.Nothing,
      $sel:resolvedSourceVersion:Build' :: Maybe Text
resolvedSourceVersion = forall a. Maybe a
Prelude.Nothing,
      $sel:secondaryArtifacts:Build' :: Maybe [BuildArtifacts]
secondaryArtifacts = forall a. Maybe a
Prelude.Nothing,
      $sel:secondarySourceVersions:Build' :: Maybe [ProjectSourceVersion]
secondarySourceVersions = forall a. Maybe a
Prelude.Nothing,
      $sel:secondarySources:Build' :: Maybe [ProjectSource]
secondarySources = forall a. Maybe a
Prelude.Nothing,
      $sel:serviceRole:Build' :: Maybe Text
serviceRole = forall a. Maybe a
Prelude.Nothing,
      $sel:source:Build' :: Maybe ProjectSource
source = forall a. Maybe a
Prelude.Nothing,
      $sel:sourceVersion:Build' :: Maybe Text
sourceVersion = forall a. Maybe a
Prelude.Nothing,
      $sel:startTime:Build' :: Maybe POSIX
startTime = forall a. Maybe a
Prelude.Nothing,
      $sel:timeoutInMinutes:Build' :: Maybe Int
timeoutInMinutes = forall a. Maybe a
Prelude.Nothing,
      $sel:vpcConfig:Build' :: Maybe VpcConfig
vpcConfig = forall a. Maybe a
Prelude.Nothing
    }

-- | The Amazon Resource Name (ARN) of the build.
build_arn :: Lens.Lens' Build (Prelude.Maybe Prelude.Text)
build_arn :: Lens' Build (Maybe Text)
build_arn = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\Build' {Maybe Text
arn :: Maybe Text
$sel:arn:Build' :: Build -> Maybe Text
arn} -> Maybe Text
arn) (\s :: Build
s@Build' {} Maybe Text
a -> Build
s {$sel:arn:Build' :: Maybe Text
arn = Maybe Text
a} :: Build)

-- | Information about the output artifacts for the build.
build_artifacts :: Lens.Lens' Build (Prelude.Maybe BuildArtifacts)
build_artifacts :: Lens' Build (Maybe BuildArtifacts)
build_artifacts = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\Build' {Maybe BuildArtifacts
artifacts :: Maybe BuildArtifacts
$sel:artifacts:Build' :: Build -> Maybe BuildArtifacts
artifacts} -> Maybe BuildArtifacts
artifacts) (\s :: Build
s@Build' {} Maybe BuildArtifacts
a -> Build
s {$sel:artifacts:Build' :: Maybe BuildArtifacts
artifacts = Maybe BuildArtifacts
a} :: Build)

-- | The ARN of the batch build that this build is a member of, if
-- applicable.
build_buildBatchArn :: Lens.Lens' Build (Prelude.Maybe Prelude.Text)
build_buildBatchArn :: Lens' Build (Maybe Text)
build_buildBatchArn = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\Build' {Maybe Text
buildBatchArn :: Maybe Text
$sel:buildBatchArn:Build' :: Build -> Maybe Text
buildBatchArn} -> Maybe Text
buildBatchArn) (\s :: Build
s@Build' {} Maybe Text
a -> Build
s {$sel:buildBatchArn:Build' :: Maybe Text
buildBatchArn = Maybe Text
a} :: Build)

-- | Whether the build is complete. True if complete; otherwise, false.
build_buildComplete :: Lens.Lens' Build (Prelude.Maybe Prelude.Bool)
build_buildComplete :: Lens' Build (Maybe Bool)
build_buildComplete = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\Build' {Maybe Bool
buildComplete :: Maybe Bool
$sel:buildComplete:Build' :: Build -> Maybe Bool
buildComplete} -> Maybe Bool
buildComplete) (\s :: Build
s@Build' {} Maybe Bool
a -> Build
s {$sel:buildComplete:Build' :: Maybe Bool
buildComplete = Maybe Bool
a} :: Build)

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

-- | The current status of the build. Valid values include:
--
-- -   @FAILED@: The build failed.
--
-- -   @FAULT@: The build faulted.
--
-- -   @IN_PROGRESS@: The build is still in progress.
--
-- -   @STOPPED@: The build stopped.
--
-- -   @SUCCEEDED@: The build succeeded.
--
-- -   @TIMED_OUT@: The build timed out.
build_buildStatus :: Lens.Lens' Build (Prelude.Maybe StatusType)
build_buildStatus :: Lens' Build (Maybe StatusType)
build_buildStatus = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\Build' {Maybe StatusType
buildStatus :: Maybe StatusType
$sel:buildStatus:Build' :: Build -> Maybe StatusType
buildStatus} -> Maybe StatusType
buildStatus) (\s :: Build
s@Build' {} Maybe StatusType
a -> Build
s {$sel:buildStatus:Build' :: Maybe StatusType
buildStatus = Maybe StatusType
a} :: Build)

-- | Information about the cache for the build.
build_cache :: Lens.Lens' Build (Prelude.Maybe ProjectCache)
build_cache :: Lens' Build (Maybe ProjectCache)
build_cache = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\Build' {Maybe ProjectCache
cache :: Maybe ProjectCache
$sel:cache:Build' :: Build -> Maybe ProjectCache
cache} -> Maybe ProjectCache
cache) (\s :: Build
s@Build' {} Maybe ProjectCache
a -> Build
s {$sel:cache:Build' :: Maybe ProjectCache
cache = Maybe ProjectCache
a} :: Build)

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

-- | Contains information about the debug session for this build.
build_debugSession :: Lens.Lens' Build (Prelude.Maybe DebugSession)
build_debugSession :: Lens' Build (Maybe DebugSession)
build_debugSession = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\Build' {Maybe DebugSession
debugSession :: Maybe DebugSession
$sel:debugSession:Build' :: Build -> Maybe DebugSession
debugSession} -> Maybe DebugSession
debugSession) (\s :: Build
s@Build' {} Maybe DebugSession
a -> Build
s {$sel:debugSession:Build' :: Maybe DebugSession
debugSession = Maybe DebugSession
a} :: Build)

-- | The Key Management Service customer master key (CMK) to be used for
-- encrypting the 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>@).
build_encryptionKey :: Lens.Lens' Build (Prelude.Maybe Prelude.Text)
build_encryptionKey :: Lens' Build (Maybe Text)
build_encryptionKey = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\Build' {Maybe Text
encryptionKey :: Maybe Text
$sel:encryptionKey:Build' :: Build -> Maybe Text
encryptionKey} -> Maybe Text
encryptionKey) (\s :: Build
s@Build' {} Maybe Text
a -> Build
s {$sel:encryptionKey:Build' :: Maybe Text
encryptionKey = Maybe Text
a} :: Build)

-- | When the build process ended, expressed in Unix time format.
build_endTime :: Lens.Lens' Build (Prelude.Maybe Prelude.UTCTime)
build_endTime :: Lens' Build (Maybe UTCTime)
build_endTime = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\Build' {Maybe POSIX
endTime :: Maybe POSIX
$sel:endTime:Build' :: Build -> Maybe POSIX
endTime} -> Maybe POSIX
endTime) (\s :: Build
s@Build' {} Maybe POSIX
a -> Build
s {$sel:endTime:Build' :: Maybe POSIX
endTime = Maybe POSIX
a} :: Build) 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

-- | Information about the build environment for this build.
build_environment :: Lens.Lens' Build (Prelude.Maybe ProjectEnvironment)
build_environment :: Lens' Build (Maybe ProjectEnvironment)
build_environment = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\Build' {Maybe ProjectEnvironment
environment :: Maybe ProjectEnvironment
$sel:environment:Build' :: Build -> Maybe ProjectEnvironment
environment} -> Maybe ProjectEnvironment
environment) (\s :: Build
s@Build' {} Maybe ProjectEnvironment
a -> Build
s {$sel:environment:Build' :: Maybe ProjectEnvironment
environment = Maybe ProjectEnvironment
a} :: Build)

-- | A list of exported environment variables for this build.
--
-- Exported environment variables are used in conjunction with CodePipeline
-- to export environment variables from the current build stage to
-- subsequent stages in the pipeline. For more information, see
-- <https://docs.aws.amazon.com/codepipeline/latest/userguide/actions-variables.html Working with variables>
-- in the /CodePipeline User Guide/.
build_exportedEnvironmentVariables :: Lens.Lens' Build (Prelude.Maybe [ExportedEnvironmentVariable])
build_exportedEnvironmentVariables :: Lens' Build (Maybe [ExportedEnvironmentVariable])
build_exportedEnvironmentVariables = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\Build' {Maybe [ExportedEnvironmentVariable]
exportedEnvironmentVariables :: Maybe [ExportedEnvironmentVariable]
$sel:exportedEnvironmentVariables:Build' :: Build -> Maybe [ExportedEnvironmentVariable]
exportedEnvironmentVariables} -> Maybe [ExportedEnvironmentVariable]
exportedEnvironmentVariables) (\s :: Build
s@Build' {} Maybe [ExportedEnvironmentVariable]
a -> Build
s {$sel:exportedEnvironmentVariables:Build' :: Maybe [ExportedEnvironmentVariable]
exportedEnvironmentVariables = Maybe [ExportedEnvironmentVariable]
a} :: Build) 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 @ProjectFileSystemLocation@ objects for a CodeBuild build
-- project. A @ProjectFileSystemLocation@ object specifies the
-- @identifier@, @location@, @mountOptions@, @mountPoint@, and @type@ of a
-- file system created using Amazon Elastic File System.
build_fileSystemLocations :: Lens.Lens' Build (Prelude.Maybe [ProjectFileSystemLocation])
build_fileSystemLocations :: Lens' Build (Maybe [ProjectFileSystemLocation])
build_fileSystemLocations = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\Build' {Maybe [ProjectFileSystemLocation]
fileSystemLocations :: Maybe [ProjectFileSystemLocation]
$sel:fileSystemLocations:Build' :: Build -> Maybe [ProjectFileSystemLocation]
fileSystemLocations} -> Maybe [ProjectFileSystemLocation]
fileSystemLocations) (\s :: Build
s@Build' {} Maybe [ProjectFileSystemLocation]
a -> Build
s {$sel:fileSystemLocations:Build' :: Maybe [ProjectFileSystemLocation]
fileSystemLocations = Maybe [ProjectFileSystemLocation]
a} :: Build) 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 unique ID for the build.
build_id :: Lens.Lens' Build (Prelude.Maybe Prelude.Text)
build_id :: Lens' Build (Maybe Text)
build_id = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\Build' {Maybe Text
id :: Maybe Text
$sel:id:Build' :: Build -> Maybe Text
id} -> Maybe Text
id) (\s :: Build
s@Build' {} Maybe Text
a -> Build
s {$sel:id:Build' :: Maybe Text
id = Maybe Text
a} :: Build)

-- | The entity that started the 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 (for example,
--     @MyUserName@).
--
-- -   If the Jenkins plugin for CodeBuild started the build, the string
--     @CodeBuild-Jenkins-Plugin@.
build_initiator :: Lens.Lens' Build (Prelude.Maybe Prelude.Text)
build_initiator :: Lens' Build (Maybe Text)
build_initiator = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\Build' {Maybe Text
initiator :: Maybe Text
$sel:initiator:Build' :: Build -> Maybe Text
initiator} -> Maybe Text
initiator) (\s :: Build
s@Build' {} Maybe Text
a -> Build
s {$sel:initiator:Build' :: Maybe Text
initiator = Maybe Text
a} :: Build)

-- | Information about the build\'s logs in CloudWatch Logs.
build_logs :: Lens.Lens' Build (Prelude.Maybe LogsLocation)
build_logs :: Lens' Build (Maybe LogsLocation)
build_logs = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\Build' {Maybe LogsLocation
logs :: Maybe LogsLocation
$sel:logs:Build' :: Build -> Maybe LogsLocation
logs} -> Maybe LogsLocation
logs) (\s :: Build
s@Build' {} Maybe LogsLocation
a -> Build
s {$sel:logs:Build' :: Maybe LogsLocation
logs = Maybe LogsLocation
a} :: Build)

-- | Describes a network interface.
build_networkInterface :: Lens.Lens' Build (Prelude.Maybe NetworkInterface)
build_networkInterface :: Lens' Build (Maybe NetworkInterface)
build_networkInterface = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\Build' {Maybe NetworkInterface
networkInterface :: Maybe NetworkInterface
$sel:networkInterface:Build' :: Build -> Maybe NetworkInterface
networkInterface} -> Maybe NetworkInterface
networkInterface) (\s :: Build
s@Build' {} Maybe NetworkInterface
a -> Build
s {$sel:networkInterface:Build' :: Maybe NetworkInterface
networkInterface = Maybe NetworkInterface
a} :: Build)

-- | Information about all previous build phases that are complete and
-- information about any current build phase that is not yet complete.
build_phases :: Lens.Lens' Build (Prelude.Maybe [BuildPhase])
build_phases :: Lens' Build (Maybe [BuildPhase])
build_phases = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\Build' {Maybe [BuildPhase]
phases :: Maybe [BuildPhase]
$sel:phases:Build' :: Build -> Maybe [BuildPhase]
phases} -> Maybe [BuildPhase]
phases) (\s :: Build
s@Build' {} Maybe [BuildPhase]
a -> Build
s {$sel:phases:Build' :: Maybe [BuildPhase]
phases = Maybe [BuildPhase]
a} :: Build) 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 CodeBuild project.
build_projectName :: Lens.Lens' Build (Prelude.Maybe Prelude.Text)
build_projectName :: Lens' Build (Maybe Text)
build_projectName = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\Build' {Maybe Text
projectName :: Maybe Text
$sel:projectName:Build' :: Build -> Maybe Text
projectName} -> Maybe Text
projectName) (\s :: Build
s@Build' {} Maybe Text
a -> Build
s {$sel:projectName:Build' :: Maybe Text
projectName = Maybe Text
a} :: Build)

-- | The number of minutes a build is allowed to be queued before it times
-- out.
build_queuedTimeoutInMinutes :: Lens.Lens' Build (Prelude.Maybe Prelude.Int)
build_queuedTimeoutInMinutes :: Lens' Build (Maybe Int)
build_queuedTimeoutInMinutes = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\Build' {Maybe Int
queuedTimeoutInMinutes :: Maybe Int
$sel:queuedTimeoutInMinutes:Build' :: Build -> Maybe Int
queuedTimeoutInMinutes} -> Maybe Int
queuedTimeoutInMinutes) (\s :: Build
s@Build' {} Maybe Int
a -> Build
s {$sel:queuedTimeoutInMinutes:Build' :: Maybe Int
queuedTimeoutInMinutes = Maybe Int
a} :: Build)

-- | An array of the ARNs associated with this build\'s reports.
build_reportArns :: Lens.Lens' Build (Prelude.Maybe [Prelude.Text])
build_reportArns :: Lens' Build (Maybe [Text])
build_reportArns = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\Build' {Maybe [Text]
reportArns :: Maybe [Text]
$sel:reportArns:Build' :: Build -> Maybe [Text]
reportArns} -> Maybe [Text]
reportArns) (\s :: Build
s@Build' {} Maybe [Text]
a -> Build
s {$sel:reportArns:Build' :: Maybe [Text]
reportArns = Maybe [Text]
a} :: Build) 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 identifier for the version of this 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.
build_resolvedSourceVersion :: Lens.Lens' Build (Prelude.Maybe Prelude.Text)
build_resolvedSourceVersion :: Lens' Build (Maybe Text)
build_resolvedSourceVersion = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\Build' {Maybe Text
resolvedSourceVersion :: Maybe Text
$sel:resolvedSourceVersion:Build' :: Build -> Maybe Text
resolvedSourceVersion} -> Maybe Text
resolvedSourceVersion) (\s :: Build
s@Build' {} Maybe Text
a -> Build
s {$sel:resolvedSourceVersion:Build' :: Maybe Text
resolvedSourceVersion = Maybe Text
a} :: Build)

-- | An array of @ProjectArtifacts@ objects.
build_secondaryArtifacts :: Lens.Lens' Build (Prelude.Maybe [BuildArtifacts])
build_secondaryArtifacts :: Lens' Build (Maybe [BuildArtifacts])
build_secondaryArtifacts = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\Build' {Maybe [BuildArtifacts]
secondaryArtifacts :: Maybe [BuildArtifacts]
$sel:secondaryArtifacts:Build' :: Build -> Maybe [BuildArtifacts]
secondaryArtifacts} -> Maybe [BuildArtifacts]
secondaryArtifacts) (\s :: Build
s@Build' {} Maybe [BuildArtifacts]
a -> Build
s {$sel:secondaryArtifacts:Build' :: Maybe [BuildArtifacts]
secondaryArtifacts = Maybe [BuildArtifacts]
a} :: Build) 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.
build_secondarySourceVersions :: Lens.Lens' Build (Prelude.Maybe [ProjectSourceVersion])
build_secondarySourceVersions :: Lens' Build (Maybe [ProjectSourceVersion])
build_secondarySourceVersions = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\Build' {Maybe [ProjectSourceVersion]
secondarySourceVersions :: Maybe [ProjectSourceVersion]
$sel:secondarySourceVersions:Build' :: Build -> Maybe [ProjectSourceVersion]
secondarySourceVersions} -> Maybe [ProjectSourceVersion]
secondarySourceVersions) (\s :: Build
s@Build' {} Maybe [ProjectSourceVersion]
a -> Build
s {$sel:secondarySourceVersions:Build' :: Maybe [ProjectSourceVersion]
secondarySourceVersions = Maybe [ProjectSourceVersion]
a} :: Build) 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.
build_secondarySources :: Lens.Lens' Build (Prelude.Maybe [ProjectSource])
build_secondarySources :: Lens' Build (Maybe [ProjectSource])
build_secondarySources = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\Build' {Maybe [ProjectSource]
secondarySources :: Maybe [ProjectSource]
$sel:secondarySources:Build' :: Build -> Maybe [ProjectSource]
secondarySources} -> Maybe [ProjectSource]
secondarySources) (\s :: Build
s@Build' {} Maybe [ProjectSource]
a -> Build
s {$sel:secondarySources:Build' :: Maybe [ProjectSource]
secondarySources = Maybe [ProjectSource]
a} :: Build) 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 this build.
build_serviceRole :: Lens.Lens' Build (Prelude.Maybe Prelude.Text)
build_serviceRole :: Lens' Build (Maybe Text)
build_serviceRole = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\Build' {Maybe Text
serviceRole :: Maybe Text
$sel:serviceRole:Build' :: Build -> Maybe Text
serviceRole} -> Maybe Text
serviceRole) (\s :: Build
s@Build' {} Maybe Text
a -> Build
s {$sel:serviceRole:Build' :: Maybe Text
serviceRole = Maybe Text
a} :: Build)

-- | Information about the source code to be built.
build_source :: Lens.Lens' Build (Prelude.Maybe ProjectSource)
build_source :: Lens' Build (Maybe ProjectSource)
build_source = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\Build' {Maybe ProjectSource
source :: Maybe ProjectSource
$sel:source:Build' :: Build -> Maybe ProjectSource
source} -> Maybe ProjectSource
source) (\s :: Build
s@Build' {} Maybe ProjectSource
a -> Build
s {$sel:source:Build' :: Maybe ProjectSource
source = Maybe ProjectSource
a} :: Build)

-- | Any version identifier for the version of the source code to be built.
-- If @sourceVersion@ is specified at the project level, then this
-- @sourceVersion@ (at the build level) takes precedence.
--
-- For more information, see
-- <https://docs.aws.amazon.com/codebuild/latest/userguide/sample-source-version.html Source Version Sample with CodeBuild>
-- in the /CodeBuild User Guide/.
build_sourceVersion :: Lens.Lens' Build (Prelude.Maybe Prelude.Text)
build_sourceVersion :: Lens' Build (Maybe Text)
build_sourceVersion = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\Build' {Maybe Text
sourceVersion :: Maybe Text
$sel:sourceVersion:Build' :: Build -> Maybe Text
sourceVersion} -> Maybe Text
sourceVersion) (\s :: Build
s@Build' {} Maybe Text
a -> Build
s {$sel:sourceVersion:Build' :: Maybe Text
sourceVersion = Maybe Text
a} :: Build)

-- | When the build process started, expressed in Unix time format.
build_startTime :: Lens.Lens' Build (Prelude.Maybe Prelude.UTCTime)
build_startTime :: Lens' Build (Maybe UTCTime)
build_startTime = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\Build' {Maybe POSIX
startTime :: Maybe POSIX
$sel:startTime:Build' :: Build -> Maybe POSIX
startTime} -> Maybe POSIX
startTime) (\s :: Build
s@Build' {} Maybe POSIX
a -> Build
s {$sel:startTime:Build' :: Maybe POSIX
startTime = Maybe POSIX
a} :: Build) 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

-- | How long, in minutes, for CodeBuild to wait before timing out this build
-- if it does not get marked as completed.
build_timeoutInMinutes :: Lens.Lens' Build (Prelude.Maybe Prelude.Int)
build_timeoutInMinutes :: Lens' Build (Maybe Int)
build_timeoutInMinutes = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\Build' {Maybe Int
timeoutInMinutes :: Maybe Int
$sel:timeoutInMinutes:Build' :: Build -> Maybe Int
timeoutInMinutes} -> Maybe Int
timeoutInMinutes) (\s :: Build
s@Build' {} Maybe Int
a -> Build
s {$sel:timeoutInMinutes:Build' :: Maybe Int
timeoutInMinutes = Maybe Int
a} :: Build)

-- | If your CodeBuild project accesses resources in an Amazon VPC, you
-- provide this parameter that identifies the VPC ID and the list of
-- security group IDs and subnet IDs. The security groups and subnets must
-- belong to the same VPC. You must provide at least one security group and
-- one subnet ID.
build_vpcConfig :: Lens.Lens' Build (Prelude.Maybe VpcConfig)
build_vpcConfig :: Lens' Build (Maybe VpcConfig)
build_vpcConfig = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\Build' {Maybe VpcConfig
vpcConfig :: Maybe VpcConfig
$sel:vpcConfig:Build' :: Build -> Maybe VpcConfig
vpcConfig} -> Maybe VpcConfig
vpcConfig) (\s :: Build
s@Build' {} Maybe VpcConfig
a -> Build
s {$sel:vpcConfig:Build' :: Maybe VpcConfig
vpcConfig = Maybe VpcConfig
a} :: Build)

instance Data.FromJSON Build where
  parseJSON :: Value -> Parser Build
parseJSON =
    forall a. String -> (Object -> Parser a) -> Value -> Parser a
Data.withObject
      String
"Build"
      ( \Object
x ->
          Maybe Text
-> Maybe BuildArtifacts
-> Maybe Text
-> Maybe Bool
-> Maybe Integer
-> Maybe StatusType
-> Maybe ProjectCache
-> Maybe Text
-> Maybe DebugSession
-> Maybe Text
-> Maybe POSIX
-> Maybe ProjectEnvironment
-> Maybe [ExportedEnvironmentVariable]
-> Maybe [ProjectFileSystemLocation]
-> Maybe Text
-> Maybe Text
-> Maybe LogsLocation
-> Maybe NetworkInterface
-> Maybe [BuildPhase]
-> Maybe Text
-> Maybe Int
-> Maybe [Text]
-> Maybe Text
-> Maybe [BuildArtifacts]
-> Maybe [ProjectSourceVersion]
-> Maybe [ProjectSource]
-> Maybe Text
-> Maybe ProjectSource
-> Maybe Text
-> Maybe POSIX
-> Maybe Int
-> Maybe VpcConfig
-> Build
Build'
            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
"buildBatchArn")
            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
"buildComplete")
            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
"buildNumber")
            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
"buildStatus")
            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
"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
"debugSession")
            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
"exportedEnvironmentVariables"
                            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
"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
"logs")
            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
"networkInterface")
            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
"reportArns" 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
"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
"timeoutInMinutes")
            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 Build where
  hashWithSalt :: Int -> Build -> Int
hashWithSalt Int
_salt Build' {Maybe Bool
Maybe Int
Maybe Integer
Maybe [Text]
Maybe [BuildArtifacts]
Maybe [ExportedEnvironmentVariable]
Maybe [ProjectFileSystemLocation]
Maybe [ProjectSourceVersion]
Maybe [ProjectSource]
Maybe [BuildPhase]
Maybe Text
Maybe POSIX
Maybe BuildArtifacts
Maybe DebugSession
Maybe NetworkInterface
Maybe ProjectCache
Maybe ProjectEnvironment
Maybe LogsLocation
Maybe ProjectSource
Maybe StatusType
Maybe VpcConfig
vpcConfig :: Maybe VpcConfig
timeoutInMinutes :: Maybe Int
startTime :: Maybe POSIX
sourceVersion :: Maybe Text
source :: Maybe ProjectSource
serviceRole :: Maybe Text
secondarySources :: Maybe [ProjectSource]
secondarySourceVersions :: Maybe [ProjectSourceVersion]
secondaryArtifacts :: Maybe [BuildArtifacts]
resolvedSourceVersion :: Maybe Text
reportArns :: Maybe [Text]
queuedTimeoutInMinutes :: Maybe Int
projectName :: Maybe Text
phases :: Maybe [BuildPhase]
networkInterface :: Maybe NetworkInterface
logs :: Maybe LogsLocation
initiator :: Maybe Text
id :: Maybe Text
fileSystemLocations :: Maybe [ProjectFileSystemLocation]
exportedEnvironmentVariables :: Maybe [ExportedEnvironmentVariable]
environment :: Maybe ProjectEnvironment
endTime :: Maybe POSIX
encryptionKey :: Maybe Text
debugSession :: Maybe DebugSession
currentPhase :: Maybe Text
cache :: Maybe ProjectCache
buildStatus :: Maybe StatusType
buildNumber :: Maybe Integer
buildComplete :: Maybe Bool
buildBatchArn :: Maybe Text
artifacts :: Maybe BuildArtifacts
arn :: Maybe Text
$sel:vpcConfig:Build' :: Build -> Maybe VpcConfig
$sel:timeoutInMinutes:Build' :: Build -> Maybe Int
$sel:startTime:Build' :: Build -> Maybe POSIX
$sel:sourceVersion:Build' :: Build -> Maybe Text
$sel:source:Build' :: Build -> Maybe ProjectSource
$sel:serviceRole:Build' :: Build -> Maybe Text
$sel:secondarySources:Build' :: Build -> Maybe [ProjectSource]
$sel:secondarySourceVersions:Build' :: Build -> Maybe [ProjectSourceVersion]
$sel:secondaryArtifacts:Build' :: Build -> Maybe [BuildArtifacts]
$sel:resolvedSourceVersion:Build' :: Build -> Maybe Text
$sel:reportArns:Build' :: Build -> Maybe [Text]
$sel:queuedTimeoutInMinutes:Build' :: Build -> Maybe Int
$sel:projectName:Build' :: Build -> Maybe Text
$sel:phases:Build' :: Build -> Maybe [BuildPhase]
$sel:networkInterface:Build' :: Build -> Maybe NetworkInterface
$sel:logs:Build' :: Build -> Maybe LogsLocation
$sel:initiator:Build' :: Build -> Maybe Text
$sel:id:Build' :: Build -> Maybe Text
$sel:fileSystemLocations:Build' :: Build -> Maybe [ProjectFileSystemLocation]
$sel:exportedEnvironmentVariables:Build' :: Build -> Maybe [ExportedEnvironmentVariable]
$sel:environment:Build' :: Build -> Maybe ProjectEnvironment
$sel:endTime:Build' :: Build -> Maybe POSIX
$sel:encryptionKey:Build' :: Build -> Maybe Text
$sel:debugSession:Build' :: Build -> Maybe DebugSession
$sel:currentPhase:Build' :: Build -> Maybe Text
$sel:cache:Build' :: Build -> Maybe ProjectCache
$sel:buildStatus:Build' :: Build -> Maybe StatusType
$sel:buildNumber:Build' :: Build -> Maybe Integer
$sel:buildComplete:Build' :: Build -> Maybe Bool
$sel:buildBatchArn:Build' :: Build -> Maybe Text
$sel:artifacts:Build' :: Build -> Maybe BuildArtifacts
$sel:arn:Build' :: Build -> 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 Text
buildBatchArn
      forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Maybe Bool
buildComplete
      forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Maybe Integer
buildNumber
      forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Maybe StatusType
buildStatus
      forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Maybe ProjectCache
cache
      forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Maybe Text
currentPhase
      forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Maybe DebugSession
debugSession
      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 [ExportedEnvironmentVariable]
exportedEnvironmentVariables
      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 LogsLocation
logs
      forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Maybe NetworkInterface
networkInterface
      forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Maybe [BuildPhase]
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]
reportArns
      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 Int
timeoutInMinutes
      forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Maybe VpcConfig
vpcConfig

instance Prelude.NFData Build where
  rnf :: Build -> ()
rnf Build' {Maybe Bool
Maybe Int
Maybe Integer
Maybe [Text]
Maybe [BuildArtifacts]
Maybe [ExportedEnvironmentVariable]
Maybe [ProjectFileSystemLocation]
Maybe [ProjectSourceVersion]
Maybe [ProjectSource]
Maybe [BuildPhase]
Maybe Text
Maybe POSIX
Maybe BuildArtifacts
Maybe DebugSession
Maybe NetworkInterface
Maybe ProjectCache
Maybe ProjectEnvironment
Maybe LogsLocation
Maybe ProjectSource
Maybe StatusType
Maybe VpcConfig
vpcConfig :: Maybe VpcConfig
timeoutInMinutes :: Maybe Int
startTime :: Maybe POSIX
sourceVersion :: Maybe Text
source :: Maybe ProjectSource
serviceRole :: Maybe Text
secondarySources :: Maybe [ProjectSource]
secondarySourceVersions :: Maybe [ProjectSourceVersion]
secondaryArtifacts :: Maybe [BuildArtifacts]
resolvedSourceVersion :: Maybe Text
reportArns :: Maybe [Text]
queuedTimeoutInMinutes :: Maybe Int
projectName :: Maybe Text
phases :: Maybe [BuildPhase]
networkInterface :: Maybe NetworkInterface
logs :: Maybe LogsLocation
initiator :: Maybe Text
id :: Maybe Text
fileSystemLocations :: Maybe [ProjectFileSystemLocation]
exportedEnvironmentVariables :: Maybe [ExportedEnvironmentVariable]
environment :: Maybe ProjectEnvironment
endTime :: Maybe POSIX
encryptionKey :: Maybe Text
debugSession :: Maybe DebugSession
currentPhase :: Maybe Text
cache :: Maybe ProjectCache
buildStatus :: Maybe StatusType
buildNumber :: Maybe Integer
buildComplete :: Maybe Bool
buildBatchArn :: Maybe Text
artifacts :: Maybe BuildArtifacts
arn :: Maybe Text
$sel:vpcConfig:Build' :: Build -> Maybe VpcConfig
$sel:timeoutInMinutes:Build' :: Build -> Maybe Int
$sel:startTime:Build' :: Build -> Maybe POSIX
$sel:sourceVersion:Build' :: Build -> Maybe Text
$sel:source:Build' :: Build -> Maybe ProjectSource
$sel:serviceRole:Build' :: Build -> Maybe Text
$sel:secondarySources:Build' :: Build -> Maybe [ProjectSource]
$sel:secondarySourceVersions:Build' :: Build -> Maybe [ProjectSourceVersion]
$sel:secondaryArtifacts:Build' :: Build -> Maybe [BuildArtifacts]
$sel:resolvedSourceVersion:Build' :: Build -> Maybe Text
$sel:reportArns:Build' :: Build -> Maybe [Text]
$sel:queuedTimeoutInMinutes:Build' :: Build -> Maybe Int
$sel:projectName:Build' :: Build -> Maybe Text
$sel:phases:Build' :: Build -> Maybe [BuildPhase]
$sel:networkInterface:Build' :: Build -> Maybe NetworkInterface
$sel:logs:Build' :: Build -> Maybe LogsLocation
$sel:initiator:Build' :: Build -> Maybe Text
$sel:id:Build' :: Build -> Maybe Text
$sel:fileSystemLocations:Build' :: Build -> Maybe [ProjectFileSystemLocation]
$sel:exportedEnvironmentVariables:Build' :: Build -> Maybe [ExportedEnvironmentVariable]
$sel:environment:Build' :: Build -> Maybe ProjectEnvironment
$sel:endTime:Build' :: Build -> Maybe POSIX
$sel:encryptionKey:Build' :: Build -> Maybe Text
$sel:debugSession:Build' :: Build -> Maybe DebugSession
$sel:currentPhase:Build' :: Build -> Maybe Text
$sel:cache:Build' :: Build -> Maybe ProjectCache
$sel:buildStatus:Build' :: Build -> Maybe StatusType
$sel:buildNumber:Build' :: Build -> Maybe Integer
$sel:buildComplete:Build' :: Build -> Maybe Bool
$sel:buildBatchArn:Build' :: Build -> Maybe Text
$sel:artifacts:Build' :: Build -> Maybe BuildArtifacts
$sel:arn:Build' :: Build -> 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 Text
buildBatchArn
      seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf Maybe Bool
buildComplete
      seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf Maybe Integer
buildNumber
      seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf Maybe StatusType
buildStatus
      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 Text
currentPhase
      seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf Maybe DebugSession
debugSession
      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 [ExportedEnvironmentVariable]
exportedEnvironmentVariables
      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 LogsLocation
logs
      seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf Maybe NetworkInterface
networkInterface
      seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf Maybe [BuildPhase]
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]
reportArns
      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 Int
timeoutInMinutes
      seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf
        Maybe VpcConfig
vpcConfig