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

import Amazonka.CodeBuild.Types.ArtifactNamespace
import Amazonka.CodeBuild.Types.ArtifactPackaging
import Amazonka.CodeBuild.Types.ArtifactsType
import Amazonka.CodeBuild.Types.BucketOwnerAccess
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 the build output artifacts for the build project.
--
-- /See:/ 'newProjectArtifacts' smart constructor.
data ProjectArtifacts = ProjectArtifacts'
  { -- | An identifier for this artifact definition.
    ProjectArtifacts -> Maybe Text
artifactIdentifier :: Prelude.Maybe Prelude.Text,
    ProjectArtifacts -> Maybe BucketOwnerAccess
bucketOwnerAccess :: Prelude.Maybe BucketOwnerAccess,
    -- | Set to true if you do not want your output artifacts encrypted. This
    -- option is valid only if your artifacts type is Amazon S3. If this is set
    -- with another artifacts type, an invalidInputException is thrown.
    ProjectArtifacts -> Maybe Bool
encryptionDisabled :: Prelude.Maybe Prelude.Bool,
    -- | Information about the build output artifact location:
    --
    -- -   If @type@ is set to @CODEPIPELINE@, CodePipeline ignores this value
    --     if specified. This is because CodePipeline manages its build output
    --     locations instead of CodeBuild.
    --
    -- -   If @type@ is set to @NO_ARTIFACTS@, this value is ignored if
    --     specified, because no build output is produced.
    --
    -- -   If @type@ is set to @S3@, this is the name of the output bucket.
    ProjectArtifacts -> Maybe Text
location :: Prelude.Maybe Prelude.Text,
    -- | Along with @path@ and @namespaceType@, the pattern that CodeBuild uses
    -- to name and store the output artifact:
    --
    -- -   If @type@ is set to @CODEPIPELINE@, CodePipeline ignores this value
    --     if specified. This is because CodePipeline manages its build output
    --     names instead of CodeBuild.
    --
    -- -   If @type@ is set to @NO_ARTIFACTS@, this value is ignored if
    --     specified, because no build output is produced.
    --
    -- -   If @type@ is set to @S3@, this is the name of the output artifact
    --     object. If you set the name to be a forward slash (\"\/\"), the
    --     artifact is stored in the root of the output bucket.
    --
    -- For example:
    --
    -- -   If @path@ is set to @MyArtifacts@, @namespaceType@ is set to
    --     @BUILD_ID@, and @name@ is set to @MyArtifact.zip@, then the output
    --     artifact is stored in @MyArtifacts\/\<build-ID>\/MyArtifact.zip@.
    --
    -- -   If @path@ is empty, @namespaceType@ is set to @NONE@, and @name@ is
    --     set to \"@\/@\", the output artifact is stored in the root of the
    --     output bucket.
    --
    -- -   If @path@ is set to @MyArtifacts@, @namespaceType@ is set to
    --     @BUILD_ID@, and @name@ is set to \"@\/@\", the output artifact is
    --     stored in @MyArtifacts\/\<build-ID>@.
    ProjectArtifacts -> Maybe Text
name :: Prelude.Maybe Prelude.Text,
    -- | Along with @path@ and @name@, the pattern that CodeBuild uses to
    -- determine the name and location to store the output artifact:
    --
    -- -   If @type@ is set to @CODEPIPELINE@, CodePipeline ignores this value
    --     if specified. This is because CodePipeline manages its build output
    --     names instead of CodeBuild.
    --
    -- -   If @type@ is set to @NO_ARTIFACTS@, this value is ignored if
    --     specified, because no build output is produced.
    --
    -- -   If @type@ is set to @S3@, valid values include:
    --
    --     -   @BUILD_ID@: Include the build ID in the location of the build
    --         output artifact.
    --
    --     -   @NONE@: Do not include the build ID. This is the default if
    --         @namespaceType@ is not specified.
    --
    -- For example, if @path@ is set to @MyArtifacts@, @namespaceType@ is set
    -- to @BUILD_ID@, and @name@ is set to @MyArtifact.zip@, the output
    -- artifact is stored in @MyArtifacts\/\<build-ID>\/MyArtifact.zip@.
    ProjectArtifacts -> Maybe ArtifactNamespace
namespaceType :: Prelude.Maybe ArtifactNamespace,
    -- | If this flag is set, a name specified in the buildspec file overrides
    -- the artifact name. The name specified in a buildspec file is calculated
    -- at build time and uses the Shell Command Language. For example, you can
    -- append a date and time to your artifact name so that it is always
    -- unique.
    ProjectArtifacts -> Maybe Bool
overrideArtifactName :: Prelude.Maybe Prelude.Bool,
    -- | The type of build output artifact to create:
    --
    -- -   If @type@ is set to @CODEPIPELINE@, CodePipeline ignores this value
    --     if specified. This is because CodePipeline manages its build output
    --     artifacts instead of CodeBuild.
    --
    -- -   If @type@ is set to @NO_ARTIFACTS@, this value is ignored if
    --     specified, because no build output is produced.
    --
    -- -   If @type@ is set to @S3@, valid values include:
    --
    --     -   @NONE@: CodeBuild creates in the output bucket a folder that
    --         contains the build output. This is the default if @packaging@ is
    --         not specified.
    --
    --     -   @ZIP@: CodeBuild creates in the output bucket a ZIP file that
    --         contains the build output.
    ProjectArtifacts -> Maybe ArtifactPackaging
packaging :: Prelude.Maybe ArtifactPackaging,
    -- | Along with @namespaceType@ and @name@, the pattern that CodeBuild uses
    -- to name and store the output artifact:
    --
    -- -   If @type@ is set to @CODEPIPELINE@, CodePipeline ignores this value
    --     if specified. This is because CodePipeline manages its build output
    --     names instead of CodeBuild.
    --
    -- -   If @type@ is set to @NO_ARTIFACTS@, this value is ignored if
    --     specified, because no build output is produced.
    --
    -- -   If @type@ is set to @S3@, this is the path to the output artifact.
    --     If @path@ is not specified, @path@ is not used.
    --
    -- For example, if @path@ is set to @MyArtifacts@, @namespaceType@ is set
    -- to @NONE@, and @name@ is set to @MyArtifact.zip@, the output artifact is
    -- stored in the output bucket at @MyArtifacts\/MyArtifact.zip@.
    ProjectArtifacts -> Maybe Text
path :: Prelude.Maybe Prelude.Text,
    -- | The type of build output artifact. Valid values include:
    --
    -- -   @CODEPIPELINE@: The build project has build output generated through
    --     CodePipeline.
    --
    --     The @CODEPIPELINE@ type is not supported for @secondaryArtifacts@.
    --
    -- -   @NO_ARTIFACTS@: The build project does not produce any build output.
    --
    -- -   @S3@: The build project stores build output in Amazon S3.
    ProjectArtifacts -> ArtifactsType
type' :: ArtifactsType
  }
  deriving (ProjectArtifacts -> ProjectArtifacts -> Bool
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: ProjectArtifacts -> ProjectArtifacts -> Bool
$c/= :: ProjectArtifacts -> ProjectArtifacts -> Bool
== :: ProjectArtifacts -> ProjectArtifacts -> Bool
$c== :: ProjectArtifacts -> ProjectArtifacts -> Bool
Prelude.Eq, ReadPrec [ProjectArtifacts]
ReadPrec ProjectArtifacts
Int -> ReadS ProjectArtifacts
ReadS [ProjectArtifacts]
forall a.
(Int -> ReadS a)
-> ReadS [a] -> ReadPrec a -> ReadPrec [a] -> Read a
readListPrec :: ReadPrec [ProjectArtifacts]
$creadListPrec :: ReadPrec [ProjectArtifacts]
readPrec :: ReadPrec ProjectArtifacts
$creadPrec :: ReadPrec ProjectArtifacts
readList :: ReadS [ProjectArtifacts]
$creadList :: ReadS [ProjectArtifacts]
readsPrec :: Int -> ReadS ProjectArtifacts
$creadsPrec :: Int -> ReadS ProjectArtifacts
Prelude.Read, Int -> ProjectArtifacts -> ShowS
[ProjectArtifacts] -> ShowS
ProjectArtifacts -> String
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [ProjectArtifacts] -> ShowS
$cshowList :: [ProjectArtifacts] -> ShowS
show :: ProjectArtifacts -> String
$cshow :: ProjectArtifacts -> String
showsPrec :: Int -> ProjectArtifacts -> ShowS
$cshowsPrec :: Int -> ProjectArtifacts -> ShowS
Prelude.Show, forall x. Rep ProjectArtifacts x -> ProjectArtifacts
forall x. ProjectArtifacts -> Rep ProjectArtifacts x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cto :: forall x. Rep ProjectArtifacts x -> ProjectArtifacts
$cfrom :: forall x. ProjectArtifacts -> Rep ProjectArtifacts x
Prelude.Generic)

-- |
-- Create a value of 'ProjectArtifacts' 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:
--
-- 'artifactIdentifier', 'projectArtifacts_artifactIdentifier' - An identifier for this artifact definition.
--
-- 'bucketOwnerAccess', 'projectArtifacts_bucketOwnerAccess' - Undocumented member.
--
-- 'encryptionDisabled', 'projectArtifacts_encryptionDisabled' - Set to true if you do not want your output artifacts encrypted. This
-- option is valid only if your artifacts type is Amazon S3. If this is set
-- with another artifacts type, an invalidInputException is thrown.
--
-- 'location', 'projectArtifacts_location' - Information about the build output artifact location:
--
-- -   If @type@ is set to @CODEPIPELINE@, CodePipeline ignores this value
--     if specified. This is because CodePipeline manages its build output
--     locations instead of CodeBuild.
--
-- -   If @type@ is set to @NO_ARTIFACTS@, this value is ignored if
--     specified, because no build output is produced.
--
-- -   If @type@ is set to @S3@, this is the name of the output bucket.
--
-- 'name', 'projectArtifacts_name' - Along with @path@ and @namespaceType@, the pattern that CodeBuild uses
-- to name and store the output artifact:
--
-- -   If @type@ is set to @CODEPIPELINE@, CodePipeline ignores this value
--     if specified. This is because CodePipeline manages its build output
--     names instead of CodeBuild.
--
-- -   If @type@ is set to @NO_ARTIFACTS@, this value is ignored if
--     specified, because no build output is produced.
--
-- -   If @type@ is set to @S3@, this is the name of the output artifact
--     object. If you set the name to be a forward slash (\"\/\"), the
--     artifact is stored in the root of the output bucket.
--
-- For example:
--
-- -   If @path@ is set to @MyArtifacts@, @namespaceType@ is set to
--     @BUILD_ID@, and @name@ is set to @MyArtifact.zip@, then the output
--     artifact is stored in @MyArtifacts\/\<build-ID>\/MyArtifact.zip@.
--
-- -   If @path@ is empty, @namespaceType@ is set to @NONE@, and @name@ is
--     set to \"@\/@\", the output artifact is stored in the root of the
--     output bucket.
--
-- -   If @path@ is set to @MyArtifacts@, @namespaceType@ is set to
--     @BUILD_ID@, and @name@ is set to \"@\/@\", the output artifact is
--     stored in @MyArtifacts\/\<build-ID>@.
--
-- 'namespaceType', 'projectArtifacts_namespaceType' - Along with @path@ and @name@, the pattern that CodeBuild uses to
-- determine the name and location to store the output artifact:
--
-- -   If @type@ is set to @CODEPIPELINE@, CodePipeline ignores this value
--     if specified. This is because CodePipeline manages its build output
--     names instead of CodeBuild.
--
-- -   If @type@ is set to @NO_ARTIFACTS@, this value is ignored if
--     specified, because no build output is produced.
--
-- -   If @type@ is set to @S3@, valid values include:
--
--     -   @BUILD_ID@: Include the build ID in the location of the build
--         output artifact.
--
--     -   @NONE@: Do not include the build ID. This is the default if
--         @namespaceType@ is not specified.
--
-- For example, if @path@ is set to @MyArtifacts@, @namespaceType@ is set
-- to @BUILD_ID@, and @name@ is set to @MyArtifact.zip@, the output
-- artifact is stored in @MyArtifacts\/\<build-ID>\/MyArtifact.zip@.
--
-- 'overrideArtifactName', 'projectArtifacts_overrideArtifactName' - If this flag is set, a name specified in the buildspec file overrides
-- the artifact name. The name specified in a buildspec file is calculated
-- at build time and uses the Shell Command Language. For example, you can
-- append a date and time to your artifact name so that it is always
-- unique.
--
-- 'packaging', 'projectArtifacts_packaging' - The type of build output artifact to create:
--
-- -   If @type@ is set to @CODEPIPELINE@, CodePipeline ignores this value
--     if specified. This is because CodePipeline manages its build output
--     artifacts instead of CodeBuild.
--
-- -   If @type@ is set to @NO_ARTIFACTS@, this value is ignored if
--     specified, because no build output is produced.
--
-- -   If @type@ is set to @S3@, valid values include:
--
--     -   @NONE@: CodeBuild creates in the output bucket a folder that
--         contains the build output. This is the default if @packaging@ is
--         not specified.
--
--     -   @ZIP@: CodeBuild creates in the output bucket a ZIP file that
--         contains the build output.
--
-- 'path', 'projectArtifacts_path' - Along with @namespaceType@ and @name@, the pattern that CodeBuild uses
-- to name and store the output artifact:
--
-- -   If @type@ is set to @CODEPIPELINE@, CodePipeline ignores this value
--     if specified. This is because CodePipeline manages its build output
--     names instead of CodeBuild.
--
-- -   If @type@ is set to @NO_ARTIFACTS@, this value is ignored if
--     specified, because no build output is produced.
--
-- -   If @type@ is set to @S3@, this is the path to the output artifact.
--     If @path@ is not specified, @path@ is not used.
--
-- For example, if @path@ is set to @MyArtifacts@, @namespaceType@ is set
-- to @NONE@, and @name@ is set to @MyArtifact.zip@, the output artifact is
-- stored in the output bucket at @MyArtifacts\/MyArtifact.zip@.
--
-- 'type'', 'projectArtifacts_type' - The type of build output artifact. Valid values include:
--
-- -   @CODEPIPELINE@: The build project has build output generated through
--     CodePipeline.
--
--     The @CODEPIPELINE@ type is not supported for @secondaryArtifacts@.
--
-- -   @NO_ARTIFACTS@: The build project does not produce any build output.
--
-- -   @S3@: The build project stores build output in Amazon S3.
newProjectArtifacts ::
  -- | 'type''
  ArtifactsType ->
  ProjectArtifacts
newProjectArtifacts :: ArtifactsType -> ProjectArtifacts
newProjectArtifacts ArtifactsType
pType_ =
  ProjectArtifacts'
    { $sel:artifactIdentifier:ProjectArtifacts' :: Maybe Text
artifactIdentifier =
        forall a. Maybe a
Prelude.Nothing,
      $sel:bucketOwnerAccess:ProjectArtifacts' :: Maybe BucketOwnerAccess
bucketOwnerAccess = forall a. Maybe a
Prelude.Nothing,
      $sel:encryptionDisabled:ProjectArtifacts' :: Maybe Bool
encryptionDisabled = forall a. Maybe a
Prelude.Nothing,
      $sel:location:ProjectArtifacts' :: Maybe Text
location = forall a. Maybe a
Prelude.Nothing,
      $sel:name:ProjectArtifacts' :: Maybe Text
name = forall a. Maybe a
Prelude.Nothing,
      $sel:namespaceType:ProjectArtifacts' :: Maybe ArtifactNamespace
namespaceType = forall a. Maybe a
Prelude.Nothing,
      $sel:overrideArtifactName:ProjectArtifacts' :: Maybe Bool
overrideArtifactName = forall a. Maybe a
Prelude.Nothing,
      $sel:packaging:ProjectArtifacts' :: Maybe ArtifactPackaging
packaging = forall a. Maybe a
Prelude.Nothing,
      $sel:path:ProjectArtifacts' :: Maybe Text
path = forall a. Maybe a
Prelude.Nothing,
      $sel:type':ProjectArtifacts' :: ArtifactsType
type' = ArtifactsType
pType_
    }

-- | An identifier for this artifact definition.
projectArtifacts_artifactIdentifier :: Lens.Lens' ProjectArtifacts (Prelude.Maybe Prelude.Text)
projectArtifacts_artifactIdentifier :: Lens' ProjectArtifacts (Maybe Text)
projectArtifacts_artifactIdentifier = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\ProjectArtifacts' {Maybe Text
artifactIdentifier :: Maybe Text
$sel:artifactIdentifier:ProjectArtifacts' :: ProjectArtifacts -> Maybe Text
artifactIdentifier} -> Maybe Text
artifactIdentifier) (\s :: ProjectArtifacts
s@ProjectArtifacts' {} Maybe Text
a -> ProjectArtifacts
s {$sel:artifactIdentifier:ProjectArtifacts' :: Maybe Text
artifactIdentifier = Maybe Text
a} :: ProjectArtifacts)

-- | Undocumented member.
projectArtifacts_bucketOwnerAccess :: Lens.Lens' ProjectArtifacts (Prelude.Maybe BucketOwnerAccess)
projectArtifacts_bucketOwnerAccess :: Lens' ProjectArtifacts (Maybe BucketOwnerAccess)
projectArtifacts_bucketOwnerAccess = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\ProjectArtifacts' {Maybe BucketOwnerAccess
bucketOwnerAccess :: Maybe BucketOwnerAccess
$sel:bucketOwnerAccess:ProjectArtifacts' :: ProjectArtifacts -> Maybe BucketOwnerAccess
bucketOwnerAccess} -> Maybe BucketOwnerAccess
bucketOwnerAccess) (\s :: ProjectArtifacts
s@ProjectArtifacts' {} Maybe BucketOwnerAccess
a -> ProjectArtifacts
s {$sel:bucketOwnerAccess:ProjectArtifacts' :: Maybe BucketOwnerAccess
bucketOwnerAccess = Maybe BucketOwnerAccess
a} :: ProjectArtifacts)

-- | Set to true if you do not want your output artifacts encrypted. This
-- option is valid only if your artifacts type is Amazon S3. If this is set
-- with another artifacts type, an invalidInputException is thrown.
projectArtifacts_encryptionDisabled :: Lens.Lens' ProjectArtifacts (Prelude.Maybe Prelude.Bool)
projectArtifacts_encryptionDisabled :: Lens' ProjectArtifacts (Maybe Bool)
projectArtifacts_encryptionDisabled = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\ProjectArtifacts' {Maybe Bool
encryptionDisabled :: Maybe Bool
$sel:encryptionDisabled:ProjectArtifacts' :: ProjectArtifacts -> Maybe Bool
encryptionDisabled} -> Maybe Bool
encryptionDisabled) (\s :: ProjectArtifacts
s@ProjectArtifacts' {} Maybe Bool
a -> ProjectArtifacts
s {$sel:encryptionDisabled:ProjectArtifacts' :: Maybe Bool
encryptionDisabled = Maybe Bool
a} :: ProjectArtifacts)

-- | Information about the build output artifact location:
--
-- -   If @type@ is set to @CODEPIPELINE@, CodePipeline ignores this value
--     if specified. This is because CodePipeline manages its build output
--     locations instead of CodeBuild.
--
-- -   If @type@ is set to @NO_ARTIFACTS@, this value is ignored if
--     specified, because no build output is produced.
--
-- -   If @type@ is set to @S3@, this is the name of the output bucket.
projectArtifacts_location :: Lens.Lens' ProjectArtifacts (Prelude.Maybe Prelude.Text)
projectArtifacts_location :: Lens' ProjectArtifacts (Maybe Text)
projectArtifacts_location = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\ProjectArtifacts' {Maybe Text
location :: Maybe Text
$sel:location:ProjectArtifacts' :: ProjectArtifacts -> Maybe Text
location} -> Maybe Text
location) (\s :: ProjectArtifacts
s@ProjectArtifacts' {} Maybe Text
a -> ProjectArtifacts
s {$sel:location:ProjectArtifacts' :: Maybe Text
location = Maybe Text
a} :: ProjectArtifacts)

-- | Along with @path@ and @namespaceType@, the pattern that CodeBuild uses
-- to name and store the output artifact:
--
-- -   If @type@ is set to @CODEPIPELINE@, CodePipeline ignores this value
--     if specified. This is because CodePipeline manages its build output
--     names instead of CodeBuild.
--
-- -   If @type@ is set to @NO_ARTIFACTS@, this value is ignored if
--     specified, because no build output is produced.
--
-- -   If @type@ is set to @S3@, this is the name of the output artifact
--     object. If you set the name to be a forward slash (\"\/\"), the
--     artifact is stored in the root of the output bucket.
--
-- For example:
--
-- -   If @path@ is set to @MyArtifacts@, @namespaceType@ is set to
--     @BUILD_ID@, and @name@ is set to @MyArtifact.zip@, then the output
--     artifact is stored in @MyArtifacts\/\<build-ID>\/MyArtifact.zip@.
--
-- -   If @path@ is empty, @namespaceType@ is set to @NONE@, and @name@ is
--     set to \"@\/@\", the output artifact is stored in the root of the
--     output bucket.
--
-- -   If @path@ is set to @MyArtifacts@, @namespaceType@ is set to
--     @BUILD_ID@, and @name@ is set to \"@\/@\", the output artifact is
--     stored in @MyArtifacts\/\<build-ID>@.
projectArtifacts_name :: Lens.Lens' ProjectArtifacts (Prelude.Maybe Prelude.Text)
projectArtifacts_name :: Lens' ProjectArtifacts (Maybe Text)
projectArtifacts_name = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\ProjectArtifacts' {Maybe Text
name :: Maybe Text
$sel:name:ProjectArtifacts' :: ProjectArtifacts -> Maybe Text
name} -> Maybe Text
name) (\s :: ProjectArtifacts
s@ProjectArtifacts' {} Maybe Text
a -> ProjectArtifacts
s {$sel:name:ProjectArtifacts' :: Maybe Text
name = Maybe Text
a} :: ProjectArtifacts)

-- | Along with @path@ and @name@, the pattern that CodeBuild uses to
-- determine the name and location to store the output artifact:
--
-- -   If @type@ is set to @CODEPIPELINE@, CodePipeline ignores this value
--     if specified. This is because CodePipeline manages its build output
--     names instead of CodeBuild.
--
-- -   If @type@ is set to @NO_ARTIFACTS@, this value is ignored if
--     specified, because no build output is produced.
--
-- -   If @type@ is set to @S3@, valid values include:
--
--     -   @BUILD_ID@: Include the build ID in the location of the build
--         output artifact.
--
--     -   @NONE@: Do not include the build ID. This is the default if
--         @namespaceType@ is not specified.
--
-- For example, if @path@ is set to @MyArtifacts@, @namespaceType@ is set
-- to @BUILD_ID@, and @name@ is set to @MyArtifact.zip@, the output
-- artifact is stored in @MyArtifacts\/\<build-ID>\/MyArtifact.zip@.
projectArtifacts_namespaceType :: Lens.Lens' ProjectArtifacts (Prelude.Maybe ArtifactNamespace)
projectArtifacts_namespaceType :: Lens' ProjectArtifacts (Maybe ArtifactNamespace)
projectArtifacts_namespaceType = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\ProjectArtifacts' {Maybe ArtifactNamespace
namespaceType :: Maybe ArtifactNamespace
$sel:namespaceType:ProjectArtifacts' :: ProjectArtifacts -> Maybe ArtifactNamespace
namespaceType} -> Maybe ArtifactNamespace
namespaceType) (\s :: ProjectArtifacts
s@ProjectArtifacts' {} Maybe ArtifactNamespace
a -> ProjectArtifacts
s {$sel:namespaceType:ProjectArtifacts' :: Maybe ArtifactNamespace
namespaceType = Maybe ArtifactNamespace
a} :: ProjectArtifacts)

-- | If this flag is set, a name specified in the buildspec file overrides
-- the artifact name. The name specified in a buildspec file is calculated
-- at build time and uses the Shell Command Language. For example, you can
-- append a date and time to your artifact name so that it is always
-- unique.
projectArtifacts_overrideArtifactName :: Lens.Lens' ProjectArtifacts (Prelude.Maybe Prelude.Bool)
projectArtifacts_overrideArtifactName :: Lens' ProjectArtifacts (Maybe Bool)
projectArtifacts_overrideArtifactName = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\ProjectArtifacts' {Maybe Bool
overrideArtifactName :: Maybe Bool
$sel:overrideArtifactName:ProjectArtifacts' :: ProjectArtifacts -> Maybe Bool
overrideArtifactName} -> Maybe Bool
overrideArtifactName) (\s :: ProjectArtifacts
s@ProjectArtifacts' {} Maybe Bool
a -> ProjectArtifacts
s {$sel:overrideArtifactName:ProjectArtifacts' :: Maybe Bool
overrideArtifactName = Maybe Bool
a} :: ProjectArtifacts)

-- | The type of build output artifact to create:
--
-- -   If @type@ is set to @CODEPIPELINE@, CodePipeline ignores this value
--     if specified. This is because CodePipeline manages its build output
--     artifacts instead of CodeBuild.
--
-- -   If @type@ is set to @NO_ARTIFACTS@, this value is ignored if
--     specified, because no build output is produced.
--
-- -   If @type@ is set to @S3@, valid values include:
--
--     -   @NONE@: CodeBuild creates in the output bucket a folder that
--         contains the build output. This is the default if @packaging@ is
--         not specified.
--
--     -   @ZIP@: CodeBuild creates in the output bucket a ZIP file that
--         contains the build output.
projectArtifacts_packaging :: Lens.Lens' ProjectArtifacts (Prelude.Maybe ArtifactPackaging)
projectArtifacts_packaging :: Lens' ProjectArtifacts (Maybe ArtifactPackaging)
projectArtifacts_packaging = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\ProjectArtifacts' {Maybe ArtifactPackaging
packaging :: Maybe ArtifactPackaging
$sel:packaging:ProjectArtifacts' :: ProjectArtifacts -> Maybe ArtifactPackaging
packaging} -> Maybe ArtifactPackaging
packaging) (\s :: ProjectArtifacts
s@ProjectArtifacts' {} Maybe ArtifactPackaging
a -> ProjectArtifacts
s {$sel:packaging:ProjectArtifacts' :: Maybe ArtifactPackaging
packaging = Maybe ArtifactPackaging
a} :: ProjectArtifacts)

-- | Along with @namespaceType@ and @name@, the pattern that CodeBuild uses
-- to name and store the output artifact:
--
-- -   If @type@ is set to @CODEPIPELINE@, CodePipeline ignores this value
--     if specified. This is because CodePipeline manages its build output
--     names instead of CodeBuild.
--
-- -   If @type@ is set to @NO_ARTIFACTS@, this value is ignored if
--     specified, because no build output is produced.
--
-- -   If @type@ is set to @S3@, this is the path to the output artifact.
--     If @path@ is not specified, @path@ is not used.
--
-- For example, if @path@ is set to @MyArtifacts@, @namespaceType@ is set
-- to @NONE@, and @name@ is set to @MyArtifact.zip@, the output artifact is
-- stored in the output bucket at @MyArtifacts\/MyArtifact.zip@.
projectArtifacts_path :: Lens.Lens' ProjectArtifacts (Prelude.Maybe Prelude.Text)
projectArtifacts_path :: Lens' ProjectArtifacts (Maybe Text)
projectArtifacts_path = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\ProjectArtifacts' {Maybe Text
path :: Maybe Text
$sel:path:ProjectArtifacts' :: ProjectArtifacts -> Maybe Text
path} -> Maybe Text
path) (\s :: ProjectArtifacts
s@ProjectArtifacts' {} Maybe Text
a -> ProjectArtifacts
s {$sel:path:ProjectArtifacts' :: Maybe Text
path = Maybe Text
a} :: ProjectArtifacts)

-- | The type of build output artifact. Valid values include:
--
-- -   @CODEPIPELINE@: The build project has build output generated through
--     CodePipeline.
--
--     The @CODEPIPELINE@ type is not supported for @secondaryArtifacts@.
--
-- -   @NO_ARTIFACTS@: The build project does not produce any build output.
--
-- -   @S3@: The build project stores build output in Amazon S3.
projectArtifacts_type :: Lens.Lens' ProjectArtifacts ArtifactsType
projectArtifacts_type :: Lens' ProjectArtifacts ArtifactsType
projectArtifacts_type = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\ProjectArtifacts' {ArtifactsType
type' :: ArtifactsType
$sel:type':ProjectArtifacts' :: ProjectArtifacts -> ArtifactsType
type'} -> ArtifactsType
type') (\s :: ProjectArtifacts
s@ProjectArtifacts' {} ArtifactsType
a -> ProjectArtifacts
s {$sel:type':ProjectArtifacts' :: ArtifactsType
type' = ArtifactsType
a} :: ProjectArtifacts)

instance Data.FromJSON ProjectArtifacts where
  parseJSON :: Value -> Parser ProjectArtifacts
parseJSON =
    forall a. String -> (Object -> Parser a) -> Value -> Parser a
Data.withObject
      String
"ProjectArtifacts"
      ( \Object
x ->
          Maybe Text
-> Maybe BucketOwnerAccess
-> Maybe Bool
-> Maybe Text
-> Maybe Text
-> Maybe ArtifactNamespace
-> Maybe Bool
-> Maybe ArtifactPackaging
-> Maybe Text
-> ArtifactsType
-> ProjectArtifacts
ProjectArtifacts'
            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
"artifactIdentifier")
            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
"bucketOwnerAccess")
            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
"encryptionDisabled")
            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
"location")
            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
"name")
            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
"namespaceType")
            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
"overrideArtifactName")
            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
"packaging")
            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
"path")
            forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
Prelude.<*> (Object
x forall a. FromJSON a => Object -> Key -> Parser a
Data..: Key
"type")
      )

instance Prelude.Hashable ProjectArtifacts where
  hashWithSalt :: Int -> ProjectArtifacts -> Int
hashWithSalt Int
_salt ProjectArtifacts' {Maybe Bool
Maybe Text
Maybe ArtifactNamespace
Maybe ArtifactPackaging
Maybe BucketOwnerAccess
ArtifactsType
type' :: ArtifactsType
path :: Maybe Text
packaging :: Maybe ArtifactPackaging
overrideArtifactName :: Maybe Bool
namespaceType :: Maybe ArtifactNamespace
name :: Maybe Text
location :: Maybe Text
encryptionDisabled :: Maybe Bool
bucketOwnerAccess :: Maybe BucketOwnerAccess
artifactIdentifier :: Maybe Text
$sel:type':ProjectArtifacts' :: ProjectArtifacts -> ArtifactsType
$sel:path:ProjectArtifacts' :: ProjectArtifacts -> Maybe Text
$sel:packaging:ProjectArtifacts' :: ProjectArtifacts -> Maybe ArtifactPackaging
$sel:overrideArtifactName:ProjectArtifacts' :: ProjectArtifacts -> Maybe Bool
$sel:namespaceType:ProjectArtifacts' :: ProjectArtifacts -> Maybe ArtifactNamespace
$sel:name:ProjectArtifacts' :: ProjectArtifacts -> Maybe Text
$sel:location:ProjectArtifacts' :: ProjectArtifacts -> Maybe Text
$sel:encryptionDisabled:ProjectArtifacts' :: ProjectArtifacts -> Maybe Bool
$sel:bucketOwnerAccess:ProjectArtifacts' :: ProjectArtifacts -> Maybe BucketOwnerAccess
$sel:artifactIdentifier:ProjectArtifacts' :: ProjectArtifacts -> Maybe Text
..} =
    Int
_salt
      forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Maybe Text
artifactIdentifier
      forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Maybe BucketOwnerAccess
bucketOwnerAccess
      forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Maybe Bool
encryptionDisabled
      forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Maybe Text
location
      forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Maybe Text
name
      forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Maybe ArtifactNamespace
namespaceType
      forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Maybe Bool
overrideArtifactName
      forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Maybe ArtifactPackaging
packaging
      forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Maybe Text
path
      forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` ArtifactsType
type'

instance Prelude.NFData ProjectArtifacts where
  rnf :: ProjectArtifacts -> ()
rnf ProjectArtifacts' {Maybe Bool
Maybe Text
Maybe ArtifactNamespace
Maybe ArtifactPackaging
Maybe BucketOwnerAccess
ArtifactsType
type' :: ArtifactsType
path :: Maybe Text
packaging :: Maybe ArtifactPackaging
overrideArtifactName :: Maybe Bool
namespaceType :: Maybe ArtifactNamespace
name :: Maybe Text
location :: Maybe Text
encryptionDisabled :: Maybe Bool
bucketOwnerAccess :: Maybe BucketOwnerAccess
artifactIdentifier :: Maybe Text
$sel:type':ProjectArtifacts' :: ProjectArtifacts -> ArtifactsType
$sel:path:ProjectArtifacts' :: ProjectArtifacts -> Maybe Text
$sel:packaging:ProjectArtifacts' :: ProjectArtifacts -> Maybe ArtifactPackaging
$sel:overrideArtifactName:ProjectArtifacts' :: ProjectArtifacts -> Maybe Bool
$sel:namespaceType:ProjectArtifacts' :: ProjectArtifacts -> Maybe ArtifactNamespace
$sel:name:ProjectArtifacts' :: ProjectArtifacts -> Maybe Text
$sel:location:ProjectArtifacts' :: ProjectArtifacts -> Maybe Text
$sel:encryptionDisabled:ProjectArtifacts' :: ProjectArtifacts -> Maybe Bool
$sel:bucketOwnerAccess:ProjectArtifacts' :: ProjectArtifacts -> Maybe BucketOwnerAccess
$sel:artifactIdentifier:ProjectArtifacts' :: ProjectArtifacts -> Maybe Text
..} =
    forall a. NFData a => a -> ()
Prelude.rnf Maybe Text
artifactIdentifier
      seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf Maybe BucketOwnerAccess
bucketOwnerAccess
      seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf Maybe Bool
encryptionDisabled
      seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf Maybe Text
location
      seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf Maybe Text
name
      seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf Maybe ArtifactNamespace
namespaceType
      seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf Maybe Bool
overrideArtifactName
      seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf Maybe ArtifactPackaging
packaging
      seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf Maybe Text
path
      seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf ArtifactsType
type'

instance Data.ToJSON ProjectArtifacts where
  toJSON :: ProjectArtifacts -> Value
toJSON ProjectArtifacts' {Maybe Bool
Maybe Text
Maybe ArtifactNamespace
Maybe ArtifactPackaging
Maybe BucketOwnerAccess
ArtifactsType
type' :: ArtifactsType
path :: Maybe Text
packaging :: Maybe ArtifactPackaging
overrideArtifactName :: Maybe Bool
namespaceType :: Maybe ArtifactNamespace
name :: Maybe Text
location :: Maybe Text
encryptionDisabled :: Maybe Bool
bucketOwnerAccess :: Maybe BucketOwnerAccess
artifactIdentifier :: Maybe Text
$sel:type':ProjectArtifacts' :: ProjectArtifacts -> ArtifactsType
$sel:path:ProjectArtifacts' :: ProjectArtifacts -> Maybe Text
$sel:packaging:ProjectArtifacts' :: ProjectArtifacts -> Maybe ArtifactPackaging
$sel:overrideArtifactName:ProjectArtifacts' :: ProjectArtifacts -> Maybe Bool
$sel:namespaceType:ProjectArtifacts' :: ProjectArtifacts -> Maybe ArtifactNamespace
$sel:name:ProjectArtifacts' :: ProjectArtifacts -> Maybe Text
$sel:location:ProjectArtifacts' :: ProjectArtifacts -> Maybe Text
$sel:encryptionDisabled:ProjectArtifacts' :: ProjectArtifacts -> Maybe Bool
$sel:bucketOwnerAccess:ProjectArtifacts' :: ProjectArtifacts -> Maybe BucketOwnerAccess
$sel:artifactIdentifier:ProjectArtifacts' :: ProjectArtifacts -> Maybe Text
..} =
    [Pair] -> Value
Data.object
      ( forall a. [Maybe a] -> [a]
Prelude.catMaybes
          [ (Key
"artifactIdentifier" forall kv v. (KeyValue kv, ToJSON v) => Key -> v -> kv
Data..=)
              forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
Prelude.<$> Maybe Text
artifactIdentifier,
            (Key
"bucketOwnerAccess" forall kv v. (KeyValue kv, ToJSON v) => Key -> v -> kv
Data..=)
              forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
Prelude.<$> Maybe BucketOwnerAccess
bucketOwnerAccess,
            (Key
"encryptionDisabled" forall kv v. (KeyValue kv, ToJSON v) => Key -> v -> kv
Data..=)
              forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
Prelude.<$> Maybe Bool
encryptionDisabled,
            (Key
"location" forall kv v. (KeyValue kv, ToJSON v) => Key -> v -> kv
Data..=) forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
Prelude.<$> Maybe Text
location,
            (Key
"name" forall kv v. (KeyValue kv, ToJSON v) => Key -> v -> kv
Data..=) forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
Prelude.<$> Maybe Text
name,
            (Key
"namespaceType" forall kv v. (KeyValue kv, ToJSON v) => Key -> v -> kv
Data..=) forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
Prelude.<$> Maybe ArtifactNamespace
namespaceType,
            (Key
"overrideArtifactName" forall kv v. (KeyValue kv, ToJSON v) => Key -> v -> kv
Data..=)
              forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
Prelude.<$> Maybe Bool
overrideArtifactName,
            (Key
"packaging" forall kv v. (KeyValue kv, ToJSON v) => Key -> v -> kv
Data..=) forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
Prelude.<$> Maybe ArtifactPackaging
packaging,
            (Key
"path" forall kv v. (KeyValue kv, ToJSON v) => Key -> v -> kv
Data..=) forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
Prelude.<$> Maybe Text
path,
            forall a. a -> Maybe a
Prelude.Just (Key
"type" forall kv v. (KeyValue kv, ToJSON v) => Key -> v -> kv
Data..= ArtifactsType
type')
          ]
      )