{-# 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.Glue.CreateMLTransform
-- Copyright   : (c) 2013-2023 Brendan Hay
-- License     : Mozilla Public License, v. 2.0.
-- Maintainer  : Brendan Hay
-- Stability   : auto-generated
-- Portability : non-portable (GHC extensions)
--
-- Creates an Glue machine learning transform. This operation creates the
-- transform and all the necessary parameters to train it.
--
-- Call this operation as the first step in the process of using a machine
-- learning transform (such as the @FindMatches@ transform) for
-- deduplicating data. You can provide an optional @Description@, in
-- addition to the parameters that you want to use for your algorithm.
--
-- You must also specify certain parameters for the tasks that Glue runs on
-- your behalf as part of learning from your data and creating a
-- high-quality machine learning transform. These parameters include
-- @Role@, and optionally, @AllocatedCapacity@, @Timeout@, and
-- @MaxRetries@. For more information, see
-- <https://docs.aws.amazon.com/glue/latest/dg/aws-glue-api-jobs-job.html Jobs>.
module Amazonka.Glue.CreateMLTransform
  ( -- * Creating a Request
    CreateMLTransform (..),
    newCreateMLTransform,

    -- * Request Lenses
    createMLTransform_description,
    createMLTransform_glueVersion,
    createMLTransform_maxCapacity,
    createMLTransform_maxRetries,
    createMLTransform_numberOfWorkers,
    createMLTransform_tags,
    createMLTransform_timeout,
    createMLTransform_transformEncryption,
    createMLTransform_workerType,
    createMLTransform_name,
    createMLTransform_inputRecordTables,
    createMLTransform_parameters,
    createMLTransform_role,

    -- * Destructuring the Response
    CreateMLTransformResponse (..),
    newCreateMLTransformResponse,

    -- * Response Lenses
    createMLTransformResponse_transformId,
    createMLTransformResponse_httpStatus,
  )
where

import qualified Amazonka.Core as Core
import qualified Amazonka.Core.Lens.Internal as Lens
import qualified Amazonka.Data as Data
import Amazonka.Glue.Types
import qualified Amazonka.Prelude as Prelude
import qualified Amazonka.Request as Request
import qualified Amazonka.Response as Response

-- | /See:/ 'newCreateMLTransform' smart constructor.
data CreateMLTransform = CreateMLTransform'
  { -- | A description of the machine learning transform that is being defined.
    -- The default is an empty string.
    CreateMLTransform -> Maybe Text
description :: Prelude.Maybe Prelude.Text,
    -- | This value determines which version of Glue this machine learning
    -- transform is compatible with. Glue 1.0 is recommended for most
    -- customers. If the value is not set, the Glue compatibility defaults to
    -- Glue 0.9. For more information, see
    -- <https://docs.aws.amazon.com/glue/latest/dg/release-notes.html#release-notes-versions Glue Versions>
    -- in the developer guide.
    CreateMLTransform -> Maybe Text
glueVersion :: Prelude.Maybe Prelude.Text,
    -- | The number of Glue data processing units (DPUs) that are allocated to
    -- task runs for this transform. You can allocate from 2 to 100 DPUs; the
    -- default is 10. A DPU is a relative measure of processing power that
    -- consists of 4 vCPUs of compute capacity and 16 GB of memory. For more
    -- information, see the
    -- <https://aws.amazon.com/glue/pricing/ Glue pricing page>.
    --
    -- @MaxCapacity@ is a mutually exclusive option with @NumberOfWorkers@ and
    -- @WorkerType@.
    --
    -- -   If either @NumberOfWorkers@ or @WorkerType@ is set, then
    --     @MaxCapacity@ cannot be set.
    --
    -- -   If @MaxCapacity@ is set then neither @NumberOfWorkers@ or
    --     @WorkerType@ can be set.
    --
    -- -   If @WorkerType@ is set, then @NumberOfWorkers@ is required (and vice
    --     versa).
    --
    -- -   @MaxCapacity@ and @NumberOfWorkers@ must both be at least 1.
    --
    -- When the @WorkerType@ field is set to a value other than @Standard@, the
    -- @MaxCapacity@ field is set automatically and becomes read-only.
    --
    -- When the @WorkerType@ field is set to a value other than @Standard@, the
    -- @MaxCapacity@ field is set automatically and becomes read-only.
    CreateMLTransform -> Maybe Double
maxCapacity :: Prelude.Maybe Prelude.Double,
    -- | The maximum number of times to retry a task for this transform after a
    -- task run fails.
    CreateMLTransform -> Maybe Int
maxRetries :: Prelude.Maybe Prelude.Int,
    -- | The number of workers of a defined @workerType@ that are allocated when
    -- this task runs.
    --
    -- If @WorkerType@ is set, then @NumberOfWorkers@ is required (and vice
    -- versa).
    CreateMLTransform -> Maybe Int
numberOfWorkers :: Prelude.Maybe Prelude.Int,
    -- | The tags to use with this machine learning transform. You may use tags
    -- to limit access to the machine learning transform. For more information
    -- about tags in Glue, see
    -- <https://docs.aws.amazon.com/glue/latest/dg/monitor-tags.html Amazon Web Services Tags in Glue>
    -- in the developer guide.
    CreateMLTransform -> Maybe (HashMap Text Text)
tags :: Prelude.Maybe (Prelude.HashMap Prelude.Text Prelude.Text),
    -- | The timeout of the task run for this transform in minutes. This is the
    -- maximum time that a task run for this transform can consume resources
    -- before it is terminated and enters @TIMEOUT@ status. The default is
    -- 2,880 minutes (48 hours).
    CreateMLTransform -> Maybe Natural
timeout :: Prelude.Maybe Prelude.Natural,
    -- | The encryption-at-rest settings of the transform that apply to accessing
    -- user data. Machine learning transforms can access user data encrypted in
    -- Amazon S3 using KMS.
    CreateMLTransform -> Maybe TransformEncryption
transformEncryption :: Prelude.Maybe TransformEncryption,
    -- | The type of predefined worker that is allocated when this task runs.
    -- Accepts a value of Standard, G.1X, or G.2X.
    --
    -- -   For the @Standard@ worker type, each worker provides 4 vCPU, 16 GB
    --     of memory and a 50GB disk, and 2 executors per worker.
    --
    -- -   For the @G.1X@ worker type, each worker provides 4 vCPU, 16 GB of
    --     memory and a 64GB disk, and 1 executor per worker.
    --
    -- -   For the @G.2X@ worker type, each worker provides 8 vCPU, 32 GB of
    --     memory and a 128GB disk, and 1 executor per worker.
    --
    -- @MaxCapacity@ is a mutually exclusive option with @NumberOfWorkers@ and
    -- @WorkerType@.
    --
    -- -   If either @NumberOfWorkers@ or @WorkerType@ is set, then
    --     @MaxCapacity@ cannot be set.
    --
    -- -   If @MaxCapacity@ is set then neither @NumberOfWorkers@ or
    --     @WorkerType@ can be set.
    --
    -- -   If @WorkerType@ is set, then @NumberOfWorkers@ is required (and vice
    --     versa).
    --
    -- -   @MaxCapacity@ and @NumberOfWorkers@ must both be at least 1.
    CreateMLTransform -> Maybe WorkerType
workerType :: Prelude.Maybe WorkerType,
    -- | The unique name that you give the transform when you create it.
    CreateMLTransform -> Text
name :: Prelude.Text,
    -- | A list of Glue table definitions used by the transform.
    CreateMLTransform -> [GlueTable]
inputRecordTables :: [GlueTable],
    -- | The algorithmic parameters that are specific to the transform type used.
    -- Conditionally dependent on the transform type.
    CreateMLTransform -> TransformParameters
parameters :: TransformParameters,
    -- | The name or Amazon Resource Name (ARN) of the IAM role with the required
    -- permissions. The required permissions include both Glue service role
    -- permissions to Glue resources, and Amazon S3 permissions required by the
    -- transform.
    --
    -- -   This role needs Glue service role permissions to allow access to
    --     resources in Glue. See
    --     <https://docs.aws.amazon.com/glue/latest/dg/attach-policy-iam-user.html Attach a Policy to IAM Users That Access Glue>.
    --
    -- -   This role needs permission to your Amazon Simple Storage Service
    --     (Amazon S3) sources, targets, temporary directory, scripts, and any
    --     libraries used by the task run for this transform.
    CreateMLTransform -> Text
role' :: Prelude.Text
  }
  deriving (CreateMLTransform -> CreateMLTransform -> Bool
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: CreateMLTransform -> CreateMLTransform -> Bool
$c/= :: CreateMLTransform -> CreateMLTransform -> Bool
== :: CreateMLTransform -> CreateMLTransform -> Bool
$c== :: CreateMLTransform -> CreateMLTransform -> Bool
Prelude.Eq, ReadPrec [CreateMLTransform]
ReadPrec CreateMLTransform
Int -> ReadS CreateMLTransform
ReadS [CreateMLTransform]
forall a.
(Int -> ReadS a)
-> ReadS [a] -> ReadPrec a -> ReadPrec [a] -> Read a
readListPrec :: ReadPrec [CreateMLTransform]
$creadListPrec :: ReadPrec [CreateMLTransform]
readPrec :: ReadPrec CreateMLTransform
$creadPrec :: ReadPrec CreateMLTransform
readList :: ReadS [CreateMLTransform]
$creadList :: ReadS [CreateMLTransform]
readsPrec :: Int -> ReadS CreateMLTransform
$creadsPrec :: Int -> ReadS CreateMLTransform
Prelude.Read, Int -> CreateMLTransform -> ShowS
[CreateMLTransform] -> ShowS
CreateMLTransform -> String
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [CreateMLTransform] -> ShowS
$cshowList :: [CreateMLTransform] -> ShowS
show :: CreateMLTransform -> String
$cshow :: CreateMLTransform -> String
showsPrec :: Int -> CreateMLTransform -> ShowS
$cshowsPrec :: Int -> CreateMLTransform -> ShowS
Prelude.Show, forall x. Rep CreateMLTransform x -> CreateMLTransform
forall x. CreateMLTransform -> Rep CreateMLTransform x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cto :: forall x. Rep CreateMLTransform x -> CreateMLTransform
$cfrom :: forall x. CreateMLTransform -> Rep CreateMLTransform x
Prelude.Generic)

-- |
-- Create a value of 'CreateMLTransform' 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:
--
-- 'description', 'createMLTransform_description' - A description of the machine learning transform that is being defined.
-- The default is an empty string.
--
-- 'glueVersion', 'createMLTransform_glueVersion' - This value determines which version of Glue this machine learning
-- transform is compatible with. Glue 1.0 is recommended for most
-- customers. If the value is not set, the Glue compatibility defaults to
-- Glue 0.9. For more information, see
-- <https://docs.aws.amazon.com/glue/latest/dg/release-notes.html#release-notes-versions Glue Versions>
-- in the developer guide.
--
-- 'maxCapacity', 'createMLTransform_maxCapacity' - The number of Glue data processing units (DPUs) that are allocated to
-- task runs for this transform. You can allocate from 2 to 100 DPUs; the
-- default is 10. A DPU is a relative measure of processing power that
-- consists of 4 vCPUs of compute capacity and 16 GB of memory. For more
-- information, see the
-- <https://aws.amazon.com/glue/pricing/ Glue pricing page>.
--
-- @MaxCapacity@ is a mutually exclusive option with @NumberOfWorkers@ and
-- @WorkerType@.
--
-- -   If either @NumberOfWorkers@ or @WorkerType@ is set, then
--     @MaxCapacity@ cannot be set.
--
-- -   If @MaxCapacity@ is set then neither @NumberOfWorkers@ or
--     @WorkerType@ can be set.
--
-- -   If @WorkerType@ is set, then @NumberOfWorkers@ is required (and vice
--     versa).
--
-- -   @MaxCapacity@ and @NumberOfWorkers@ must both be at least 1.
--
-- When the @WorkerType@ field is set to a value other than @Standard@, the
-- @MaxCapacity@ field is set automatically and becomes read-only.
--
-- When the @WorkerType@ field is set to a value other than @Standard@, the
-- @MaxCapacity@ field is set automatically and becomes read-only.
--
-- 'maxRetries', 'createMLTransform_maxRetries' - The maximum number of times to retry a task for this transform after a
-- task run fails.
--
-- 'numberOfWorkers', 'createMLTransform_numberOfWorkers' - The number of workers of a defined @workerType@ that are allocated when
-- this task runs.
--
-- If @WorkerType@ is set, then @NumberOfWorkers@ is required (and vice
-- versa).
--
-- 'tags', 'createMLTransform_tags' - The tags to use with this machine learning transform. You may use tags
-- to limit access to the machine learning transform. For more information
-- about tags in Glue, see
-- <https://docs.aws.amazon.com/glue/latest/dg/monitor-tags.html Amazon Web Services Tags in Glue>
-- in the developer guide.
--
-- 'timeout', 'createMLTransform_timeout' - The timeout of the task run for this transform in minutes. This is the
-- maximum time that a task run for this transform can consume resources
-- before it is terminated and enters @TIMEOUT@ status. The default is
-- 2,880 minutes (48 hours).
--
-- 'transformEncryption', 'createMLTransform_transformEncryption' - The encryption-at-rest settings of the transform that apply to accessing
-- user data. Machine learning transforms can access user data encrypted in
-- Amazon S3 using KMS.
--
-- 'workerType', 'createMLTransform_workerType' - The type of predefined worker that is allocated when this task runs.
-- Accepts a value of Standard, G.1X, or G.2X.
--
-- -   For the @Standard@ worker type, each worker provides 4 vCPU, 16 GB
--     of memory and a 50GB disk, and 2 executors per worker.
--
-- -   For the @G.1X@ worker type, each worker provides 4 vCPU, 16 GB of
--     memory and a 64GB disk, and 1 executor per worker.
--
-- -   For the @G.2X@ worker type, each worker provides 8 vCPU, 32 GB of
--     memory and a 128GB disk, and 1 executor per worker.
--
-- @MaxCapacity@ is a mutually exclusive option with @NumberOfWorkers@ and
-- @WorkerType@.
--
-- -   If either @NumberOfWorkers@ or @WorkerType@ is set, then
--     @MaxCapacity@ cannot be set.
--
-- -   If @MaxCapacity@ is set then neither @NumberOfWorkers@ or
--     @WorkerType@ can be set.
--
-- -   If @WorkerType@ is set, then @NumberOfWorkers@ is required (and vice
--     versa).
--
-- -   @MaxCapacity@ and @NumberOfWorkers@ must both be at least 1.
--
-- 'name', 'createMLTransform_name' - The unique name that you give the transform when you create it.
--
-- 'inputRecordTables', 'createMLTransform_inputRecordTables' - A list of Glue table definitions used by the transform.
--
-- 'parameters', 'createMLTransform_parameters' - The algorithmic parameters that are specific to the transform type used.
-- Conditionally dependent on the transform type.
--
-- 'role'', 'createMLTransform_role' - The name or Amazon Resource Name (ARN) of the IAM role with the required
-- permissions. The required permissions include both Glue service role
-- permissions to Glue resources, and Amazon S3 permissions required by the
-- transform.
--
-- -   This role needs Glue service role permissions to allow access to
--     resources in Glue. See
--     <https://docs.aws.amazon.com/glue/latest/dg/attach-policy-iam-user.html Attach a Policy to IAM Users That Access Glue>.
--
-- -   This role needs permission to your Amazon Simple Storage Service
--     (Amazon S3) sources, targets, temporary directory, scripts, and any
--     libraries used by the task run for this transform.
newCreateMLTransform ::
  -- | 'name'
  Prelude.Text ->
  -- | 'parameters'
  TransformParameters ->
  -- | 'role''
  Prelude.Text ->
  CreateMLTransform
newCreateMLTransform :: Text -> TransformParameters -> Text -> CreateMLTransform
newCreateMLTransform Text
pName_ TransformParameters
pParameters_ Text
pRole_ =
  CreateMLTransform'
    { $sel:description:CreateMLTransform' :: Maybe Text
description = forall a. Maybe a
Prelude.Nothing,
      $sel:glueVersion:CreateMLTransform' :: Maybe Text
glueVersion = forall a. Maybe a
Prelude.Nothing,
      $sel:maxCapacity:CreateMLTransform' :: Maybe Double
maxCapacity = forall a. Maybe a
Prelude.Nothing,
      $sel:maxRetries:CreateMLTransform' :: Maybe Int
maxRetries = forall a. Maybe a
Prelude.Nothing,
      $sel:numberOfWorkers:CreateMLTransform' :: Maybe Int
numberOfWorkers = forall a. Maybe a
Prelude.Nothing,
      $sel:tags:CreateMLTransform' :: Maybe (HashMap Text Text)
tags = forall a. Maybe a
Prelude.Nothing,
      $sel:timeout:CreateMLTransform' :: Maybe Natural
timeout = forall a. Maybe a
Prelude.Nothing,
      $sel:transformEncryption:CreateMLTransform' :: Maybe TransformEncryption
transformEncryption = forall a. Maybe a
Prelude.Nothing,
      $sel:workerType:CreateMLTransform' :: Maybe WorkerType
workerType = forall a. Maybe a
Prelude.Nothing,
      $sel:name:CreateMLTransform' :: Text
name = Text
pName_,
      $sel:inputRecordTables:CreateMLTransform' :: [GlueTable]
inputRecordTables = forall a. Monoid a => a
Prelude.mempty,
      $sel:parameters:CreateMLTransform' :: TransformParameters
parameters = TransformParameters
pParameters_,
      $sel:role':CreateMLTransform' :: Text
role' = Text
pRole_
    }

-- | A description of the machine learning transform that is being defined.
-- The default is an empty string.
createMLTransform_description :: Lens.Lens' CreateMLTransform (Prelude.Maybe Prelude.Text)
createMLTransform_description :: Lens' CreateMLTransform (Maybe Text)
createMLTransform_description = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\CreateMLTransform' {Maybe Text
description :: Maybe Text
$sel:description:CreateMLTransform' :: CreateMLTransform -> Maybe Text
description} -> Maybe Text
description) (\s :: CreateMLTransform
s@CreateMLTransform' {} Maybe Text
a -> CreateMLTransform
s {$sel:description:CreateMLTransform' :: Maybe Text
description = Maybe Text
a} :: CreateMLTransform)

-- | This value determines which version of Glue this machine learning
-- transform is compatible with. Glue 1.0 is recommended for most
-- customers. If the value is not set, the Glue compatibility defaults to
-- Glue 0.9. For more information, see
-- <https://docs.aws.amazon.com/glue/latest/dg/release-notes.html#release-notes-versions Glue Versions>
-- in the developer guide.
createMLTransform_glueVersion :: Lens.Lens' CreateMLTransform (Prelude.Maybe Prelude.Text)
createMLTransform_glueVersion :: Lens' CreateMLTransform (Maybe Text)
createMLTransform_glueVersion = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\CreateMLTransform' {Maybe Text
glueVersion :: Maybe Text
$sel:glueVersion:CreateMLTransform' :: CreateMLTransform -> Maybe Text
glueVersion} -> Maybe Text
glueVersion) (\s :: CreateMLTransform
s@CreateMLTransform' {} Maybe Text
a -> CreateMLTransform
s {$sel:glueVersion:CreateMLTransform' :: Maybe Text
glueVersion = Maybe Text
a} :: CreateMLTransform)

-- | The number of Glue data processing units (DPUs) that are allocated to
-- task runs for this transform. You can allocate from 2 to 100 DPUs; the
-- default is 10. A DPU is a relative measure of processing power that
-- consists of 4 vCPUs of compute capacity and 16 GB of memory. For more
-- information, see the
-- <https://aws.amazon.com/glue/pricing/ Glue pricing page>.
--
-- @MaxCapacity@ is a mutually exclusive option with @NumberOfWorkers@ and
-- @WorkerType@.
--
-- -   If either @NumberOfWorkers@ or @WorkerType@ is set, then
--     @MaxCapacity@ cannot be set.
--
-- -   If @MaxCapacity@ is set then neither @NumberOfWorkers@ or
--     @WorkerType@ can be set.
--
-- -   If @WorkerType@ is set, then @NumberOfWorkers@ is required (and vice
--     versa).
--
-- -   @MaxCapacity@ and @NumberOfWorkers@ must both be at least 1.
--
-- When the @WorkerType@ field is set to a value other than @Standard@, the
-- @MaxCapacity@ field is set automatically and becomes read-only.
--
-- When the @WorkerType@ field is set to a value other than @Standard@, the
-- @MaxCapacity@ field is set automatically and becomes read-only.
createMLTransform_maxCapacity :: Lens.Lens' CreateMLTransform (Prelude.Maybe Prelude.Double)
createMLTransform_maxCapacity :: Lens' CreateMLTransform (Maybe Double)
createMLTransform_maxCapacity = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\CreateMLTransform' {Maybe Double
maxCapacity :: Maybe Double
$sel:maxCapacity:CreateMLTransform' :: CreateMLTransform -> Maybe Double
maxCapacity} -> Maybe Double
maxCapacity) (\s :: CreateMLTransform
s@CreateMLTransform' {} Maybe Double
a -> CreateMLTransform
s {$sel:maxCapacity:CreateMLTransform' :: Maybe Double
maxCapacity = Maybe Double
a} :: CreateMLTransform)

-- | The maximum number of times to retry a task for this transform after a
-- task run fails.
createMLTransform_maxRetries :: Lens.Lens' CreateMLTransform (Prelude.Maybe Prelude.Int)
createMLTransform_maxRetries :: Lens' CreateMLTransform (Maybe Int)
createMLTransform_maxRetries = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\CreateMLTransform' {Maybe Int
maxRetries :: Maybe Int
$sel:maxRetries:CreateMLTransform' :: CreateMLTransform -> Maybe Int
maxRetries} -> Maybe Int
maxRetries) (\s :: CreateMLTransform
s@CreateMLTransform' {} Maybe Int
a -> CreateMLTransform
s {$sel:maxRetries:CreateMLTransform' :: Maybe Int
maxRetries = Maybe Int
a} :: CreateMLTransform)

-- | The number of workers of a defined @workerType@ that are allocated when
-- this task runs.
--
-- If @WorkerType@ is set, then @NumberOfWorkers@ is required (and vice
-- versa).
createMLTransform_numberOfWorkers :: Lens.Lens' CreateMLTransform (Prelude.Maybe Prelude.Int)
createMLTransform_numberOfWorkers :: Lens' CreateMLTransform (Maybe Int)
createMLTransform_numberOfWorkers = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\CreateMLTransform' {Maybe Int
numberOfWorkers :: Maybe Int
$sel:numberOfWorkers:CreateMLTransform' :: CreateMLTransform -> Maybe Int
numberOfWorkers} -> Maybe Int
numberOfWorkers) (\s :: CreateMLTransform
s@CreateMLTransform' {} Maybe Int
a -> CreateMLTransform
s {$sel:numberOfWorkers:CreateMLTransform' :: Maybe Int
numberOfWorkers = Maybe Int
a} :: CreateMLTransform)

-- | The tags to use with this machine learning transform. You may use tags
-- to limit access to the machine learning transform. For more information
-- about tags in Glue, see
-- <https://docs.aws.amazon.com/glue/latest/dg/monitor-tags.html Amazon Web Services Tags in Glue>
-- in the developer guide.
createMLTransform_tags :: Lens.Lens' CreateMLTransform (Prelude.Maybe (Prelude.HashMap Prelude.Text Prelude.Text))
createMLTransform_tags :: Lens' CreateMLTransform (Maybe (HashMap Text Text))
createMLTransform_tags = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\CreateMLTransform' {Maybe (HashMap Text Text)
tags :: Maybe (HashMap Text Text)
$sel:tags:CreateMLTransform' :: CreateMLTransform -> Maybe (HashMap Text Text)
tags} -> Maybe (HashMap Text Text)
tags) (\s :: CreateMLTransform
s@CreateMLTransform' {} Maybe (HashMap Text Text)
a -> CreateMLTransform
s {$sel:tags:CreateMLTransform' :: Maybe (HashMap Text Text)
tags = Maybe (HashMap Text Text)
a} :: CreateMLTransform) forall b c a. (b -> c) -> (a -> b) -> a -> c
Prelude.. forall (f :: * -> *) (g :: * -> *) s t a b.
(Functor f, Functor g) =>
AnIso s t a b -> Iso (f s) (g t) (f a) (g b)
Lens.mapping forall s t a b. (Coercible s a, Coercible t b) => Iso s t a b
Lens.coerced

-- | The timeout of the task run for this transform in minutes. This is the
-- maximum time that a task run for this transform can consume resources
-- before it is terminated and enters @TIMEOUT@ status. The default is
-- 2,880 minutes (48 hours).
createMLTransform_timeout :: Lens.Lens' CreateMLTransform (Prelude.Maybe Prelude.Natural)
createMLTransform_timeout :: Lens' CreateMLTransform (Maybe Natural)
createMLTransform_timeout = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\CreateMLTransform' {Maybe Natural
timeout :: Maybe Natural
$sel:timeout:CreateMLTransform' :: CreateMLTransform -> Maybe Natural
timeout} -> Maybe Natural
timeout) (\s :: CreateMLTransform
s@CreateMLTransform' {} Maybe Natural
a -> CreateMLTransform
s {$sel:timeout:CreateMLTransform' :: Maybe Natural
timeout = Maybe Natural
a} :: CreateMLTransform)

-- | The encryption-at-rest settings of the transform that apply to accessing
-- user data. Machine learning transforms can access user data encrypted in
-- Amazon S3 using KMS.
createMLTransform_transformEncryption :: Lens.Lens' CreateMLTransform (Prelude.Maybe TransformEncryption)
createMLTransform_transformEncryption :: Lens' CreateMLTransform (Maybe TransformEncryption)
createMLTransform_transformEncryption = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\CreateMLTransform' {Maybe TransformEncryption
transformEncryption :: Maybe TransformEncryption
$sel:transformEncryption:CreateMLTransform' :: CreateMLTransform -> Maybe TransformEncryption
transformEncryption} -> Maybe TransformEncryption
transformEncryption) (\s :: CreateMLTransform
s@CreateMLTransform' {} Maybe TransformEncryption
a -> CreateMLTransform
s {$sel:transformEncryption:CreateMLTransform' :: Maybe TransformEncryption
transformEncryption = Maybe TransformEncryption
a} :: CreateMLTransform)

-- | The type of predefined worker that is allocated when this task runs.
-- Accepts a value of Standard, G.1X, or G.2X.
--
-- -   For the @Standard@ worker type, each worker provides 4 vCPU, 16 GB
--     of memory and a 50GB disk, and 2 executors per worker.
--
-- -   For the @G.1X@ worker type, each worker provides 4 vCPU, 16 GB of
--     memory and a 64GB disk, and 1 executor per worker.
--
-- -   For the @G.2X@ worker type, each worker provides 8 vCPU, 32 GB of
--     memory and a 128GB disk, and 1 executor per worker.
--
-- @MaxCapacity@ is a mutually exclusive option with @NumberOfWorkers@ and
-- @WorkerType@.
--
-- -   If either @NumberOfWorkers@ or @WorkerType@ is set, then
--     @MaxCapacity@ cannot be set.
--
-- -   If @MaxCapacity@ is set then neither @NumberOfWorkers@ or
--     @WorkerType@ can be set.
--
-- -   If @WorkerType@ is set, then @NumberOfWorkers@ is required (and vice
--     versa).
--
-- -   @MaxCapacity@ and @NumberOfWorkers@ must both be at least 1.
createMLTransform_workerType :: Lens.Lens' CreateMLTransform (Prelude.Maybe WorkerType)
createMLTransform_workerType :: Lens' CreateMLTransform (Maybe WorkerType)
createMLTransform_workerType = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\CreateMLTransform' {Maybe WorkerType
workerType :: Maybe WorkerType
$sel:workerType:CreateMLTransform' :: CreateMLTransform -> Maybe WorkerType
workerType} -> Maybe WorkerType
workerType) (\s :: CreateMLTransform
s@CreateMLTransform' {} Maybe WorkerType
a -> CreateMLTransform
s {$sel:workerType:CreateMLTransform' :: Maybe WorkerType
workerType = Maybe WorkerType
a} :: CreateMLTransform)

-- | The unique name that you give the transform when you create it.
createMLTransform_name :: Lens.Lens' CreateMLTransform Prelude.Text
createMLTransform_name :: Lens' CreateMLTransform Text
createMLTransform_name = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\CreateMLTransform' {Text
name :: Text
$sel:name:CreateMLTransform' :: CreateMLTransform -> Text
name} -> Text
name) (\s :: CreateMLTransform
s@CreateMLTransform' {} Text
a -> CreateMLTransform
s {$sel:name:CreateMLTransform' :: Text
name = Text
a} :: CreateMLTransform)

-- | A list of Glue table definitions used by the transform.
createMLTransform_inputRecordTables :: Lens.Lens' CreateMLTransform [GlueTable]
createMLTransform_inputRecordTables :: Lens' CreateMLTransform [GlueTable]
createMLTransform_inputRecordTables = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\CreateMLTransform' {[GlueTable]
inputRecordTables :: [GlueTable]
$sel:inputRecordTables:CreateMLTransform' :: CreateMLTransform -> [GlueTable]
inputRecordTables} -> [GlueTable]
inputRecordTables) (\s :: CreateMLTransform
s@CreateMLTransform' {} [GlueTable]
a -> CreateMLTransform
s {$sel:inputRecordTables:CreateMLTransform' :: [GlueTable]
inputRecordTables = [GlueTable]
a} :: CreateMLTransform) forall b c a. (b -> c) -> (a -> b) -> a -> c
Prelude.. forall s t a b. (Coercible s a, Coercible t b) => Iso s t a b
Lens.coerced

-- | The algorithmic parameters that are specific to the transform type used.
-- Conditionally dependent on the transform type.
createMLTransform_parameters :: Lens.Lens' CreateMLTransform TransformParameters
createMLTransform_parameters :: Lens' CreateMLTransform TransformParameters
createMLTransform_parameters = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\CreateMLTransform' {TransformParameters
parameters :: TransformParameters
$sel:parameters:CreateMLTransform' :: CreateMLTransform -> TransformParameters
parameters} -> TransformParameters
parameters) (\s :: CreateMLTransform
s@CreateMLTransform' {} TransformParameters
a -> CreateMLTransform
s {$sel:parameters:CreateMLTransform' :: TransformParameters
parameters = TransformParameters
a} :: CreateMLTransform)

-- | The name or Amazon Resource Name (ARN) of the IAM role with the required
-- permissions. The required permissions include both Glue service role
-- permissions to Glue resources, and Amazon S3 permissions required by the
-- transform.
--
-- -   This role needs Glue service role permissions to allow access to
--     resources in Glue. See
--     <https://docs.aws.amazon.com/glue/latest/dg/attach-policy-iam-user.html Attach a Policy to IAM Users That Access Glue>.
--
-- -   This role needs permission to your Amazon Simple Storage Service
--     (Amazon S3) sources, targets, temporary directory, scripts, and any
--     libraries used by the task run for this transform.
createMLTransform_role :: Lens.Lens' CreateMLTransform Prelude.Text
createMLTransform_role :: Lens' CreateMLTransform Text
createMLTransform_role = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\CreateMLTransform' {Text
role' :: Text
$sel:role':CreateMLTransform' :: CreateMLTransform -> Text
role'} -> Text
role') (\s :: CreateMLTransform
s@CreateMLTransform' {} Text
a -> CreateMLTransform
s {$sel:role':CreateMLTransform' :: Text
role' = Text
a} :: CreateMLTransform)

instance Core.AWSRequest CreateMLTransform where
  type
    AWSResponse CreateMLTransform =
      CreateMLTransformResponse
  request :: (Service -> Service)
-> CreateMLTransform -> Request CreateMLTransform
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 CreateMLTransform
-> ClientResponse ClientBody
-> m (Either
        Error (ClientResponse (AWSResponse CreateMLTransform)))
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 -> Int -> CreateMLTransformResponse
CreateMLTransformResponse'
            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
"TransformId")
            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))
      )

instance Prelude.Hashable CreateMLTransform where
  hashWithSalt :: Int -> CreateMLTransform -> Int
hashWithSalt Int
_salt CreateMLTransform' {[GlueTable]
Maybe Double
Maybe Int
Maybe Natural
Maybe Text
Maybe (HashMap Text Text)
Maybe TransformEncryption
Maybe WorkerType
Text
TransformParameters
role' :: Text
parameters :: TransformParameters
inputRecordTables :: [GlueTable]
name :: Text
workerType :: Maybe WorkerType
transformEncryption :: Maybe TransformEncryption
timeout :: Maybe Natural
tags :: Maybe (HashMap Text Text)
numberOfWorkers :: Maybe Int
maxRetries :: Maybe Int
maxCapacity :: Maybe Double
glueVersion :: Maybe Text
description :: Maybe Text
$sel:role':CreateMLTransform' :: CreateMLTransform -> Text
$sel:parameters:CreateMLTransform' :: CreateMLTransform -> TransformParameters
$sel:inputRecordTables:CreateMLTransform' :: CreateMLTransform -> [GlueTable]
$sel:name:CreateMLTransform' :: CreateMLTransform -> Text
$sel:workerType:CreateMLTransform' :: CreateMLTransform -> Maybe WorkerType
$sel:transformEncryption:CreateMLTransform' :: CreateMLTransform -> Maybe TransformEncryption
$sel:timeout:CreateMLTransform' :: CreateMLTransform -> Maybe Natural
$sel:tags:CreateMLTransform' :: CreateMLTransform -> Maybe (HashMap Text Text)
$sel:numberOfWorkers:CreateMLTransform' :: CreateMLTransform -> Maybe Int
$sel:maxRetries:CreateMLTransform' :: CreateMLTransform -> Maybe Int
$sel:maxCapacity:CreateMLTransform' :: CreateMLTransform -> Maybe Double
$sel:glueVersion:CreateMLTransform' :: CreateMLTransform -> Maybe Text
$sel:description:CreateMLTransform' :: CreateMLTransform -> Maybe Text
..} =
    Int
_salt
      forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Maybe Text
description
      forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Maybe Text
glueVersion
      forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Maybe Double
maxCapacity
      forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Maybe Int
maxRetries
      forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Maybe Int
numberOfWorkers
      forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Maybe (HashMap Text Text)
tags
      forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Maybe Natural
timeout
      forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Maybe TransformEncryption
transformEncryption
      forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Maybe WorkerType
workerType
      forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Text
name
      forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` [GlueTable]
inputRecordTables
      forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` TransformParameters
parameters
      forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Text
role'

instance Prelude.NFData CreateMLTransform where
  rnf :: CreateMLTransform -> ()
rnf CreateMLTransform' {[GlueTable]
Maybe Double
Maybe Int
Maybe Natural
Maybe Text
Maybe (HashMap Text Text)
Maybe TransformEncryption
Maybe WorkerType
Text
TransformParameters
role' :: Text
parameters :: TransformParameters
inputRecordTables :: [GlueTable]
name :: Text
workerType :: Maybe WorkerType
transformEncryption :: Maybe TransformEncryption
timeout :: Maybe Natural
tags :: Maybe (HashMap Text Text)
numberOfWorkers :: Maybe Int
maxRetries :: Maybe Int
maxCapacity :: Maybe Double
glueVersion :: Maybe Text
description :: Maybe Text
$sel:role':CreateMLTransform' :: CreateMLTransform -> Text
$sel:parameters:CreateMLTransform' :: CreateMLTransform -> TransformParameters
$sel:inputRecordTables:CreateMLTransform' :: CreateMLTransform -> [GlueTable]
$sel:name:CreateMLTransform' :: CreateMLTransform -> Text
$sel:workerType:CreateMLTransform' :: CreateMLTransform -> Maybe WorkerType
$sel:transformEncryption:CreateMLTransform' :: CreateMLTransform -> Maybe TransformEncryption
$sel:timeout:CreateMLTransform' :: CreateMLTransform -> Maybe Natural
$sel:tags:CreateMLTransform' :: CreateMLTransform -> Maybe (HashMap Text Text)
$sel:numberOfWorkers:CreateMLTransform' :: CreateMLTransform -> Maybe Int
$sel:maxRetries:CreateMLTransform' :: CreateMLTransform -> Maybe Int
$sel:maxCapacity:CreateMLTransform' :: CreateMLTransform -> Maybe Double
$sel:glueVersion:CreateMLTransform' :: CreateMLTransform -> Maybe Text
$sel:description:CreateMLTransform' :: CreateMLTransform -> Maybe Text
..} =
    forall a. NFData a => a -> ()
Prelude.rnf Maybe Text
description
      seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf Maybe Text
glueVersion
      seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf Maybe Double
maxCapacity
      seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf Maybe Int
maxRetries
      seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf Maybe Int
numberOfWorkers
      seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf Maybe (HashMap Text Text)
tags
      seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf Maybe Natural
timeout
      seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf Maybe TransformEncryption
transformEncryption
      seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf Maybe WorkerType
workerType
      seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf Text
name
      seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf [GlueTable]
inputRecordTables
      seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf TransformParameters
parameters
      seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf Text
role'

instance Data.ToHeaders CreateMLTransform where
  toHeaders :: CreateMLTransform -> 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
"AWSGlue.CreateMLTransform" :: 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 CreateMLTransform where
  toJSON :: CreateMLTransform -> Value
toJSON CreateMLTransform' {[GlueTable]
Maybe Double
Maybe Int
Maybe Natural
Maybe Text
Maybe (HashMap Text Text)
Maybe TransformEncryption
Maybe WorkerType
Text
TransformParameters
role' :: Text
parameters :: TransformParameters
inputRecordTables :: [GlueTable]
name :: Text
workerType :: Maybe WorkerType
transformEncryption :: Maybe TransformEncryption
timeout :: Maybe Natural
tags :: Maybe (HashMap Text Text)
numberOfWorkers :: Maybe Int
maxRetries :: Maybe Int
maxCapacity :: Maybe Double
glueVersion :: Maybe Text
description :: Maybe Text
$sel:role':CreateMLTransform' :: CreateMLTransform -> Text
$sel:parameters:CreateMLTransform' :: CreateMLTransform -> TransformParameters
$sel:inputRecordTables:CreateMLTransform' :: CreateMLTransform -> [GlueTable]
$sel:name:CreateMLTransform' :: CreateMLTransform -> Text
$sel:workerType:CreateMLTransform' :: CreateMLTransform -> Maybe WorkerType
$sel:transformEncryption:CreateMLTransform' :: CreateMLTransform -> Maybe TransformEncryption
$sel:timeout:CreateMLTransform' :: CreateMLTransform -> Maybe Natural
$sel:tags:CreateMLTransform' :: CreateMLTransform -> Maybe (HashMap Text Text)
$sel:numberOfWorkers:CreateMLTransform' :: CreateMLTransform -> Maybe Int
$sel:maxRetries:CreateMLTransform' :: CreateMLTransform -> Maybe Int
$sel:maxCapacity:CreateMLTransform' :: CreateMLTransform -> Maybe Double
$sel:glueVersion:CreateMLTransform' :: CreateMLTransform -> Maybe Text
$sel:description:CreateMLTransform' :: CreateMLTransform -> Maybe Text
..} =
    [Pair] -> Value
Data.object
      ( forall a. [Maybe a] -> [a]
Prelude.catMaybes
          [ (Key
"Description" forall kv v. (KeyValue kv, ToJSON v) => Key -> v -> kv
Data..=) forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
Prelude.<$> Maybe Text
description,
            (Key
"GlueVersion" forall kv v. (KeyValue kv, ToJSON v) => Key -> v -> kv
Data..=) forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
Prelude.<$> Maybe Text
glueVersion,
            (Key
"MaxCapacity" forall kv v. (KeyValue kv, ToJSON v) => Key -> v -> kv
Data..=) forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
Prelude.<$> Maybe Double
maxCapacity,
            (Key
"MaxRetries" forall kv v. (KeyValue kv, ToJSON v) => Key -> v -> kv
Data..=) forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
Prelude.<$> Maybe Int
maxRetries,
            (Key
"NumberOfWorkers" forall kv v. (KeyValue kv, ToJSON v) => Key -> v -> kv
Data..=)
              forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
Prelude.<$> Maybe Int
numberOfWorkers,
            (Key
"Tags" forall kv v. (KeyValue kv, ToJSON v) => Key -> v -> kv
Data..=) forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
Prelude.<$> Maybe (HashMap Text Text)
tags,
            (Key
"Timeout" forall kv v. (KeyValue kv, ToJSON v) => Key -> v -> kv
Data..=) forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
Prelude.<$> Maybe Natural
timeout,
            (Key
"TransformEncryption" forall kv v. (KeyValue kv, ToJSON v) => Key -> v -> kv
Data..=)
              forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
Prelude.<$> Maybe TransformEncryption
transformEncryption,
            (Key
"WorkerType" forall kv v. (KeyValue kv, ToJSON v) => Key -> v -> kv
Data..=) forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
Prelude.<$> Maybe WorkerType
workerType,
            forall a. a -> Maybe a
Prelude.Just (Key
"Name" forall kv v. (KeyValue kv, ToJSON v) => Key -> v -> kv
Data..= Text
name),
            forall a. a -> Maybe a
Prelude.Just
              (Key
"InputRecordTables" forall kv v. (KeyValue kv, ToJSON v) => Key -> v -> kv
Data..= [GlueTable]
inputRecordTables),
            forall a. a -> Maybe a
Prelude.Just (Key
"Parameters" forall kv v. (KeyValue kv, ToJSON v) => Key -> v -> kv
Data..= TransformParameters
parameters),
            forall a. a -> Maybe a
Prelude.Just (Key
"Role" forall kv v. (KeyValue kv, ToJSON v) => Key -> v -> kv
Data..= Text
role')
          ]
      )

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

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

-- | /See:/ 'newCreateMLTransformResponse' smart constructor.
data CreateMLTransformResponse = CreateMLTransformResponse'
  { -- | A unique identifier that is generated for the transform.
    CreateMLTransformResponse -> Maybe Text
transformId :: Prelude.Maybe Prelude.Text,
    -- | The response's http status code.
    CreateMLTransformResponse -> Int
httpStatus :: Prelude.Int
  }
  deriving (CreateMLTransformResponse -> CreateMLTransformResponse -> Bool
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: CreateMLTransformResponse -> CreateMLTransformResponse -> Bool
$c/= :: CreateMLTransformResponse -> CreateMLTransformResponse -> Bool
== :: CreateMLTransformResponse -> CreateMLTransformResponse -> Bool
$c== :: CreateMLTransformResponse -> CreateMLTransformResponse -> Bool
Prelude.Eq, ReadPrec [CreateMLTransformResponse]
ReadPrec CreateMLTransformResponse
Int -> ReadS CreateMLTransformResponse
ReadS [CreateMLTransformResponse]
forall a.
(Int -> ReadS a)
-> ReadS [a] -> ReadPrec a -> ReadPrec [a] -> Read a
readListPrec :: ReadPrec [CreateMLTransformResponse]
$creadListPrec :: ReadPrec [CreateMLTransformResponse]
readPrec :: ReadPrec CreateMLTransformResponse
$creadPrec :: ReadPrec CreateMLTransformResponse
readList :: ReadS [CreateMLTransformResponse]
$creadList :: ReadS [CreateMLTransformResponse]
readsPrec :: Int -> ReadS CreateMLTransformResponse
$creadsPrec :: Int -> ReadS CreateMLTransformResponse
Prelude.Read, Int -> CreateMLTransformResponse -> ShowS
[CreateMLTransformResponse] -> ShowS
CreateMLTransformResponse -> String
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [CreateMLTransformResponse] -> ShowS
$cshowList :: [CreateMLTransformResponse] -> ShowS
show :: CreateMLTransformResponse -> String
$cshow :: CreateMLTransformResponse -> String
showsPrec :: Int -> CreateMLTransformResponse -> ShowS
$cshowsPrec :: Int -> CreateMLTransformResponse -> ShowS
Prelude.Show, forall x.
Rep CreateMLTransformResponse x -> CreateMLTransformResponse
forall x.
CreateMLTransformResponse -> Rep CreateMLTransformResponse x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cto :: forall x.
Rep CreateMLTransformResponse x -> CreateMLTransformResponse
$cfrom :: forall x.
CreateMLTransformResponse -> Rep CreateMLTransformResponse x
Prelude.Generic)

-- |
-- Create a value of 'CreateMLTransformResponse' 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:
--
-- 'transformId', 'createMLTransformResponse_transformId' - A unique identifier that is generated for the transform.
--
-- 'httpStatus', 'createMLTransformResponse_httpStatus' - The response's http status code.
newCreateMLTransformResponse ::
  -- | 'httpStatus'
  Prelude.Int ->
  CreateMLTransformResponse
newCreateMLTransformResponse :: Int -> CreateMLTransformResponse
newCreateMLTransformResponse Int
pHttpStatus_ =
  CreateMLTransformResponse'
    { $sel:transformId:CreateMLTransformResponse' :: Maybe Text
transformId =
        forall a. Maybe a
Prelude.Nothing,
      $sel:httpStatus:CreateMLTransformResponse' :: Int
httpStatus = Int
pHttpStatus_
    }

-- | A unique identifier that is generated for the transform.
createMLTransformResponse_transformId :: Lens.Lens' CreateMLTransformResponse (Prelude.Maybe Prelude.Text)
createMLTransformResponse_transformId :: Lens' CreateMLTransformResponse (Maybe Text)
createMLTransformResponse_transformId = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\CreateMLTransformResponse' {Maybe Text
transformId :: Maybe Text
$sel:transformId:CreateMLTransformResponse' :: CreateMLTransformResponse -> Maybe Text
transformId} -> Maybe Text
transformId) (\s :: CreateMLTransformResponse
s@CreateMLTransformResponse' {} Maybe Text
a -> CreateMLTransformResponse
s {$sel:transformId:CreateMLTransformResponse' :: Maybe Text
transformId = Maybe Text
a} :: CreateMLTransformResponse)

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

instance Prelude.NFData CreateMLTransformResponse where
  rnf :: CreateMLTransformResponse -> ()
rnf CreateMLTransformResponse' {Int
Maybe Text
httpStatus :: Int
transformId :: Maybe Text
$sel:httpStatus:CreateMLTransformResponse' :: CreateMLTransformResponse -> Int
$sel:transformId:CreateMLTransformResponse' :: CreateMLTransformResponse -> Maybe Text
..} =
    forall a. NFData a => a -> ()
Prelude.rnf Maybe Text
transformId
      seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf Int
httpStatus