{-# 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.DataBrew.CreateRecipeJob
-- 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 a new job to transform input data, using steps defined in an
-- existing Glue DataBrew recipe
module Amazonka.DataBrew.CreateRecipeJob
  ( -- * Creating a Request
    CreateRecipeJob (..),
    newCreateRecipeJob,

    -- * Request Lenses
    createRecipeJob_dataCatalogOutputs,
    createRecipeJob_databaseOutputs,
    createRecipeJob_datasetName,
    createRecipeJob_encryptionKeyArn,
    createRecipeJob_encryptionMode,
    createRecipeJob_logSubscription,
    createRecipeJob_maxCapacity,
    createRecipeJob_maxRetries,
    createRecipeJob_outputs,
    createRecipeJob_projectName,
    createRecipeJob_recipeReference,
    createRecipeJob_tags,
    createRecipeJob_timeout,
    createRecipeJob_name,
    createRecipeJob_roleArn,

    -- * Destructuring the Response
    CreateRecipeJobResponse (..),
    newCreateRecipeJobResponse,

    -- * Response Lenses
    createRecipeJobResponse_httpStatus,
    createRecipeJobResponse_name,
  )
where

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

-- | /See:/ 'newCreateRecipeJob' smart constructor.
data CreateRecipeJob = CreateRecipeJob'
  { -- | One or more artifacts that represent the Glue Data Catalog output from
    -- running the job.
    CreateRecipeJob -> Maybe (NonEmpty DataCatalogOutput)
dataCatalogOutputs :: Prelude.Maybe (Prelude.NonEmpty DataCatalogOutput),
    -- | Represents a list of JDBC database output objects which defines the
    -- output destination for a DataBrew recipe job to write to.
    CreateRecipeJob -> Maybe (NonEmpty DatabaseOutput)
databaseOutputs :: Prelude.Maybe (Prelude.NonEmpty DatabaseOutput),
    -- | The name of the dataset that this job processes.
    CreateRecipeJob -> Maybe Text
datasetName :: Prelude.Maybe Prelude.Text,
    -- | The Amazon Resource Name (ARN) of an encryption key that is used to
    -- protect the job.
    CreateRecipeJob -> Maybe Text
encryptionKeyArn :: Prelude.Maybe Prelude.Text,
    -- | The encryption mode for the job, which can be one of the following:
    --
    -- -   @SSE-KMS@ - Server-side encryption with keys managed by KMS.
    --
    -- -   @SSE-S3@ - Server-side encryption with keys managed by Amazon S3.
    CreateRecipeJob -> Maybe EncryptionMode
encryptionMode :: Prelude.Maybe EncryptionMode,
    -- | Enables or disables Amazon CloudWatch logging for the job. If logging is
    -- enabled, CloudWatch writes one log stream for each job run.
    CreateRecipeJob -> Maybe LogSubscription
logSubscription :: Prelude.Maybe LogSubscription,
    -- | The maximum number of nodes that DataBrew can consume when the job
    -- processes data.
    CreateRecipeJob -> Maybe Int
maxCapacity :: Prelude.Maybe Prelude.Int,
    -- | The maximum number of times to retry the job after a job run fails.
    CreateRecipeJob -> Maybe Natural
maxRetries :: Prelude.Maybe Prelude.Natural,
    -- | One or more artifacts that represent the output from running the job.
    CreateRecipeJob -> Maybe (NonEmpty Output)
outputs :: Prelude.Maybe (Prelude.NonEmpty Output),
    -- | Either the name of an existing project, or a combination of a recipe and
    -- a dataset to associate with the recipe.
    CreateRecipeJob -> Maybe Text
projectName :: Prelude.Maybe Prelude.Text,
    CreateRecipeJob -> Maybe RecipeReference
recipeReference :: Prelude.Maybe RecipeReference,
    -- | Metadata tags to apply to this job.
    CreateRecipeJob -> Maybe (HashMap Text Text)
tags :: Prelude.Maybe (Prelude.HashMap Prelude.Text Prelude.Text),
    -- | The job\'s timeout in minutes. A job that attempts to run longer than
    -- this timeout period ends with a status of @TIMEOUT@.
    CreateRecipeJob -> Maybe Natural
timeout :: Prelude.Maybe Prelude.Natural,
    -- | A unique name for the job. Valid characters are alphanumeric (A-Z, a-z,
    -- 0-9), hyphen (-), period (.), and space.
    CreateRecipeJob -> Text
name :: Prelude.Text,
    -- | The Amazon Resource Name (ARN) of the Identity and Access Management
    -- (IAM) role to be assumed when DataBrew runs the job.
    CreateRecipeJob -> Text
roleArn :: Prelude.Text
  }
  deriving (CreateRecipeJob -> CreateRecipeJob -> Bool
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: CreateRecipeJob -> CreateRecipeJob -> Bool
$c/= :: CreateRecipeJob -> CreateRecipeJob -> Bool
== :: CreateRecipeJob -> CreateRecipeJob -> Bool
$c== :: CreateRecipeJob -> CreateRecipeJob -> Bool
Prelude.Eq, ReadPrec [CreateRecipeJob]
ReadPrec CreateRecipeJob
Int -> ReadS CreateRecipeJob
ReadS [CreateRecipeJob]
forall a.
(Int -> ReadS a)
-> ReadS [a] -> ReadPrec a -> ReadPrec [a] -> Read a
readListPrec :: ReadPrec [CreateRecipeJob]
$creadListPrec :: ReadPrec [CreateRecipeJob]
readPrec :: ReadPrec CreateRecipeJob
$creadPrec :: ReadPrec CreateRecipeJob
readList :: ReadS [CreateRecipeJob]
$creadList :: ReadS [CreateRecipeJob]
readsPrec :: Int -> ReadS CreateRecipeJob
$creadsPrec :: Int -> ReadS CreateRecipeJob
Prelude.Read, Int -> CreateRecipeJob -> ShowS
[CreateRecipeJob] -> ShowS
CreateRecipeJob -> String
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [CreateRecipeJob] -> ShowS
$cshowList :: [CreateRecipeJob] -> ShowS
show :: CreateRecipeJob -> String
$cshow :: CreateRecipeJob -> String
showsPrec :: Int -> CreateRecipeJob -> ShowS
$cshowsPrec :: Int -> CreateRecipeJob -> ShowS
Prelude.Show, forall x. Rep CreateRecipeJob x -> CreateRecipeJob
forall x. CreateRecipeJob -> Rep CreateRecipeJob x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cto :: forall x. Rep CreateRecipeJob x -> CreateRecipeJob
$cfrom :: forall x. CreateRecipeJob -> Rep CreateRecipeJob x
Prelude.Generic)

-- |
-- Create a value of 'CreateRecipeJob' 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:
--
-- 'dataCatalogOutputs', 'createRecipeJob_dataCatalogOutputs' - One or more artifacts that represent the Glue Data Catalog output from
-- running the job.
--
-- 'databaseOutputs', 'createRecipeJob_databaseOutputs' - Represents a list of JDBC database output objects which defines the
-- output destination for a DataBrew recipe job to write to.
--
-- 'datasetName', 'createRecipeJob_datasetName' - The name of the dataset that this job processes.
--
-- 'encryptionKeyArn', 'createRecipeJob_encryptionKeyArn' - The Amazon Resource Name (ARN) of an encryption key that is used to
-- protect the job.
--
-- 'encryptionMode', 'createRecipeJob_encryptionMode' - The encryption mode for the job, which can be one of the following:
--
-- -   @SSE-KMS@ - Server-side encryption with keys managed by KMS.
--
-- -   @SSE-S3@ - Server-side encryption with keys managed by Amazon S3.
--
-- 'logSubscription', 'createRecipeJob_logSubscription' - Enables or disables Amazon CloudWatch logging for the job. If logging is
-- enabled, CloudWatch writes one log stream for each job run.
--
-- 'maxCapacity', 'createRecipeJob_maxCapacity' - The maximum number of nodes that DataBrew can consume when the job
-- processes data.
--
-- 'maxRetries', 'createRecipeJob_maxRetries' - The maximum number of times to retry the job after a job run fails.
--
-- 'outputs', 'createRecipeJob_outputs' - One or more artifacts that represent the output from running the job.
--
-- 'projectName', 'createRecipeJob_projectName' - Either the name of an existing project, or a combination of a recipe and
-- a dataset to associate with the recipe.
--
-- 'recipeReference', 'createRecipeJob_recipeReference' - Undocumented member.
--
-- 'tags', 'createRecipeJob_tags' - Metadata tags to apply to this job.
--
-- 'timeout', 'createRecipeJob_timeout' - The job\'s timeout in minutes. A job that attempts to run longer than
-- this timeout period ends with a status of @TIMEOUT@.
--
-- 'name', 'createRecipeJob_name' - A unique name for the job. Valid characters are alphanumeric (A-Z, a-z,
-- 0-9), hyphen (-), period (.), and space.
--
-- 'roleArn', 'createRecipeJob_roleArn' - The Amazon Resource Name (ARN) of the Identity and Access Management
-- (IAM) role to be assumed when DataBrew runs the job.
newCreateRecipeJob ::
  -- | 'name'
  Prelude.Text ->
  -- | 'roleArn'
  Prelude.Text ->
  CreateRecipeJob
newCreateRecipeJob :: Text -> Text -> CreateRecipeJob
newCreateRecipeJob Text
pName_ Text
pRoleArn_ =
  CreateRecipeJob'
    { $sel:dataCatalogOutputs:CreateRecipeJob' :: Maybe (NonEmpty DataCatalogOutput)
dataCatalogOutputs =
        forall a. Maybe a
Prelude.Nothing,
      $sel:databaseOutputs:CreateRecipeJob' :: Maybe (NonEmpty DatabaseOutput)
databaseOutputs = forall a. Maybe a
Prelude.Nothing,
      $sel:datasetName:CreateRecipeJob' :: Maybe Text
datasetName = forall a. Maybe a
Prelude.Nothing,
      $sel:encryptionKeyArn:CreateRecipeJob' :: Maybe Text
encryptionKeyArn = forall a. Maybe a
Prelude.Nothing,
      $sel:encryptionMode:CreateRecipeJob' :: Maybe EncryptionMode
encryptionMode = forall a. Maybe a
Prelude.Nothing,
      $sel:logSubscription:CreateRecipeJob' :: Maybe LogSubscription
logSubscription = forall a. Maybe a
Prelude.Nothing,
      $sel:maxCapacity:CreateRecipeJob' :: Maybe Int
maxCapacity = forall a. Maybe a
Prelude.Nothing,
      $sel:maxRetries:CreateRecipeJob' :: Maybe Natural
maxRetries = forall a. Maybe a
Prelude.Nothing,
      $sel:outputs:CreateRecipeJob' :: Maybe (NonEmpty Output)
outputs = forall a. Maybe a
Prelude.Nothing,
      $sel:projectName:CreateRecipeJob' :: Maybe Text
projectName = forall a. Maybe a
Prelude.Nothing,
      $sel:recipeReference:CreateRecipeJob' :: Maybe RecipeReference
recipeReference = forall a. Maybe a
Prelude.Nothing,
      $sel:tags:CreateRecipeJob' :: Maybe (HashMap Text Text)
tags = forall a. Maybe a
Prelude.Nothing,
      $sel:timeout:CreateRecipeJob' :: Maybe Natural
timeout = forall a. Maybe a
Prelude.Nothing,
      $sel:name:CreateRecipeJob' :: Text
name = Text
pName_,
      $sel:roleArn:CreateRecipeJob' :: Text
roleArn = Text
pRoleArn_
    }

-- | One or more artifacts that represent the Glue Data Catalog output from
-- running the job.
createRecipeJob_dataCatalogOutputs :: Lens.Lens' CreateRecipeJob (Prelude.Maybe (Prelude.NonEmpty DataCatalogOutput))
createRecipeJob_dataCatalogOutputs :: Lens' CreateRecipeJob (Maybe (NonEmpty DataCatalogOutput))
createRecipeJob_dataCatalogOutputs = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\CreateRecipeJob' {Maybe (NonEmpty DataCatalogOutput)
dataCatalogOutputs :: Maybe (NonEmpty DataCatalogOutput)
$sel:dataCatalogOutputs:CreateRecipeJob' :: CreateRecipeJob -> Maybe (NonEmpty DataCatalogOutput)
dataCatalogOutputs} -> Maybe (NonEmpty DataCatalogOutput)
dataCatalogOutputs) (\s :: CreateRecipeJob
s@CreateRecipeJob' {} Maybe (NonEmpty DataCatalogOutput)
a -> CreateRecipeJob
s {$sel:dataCatalogOutputs:CreateRecipeJob' :: Maybe (NonEmpty DataCatalogOutput)
dataCatalogOutputs = Maybe (NonEmpty DataCatalogOutput)
a} :: CreateRecipeJob) forall b c a. (b -> c) -> (a -> b) -> a -> c
Prelude.. forall (f :: * -> *) (g :: * -> *) s t a b.
(Functor f, Functor g) =>
AnIso s t a b -> Iso (f s) (g t) (f a) (g b)
Lens.mapping forall s t a b. (Coercible s a, Coercible t b) => Iso s t a b
Lens.coerced

-- | Represents a list of JDBC database output objects which defines the
-- output destination for a DataBrew recipe job to write to.
createRecipeJob_databaseOutputs :: Lens.Lens' CreateRecipeJob (Prelude.Maybe (Prelude.NonEmpty DatabaseOutput))
createRecipeJob_databaseOutputs :: Lens' CreateRecipeJob (Maybe (NonEmpty DatabaseOutput))
createRecipeJob_databaseOutputs = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\CreateRecipeJob' {Maybe (NonEmpty DatabaseOutput)
databaseOutputs :: Maybe (NonEmpty DatabaseOutput)
$sel:databaseOutputs:CreateRecipeJob' :: CreateRecipeJob -> Maybe (NonEmpty DatabaseOutput)
databaseOutputs} -> Maybe (NonEmpty DatabaseOutput)
databaseOutputs) (\s :: CreateRecipeJob
s@CreateRecipeJob' {} Maybe (NonEmpty DatabaseOutput)
a -> CreateRecipeJob
s {$sel:databaseOutputs:CreateRecipeJob' :: Maybe (NonEmpty DatabaseOutput)
databaseOutputs = Maybe (NonEmpty DatabaseOutput)
a} :: CreateRecipeJob) 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 name of the dataset that this job processes.
createRecipeJob_datasetName :: Lens.Lens' CreateRecipeJob (Prelude.Maybe Prelude.Text)
createRecipeJob_datasetName :: Lens' CreateRecipeJob (Maybe Text)
createRecipeJob_datasetName = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\CreateRecipeJob' {Maybe Text
datasetName :: Maybe Text
$sel:datasetName:CreateRecipeJob' :: CreateRecipeJob -> Maybe Text
datasetName} -> Maybe Text
datasetName) (\s :: CreateRecipeJob
s@CreateRecipeJob' {} Maybe Text
a -> CreateRecipeJob
s {$sel:datasetName:CreateRecipeJob' :: Maybe Text
datasetName = Maybe Text
a} :: CreateRecipeJob)

-- | The Amazon Resource Name (ARN) of an encryption key that is used to
-- protect the job.
createRecipeJob_encryptionKeyArn :: Lens.Lens' CreateRecipeJob (Prelude.Maybe Prelude.Text)
createRecipeJob_encryptionKeyArn :: Lens' CreateRecipeJob (Maybe Text)
createRecipeJob_encryptionKeyArn = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\CreateRecipeJob' {Maybe Text
encryptionKeyArn :: Maybe Text
$sel:encryptionKeyArn:CreateRecipeJob' :: CreateRecipeJob -> Maybe Text
encryptionKeyArn} -> Maybe Text
encryptionKeyArn) (\s :: CreateRecipeJob
s@CreateRecipeJob' {} Maybe Text
a -> CreateRecipeJob
s {$sel:encryptionKeyArn:CreateRecipeJob' :: Maybe Text
encryptionKeyArn = Maybe Text
a} :: CreateRecipeJob)

-- | The encryption mode for the job, which can be one of the following:
--
-- -   @SSE-KMS@ - Server-side encryption with keys managed by KMS.
--
-- -   @SSE-S3@ - Server-side encryption with keys managed by Amazon S3.
createRecipeJob_encryptionMode :: Lens.Lens' CreateRecipeJob (Prelude.Maybe EncryptionMode)
createRecipeJob_encryptionMode :: Lens' CreateRecipeJob (Maybe EncryptionMode)
createRecipeJob_encryptionMode = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\CreateRecipeJob' {Maybe EncryptionMode
encryptionMode :: Maybe EncryptionMode
$sel:encryptionMode:CreateRecipeJob' :: CreateRecipeJob -> Maybe EncryptionMode
encryptionMode} -> Maybe EncryptionMode
encryptionMode) (\s :: CreateRecipeJob
s@CreateRecipeJob' {} Maybe EncryptionMode
a -> CreateRecipeJob
s {$sel:encryptionMode:CreateRecipeJob' :: Maybe EncryptionMode
encryptionMode = Maybe EncryptionMode
a} :: CreateRecipeJob)

-- | Enables or disables Amazon CloudWatch logging for the job. If logging is
-- enabled, CloudWatch writes one log stream for each job run.
createRecipeJob_logSubscription :: Lens.Lens' CreateRecipeJob (Prelude.Maybe LogSubscription)
createRecipeJob_logSubscription :: Lens' CreateRecipeJob (Maybe LogSubscription)
createRecipeJob_logSubscription = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\CreateRecipeJob' {Maybe LogSubscription
logSubscription :: Maybe LogSubscription
$sel:logSubscription:CreateRecipeJob' :: CreateRecipeJob -> Maybe LogSubscription
logSubscription} -> Maybe LogSubscription
logSubscription) (\s :: CreateRecipeJob
s@CreateRecipeJob' {} Maybe LogSubscription
a -> CreateRecipeJob
s {$sel:logSubscription:CreateRecipeJob' :: Maybe LogSubscription
logSubscription = Maybe LogSubscription
a} :: CreateRecipeJob)

-- | The maximum number of nodes that DataBrew can consume when the job
-- processes data.
createRecipeJob_maxCapacity :: Lens.Lens' CreateRecipeJob (Prelude.Maybe Prelude.Int)
createRecipeJob_maxCapacity :: Lens' CreateRecipeJob (Maybe Int)
createRecipeJob_maxCapacity = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\CreateRecipeJob' {Maybe Int
maxCapacity :: Maybe Int
$sel:maxCapacity:CreateRecipeJob' :: CreateRecipeJob -> Maybe Int
maxCapacity} -> Maybe Int
maxCapacity) (\s :: CreateRecipeJob
s@CreateRecipeJob' {} Maybe Int
a -> CreateRecipeJob
s {$sel:maxCapacity:CreateRecipeJob' :: Maybe Int
maxCapacity = Maybe Int
a} :: CreateRecipeJob)

-- | The maximum number of times to retry the job after a job run fails.
createRecipeJob_maxRetries :: Lens.Lens' CreateRecipeJob (Prelude.Maybe Prelude.Natural)
createRecipeJob_maxRetries :: Lens' CreateRecipeJob (Maybe Natural)
createRecipeJob_maxRetries = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\CreateRecipeJob' {Maybe Natural
maxRetries :: Maybe Natural
$sel:maxRetries:CreateRecipeJob' :: CreateRecipeJob -> Maybe Natural
maxRetries} -> Maybe Natural
maxRetries) (\s :: CreateRecipeJob
s@CreateRecipeJob' {} Maybe Natural
a -> CreateRecipeJob
s {$sel:maxRetries:CreateRecipeJob' :: Maybe Natural
maxRetries = Maybe Natural
a} :: CreateRecipeJob)

-- | One or more artifacts that represent the output from running the job.
createRecipeJob_outputs :: Lens.Lens' CreateRecipeJob (Prelude.Maybe (Prelude.NonEmpty Output))
createRecipeJob_outputs :: Lens' CreateRecipeJob (Maybe (NonEmpty Output))
createRecipeJob_outputs = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\CreateRecipeJob' {Maybe (NonEmpty Output)
outputs :: Maybe (NonEmpty Output)
$sel:outputs:CreateRecipeJob' :: CreateRecipeJob -> Maybe (NonEmpty Output)
outputs} -> Maybe (NonEmpty Output)
outputs) (\s :: CreateRecipeJob
s@CreateRecipeJob' {} Maybe (NonEmpty Output)
a -> CreateRecipeJob
s {$sel:outputs:CreateRecipeJob' :: Maybe (NonEmpty Output)
outputs = Maybe (NonEmpty Output)
a} :: CreateRecipeJob) 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

-- | Either the name of an existing project, or a combination of a recipe and
-- a dataset to associate with the recipe.
createRecipeJob_projectName :: Lens.Lens' CreateRecipeJob (Prelude.Maybe Prelude.Text)
createRecipeJob_projectName :: Lens' CreateRecipeJob (Maybe Text)
createRecipeJob_projectName = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\CreateRecipeJob' {Maybe Text
projectName :: Maybe Text
$sel:projectName:CreateRecipeJob' :: CreateRecipeJob -> Maybe Text
projectName} -> Maybe Text
projectName) (\s :: CreateRecipeJob
s@CreateRecipeJob' {} Maybe Text
a -> CreateRecipeJob
s {$sel:projectName:CreateRecipeJob' :: Maybe Text
projectName = Maybe Text
a} :: CreateRecipeJob)

-- | Undocumented member.
createRecipeJob_recipeReference :: Lens.Lens' CreateRecipeJob (Prelude.Maybe RecipeReference)
createRecipeJob_recipeReference :: Lens' CreateRecipeJob (Maybe RecipeReference)
createRecipeJob_recipeReference = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\CreateRecipeJob' {Maybe RecipeReference
recipeReference :: Maybe RecipeReference
$sel:recipeReference:CreateRecipeJob' :: CreateRecipeJob -> Maybe RecipeReference
recipeReference} -> Maybe RecipeReference
recipeReference) (\s :: CreateRecipeJob
s@CreateRecipeJob' {} Maybe RecipeReference
a -> CreateRecipeJob
s {$sel:recipeReference:CreateRecipeJob' :: Maybe RecipeReference
recipeReference = Maybe RecipeReference
a} :: CreateRecipeJob)

-- | Metadata tags to apply to this job.
createRecipeJob_tags :: Lens.Lens' CreateRecipeJob (Prelude.Maybe (Prelude.HashMap Prelude.Text Prelude.Text))
createRecipeJob_tags :: Lens' CreateRecipeJob (Maybe (HashMap Text Text))
createRecipeJob_tags = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\CreateRecipeJob' {Maybe (HashMap Text Text)
tags :: Maybe (HashMap Text Text)
$sel:tags:CreateRecipeJob' :: CreateRecipeJob -> Maybe (HashMap Text Text)
tags} -> Maybe (HashMap Text Text)
tags) (\s :: CreateRecipeJob
s@CreateRecipeJob' {} Maybe (HashMap Text Text)
a -> CreateRecipeJob
s {$sel:tags:CreateRecipeJob' :: Maybe (HashMap Text Text)
tags = Maybe (HashMap Text Text)
a} :: CreateRecipeJob) 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 job\'s timeout in minutes. A job that attempts to run longer than
-- this timeout period ends with a status of @TIMEOUT@.
createRecipeJob_timeout :: Lens.Lens' CreateRecipeJob (Prelude.Maybe Prelude.Natural)
createRecipeJob_timeout :: Lens' CreateRecipeJob (Maybe Natural)
createRecipeJob_timeout = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\CreateRecipeJob' {Maybe Natural
timeout :: Maybe Natural
$sel:timeout:CreateRecipeJob' :: CreateRecipeJob -> Maybe Natural
timeout} -> Maybe Natural
timeout) (\s :: CreateRecipeJob
s@CreateRecipeJob' {} Maybe Natural
a -> CreateRecipeJob
s {$sel:timeout:CreateRecipeJob' :: Maybe Natural
timeout = Maybe Natural
a} :: CreateRecipeJob)

-- | A unique name for the job. Valid characters are alphanumeric (A-Z, a-z,
-- 0-9), hyphen (-), period (.), and space.
createRecipeJob_name :: Lens.Lens' CreateRecipeJob Prelude.Text
createRecipeJob_name :: Lens' CreateRecipeJob Text
createRecipeJob_name = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\CreateRecipeJob' {Text
name :: Text
$sel:name:CreateRecipeJob' :: CreateRecipeJob -> Text
name} -> Text
name) (\s :: CreateRecipeJob
s@CreateRecipeJob' {} Text
a -> CreateRecipeJob
s {$sel:name:CreateRecipeJob' :: Text
name = Text
a} :: CreateRecipeJob)

-- | The Amazon Resource Name (ARN) of the Identity and Access Management
-- (IAM) role to be assumed when DataBrew runs the job.
createRecipeJob_roleArn :: Lens.Lens' CreateRecipeJob Prelude.Text
createRecipeJob_roleArn :: Lens' CreateRecipeJob Text
createRecipeJob_roleArn = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\CreateRecipeJob' {Text
roleArn :: Text
$sel:roleArn:CreateRecipeJob' :: CreateRecipeJob -> Text
roleArn} -> Text
roleArn) (\s :: CreateRecipeJob
s@CreateRecipeJob' {} Text
a -> CreateRecipeJob
s {$sel:roleArn:CreateRecipeJob' :: Text
roleArn = Text
a} :: CreateRecipeJob)

instance Core.AWSRequest CreateRecipeJob where
  type
    AWSResponse CreateRecipeJob =
      CreateRecipeJobResponse
  request :: (Service -> Service) -> CreateRecipeJob -> Request CreateRecipeJob
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 CreateRecipeJob
-> ClientResponse ClientBody
-> m (Either Error (ClientResponse (AWSResponse CreateRecipeJob)))
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 ->
          Int -> Text -> CreateRecipeJobResponse
CreateRecipeJobResponse'
            forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
Prelude.<$> (forall (f :: * -> *) a. Applicative f => a -> f a
Prelude.pure (forall a. Enum a => a -> Int
Prelude.fromEnum Int
s))
            forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
Prelude.<*> (Object
x forall a. FromJSON a => Object -> Key -> Either String a
Data..:> Key
"Name")
      )

instance Prelude.Hashable CreateRecipeJob where
  hashWithSalt :: Int -> CreateRecipeJob -> Int
hashWithSalt Int
_salt CreateRecipeJob' {Maybe Int
Maybe Natural
Maybe (NonEmpty Output)
Maybe (NonEmpty DatabaseOutput)
Maybe (NonEmpty DataCatalogOutput)
Maybe Text
Maybe (HashMap Text Text)
Maybe EncryptionMode
Maybe LogSubscription
Maybe RecipeReference
Text
roleArn :: Text
name :: Text
timeout :: Maybe Natural
tags :: Maybe (HashMap Text Text)
recipeReference :: Maybe RecipeReference
projectName :: Maybe Text
outputs :: Maybe (NonEmpty Output)
maxRetries :: Maybe Natural
maxCapacity :: Maybe Int
logSubscription :: Maybe LogSubscription
encryptionMode :: Maybe EncryptionMode
encryptionKeyArn :: Maybe Text
datasetName :: Maybe Text
databaseOutputs :: Maybe (NonEmpty DatabaseOutput)
dataCatalogOutputs :: Maybe (NonEmpty DataCatalogOutput)
$sel:roleArn:CreateRecipeJob' :: CreateRecipeJob -> Text
$sel:name:CreateRecipeJob' :: CreateRecipeJob -> Text
$sel:timeout:CreateRecipeJob' :: CreateRecipeJob -> Maybe Natural
$sel:tags:CreateRecipeJob' :: CreateRecipeJob -> Maybe (HashMap Text Text)
$sel:recipeReference:CreateRecipeJob' :: CreateRecipeJob -> Maybe RecipeReference
$sel:projectName:CreateRecipeJob' :: CreateRecipeJob -> Maybe Text
$sel:outputs:CreateRecipeJob' :: CreateRecipeJob -> Maybe (NonEmpty Output)
$sel:maxRetries:CreateRecipeJob' :: CreateRecipeJob -> Maybe Natural
$sel:maxCapacity:CreateRecipeJob' :: CreateRecipeJob -> Maybe Int
$sel:logSubscription:CreateRecipeJob' :: CreateRecipeJob -> Maybe LogSubscription
$sel:encryptionMode:CreateRecipeJob' :: CreateRecipeJob -> Maybe EncryptionMode
$sel:encryptionKeyArn:CreateRecipeJob' :: CreateRecipeJob -> Maybe Text
$sel:datasetName:CreateRecipeJob' :: CreateRecipeJob -> Maybe Text
$sel:databaseOutputs:CreateRecipeJob' :: CreateRecipeJob -> Maybe (NonEmpty DatabaseOutput)
$sel:dataCatalogOutputs:CreateRecipeJob' :: CreateRecipeJob -> Maybe (NonEmpty DataCatalogOutput)
..} =
    Int
_salt
      forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Maybe (NonEmpty DataCatalogOutput)
dataCatalogOutputs
      forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Maybe (NonEmpty DatabaseOutput)
databaseOutputs
      forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Maybe Text
datasetName
      forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Maybe Text
encryptionKeyArn
      forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Maybe EncryptionMode
encryptionMode
      forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Maybe LogSubscription
logSubscription
      forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Maybe Int
maxCapacity
      forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Maybe Natural
maxRetries
      forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Maybe (NonEmpty Output)
outputs
      forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Maybe Text
projectName
      forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Maybe RecipeReference
recipeReference
      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` Text
name
      forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Text
roleArn

instance Prelude.NFData CreateRecipeJob where
  rnf :: CreateRecipeJob -> ()
rnf CreateRecipeJob' {Maybe Int
Maybe Natural
Maybe (NonEmpty Output)
Maybe (NonEmpty DatabaseOutput)
Maybe (NonEmpty DataCatalogOutput)
Maybe Text
Maybe (HashMap Text Text)
Maybe EncryptionMode
Maybe LogSubscription
Maybe RecipeReference
Text
roleArn :: Text
name :: Text
timeout :: Maybe Natural
tags :: Maybe (HashMap Text Text)
recipeReference :: Maybe RecipeReference
projectName :: Maybe Text
outputs :: Maybe (NonEmpty Output)
maxRetries :: Maybe Natural
maxCapacity :: Maybe Int
logSubscription :: Maybe LogSubscription
encryptionMode :: Maybe EncryptionMode
encryptionKeyArn :: Maybe Text
datasetName :: Maybe Text
databaseOutputs :: Maybe (NonEmpty DatabaseOutput)
dataCatalogOutputs :: Maybe (NonEmpty DataCatalogOutput)
$sel:roleArn:CreateRecipeJob' :: CreateRecipeJob -> Text
$sel:name:CreateRecipeJob' :: CreateRecipeJob -> Text
$sel:timeout:CreateRecipeJob' :: CreateRecipeJob -> Maybe Natural
$sel:tags:CreateRecipeJob' :: CreateRecipeJob -> Maybe (HashMap Text Text)
$sel:recipeReference:CreateRecipeJob' :: CreateRecipeJob -> Maybe RecipeReference
$sel:projectName:CreateRecipeJob' :: CreateRecipeJob -> Maybe Text
$sel:outputs:CreateRecipeJob' :: CreateRecipeJob -> Maybe (NonEmpty Output)
$sel:maxRetries:CreateRecipeJob' :: CreateRecipeJob -> Maybe Natural
$sel:maxCapacity:CreateRecipeJob' :: CreateRecipeJob -> Maybe Int
$sel:logSubscription:CreateRecipeJob' :: CreateRecipeJob -> Maybe LogSubscription
$sel:encryptionMode:CreateRecipeJob' :: CreateRecipeJob -> Maybe EncryptionMode
$sel:encryptionKeyArn:CreateRecipeJob' :: CreateRecipeJob -> Maybe Text
$sel:datasetName:CreateRecipeJob' :: CreateRecipeJob -> Maybe Text
$sel:databaseOutputs:CreateRecipeJob' :: CreateRecipeJob -> Maybe (NonEmpty DatabaseOutput)
$sel:dataCatalogOutputs:CreateRecipeJob' :: CreateRecipeJob -> Maybe (NonEmpty DataCatalogOutput)
..} =
    forall a. NFData a => a -> ()
Prelude.rnf Maybe (NonEmpty DataCatalogOutput)
dataCatalogOutputs
      seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf Maybe (NonEmpty DatabaseOutput)
databaseOutputs
      seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf Maybe Text
datasetName
      seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf Maybe Text
encryptionKeyArn
      seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf Maybe EncryptionMode
encryptionMode
      seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf Maybe LogSubscription
logSubscription
      seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf Maybe Int
maxCapacity
      seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf Maybe Natural
maxRetries
      seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf Maybe (NonEmpty Output)
outputs
      seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf Maybe Text
projectName
      seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf Maybe RecipeReference
recipeReference
      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 Text
name
      seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf Text
roleArn

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

instance Data.ToJSON CreateRecipeJob where
  toJSON :: CreateRecipeJob -> Value
toJSON CreateRecipeJob' {Maybe Int
Maybe Natural
Maybe (NonEmpty Output)
Maybe (NonEmpty DatabaseOutput)
Maybe (NonEmpty DataCatalogOutput)
Maybe Text
Maybe (HashMap Text Text)
Maybe EncryptionMode
Maybe LogSubscription
Maybe RecipeReference
Text
roleArn :: Text
name :: Text
timeout :: Maybe Natural
tags :: Maybe (HashMap Text Text)
recipeReference :: Maybe RecipeReference
projectName :: Maybe Text
outputs :: Maybe (NonEmpty Output)
maxRetries :: Maybe Natural
maxCapacity :: Maybe Int
logSubscription :: Maybe LogSubscription
encryptionMode :: Maybe EncryptionMode
encryptionKeyArn :: Maybe Text
datasetName :: Maybe Text
databaseOutputs :: Maybe (NonEmpty DatabaseOutput)
dataCatalogOutputs :: Maybe (NonEmpty DataCatalogOutput)
$sel:roleArn:CreateRecipeJob' :: CreateRecipeJob -> Text
$sel:name:CreateRecipeJob' :: CreateRecipeJob -> Text
$sel:timeout:CreateRecipeJob' :: CreateRecipeJob -> Maybe Natural
$sel:tags:CreateRecipeJob' :: CreateRecipeJob -> Maybe (HashMap Text Text)
$sel:recipeReference:CreateRecipeJob' :: CreateRecipeJob -> Maybe RecipeReference
$sel:projectName:CreateRecipeJob' :: CreateRecipeJob -> Maybe Text
$sel:outputs:CreateRecipeJob' :: CreateRecipeJob -> Maybe (NonEmpty Output)
$sel:maxRetries:CreateRecipeJob' :: CreateRecipeJob -> Maybe Natural
$sel:maxCapacity:CreateRecipeJob' :: CreateRecipeJob -> Maybe Int
$sel:logSubscription:CreateRecipeJob' :: CreateRecipeJob -> Maybe LogSubscription
$sel:encryptionMode:CreateRecipeJob' :: CreateRecipeJob -> Maybe EncryptionMode
$sel:encryptionKeyArn:CreateRecipeJob' :: CreateRecipeJob -> Maybe Text
$sel:datasetName:CreateRecipeJob' :: CreateRecipeJob -> Maybe Text
$sel:databaseOutputs:CreateRecipeJob' :: CreateRecipeJob -> Maybe (NonEmpty DatabaseOutput)
$sel:dataCatalogOutputs:CreateRecipeJob' :: CreateRecipeJob -> Maybe (NonEmpty DataCatalogOutput)
..} =
    [Pair] -> Value
Data.object
      ( forall a. [Maybe a] -> [a]
Prelude.catMaybes
          [ (Key
"DataCatalogOutputs" 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 (NonEmpty DataCatalogOutput)
dataCatalogOutputs,
            (Key
"DatabaseOutputs" 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 (NonEmpty DatabaseOutput)
databaseOutputs,
            (Key
"DatasetName" 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
datasetName,
            (Key
"EncryptionKeyArn" 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
encryptionKeyArn,
            (Key
"EncryptionMode" 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 EncryptionMode
encryptionMode,
            (Key
"LogSubscription" 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 LogSubscription
logSubscription,
            (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 Int
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 Natural
maxRetries,
            (Key
"Outputs" 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 (NonEmpty Output)
outputs,
            (Key
"ProjectName" 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
projectName,
            (Key
"RecipeReference" 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 RecipeReference
recipeReference,
            (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,
            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
"RoleArn" forall kv v. (KeyValue kv, ToJSON v) => Key -> v -> kv
Data..= Text
roleArn)
          ]
      )

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

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

-- | /See:/ 'newCreateRecipeJobResponse' smart constructor.
data CreateRecipeJobResponse = CreateRecipeJobResponse'
  { -- | The response's http status code.
    CreateRecipeJobResponse -> Int
httpStatus :: Prelude.Int,
    -- | The name of the job that you created.
    CreateRecipeJobResponse -> Text
name :: Prelude.Text
  }
  deriving (CreateRecipeJobResponse -> CreateRecipeJobResponse -> Bool
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: CreateRecipeJobResponse -> CreateRecipeJobResponse -> Bool
$c/= :: CreateRecipeJobResponse -> CreateRecipeJobResponse -> Bool
== :: CreateRecipeJobResponse -> CreateRecipeJobResponse -> Bool
$c== :: CreateRecipeJobResponse -> CreateRecipeJobResponse -> Bool
Prelude.Eq, ReadPrec [CreateRecipeJobResponse]
ReadPrec CreateRecipeJobResponse
Int -> ReadS CreateRecipeJobResponse
ReadS [CreateRecipeJobResponse]
forall a.
(Int -> ReadS a)
-> ReadS [a] -> ReadPrec a -> ReadPrec [a] -> Read a
readListPrec :: ReadPrec [CreateRecipeJobResponse]
$creadListPrec :: ReadPrec [CreateRecipeJobResponse]
readPrec :: ReadPrec CreateRecipeJobResponse
$creadPrec :: ReadPrec CreateRecipeJobResponse
readList :: ReadS [CreateRecipeJobResponse]
$creadList :: ReadS [CreateRecipeJobResponse]
readsPrec :: Int -> ReadS CreateRecipeJobResponse
$creadsPrec :: Int -> ReadS CreateRecipeJobResponse
Prelude.Read, Int -> CreateRecipeJobResponse -> ShowS
[CreateRecipeJobResponse] -> ShowS
CreateRecipeJobResponse -> String
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [CreateRecipeJobResponse] -> ShowS
$cshowList :: [CreateRecipeJobResponse] -> ShowS
show :: CreateRecipeJobResponse -> String
$cshow :: CreateRecipeJobResponse -> String
showsPrec :: Int -> CreateRecipeJobResponse -> ShowS
$cshowsPrec :: Int -> CreateRecipeJobResponse -> ShowS
Prelude.Show, forall x. Rep CreateRecipeJobResponse x -> CreateRecipeJobResponse
forall x. CreateRecipeJobResponse -> Rep CreateRecipeJobResponse x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cto :: forall x. Rep CreateRecipeJobResponse x -> CreateRecipeJobResponse
$cfrom :: forall x. CreateRecipeJobResponse -> Rep CreateRecipeJobResponse x
Prelude.Generic)

-- |
-- Create a value of 'CreateRecipeJobResponse' 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:
--
-- 'httpStatus', 'createRecipeJobResponse_httpStatus' - The response's http status code.
--
-- 'name', 'createRecipeJobResponse_name' - The name of the job that you created.
newCreateRecipeJobResponse ::
  -- | 'httpStatus'
  Prelude.Int ->
  -- | 'name'
  Prelude.Text ->
  CreateRecipeJobResponse
newCreateRecipeJobResponse :: Int -> Text -> CreateRecipeJobResponse
newCreateRecipeJobResponse Int
pHttpStatus_ Text
pName_ =
  CreateRecipeJobResponse'
    { $sel:httpStatus:CreateRecipeJobResponse' :: Int
httpStatus = Int
pHttpStatus_,
      $sel:name:CreateRecipeJobResponse' :: Text
name = Text
pName_
    }

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

-- | The name of the job that you created.
createRecipeJobResponse_name :: Lens.Lens' CreateRecipeJobResponse Prelude.Text
createRecipeJobResponse_name :: Lens' CreateRecipeJobResponse Text
createRecipeJobResponse_name = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\CreateRecipeJobResponse' {Text
name :: Text
$sel:name:CreateRecipeJobResponse' :: CreateRecipeJobResponse -> Text
name} -> Text
name) (\s :: CreateRecipeJobResponse
s@CreateRecipeJobResponse' {} Text
a -> CreateRecipeJobResponse
s {$sel:name:CreateRecipeJobResponse' :: Text
name = Text
a} :: CreateRecipeJobResponse)

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