{-# 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.PutThirdPartyJobSuccessResult
-- 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 third party job as returned to the pipeline
-- by a job worker. Used for partner actions only.
module Amazonka.CodePipeline.PutThirdPartyJobSuccessResult
  ( -- * Creating a Request
    PutThirdPartyJobSuccessResult (..),
    newPutThirdPartyJobSuccessResult,

    -- * Request Lenses
    putThirdPartyJobSuccessResult_continuationToken,
    putThirdPartyJobSuccessResult_currentRevision,
    putThirdPartyJobSuccessResult_executionDetails,
    putThirdPartyJobSuccessResult_jobId,
    putThirdPartyJobSuccessResult_clientToken,

    -- * Destructuring the Response
    PutThirdPartyJobSuccessResultResponse (..),
    newPutThirdPartyJobSuccessResultResponse,
  )
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 @PutThirdPartyJobSuccessResult@ action.
--
-- /See:/ 'newPutThirdPartyJobSuccessResult' smart constructor.
data PutThirdPartyJobSuccessResult = PutThirdPartyJobSuccessResult'
  { -- | A token generated by a job worker, such as an AWS CodeDeploy deployment
    -- ID, that a successful job provides to identify a partner 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 partner action. When the action is complete, no
    -- continuation token should be supplied.
    PutThirdPartyJobSuccessResult -> Maybe Text
continuationToken :: Prelude.Maybe Prelude.Text,
    -- | Represents information about a current revision.
    PutThirdPartyJobSuccessResult -> Maybe CurrentRevision
currentRevision :: Prelude.Maybe CurrentRevision,
    -- | The details of the actions taken and results produced on an artifact as
    -- it passes through stages in the pipeline.
    PutThirdPartyJobSuccessResult -> Maybe ExecutionDetails
executionDetails :: Prelude.Maybe ExecutionDetails,
    -- | The ID of the job that successfully completed. This is the same ID
    -- returned from @PollForThirdPartyJobs@.
    PutThirdPartyJobSuccessResult -> Text
jobId :: Prelude.Text,
    -- | The clientToken portion of the clientId and clientToken pair used to
    -- verify that the calling entity is allowed access to the job and its
    -- details.
    PutThirdPartyJobSuccessResult -> Text
clientToken :: Prelude.Text
  }
  deriving (PutThirdPartyJobSuccessResult
-> PutThirdPartyJobSuccessResult -> Bool
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: PutThirdPartyJobSuccessResult
-> PutThirdPartyJobSuccessResult -> Bool
$c/= :: PutThirdPartyJobSuccessResult
-> PutThirdPartyJobSuccessResult -> Bool
== :: PutThirdPartyJobSuccessResult
-> PutThirdPartyJobSuccessResult -> Bool
$c== :: PutThirdPartyJobSuccessResult
-> PutThirdPartyJobSuccessResult -> Bool
Prelude.Eq, ReadPrec [PutThirdPartyJobSuccessResult]
ReadPrec PutThirdPartyJobSuccessResult
Int -> ReadS PutThirdPartyJobSuccessResult
ReadS [PutThirdPartyJobSuccessResult]
forall a.
(Int -> ReadS a)
-> ReadS [a] -> ReadPrec a -> ReadPrec [a] -> Read a
readListPrec :: ReadPrec [PutThirdPartyJobSuccessResult]
$creadListPrec :: ReadPrec [PutThirdPartyJobSuccessResult]
readPrec :: ReadPrec PutThirdPartyJobSuccessResult
$creadPrec :: ReadPrec PutThirdPartyJobSuccessResult
readList :: ReadS [PutThirdPartyJobSuccessResult]
$creadList :: ReadS [PutThirdPartyJobSuccessResult]
readsPrec :: Int -> ReadS PutThirdPartyJobSuccessResult
$creadsPrec :: Int -> ReadS PutThirdPartyJobSuccessResult
Prelude.Read, Int -> PutThirdPartyJobSuccessResult -> ShowS
[PutThirdPartyJobSuccessResult] -> ShowS
PutThirdPartyJobSuccessResult -> String
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [PutThirdPartyJobSuccessResult] -> ShowS
$cshowList :: [PutThirdPartyJobSuccessResult] -> ShowS
show :: PutThirdPartyJobSuccessResult -> String
$cshow :: PutThirdPartyJobSuccessResult -> String
showsPrec :: Int -> PutThirdPartyJobSuccessResult -> ShowS
$cshowsPrec :: Int -> PutThirdPartyJobSuccessResult -> ShowS
Prelude.Show, forall x.
Rep PutThirdPartyJobSuccessResult x
-> PutThirdPartyJobSuccessResult
forall x.
PutThirdPartyJobSuccessResult
-> Rep PutThirdPartyJobSuccessResult x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cto :: forall x.
Rep PutThirdPartyJobSuccessResult x
-> PutThirdPartyJobSuccessResult
$cfrom :: forall x.
PutThirdPartyJobSuccessResult
-> Rep PutThirdPartyJobSuccessResult x
Prelude.Generic)

-- |
-- Create a value of 'PutThirdPartyJobSuccessResult' 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', 'putThirdPartyJobSuccessResult_continuationToken' - A token generated by a job worker, such as an AWS CodeDeploy deployment
-- ID, that a successful job provides to identify a partner 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 partner action. When the action is complete, no
-- continuation token should be supplied.
--
-- 'currentRevision', 'putThirdPartyJobSuccessResult_currentRevision' - Represents information about a current revision.
--
-- 'executionDetails', 'putThirdPartyJobSuccessResult_executionDetails' - The details of the actions taken and results produced on an artifact as
-- it passes through stages in the pipeline.
--
-- 'jobId', 'putThirdPartyJobSuccessResult_jobId' - The ID of the job that successfully completed. This is the same ID
-- returned from @PollForThirdPartyJobs@.
--
-- 'clientToken', 'putThirdPartyJobSuccessResult_clientToken' - The clientToken portion of the clientId and clientToken pair used to
-- verify that the calling entity is allowed access to the job and its
-- details.
newPutThirdPartyJobSuccessResult ::
  -- | 'jobId'
  Prelude.Text ->
  -- | 'clientToken'
  Prelude.Text ->
  PutThirdPartyJobSuccessResult
newPutThirdPartyJobSuccessResult :: Text -> Text -> PutThirdPartyJobSuccessResult
newPutThirdPartyJobSuccessResult
  Text
pJobId_
  Text
pClientToken_ =
    PutThirdPartyJobSuccessResult'
      { $sel:continuationToken:PutThirdPartyJobSuccessResult' :: Maybe Text
continuationToken =
          forall a. Maybe a
Prelude.Nothing,
        $sel:currentRevision:PutThirdPartyJobSuccessResult' :: Maybe CurrentRevision
currentRevision = forall a. Maybe a
Prelude.Nothing,
        $sel:executionDetails:PutThirdPartyJobSuccessResult' :: Maybe ExecutionDetails
executionDetails = forall a. Maybe a
Prelude.Nothing,
        $sel:jobId:PutThirdPartyJobSuccessResult' :: Text
jobId = Text
pJobId_,
        $sel:clientToken:PutThirdPartyJobSuccessResult' :: Text
clientToken = Text
pClientToken_
      }

-- | A token generated by a job worker, such as an AWS CodeDeploy deployment
-- ID, that a successful job provides to identify a partner 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 partner action. When the action is complete, no
-- continuation token should be supplied.
putThirdPartyJobSuccessResult_continuationToken :: Lens.Lens' PutThirdPartyJobSuccessResult (Prelude.Maybe Prelude.Text)
putThirdPartyJobSuccessResult_continuationToken :: Lens' PutThirdPartyJobSuccessResult (Maybe Text)
putThirdPartyJobSuccessResult_continuationToken = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\PutThirdPartyJobSuccessResult' {Maybe Text
continuationToken :: Maybe Text
$sel:continuationToken:PutThirdPartyJobSuccessResult' :: PutThirdPartyJobSuccessResult -> Maybe Text
continuationToken} -> Maybe Text
continuationToken) (\s :: PutThirdPartyJobSuccessResult
s@PutThirdPartyJobSuccessResult' {} Maybe Text
a -> PutThirdPartyJobSuccessResult
s {$sel:continuationToken:PutThirdPartyJobSuccessResult' :: Maybe Text
continuationToken = Maybe Text
a} :: PutThirdPartyJobSuccessResult)

-- | Represents information about a current revision.
putThirdPartyJobSuccessResult_currentRevision :: Lens.Lens' PutThirdPartyJobSuccessResult (Prelude.Maybe CurrentRevision)
putThirdPartyJobSuccessResult_currentRevision :: Lens' PutThirdPartyJobSuccessResult (Maybe CurrentRevision)
putThirdPartyJobSuccessResult_currentRevision = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\PutThirdPartyJobSuccessResult' {Maybe CurrentRevision
currentRevision :: Maybe CurrentRevision
$sel:currentRevision:PutThirdPartyJobSuccessResult' :: PutThirdPartyJobSuccessResult -> Maybe CurrentRevision
currentRevision} -> Maybe CurrentRevision
currentRevision) (\s :: PutThirdPartyJobSuccessResult
s@PutThirdPartyJobSuccessResult' {} Maybe CurrentRevision
a -> PutThirdPartyJobSuccessResult
s {$sel:currentRevision:PutThirdPartyJobSuccessResult' :: Maybe CurrentRevision
currentRevision = Maybe CurrentRevision
a} :: PutThirdPartyJobSuccessResult)

-- | The details of the actions taken and results produced on an artifact as
-- it passes through stages in the pipeline.
putThirdPartyJobSuccessResult_executionDetails :: Lens.Lens' PutThirdPartyJobSuccessResult (Prelude.Maybe ExecutionDetails)
putThirdPartyJobSuccessResult_executionDetails :: Lens' PutThirdPartyJobSuccessResult (Maybe ExecutionDetails)
putThirdPartyJobSuccessResult_executionDetails = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\PutThirdPartyJobSuccessResult' {Maybe ExecutionDetails
executionDetails :: Maybe ExecutionDetails
$sel:executionDetails:PutThirdPartyJobSuccessResult' :: PutThirdPartyJobSuccessResult -> Maybe ExecutionDetails
executionDetails} -> Maybe ExecutionDetails
executionDetails) (\s :: PutThirdPartyJobSuccessResult
s@PutThirdPartyJobSuccessResult' {} Maybe ExecutionDetails
a -> PutThirdPartyJobSuccessResult
s {$sel:executionDetails:PutThirdPartyJobSuccessResult' :: Maybe ExecutionDetails
executionDetails = Maybe ExecutionDetails
a} :: PutThirdPartyJobSuccessResult)

-- | The ID of the job that successfully completed. This is the same ID
-- returned from @PollForThirdPartyJobs@.
putThirdPartyJobSuccessResult_jobId :: Lens.Lens' PutThirdPartyJobSuccessResult Prelude.Text
putThirdPartyJobSuccessResult_jobId :: Lens' PutThirdPartyJobSuccessResult Text
putThirdPartyJobSuccessResult_jobId = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\PutThirdPartyJobSuccessResult' {Text
jobId :: Text
$sel:jobId:PutThirdPartyJobSuccessResult' :: PutThirdPartyJobSuccessResult -> Text
jobId} -> Text
jobId) (\s :: PutThirdPartyJobSuccessResult
s@PutThirdPartyJobSuccessResult' {} Text
a -> PutThirdPartyJobSuccessResult
s {$sel:jobId:PutThirdPartyJobSuccessResult' :: Text
jobId = Text
a} :: PutThirdPartyJobSuccessResult)

-- | The clientToken portion of the clientId and clientToken pair used to
-- verify that the calling entity is allowed access to the job and its
-- details.
putThirdPartyJobSuccessResult_clientToken :: Lens.Lens' PutThirdPartyJobSuccessResult Prelude.Text
putThirdPartyJobSuccessResult_clientToken :: Lens' PutThirdPartyJobSuccessResult Text
putThirdPartyJobSuccessResult_clientToken = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\PutThirdPartyJobSuccessResult' {Text
clientToken :: Text
$sel:clientToken:PutThirdPartyJobSuccessResult' :: PutThirdPartyJobSuccessResult -> Text
clientToken} -> Text
clientToken) (\s :: PutThirdPartyJobSuccessResult
s@PutThirdPartyJobSuccessResult' {} Text
a -> PutThirdPartyJobSuccessResult
s {$sel:clientToken:PutThirdPartyJobSuccessResult' :: Text
clientToken = Text
a} :: PutThirdPartyJobSuccessResult)

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

instance
  Prelude.Hashable
    PutThirdPartyJobSuccessResult
  where
  hashWithSalt :: Int -> PutThirdPartyJobSuccessResult -> Int
hashWithSalt Int
_salt PutThirdPartyJobSuccessResult' {Maybe Text
Maybe CurrentRevision
Maybe ExecutionDetails
Text
clientToken :: Text
jobId :: Text
executionDetails :: Maybe ExecutionDetails
currentRevision :: Maybe CurrentRevision
continuationToken :: Maybe Text
$sel:clientToken:PutThirdPartyJobSuccessResult' :: PutThirdPartyJobSuccessResult -> Text
$sel:jobId:PutThirdPartyJobSuccessResult' :: PutThirdPartyJobSuccessResult -> Text
$sel:executionDetails:PutThirdPartyJobSuccessResult' :: PutThirdPartyJobSuccessResult -> Maybe ExecutionDetails
$sel:currentRevision:PutThirdPartyJobSuccessResult' :: PutThirdPartyJobSuccessResult -> Maybe CurrentRevision
$sel:continuationToken:PutThirdPartyJobSuccessResult' :: PutThirdPartyJobSuccessResult -> 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` Text
jobId
      forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Text
clientToken

instance Prelude.NFData PutThirdPartyJobSuccessResult where
  rnf :: PutThirdPartyJobSuccessResult -> ()
rnf PutThirdPartyJobSuccessResult' {Maybe Text
Maybe CurrentRevision
Maybe ExecutionDetails
Text
clientToken :: Text
jobId :: Text
executionDetails :: Maybe ExecutionDetails
currentRevision :: Maybe CurrentRevision
continuationToken :: Maybe Text
$sel:clientToken:PutThirdPartyJobSuccessResult' :: PutThirdPartyJobSuccessResult -> Text
$sel:jobId:PutThirdPartyJobSuccessResult' :: PutThirdPartyJobSuccessResult -> Text
$sel:executionDetails:PutThirdPartyJobSuccessResult' :: PutThirdPartyJobSuccessResult -> Maybe ExecutionDetails
$sel:currentRevision:PutThirdPartyJobSuccessResult' :: PutThirdPartyJobSuccessResult -> Maybe CurrentRevision
$sel:continuationToken:PutThirdPartyJobSuccessResult' :: PutThirdPartyJobSuccessResult -> 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 Text
jobId
      seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf Text
clientToken

instance Data.ToHeaders PutThirdPartyJobSuccessResult where
  toHeaders :: PutThirdPartyJobSuccessResult -> [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.PutThirdPartyJobSuccessResult" ::
                          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 PutThirdPartyJobSuccessResult where
  toJSON :: PutThirdPartyJobSuccessResult -> Value
toJSON PutThirdPartyJobSuccessResult' {Maybe Text
Maybe CurrentRevision
Maybe ExecutionDetails
Text
clientToken :: Text
jobId :: Text
executionDetails :: Maybe ExecutionDetails
currentRevision :: Maybe CurrentRevision
continuationToken :: Maybe Text
$sel:clientToken:PutThirdPartyJobSuccessResult' :: PutThirdPartyJobSuccessResult -> Text
$sel:jobId:PutThirdPartyJobSuccessResult' :: PutThirdPartyJobSuccessResult -> Text
$sel:executionDetails:PutThirdPartyJobSuccessResult' :: PutThirdPartyJobSuccessResult -> Maybe ExecutionDetails
$sel:currentRevision:PutThirdPartyJobSuccessResult' :: PutThirdPartyJobSuccessResult -> Maybe CurrentRevision
$sel:continuationToken:PutThirdPartyJobSuccessResult' :: PutThirdPartyJobSuccessResult -> 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,
            forall a. a -> Maybe a
Prelude.Just (Key
"jobId" forall kv v. (KeyValue kv, ToJSON v) => Key -> v -> kv
Data..= Text
jobId),
            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 PutThirdPartyJobSuccessResult where
  toPath :: PutThirdPartyJobSuccessResult -> ByteString
toPath = forall a b. a -> b -> a
Prelude.const ByteString
"/"

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

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

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

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