{-# 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.SageMaker.Types.ProcessingJob
-- 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.SageMaker.Types.ProcessingJob where

import qualified Amazonka.Core as Core
import qualified Amazonka.Core.Lens.Internal as Lens
import qualified Amazonka.Data as Data
import qualified Amazonka.Prelude as Prelude
import Amazonka.SageMaker.Types.AppSpecification
import Amazonka.SageMaker.Types.ExperimentConfig
import Amazonka.SageMaker.Types.NetworkConfig
import Amazonka.SageMaker.Types.ProcessingInput
import Amazonka.SageMaker.Types.ProcessingJobStatus
import Amazonka.SageMaker.Types.ProcessingOutputConfig
import Amazonka.SageMaker.Types.ProcessingResources
import Amazonka.SageMaker.Types.ProcessingStoppingCondition
import Amazonka.SageMaker.Types.Tag

-- | An Amazon SageMaker processing job that is used to analyze data and
-- evaluate models. For more information, see
-- <https://docs.aws.amazon.com/sagemaker/latest/dg/processing-job.html Process Data and Evaluate Models>.
--
-- /See:/ 'newProcessingJob' smart constructor.
data ProcessingJob = ProcessingJob'
  { ProcessingJob -> Maybe AppSpecification
appSpecification :: Prelude.Maybe AppSpecification,
    -- | The Amazon Resource Name (ARN) of the AutoML job associated with this
    -- processing job.
    ProcessingJob -> Maybe Text
autoMLJobArn :: Prelude.Maybe Prelude.Text,
    -- | The time the processing job was created.
    ProcessingJob -> Maybe POSIX
creationTime :: Prelude.Maybe Data.POSIX,
    -- | Sets the environment variables in the Docker container.
    ProcessingJob -> Maybe (HashMap Text Text)
environment :: Prelude.Maybe (Prelude.HashMap Prelude.Text Prelude.Text),
    -- | A string, up to one KB in size, that contains metadata from the
    -- processing container when the processing job exits.
    ProcessingJob -> Maybe Text
exitMessage :: Prelude.Maybe Prelude.Text,
    ProcessingJob -> Maybe ExperimentConfig
experimentConfig :: Prelude.Maybe ExperimentConfig,
    -- | A string, up to one KB in size, that contains the reason a processing
    -- job failed, if it failed.
    ProcessingJob -> Maybe Text
failureReason :: Prelude.Maybe Prelude.Text,
    -- | The time the processing job was last modified.
    ProcessingJob -> Maybe POSIX
lastModifiedTime :: Prelude.Maybe Data.POSIX,
    -- | The ARN of a monitoring schedule for an endpoint associated with this
    -- processing job.
    ProcessingJob -> Maybe Text
monitoringScheduleArn :: Prelude.Maybe Prelude.Text,
    ProcessingJob -> Maybe NetworkConfig
networkConfig :: Prelude.Maybe NetworkConfig,
    -- | The time that the processing job ended.
    ProcessingJob -> Maybe POSIX
processingEndTime :: Prelude.Maybe Data.POSIX,
    -- | List of input configurations for the processing job.
    ProcessingJob -> Maybe [ProcessingInput]
processingInputs :: Prelude.Maybe [ProcessingInput],
    -- | The ARN of the processing job.
    ProcessingJob -> Maybe Text
processingJobArn :: Prelude.Maybe Prelude.Text,
    -- | The name of the processing job.
    ProcessingJob -> Maybe Text
processingJobName :: Prelude.Maybe Prelude.Text,
    -- | The status of the processing job.
    ProcessingJob -> Maybe ProcessingJobStatus
processingJobStatus :: Prelude.Maybe ProcessingJobStatus,
    ProcessingJob -> Maybe ProcessingOutputConfig
processingOutputConfig :: Prelude.Maybe ProcessingOutputConfig,
    ProcessingJob -> Maybe ProcessingResources
processingResources :: Prelude.Maybe ProcessingResources,
    -- | The time that the processing job started.
    ProcessingJob -> Maybe POSIX
processingStartTime :: Prelude.Maybe Data.POSIX,
    -- | The ARN of the role used to create the processing job.
    ProcessingJob -> Maybe Text
roleArn :: Prelude.Maybe Prelude.Text,
    ProcessingJob -> Maybe ProcessingStoppingCondition
stoppingCondition :: Prelude.Maybe ProcessingStoppingCondition,
    -- | An array of key-value pairs. For more information, see
    -- <https://docs.aws.amazon.com/awsaccountbilling/latest/aboutv2/cost-alloc-tags.html#allocation-whatURL Using Cost Allocation Tags>
    -- in the /Amazon Web Services Billing and Cost Management User Guide/.
    ProcessingJob -> Maybe [Tag]
tags :: Prelude.Maybe [Tag],
    -- | The ARN of the training job associated with this processing job.
    ProcessingJob -> Maybe Text
trainingJobArn :: Prelude.Maybe Prelude.Text
  }
  deriving (ProcessingJob -> ProcessingJob -> Bool
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: ProcessingJob -> ProcessingJob -> Bool
$c/= :: ProcessingJob -> ProcessingJob -> Bool
== :: ProcessingJob -> ProcessingJob -> Bool
$c== :: ProcessingJob -> ProcessingJob -> Bool
Prelude.Eq, ReadPrec [ProcessingJob]
ReadPrec ProcessingJob
Int -> ReadS ProcessingJob
ReadS [ProcessingJob]
forall a.
(Int -> ReadS a)
-> ReadS [a] -> ReadPrec a -> ReadPrec [a] -> Read a
readListPrec :: ReadPrec [ProcessingJob]
$creadListPrec :: ReadPrec [ProcessingJob]
readPrec :: ReadPrec ProcessingJob
$creadPrec :: ReadPrec ProcessingJob
readList :: ReadS [ProcessingJob]
$creadList :: ReadS [ProcessingJob]
readsPrec :: Int -> ReadS ProcessingJob
$creadsPrec :: Int -> ReadS ProcessingJob
Prelude.Read, Int -> ProcessingJob -> ShowS
[ProcessingJob] -> ShowS
ProcessingJob -> String
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [ProcessingJob] -> ShowS
$cshowList :: [ProcessingJob] -> ShowS
show :: ProcessingJob -> String
$cshow :: ProcessingJob -> String
showsPrec :: Int -> ProcessingJob -> ShowS
$cshowsPrec :: Int -> ProcessingJob -> ShowS
Prelude.Show, forall x. Rep ProcessingJob x -> ProcessingJob
forall x. ProcessingJob -> Rep ProcessingJob x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cto :: forall x. Rep ProcessingJob x -> ProcessingJob
$cfrom :: forall x. ProcessingJob -> Rep ProcessingJob x
Prelude.Generic)

-- |
-- Create a value of 'ProcessingJob' 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:
--
-- 'appSpecification', 'processingJob_appSpecification' - Undocumented member.
--
-- 'autoMLJobArn', 'processingJob_autoMLJobArn' - The Amazon Resource Name (ARN) of the AutoML job associated with this
-- processing job.
--
-- 'creationTime', 'processingJob_creationTime' - The time the processing job was created.
--
-- 'environment', 'processingJob_environment' - Sets the environment variables in the Docker container.
--
-- 'exitMessage', 'processingJob_exitMessage' - A string, up to one KB in size, that contains metadata from the
-- processing container when the processing job exits.
--
-- 'experimentConfig', 'processingJob_experimentConfig' - Undocumented member.
--
-- 'failureReason', 'processingJob_failureReason' - A string, up to one KB in size, that contains the reason a processing
-- job failed, if it failed.
--
-- 'lastModifiedTime', 'processingJob_lastModifiedTime' - The time the processing job was last modified.
--
-- 'monitoringScheduleArn', 'processingJob_monitoringScheduleArn' - The ARN of a monitoring schedule for an endpoint associated with this
-- processing job.
--
-- 'networkConfig', 'processingJob_networkConfig' - Undocumented member.
--
-- 'processingEndTime', 'processingJob_processingEndTime' - The time that the processing job ended.
--
-- 'processingInputs', 'processingJob_processingInputs' - List of input configurations for the processing job.
--
-- 'processingJobArn', 'processingJob_processingJobArn' - The ARN of the processing job.
--
-- 'processingJobName', 'processingJob_processingJobName' - The name of the processing job.
--
-- 'processingJobStatus', 'processingJob_processingJobStatus' - The status of the processing job.
--
-- 'processingOutputConfig', 'processingJob_processingOutputConfig' - Undocumented member.
--
-- 'processingResources', 'processingJob_processingResources' - Undocumented member.
--
-- 'processingStartTime', 'processingJob_processingStartTime' - The time that the processing job started.
--
-- 'roleArn', 'processingJob_roleArn' - The ARN of the role used to create the processing job.
--
-- 'stoppingCondition', 'processingJob_stoppingCondition' - Undocumented member.
--
-- 'tags', 'processingJob_tags' - An array of key-value pairs. For more information, see
-- <https://docs.aws.amazon.com/awsaccountbilling/latest/aboutv2/cost-alloc-tags.html#allocation-whatURL Using Cost Allocation Tags>
-- in the /Amazon Web Services Billing and Cost Management User Guide/.
--
-- 'trainingJobArn', 'processingJob_trainingJobArn' - The ARN of the training job associated with this processing job.
newProcessingJob ::
  ProcessingJob
newProcessingJob :: ProcessingJob
newProcessingJob =
  ProcessingJob'
    { $sel:appSpecification:ProcessingJob' :: Maybe AppSpecification
appSpecification = forall a. Maybe a
Prelude.Nothing,
      $sel:autoMLJobArn:ProcessingJob' :: Maybe Text
autoMLJobArn = forall a. Maybe a
Prelude.Nothing,
      $sel:creationTime:ProcessingJob' :: Maybe POSIX
creationTime = forall a. Maybe a
Prelude.Nothing,
      $sel:environment:ProcessingJob' :: Maybe (HashMap Text Text)
environment = forall a. Maybe a
Prelude.Nothing,
      $sel:exitMessage:ProcessingJob' :: Maybe Text
exitMessage = forall a. Maybe a
Prelude.Nothing,
      $sel:experimentConfig:ProcessingJob' :: Maybe ExperimentConfig
experimentConfig = forall a. Maybe a
Prelude.Nothing,
      $sel:failureReason:ProcessingJob' :: Maybe Text
failureReason = forall a. Maybe a
Prelude.Nothing,
      $sel:lastModifiedTime:ProcessingJob' :: Maybe POSIX
lastModifiedTime = forall a. Maybe a
Prelude.Nothing,
      $sel:monitoringScheduleArn:ProcessingJob' :: Maybe Text
monitoringScheduleArn = forall a. Maybe a
Prelude.Nothing,
      $sel:networkConfig:ProcessingJob' :: Maybe NetworkConfig
networkConfig = forall a. Maybe a
Prelude.Nothing,
      $sel:processingEndTime:ProcessingJob' :: Maybe POSIX
processingEndTime = forall a. Maybe a
Prelude.Nothing,
      $sel:processingInputs:ProcessingJob' :: Maybe [ProcessingInput]
processingInputs = forall a. Maybe a
Prelude.Nothing,
      $sel:processingJobArn:ProcessingJob' :: Maybe Text
processingJobArn = forall a. Maybe a
Prelude.Nothing,
      $sel:processingJobName:ProcessingJob' :: Maybe Text
processingJobName = forall a. Maybe a
Prelude.Nothing,
      $sel:processingJobStatus:ProcessingJob' :: Maybe ProcessingJobStatus
processingJobStatus = forall a. Maybe a
Prelude.Nothing,
      $sel:processingOutputConfig:ProcessingJob' :: Maybe ProcessingOutputConfig
processingOutputConfig = forall a. Maybe a
Prelude.Nothing,
      $sel:processingResources:ProcessingJob' :: Maybe ProcessingResources
processingResources = forall a. Maybe a
Prelude.Nothing,
      $sel:processingStartTime:ProcessingJob' :: Maybe POSIX
processingStartTime = forall a. Maybe a
Prelude.Nothing,
      $sel:roleArn:ProcessingJob' :: Maybe Text
roleArn = forall a. Maybe a
Prelude.Nothing,
      $sel:stoppingCondition:ProcessingJob' :: Maybe ProcessingStoppingCondition
stoppingCondition = forall a. Maybe a
Prelude.Nothing,
      $sel:tags:ProcessingJob' :: Maybe [Tag]
tags = forall a. Maybe a
Prelude.Nothing,
      $sel:trainingJobArn:ProcessingJob' :: Maybe Text
trainingJobArn = forall a. Maybe a
Prelude.Nothing
    }

-- | Undocumented member.
processingJob_appSpecification :: Lens.Lens' ProcessingJob (Prelude.Maybe AppSpecification)
processingJob_appSpecification :: Lens' ProcessingJob (Maybe AppSpecification)
processingJob_appSpecification = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\ProcessingJob' {Maybe AppSpecification
appSpecification :: Maybe AppSpecification
$sel:appSpecification:ProcessingJob' :: ProcessingJob -> Maybe AppSpecification
appSpecification} -> Maybe AppSpecification
appSpecification) (\s :: ProcessingJob
s@ProcessingJob' {} Maybe AppSpecification
a -> ProcessingJob
s {$sel:appSpecification:ProcessingJob' :: Maybe AppSpecification
appSpecification = Maybe AppSpecification
a} :: ProcessingJob)

-- | The Amazon Resource Name (ARN) of the AutoML job associated with this
-- processing job.
processingJob_autoMLJobArn :: Lens.Lens' ProcessingJob (Prelude.Maybe Prelude.Text)
processingJob_autoMLJobArn :: Lens' ProcessingJob (Maybe Text)
processingJob_autoMLJobArn = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\ProcessingJob' {Maybe Text
autoMLJobArn :: Maybe Text
$sel:autoMLJobArn:ProcessingJob' :: ProcessingJob -> Maybe Text
autoMLJobArn} -> Maybe Text
autoMLJobArn) (\s :: ProcessingJob
s@ProcessingJob' {} Maybe Text
a -> ProcessingJob
s {$sel:autoMLJobArn:ProcessingJob' :: Maybe Text
autoMLJobArn = Maybe Text
a} :: ProcessingJob)

-- | The time the processing job was created.
processingJob_creationTime :: Lens.Lens' ProcessingJob (Prelude.Maybe Prelude.UTCTime)
processingJob_creationTime :: Lens' ProcessingJob (Maybe UTCTime)
processingJob_creationTime = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\ProcessingJob' {Maybe POSIX
creationTime :: Maybe POSIX
$sel:creationTime:ProcessingJob' :: ProcessingJob -> Maybe POSIX
creationTime} -> Maybe POSIX
creationTime) (\s :: ProcessingJob
s@ProcessingJob' {} Maybe POSIX
a -> ProcessingJob
s {$sel:creationTime:ProcessingJob' :: Maybe POSIX
creationTime = Maybe POSIX
a} :: ProcessingJob) 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

-- | Sets the environment variables in the Docker container.
processingJob_environment :: Lens.Lens' ProcessingJob (Prelude.Maybe (Prelude.HashMap Prelude.Text Prelude.Text))
processingJob_environment :: Lens' ProcessingJob (Maybe (HashMap Text Text))
processingJob_environment = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\ProcessingJob' {Maybe (HashMap Text Text)
environment :: Maybe (HashMap Text Text)
$sel:environment:ProcessingJob' :: ProcessingJob -> Maybe (HashMap Text Text)
environment} -> Maybe (HashMap Text Text)
environment) (\s :: ProcessingJob
s@ProcessingJob' {} Maybe (HashMap Text Text)
a -> ProcessingJob
s {$sel:environment:ProcessingJob' :: Maybe (HashMap Text Text)
environment = Maybe (HashMap Text Text)
a} :: ProcessingJob) 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

-- | A string, up to one KB in size, that contains metadata from the
-- processing container when the processing job exits.
processingJob_exitMessage :: Lens.Lens' ProcessingJob (Prelude.Maybe Prelude.Text)
processingJob_exitMessage :: Lens' ProcessingJob (Maybe Text)
processingJob_exitMessage = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\ProcessingJob' {Maybe Text
exitMessage :: Maybe Text
$sel:exitMessage:ProcessingJob' :: ProcessingJob -> Maybe Text
exitMessage} -> Maybe Text
exitMessage) (\s :: ProcessingJob
s@ProcessingJob' {} Maybe Text
a -> ProcessingJob
s {$sel:exitMessage:ProcessingJob' :: Maybe Text
exitMessage = Maybe Text
a} :: ProcessingJob)

-- | Undocumented member.
processingJob_experimentConfig :: Lens.Lens' ProcessingJob (Prelude.Maybe ExperimentConfig)
processingJob_experimentConfig :: Lens' ProcessingJob (Maybe ExperimentConfig)
processingJob_experimentConfig = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\ProcessingJob' {Maybe ExperimentConfig
experimentConfig :: Maybe ExperimentConfig
$sel:experimentConfig:ProcessingJob' :: ProcessingJob -> Maybe ExperimentConfig
experimentConfig} -> Maybe ExperimentConfig
experimentConfig) (\s :: ProcessingJob
s@ProcessingJob' {} Maybe ExperimentConfig
a -> ProcessingJob
s {$sel:experimentConfig:ProcessingJob' :: Maybe ExperimentConfig
experimentConfig = Maybe ExperimentConfig
a} :: ProcessingJob)

-- | A string, up to one KB in size, that contains the reason a processing
-- job failed, if it failed.
processingJob_failureReason :: Lens.Lens' ProcessingJob (Prelude.Maybe Prelude.Text)
processingJob_failureReason :: Lens' ProcessingJob (Maybe Text)
processingJob_failureReason = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\ProcessingJob' {Maybe Text
failureReason :: Maybe Text
$sel:failureReason:ProcessingJob' :: ProcessingJob -> Maybe Text
failureReason} -> Maybe Text
failureReason) (\s :: ProcessingJob
s@ProcessingJob' {} Maybe Text
a -> ProcessingJob
s {$sel:failureReason:ProcessingJob' :: Maybe Text
failureReason = Maybe Text
a} :: ProcessingJob)

-- | The time the processing job was last modified.
processingJob_lastModifiedTime :: Lens.Lens' ProcessingJob (Prelude.Maybe Prelude.UTCTime)
processingJob_lastModifiedTime :: Lens' ProcessingJob (Maybe UTCTime)
processingJob_lastModifiedTime = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\ProcessingJob' {Maybe POSIX
lastModifiedTime :: Maybe POSIX
$sel:lastModifiedTime:ProcessingJob' :: ProcessingJob -> Maybe POSIX
lastModifiedTime} -> Maybe POSIX
lastModifiedTime) (\s :: ProcessingJob
s@ProcessingJob' {} Maybe POSIX
a -> ProcessingJob
s {$sel:lastModifiedTime:ProcessingJob' :: Maybe POSIX
lastModifiedTime = Maybe POSIX
a} :: ProcessingJob) 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

-- | The ARN of a monitoring schedule for an endpoint associated with this
-- processing job.
processingJob_monitoringScheduleArn :: Lens.Lens' ProcessingJob (Prelude.Maybe Prelude.Text)
processingJob_monitoringScheduleArn :: Lens' ProcessingJob (Maybe Text)
processingJob_monitoringScheduleArn = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\ProcessingJob' {Maybe Text
monitoringScheduleArn :: Maybe Text
$sel:monitoringScheduleArn:ProcessingJob' :: ProcessingJob -> Maybe Text
monitoringScheduleArn} -> Maybe Text
monitoringScheduleArn) (\s :: ProcessingJob
s@ProcessingJob' {} Maybe Text
a -> ProcessingJob
s {$sel:monitoringScheduleArn:ProcessingJob' :: Maybe Text
monitoringScheduleArn = Maybe Text
a} :: ProcessingJob)

-- | Undocumented member.
processingJob_networkConfig :: Lens.Lens' ProcessingJob (Prelude.Maybe NetworkConfig)
processingJob_networkConfig :: Lens' ProcessingJob (Maybe NetworkConfig)
processingJob_networkConfig = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\ProcessingJob' {Maybe NetworkConfig
networkConfig :: Maybe NetworkConfig
$sel:networkConfig:ProcessingJob' :: ProcessingJob -> Maybe NetworkConfig
networkConfig} -> Maybe NetworkConfig
networkConfig) (\s :: ProcessingJob
s@ProcessingJob' {} Maybe NetworkConfig
a -> ProcessingJob
s {$sel:networkConfig:ProcessingJob' :: Maybe NetworkConfig
networkConfig = Maybe NetworkConfig
a} :: ProcessingJob)

-- | The time that the processing job ended.
processingJob_processingEndTime :: Lens.Lens' ProcessingJob (Prelude.Maybe Prelude.UTCTime)
processingJob_processingEndTime :: Lens' ProcessingJob (Maybe UTCTime)
processingJob_processingEndTime = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\ProcessingJob' {Maybe POSIX
processingEndTime :: Maybe POSIX
$sel:processingEndTime:ProcessingJob' :: ProcessingJob -> Maybe POSIX
processingEndTime} -> Maybe POSIX
processingEndTime) (\s :: ProcessingJob
s@ProcessingJob' {} Maybe POSIX
a -> ProcessingJob
s {$sel:processingEndTime:ProcessingJob' :: Maybe POSIX
processingEndTime = Maybe POSIX
a} :: ProcessingJob) 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

-- | List of input configurations for the processing job.
processingJob_processingInputs :: Lens.Lens' ProcessingJob (Prelude.Maybe [ProcessingInput])
processingJob_processingInputs :: Lens' ProcessingJob (Maybe [ProcessingInput])
processingJob_processingInputs = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\ProcessingJob' {Maybe [ProcessingInput]
processingInputs :: Maybe [ProcessingInput]
$sel:processingInputs:ProcessingJob' :: ProcessingJob -> Maybe [ProcessingInput]
processingInputs} -> Maybe [ProcessingInput]
processingInputs) (\s :: ProcessingJob
s@ProcessingJob' {} Maybe [ProcessingInput]
a -> ProcessingJob
s {$sel:processingInputs:ProcessingJob' :: Maybe [ProcessingInput]
processingInputs = Maybe [ProcessingInput]
a} :: ProcessingJob) 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 ARN of the processing job.
processingJob_processingJobArn :: Lens.Lens' ProcessingJob (Prelude.Maybe Prelude.Text)
processingJob_processingJobArn :: Lens' ProcessingJob (Maybe Text)
processingJob_processingJobArn = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\ProcessingJob' {Maybe Text
processingJobArn :: Maybe Text
$sel:processingJobArn:ProcessingJob' :: ProcessingJob -> Maybe Text
processingJobArn} -> Maybe Text
processingJobArn) (\s :: ProcessingJob
s@ProcessingJob' {} Maybe Text
a -> ProcessingJob
s {$sel:processingJobArn:ProcessingJob' :: Maybe Text
processingJobArn = Maybe Text
a} :: ProcessingJob)

-- | The name of the processing job.
processingJob_processingJobName :: Lens.Lens' ProcessingJob (Prelude.Maybe Prelude.Text)
processingJob_processingJobName :: Lens' ProcessingJob (Maybe Text)
processingJob_processingJobName = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\ProcessingJob' {Maybe Text
processingJobName :: Maybe Text
$sel:processingJobName:ProcessingJob' :: ProcessingJob -> Maybe Text
processingJobName} -> Maybe Text
processingJobName) (\s :: ProcessingJob
s@ProcessingJob' {} Maybe Text
a -> ProcessingJob
s {$sel:processingJobName:ProcessingJob' :: Maybe Text
processingJobName = Maybe Text
a} :: ProcessingJob)

-- | The status of the processing job.
processingJob_processingJobStatus :: Lens.Lens' ProcessingJob (Prelude.Maybe ProcessingJobStatus)
processingJob_processingJobStatus :: Lens' ProcessingJob (Maybe ProcessingJobStatus)
processingJob_processingJobStatus = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\ProcessingJob' {Maybe ProcessingJobStatus
processingJobStatus :: Maybe ProcessingJobStatus
$sel:processingJobStatus:ProcessingJob' :: ProcessingJob -> Maybe ProcessingJobStatus
processingJobStatus} -> Maybe ProcessingJobStatus
processingJobStatus) (\s :: ProcessingJob
s@ProcessingJob' {} Maybe ProcessingJobStatus
a -> ProcessingJob
s {$sel:processingJobStatus:ProcessingJob' :: Maybe ProcessingJobStatus
processingJobStatus = Maybe ProcessingJobStatus
a} :: ProcessingJob)

-- | Undocumented member.
processingJob_processingOutputConfig :: Lens.Lens' ProcessingJob (Prelude.Maybe ProcessingOutputConfig)
processingJob_processingOutputConfig :: Lens' ProcessingJob (Maybe ProcessingOutputConfig)
processingJob_processingOutputConfig = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\ProcessingJob' {Maybe ProcessingOutputConfig
processingOutputConfig :: Maybe ProcessingOutputConfig
$sel:processingOutputConfig:ProcessingJob' :: ProcessingJob -> Maybe ProcessingOutputConfig
processingOutputConfig} -> Maybe ProcessingOutputConfig
processingOutputConfig) (\s :: ProcessingJob
s@ProcessingJob' {} Maybe ProcessingOutputConfig
a -> ProcessingJob
s {$sel:processingOutputConfig:ProcessingJob' :: Maybe ProcessingOutputConfig
processingOutputConfig = Maybe ProcessingOutputConfig
a} :: ProcessingJob)

-- | Undocumented member.
processingJob_processingResources :: Lens.Lens' ProcessingJob (Prelude.Maybe ProcessingResources)
processingJob_processingResources :: Lens' ProcessingJob (Maybe ProcessingResources)
processingJob_processingResources = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\ProcessingJob' {Maybe ProcessingResources
processingResources :: Maybe ProcessingResources
$sel:processingResources:ProcessingJob' :: ProcessingJob -> Maybe ProcessingResources
processingResources} -> Maybe ProcessingResources
processingResources) (\s :: ProcessingJob
s@ProcessingJob' {} Maybe ProcessingResources
a -> ProcessingJob
s {$sel:processingResources:ProcessingJob' :: Maybe ProcessingResources
processingResources = Maybe ProcessingResources
a} :: ProcessingJob)

-- | The time that the processing job started.
processingJob_processingStartTime :: Lens.Lens' ProcessingJob (Prelude.Maybe Prelude.UTCTime)
processingJob_processingStartTime :: Lens' ProcessingJob (Maybe UTCTime)
processingJob_processingStartTime = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\ProcessingJob' {Maybe POSIX
processingStartTime :: Maybe POSIX
$sel:processingStartTime:ProcessingJob' :: ProcessingJob -> Maybe POSIX
processingStartTime} -> Maybe POSIX
processingStartTime) (\s :: ProcessingJob
s@ProcessingJob' {} Maybe POSIX
a -> ProcessingJob
s {$sel:processingStartTime:ProcessingJob' :: Maybe POSIX
processingStartTime = Maybe POSIX
a} :: ProcessingJob) 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

-- | The ARN of the role used to create the processing job.
processingJob_roleArn :: Lens.Lens' ProcessingJob (Prelude.Maybe Prelude.Text)
processingJob_roleArn :: Lens' ProcessingJob (Maybe Text)
processingJob_roleArn = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\ProcessingJob' {Maybe Text
roleArn :: Maybe Text
$sel:roleArn:ProcessingJob' :: ProcessingJob -> Maybe Text
roleArn} -> Maybe Text
roleArn) (\s :: ProcessingJob
s@ProcessingJob' {} Maybe Text
a -> ProcessingJob
s {$sel:roleArn:ProcessingJob' :: Maybe Text
roleArn = Maybe Text
a} :: ProcessingJob)

-- | Undocumented member.
processingJob_stoppingCondition :: Lens.Lens' ProcessingJob (Prelude.Maybe ProcessingStoppingCondition)
processingJob_stoppingCondition :: Lens' ProcessingJob (Maybe ProcessingStoppingCondition)
processingJob_stoppingCondition = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\ProcessingJob' {Maybe ProcessingStoppingCondition
stoppingCondition :: Maybe ProcessingStoppingCondition
$sel:stoppingCondition:ProcessingJob' :: ProcessingJob -> Maybe ProcessingStoppingCondition
stoppingCondition} -> Maybe ProcessingStoppingCondition
stoppingCondition) (\s :: ProcessingJob
s@ProcessingJob' {} Maybe ProcessingStoppingCondition
a -> ProcessingJob
s {$sel:stoppingCondition:ProcessingJob' :: Maybe ProcessingStoppingCondition
stoppingCondition = Maybe ProcessingStoppingCondition
a} :: ProcessingJob)

-- | An array of key-value pairs. For more information, see
-- <https://docs.aws.amazon.com/awsaccountbilling/latest/aboutv2/cost-alloc-tags.html#allocation-whatURL Using Cost Allocation Tags>
-- in the /Amazon Web Services Billing and Cost Management User Guide/.
processingJob_tags :: Lens.Lens' ProcessingJob (Prelude.Maybe [Tag])
processingJob_tags :: Lens' ProcessingJob (Maybe [Tag])
processingJob_tags = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\ProcessingJob' {Maybe [Tag]
tags :: Maybe [Tag]
$sel:tags:ProcessingJob' :: ProcessingJob -> Maybe [Tag]
tags} -> Maybe [Tag]
tags) (\s :: ProcessingJob
s@ProcessingJob' {} Maybe [Tag]
a -> ProcessingJob
s {$sel:tags:ProcessingJob' :: Maybe [Tag]
tags = Maybe [Tag]
a} :: ProcessingJob) 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 ARN of the training job associated with this processing job.
processingJob_trainingJobArn :: Lens.Lens' ProcessingJob (Prelude.Maybe Prelude.Text)
processingJob_trainingJobArn :: Lens' ProcessingJob (Maybe Text)
processingJob_trainingJobArn = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\ProcessingJob' {Maybe Text
trainingJobArn :: Maybe Text
$sel:trainingJobArn:ProcessingJob' :: ProcessingJob -> Maybe Text
trainingJobArn} -> Maybe Text
trainingJobArn) (\s :: ProcessingJob
s@ProcessingJob' {} Maybe Text
a -> ProcessingJob
s {$sel:trainingJobArn:ProcessingJob' :: Maybe Text
trainingJobArn = Maybe Text
a} :: ProcessingJob)

instance Data.FromJSON ProcessingJob where
  parseJSON :: Value -> Parser ProcessingJob
parseJSON =
    forall a. String -> (Object -> Parser a) -> Value -> Parser a
Data.withObject
      String
"ProcessingJob"
      ( \Object
x ->
          Maybe AppSpecification
-> Maybe Text
-> Maybe POSIX
-> Maybe (HashMap Text Text)
-> Maybe Text
-> Maybe ExperimentConfig
-> Maybe Text
-> Maybe POSIX
-> Maybe Text
-> Maybe NetworkConfig
-> Maybe POSIX
-> Maybe [ProcessingInput]
-> Maybe Text
-> Maybe Text
-> Maybe ProcessingJobStatus
-> Maybe ProcessingOutputConfig
-> Maybe ProcessingResources
-> Maybe POSIX
-> Maybe Text
-> Maybe ProcessingStoppingCondition
-> Maybe [Tag]
-> Maybe Text
-> ProcessingJob
ProcessingJob'
            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
"AppSpecification")
            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
"AutoMLJobArn")
            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
"CreationTime")
            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 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
"ExitMessage")
            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
"ExperimentConfig")
            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
"FailureReason")
            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
"LastModifiedTime")
            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
"MonitoringScheduleArn")
            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
"NetworkConfig")
            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
"ProcessingEndTime")
            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
"ProcessingInputs"
                            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
"ProcessingJobArn")
            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
"ProcessingJobName")
            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
"ProcessingJobStatus")
            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
"ProcessingOutputConfig")
            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
"ProcessingResources")
            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
"ProcessingStartTime")
            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
"RoleArn")
            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
"StoppingCondition")
            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
"Tags" 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
"TrainingJobArn")
      )

instance Prelude.Hashable ProcessingJob where
  hashWithSalt :: Int -> ProcessingJob -> Int
hashWithSalt Int
_salt ProcessingJob' {Maybe [ProcessingInput]
Maybe [Tag]
Maybe Text
Maybe (HashMap Text Text)
Maybe POSIX
Maybe AppSpecification
Maybe ExperimentConfig
Maybe ProcessingJobStatus
Maybe ProcessingResources
Maybe ProcessingOutputConfig
Maybe ProcessingStoppingCondition
Maybe NetworkConfig
trainingJobArn :: Maybe Text
tags :: Maybe [Tag]
stoppingCondition :: Maybe ProcessingStoppingCondition
roleArn :: Maybe Text
processingStartTime :: Maybe POSIX
processingResources :: Maybe ProcessingResources
processingOutputConfig :: Maybe ProcessingOutputConfig
processingJobStatus :: Maybe ProcessingJobStatus
processingJobName :: Maybe Text
processingJobArn :: Maybe Text
processingInputs :: Maybe [ProcessingInput]
processingEndTime :: Maybe POSIX
networkConfig :: Maybe NetworkConfig
monitoringScheduleArn :: Maybe Text
lastModifiedTime :: Maybe POSIX
failureReason :: Maybe Text
experimentConfig :: Maybe ExperimentConfig
exitMessage :: Maybe Text
environment :: Maybe (HashMap Text Text)
creationTime :: Maybe POSIX
autoMLJobArn :: Maybe Text
appSpecification :: Maybe AppSpecification
$sel:trainingJobArn:ProcessingJob' :: ProcessingJob -> Maybe Text
$sel:tags:ProcessingJob' :: ProcessingJob -> Maybe [Tag]
$sel:stoppingCondition:ProcessingJob' :: ProcessingJob -> Maybe ProcessingStoppingCondition
$sel:roleArn:ProcessingJob' :: ProcessingJob -> Maybe Text
$sel:processingStartTime:ProcessingJob' :: ProcessingJob -> Maybe POSIX
$sel:processingResources:ProcessingJob' :: ProcessingJob -> Maybe ProcessingResources
$sel:processingOutputConfig:ProcessingJob' :: ProcessingJob -> Maybe ProcessingOutputConfig
$sel:processingJobStatus:ProcessingJob' :: ProcessingJob -> Maybe ProcessingJobStatus
$sel:processingJobName:ProcessingJob' :: ProcessingJob -> Maybe Text
$sel:processingJobArn:ProcessingJob' :: ProcessingJob -> Maybe Text
$sel:processingInputs:ProcessingJob' :: ProcessingJob -> Maybe [ProcessingInput]
$sel:processingEndTime:ProcessingJob' :: ProcessingJob -> Maybe POSIX
$sel:networkConfig:ProcessingJob' :: ProcessingJob -> Maybe NetworkConfig
$sel:monitoringScheduleArn:ProcessingJob' :: ProcessingJob -> Maybe Text
$sel:lastModifiedTime:ProcessingJob' :: ProcessingJob -> Maybe POSIX
$sel:failureReason:ProcessingJob' :: ProcessingJob -> Maybe Text
$sel:experimentConfig:ProcessingJob' :: ProcessingJob -> Maybe ExperimentConfig
$sel:exitMessage:ProcessingJob' :: ProcessingJob -> Maybe Text
$sel:environment:ProcessingJob' :: ProcessingJob -> Maybe (HashMap Text Text)
$sel:creationTime:ProcessingJob' :: ProcessingJob -> Maybe POSIX
$sel:autoMLJobArn:ProcessingJob' :: ProcessingJob -> Maybe Text
$sel:appSpecification:ProcessingJob' :: ProcessingJob -> Maybe AppSpecification
..} =
    Int
_salt
      forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Maybe AppSpecification
appSpecification
      forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Maybe Text
autoMLJobArn
      forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Maybe POSIX
creationTime
      forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Maybe (HashMap Text Text)
environment
      forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Maybe Text
exitMessage
      forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Maybe ExperimentConfig
experimentConfig
      forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Maybe Text
failureReason
      forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Maybe POSIX
lastModifiedTime
      forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Maybe Text
monitoringScheduleArn
      forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Maybe NetworkConfig
networkConfig
      forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Maybe POSIX
processingEndTime
      forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Maybe [ProcessingInput]
processingInputs
      forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Maybe Text
processingJobArn
      forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Maybe Text
processingJobName
      forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Maybe ProcessingJobStatus
processingJobStatus
      forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Maybe ProcessingOutputConfig
processingOutputConfig
      forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Maybe ProcessingResources
processingResources
      forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Maybe POSIX
processingStartTime
      forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Maybe Text
roleArn
      forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Maybe ProcessingStoppingCondition
stoppingCondition
      forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Maybe [Tag]
tags
      forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Maybe Text
trainingJobArn

instance Prelude.NFData ProcessingJob where
  rnf :: ProcessingJob -> ()
rnf ProcessingJob' {Maybe [ProcessingInput]
Maybe [Tag]
Maybe Text
Maybe (HashMap Text Text)
Maybe POSIX
Maybe AppSpecification
Maybe ExperimentConfig
Maybe ProcessingJobStatus
Maybe ProcessingResources
Maybe ProcessingOutputConfig
Maybe ProcessingStoppingCondition
Maybe NetworkConfig
trainingJobArn :: Maybe Text
tags :: Maybe [Tag]
stoppingCondition :: Maybe ProcessingStoppingCondition
roleArn :: Maybe Text
processingStartTime :: Maybe POSIX
processingResources :: Maybe ProcessingResources
processingOutputConfig :: Maybe ProcessingOutputConfig
processingJobStatus :: Maybe ProcessingJobStatus
processingJobName :: Maybe Text
processingJobArn :: Maybe Text
processingInputs :: Maybe [ProcessingInput]
processingEndTime :: Maybe POSIX
networkConfig :: Maybe NetworkConfig
monitoringScheduleArn :: Maybe Text
lastModifiedTime :: Maybe POSIX
failureReason :: Maybe Text
experimentConfig :: Maybe ExperimentConfig
exitMessage :: Maybe Text
environment :: Maybe (HashMap Text Text)
creationTime :: Maybe POSIX
autoMLJobArn :: Maybe Text
appSpecification :: Maybe AppSpecification
$sel:trainingJobArn:ProcessingJob' :: ProcessingJob -> Maybe Text
$sel:tags:ProcessingJob' :: ProcessingJob -> Maybe [Tag]
$sel:stoppingCondition:ProcessingJob' :: ProcessingJob -> Maybe ProcessingStoppingCondition
$sel:roleArn:ProcessingJob' :: ProcessingJob -> Maybe Text
$sel:processingStartTime:ProcessingJob' :: ProcessingJob -> Maybe POSIX
$sel:processingResources:ProcessingJob' :: ProcessingJob -> Maybe ProcessingResources
$sel:processingOutputConfig:ProcessingJob' :: ProcessingJob -> Maybe ProcessingOutputConfig
$sel:processingJobStatus:ProcessingJob' :: ProcessingJob -> Maybe ProcessingJobStatus
$sel:processingJobName:ProcessingJob' :: ProcessingJob -> Maybe Text
$sel:processingJobArn:ProcessingJob' :: ProcessingJob -> Maybe Text
$sel:processingInputs:ProcessingJob' :: ProcessingJob -> Maybe [ProcessingInput]
$sel:processingEndTime:ProcessingJob' :: ProcessingJob -> Maybe POSIX
$sel:networkConfig:ProcessingJob' :: ProcessingJob -> Maybe NetworkConfig
$sel:monitoringScheduleArn:ProcessingJob' :: ProcessingJob -> Maybe Text
$sel:lastModifiedTime:ProcessingJob' :: ProcessingJob -> Maybe POSIX
$sel:failureReason:ProcessingJob' :: ProcessingJob -> Maybe Text
$sel:experimentConfig:ProcessingJob' :: ProcessingJob -> Maybe ExperimentConfig
$sel:exitMessage:ProcessingJob' :: ProcessingJob -> Maybe Text
$sel:environment:ProcessingJob' :: ProcessingJob -> Maybe (HashMap Text Text)
$sel:creationTime:ProcessingJob' :: ProcessingJob -> Maybe POSIX
$sel:autoMLJobArn:ProcessingJob' :: ProcessingJob -> Maybe Text
$sel:appSpecification:ProcessingJob' :: ProcessingJob -> Maybe AppSpecification
..} =
    forall a. NFData a => a -> ()
Prelude.rnf Maybe AppSpecification
appSpecification
      seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf Maybe Text
autoMLJobArn
      seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf Maybe POSIX
creationTime
      seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf Maybe (HashMap Text Text)
environment
      seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf Maybe Text
exitMessage
      seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf Maybe ExperimentConfig
experimentConfig
      seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf Maybe Text
failureReason
      seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf Maybe POSIX
lastModifiedTime
      seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf Maybe Text
monitoringScheduleArn
      seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf Maybe NetworkConfig
networkConfig
      seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf Maybe POSIX
processingEndTime
      seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf Maybe [ProcessingInput]
processingInputs
      seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf Maybe Text
processingJobArn
      seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf Maybe Text
processingJobName
      seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf Maybe ProcessingJobStatus
processingJobStatus
      seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf Maybe ProcessingOutputConfig
processingOutputConfig
      seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf Maybe ProcessingResources
processingResources
      seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf Maybe POSIX
processingStartTime
      seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf Maybe Text
roleArn
      seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf Maybe ProcessingStoppingCondition
stoppingCondition
      seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf Maybe [Tag]
tags
      seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf Maybe Text
trainingJobArn