{-# 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.CodePipeline.Types.JobData
-- 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.CodePipeline.Types.JobData where

import Amazonka.CodePipeline.Types.AWSSessionCredentials
import Amazonka.CodePipeline.Types.ActionConfiguration
import Amazonka.CodePipeline.Types.ActionTypeId
import Amazonka.CodePipeline.Types.Artifact
import Amazonka.CodePipeline.Types.EncryptionKey
import Amazonka.CodePipeline.Types.PipelineContext
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

-- | Represents other information about a job required for a job worker to
-- complete the job.
--
-- /See:/ 'newJobData' smart constructor.
data JobData = JobData'
  { -- | Represents information about an action configuration.
    JobData -> Maybe ActionConfiguration
actionConfiguration :: Prelude.Maybe ActionConfiguration,
    -- | Represents information about an action type.
    JobData -> Maybe ActionTypeId
actionTypeId :: Prelude.Maybe ActionTypeId,
    -- | Represents an AWS session credentials object. These credentials are
    -- temporary credentials that are issued by AWS Secure Token Service (STS).
    -- They can be used to access input and output artifacts in the S3 bucket
    -- used to store artifacts for the pipeline in AWS CodePipeline.
    JobData -> Maybe (Sensitive AWSSessionCredentials)
artifactCredentials :: Prelude.Maybe (Data.Sensitive AWSSessionCredentials),
    -- | A system-generated token, such as a AWS CodeDeploy deployment ID,
    -- required by a job to continue the job asynchronously.
    JobData -> Maybe Text
continuationToken :: Prelude.Maybe Prelude.Text,
    -- | Represents information about the key used to encrypt data in the
    -- artifact store, such as an AWS Key Management Service (AWS KMS) key.
    JobData -> Maybe EncryptionKey
encryptionKey :: Prelude.Maybe EncryptionKey,
    -- | The artifact supplied to the job.
    JobData -> Maybe [Artifact]
inputArtifacts :: Prelude.Maybe [Artifact],
    -- | The output of the job.
    JobData -> Maybe [Artifact]
outputArtifacts :: Prelude.Maybe [Artifact],
    -- | Represents information about a pipeline to a job worker.
    --
    -- Includes @pipelineArn@ and @pipelineExecutionId@ for custom jobs.
    JobData -> Maybe PipelineContext
pipelineContext :: Prelude.Maybe PipelineContext
  }
  deriving (JobData -> JobData -> Bool
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: JobData -> JobData -> Bool
$c/= :: JobData -> JobData -> Bool
== :: JobData -> JobData -> Bool
$c== :: JobData -> JobData -> Bool
Prelude.Eq, Int -> JobData -> ShowS
[JobData] -> ShowS
JobData -> String
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [JobData] -> ShowS
$cshowList :: [JobData] -> ShowS
show :: JobData -> String
$cshow :: JobData -> String
showsPrec :: Int -> JobData -> ShowS
$cshowsPrec :: Int -> JobData -> ShowS
Prelude.Show, forall x. Rep JobData x -> JobData
forall x. JobData -> Rep JobData x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cto :: forall x. Rep JobData x -> JobData
$cfrom :: forall x. JobData -> Rep JobData x
Prelude.Generic)

-- |
-- Create a value of 'JobData' 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:
--
-- 'actionConfiguration', 'jobData_actionConfiguration' - Represents information about an action configuration.
--
-- 'actionTypeId', 'jobData_actionTypeId' - Represents information about an action type.
--
-- 'artifactCredentials', 'jobData_artifactCredentials' - Represents an AWS session credentials object. These credentials are
-- temporary credentials that are issued by AWS Secure Token Service (STS).
-- They can be used to access input and output artifacts in the S3 bucket
-- used to store artifacts for the pipeline in AWS CodePipeline.
--
-- 'continuationToken', 'jobData_continuationToken' - A system-generated token, such as a AWS CodeDeploy deployment ID,
-- required by a job to continue the job asynchronously.
--
-- 'encryptionKey', 'jobData_encryptionKey' - Represents information about the key used to encrypt data in the
-- artifact store, such as an AWS Key Management Service (AWS KMS) key.
--
-- 'inputArtifacts', 'jobData_inputArtifacts' - The artifact supplied to the job.
--
-- 'outputArtifacts', 'jobData_outputArtifacts' - The output of the job.
--
-- 'pipelineContext', 'jobData_pipelineContext' - Represents information about a pipeline to a job worker.
--
-- Includes @pipelineArn@ and @pipelineExecutionId@ for custom jobs.
newJobData ::
  JobData
newJobData :: JobData
newJobData =
  JobData'
    { $sel:actionConfiguration:JobData' :: Maybe ActionConfiguration
actionConfiguration = forall a. Maybe a
Prelude.Nothing,
      $sel:actionTypeId:JobData' :: Maybe ActionTypeId
actionTypeId = forall a. Maybe a
Prelude.Nothing,
      $sel:artifactCredentials:JobData' :: Maybe (Sensitive AWSSessionCredentials)
artifactCredentials = forall a. Maybe a
Prelude.Nothing,
      $sel:continuationToken:JobData' :: Maybe Text
continuationToken = forall a. Maybe a
Prelude.Nothing,
      $sel:encryptionKey:JobData' :: Maybe EncryptionKey
encryptionKey = forall a. Maybe a
Prelude.Nothing,
      $sel:inputArtifacts:JobData' :: Maybe [Artifact]
inputArtifacts = forall a. Maybe a
Prelude.Nothing,
      $sel:outputArtifacts:JobData' :: Maybe [Artifact]
outputArtifacts = forall a. Maybe a
Prelude.Nothing,
      $sel:pipelineContext:JobData' :: Maybe PipelineContext
pipelineContext = forall a. Maybe a
Prelude.Nothing
    }

-- | Represents information about an action configuration.
jobData_actionConfiguration :: Lens.Lens' JobData (Prelude.Maybe ActionConfiguration)
jobData_actionConfiguration :: Lens' JobData (Maybe ActionConfiguration)
jobData_actionConfiguration = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\JobData' {Maybe ActionConfiguration
actionConfiguration :: Maybe ActionConfiguration
$sel:actionConfiguration:JobData' :: JobData -> Maybe ActionConfiguration
actionConfiguration} -> Maybe ActionConfiguration
actionConfiguration) (\s :: JobData
s@JobData' {} Maybe ActionConfiguration
a -> JobData
s {$sel:actionConfiguration:JobData' :: Maybe ActionConfiguration
actionConfiguration = Maybe ActionConfiguration
a} :: JobData)

-- | Represents information about an action type.
jobData_actionTypeId :: Lens.Lens' JobData (Prelude.Maybe ActionTypeId)
jobData_actionTypeId :: Lens' JobData (Maybe ActionTypeId)
jobData_actionTypeId = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\JobData' {Maybe ActionTypeId
actionTypeId :: Maybe ActionTypeId
$sel:actionTypeId:JobData' :: JobData -> Maybe ActionTypeId
actionTypeId} -> Maybe ActionTypeId
actionTypeId) (\s :: JobData
s@JobData' {} Maybe ActionTypeId
a -> JobData
s {$sel:actionTypeId:JobData' :: Maybe ActionTypeId
actionTypeId = Maybe ActionTypeId
a} :: JobData)

-- | Represents an AWS session credentials object. These credentials are
-- temporary credentials that are issued by AWS Secure Token Service (STS).
-- They can be used to access input and output artifacts in the S3 bucket
-- used to store artifacts for the pipeline in AWS CodePipeline.
jobData_artifactCredentials :: Lens.Lens' JobData (Prelude.Maybe AWSSessionCredentials)
jobData_artifactCredentials :: Lens' JobData (Maybe AWSSessionCredentials)
jobData_artifactCredentials = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\JobData' {Maybe (Sensitive AWSSessionCredentials)
artifactCredentials :: Maybe (Sensitive AWSSessionCredentials)
$sel:artifactCredentials:JobData' :: JobData -> Maybe (Sensitive AWSSessionCredentials)
artifactCredentials} -> Maybe (Sensitive AWSSessionCredentials)
artifactCredentials) (\s :: JobData
s@JobData' {} Maybe (Sensitive AWSSessionCredentials)
a -> JobData
s {$sel:artifactCredentials:JobData' :: Maybe (Sensitive AWSSessionCredentials)
artifactCredentials = Maybe (Sensitive AWSSessionCredentials)
a} :: JobData) 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. Iso' (Sensitive a) a
Data._Sensitive

-- | A system-generated token, such as a AWS CodeDeploy deployment ID,
-- required by a job to continue the job asynchronously.
jobData_continuationToken :: Lens.Lens' JobData (Prelude.Maybe Prelude.Text)
jobData_continuationToken :: Lens' JobData (Maybe Text)
jobData_continuationToken = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\JobData' {Maybe Text
continuationToken :: Maybe Text
$sel:continuationToken:JobData' :: JobData -> Maybe Text
continuationToken} -> Maybe Text
continuationToken) (\s :: JobData
s@JobData' {} Maybe Text
a -> JobData
s {$sel:continuationToken:JobData' :: Maybe Text
continuationToken = Maybe Text
a} :: JobData)

-- | Represents information about the key used to encrypt data in the
-- artifact store, such as an AWS Key Management Service (AWS KMS) key.
jobData_encryptionKey :: Lens.Lens' JobData (Prelude.Maybe EncryptionKey)
jobData_encryptionKey :: Lens' JobData (Maybe EncryptionKey)
jobData_encryptionKey = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\JobData' {Maybe EncryptionKey
encryptionKey :: Maybe EncryptionKey
$sel:encryptionKey:JobData' :: JobData -> Maybe EncryptionKey
encryptionKey} -> Maybe EncryptionKey
encryptionKey) (\s :: JobData
s@JobData' {} Maybe EncryptionKey
a -> JobData
s {$sel:encryptionKey:JobData' :: Maybe EncryptionKey
encryptionKey = Maybe EncryptionKey
a} :: JobData)

-- | The artifact supplied to the job.
jobData_inputArtifacts :: Lens.Lens' JobData (Prelude.Maybe [Artifact])
jobData_inputArtifacts :: Lens' JobData (Maybe [Artifact])
jobData_inputArtifacts = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\JobData' {Maybe [Artifact]
inputArtifacts :: Maybe [Artifact]
$sel:inputArtifacts:JobData' :: JobData -> Maybe [Artifact]
inputArtifacts} -> Maybe [Artifact]
inputArtifacts) (\s :: JobData
s@JobData' {} Maybe [Artifact]
a -> JobData
s {$sel:inputArtifacts:JobData' :: Maybe [Artifact]
inputArtifacts = Maybe [Artifact]
a} :: JobData) 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 output of the job.
jobData_outputArtifacts :: Lens.Lens' JobData (Prelude.Maybe [Artifact])
jobData_outputArtifacts :: Lens' JobData (Maybe [Artifact])
jobData_outputArtifacts = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\JobData' {Maybe [Artifact]
outputArtifacts :: Maybe [Artifact]
$sel:outputArtifacts:JobData' :: JobData -> Maybe [Artifact]
outputArtifacts} -> Maybe [Artifact]
outputArtifacts) (\s :: JobData
s@JobData' {} Maybe [Artifact]
a -> JobData
s {$sel:outputArtifacts:JobData' :: Maybe [Artifact]
outputArtifacts = Maybe [Artifact]
a} :: JobData) 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

-- | Represents information about a pipeline to a job worker.
--
-- Includes @pipelineArn@ and @pipelineExecutionId@ for custom jobs.
jobData_pipelineContext :: Lens.Lens' JobData (Prelude.Maybe PipelineContext)
jobData_pipelineContext :: Lens' JobData (Maybe PipelineContext)
jobData_pipelineContext = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\JobData' {Maybe PipelineContext
pipelineContext :: Maybe PipelineContext
$sel:pipelineContext:JobData' :: JobData -> Maybe PipelineContext
pipelineContext} -> Maybe PipelineContext
pipelineContext) (\s :: JobData
s@JobData' {} Maybe PipelineContext
a -> JobData
s {$sel:pipelineContext:JobData' :: Maybe PipelineContext
pipelineContext = Maybe PipelineContext
a} :: JobData)

instance Data.FromJSON JobData where
  parseJSON :: Value -> Parser JobData
parseJSON =
    forall a. String -> (Object -> Parser a) -> Value -> Parser a
Data.withObject
      String
"JobData"
      ( \Object
x ->
          Maybe ActionConfiguration
-> Maybe ActionTypeId
-> Maybe (Sensitive AWSSessionCredentials)
-> Maybe Text
-> Maybe EncryptionKey
-> Maybe [Artifact]
-> Maybe [Artifact]
-> Maybe PipelineContext
-> JobData
JobData'
            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
"actionConfiguration")
            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
"actionTypeId")
            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
"artifactCredentials")
            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
"continuationToken")
            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
"inputArtifacts" 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
"outputArtifacts"
                            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
"pipelineContext")
      )

instance Prelude.Hashable JobData where
  hashWithSalt :: Int -> JobData -> Int
hashWithSalt Int
_salt JobData' {Maybe [Artifact]
Maybe Text
Maybe (Sensitive AWSSessionCredentials)
Maybe ActionConfiguration
Maybe ActionTypeId
Maybe EncryptionKey
Maybe PipelineContext
pipelineContext :: Maybe PipelineContext
outputArtifacts :: Maybe [Artifact]
inputArtifacts :: Maybe [Artifact]
encryptionKey :: Maybe EncryptionKey
continuationToken :: Maybe Text
artifactCredentials :: Maybe (Sensitive AWSSessionCredentials)
actionTypeId :: Maybe ActionTypeId
actionConfiguration :: Maybe ActionConfiguration
$sel:pipelineContext:JobData' :: JobData -> Maybe PipelineContext
$sel:outputArtifacts:JobData' :: JobData -> Maybe [Artifact]
$sel:inputArtifacts:JobData' :: JobData -> Maybe [Artifact]
$sel:encryptionKey:JobData' :: JobData -> Maybe EncryptionKey
$sel:continuationToken:JobData' :: JobData -> Maybe Text
$sel:artifactCredentials:JobData' :: JobData -> Maybe (Sensitive AWSSessionCredentials)
$sel:actionTypeId:JobData' :: JobData -> Maybe ActionTypeId
$sel:actionConfiguration:JobData' :: JobData -> Maybe ActionConfiguration
..} =
    Int
_salt
      forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Maybe ActionConfiguration
actionConfiguration
      forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Maybe ActionTypeId
actionTypeId
      forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Maybe (Sensitive AWSSessionCredentials)
artifactCredentials
      forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Maybe Text
continuationToken
      forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Maybe EncryptionKey
encryptionKey
      forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Maybe [Artifact]
inputArtifacts
      forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Maybe [Artifact]
outputArtifacts
      forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Maybe PipelineContext
pipelineContext

instance Prelude.NFData JobData where
  rnf :: JobData -> ()
rnf JobData' {Maybe [Artifact]
Maybe Text
Maybe (Sensitive AWSSessionCredentials)
Maybe ActionConfiguration
Maybe ActionTypeId
Maybe EncryptionKey
Maybe PipelineContext
pipelineContext :: Maybe PipelineContext
outputArtifacts :: Maybe [Artifact]
inputArtifacts :: Maybe [Artifact]
encryptionKey :: Maybe EncryptionKey
continuationToken :: Maybe Text
artifactCredentials :: Maybe (Sensitive AWSSessionCredentials)
actionTypeId :: Maybe ActionTypeId
actionConfiguration :: Maybe ActionConfiguration
$sel:pipelineContext:JobData' :: JobData -> Maybe PipelineContext
$sel:outputArtifacts:JobData' :: JobData -> Maybe [Artifact]
$sel:inputArtifacts:JobData' :: JobData -> Maybe [Artifact]
$sel:encryptionKey:JobData' :: JobData -> Maybe EncryptionKey
$sel:continuationToken:JobData' :: JobData -> Maybe Text
$sel:artifactCredentials:JobData' :: JobData -> Maybe (Sensitive AWSSessionCredentials)
$sel:actionTypeId:JobData' :: JobData -> Maybe ActionTypeId
$sel:actionConfiguration:JobData' :: JobData -> Maybe ActionConfiguration
..} =
    forall a. NFData a => a -> ()
Prelude.rnf Maybe ActionConfiguration
actionConfiguration
      seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf Maybe ActionTypeId
actionTypeId
      seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf Maybe (Sensitive AWSSessionCredentials)
artifactCredentials
      seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf Maybe Text
continuationToken
      seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf Maybe EncryptionKey
encryptionKey
      seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf Maybe [Artifact]
inputArtifacts
      seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf Maybe [Artifact]
outputArtifacts
      seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf Maybe PipelineContext
pipelineContext