{-# 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.M2.StartBatchJob
-- 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 batch job and returns the unique identifier of this execution
-- of the batch job. The associated application must be running in order to
-- start the batch job.
module Amazonka.M2.StartBatchJob
  ( -- * Creating a Request
    StartBatchJob (..),
    newStartBatchJob,

    -- * Request Lenses
    startBatchJob_jobParams,
    startBatchJob_applicationId,
    startBatchJob_batchJobIdentifier,

    -- * Destructuring the Response
    StartBatchJobResponse (..),
    newStartBatchJobResponse,

    -- * Response Lenses
    startBatchJobResponse_httpStatus,
    startBatchJobResponse_executionId,
  )
where

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

-- | /See:/ 'newStartBatchJob' smart constructor.
data StartBatchJob = StartBatchJob'
  { -- | The collection of batch job parameters. For details about limits for
    -- keys and values, see
    -- <https://www.ibm.com/docs/en/workload-automation/9.3.0?topic=zos-coding-variables-in-jcl Coding variables in JCL>.
    StartBatchJob -> Maybe (HashMap Text Text)
jobParams :: Prelude.Maybe (Prelude.HashMap Prelude.Text Prelude.Text),
    -- | The unique identifier of the application associated with this batch job.
    StartBatchJob -> Text
applicationId :: Prelude.Text,
    -- | The unique identifier of the batch job.
    StartBatchJob -> BatchJobIdentifier
batchJobIdentifier :: BatchJobIdentifier
  }
  deriving (StartBatchJob -> StartBatchJob -> Bool
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: StartBatchJob -> StartBatchJob -> Bool
$c/= :: StartBatchJob -> StartBatchJob -> Bool
== :: StartBatchJob -> StartBatchJob -> Bool
$c== :: StartBatchJob -> StartBatchJob -> Bool
Prelude.Eq, ReadPrec [StartBatchJob]
ReadPrec StartBatchJob
Int -> ReadS StartBatchJob
ReadS [StartBatchJob]
forall a.
(Int -> ReadS a)
-> ReadS [a] -> ReadPrec a -> ReadPrec [a] -> Read a
readListPrec :: ReadPrec [StartBatchJob]
$creadListPrec :: ReadPrec [StartBatchJob]
readPrec :: ReadPrec StartBatchJob
$creadPrec :: ReadPrec StartBatchJob
readList :: ReadS [StartBatchJob]
$creadList :: ReadS [StartBatchJob]
readsPrec :: Int -> ReadS StartBatchJob
$creadsPrec :: Int -> ReadS StartBatchJob
Prelude.Read, Int -> StartBatchJob -> ShowS
[StartBatchJob] -> ShowS
StartBatchJob -> String
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [StartBatchJob] -> ShowS
$cshowList :: [StartBatchJob] -> ShowS
show :: StartBatchJob -> String
$cshow :: StartBatchJob -> String
showsPrec :: Int -> StartBatchJob -> ShowS
$cshowsPrec :: Int -> StartBatchJob -> ShowS
Prelude.Show, forall x. Rep StartBatchJob x -> StartBatchJob
forall x. StartBatchJob -> Rep StartBatchJob x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cto :: forall x. Rep StartBatchJob x -> StartBatchJob
$cfrom :: forall x. StartBatchJob -> Rep StartBatchJob x
Prelude.Generic)

-- |
-- Create a value of 'StartBatchJob' 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:
--
-- 'jobParams', 'startBatchJob_jobParams' - The collection of batch job parameters. For details about limits for
-- keys and values, see
-- <https://www.ibm.com/docs/en/workload-automation/9.3.0?topic=zos-coding-variables-in-jcl Coding variables in JCL>.
--
-- 'applicationId', 'startBatchJob_applicationId' - The unique identifier of the application associated with this batch job.
--
-- 'batchJobIdentifier', 'startBatchJob_batchJobIdentifier' - The unique identifier of the batch job.
newStartBatchJob ::
  -- | 'applicationId'
  Prelude.Text ->
  -- | 'batchJobIdentifier'
  BatchJobIdentifier ->
  StartBatchJob
newStartBatchJob :: Text -> BatchJobIdentifier -> StartBatchJob
newStartBatchJob Text
pApplicationId_ BatchJobIdentifier
pBatchJobIdentifier_ =
  StartBatchJob'
    { $sel:jobParams:StartBatchJob' :: Maybe (HashMap Text Text)
jobParams = forall a. Maybe a
Prelude.Nothing,
      $sel:applicationId:StartBatchJob' :: Text
applicationId = Text
pApplicationId_,
      $sel:batchJobIdentifier:StartBatchJob' :: BatchJobIdentifier
batchJobIdentifier = BatchJobIdentifier
pBatchJobIdentifier_
    }

-- | The collection of batch job parameters. For details about limits for
-- keys and values, see
-- <https://www.ibm.com/docs/en/workload-automation/9.3.0?topic=zos-coding-variables-in-jcl Coding variables in JCL>.
startBatchJob_jobParams :: Lens.Lens' StartBatchJob (Prelude.Maybe (Prelude.HashMap Prelude.Text Prelude.Text))
startBatchJob_jobParams :: Lens' StartBatchJob (Maybe (HashMap Text Text))
startBatchJob_jobParams = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\StartBatchJob' {Maybe (HashMap Text Text)
jobParams :: Maybe (HashMap Text Text)
$sel:jobParams:StartBatchJob' :: StartBatchJob -> Maybe (HashMap Text Text)
jobParams} -> Maybe (HashMap Text Text)
jobParams) (\s :: StartBatchJob
s@StartBatchJob' {} Maybe (HashMap Text Text)
a -> StartBatchJob
s {$sel:jobParams:StartBatchJob' :: Maybe (HashMap Text Text)
jobParams = Maybe (HashMap Text Text)
a} :: StartBatchJob) 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 unique identifier of the application associated with this batch job.
startBatchJob_applicationId :: Lens.Lens' StartBatchJob Prelude.Text
startBatchJob_applicationId :: Lens' StartBatchJob Text
startBatchJob_applicationId = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\StartBatchJob' {Text
applicationId :: Text
$sel:applicationId:StartBatchJob' :: StartBatchJob -> Text
applicationId} -> Text
applicationId) (\s :: StartBatchJob
s@StartBatchJob' {} Text
a -> StartBatchJob
s {$sel:applicationId:StartBatchJob' :: Text
applicationId = Text
a} :: StartBatchJob)

-- | The unique identifier of the batch job.
startBatchJob_batchJobIdentifier :: Lens.Lens' StartBatchJob BatchJobIdentifier
startBatchJob_batchJobIdentifier :: Lens' StartBatchJob BatchJobIdentifier
startBatchJob_batchJobIdentifier = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\StartBatchJob' {BatchJobIdentifier
batchJobIdentifier :: BatchJobIdentifier
$sel:batchJobIdentifier:StartBatchJob' :: StartBatchJob -> BatchJobIdentifier
batchJobIdentifier} -> BatchJobIdentifier
batchJobIdentifier) (\s :: StartBatchJob
s@StartBatchJob' {} BatchJobIdentifier
a -> StartBatchJob
s {$sel:batchJobIdentifier:StartBatchJob' :: BatchJobIdentifier
batchJobIdentifier = BatchJobIdentifier
a} :: StartBatchJob)

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

instance Prelude.Hashable StartBatchJob where
  hashWithSalt :: Int -> StartBatchJob -> Int
hashWithSalt Int
_salt StartBatchJob' {Maybe (HashMap Text Text)
Text
BatchJobIdentifier
batchJobIdentifier :: BatchJobIdentifier
applicationId :: Text
jobParams :: Maybe (HashMap Text Text)
$sel:batchJobIdentifier:StartBatchJob' :: StartBatchJob -> BatchJobIdentifier
$sel:applicationId:StartBatchJob' :: StartBatchJob -> Text
$sel:jobParams:StartBatchJob' :: StartBatchJob -> Maybe (HashMap Text Text)
..} =
    Int
_salt
      forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Maybe (HashMap Text Text)
jobParams
      forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Text
applicationId
      forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` BatchJobIdentifier
batchJobIdentifier

instance Prelude.NFData StartBatchJob where
  rnf :: StartBatchJob -> ()
rnf StartBatchJob' {Maybe (HashMap Text Text)
Text
BatchJobIdentifier
batchJobIdentifier :: BatchJobIdentifier
applicationId :: Text
jobParams :: Maybe (HashMap Text Text)
$sel:batchJobIdentifier:StartBatchJob' :: StartBatchJob -> BatchJobIdentifier
$sel:applicationId:StartBatchJob' :: StartBatchJob -> Text
$sel:jobParams:StartBatchJob' :: StartBatchJob -> Maybe (HashMap Text Text)
..} =
    forall a. NFData a => a -> ()
Prelude.rnf Maybe (HashMap Text Text)
jobParams
      seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf Text
applicationId
      seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf BatchJobIdentifier
batchJobIdentifier

instance Data.ToHeaders StartBatchJob where
  toHeaders :: StartBatchJob -> 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 StartBatchJob where
  toJSON :: StartBatchJob -> Value
toJSON StartBatchJob' {Maybe (HashMap Text Text)
Text
BatchJobIdentifier
batchJobIdentifier :: BatchJobIdentifier
applicationId :: Text
jobParams :: Maybe (HashMap Text Text)
$sel:batchJobIdentifier:StartBatchJob' :: StartBatchJob -> BatchJobIdentifier
$sel:applicationId:StartBatchJob' :: StartBatchJob -> Text
$sel:jobParams:StartBatchJob' :: StartBatchJob -> Maybe (HashMap Text Text)
..} =
    [Pair] -> Value
Data.object
      ( forall a. [Maybe a] -> [a]
Prelude.catMaybes
          [ (Key
"jobParams" 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)
jobParams,
            forall a. a -> Maybe a
Prelude.Just
              (Key
"batchJobIdentifier" forall kv v. (KeyValue kv, ToJSON v) => Key -> v -> kv
Data..= BatchJobIdentifier
batchJobIdentifier)
          ]
      )

instance Data.ToPath StartBatchJob where
  toPath :: StartBatchJob -> ByteString
toPath StartBatchJob' {Maybe (HashMap Text Text)
Text
BatchJobIdentifier
batchJobIdentifier :: BatchJobIdentifier
applicationId :: Text
jobParams :: Maybe (HashMap Text Text)
$sel:batchJobIdentifier:StartBatchJob' :: StartBatchJob -> BatchJobIdentifier
$sel:applicationId:StartBatchJob' :: StartBatchJob -> Text
$sel:jobParams:StartBatchJob' :: StartBatchJob -> Maybe (HashMap Text Text)
..} =
    forall a. Monoid a => [a] -> a
Prelude.mconcat
      [ ByteString
"/applications/",
        forall a. ToByteString a => a -> ByteString
Data.toBS Text
applicationId,
        ByteString
"/batch-job"
      ]

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

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

-- |
-- Create a value of 'StartBatchJobResponse' 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', 'startBatchJobResponse_httpStatus' - The response's http status code.
--
-- 'executionId', 'startBatchJobResponse_executionId' - The unique identifier of this execution of the batch job.
newStartBatchJobResponse ::
  -- | 'httpStatus'
  Prelude.Int ->
  -- | 'executionId'
  Prelude.Text ->
  StartBatchJobResponse
newStartBatchJobResponse :: Int -> Text -> StartBatchJobResponse
newStartBatchJobResponse Int
pHttpStatus_ Text
pExecutionId_ =
  StartBatchJobResponse'
    { $sel:httpStatus:StartBatchJobResponse' :: Int
httpStatus = Int
pHttpStatus_,
      $sel:executionId:StartBatchJobResponse' :: Text
executionId = Text
pExecutionId_
    }

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

-- | The unique identifier of this execution of the batch job.
startBatchJobResponse_executionId :: Lens.Lens' StartBatchJobResponse Prelude.Text
startBatchJobResponse_executionId :: Lens' StartBatchJobResponse Text
startBatchJobResponse_executionId = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\StartBatchJobResponse' {Text
executionId :: Text
$sel:executionId:StartBatchJobResponse' :: StartBatchJobResponse -> Text
executionId} -> Text
executionId) (\s :: StartBatchJobResponse
s@StartBatchJobResponse' {} Text
a -> StartBatchJobResponse
s {$sel:executionId:StartBatchJobResponse' :: Text
executionId = Text
a} :: StartBatchJobResponse)

instance Prelude.NFData StartBatchJobResponse where
  rnf :: StartBatchJobResponse -> ()
rnf StartBatchJobResponse' {Int
Text
executionId :: Text
httpStatus :: Int
$sel:executionId:StartBatchJobResponse' :: StartBatchJobResponse -> Text
$sel:httpStatus:StartBatchJobResponse' :: StartBatchJobResponse -> 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
executionId