{-# LANGUAGE DeriveGeneric #-}
{-# LANGUAGE DuplicateRecordFields #-}
{-# LANGUAGE NamedFieldPuns #-}
{-# LANGUAGE OverloadedStrings #-}
{-# LANGUAGE RecordWildCards #-}
{-# LANGUAGE StrictData #-}
{-# LANGUAGE TypeFamilies #-}
{-# LANGUAGE NoImplicitPrelude #-}
{-# OPTIONS_GHC -fno-warn-unused-binds #-}
{-# 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.DescribeProcessingJob
-- Copyright   : (c) 2013-2023 Brendan Hay
-- License     : Mozilla Public License, v. 2.0.
-- Maintainer  : Brendan Hay
-- Stability   : auto-generated
-- Portability : non-portable (GHC extensions)
--
-- Returns a description of a processing job.
module Amazonka.SageMaker.DescribeProcessingJob
  ( -- * Creating a Request
    DescribeProcessingJob (..),
    newDescribeProcessingJob,

    -- * Request Lenses
    describeProcessingJob_processingJobName,

    -- * Destructuring the Response
    DescribeProcessingJobResponse (..),
    newDescribeProcessingJobResponse,

    -- * Response Lenses
    describeProcessingJobResponse_autoMLJobArn,
    describeProcessingJobResponse_environment,
    describeProcessingJobResponse_exitMessage,
    describeProcessingJobResponse_experimentConfig,
    describeProcessingJobResponse_failureReason,
    describeProcessingJobResponse_lastModifiedTime,
    describeProcessingJobResponse_monitoringScheduleArn,
    describeProcessingJobResponse_networkConfig,
    describeProcessingJobResponse_processingEndTime,
    describeProcessingJobResponse_processingInputs,
    describeProcessingJobResponse_processingOutputConfig,
    describeProcessingJobResponse_processingStartTime,
    describeProcessingJobResponse_roleArn,
    describeProcessingJobResponse_stoppingCondition,
    describeProcessingJobResponse_trainingJobArn,
    describeProcessingJobResponse_httpStatus,
    describeProcessingJobResponse_processingJobName,
    describeProcessingJobResponse_processingResources,
    describeProcessingJobResponse_appSpecification,
    describeProcessingJobResponse_processingJobArn,
    describeProcessingJobResponse_processingJobStatus,
    describeProcessingJobResponse_creationTime,
  )
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 qualified Amazonka.Request as Request
import qualified Amazonka.Response as Response
import Amazonka.SageMaker.Types

-- | /See:/ 'newDescribeProcessingJob' smart constructor.
data DescribeProcessingJob = DescribeProcessingJob'
  { -- | The name of the processing job. The name must be unique within an Amazon
    -- Web Services Region in the Amazon Web Services account.
    DescribeProcessingJob -> Text
processingJobName :: Prelude.Text
  }
  deriving (DescribeProcessingJob -> DescribeProcessingJob -> Bool
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: DescribeProcessingJob -> DescribeProcessingJob -> Bool
$c/= :: DescribeProcessingJob -> DescribeProcessingJob -> Bool
== :: DescribeProcessingJob -> DescribeProcessingJob -> Bool
$c== :: DescribeProcessingJob -> DescribeProcessingJob -> Bool
Prelude.Eq, ReadPrec [DescribeProcessingJob]
ReadPrec DescribeProcessingJob
Int -> ReadS DescribeProcessingJob
ReadS [DescribeProcessingJob]
forall a.
(Int -> ReadS a)
-> ReadS [a] -> ReadPrec a -> ReadPrec [a] -> Read a
readListPrec :: ReadPrec [DescribeProcessingJob]
$creadListPrec :: ReadPrec [DescribeProcessingJob]
readPrec :: ReadPrec DescribeProcessingJob
$creadPrec :: ReadPrec DescribeProcessingJob
readList :: ReadS [DescribeProcessingJob]
$creadList :: ReadS [DescribeProcessingJob]
readsPrec :: Int -> ReadS DescribeProcessingJob
$creadsPrec :: Int -> ReadS DescribeProcessingJob
Prelude.Read, Int -> DescribeProcessingJob -> ShowS
[DescribeProcessingJob] -> ShowS
DescribeProcessingJob -> String
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [DescribeProcessingJob] -> ShowS
$cshowList :: [DescribeProcessingJob] -> ShowS
show :: DescribeProcessingJob -> String
$cshow :: DescribeProcessingJob -> String
showsPrec :: Int -> DescribeProcessingJob -> ShowS
$cshowsPrec :: Int -> DescribeProcessingJob -> ShowS
Prelude.Show, forall x. Rep DescribeProcessingJob x -> DescribeProcessingJob
forall x. DescribeProcessingJob -> Rep DescribeProcessingJob x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cto :: forall x. Rep DescribeProcessingJob x -> DescribeProcessingJob
$cfrom :: forall x. DescribeProcessingJob -> Rep DescribeProcessingJob x
Prelude.Generic)

-- |
-- Create a value of 'DescribeProcessingJob' 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:
--
-- 'processingJobName', 'describeProcessingJob_processingJobName' - The name of the processing job. The name must be unique within an Amazon
-- Web Services Region in the Amazon Web Services account.
newDescribeProcessingJob ::
  -- | 'processingJobName'
  Prelude.Text ->
  DescribeProcessingJob
newDescribeProcessingJob :: Text -> DescribeProcessingJob
newDescribeProcessingJob Text
pProcessingJobName_ =
  DescribeProcessingJob'
    { $sel:processingJobName:DescribeProcessingJob' :: Text
processingJobName =
        Text
pProcessingJobName_
    }

-- | The name of the processing job. The name must be unique within an Amazon
-- Web Services Region in the Amazon Web Services account.
describeProcessingJob_processingJobName :: Lens.Lens' DescribeProcessingJob Prelude.Text
describeProcessingJob_processingJobName :: Lens' DescribeProcessingJob Text
describeProcessingJob_processingJobName = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\DescribeProcessingJob' {Text
processingJobName :: Text
$sel:processingJobName:DescribeProcessingJob' :: DescribeProcessingJob -> Text
processingJobName} -> Text
processingJobName) (\s :: DescribeProcessingJob
s@DescribeProcessingJob' {} Text
a -> DescribeProcessingJob
s {$sel:processingJobName:DescribeProcessingJob' :: Text
processingJobName = Text
a} :: DescribeProcessingJob)

instance Core.AWSRequest DescribeProcessingJob where
  type
    AWSResponse DescribeProcessingJob =
      DescribeProcessingJobResponse
  request :: (Service -> Service)
-> DescribeProcessingJob -> Request DescribeProcessingJob
request Service -> Service
overrides =
    forall a. (ToRequest a, ToJSON a) => Service -> a -> Request a
Request.postJSON (Service -> Service
overrides Service
defaultService)
  response :: forall (m :: * -> *).
MonadResource m =>
(ByteStringLazy -> IO ByteStringLazy)
-> Service
-> Proxy DescribeProcessingJob
-> ClientResponse ClientBody
-> m (Either
        Error (ClientResponse (AWSResponse DescribeProcessingJob)))
response =
    forall (m :: * -> *) a.
MonadResource m =>
(Int -> ResponseHeaders -> Object -> Either String (AWSResponse a))
-> (ByteStringLazy -> IO ByteStringLazy)
-> Service
-> Proxy a
-> ClientResponse ClientBody
-> m (Either Error (ClientResponse (AWSResponse a)))
Response.receiveJSON
      ( \Int
s ResponseHeaders
h Object
x ->
          Maybe Text
-> Maybe (HashMap Text Text)
-> Maybe Text
-> Maybe ExperimentConfig
-> Maybe Text
-> Maybe POSIX
-> Maybe Text
-> Maybe NetworkConfig
-> Maybe POSIX
-> Maybe [ProcessingInput]
-> Maybe ProcessingOutputConfig
-> Maybe POSIX
-> Maybe Text
-> Maybe ProcessingStoppingCondition
-> Maybe Text
-> Int
-> Text
-> ProcessingResources
-> AppSpecification
-> Text
-> ProcessingJobStatus
-> POSIX
-> DescribeProcessingJobResponse
DescribeProcessingJobResponse'
            forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
Prelude.<$> (Object
x forall a. FromJSON a => Object -> Key -> Either String (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 -> Either String (Maybe a)
Data..?> Key
"Environment" forall (f :: * -> *) a. Functor f => f (Maybe a) -> a -> f a
Core..!@ 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 -> Either String (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 -> Either String (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 -> Either String (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 -> Either String (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 -> Either String (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 -> Either String (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 -> Either String (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 -> Either String (Maybe a)
Data..?> Key
"ProcessingInputs"
                            forall (f :: * -> *) a. Functor f => f (Maybe a) -> a -> f a
Core..!@ 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 -> Either String (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 -> Either String (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 -> Either String (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 -> Either String (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 -> Either String (Maybe a)
Data..?> Key
"TrainingJobArn")
            forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
Prelude.<*> (forall (f :: * -> *) a. Applicative f => a -> f a
Prelude.pure (forall a. Enum a => a -> Int
Prelude.fromEnum Int
s))
            forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
Prelude.<*> (Object
x forall a. FromJSON a => Object -> Key -> Either String 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 -> Either String 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 -> Either String 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 -> Either String 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 -> Either String 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 -> Either String a
Data..:> Key
"CreationTime")
      )

instance Prelude.Hashable DescribeProcessingJob where
  hashWithSalt :: Int -> DescribeProcessingJob -> Int
hashWithSalt Int
_salt DescribeProcessingJob' {Text
processingJobName :: Text
$sel:processingJobName:DescribeProcessingJob' :: DescribeProcessingJob -> Text
..} =
    Int
_salt forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Text
processingJobName

instance Prelude.NFData DescribeProcessingJob where
  rnf :: DescribeProcessingJob -> ()
rnf DescribeProcessingJob' {Text
processingJobName :: Text
$sel:processingJobName:DescribeProcessingJob' :: DescribeProcessingJob -> Text
..} =
    forall a. NFData a => a -> ()
Prelude.rnf Text
processingJobName

instance Data.ToHeaders DescribeProcessingJob where
  toHeaders :: DescribeProcessingJob -> ResponseHeaders
toHeaders =
    forall a b. a -> b -> a
Prelude.const
      ( forall a. Monoid a => [a] -> a
Prelude.mconcat
          [ HeaderName
"X-Amz-Target"
              forall a. ToHeader a => HeaderName -> a -> ResponseHeaders
Data.=# ( ByteString
"SageMaker.DescribeProcessingJob" ::
                          Prelude.ByteString
                      ),
            HeaderName
"Content-Type"
              forall a. ToHeader a => HeaderName -> a -> ResponseHeaders
Data.=# ( ByteString
"application/x-amz-json-1.1" ::
                          Prelude.ByteString
                      )
          ]
      )

instance Data.ToJSON DescribeProcessingJob where
  toJSON :: DescribeProcessingJob -> Value
toJSON DescribeProcessingJob' {Text
processingJobName :: Text
$sel:processingJobName:DescribeProcessingJob' :: DescribeProcessingJob -> Text
..} =
    [Pair] -> Value
Data.object
      ( forall a. [Maybe a] -> [a]
Prelude.catMaybes
          [ forall a. a -> Maybe a
Prelude.Just
              (Key
"ProcessingJobName" forall kv v. (KeyValue kv, ToJSON v) => Key -> v -> kv
Data..= Text
processingJobName)
          ]
      )

instance Data.ToPath DescribeProcessingJob where
  toPath :: DescribeProcessingJob -> ByteString
toPath = forall a b. a -> b -> a
Prelude.const ByteString
"/"

instance Data.ToQuery DescribeProcessingJob where
  toQuery :: DescribeProcessingJob -> QueryString
toQuery = forall a b. a -> b -> a
Prelude.const forall a. Monoid a => a
Prelude.mempty

-- | /See:/ 'newDescribeProcessingJobResponse' smart constructor.
data DescribeProcessingJobResponse = DescribeProcessingJobResponse'
  { -- | The ARN of an AutoML job associated with this processing job.
    DescribeProcessingJobResponse -> Maybe Text
autoMLJobArn :: Prelude.Maybe Prelude.Text,
    -- | The environment variables set in the Docker container.
    DescribeProcessingJobResponse -> Maybe (HashMap Text Text)
environment :: Prelude.Maybe (Prelude.HashMap Prelude.Text Prelude.Text),
    -- | An optional string, up to one KB in size, that contains metadata from
    -- the processing container when the processing job exits.
    DescribeProcessingJobResponse -> Maybe Text
exitMessage :: Prelude.Maybe Prelude.Text,
    -- | The configuration information used to create an experiment.
    DescribeProcessingJobResponse -> 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.
    DescribeProcessingJobResponse -> Maybe Text
failureReason :: Prelude.Maybe Prelude.Text,
    -- | The time at which the processing job was last modified.
    DescribeProcessingJobResponse -> Maybe POSIX
lastModifiedTime :: Prelude.Maybe Data.POSIX,
    -- | The ARN of a monitoring schedule for an endpoint associated with this
    -- processing job.
    DescribeProcessingJobResponse -> Maybe Text
monitoringScheduleArn :: Prelude.Maybe Prelude.Text,
    -- | Networking options for a processing job.
    DescribeProcessingJobResponse -> Maybe NetworkConfig
networkConfig :: Prelude.Maybe NetworkConfig,
    -- | The time at which the processing job completed.
    DescribeProcessingJobResponse -> Maybe POSIX
processingEndTime :: Prelude.Maybe Data.POSIX,
    -- | The inputs for a processing job.
    DescribeProcessingJobResponse -> Maybe [ProcessingInput]
processingInputs :: Prelude.Maybe [ProcessingInput],
    -- | Output configuration for the processing job.
    DescribeProcessingJobResponse -> Maybe ProcessingOutputConfig
processingOutputConfig :: Prelude.Maybe ProcessingOutputConfig,
    -- | The time at which the processing job started.
    DescribeProcessingJobResponse -> Maybe POSIX
processingStartTime :: Prelude.Maybe Data.POSIX,
    -- | The Amazon Resource Name (ARN) of an IAM role that Amazon SageMaker can
    -- assume to perform tasks on your behalf.
    DescribeProcessingJobResponse -> Maybe Text
roleArn :: Prelude.Maybe Prelude.Text,
    -- | The time limit for how long the processing job is allowed to run.
    DescribeProcessingJobResponse -> Maybe ProcessingStoppingCondition
stoppingCondition :: Prelude.Maybe ProcessingStoppingCondition,
    -- | The ARN of a training job associated with this processing job.
    DescribeProcessingJobResponse -> Maybe Text
trainingJobArn :: Prelude.Maybe Prelude.Text,
    -- | The response's http status code.
    DescribeProcessingJobResponse -> Int
httpStatus :: Prelude.Int,
    -- | The name of the processing job. The name must be unique within an Amazon
    -- Web Services Region in the Amazon Web Services account.
    DescribeProcessingJobResponse -> Text
processingJobName :: Prelude.Text,
    -- | Identifies the resources, ML compute instances, and ML storage volumes
    -- to deploy for a processing job. In distributed training, you specify
    -- more than one instance.
    DescribeProcessingJobResponse -> ProcessingResources
processingResources :: ProcessingResources,
    -- | Configures the processing job to run a specified container image.
    DescribeProcessingJobResponse -> AppSpecification
appSpecification :: AppSpecification,
    -- | The Amazon Resource Name (ARN) of the processing job.
    DescribeProcessingJobResponse -> Text
processingJobArn :: Prelude.Text,
    -- | Provides the status of a processing job.
    DescribeProcessingJobResponse -> ProcessingJobStatus
processingJobStatus :: ProcessingJobStatus,
    -- | The time at which the processing job was created.
    DescribeProcessingJobResponse -> POSIX
creationTime :: Data.POSIX
  }
  deriving (DescribeProcessingJobResponse
-> DescribeProcessingJobResponse -> Bool
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: DescribeProcessingJobResponse
-> DescribeProcessingJobResponse -> Bool
$c/= :: DescribeProcessingJobResponse
-> DescribeProcessingJobResponse -> Bool
== :: DescribeProcessingJobResponse
-> DescribeProcessingJobResponse -> Bool
$c== :: DescribeProcessingJobResponse
-> DescribeProcessingJobResponse -> Bool
Prelude.Eq, ReadPrec [DescribeProcessingJobResponse]
ReadPrec DescribeProcessingJobResponse
Int -> ReadS DescribeProcessingJobResponse
ReadS [DescribeProcessingJobResponse]
forall a.
(Int -> ReadS a)
-> ReadS [a] -> ReadPrec a -> ReadPrec [a] -> Read a
readListPrec :: ReadPrec [DescribeProcessingJobResponse]
$creadListPrec :: ReadPrec [DescribeProcessingJobResponse]
readPrec :: ReadPrec DescribeProcessingJobResponse
$creadPrec :: ReadPrec DescribeProcessingJobResponse
readList :: ReadS [DescribeProcessingJobResponse]
$creadList :: ReadS [DescribeProcessingJobResponse]
readsPrec :: Int -> ReadS DescribeProcessingJobResponse
$creadsPrec :: Int -> ReadS DescribeProcessingJobResponse
Prelude.Read, Int -> DescribeProcessingJobResponse -> ShowS
[DescribeProcessingJobResponse] -> ShowS
DescribeProcessingJobResponse -> String
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [DescribeProcessingJobResponse] -> ShowS
$cshowList :: [DescribeProcessingJobResponse] -> ShowS
show :: DescribeProcessingJobResponse -> String
$cshow :: DescribeProcessingJobResponse -> String
showsPrec :: Int -> DescribeProcessingJobResponse -> ShowS
$cshowsPrec :: Int -> DescribeProcessingJobResponse -> ShowS
Prelude.Show, forall x.
Rep DescribeProcessingJobResponse x
-> DescribeProcessingJobResponse
forall x.
DescribeProcessingJobResponse
-> Rep DescribeProcessingJobResponse x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cto :: forall x.
Rep DescribeProcessingJobResponse x
-> DescribeProcessingJobResponse
$cfrom :: forall x.
DescribeProcessingJobResponse
-> Rep DescribeProcessingJobResponse x
Prelude.Generic)

-- |
-- Create a value of 'DescribeProcessingJobResponse' 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:
--
-- 'autoMLJobArn', 'describeProcessingJobResponse_autoMLJobArn' - The ARN of an AutoML job associated with this processing job.
--
-- 'environment', 'describeProcessingJobResponse_environment' - The environment variables set in the Docker container.
--
-- 'exitMessage', 'describeProcessingJobResponse_exitMessage' - An optional string, up to one KB in size, that contains metadata from
-- the processing container when the processing job exits.
--
-- 'experimentConfig', 'describeProcessingJobResponse_experimentConfig' - The configuration information used to create an experiment.
--
-- 'failureReason', 'describeProcessingJobResponse_failureReason' - A string, up to one KB in size, that contains the reason a processing
-- job failed, if it failed.
--
-- 'lastModifiedTime', 'describeProcessingJobResponse_lastModifiedTime' - The time at which the processing job was last modified.
--
-- 'monitoringScheduleArn', 'describeProcessingJobResponse_monitoringScheduleArn' - The ARN of a monitoring schedule for an endpoint associated with this
-- processing job.
--
-- 'networkConfig', 'describeProcessingJobResponse_networkConfig' - Networking options for a processing job.
--
-- 'processingEndTime', 'describeProcessingJobResponse_processingEndTime' - The time at which the processing job completed.
--
-- 'processingInputs', 'describeProcessingJobResponse_processingInputs' - The inputs for a processing job.
--
-- 'processingOutputConfig', 'describeProcessingJobResponse_processingOutputConfig' - Output configuration for the processing job.
--
-- 'processingStartTime', 'describeProcessingJobResponse_processingStartTime' - The time at which the processing job started.
--
-- 'roleArn', 'describeProcessingJobResponse_roleArn' - The Amazon Resource Name (ARN) of an IAM role that Amazon SageMaker can
-- assume to perform tasks on your behalf.
--
-- 'stoppingCondition', 'describeProcessingJobResponse_stoppingCondition' - The time limit for how long the processing job is allowed to run.
--
-- 'trainingJobArn', 'describeProcessingJobResponse_trainingJobArn' - The ARN of a training job associated with this processing job.
--
-- 'httpStatus', 'describeProcessingJobResponse_httpStatus' - The response's http status code.
--
-- 'processingJobName', 'describeProcessingJobResponse_processingJobName' - The name of the processing job. The name must be unique within an Amazon
-- Web Services Region in the Amazon Web Services account.
--
-- 'processingResources', 'describeProcessingJobResponse_processingResources' - Identifies the resources, ML compute instances, and ML storage volumes
-- to deploy for a processing job. In distributed training, you specify
-- more than one instance.
--
-- 'appSpecification', 'describeProcessingJobResponse_appSpecification' - Configures the processing job to run a specified container image.
--
-- 'processingJobArn', 'describeProcessingJobResponse_processingJobArn' - The Amazon Resource Name (ARN) of the processing job.
--
-- 'processingJobStatus', 'describeProcessingJobResponse_processingJobStatus' - Provides the status of a processing job.
--
-- 'creationTime', 'describeProcessingJobResponse_creationTime' - The time at which the processing job was created.
newDescribeProcessingJobResponse ::
  -- | 'httpStatus'
  Prelude.Int ->
  -- | 'processingJobName'
  Prelude.Text ->
  -- | 'processingResources'
  ProcessingResources ->
  -- | 'appSpecification'
  AppSpecification ->
  -- | 'processingJobArn'
  Prelude.Text ->
  -- | 'processingJobStatus'
  ProcessingJobStatus ->
  -- | 'creationTime'
  Prelude.UTCTime ->
  DescribeProcessingJobResponse
newDescribeProcessingJobResponse :: Int
-> Text
-> ProcessingResources
-> AppSpecification
-> Text
-> ProcessingJobStatus
-> UTCTime
-> DescribeProcessingJobResponse
newDescribeProcessingJobResponse
  Int
pHttpStatus_
  Text
pProcessingJobName_
  ProcessingResources
pProcessingResources_
  AppSpecification
pAppSpecification_
  Text
pProcessingJobArn_
  ProcessingJobStatus
pProcessingJobStatus_
  UTCTime
pCreationTime_ =
    DescribeProcessingJobResponse'
      { $sel:autoMLJobArn:DescribeProcessingJobResponse' :: Maybe Text
autoMLJobArn =
          forall a. Maybe a
Prelude.Nothing,
        $sel:environment:DescribeProcessingJobResponse' :: Maybe (HashMap Text Text)
environment = forall a. Maybe a
Prelude.Nothing,
        $sel:exitMessage:DescribeProcessingJobResponse' :: Maybe Text
exitMessage = forall a. Maybe a
Prelude.Nothing,
        $sel:experimentConfig:DescribeProcessingJobResponse' :: Maybe ExperimentConfig
experimentConfig = forall a. Maybe a
Prelude.Nothing,
        $sel:failureReason:DescribeProcessingJobResponse' :: Maybe Text
failureReason = forall a. Maybe a
Prelude.Nothing,
        $sel:lastModifiedTime:DescribeProcessingJobResponse' :: Maybe POSIX
lastModifiedTime = forall a. Maybe a
Prelude.Nothing,
        $sel:monitoringScheduleArn:DescribeProcessingJobResponse' :: Maybe Text
monitoringScheduleArn = forall a. Maybe a
Prelude.Nothing,
        $sel:networkConfig:DescribeProcessingJobResponse' :: Maybe NetworkConfig
networkConfig = forall a. Maybe a
Prelude.Nothing,
        $sel:processingEndTime:DescribeProcessingJobResponse' :: Maybe POSIX
processingEndTime = forall a. Maybe a
Prelude.Nothing,
        $sel:processingInputs:DescribeProcessingJobResponse' :: Maybe [ProcessingInput]
processingInputs = forall a. Maybe a
Prelude.Nothing,
        $sel:processingOutputConfig:DescribeProcessingJobResponse' :: Maybe ProcessingOutputConfig
processingOutputConfig = forall a. Maybe a
Prelude.Nothing,
        $sel:processingStartTime:DescribeProcessingJobResponse' :: Maybe POSIX
processingStartTime = forall a. Maybe a
Prelude.Nothing,
        $sel:roleArn:DescribeProcessingJobResponse' :: Maybe Text
roleArn = forall a. Maybe a
Prelude.Nothing,
        $sel:stoppingCondition:DescribeProcessingJobResponse' :: Maybe ProcessingStoppingCondition
stoppingCondition = forall a. Maybe a
Prelude.Nothing,
        $sel:trainingJobArn:DescribeProcessingJobResponse' :: Maybe Text
trainingJobArn = forall a. Maybe a
Prelude.Nothing,
        $sel:httpStatus:DescribeProcessingJobResponse' :: Int
httpStatus = Int
pHttpStatus_,
        $sel:processingJobName:DescribeProcessingJobResponse' :: Text
processingJobName = Text
pProcessingJobName_,
        $sel:processingResources:DescribeProcessingJobResponse' :: ProcessingResources
processingResources = ProcessingResources
pProcessingResources_,
        $sel:appSpecification:DescribeProcessingJobResponse' :: AppSpecification
appSpecification = AppSpecification
pAppSpecification_,
        $sel:processingJobArn:DescribeProcessingJobResponse' :: Text
processingJobArn = Text
pProcessingJobArn_,
        $sel:processingJobStatus:DescribeProcessingJobResponse' :: ProcessingJobStatus
processingJobStatus = ProcessingJobStatus
pProcessingJobStatus_,
        $sel:creationTime:DescribeProcessingJobResponse' :: POSIX
creationTime =
          forall (a :: Format). Iso' (Time a) UTCTime
Data._Time forall t b. AReview t b -> b -> t
Lens.# UTCTime
pCreationTime_
      }

-- | The ARN of an AutoML job associated with this processing job.
describeProcessingJobResponse_autoMLJobArn :: Lens.Lens' DescribeProcessingJobResponse (Prelude.Maybe Prelude.Text)
describeProcessingJobResponse_autoMLJobArn :: Lens' DescribeProcessingJobResponse (Maybe Text)
describeProcessingJobResponse_autoMLJobArn = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\DescribeProcessingJobResponse' {Maybe Text
autoMLJobArn :: Maybe Text
$sel:autoMLJobArn:DescribeProcessingJobResponse' :: DescribeProcessingJobResponse -> Maybe Text
autoMLJobArn} -> Maybe Text
autoMLJobArn) (\s :: DescribeProcessingJobResponse
s@DescribeProcessingJobResponse' {} Maybe Text
a -> DescribeProcessingJobResponse
s {$sel:autoMLJobArn:DescribeProcessingJobResponse' :: Maybe Text
autoMLJobArn = Maybe Text
a} :: DescribeProcessingJobResponse)

-- | The environment variables set in the Docker container.
describeProcessingJobResponse_environment :: Lens.Lens' DescribeProcessingJobResponse (Prelude.Maybe (Prelude.HashMap Prelude.Text Prelude.Text))
describeProcessingJobResponse_environment :: Lens' DescribeProcessingJobResponse (Maybe (HashMap Text Text))
describeProcessingJobResponse_environment = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\DescribeProcessingJobResponse' {Maybe (HashMap Text Text)
environment :: Maybe (HashMap Text Text)
$sel:environment:DescribeProcessingJobResponse' :: DescribeProcessingJobResponse -> Maybe (HashMap Text Text)
environment} -> Maybe (HashMap Text Text)
environment) (\s :: DescribeProcessingJobResponse
s@DescribeProcessingJobResponse' {} Maybe (HashMap Text Text)
a -> DescribeProcessingJobResponse
s {$sel:environment:DescribeProcessingJobResponse' :: Maybe (HashMap Text Text)
environment = Maybe (HashMap Text Text)
a} :: DescribeProcessingJobResponse) forall b c a. (b -> c) -> (a -> b) -> a -> c
Prelude.. forall (f :: * -> *) (g :: * -> *) s t a b.
(Functor f, Functor g) =>
AnIso s t a b -> Iso (f s) (g t) (f a) (g b)
Lens.mapping forall s t a b. (Coercible s a, Coercible t b) => Iso s t a b
Lens.coerced

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

-- | The configuration information used to create an experiment.
describeProcessingJobResponse_experimentConfig :: Lens.Lens' DescribeProcessingJobResponse (Prelude.Maybe ExperimentConfig)
describeProcessingJobResponse_experimentConfig :: Lens' DescribeProcessingJobResponse (Maybe ExperimentConfig)
describeProcessingJobResponse_experimentConfig = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\DescribeProcessingJobResponse' {Maybe ExperimentConfig
experimentConfig :: Maybe ExperimentConfig
$sel:experimentConfig:DescribeProcessingJobResponse' :: DescribeProcessingJobResponse -> Maybe ExperimentConfig
experimentConfig} -> Maybe ExperimentConfig
experimentConfig) (\s :: DescribeProcessingJobResponse
s@DescribeProcessingJobResponse' {} Maybe ExperimentConfig
a -> DescribeProcessingJobResponse
s {$sel:experimentConfig:DescribeProcessingJobResponse' :: Maybe ExperimentConfig
experimentConfig = Maybe ExperimentConfig
a} :: DescribeProcessingJobResponse)

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

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

-- | Networking options for a processing job.
describeProcessingJobResponse_networkConfig :: Lens.Lens' DescribeProcessingJobResponse (Prelude.Maybe NetworkConfig)
describeProcessingJobResponse_networkConfig :: Lens' DescribeProcessingJobResponse (Maybe NetworkConfig)
describeProcessingJobResponse_networkConfig = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\DescribeProcessingJobResponse' {Maybe NetworkConfig
networkConfig :: Maybe NetworkConfig
$sel:networkConfig:DescribeProcessingJobResponse' :: DescribeProcessingJobResponse -> Maybe NetworkConfig
networkConfig} -> Maybe NetworkConfig
networkConfig) (\s :: DescribeProcessingJobResponse
s@DescribeProcessingJobResponse' {} Maybe NetworkConfig
a -> DescribeProcessingJobResponse
s {$sel:networkConfig:DescribeProcessingJobResponse' :: Maybe NetworkConfig
networkConfig = Maybe NetworkConfig
a} :: DescribeProcessingJobResponse)

-- | The time at which the processing job completed.
describeProcessingJobResponse_processingEndTime :: Lens.Lens' DescribeProcessingJobResponse (Prelude.Maybe Prelude.UTCTime)
describeProcessingJobResponse_processingEndTime :: Lens' DescribeProcessingJobResponse (Maybe UTCTime)
describeProcessingJobResponse_processingEndTime = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\DescribeProcessingJobResponse' {Maybe POSIX
processingEndTime :: Maybe POSIX
$sel:processingEndTime:DescribeProcessingJobResponse' :: DescribeProcessingJobResponse -> Maybe POSIX
processingEndTime} -> Maybe POSIX
processingEndTime) (\s :: DescribeProcessingJobResponse
s@DescribeProcessingJobResponse' {} Maybe POSIX
a -> DescribeProcessingJobResponse
s {$sel:processingEndTime:DescribeProcessingJobResponse' :: Maybe POSIX
processingEndTime = Maybe POSIX
a} :: DescribeProcessingJobResponse) 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 inputs for a processing job.
describeProcessingJobResponse_processingInputs :: Lens.Lens' DescribeProcessingJobResponse (Prelude.Maybe [ProcessingInput])
describeProcessingJobResponse_processingInputs :: Lens' DescribeProcessingJobResponse (Maybe [ProcessingInput])
describeProcessingJobResponse_processingInputs = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\DescribeProcessingJobResponse' {Maybe [ProcessingInput]
processingInputs :: Maybe [ProcessingInput]
$sel:processingInputs:DescribeProcessingJobResponse' :: DescribeProcessingJobResponse -> Maybe [ProcessingInput]
processingInputs} -> Maybe [ProcessingInput]
processingInputs) (\s :: DescribeProcessingJobResponse
s@DescribeProcessingJobResponse' {} Maybe [ProcessingInput]
a -> DescribeProcessingJobResponse
s {$sel:processingInputs:DescribeProcessingJobResponse' :: Maybe [ProcessingInput]
processingInputs = Maybe [ProcessingInput]
a} :: DescribeProcessingJobResponse) 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

-- | Output configuration for the processing job.
describeProcessingJobResponse_processingOutputConfig :: Lens.Lens' DescribeProcessingJobResponse (Prelude.Maybe ProcessingOutputConfig)
describeProcessingJobResponse_processingOutputConfig :: Lens' DescribeProcessingJobResponse (Maybe ProcessingOutputConfig)
describeProcessingJobResponse_processingOutputConfig = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\DescribeProcessingJobResponse' {Maybe ProcessingOutputConfig
processingOutputConfig :: Maybe ProcessingOutputConfig
$sel:processingOutputConfig:DescribeProcessingJobResponse' :: DescribeProcessingJobResponse -> Maybe ProcessingOutputConfig
processingOutputConfig} -> Maybe ProcessingOutputConfig
processingOutputConfig) (\s :: DescribeProcessingJobResponse
s@DescribeProcessingJobResponse' {} Maybe ProcessingOutputConfig
a -> DescribeProcessingJobResponse
s {$sel:processingOutputConfig:DescribeProcessingJobResponse' :: Maybe ProcessingOutputConfig
processingOutputConfig = Maybe ProcessingOutputConfig
a} :: DescribeProcessingJobResponse)

-- | The time at which the processing job started.
describeProcessingJobResponse_processingStartTime :: Lens.Lens' DescribeProcessingJobResponse (Prelude.Maybe Prelude.UTCTime)
describeProcessingJobResponse_processingStartTime :: Lens' DescribeProcessingJobResponse (Maybe UTCTime)
describeProcessingJobResponse_processingStartTime = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\DescribeProcessingJobResponse' {Maybe POSIX
processingStartTime :: Maybe POSIX
$sel:processingStartTime:DescribeProcessingJobResponse' :: DescribeProcessingJobResponse -> Maybe POSIX
processingStartTime} -> Maybe POSIX
processingStartTime) (\s :: DescribeProcessingJobResponse
s@DescribeProcessingJobResponse' {} Maybe POSIX
a -> DescribeProcessingJobResponse
s {$sel:processingStartTime:DescribeProcessingJobResponse' :: Maybe POSIX
processingStartTime = Maybe POSIX
a} :: DescribeProcessingJobResponse) 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 Amazon Resource Name (ARN) of an IAM role that Amazon SageMaker can
-- assume to perform tasks on your behalf.
describeProcessingJobResponse_roleArn :: Lens.Lens' DescribeProcessingJobResponse (Prelude.Maybe Prelude.Text)
describeProcessingJobResponse_roleArn :: Lens' DescribeProcessingJobResponse (Maybe Text)
describeProcessingJobResponse_roleArn = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\DescribeProcessingJobResponse' {Maybe Text
roleArn :: Maybe Text
$sel:roleArn:DescribeProcessingJobResponse' :: DescribeProcessingJobResponse -> Maybe Text
roleArn} -> Maybe Text
roleArn) (\s :: DescribeProcessingJobResponse
s@DescribeProcessingJobResponse' {} Maybe Text
a -> DescribeProcessingJobResponse
s {$sel:roleArn:DescribeProcessingJobResponse' :: Maybe Text
roleArn = Maybe Text
a} :: DescribeProcessingJobResponse)

-- | The time limit for how long the processing job is allowed to run.
describeProcessingJobResponse_stoppingCondition :: Lens.Lens' DescribeProcessingJobResponse (Prelude.Maybe ProcessingStoppingCondition)
describeProcessingJobResponse_stoppingCondition :: Lens'
  DescribeProcessingJobResponse (Maybe ProcessingStoppingCondition)
describeProcessingJobResponse_stoppingCondition = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\DescribeProcessingJobResponse' {Maybe ProcessingStoppingCondition
stoppingCondition :: Maybe ProcessingStoppingCondition
$sel:stoppingCondition:DescribeProcessingJobResponse' :: DescribeProcessingJobResponse -> Maybe ProcessingStoppingCondition
stoppingCondition} -> Maybe ProcessingStoppingCondition
stoppingCondition) (\s :: DescribeProcessingJobResponse
s@DescribeProcessingJobResponse' {} Maybe ProcessingStoppingCondition
a -> DescribeProcessingJobResponse
s {$sel:stoppingCondition:DescribeProcessingJobResponse' :: Maybe ProcessingStoppingCondition
stoppingCondition = Maybe ProcessingStoppingCondition
a} :: DescribeProcessingJobResponse)

-- | The ARN of a training job associated with this processing job.
describeProcessingJobResponse_trainingJobArn :: Lens.Lens' DescribeProcessingJobResponse (Prelude.Maybe Prelude.Text)
describeProcessingJobResponse_trainingJobArn :: Lens' DescribeProcessingJobResponse (Maybe Text)
describeProcessingJobResponse_trainingJobArn = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\DescribeProcessingJobResponse' {Maybe Text
trainingJobArn :: Maybe Text
$sel:trainingJobArn:DescribeProcessingJobResponse' :: DescribeProcessingJobResponse -> Maybe Text
trainingJobArn} -> Maybe Text
trainingJobArn) (\s :: DescribeProcessingJobResponse
s@DescribeProcessingJobResponse' {} Maybe Text
a -> DescribeProcessingJobResponse
s {$sel:trainingJobArn:DescribeProcessingJobResponse' :: Maybe Text
trainingJobArn = Maybe Text
a} :: DescribeProcessingJobResponse)

-- | The response's http status code.
describeProcessingJobResponse_httpStatus :: Lens.Lens' DescribeProcessingJobResponse Prelude.Int
describeProcessingJobResponse_httpStatus :: Lens' DescribeProcessingJobResponse Int
describeProcessingJobResponse_httpStatus = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\DescribeProcessingJobResponse' {Int
httpStatus :: Int
$sel:httpStatus:DescribeProcessingJobResponse' :: DescribeProcessingJobResponse -> Int
httpStatus} -> Int
httpStatus) (\s :: DescribeProcessingJobResponse
s@DescribeProcessingJobResponse' {} Int
a -> DescribeProcessingJobResponse
s {$sel:httpStatus:DescribeProcessingJobResponse' :: Int
httpStatus = Int
a} :: DescribeProcessingJobResponse)

-- | The name of the processing job. The name must be unique within an Amazon
-- Web Services Region in the Amazon Web Services account.
describeProcessingJobResponse_processingJobName :: Lens.Lens' DescribeProcessingJobResponse Prelude.Text
describeProcessingJobResponse_processingJobName :: Lens' DescribeProcessingJobResponse Text
describeProcessingJobResponse_processingJobName = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\DescribeProcessingJobResponse' {Text
processingJobName :: Text
$sel:processingJobName:DescribeProcessingJobResponse' :: DescribeProcessingJobResponse -> Text
processingJobName} -> Text
processingJobName) (\s :: DescribeProcessingJobResponse
s@DescribeProcessingJobResponse' {} Text
a -> DescribeProcessingJobResponse
s {$sel:processingJobName:DescribeProcessingJobResponse' :: Text
processingJobName = Text
a} :: DescribeProcessingJobResponse)

-- | Identifies the resources, ML compute instances, and ML storage volumes
-- to deploy for a processing job. In distributed training, you specify
-- more than one instance.
describeProcessingJobResponse_processingResources :: Lens.Lens' DescribeProcessingJobResponse ProcessingResources
describeProcessingJobResponse_processingResources :: Lens' DescribeProcessingJobResponse ProcessingResources
describeProcessingJobResponse_processingResources = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\DescribeProcessingJobResponse' {ProcessingResources
processingResources :: ProcessingResources
$sel:processingResources:DescribeProcessingJobResponse' :: DescribeProcessingJobResponse -> ProcessingResources
processingResources} -> ProcessingResources
processingResources) (\s :: DescribeProcessingJobResponse
s@DescribeProcessingJobResponse' {} ProcessingResources
a -> DescribeProcessingJobResponse
s {$sel:processingResources:DescribeProcessingJobResponse' :: ProcessingResources
processingResources = ProcessingResources
a} :: DescribeProcessingJobResponse)

-- | Configures the processing job to run a specified container image.
describeProcessingJobResponse_appSpecification :: Lens.Lens' DescribeProcessingJobResponse AppSpecification
describeProcessingJobResponse_appSpecification :: Lens' DescribeProcessingJobResponse AppSpecification
describeProcessingJobResponse_appSpecification = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\DescribeProcessingJobResponse' {AppSpecification
appSpecification :: AppSpecification
$sel:appSpecification:DescribeProcessingJobResponse' :: DescribeProcessingJobResponse -> AppSpecification
appSpecification} -> AppSpecification
appSpecification) (\s :: DescribeProcessingJobResponse
s@DescribeProcessingJobResponse' {} AppSpecification
a -> DescribeProcessingJobResponse
s {$sel:appSpecification:DescribeProcessingJobResponse' :: AppSpecification
appSpecification = AppSpecification
a} :: DescribeProcessingJobResponse)

-- | The Amazon Resource Name (ARN) of the processing job.
describeProcessingJobResponse_processingJobArn :: Lens.Lens' DescribeProcessingJobResponse Prelude.Text
describeProcessingJobResponse_processingJobArn :: Lens' DescribeProcessingJobResponse Text
describeProcessingJobResponse_processingJobArn = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\DescribeProcessingJobResponse' {Text
processingJobArn :: Text
$sel:processingJobArn:DescribeProcessingJobResponse' :: DescribeProcessingJobResponse -> Text
processingJobArn} -> Text
processingJobArn) (\s :: DescribeProcessingJobResponse
s@DescribeProcessingJobResponse' {} Text
a -> DescribeProcessingJobResponse
s {$sel:processingJobArn:DescribeProcessingJobResponse' :: Text
processingJobArn = Text
a} :: DescribeProcessingJobResponse)

-- | Provides the status of a processing job.
describeProcessingJobResponse_processingJobStatus :: Lens.Lens' DescribeProcessingJobResponse ProcessingJobStatus
describeProcessingJobResponse_processingJobStatus :: Lens' DescribeProcessingJobResponse ProcessingJobStatus
describeProcessingJobResponse_processingJobStatus = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\DescribeProcessingJobResponse' {ProcessingJobStatus
processingJobStatus :: ProcessingJobStatus
$sel:processingJobStatus:DescribeProcessingJobResponse' :: DescribeProcessingJobResponse -> ProcessingJobStatus
processingJobStatus} -> ProcessingJobStatus
processingJobStatus) (\s :: DescribeProcessingJobResponse
s@DescribeProcessingJobResponse' {} ProcessingJobStatus
a -> DescribeProcessingJobResponse
s {$sel:processingJobStatus:DescribeProcessingJobResponse' :: ProcessingJobStatus
processingJobStatus = ProcessingJobStatus
a} :: DescribeProcessingJobResponse)

-- | The time at which the processing job was created.
describeProcessingJobResponse_creationTime :: Lens.Lens' DescribeProcessingJobResponse Prelude.UTCTime
describeProcessingJobResponse_creationTime :: Lens' DescribeProcessingJobResponse UTCTime
describeProcessingJobResponse_creationTime = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\DescribeProcessingJobResponse' {POSIX
creationTime :: POSIX
$sel:creationTime:DescribeProcessingJobResponse' :: DescribeProcessingJobResponse -> POSIX
creationTime} -> POSIX
creationTime) (\s :: DescribeProcessingJobResponse
s@DescribeProcessingJobResponse' {} POSIX
a -> DescribeProcessingJobResponse
s {$sel:creationTime:DescribeProcessingJobResponse' :: POSIX
creationTime = POSIX
a} :: DescribeProcessingJobResponse) forall b c a. (b -> c) -> (a -> b) -> a -> c
Prelude.. forall (a :: Format). Iso' (Time a) UTCTime
Data._Time

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