{-# 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.CodePipeline.PutJobSuccessResult
-- Copyright   : (c) 2013-2023 Brendan Hay
-- License     : Mozilla Public License, v. 2.0.
-- Maintainer  : Brendan Hay
-- Stability   : auto-generated
-- Portability : non-portable (GHC extensions)
--
-- Represents the success of a job as returned to the pipeline by a job
-- worker. Used for custom actions only.
module Amazonka.CodePipeline.PutJobSuccessResult
  ( -- * Creating a Request
    PutJobSuccessResult (..),
    newPutJobSuccessResult,

    -- * Request Lenses
    putJobSuccessResult_continuationToken,
    putJobSuccessResult_currentRevision,
    putJobSuccessResult_executionDetails,
    putJobSuccessResult_outputVariables,
    putJobSuccessResult_jobId,

    -- * Destructuring the Response
    PutJobSuccessResultResponse (..),
    newPutJobSuccessResultResponse,
  )
where

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

-- | Represents the input of a @PutJobSuccessResult@ action.
--
-- /See:/ 'newPutJobSuccessResult' smart constructor.
data PutJobSuccessResult = PutJobSuccessResult'
  { -- | A token generated by a job worker, such as an AWS CodeDeploy deployment
    -- ID, that a successful job provides to identify a custom action in
    -- progress. Future jobs use this token to identify the running instance of
    -- the action. It can be reused to return more information about the
    -- progress of the custom action. When the action is complete, no
    -- continuation token should be supplied.
    PutJobSuccessResult -> Maybe Text
continuationToken :: Prelude.Maybe Prelude.Text,
    -- | The ID of the current revision of the artifact successfully worked on by
    -- the job.
    PutJobSuccessResult -> Maybe CurrentRevision
currentRevision :: Prelude.Maybe CurrentRevision,
    -- | The execution details of the successful job, such as the actions taken
    -- by the job worker.
    PutJobSuccessResult -> Maybe ExecutionDetails
executionDetails :: Prelude.Maybe ExecutionDetails,
    -- | Key-value pairs produced as output by a job worker that can be made
    -- available to a downstream action configuration. @outputVariables@ can be
    -- included only when there is no continuation token on the request.
    PutJobSuccessResult -> Maybe (HashMap Text Text)
outputVariables :: Prelude.Maybe (Prelude.HashMap Prelude.Text Prelude.Text),
    -- | The unique system-generated ID of the job that succeeded. This is the
    -- same ID returned from @PollForJobs@.
    PutJobSuccessResult -> Text
jobId :: Prelude.Text
  }
  deriving (PutJobSuccessResult -> PutJobSuccessResult -> Bool
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: PutJobSuccessResult -> PutJobSuccessResult -> Bool
$c/= :: PutJobSuccessResult -> PutJobSuccessResult -> Bool
== :: PutJobSuccessResult -> PutJobSuccessResult -> Bool
$c== :: PutJobSuccessResult -> PutJobSuccessResult -> Bool
Prelude.Eq, ReadPrec [PutJobSuccessResult]
ReadPrec PutJobSuccessResult
Int -> ReadS PutJobSuccessResult
ReadS [PutJobSuccessResult]
forall a.
(Int -> ReadS a)
-> ReadS [a] -> ReadPrec a -> ReadPrec [a] -> Read a
readListPrec :: ReadPrec [PutJobSuccessResult]
$creadListPrec :: ReadPrec [PutJobSuccessResult]
readPrec :: ReadPrec PutJobSuccessResult
$creadPrec :: ReadPrec PutJobSuccessResult
readList :: ReadS [PutJobSuccessResult]
$creadList :: ReadS [PutJobSuccessResult]
readsPrec :: Int -> ReadS PutJobSuccessResult
$creadsPrec :: Int -> ReadS PutJobSuccessResult
Prelude.Read, Int -> PutJobSuccessResult -> ShowS
[PutJobSuccessResult] -> ShowS
PutJobSuccessResult -> String
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [PutJobSuccessResult] -> ShowS
$cshowList :: [PutJobSuccessResult] -> ShowS
show :: PutJobSuccessResult -> String
$cshow :: PutJobSuccessResult -> String
showsPrec :: Int -> PutJobSuccessResult -> ShowS
$cshowsPrec :: Int -> PutJobSuccessResult -> ShowS
Prelude.Show, forall x. Rep PutJobSuccessResult x -> PutJobSuccessResult
forall x. PutJobSuccessResult -> Rep PutJobSuccessResult x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cto :: forall x. Rep PutJobSuccessResult x -> PutJobSuccessResult
$cfrom :: forall x. PutJobSuccessResult -> Rep PutJobSuccessResult x
Prelude.Generic)

-- |
-- Create a value of 'PutJobSuccessResult' 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:
--
-- 'continuationToken', 'putJobSuccessResult_continuationToken' - A token generated by a job worker, such as an AWS CodeDeploy deployment
-- ID, that a successful job provides to identify a custom action in
-- progress. Future jobs use this token to identify the running instance of
-- the action. It can be reused to return more information about the
-- progress of the custom action. When the action is complete, no
-- continuation token should be supplied.
--
-- 'currentRevision', 'putJobSuccessResult_currentRevision' - The ID of the current revision of the artifact successfully worked on by
-- the job.
--
-- 'executionDetails', 'putJobSuccessResult_executionDetails' - The execution details of the successful job, such as the actions taken
-- by the job worker.
--
-- 'outputVariables', 'putJobSuccessResult_outputVariables' - Key-value pairs produced as output by a job worker that can be made
-- available to a downstream action configuration. @outputVariables@ can be
-- included only when there is no continuation token on the request.
--
-- 'jobId', 'putJobSuccessResult_jobId' - The unique system-generated ID of the job that succeeded. This is the
-- same ID returned from @PollForJobs@.
newPutJobSuccessResult ::
  -- | 'jobId'
  Prelude.Text ->
  PutJobSuccessResult
newPutJobSuccessResult :: Text -> PutJobSuccessResult
newPutJobSuccessResult Text
pJobId_ =
  PutJobSuccessResult'
    { $sel:continuationToken:PutJobSuccessResult' :: Maybe Text
continuationToken =
        forall a. Maybe a
Prelude.Nothing,
      $sel:currentRevision:PutJobSuccessResult' :: Maybe CurrentRevision
currentRevision = forall a. Maybe a
Prelude.Nothing,
      $sel:executionDetails:PutJobSuccessResult' :: Maybe ExecutionDetails
executionDetails = forall a. Maybe a
Prelude.Nothing,
      $sel:outputVariables:PutJobSuccessResult' :: Maybe (HashMap Text Text)
outputVariables = forall a. Maybe a
Prelude.Nothing,
      $sel:jobId:PutJobSuccessResult' :: Text
jobId = Text
pJobId_
    }

-- | A token generated by a job worker, such as an AWS CodeDeploy deployment
-- ID, that a successful job provides to identify a custom action in
-- progress. Future jobs use this token to identify the running instance of
-- the action. It can be reused to return more information about the
-- progress of the custom action. When the action is complete, no
-- continuation token should be supplied.
putJobSuccessResult_continuationToken :: Lens.Lens' PutJobSuccessResult (Prelude.Maybe Prelude.Text)
putJobSuccessResult_continuationToken :: Lens' PutJobSuccessResult (Maybe Text)
putJobSuccessResult_continuationToken = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\PutJobSuccessResult' {Maybe Text
continuationToken :: Maybe Text
$sel:continuationToken:PutJobSuccessResult' :: PutJobSuccessResult -> Maybe Text
continuationToken} -> Maybe Text
continuationToken) (\s :: PutJobSuccessResult
s@PutJobSuccessResult' {} Maybe Text
a -> PutJobSuccessResult
s {$sel:continuationToken:PutJobSuccessResult' :: Maybe Text
continuationToken = Maybe Text
a} :: PutJobSuccessResult)

-- | The ID of the current revision of the artifact successfully worked on by
-- the job.
putJobSuccessResult_currentRevision :: Lens.Lens' PutJobSuccessResult (Prelude.Maybe CurrentRevision)
putJobSuccessResult_currentRevision :: Lens' PutJobSuccessResult (Maybe CurrentRevision)
putJobSuccessResult_currentRevision = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\PutJobSuccessResult' {Maybe CurrentRevision
currentRevision :: Maybe CurrentRevision
$sel:currentRevision:PutJobSuccessResult' :: PutJobSuccessResult -> Maybe CurrentRevision
currentRevision} -> Maybe CurrentRevision
currentRevision) (\s :: PutJobSuccessResult
s@PutJobSuccessResult' {} Maybe CurrentRevision
a -> PutJobSuccessResult
s {$sel:currentRevision:PutJobSuccessResult' :: Maybe CurrentRevision
currentRevision = Maybe CurrentRevision
a} :: PutJobSuccessResult)

-- | The execution details of the successful job, such as the actions taken
-- by the job worker.
putJobSuccessResult_executionDetails :: Lens.Lens' PutJobSuccessResult (Prelude.Maybe ExecutionDetails)
putJobSuccessResult_executionDetails :: Lens' PutJobSuccessResult (Maybe ExecutionDetails)
putJobSuccessResult_executionDetails = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\PutJobSuccessResult' {Maybe ExecutionDetails
executionDetails :: Maybe ExecutionDetails
$sel:executionDetails:PutJobSuccessResult' :: PutJobSuccessResult -> Maybe ExecutionDetails
executionDetails} -> Maybe ExecutionDetails
executionDetails) (\s :: PutJobSuccessResult
s@PutJobSuccessResult' {} Maybe ExecutionDetails
a -> PutJobSuccessResult
s {$sel:executionDetails:PutJobSuccessResult' :: Maybe ExecutionDetails
executionDetails = Maybe ExecutionDetails
a} :: PutJobSuccessResult)

-- | Key-value pairs produced as output by a job worker that can be made
-- available to a downstream action configuration. @outputVariables@ can be
-- included only when there is no continuation token on the request.
putJobSuccessResult_outputVariables :: Lens.Lens' PutJobSuccessResult (Prelude.Maybe (Prelude.HashMap Prelude.Text Prelude.Text))
putJobSuccessResult_outputVariables :: Lens' PutJobSuccessResult (Maybe (HashMap Text Text))
putJobSuccessResult_outputVariables = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\PutJobSuccessResult' {Maybe (HashMap Text Text)
outputVariables :: Maybe (HashMap Text Text)
$sel:outputVariables:PutJobSuccessResult' :: PutJobSuccessResult -> Maybe (HashMap Text Text)
outputVariables} -> Maybe (HashMap Text Text)
outputVariables) (\s :: PutJobSuccessResult
s@PutJobSuccessResult' {} Maybe (HashMap Text Text)
a -> PutJobSuccessResult
s {$sel:outputVariables:PutJobSuccessResult' :: Maybe (HashMap Text Text)
outputVariables = Maybe (HashMap Text Text)
a} :: PutJobSuccessResult) 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 system-generated ID of the job that succeeded. This is the
-- same ID returned from @PollForJobs@.
putJobSuccessResult_jobId :: Lens.Lens' PutJobSuccessResult Prelude.Text
putJobSuccessResult_jobId :: Lens' PutJobSuccessResult Text
putJobSuccessResult_jobId = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\PutJobSuccessResult' {Text
jobId :: Text
$sel:jobId:PutJobSuccessResult' :: PutJobSuccessResult -> Text
jobId} -> Text
jobId) (\s :: PutJobSuccessResult
s@PutJobSuccessResult' {} Text
a -> PutJobSuccessResult
s {$sel:jobId:PutJobSuccessResult' :: Text
jobId = Text
a} :: PutJobSuccessResult)

instance Core.AWSRequest PutJobSuccessResult where
  type
    AWSResponse PutJobSuccessResult =
      PutJobSuccessResultResponse
  request :: (Service -> Service)
-> PutJobSuccessResult -> Request PutJobSuccessResult
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 PutJobSuccessResult
-> ClientResponse ClientBody
-> m (Either
        Error (ClientResponse (AWSResponse PutJobSuccessResult)))
response =
    forall (m :: * -> *) a.
MonadResource m =>
AWSResponse a
-> (ByteStringLazy -> IO ByteStringLazy)
-> Service
-> Proxy a
-> ClientResponse ClientBody
-> m (Either Error (ClientResponse (AWSResponse a)))
Response.receiveNull PutJobSuccessResultResponse
PutJobSuccessResultResponse'

instance Prelude.Hashable PutJobSuccessResult where
  hashWithSalt :: Int -> PutJobSuccessResult -> Int
hashWithSalt Int
_salt PutJobSuccessResult' {Maybe Text
Maybe (HashMap Text Text)
Maybe CurrentRevision
Maybe ExecutionDetails
Text
jobId :: Text
outputVariables :: Maybe (HashMap Text Text)
executionDetails :: Maybe ExecutionDetails
currentRevision :: Maybe CurrentRevision
continuationToken :: Maybe Text
$sel:jobId:PutJobSuccessResult' :: PutJobSuccessResult -> Text
$sel:outputVariables:PutJobSuccessResult' :: PutJobSuccessResult -> Maybe (HashMap Text Text)
$sel:executionDetails:PutJobSuccessResult' :: PutJobSuccessResult -> Maybe ExecutionDetails
$sel:currentRevision:PutJobSuccessResult' :: PutJobSuccessResult -> Maybe CurrentRevision
$sel:continuationToken:PutJobSuccessResult' :: PutJobSuccessResult -> Maybe Text
..} =
    Int
_salt
      forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Maybe Text
continuationToken
      forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Maybe CurrentRevision
currentRevision
      forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Maybe ExecutionDetails
executionDetails
      forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Maybe (HashMap Text Text)
outputVariables
      forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Text
jobId

instance Prelude.NFData PutJobSuccessResult where
  rnf :: PutJobSuccessResult -> ()
rnf PutJobSuccessResult' {Maybe Text
Maybe (HashMap Text Text)
Maybe CurrentRevision
Maybe ExecutionDetails
Text
jobId :: Text
outputVariables :: Maybe (HashMap Text Text)
executionDetails :: Maybe ExecutionDetails
currentRevision :: Maybe CurrentRevision
continuationToken :: Maybe Text
$sel:jobId:PutJobSuccessResult' :: PutJobSuccessResult -> Text
$sel:outputVariables:PutJobSuccessResult' :: PutJobSuccessResult -> Maybe (HashMap Text Text)
$sel:executionDetails:PutJobSuccessResult' :: PutJobSuccessResult -> Maybe ExecutionDetails
$sel:currentRevision:PutJobSuccessResult' :: PutJobSuccessResult -> Maybe CurrentRevision
$sel:continuationToken:PutJobSuccessResult' :: PutJobSuccessResult -> Maybe Text
..} =
    forall a. NFData a => a -> ()
Prelude.rnf Maybe Text
continuationToken
      seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf Maybe CurrentRevision
currentRevision
      seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf Maybe ExecutionDetails
executionDetails
      seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf Maybe (HashMap Text Text)
outputVariables
      seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf Text
jobId

instance Data.ToHeaders PutJobSuccessResult where
  toHeaders :: PutJobSuccessResult -> [Header]
toHeaders =
    forall a b. a -> b -> a
Prelude.const
      ( forall a. Monoid a => [a] -> a
Prelude.mconcat
          [ HeaderName
"X-Amz-Target"
              forall a. ToHeader a => HeaderName -> a -> [Header]
Data.=# ( ByteString
"CodePipeline_20150709.PutJobSuccessResult" ::
                          Prelude.ByteString
                      ),
            HeaderName
"Content-Type"
              forall a. ToHeader a => HeaderName -> a -> [Header]
Data.=# ( ByteString
"application/x-amz-json-1.1" ::
                          Prelude.ByteString
                      )
          ]
      )

instance Data.ToJSON PutJobSuccessResult where
  toJSON :: PutJobSuccessResult -> Value
toJSON PutJobSuccessResult' {Maybe Text
Maybe (HashMap Text Text)
Maybe CurrentRevision
Maybe ExecutionDetails
Text
jobId :: Text
outputVariables :: Maybe (HashMap Text Text)
executionDetails :: Maybe ExecutionDetails
currentRevision :: Maybe CurrentRevision
continuationToken :: Maybe Text
$sel:jobId:PutJobSuccessResult' :: PutJobSuccessResult -> Text
$sel:outputVariables:PutJobSuccessResult' :: PutJobSuccessResult -> Maybe (HashMap Text Text)
$sel:executionDetails:PutJobSuccessResult' :: PutJobSuccessResult -> Maybe ExecutionDetails
$sel:currentRevision:PutJobSuccessResult' :: PutJobSuccessResult -> Maybe CurrentRevision
$sel:continuationToken:PutJobSuccessResult' :: PutJobSuccessResult -> Maybe Text
..} =
    [Pair] -> Value
Data.object
      ( forall a. [Maybe a] -> [a]
Prelude.catMaybes
          [ (Key
"continuationToken" 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
continuationToken,
            (Key
"currentRevision" 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 CurrentRevision
currentRevision,
            (Key
"executionDetails" 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 ExecutionDetails
executionDetails,
            (Key
"outputVariables" 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)
outputVariables,
            forall a. a -> Maybe a
Prelude.Just (Key
"jobId" forall kv v. (KeyValue kv, ToJSON v) => Key -> v -> kv
Data..= Text
jobId)
          ]
      )

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

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

-- | /See:/ 'newPutJobSuccessResultResponse' smart constructor.
data PutJobSuccessResultResponse = PutJobSuccessResultResponse'
  {
  }
  deriving (PutJobSuccessResultResponse -> PutJobSuccessResultResponse -> Bool
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: PutJobSuccessResultResponse -> PutJobSuccessResultResponse -> Bool
$c/= :: PutJobSuccessResultResponse -> PutJobSuccessResultResponse -> Bool
== :: PutJobSuccessResultResponse -> PutJobSuccessResultResponse -> Bool
$c== :: PutJobSuccessResultResponse -> PutJobSuccessResultResponse -> Bool
Prelude.Eq, ReadPrec [PutJobSuccessResultResponse]
ReadPrec PutJobSuccessResultResponse
Int -> ReadS PutJobSuccessResultResponse
ReadS [PutJobSuccessResultResponse]
forall a.
(Int -> ReadS a)
-> ReadS [a] -> ReadPrec a -> ReadPrec [a] -> Read a
readListPrec :: ReadPrec [PutJobSuccessResultResponse]
$creadListPrec :: ReadPrec [PutJobSuccessResultResponse]
readPrec :: ReadPrec PutJobSuccessResultResponse
$creadPrec :: ReadPrec PutJobSuccessResultResponse
readList :: ReadS [PutJobSuccessResultResponse]
$creadList :: ReadS [PutJobSuccessResultResponse]
readsPrec :: Int -> ReadS PutJobSuccessResultResponse
$creadsPrec :: Int -> ReadS PutJobSuccessResultResponse
Prelude.Read, Int -> PutJobSuccessResultResponse -> ShowS
[PutJobSuccessResultResponse] -> ShowS
PutJobSuccessResultResponse -> String
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [PutJobSuccessResultResponse] -> ShowS
$cshowList :: [PutJobSuccessResultResponse] -> ShowS
show :: PutJobSuccessResultResponse -> String
$cshow :: PutJobSuccessResultResponse -> String
showsPrec :: Int -> PutJobSuccessResultResponse -> ShowS
$cshowsPrec :: Int -> PutJobSuccessResultResponse -> ShowS
Prelude.Show, forall x.
Rep PutJobSuccessResultResponse x -> PutJobSuccessResultResponse
forall x.
PutJobSuccessResultResponse -> Rep PutJobSuccessResultResponse x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cto :: forall x.
Rep PutJobSuccessResultResponse x -> PutJobSuccessResultResponse
$cfrom :: forall x.
PutJobSuccessResultResponse -> Rep PutJobSuccessResultResponse x
Prelude.Generic)

-- |
-- Create a value of 'PutJobSuccessResultResponse' 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.
newPutJobSuccessResultResponse ::
  PutJobSuccessResultResponse
newPutJobSuccessResultResponse :: PutJobSuccessResultResponse
newPutJobSuccessResultResponse =
  PutJobSuccessResultResponse
PutJobSuccessResultResponse'

instance Prelude.NFData PutJobSuccessResultResponse where
  rnf :: PutJobSuccessResultResponse -> ()
rnf PutJobSuccessResultResponse
_ = ()