{-# 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.TransformJob
-- 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.TransformJob 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.BatchStrategy
import Amazonka.SageMaker.Types.DataProcessing
import Amazonka.SageMaker.Types.ExperimentConfig
import Amazonka.SageMaker.Types.ModelClientConfig
import Amazonka.SageMaker.Types.Tag
import Amazonka.SageMaker.Types.TransformInput
import Amazonka.SageMaker.Types.TransformJobStatus
import Amazonka.SageMaker.Types.TransformOutput
import Amazonka.SageMaker.Types.TransformResources

-- | A batch transform job. For information about SageMaker batch transform,
-- see
-- <https://docs.aws.amazon.com/sagemaker/latest/dg/batch-transform.html Use Batch Transform>.
--
-- /See:/ 'newTransformJob' smart constructor.
data TransformJob = TransformJob'
  { -- | The Amazon Resource Name (ARN) of the AutoML job that created the
    -- transform job.
    TransformJob -> Maybe Text
autoMLJobArn :: Prelude.Maybe Prelude.Text,
    -- | Specifies the number of records to include in a mini-batch for an HTTP
    -- inference request. A record is a single unit of input data that
    -- inference can be made on. For example, a single line in a CSV file is a
    -- record.
    TransformJob -> Maybe BatchStrategy
batchStrategy :: Prelude.Maybe BatchStrategy,
    -- | A timestamp that shows when the transform Job was created.
    TransformJob -> Maybe POSIX
creationTime :: Prelude.Maybe Data.POSIX,
    TransformJob -> Maybe DataProcessing
dataProcessing :: Prelude.Maybe DataProcessing,
    -- | The environment variables to set in the Docker container. We support up
    -- to 16 key and values entries in the map.
    TransformJob -> Maybe (HashMap Text Text)
environment :: Prelude.Maybe (Prelude.HashMap Prelude.Text Prelude.Text),
    TransformJob -> Maybe ExperimentConfig
experimentConfig :: Prelude.Maybe ExperimentConfig,
    -- | If the transform job failed, the reason it failed.
    TransformJob -> Maybe Text
failureReason :: Prelude.Maybe Prelude.Text,
    -- | The Amazon Resource Name (ARN) of the labeling job that created the
    -- transform job.
    TransformJob -> Maybe Text
labelingJobArn :: Prelude.Maybe Prelude.Text,
    -- | The maximum number of parallel requests that can be sent to each
    -- instance in a transform job. If @MaxConcurrentTransforms@ is set to 0 or
    -- left unset, SageMaker checks the optional execution-parameters to
    -- determine the settings for your chosen algorithm. If the
    -- execution-parameters endpoint is not enabled, the default value is 1.
    -- For built-in algorithms, you don\'t need to set a value for
    -- @MaxConcurrentTransforms@.
    TransformJob -> Maybe Natural
maxConcurrentTransforms :: Prelude.Maybe Prelude.Natural,
    -- | The maximum allowed size of the payload, in MB. A payload is the data
    -- portion of a record (without metadata). The value in @MaxPayloadInMB@
    -- must be greater than, or equal to, the size of a single record. To
    -- estimate the size of a record in MB, divide the size of your dataset by
    -- the number of records. To ensure that the records fit within the maximum
    -- payload size, we recommend using a slightly larger value. The default
    -- value is 6 MB. For cases where the payload might be arbitrarily large
    -- and is transmitted using HTTP chunked encoding, set the value to 0. This
    -- feature works only in supported algorithms. Currently, SageMaker
    -- built-in algorithms do not support HTTP chunked encoding.
    TransformJob -> Maybe Natural
maxPayloadInMB :: Prelude.Maybe Prelude.Natural,
    TransformJob -> Maybe ModelClientConfig
modelClientConfig :: Prelude.Maybe ModelClientConfig,
    -- | The name of the model associated with the transform job.
    TransformJob -> Maybe Text
modelName :: Prelude.Maybe Prelude.Text,
    -- | A list of tags associated with the transform job.
    TransformJob -> Maybe [Tag]
tags :: Prelude.Maybe [Tag],
    -- | Indicates when the transform job has been completed, or has stopped or
    -- failed. You are billed for the time interval between this time and the
    -- value of @TransformStartTime@.
    TransformJob -> Maybe POSIX
transformEndTime :: Prelude.Maybe Data.POSIX,
    TransformJob -> Maybe TransformInput
transformInput :: Prelude.Maybe TransformInput,
    -- | The Amazon Resource Name (ARN) of the transform job.
    TransformJob -> Maybe Text
transformJobArn :: Prelude.Maybe Prelude.Text,
    -- | The name of the transform job.
    TransformJob -> Maybe Text
transformJobName :: Prelude.Maybe Prelude.Text,
    -- | The status of the transform job.
    --
    -- Transform job statuses are:
    --
    -- -   @InProgress@ - The job is in progress.
    --
    -- -   @Completed@ - The job has completed.
    --
    -- -   @Failed@ - The transform job has failed. To see the reason for the
    --     failure, see the @FailureReason@ field in the response to a
    --     @DescribeTransformJob@ call.
    --
    -- -   @Stopping@ - The transform job is stopping.
    --
    -- -   @Stopped@ - The transform job has stopped.
    TransformJob -> Maybe TransformJobStatus
transformJobStatus :: Prelude.Maybe TransformJobStatus,
    TransformJob -> Maybe TransformOutput
transformOutput :: Prelude.Maybe TransformOutput,
    TransformJob -> Maybe TransformResources
transformResources :: Prelude.Maybe TransformResources,
    -- | Indicates when the transform job starts on ML instances. You are billed
    -- for the time interval between this time and the value of
    -- @TransformEndTime@.
    TransformJob -> Maybe POSIX
transformStartTime :: Prelude.Maybe Data.POSIX
  }
  deriving (TransformJob -> TransformJob -> Bool
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: TransformJob -> TransformJob -> Bool
$c/= :: TransformJob -> TransformJob -> Bool
== :: TransformJob -> TransformJob -> Bool
$c== :: TransformJob -> TransformJob -> Bool
Prelude.Eq, ReadPrec [TransformJob]
ReadPrec TransformJob
Int -> ReadS TransformJob
ReadS [TransformJob]
forall a.
(Int -> ReadS a)
-> ReadS [a] -> ReadPrec a -> ReadPrec [a] -> Read a
readListPrec :: ReadPrec [TransformJob]
$creadListPrec :: ReadPrec [TransformJob]
readPrec :: ReadPrec TransformJob
$creadPrec :: ReadPrec TransformJob
readList :: ReadS [TransformJob]
$creadList :: ReadS [TransformJob]
readsPrec :: Int -> ReadS TransformJob
$creadsPrec :: Int -> ReadS TransformJob
Prelude.Read, Int -> TransformJob -> ShowS
[TransformJob] -> ShowS
TransformJob -> String
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [TransformJob] -> ShowS
$cshowList :: [TransformJob] -> ShowS
show :: TransformJob -> String
$cshow :: TransformJob -> String
showsPrec :: Int -> TransformJob -> ShowS
$cshowsPrec :: Int -> TransformJob -> ShowS
Prelude.Show, forall x. Rep TransformJob x -> TransformJob
forall x. TransformJob -> Rep TransformJob x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cto :: forall x. Rep TransformJob x -> TransformJob
$cfrom :: forall x. TransformJob -> Rep TransformJob x
Prelude.Generic)

-- |
-- Create a value of 'TransformJob' 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', 'transformJob_autoMLJobArn' - The Amazon Resource Name (ARN) of the AutoML job that created the
-- transform job.
--
-- 'batchStrategy', 'transformJob_batchStrategy' - Specifies the number of records to include in a mini-batch for an HTTP
-- inference request. A record is a single unit of input data that
-- inference can be made on. For example, a single line in a CSV file is a
-- record.
--
-- 'creationTime', 'transformJob_creationTime' - A timestamp that shows when the transform Job was created.
--
-- 'dataProcessing', 'transformJob_dataProcessing' - Undocumented member.
--
-- 'environment', 'transformJob_environment' - The environment variables to set in the Docker container. We support up
-- to 16 key and values entries in the map.
--
-- 'experimentConfig', 'transformJob_experimentConfig' - Undocumented member.
--
-- 'failureReason', 'transformJob_failureReason' - If the transform job failed, the reason it failed.
--
-- 'labelingJobArn', 'transformJob_labelingJobArn' - The Amazon Resource Name (ARN) of the labeling job that created the
-- transform job.
--
-- 'maxConcurrentTransforms', 'transformJob_maxConcurrentTransforms' - The maximum number of parallel requests that can be sent to each
-- instance in a transform job. If @MaxConcurrentTransforms@ is set to 0 or
-- left unset, SageMaker checks the optional execution-parameters to
-- determine the settings for your chosen algorithm. If the
-- execution-parameters endpoint is not enabled, the default value is 1.
-- For built-in algorithms, you don\'t need to set a value for
-- @MaxConcurrentTransforms@.
--
-- 'maxPayloadInMB', 'transformJob_maxPayloadInMB' - The maximum allowed size of the payload, in MB. A payload is the data
-- portion of a record (without metadata). The value in @MaxPayloadInMB@
-- must be greater than, or equal to, the size of a single record. To
-- estimate the size of a record in MB, divide the size of your dataset by
-- the number of records. To ensure that the records fit within the maximum
-- payload size, we recommend using a slightly larger value. The default
-- value is 6 MB. For cases where the payload might be arbitrarily large
-- and is transmitted using HTTP chunked encoding, set the value to 0. This
-- feature works only in supported algorithms. Currently, SageMaker
-- built-in algorithms do not support HTTP chunked encoding.
--
-- 'modelClientConfig', 'transformJob_modelClientConfig' - Undocumented member.
--
-- 'modelName', 'transformJob_modelName' - The name of the model associated with the transform job.
--
-- 'tags', 'transformJob_tags' - A list of tags associated with the transform job.
--
-- 'transformEndTime', 'transformJob_transformEndTime' - Indicates when the transform job has been completed, or has stopped or
-- failed. You are billed for the time interval between this time and the
-- value of @TransformStartTime@.
--
-- 'transformInput', 'transformJob_transformInput' - Undocumented member.
--
-- 'transformJobArn', 'transformJob_transformJobArn' - The Amazon Resource Name (ARN) of the transform job.
--
-- 'transformJobName', 'transformJob_transformJobName' - The name of the transform job.
--
-- 'transformJobStatus', 'transformJob_transformJobStatus' - The status of the transform job.
--
-- Transform job statuses are:
--
-- -   @InProgress@ - The job is in progress.
--
-- -   @Completed@ - The job has completed.
--
-- -   @Failed@ - The transform job has failed. To see the reason for the
--     failure, see the @FailureReason@ field in the response to a
--     @DescribeTransformJob@ call.
--
-- -   @Stopping@ - The transform job is stopping.
--
-- -   @Stopped@ - The transform job has stopped.
--
-- 'transformOutput', 'transformJob_transformOutput' - Undocumented member.
--
-- 'transformResources', 'transformJob_transformResources' - Undocumented member.
--
-- 'transformStartTime', 'transformJob_transformStartTime' - Indicates when the transform job starts on ML instances. You are billed
-- for the time interval between this time and the value of
-- @TransformEndTime@.
newTransformJob ::
  TransformJob
newTransformJob :: TransformJob
newTransformJob =
  TransformJob'
    { $sel:autoMLJobArn:TransformJob' :: Maybe Text
autoMLJobArn = forall a. Maybe a
Prelude.Nothing,
      $sel:batchStrategy:TransformJob' :: Maybe BatchStrategy
batchStrategy = forall a. Maybe a
Prelude.Nothing,
      $sel:creationTime:TransformJob' :: Maybe POSIX
creationTime = forall a. Maybe a
Prelude.Nothing,
      $sel:dataProcessing:TransformJob' :: Maybe DataProcessing
dataProcessing = forall a. Maybe a
Prelude.Nothing,
      $sel:environment:TransformJob' :: Maybe (HashMap Text Text)
environment = forall a. Maybe a
Prelude.Nothing,
      $sel:experimentConfig:TransformJob' :: Maybe ExperimentConfig
experimentConfig = forall a. Maybe a
Prelude.Nothing,
      $sel:failureReason:TransformJob' :: Maybe Text
failureReason = forall a. Maybe a
Prelude.Nothing,
      $sel:labelingJobArn:TransformJob' :: Maybe Text
labelingJobArn = forall a. Maybe a
Prelude.Nothing,
      $sel:maxConcurrentTransforms:TransformJob' :: Maybe Natural
maxConcurrentTransforms = forall a. Maybe a
Prelude.Nothing,
      $sel:maxPayloadInMB:TransformJob' :: Maybe Natural
maxPayloadInMB = forall a. Maybe a
Prelude.Nothing,
      $sel:modelClientConfig:TransformJob' :: Maybe ModelClientConfig
modelClientConfig = forall a. Maybe a
Prelude.Nothing,
      $sel:modelName:TransformJob' :: Maybe Text
modelName = forall a. Maybe a
Prelude.Nothing,
      $sel:tags:TransformJob' :: Maybe [Tag]
tags = forall a. Maybe a
Prelude.Nothing,
      $sel:transformEndTime:TransformJob' :: Maybe POSIX
transformEndTime = forall a. Maybe a
Prelude.Nothing,
      $sel:transformInput:TransformJob' :: Maybe TransformInput
transformInput = forall a. Maybe a
Prelude.Nothing,
      $sel:transformJobArn:TransformJob' :: Maybe Text
transformJobArn = forall a. Maybe a
Prelude.Nothing,
      $sel:transformJobName:TransformJob' :: Maybe Text
transformJobName = forall a. Maybe a
Prelude.Nothing,
      $sel:transformJobStatus:TransformJob' :: Maybe TransformJobStatus
transformJobStatus = forall a. Maybe a
Prelude.Nothing,
      $sel:transformOutput:TransformJob' :: Maybe TransformOutput
transformOutput = forall a. Maybe a
Prelude.Nothing,
      $sel:transformResources:TransformJob' :: Maybe TransformResources
transformResources = forall a. Maybe a
Prelude.Nothing,
      $sel:transformStartTime:TransformJob' :: Maybe POSIX
transformStartTime = forall a. Maybe a
Prelude.Nothing
    }

-- | The Amazon Resource Name (ARN) of the AutoML job that created the
-- transform job.
transformJob_autoMLJobArn :: Lens.Lens' TransformJob (Prelude.Maybe Prelude.Text)
transformJob_autoMLJobArn :: Lens' TransformJob (Maybe Text)
transformJob_autoMLJobArn = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\TransformJob' {Maybe Text
autoMLJobArn :: Maybe Text
$sel:autoMLJobArn:TransformJob' :: TransformJob -> Maybe Text
autoMLJobArn} -> Maybe Text
autoMLJobArn) (\s :: TransformJob
s@TransformJob' {} Maybe Text
a -> TransformJob
s {$sel:autoMLJobArn:TransformJob' :: Maybe Text
autoMLJobArn = Maybe Text
a} :: TransformJob)

-- | Specifies the number of records to include in a mini-batch for an HTTP
-- inference request. A record is a single unit of input data that
-- inference can be made on. For example, a single line in a CSV file is a
-- record.
transformJob_batchStrategy :: Lens.Lens' TransformJob (Prelude.Maybe BatchStrategy)
transformJob_batchStrategy :: Lens' TransformJob (Maybe BatchStrategy)
transformJob_batchStrategy = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\TransformJob' {Maybe BatchStrategy
batchStrategy :: Maybe BatchStrategy
$sel:batchStrategy:TransformJob' :: TransformJob -> Maybe BatchStrategy
batchStrategy} -> Maybe BatchStrategy
batchStrategy) (\s :: TransformJob
s@TransformJob' {} Maybe BatchStrategy
a -> TransformJob
s {$sel:batchStrategy:TransformJob' :: Maybe BatchStrategy
batchStrategy = Maybe BatchStrategy
a} :: TransformJob)

-- | A timestamp that shows when the transform Job was created.
transformJob_creationTime :: Lens.Lens' TransformJob (Prelude.Maybe Prelude.UTCTime)
transformJob_creationTime :: Lens' TransformJob (Maybe UTCTime)
transformJob_creationTime = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\TransformJob' {Maybe POSIX
creationTime :: Maybe POSIX
$sel:creationTime:TransformJob' :: TransformJob -> Maybe POSIX
creationTime} -> Maybe POSIX
creationTime) (\s :: TransformJob
s@TransformJob' {} Maybe POSIX
a -> TransformJob
s {$sel:creationTime:TransformJob' :: Maybe POSIX
creationTime = Maybe POSIX
a} :: TransformJob) 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

-- | Undocumented member.
transformJob_dataProcessing :: Lens.Lens' TransformJob (Prelude.Maybe DataProcessing)
transformJob_dataProcessing :: Lens' TransformJob (Maybe DataProcessing)
transformJob_dataProcessing = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\TransformJob' {Maybe DataProcessing
dataProcessing :: Maybe DataProcessing
$sel:dataProcessing:TransformJob' :: TransformJob -> Maybe DataProcessing
dataProcessing} -> Maybe DataProcessing
dataProcessing) (\s :: TransformJob
s@TransformJob' {} Maybe DataProcessing
a -> TransformJob
s {$sel:dataProcessing:TransformJob' :: Maybe DataProcessing
dataProcessing = Maybe DataProcessing
a} :: TransformJob)

-- | The environment variables to set in the Docker container. We support up
-- to 16 key and values entries in the map.
transformJob_environment :: Lens.Lens' TransformJob (Prelude.Maybe (Prelude.HashMap Prelude.Text Prelude.Text))
transformJob_environment :: Lens' TransformJob (Maybe (HashMap Text Text))
transformJob_environment = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\TransformJob' {Maybe (HashMap Text Text)
environment :: Maybe (HashMap Text Text)
$sel:environment:TransformJob' :: TransformJob -> Maybe (HashMap Text Text)
environment} -> Maybe (HashMap Text Text)
environment) (\s :: TransformJob
s@TransformJob' {} Maybe (HashMap Text Text)
a -> TransformJob
s {$sel:environment:TransformJob' :: Maybe (HashMap Text Text)
environment = Maybe (HashMap Text Text)
a} :: TransformJob) 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

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

-- | If the transform job failed, the reason it failed.
transformJob_failureReason :: Lens.Lens' TransformJob (Prelude.Maybe Prelude.Text)
transformJob_failureReason :: Lens' TransformJob (Maybe Text)
transformJob_failureReason = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\TransformJob' {Maybe Text
failureReason :: Maybe Text
$sel:failureReason:TransformJob' :: TransformJob -> Maybe Text
failureReason} -> Maybe Text
failureReason) (\s :: TransformJob
s@TransformJob' {} Maybe Text
a -> TransformJob
s {$sel:failureReason:TransformJob' :: Maybe Text
failureReason = Maybe Text
a} :: TransformJob)

-- | The Amazon Resource Name (ARN) of the labeling job that created the
-- transform job.
transformJob_labelingJobArn :: Lens.Lens' TransformJob (Prelude.Maybe Prelude.Text)
transformJob_labelingJobArn :: Lens' TransformJob (Maybe Text)
transformJob_labelingJobArn = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\TransformJob' {Maybe Text
labelingJobArn :: Maybe Text
$sel:labelingJobArn:TransformJob' :: TransformJob -> Maybe Text
labelingJobArn} -> Maybe Text
labelingJobArn) (\s :: TransformJob
s@TransformJob' {} Maybe Text
a -> TransformJob
s {$sel:labelingJobArn:TransformJob' :: Maybe Text
labelingJobArn = Maybe Text
a} :: TransformJob)

-- | The maximum number of parallel requests that can be sent to each
-- instance in a transform job. If @MaxConcurrentTransforms@ is set to 0 or
-- left unset, SageMaker checks the optional execution-parameters to
-- determine the settings for your chosen algorithm. If the
-- execution-parameters endpoint is not enabled, the default value is 1.
-- For built-in algorithms, you don\'t need to set a value for
-- @MaxConcurrentTransforms@.
transformJob_maxConcurrentTransforms :: Lens.Lens' TransformJob (Prelude.Maybe Prelude.Natural)
transformJob_maxConcurrentTransforms :: Lens' TransformJob (Maybe Natural)
transformJob_maxConcurrentTransforms = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\TransformJob' {Maybe Natural
maxConcurrentTransforms :: Maybe Natural
$sel:maxConcurrentTransforms:TransformJob' :: TransformJob -> Maybe Natural
maxConcurrentTransforms} -> Maybe Natural
maxConcurrentTransforms) (\s :: TransformJob
s@TransformJob' {} Maybe Natural
a -> TransformJob
s {$sel:maxConcurrentTransforms:TransformJob' :: Maybe Natural
maxConcurrentTransforms = Maybe Natural
a} :: TransformJob)

-- | The maximum allowed size of the payload, in MB. A payload is the data
-- portion of a record (without metadata). The value in @MaxPayloadInMB@
-- must be greater than, or equal to, the size of a single record. To
-- estimate the size of a record in MB, divide the size of your dataset by
-- the number of records. To ensure that the records fit within the maximum
-- payload size, we recommend using a slightly larger value. The default
-- value is 6 MB. For cases where the payload might be arbitrarily large
-- and is transmitted using HTTP chunked encoding, set the value to 0. This
-- feature works only in supported algorithms. Currently, SageMaker
-- built-in algorithms do not support HTTP chunked encoding.
transformJob_maxPayloadInMB :: Lens.Lens' TransformJob (Prelude.Maybe Prelude.Natural)
transformJob_maxPayloadInMB :: Lens' TransformJob (Maybe Natural)
transformJob_maxPayloadInMB = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\TransformJob' {Maybe Natural
maxPayloadInMB :: Maybe Natural
$sel:maxPayloadInMB:TransformJob' :: TransformJob -> Maybe Natural
maxPayloadInMB} -> Maybe Natural
maxPayloadInMB) (\s :: TransformJob
s@TransformJob' {} Maybe Natural
a -> TransformJob
s {$sel:maxPayloadInMB:TransformJob' :: Maybe Natural
maxPayloadInMB = Maybe Natural
a} :: TransformJob)

-- | Undocumented member.
transformJob_modelClientConfig :: Lens.Lens' TransformJob (Prelude.Maybe ModelClientConfig)
transformJob_modelClientConfig :: Lens' TransformJob (Maybe ModelClientConfig)
transformJob_modelClientConfig = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\TransformJob' {Maybe ModelClientConfig
modelClientConfig :: Maybe ModelClientConfig
$sel:modelClientConfig:TransformJob' :: TransformJob -> Maybe ModelClientConfig
modelClientConfig} -> Maybe ModelClientConfig
modelClientConfig) (\s :: TransformJob
s@TransformJob' {} Maybe ModelClientConfig
a -> TransformJob
s {$sel:modelClientConfig:TransformJob' :: Maybe ModelClientConfig
modelClientConfig = Maybe ModelClientConfig
a} :: TransformJob)

-- | The name of the model associated with the transform job.
transformJob_modelName :: Lens.Lens' TransformJob (Prelude.Maybe Prelude.Text)
transformJob_modelName :: Lens' TransformJob (Maybe Text)
transformJob_modelName = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\TransformJob' {Maybe Text
modelName :: Maybe Text
$sel:modelName:TransformJob' :: TransformJob -> Maybe Text
modelName} -> Maybe Text
modelName) (\s :: TransformJob
s@TransformJob' {} Maybe Text
a -> TransformJob
s {$sel:modelName:TransformJob' :: Maybe Text
modelName = Maybe Text
a} :: TransformJob)

-- | A list of tags associated with the transform job.
transformJob_tags :: Lens.Lens' TransformJob (Prelude.Maybe [Tag])
transformJob_tags :: Lens' TransformJob (Maybe [Tag])
transformJob_tags = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\TransformJob' {Maybe [Tag]
tags :: Maybe [Tag]
$sel:tags:TransformJob' :: TransformJob -> Maybe [Tag]
tags} -> Maybe [Tag]
tags) (\s :: TransformJob
s@TransformJob' {} Maybe [Tag]
a -> TransformJob
s {$sel:tags:TransformJob' :: Maybe [Tag]
tags = Maybe [Tag]
a} :: TransformJob) 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

-- | Indicates when the transform job has been completed, or has stopped or
-- failed. You are billed for the time interval between this time and the
-- value of @TransformStartTime@.
transformJob_transformEndTime :: Lens.Lens' TransformJob (Prelude.Maybe Prelude.UTCTime)
transformJob_transformEndTime :: Lens' TransformJob (Maybe UTCTime)
transformJob_transformEndTime = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\TransformJob' {Maybe POSIX
transformEndTime :: Maybe POSIX
$sel:transformEndTime:TransformJob' :: TransformJob -> Maybe POSIX
transformEndTime} -> Maybe POSIX
transformEndTime) (\s :: TransformJob
s@TransformJob' {} Maybe POSIX
a -> TransformJob
s {$sel:transformEndTime:TransformJob' :: Maybe POSIX
transformEndTime = Maybe POSIX
a} :: TransformJob) 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

-- | Undocumented member.
transformJob_transformInput :: Lens.Lens' TransformJob (Prelude.Maybe TransformInput)
transformJob_transformInput :: Lens' TransformJob (Maybe TransformInput)
transformJob_transformInput = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\TransformJob' {Maybe TransformInput
transformInput :: Maybe TransformInput
$sel:transformInput:TransformJob' :: TransformJob -> Maybe TransformInput
transformInput} -> Maybe TransformInput
transformInput) (\s :: TransformJob
s@TransformJob' {} Maybe TransformInput
a -> TransformJob
s {$sel:transformInput:TransformJob' :: Maybe TransformInput
transformInput = Maybe TransformInput
a} :: TransformJob)

-- | The Amazon Resource Name (ARN) of the transform job.
transformJob_transformJobArn :: Lens.Lens' TransformJob (Prelude.Maybe Prelude.Text)
transformJob_transformJobArn :: Lens' TransformJob (Maybe Text)
transformJob_transformJobArn = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\TransformJob' {Maybe Text
transformJobArn :: Maybe Text
$sel:transformJobArn:TransformJob' :: TransformJob -> Maybe Text
transformJobArn} -> Maybe Text
transformJobArn) (\s :: TransformJob
s@TransformJob' {} Maybe Text
a -> TransformJob
s {$sel:transformJobArn:TransformJob' :: Maybe Text
transformJobArn = Maybe Text
a} :: TransformJob)

-- | The name of the transform job.
transformJob_transformJobName :: Lens.Lens' TransformJob (Prelude.Maybe Prelude.Text)
transformJob_transformJobName :: Lens' TransformJob (Maybe Text)
transformJob_transformJobName = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\TransformJob' {Maybe Text
transformJobName :: Maybe Text
$sel:transformJobName:TransformJob' :: TransformJob -> Maybe Text
transformJobName} -> Maybe Text
transformJobName) (\s :: TransformJob
s@TransformJob' {} Maybe Text
a -> TransformJob
s {$sel:transformJobName:TransformJob' :: Maybe Text
transformJobName = Maybe Text
a} :: TransformJob)

-- | The status of the transform job.
--
-- Transform job statuses are:
--
-- -   @InProgress@ - The job is in progress.
--
-- -   @Completed@ - The job has completed.
--
-- -   @Failed@ - The transform job has failed. To see the reason for the
--     failure, see the @FailureReason@ field in the response to a
--     @DescribeTransformJob@ call.
--
-- -   @Stopping@ - The transform job is stopping.
--
-- -   @Stopped@ - The transform job has stopped.
transformJob_transformJobStatus :: Lens.Lens' TransformJob (Prelude.Maybe TransformJobStatus)
transformJob_transformJobStatus :: Lens' TransformJob (Maybe TransformJobStatus)
transformJob_transformJobStatus = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\TransformJob' {Maybe TransformJobStatus
transformJobStatus :: Maybe TransformJobStatus
$sel:transformJobStatus:TransformJob' :: TransformJob -> Maybe TransformJobStatus
transformJobStatus} -> Maybe TransformJobStatus
transformJobStatus) (\s :: TransformJob
s@TransformJob' {} Maybe TransformJobStatus
a -> TransformJob
s {$sel:transformJobStatus:TransformJob' :: Maybe TransformJobStatus
transformJobStatus = Maybe TransformJobStatus
a} :: TransformJob)

-- | Undocumented member.
transformJob_transformOutput :: Lens.Lens' TransformJob (Prelude.Maybe TransformOutput)
transformJob_transformOutput :: Lens' TransformJob (Maybe TransformOutput)
transformJob_transformOutput = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\TransformJob' {Maybe TransformOutput
transformOutput :: Maybe TransformOutput
$sel:transformOutput:TransformJob' :: TransformJob -> Maybe TransformOutput
transformOutput} -> Maybe TransformOutput
transformOutput) (\s :: TransformJob
s@TransformJob' {} Maybe TransformOutput
a -> TransformJob
s {$sel:transformOutput:TransformJob' :: Maybe TransformOutput
transformOutput = Maybe TransformOutput
a} :: TransformJob)

-- | Undocumented member.
transformJob_transformResources :: Lens.Lens' TransformJob (Prelude.Maybe TransformResources)
transformJob_transformResources :: Lens' TransformJob (Maybe TransformResources)
transformJob_transformResources = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\TransformJob' {Maybe TransformResources
transformResources :: Maybe TransformResources
$sel:transformResources:TransformJob' :: TransformJob -> Maybe TransformResources
transformResources} -> Maybe TransformResources
transformResources) (\s :: TransformJob
s@TransformJob' {} Maybe TransformResources
a -> TransformJob
s {$sel:transformResources:TransformJob' :: Maybe TransformResources
transformResources = Maybe TransformResources
a} :: TransformJob)

-- | Indicates when the transform job starts on ML instances. You are billed
-- for the time interval between this time and the value of
-- @TransformEndTime@.
transformJob_transformStartTime :: Lens.Lens' TransformJob (Prelude.Maybe Prelude.UTCTime)
transformJob_transformStartTime :: Lens' TransformJob (Maybe UTCTime)
transformJob_transformStartTime = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\TransformJob' {Maybe POSIX
transformStartTime :: Maybe POSIX
$sel:transformStartTime:TransformJob' :: TransformJob -> Maybe POSIX
transformStartTime} -> Maybe POSIX
transformStartTime) (\s :: TransformJob
s@TransformJob' {} Maybe POSIX
a -> TransformJob
s {$sel:transformStartTime:TransformJob' :: Maybe POSIX
transformStartTime = Maybe POSIX
a} :: TransformJob) 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

instance Data.FromJSON TransformJob where
  parseJSON :: Value -> Parser TransformJob
parseJSON =
    forall a. String -> (Object -> Parser a) -> Value -> Parser a
Data.withObject
      String
"TransformJob"
      ( \Object
x ->
          Maybe Text
-> Maybe BatchStrategy
-> Maybe POSIX
-> Maybe DataProcessing
-> Maybe (HashMap Text Text)
-> Maybe ExperimentConfig
-> Maybe Text
-> Maybe Text
-> Maybe Natural
-> Maybe Natural
-> Maybe ModelClientConfig
-> Maybe Text
-> Maybe [Tag]
-> Maybe POSIX
-> Maybe TransformInput
-> Maybe Text
-> Maybe Text
-> Maybe TransformJobStatus
-> Maybe TransformOutput
-> Maybe TransformResources
-> Maybe POSIX
-> TransformJob
TransformJob'
            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
"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
"BatchStrategy")
            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
"DataProcessing")
            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
"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
"LabelingJobArn")
            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
"MaxConcurrentTransforms")
            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
"MaxPayloadInMB")
            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
"ModelClientConfig")
            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
"ModelName")
            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
"TransformEndTime")
            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
"TransformInput")
            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
"TransformJobArn")
            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
"TransformJobName")
            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
"TransformJobStatus")
            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
"TransformOutput")
            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
"TransformResources")
            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
"TransformStartTime")
      )

instance Prelude.Hashable TransformJob where
  hashWithSalt :: Int -> TransformJob -> Int
hashWithSalt Int
_salt TransformJob' {Maybe Natural
Maybe [Tag]
Maybe Text
Maybe (HashMap Text Text)
Maybe POSIX
Maybe BatchStrategy
Maybe ExperimentConfig
Maybe DataProcessing
Maybe ModelClientConfig
Maybe TransformJobStatus
Maybe TransformOutput
Maybe TransformResources
Maybe TransformInput
transformStartTime :: Maybe POSIX
transformResources :: Maybe TransformResources
transformOutput :: Maybe TransformOutput
transformJobStatus :: Maybe TransformJobStatus
transformJobName :: Maybe Text
transformJobArn :: Maybe Text
transformInput :: Maybe TransformInput
transformEndTime :: Maybe POSIX
tags :: Maybe [Tag]
modelName :: Maybe Text
modelClientConfig :: Maybe ModelClientConfig
maxPayloadInMB :: Maybe Natural
maxConcurrentTransforms :: Maybe Natural
labelingJobArn :: Maybe Text
failureReason :: Maybe Text
experimentConfig :: Maybe ExperimentConfig
environment :: Maybe (HashMap Text Text)
dataProcessing :: Maybe DataProcessing
creationTime :: Maybe POSIX
batchStrategy :: Maybe BatchStrategy
autoMLJobArn :: Maybe Text
$sel:transformStartTime:TransformJob' :: TransformJob -> Maybe POSIX
$sel:transformResources:TransformJob' :: TransformJob -> Maybe TransformResources
$sel:transformOutput:TransformJob' :: TransformJob -> Maybe TransformOutput
$sel:transformJobStatus:TransformJob' :: TransformJob -> Maybe TransformJobStatus
$sel:transformJobName:TransformJob' :: TransformJob -> Maybe Text
$sel:transformJobArn:TransformJob' :: TransformJob -> Maybe Text
$sel:transformInput:TransformJob' :: TransformJob -> Maybe TransformInput
$sel:transformEndTime:TransformJob' :: TransformJob -> Maybe POSIX
$sel:tags:TransformJob' :: TransformJob -> Maybe [Tag]
$sel:modelName:TransformJob' :: TransformJob -> Maybe Text
$sel:modelClientConfig:TransformJob' :: TransformJob -> Maybe ModelClientConfig
$sel:maxPayloadInMB:TransformJob' :: TransformJob -> Maybe Natural
$sel:maxConcurrentTransforms:TransformJob' :: TransformJob -> Maybe Natural
$sel:labelingJobArn:TransformJob' :: TransformJob -> Maybe Text
$sel:failureReason:TransformJob' :: TransformJob -> Maybe Text
$sel:experimentConfig:TransformJob' :: TransformJob -> Maybe ExperimentConfig
$sel:environment:TransformJob' :: TransformJob -> Maybe (HashMap Text Text)
$sel:dataProcessing:TransformJob' :: TransformJob -> Maybe DataProcessing
$sel:creationTime:TransformJob' :: TransformJob -> Maybe POSIX
$sel:batchStrategy:TransformJob' :: TransformJob -> Maybe BatchStrategy
$sel:autoMLJobArn:TransformJob' :: TransformJob -> Maybe Text
..} =
    Int
_salt
      forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Maybe Text
autoMLJobArn
      forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Maybe BatchStrategy
batchStrategy
      forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Maybe POSIX
creationTime
      forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Maybe DataProcessing
dataProcessing
      forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Maybe (HashMap Text Text)
environment
      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 Text
labelingJobArn
      forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Maybe Natural
maxConcurrentTransforms
      forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Maybe Natural
maxPayloadInMB
      forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Maybe ModelClientConfig
modelClientConfig
      forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Maybe Text
modelName
      forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Maybe [Tag]
tags
      forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Maybe POSIX
transformEndTime
      forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Maybe TransformInput
transformInput
      forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Maybe Text
transformJobArn
      forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Maybe Text
transformJobName
      forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Maybe TransformJobStatus
transformJobStatus
      forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Maybe TransformOutput
transformOutput
      forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Maybe TransformResources
transformResources
      forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Maybe POSIX
transformStartTime

instance Prelude.NFData TransformJob where
  rnf :: TransformJob -> ()
rnf TransformJob' {Maybe Natural
Maybe [Tag]
Maybe Text
Maybe (HashMap Text Text)
Maybe POSIX
Maybe BatchStrategy
Maybe ExperimentConfig
Maybe DataProcessing
Maybe ModelClientConfig
Maybe TransformJobStatus
Maybe TransformOutput
Maybe TransformResources
Maybe TransformInput
transformStartTime :: Maybe POSIX
transformResources :: Maybe TransformResources
transformOutput :: Maybe TransformOutput
transformJobStatus :: Maybe TransformJobStatus
transformJobName :: Maybe Text
transformJobArn :: Maybe Text
transformInput :: Maybe TransformInput
transformEndTime :: Maybe POSIX
tags :: Maybe [Tag]
modelName :: Maybe Text
modelClientConfig :: Maybe ModelClientConfig
maxPayloadInMB :: Maybe Natural
maxConcurrentTransforms :: Maybe Natural
labelingJobArn :: Maybe Text
failureReason :: Maybe Text
experimentConfig :: Maybe ExperimentConfig
environment :: Maybe (HashMap Text Text)
dataProcessing :: Maybe DataProcessing
creationTime :: Maybe POSIX
batchStrategy :: Maybe BatchStrategy
autoMLJobArn :: Maybe Text
$sel:transformStartTime:TransformJob' :: TransformJob -> Maybe POSIX
$sel:transformResources:TransformJob' :: TransformJob -> Maybe TransformResources
$sel:transformOutput:TransformJob' :: TransformJob -> Maybe TransformOutput
$sel:transformJobStatus:TransformJob' :: TransformJob -> Maybe TransformJobStatus
$sel:transformJobName:TransformJob' :: TransformJob -> Maybe Text
$sel:transformJobArn:TransformJob' :: TransformJob -> Maybe Text
$sel:transformInput:TransformJob' :: TransformJob -> Maybe TransformInput
$sel:transformEndTime:TransformJob' :: TransformJob -> Maybe POSIX
$sel:tags:TransformJob' :: TransformJob -> Maybe [Tag]
$sel:modelName:TransformJob' :: TransformJob -> Maybe Text
$sel:modelClientConfig:TransformJob' :: TransformJob -> Maybe ModelClientConfig
$sel:maxPayloadInMB:TransformJob' :: TransformJob -> Maybe Natural
$sel:maxConcurrentTransforms:TransformJob' :: TransformJob -> Maybe Natural
$sel:labelingJobArn:TransformJob' :: TransformJob -> Maybe Text
$sel:failureReason:TransformJob' :: TransformJob -> Maybe Text
$sel:experimentConfig:TransformJob' :: TransformJob -> Maybe ExperimentConfig
$sel:environment:TransformJob' :: TransformJob -> Maybe (HashMap Text Text)
$sel:dataProcessing:TransformJob' :: TransformJob -> Maybe DataProcessing
$sel:creationTime:TransformJob' :: TransformJob -> Maybe POSIX
$sel:batchStrategy:TransformJob' :: TransformJob -> Maybe BatchStrategy
$sel:autoMLJobArn:TransformJob' :: TransformJob -> 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 BatchStrategy
batchStrategy
      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 DataProcessing
dataProcessing
      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 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 Text
labelingJobArn
      seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf Maybe Natural
maxConcurrentTransforms
      seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf Maybe Natural
maxPayloadInMB
      seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf Maybe ModelClientConfig
modelClientConfig
      seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf Maybe Text
modelName
      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 POSIX
transformEndTime
      seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf Maybe TransformInput
transformInput
      seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf Maybe Text
transformJobArn
      seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf Maybe Text
transformJobName
      seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf Maybe TransformJobStatus
transformJobStatus
      seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf Maybe TransformOutput
transformOutput
      seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf Maybe TransformResources
transformResources
      seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf
        Maybe POSIX
transformStartTime