{-# 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.EMRContainers.StartJobRun
-- Copyright   : (c) 2013-2023 Brendan Hay
-- License     : Mozilla Public License, v. 2.0.
-- Maintainer  : Brendan Hay
-- Stability   : auto-generated
-- Portability : non-portable (GHC extensions)
--
-- Starts a job run. A job run is a unit of work, such as a Spark jar,
-- PySpark script, or SparkSQL query, that you submit to Amazon EMR on EKS.
module Amazonka.EMRContainers.StartJobRun
  ( -- * Creating a Request
    StartJobRun (..),
    newStartJobRun,

    -- * Request Lenses
    startJobRun_configurationOverrides,
    startJobRun_executionRoleArn,
    startJobRun_jobDriver,
    startJobRun_jobTemplateId,
    startJobRun_jobTemplateParameters,
    startJobRun_name,
    startJobRun_releaseLabel,
    startJobRun_tags,
    startJobRun_virtualClusterId,
    startJobRun_clientToken,

    -- * Destructuring the Response
    StartJobRunResponse (..),
    newStartJobRunResponse,

    -- * Response Lenses
    startJobRunResponse_arn,
    startJobRunResponse_id,
    startJobRunResponse_name,
    startJobRunResponse_virtualClusterId,
    startJobRunResponse_httpStatus,
  )
where

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

-- | /See:/ 'newStartJobRun' smart constructor.
data StartJobRun = StartJobRun'
  { -- | The configuration overrides for the job run.
    StartJobRun -> Maybe ConfigurationOverrides
configurationOverrides :: Prelude.Maybe ConfigurationOverrides,
    -- | The execution role ARN for the job run.
    StartJobRun -> Maybe Text
executionRoleArn :: Prelude.Maybe Prelude.Text,
    -- | The job driver for the job run.
    StartJobRun -> Maybe JobDriver
jobDriver :: Prelude.Maybe JobDriver,
    -- | The job template ID to be used to start the job run.
    StartJobRun -> Maybe Text
jobTemplateId :: Prelude.Maybe Prelude.Text,
    -- | The values of job template parameters to start a job run.
    StartJobRun -> Maybe (HashMap Text Text)
jobTemplateParameters :: Prelude.Maybe (Prelude.HashMap Prelude.Text Prelude.Text),
    -- | The name of the job run.
    StartJobRun -> Maybe Text
name :: Prelude.Maybe Prelude.Text,
    -- | The Amazon EMR release version to use for the job run.
    StartJobRun -> Maybe Text
releaseLabel :: Prelude.Maybe Prelude.Text,
    -- | The tags assigned to job runs.
    StartJobRun -> Maybe (HashMap Text Text)
tags :: Prelude.Maybe (Prelude.HashMap Prelude.Text Prelude.Text),
    -- | The virtual cluster ID for which the job run request is submitted.
    StartJobRun -> Text
virtualClusterId :: Prelude.Text,
    -- | The client idempotency token of the job run request.
    StartJobRun -> Text
clientToken :: Prelude.Text
  }
  deriving (StartJobRun -> StartJobRun -> Bool
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: StartJobRun -> StartJobRun -> Bool
$c/= :: StartJobRun -> StartJobRun -> Bool
== :: StartJobRun -> StartJobRun -> Bool
$c== :: StartJobRun -> StartJobRun -> Bool
Prelude.Eq, Int -> StartJobRun -> ShowS
[StartJobRun] -> ShowS
StartJobRun -> String
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [StartJobRun] -> ShowS
$cshowList :: [StartJobRun] -> ShowS
show :: StartJobRun -> String
$cshow :: StartJobRun -> String
showsPrec :: Int -> StartJobRun -> ShowS
$cshowsPrec :: Int -> StartJobRun -> ShowS
Prelude.Show, forall x. Rep StartJobRun x -> StartJobRun
forall x. StartJobRun -> Rep StartJobRun x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cto :: forall x. Rep StartJobRun x -> StartJobRun
$cfrom :: forall x. StartJobRun -> Rep StartJobRun x
Prelude.Generic)

-- |
-- Create a value of 'StartJobRun' 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:
--
-- 'configurationOverrides', 'startJobRun_configurationOverrides' - The configuration overrides for the job run.
--
-- 'executionRoleArn', 'startJobRun_executionRoleArn' - The execution role ARN for the job run.
--
-- 'jobDriver', 'startJobRun_jobDriver' - The job driver for the job run.
--
-- 'jobTemplateId', 'startJobRun_jobTemplateId' - The job template ID to be used to start the job run.
--
-- 'jobTemplateParameters', 'startJobRun_jobTemplateParameters' - The values of job template parameters to start a job run.
--
-- 'name', 'startJobRun_name' - The name of the job run.
--
-- 'releaseLabel', 'startJobRun_releaseLabel' - The Amazon EMR release version to use for the job run.
--
-- 'tags', 'startJobRun_tags' - The tags assigned to job runs.
--
-- 'virtualClusterId', 'startJobRun_virtualClusterId' - The virtual cluster ID for which the job run request is submitted.
--
-- 'clientToken', 'startJobRun_clientToken' - The client idempotency token of the job run request.
newStartJobRun ::
  -- | 'virtualClusterId'
  Prelude.Text ->
  -- | 'clientToken'
  Prelude.Text ->
  StartJobRun
newStartJobRun :: Text -> Text -> StartJobRun
newStartJobRun Text
pVirtualClusterId_ Text
pClientToken_ =
  StartJobRun'
    { $sel:configurationOverrides:StartJobRun' :: Maybe ConfigurationOverrides
configurationOverrides =
        forall a. Maybe a
Prelude.Nothing,
      $sel:executionRoleArn:StartJobRun' :: Maybe Text
executionRoleArn = forall a. Maybe a
Prelude.Nothing,
      $sel:jobDriver:StartJobRun' :: Maybe JobDriver
jobDriver = forall a. Maybe a
Prelude.Nothing,
      $sel:jobTemplateId:StartJobRun' :: Maybe Text
jobTemplateId = forall a. Maybe a
Prelude.Nothing,
      $sel:jobTemplateParameters:StartJobRun' :: Maybe (HashMap Text Text)
jobTemplateParameters = forall a. Maybe a
Prelude.Nothing,
      $sel:name:StartJobRun' :: Maybe Text
name = forall a. Maybe a
Prelude.Nothing,
      $sel:releaseLabel:StartJobRun' :: Maybe Text
releaseLabel = forall a. Maybe a
Prelude.Nothing,
      $sel:tags:StartJobRun' :: Maybe (HashMap Text Text)
tags = forall a. Maybe a
Prelude.Nothing,
      $sel:virtualClusterId:StartJobRun' :: Text
virtualClusterId = Text
pVirtualClusterId_,
      $sel:clientToken:StartJobRun' :: Text
clientToken = Text
pClientToken_
    }

-- | The configuration overrides for the job run.
startJobRun_configurationOverrides :: Lens.Lens' StartJobRun (Prelude.Maybe ConfigurationOverrides)
startJobRun_configurationOverrides :: Lens' StartJobRun (Maybe ConfigurationOverrides)
startJobRun_configurationOverrides = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\StartJobRun' {Maybe ConfigurationOverrides
configurationOverrides :: Maybe ConfigurationOverrides
$sel:configurationOverrides:StartJobRun' :: StartJobRun -> Maybe ConfigurationOverrides
configurationOverrides} -> Maybe ConfigurationOverrides
configurationOverrides) (\s :: StartJobRun
s@StartJobRun' {} Maybe ConfigurationOverrides
a -> StartJobRun
s {$sel:configurationOverrides:StartJobRun' :: Maybe ConfigurationOverrides
configurationOverrides = Maybe ConfigurationOverrides
a} :: StartJobRun)

-- | The execution role ARN for the job run.
startJobRun_executionRoleArn :: Lens.Lens' StartJobRun (Prelude.Maybe Prelude.Text)
startJobRun_executionRoleArn :: Lens' StartJobRun (Maybe Text)
startJobRun_executionRoleArn = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\StartJobRun' {Maybe Text
executionRoleArn :: Maybe Text
$sel:executionRoleArn:StartJobRun' :: StartJobRun -> Maybe Text
executionRoleArn} -> Maybe Text
executionRoleArn) (\s :: StartJobRun
s@StartJobRun' {} Maybe Text
a -> StartJobRun
s {$sel:executionRoleArn:StartJobRun' :: Maybe Text
executionRoleArn = Maybe Text
a} :: StartJobRun)

-- | The job driver for the job run.
startJobRun_jobDriver :: Lens.Lens' StartJobRun (Prelude.Maybe JobDriver)
startJobRun_jobDriver :: Lens' StartJobRun (Maybe JobDriver)
startJobRun_jobDriver = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\StartJobRun' {Maybe JobDriver
jobDriver :: Maybe JobDriver
$sel:jobDriver:StartJobRun' :: StartJobRun -> Maybe JobDriver
jobDriver} -> Maybe JobDriver
jobDriver) (\s :: StartJobRun
s@StartJobRun' {} Maybe JobDriver
a -> StartJobRun
s {$sel:jobDriver:StartJobRun' :: Maybe JobDriver
jobDriver = Maybe JobDriver
a} :: StartJobRun)

-- | The job template ID to be used to start the job run.
startJobRun_jobTemplateId :: Lens.Lens' StartJobRun (Prelude.Maybe Prelude.Text)
startJobRun_jobTemplateId :: Lens' StartJobRun (Maybe Text)
startJobRun_jobTemplateId = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\StartJobRun' {Maybe Text
jobTemplateId :: Maybe Text
$sel:jobTemplateId:StartJobRun' :: StartJobRun -> Maybe Text
jobTemplateId} -> Maybe Text
jobTemplateId) (\s :: StartJobRun
s@StartJobRun' {} Maybe Text
a -> StartJobRun
s {$sel:jobTemplateId:StartJobRun' :: Maybe Text
jobTemplateId = Maybe Text
a} :: StartJobRun)

-- | The values of job template parameters to start a job run.
startJobRun_jobTemplateParameters :: Lens.Lens' StartJobRun (Prelude.Maybe (Prelude.HashMap Prelude.Text Prelude.Text))
startJobRun_jobTemplateParameters :: Lens' StartJobRun (Maybe (HashMap Text Text))
startJobRun_jobTemplateParameters = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\StartJobRun' {Maybe (HashMap Text Text)
jobTemplateParameters :: Maybe (HashMap Text Text)
$sel:jobTemplateParameters:StartJobRun' :: StartJobRun -> Maybe (HashMap Text Text)
jobTemplateParameters} -> Maybe (HashMap Text Text)
jobTemplateParameters) (\s :: StartJobRun
s@StartJobRun' {} Maybe (HashMap Text Text)
a -> StartJobRun
s {$sel:jobTemplateParameters:StartJobRun' :: Maybe (HashMap Text Text)
jobTemplateParameters = Maybe (HashMap Text Text)
a} :: StartJobRun) 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 job run.
startJobRun_name :: Lens.Lens' StartJobRun (Prelude.Maybe Prelude.Text)
startJobRun_name :: Lens' StartJobRun (Maybe Text)
startJobRun_name = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\StartJobRun' {Maybe Text
name :: Maybe Text
$sel:name:StartJobRun' :: StartJobRun -> Maybe Text
name} -> Maybe Text
name) (\s :: StartJobRun
s@StartJobRun' {} Maybe Text
a -> StartJobRun
s {$sel:name:StartJobRun' :: Maybe Text
name = Maybe Text
a} :: StartJobRun)

-- | The Amazon EMR release version to use for the job run.
startJobRun_releaseLabel :: Lens.Lens' StartJobRun (Prelude.Maybe Prelude.Text)
startJobRun_releaseLabel :: Lens' StartJobRun (Maybe Text)
startJobRun_releaseLabel = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\StartJobRun' {Maybe Text
releaseLabel :: Maybe Text
$sel:releaseLabel:StartJobRun' :: StartJobRun -> Maybe Text
releaseLabel} -> Maybe Text
releaseLabel) (\s :: StartJobRun
s@StartJobRun' {} Maybe Text
a -> StartJobRun
s {$sel:releaseLabel:StartJobRun' :: Maybe Text
releaseLabel = Maybe Text
a} :: StartJobRun)

-- | The tags assigned to job runs.
startJobRun_tags :: Lens.Lens' StartJobRun (Prelude.Maybe (Prelude.HashMap Prelude.Text Prelude.Text))
startJobRun_tags :: Lens' StartJobRun (Maybe (HashMap Text Text))
startJobRun_tags = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\StartJobRun' {Maybe (HashMap Text Text)
tags :: Maybe (HashMap Text Text)
$sel:tags:StartJobRun' :: StartJobRun -> Maybe (HashMap Text Text)
tags} -> Maybe (HashMap Text Text)
tags) (\s :: StartJobRun
s@StartJobRun' {} Maybe (HashMap Text Text)
a -> StartJobRun
s {$sel:tags:StartJobRun' :: Maybe (HashMap Text Text)
tags = Maybe (HashMap Text Text)
a} :: StartJobRun) 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 virtual cluster ID for which the job run request is submitted.
startJobRun_virtualClusterId :: Lens.Lens' StartJobRun Prelude.Text
startJobRun_virtualClusterId :: Lens' StartJobRun Text
startJobRun_virtualClusterId = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\StartJobRun' {Text
virtualClusterId :: Text
$sel:virtualClusterId:StartJobRun' :: StartJobRun -> Text
virtualClusterId} -> Text
virtualClusterId) (\s :: StartJobRun
s@StartJobRun' {} Text
a -> StartJobRun
s {$sel:virtualClusterId:StartJobRun' :: Text
virtualClusterId = Text
a} :: StartJobRun)

-- | The client idempotency token of the job run request.
startJobRun_clientToken :: Lens.Lens' StartJobRun Prelude.Text
startJobRun_clientToken :: Lens' StartJobRun Text
startJobRun_clientToken = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\StartJobRun' {Text
clientToken :: Text
$sel:clientToken:StartJobRun' :: StartJobRun -> Text
clientToken} -> Text
clientToken) (\s :: StartJobRun
s@StartJobRun' {} Text
a -> StartJobRun
s {$sel:clientToken:StartJobRun' :: Text
clientToken = Text
a} :: StartJobRun)

instance Core.AWSRequest StartJobRun where
  type AWSResponse StartJobRun = StartJobRunResponse
  request :: (Service -> Service) -> StartJobRun -> Request StartJobRun
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 StartJobRun
-> ClientResponse ClientBody
-> m (Either Error (ClientResponse (AWSResponse StartJobRun)))
response =
    forall (m :: * -> *) a.
MonadResource m =>
(Int -> ResponseHeaders -> Object -> Either String (AWSResponse a))
-> (ByteStringLazy -> IO ByteStringLazy)
-> Service
-> Proxy a
-> ClientResponse ClientBody
-> m (Either Error (ClientResponse (AWSResponse a)))
Response.receiveJSON
      ( \Int
s ResponseHeaders
h Object
x ->
          Maybe Text
-> Maybe Text
-> Maybe Text
-> Maybe Text
-> Int
-> StartJobRunResponse
StartJobRunResponse'
            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
"arn")
            forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
Prelude.<*> (Object
x forall a. FromJSON a => Object -> Key -> Either String (Maybe a)
Data..?> Key
"id")
            forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
Prelude.<*> (Object
x forall a. FromJSON a => Object -> Key -> Either String (Maybe a)
Data..?> Key
"name")
            forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
Prelude.<*> (Object
x forall a. FromJSON a => Object -> Key -> Either String (Maybe a)
Data..?> Key
"virtualClusterId")
            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 StartJobRun where
  hashWithSalt :: Int -> StartJobRun -> Int
hashWithSalt Int
_salt StartJobRun' {Maybe Text
Maybe (HashMap Text Text)
Maybe ConfigurationOverrides
Maybe JobDriver
Text
clientToken :: Text
virtualClusterId :: Text
tags :: Maybe (HashMap Text Text)
releaseLabel :: Maybe Text
name :: Maybe Text
jobTemplateParameters :: Maybe (HashMap Text Text)
jobTemplateId :: Maybe Text
jobDriver :: Maybe JobDriver
executionRoleArn :: Maybe Text
configurationOverrides :: Maybe ConfigurationOverrides
$sel:clientToken:StartJobRun' :: StartJobRun -> Text
$sel:virtualClusterId:StartJobRun' :: StartJobRun -> Text
$sel:tags:StartJobRun' :: StartJobRun -> Maybe (HashMap Text Text)
$sel:releaseLabel:StartJobRun' :: StartJobRun -> Maybe Text
$sel:name:StartJobRun' :: StartJobRun -> Maybe Text
$sel:jobTemplateParameters:StartJobRun' :: StartJobRun -> Maybe (HashMap Text Text)
$sel:jobTemplateId:StartJobRun' :: StartJobRun -> Maybe Text
$sel:jobDriver:StartJobRun' :: StartJobRun -> Maybe JobDriver
$sel:executionRoleArn:StartJobRun' :: StartJobRun -> Maybe Text
$sel:configurationOverrides:StartJobRun' :: StartJobRun -> Maybe ConfigurationOverrides
..} =
    Int
_salt
      forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Maybe ConfigurationOverrides
configurationOverrides
      forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Maybe Text
executionRoleArn
      forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Maybe JobDriver
jobDriver
      forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Maybe Text
jobTemplateId
      forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Maybe (HashMap Text Text)
jobTemplateParameters
      forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Maybe Text
name
      forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Maybe Text
releaseLabel
      forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Maybe (HashMap Text Text)
tags
      forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Text
virtualClusterId
      forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Text
clientToken

instance Prelude.NFData StartJobRun where
  rnf :: StartJobRun -> ()
rnf StartJobRun' {Maybe Text
Maybe (HashMap Text Text)
Maybe ConfigurationOverrides
Maybe JobDriver
Text
clientToken :: Text
virtualClusterId :: Text
tags :: Maybe (HashMap Text Text)
releaseLabel :: Maybe Text
name :: Maybe Text
jobTemplateParameters :: Maybe (HashMap Text Text)
jobTemplateId :: Maybe Text
jobDriver :: Maybe JobDriver
executionRoleArn :: Maybe Text
configurationOverrides :: Maybe ConfigurationOverrides
$sel:clientToken:StartJobRun' :: StartJobRun -> Text
$sel:virtualClusterId:StartJobRun' :: StartJobRun -> Text
$sel:tags:StartJobRun' :: StartJobRun -> Maybe (HashMap Text Text)
$sel:releaseLabel:StartJobRun' :: StartJobRun -> Maybe Text
$sel:name:StartJobRun' :: StartJobRun -> Maybe Text
$sel:jobTemplateParameters:StartJobRun' :: StartJobRun -> Maybe (HashMap Text Text)
$sel:jobTemplateId:StartJobRun' :: StartJobRun -> Maybe Text
$sel:jobDriver:StartJobRun' :: StartJobRun -> Maybe JobDriver
$sel:executionRoleArn:StartJobRun' :: StartJobRun -> Maybe Text
$sel:configurationOverrides:StartJobRun' :: StartJobRun -> Maybe ConfigurationOverrides
..} =
    forall a. NFData a => a -> ()
Prelude.rnf Maybe ConfigurationOverrides
configurationOverrides
      seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf Maybe Text
executionRoleArn
      seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf Maybe JobDriver
jobDriver
      seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf Maybe Text
jobTemplateId
      seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf Maybe (HashMap Text Text)
jobTemplateParameters
      seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf Maybe Text
name
      seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf Maybe Text
releaseLabel
      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 Text
virtualClusterId
      seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf Text
clientToken

instance Data.ToHeaders StartJobRun where
  toHeaders :: StartJobRun -> 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 StartJobRun where
  toJSON :: StartJobRun -> Value
toJSON StartJobRun' {Maybe Text
Maybe (HashMap Text Text)
Maybe ConfigurationOverrides
Maybe JobDriver
Text
clientToken :: Text
virtualClusterId :: Text
tags :: Maybe (HashMap Text Text)
releaseLabel :: Maybe Text
name :: Maybe Text
jobTemplateParameters :: Maybe (HashMap Text Text)
jobTemplateId :: Maybe Text
jobDriver :: Maybe JobDriver
executionRoleArn :: Maybe Text
configurationOverrides :: Maybe ConfigurationOverrides
$sel:clientToken:StartJobRun' :: StartJobRun -> Text
$sel:virtualClusterId:StartJobRun' :: StartJobRun -> Text
$sel:tags:StartJobRun' :: StartJobRun -> Maybe (HashMap Text Text)
$sel:releaseLabel:StartJobRun' :: StartJobRun -> Maybe Text
$sel:name:StartJobRun' :: StartJobRun -> Maybe Text
$sel:jobTemplateParameters:StartJobRun' :: StartJobRun -> Maybe (HashMap Text Text)
$sel:jobTemplateId:StartJobRun' :: StartJobRun -> Maybe Text
$sel:jobDriver:StartJobRun' :: StartJobRun -> Maybe JobDriver
$sel:executionRoleArn:StartJobRun' :: StartJobRun -> Maybe Text
$sel:configurationOverrides:StartJobRun' :: StartJobRun -> Maybe ConfigurationOverrides
..} =
    [Pair] -> Value
Data.object
      ( forall a. [Maybe a] -> [a]
Prelude.catMaybes
          [ (Key
"configurationOverrides" 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 ConfigurationOverrides
configurationOverrides,
            (Key
"executionRoleArn" 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
executionRoleArn,
            (Key
"jobDriver" 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 JobDriver
jobDriver,
            (Key
"jobTemplateId" 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
jobTemplateId,
            (Key
"jobTemplateParameters" 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)
jobTemplateParameters,
            (Key
"name" 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
name,
            (Key
"releaseLabel" 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
releaseLabel,
            (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,
            forall a. a -> Maybe a
Prelude.Just (Key
"clientToken" forall kv v. (KeyValue kv, ToJSON v) => Key -> v -> kv
Data..= Text
clientToken)
          ]
      )

instance Data.ToPath StartJobRun where
  toPath :: StartJobRun -> ByteString
toPath StartJobRun' {Maybe Text
Maybe (HashMap Text Text)
Maybe ConfigurationOverrides
Maybe JobDriver
Text
clientToken :: Text
virtualClusterId :: Text
tags :: Maybe (HashMap Text Text)
releaseLabel :: Maybe Text
name :: Maybe Text
jobTemplateParameters :: Maybe (HashMap Text Text)
jobTemplateId :: Maybe Text
jobDriver :: Maybe JobDriver
executionRoleArn :: Maybe Text
configurationOverrides :: Maybe ConfigurationOverrides
$sel:clientToken:StartJobRun' :: StartJobRun -> Text
$sel:virtualClusterId:StartJobRun' :: StartJobRun -> Text
$sel:tags:StartJobRun' :: StartJobRun -> Maybe (HashMap Text Text)
$sel:releaseLabel:StartJobRun' :: StartJobRun -> Maybe Text
$sel:name:StartJobRun' :: StartJobRun -> Maybe Text
$sel:jobTemplateParameters:StartJobRun' :: StartJobRun -> Maybe (HashMap Text Text)
$sel:jobTemplateId:StartJobRun' :: StartJobRun -> Maybe Text
$sel:jobDriver:StartJobRun' :: StartJobRun -> Maybe JobDriver
$sel:executionRoleArn:StartJobRun' :: StartJobRun -> Maybe Text
$sel:configurationOverrides:StartJobRun' :: StartJobRun -> Maybe ConfigurationOverrides
..} =
    forall a. Monoid a => [a] -> a
Prelude.mconcat
      [ ByteString
"/virtualclusters/",
        forall a. ToByteString a => a -> ByteString
Data.toBS Text
virtualClusterId,
        ByteString
"/jobruns"
      ]

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

-- | /See:/ 'newStartJobRunResponse' smart constructor.
data StartJobRunResponse = StartJobRunResponse'
  { -- | This output lists the ARN of job run.
    StartJobRunResponse -> Maybe Text
arn :: Prelude.Maybe Prelude.Text,
    -- | This output displays the started job run ID.
    StartJobRunResponse -> Maybe Text
id :: Prelude.Maybe Prelude.Text,
    -- | This output displays the name of the started job run.
    StartJobRunResponse -> Maybe Text
name :: Prelude.Maybe Prelude.Text,
    -- | This output displays the virtual cluster ID for which the job run was
    -- submitted.
    StartJobRunResponse -> Maybe Text
virtualClusterId :: Prelude.Maybe Prelude.Text,
    -- | The response's http status code.
    StartJobRunResponse -> Int
httpStatus :: Prelude.Int
  }
  deriving (StartJobRunResponse -> StartJobRunResponse -> Bool
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: StartJobRunResponse -> StartJobRunResponse -> Bool
$c/= :: StartJobRunResponse -> StartJobRunResponse -> Bool
== :: StartJobRunResponse -> StartJobRunResponse -> Bool
$c== :: StartJobRunResponse -> StartJobRunResponse -> Bool
Prelude.Eq, ReadPrec [StartJobRunResponse]
ReadPrec StartJobRunResponse
Int -> ReadS StartJobRunResponse
ReadS [StartJobRunResponse]
forall a.
(Int -> ReadS a)
-> ReadS [a] -> ReadPrec a -> ReadPrec [a] -> Read a
readListPrec :: ReadPrec [StartJobRunResponse]
$creadListPrec :: ReadPrec [StartJobRunResponse]
readPrec :: ReadPrec StartJobRunResponse
$creadPrec :: ReadPrec StartJobRunResponse
readList :: ReadS [StartJobRunResponse]
$creadList :: ReadS [StartJobRunResponse]
readsPrec :: Int -> ReadS StartJobRunResponse
$creadsPrec :: Int -> ReadS StartJobRunResponse
Prelude.Read, Int -> StartJobRunResponse -> ShowS
[StartJobRunResponse] -> ShowS
StartJobRunResponse -> String
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [StartJobRunResponse] -> ShowS
$cshowList :: [StartJobRunResponse] -> ShowS
show :: StartJobRunResponse -> String
$cshow :: StartJobRunResponse -> String
showsPrec :: Int -> StartJobRunResponse -> ShowS
$cshowsPrec :: Int -> StartJobRunResponse -> ShowS
Prelude.Show, forall x. Rep StartJobRunResponse x -> StartJobRunResponse
forall x. StartJobRunResponse -> Rep StartJobRunResponse x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cto :: forall x. Rep StartJobRunResponse x -> StartJobRunResponse
$cfrom :: forall x. StartJobRunResponse -> Rep StartJobRunResponse x
Prelude.Generic)

-- |
-- Create a value of 'StartJobRunResponse' 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:
--
-- 'arn', 'startJobRunResponse_arn' - This output lists the ARN of job run.
--
-- 'id', 'startJobRunResponse_id' - This output displays the started job run ID.
--
-- 'name', 'startJobRunResponse_name' - This output displays the name of the started job run.
--
-- 'virtualClusterId', 'startJobRunResponse_virtualClusterId' - This output displays the virtual cluster ID for which the job run was
-- submitted.
--
-- 'httpStatus', 'startJobRunResponse_httpStatus' - The response's http status code.
newStartJobRunResponse ::
  -- | 'httpStatus'
  Prelude.Int ->
  StartJobRunResponse
newStartJobRunResponse :: Int -> StartJobRunResponse
newStartJobRunResponse Int
pHttpStatus_ =
  StartJobRunResponse'
    { $sel:arn:StartJobRunResponse' :: Maybe Text
arn = forall a. Maybe a
Prelude.Nothing,
      $sel:id:StartJobRunResponse' :: Maybe Text
id = forall a. Maybe a
Prelude.Nothing,
      $sel:name:StartJobRunResponse' :: Maybe Text
name = forall a. Maybe a
Prelude.Nothing,
      $sel:virtualClusterId:StartJobRunResponse' :: Maybe Text
virtualClusterId = forall a. Maybe a
Prelude.Nothing,
      $sel:httpStatus:StartJobRunResponse' :: Int
httpStatus = Int
pHttpStatus_
    }

-- | This output lists the ARN of job run.
startJobRunResponse_arn :: Lens.Lens' StartJobRunResponse (Prelude.Maybe Prelude.Text)
startJobRunResponse_arn :: Lens' StartJobRunResponse (Maybe Text)
startJobRunResponse_arn = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\StartJobRunResponse' {Maybe Text
arn :: Maybe Text
$sel:arn:StartJobRunResponse' :: StartJobRunResponse -> Maybe Text
arn} -> Maybe Text
arn) (\s :: StartJobRunResponse
s@StartJobRunResponse' {} Maybe Text
a -> StartJobRunResponse
s {$sel:arn:StartJobRunResponse' :: Maybe Text
arn = Maybe Text
a} :: StartJobRunResponse)

-- | This output displays the started job run ID.
startJobRunResponse_id :: Lens.Lens' StartJobRunResponse (Prelude.Maybe Prelude.Text)
startJobRunResponse_id :: Lens' StartJobRunResponse (Maybe Text)
startJobRunResponse_id = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\StartJobRunResponse' {Maybe Text
id :: Maybe Text
$sel:id:StartJobRunResponse' :: StartJobRunResponse -> Maybe Text
id} -> Maybe Text
id) (\s :: StartJobRunResponse
s@StartJobRunResponse' {} Maybe Text
a -> StartJobRunResponse
s {$sel:id:StartJobRunResponse' :: Maybe Text
id = Maybe Text
a} :: StartJobRunResponse)

-- | This output displays the name of the started job run.
startJobRunResponse_name :: Lens.Lens' StartJobRunResponse (Prelude.Maybe Prelude.Text)
startJobRunResponse_name :: Lens' StartJobRunResponse (Maybe Text)
startJobRunResponse_name = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\StartJobRunResponse' {Maybe Text
name :: Maybe Text
$sel:name:StartJobRunResponse' :: StartJobRunResponse -> Maybe Text
name} -> Maybe Text
name) (\s :: StartJobRunResponse
s@StartJobRunResponse' {} Maybe Text
a -> StartJobRunResponse
s {$sel:name:StartJobRunResponse' :: Maybe Text
name = Maybe Text
a} :: StartJobRunResponse)

-- | This output displays the virtual cluster ID for which the job run was
-- submitted.
startJobRunResponse_virtualClusterId :: Lens.Lens' StartJobRunResponse (Prelude.Maybe Prelude.Text)
startJobRunResponse_virtualClusterId :: Lens' StartJobRunResponse (Maybe Text)
startJobRunResponse_virtualClusterId = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\StartJobRunResponse' {Maybe Text
virtualClusterId :: Maybe Text
$sel:virtualClusterId:StartJobRunResponse' :: StartJobRunResponse -> Maybe Text
virtualClusterId} -> Maybe Text
virtualClusterId) (\s :: StartJobRunResponse
s@StartJobRunResponse' {} Maybe Text
a -> StartJobRunResponse
s {$sel:virtualClusterId:StartJobRunResponse' :: Maybe Text
virtualClusterId = Maybe Text
a} :: StartJobRunResponse)

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

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