{-# 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.ImportExport.UpdateJob
-- Copyright   : (c) 2013-2023 Brendan Hay
-- License     : Mozilla Public License, v. 2.0.
-- Maintainer  : Brendan Hay
-- Stability   : auto-generated
-- Portability : non-portable (GHC extensions)
--
-- You use this operation to change the parameters specified in the
-- original manifest file by supplying a new manifest file. The manifest
-- file attached to this request replaces the original manifest file. You
-- can only use the operation after a CreateJob request but before the data
-- transfer starts and you can only use it on jobs you own.
module Amazonka.ImportExport.UpdateJob
  ( -- * Creating a Request
    UpdateJob (..),
    newUpdateJob,

    -- * Request Lenses
    updateJob_aPIVersion,
    updateJob_jobId,
    updateJob_manifest,
    updateJob_jobType,
    updateJob_validateOnly,

    -- * Destructuring the Response
    UpdateJobResponse (..),
    newUpdateJobResponse,

    -- * Response Lenses
    updateJobResponse_artifactList,
    updateJobResponse_success,
    updateJobResponse_warningMessage,
    updateJobResponse_httpStatus,
  )
where

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

-- | Input structure for the UpateJob operation.
--
-- /See:/ 'newUpdateJob' smart constructor.
data UpdateJob = UpdateJob'
  { UpdateJob -> Maybe Text
aPIVersion :: Prelude.Maybe Prelude.Text,
    UpdateJob -> Text
jobId :: Prelude.Text,
    UpdateJob -> Text
manifest :: Prelude.Text,
    UpdateJob -> JobType
jobType :: JobType,
    UpdateJob -> Bool
validateOnly :: Prelude.Bool
  }
  deriving (UpdateJob -> UpdateJob -> Bool
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: UpdateJob -> UpdateJob -> Bool
$c/= :: UpdateJob -> UpdateJob -> Bool
== :: UpdateJob -> UpdateJob -> Bool
$c== :: UpdateJob -> UpdateJob -> Bool
Prelude.Eq, ReadPrec [UpdateJob]
ReadPrec UpdateJob
Int -> ReadS UpdateJob
ReadS [UpdateJob]
forall a.
(Int -> ReadS a)
-> ReadS [a] -> ReadPrec a -> ReadPrec [a] -> Read a
readListPrec :: ReadPrec [UpdateJob]
$creadListPrec :: ReadPrec [UpdateJob]
readPrec :: ReadPrec UpdateJob
$creadPrec :: ReadPrec UpdateJob
readList :: ReadS [UpdateJob]
$creadList :: ReadS [UpdateJob]
readsPrec :: Int -> ReadS UpdateJob
$creadsPrec :: Int -> ReadS UpdateJob
Prelude.Read, Int -> UpdateJob -> ShowS
[UpdateJob] -> ShowS
UpdateJob -> String
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [UpdateJob] -> ShowS
$cshowList :: [UpdateJob] -> ShowS
show :: UpdateJob -> String
$cshow :: UpdateJob -> String
showsPrec :: Int -> UpdateJob -> ShowS
$cshowsPrec :: Int -> UpdateJob -> ShowS
Prelude.Show, forall x. Rep UpdateJob x -> UpdateJob
forall x. UpdateJob -> Rep UpdateJob x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cto :: forall x. Rep UpdateJob x -> UpdateJob
$cfrom :: forall x. UpdateJob -> Rep UpdateJob x
Prelude.Generic)

-- |
-- Create a value of 'UpdateJob' 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:
--
-- 'aPIVersion', 'updateJob_aPIVersion' - Undocumented member.
--
-- 'jobId', 'updateJob_jobId' - Undocumented member.
--
-- 'manifest', 'updateJob_manifest' - Undocumented member.
--
-- 'jobType', 'updateJob_jobType' - Undocumented member.
--
-- 'validateOnly', 'updateJob_validateOnly' - Undocumented member.
newUpdateJob ::
  -- | 'jobId'
  Prelude.Text ->
  -- | 'manifest'
  Prelude.Text ->
  -- | 'jobType'
  JobType ->
  -- | 'validateOnly'
  Prelude.Bool ->
  UpdateJob
newUpdateJob :: Text -> Text -> JobType -> Bool -> UpdateJob
newUpdateJob
  Text
pJobId_
  Text
pManifest_
  JobType
pJobType_
  Bool
pValidateOnly_ =
    UpdateJob'
      { $sel:aPIVersion:UpdateJob' :: Maybe Text
aPIVersion = forall a. Maybe a
Prelude.Nothing,
        $sel:jobId:UpdateJob' :: Text
jobId = Text
pJobId_,
        $sel:manifest:UpdateJob' :: Text
manifest = Text
pManifest_,
        $sel:jobType:UpdateJob' :: JobType
jobType = JobType
pJobType_,
        $sel:validateOnly:UpdateJob' :: Bool
validateOnly = Bool
pValidateOnly_
      }

-- | Undocumented member.
updateJob_aPIVersion :: Lens.Lens' UpdateJob (Prelude.Maybe Prelude.Text)
updateJob_aPIVersion :: Lens' UpdateJob (Maybe Text)
updateJob_aPIVersion = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\UpdateJob' {Maybe Text
aPIVersion :: Maybe Text
$sel:aPIVersion:UpdateJob' :: UpdateJob -> Maybe Text
aPIVersion} -> Maybe Text
aPIVersion) (\s :: UpdateJob
s@UpdateJob' {} Maybe Text
a -> UpdateJob
s {$sel:aPIVersion:UpdateJob' :: Maybe Text
aPIVersion = Maybe Text
a} :: UpdateJob)

-- | Undocumented member.
updateJob_jobId :: Lens.Lens' UpdateJob Prelude.Text
updateJob_jobId :: Lens' UpdateJob Text
updateJob_jobId = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\UpdateJob' {Text
jobId :: Text
$sel:jobId:UpdateJob' :: UpdateJob -> Text
jobId} -> Text
jobId) (\s :: UpdateJob
s@UpdateJob' {} Text
a -> UpdateJob
s {$sel:jobId:UpdateJob' :: Text
jobId = Text
a} :: UpdateJob)

-- | Undocumented member.
updateJob_manifest :: Lens.Lens' UpdateJob Prelude.Text
updateJob_manifest :: Lens' UpdateJob Text
updateJob_manifest = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\UpdateJob' {Text
manifest :: Text
$sel:manifest:UpdateJob' :: UpdateJob -> Text
manifest} -> Text
manifest) (\s :: UpdateJob
s@UpdateJob' {} Text
a -> UpdateJob
s {$sel:manifest:UpdateJob' :: Text
manifest = Text
a} :: UpdateJob)

-- | Undocumented member.
updateJob_jobType :: Lens.Lens' UpdateJob JobType
updateJob_jobType :: Lens' UpdateJob JobType
updateJob_jobType = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\UpdateJob' {JobType
jobType :: JobType
$sel:jobType:UpdateJob' :: UpdateJob -> JobType
jobType} -> JobType
jobType) (\s :: UpdateJob
s@UpdateJob' {} JobType
a -> UpdateJob
s {$sel:jobType:UpdateJob' :: JobType
jobType = JobType
a} :: UpdateJob)

-- | Undocumented member.
updateJob_validateOnly :: Lens.Lens' UpdateJob Prelude.Bool
updateJob_validateOnly :: Lens' UpdateJob Bool
updateJob_validateOnly = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\UpdateJob' {Bool
validateOnly :: Bool
$sel:validateOnly:UpdateJob' :: UpdateJob -> Bool
validateOnly} -> Bool
validateOnly) (\s :: UpdateJob
s@UpdateJob' {} Bool
a -> UpdateJob
s {$sel:validateOnly:UpdateJob' :: Bool
validateOnly = Bool
a} :: UpdateJob)

instance Core.AWSRequest UpdateJob where
  type AWSResponse UpdateJob = UpdateJobResponse
  request :: (Service -> Service) -> UpdateJob -> Request UpdateJob
request Service -> Service
overrides =
    forall a. ToRequest a => Service -> a -> Request a
Request.postQuery (Service -> Service
overrides Service
defaultService)
  response :: forall (m :: * -> *).
MonadResource m =>
(ByteStringLazy -> IO ByteStringLazy)
-> Service
-> Proxy UpdateJob
-> ClientResponse ClientBody
-> m (Either Error (ClientResponse (AWSResponse UpdateJob)))
response =
    forall (m :: * -> *) a.
MonadResource m =>
Text
-> (Int
    -> ResponseHeaders -> [Node] -> Either String (AWSResponse a))
-> (ByteStringLazy -> IO ByteStringLazy)
-> Service
-> Proxy a
-> ClientResponse ClientBody
-> m (Either Error (ClientResponse (AWSResponse a)))
Response.receiveXMLWrapper
      Text
"UpdateJobResult"
      ( \Int
s ResponseHeaders
h [Node]
x ->
          Maybe [Artifact]
-> Maybe Bool -> Maybe Text -> Int -> UpdateJobResponse
UpdateJobResponse'
            forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
Prelude.<$> ( [Node]
x
                            forall a. FromXML a => [Node] -> Text -> Either String (Maybe a)
Data..@? Text
"ArtifactList"
                            forall (f :: * -> *) a. Functor f => f (Maybe a) -> a -> f a
Core..!@ forall a. Monoid a => a
Prelude.mempty
                            forall (m :: * -> *) a b. Monad m => m a -> (a -> m b) -> m b
Prelude.>>= forall (f :: * -> *) a b.
Applicative f =>
([a] -> f b) -> [a] -> f (Maybe b)
Core.may (forall a. FromXML a => Text -> [Node] -> Either String [a]
Data.parseXMLList Text
"member")
                        )
            forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
Prelude.<*> ([Node]
x forall a. FromXML a => [Node] -> Text -> Either String (Maybe a)
Data..@? Text
"Success")
            forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
Prelude.<*> ([Node]
x forall a. FromXML a => [Node] -> Text -> Either String (Maybe a)
Data..@? Text
"WarningMessage")
            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 UpdateJob where
  hashWithSalt :: Int -> UpdateJob -> Int
hashWithSalt Int
_salt UpdateJob' {Bool
Maybe Text
Text
JobType
validateOnly :: Bool
jobType :: JobType
manifest :: Text
jobId :: Text
aPIVersion :: Maybe Text
$sel:validateOnly:UpdateJob' :: UpdateJob -> Bool
$sel:jobType:UpdateJob' :: UpdateJob -> JobType
$sel:manifest:UpdateJob' :: UpdateJob -> Text
$sel:jobId:UpdateJob' :: UpdateJob -> Text
$sel:aPIVersion:UpdateJob' :: UpdateJob -> Maybe Text
..} =
    Int
_salt
      forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Maybe Text
aPIVersion
      forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Text
jobId
      forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Text
manifest
      forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` JobType
jobType
      forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Bool
validateOnly

instance Prelude.NFData UpdateJob where
  rnf :: UpdateJob -> ()
rnf UpdateJob' {Bool
Maybe Text
Text
JobType
validateOnly :: Bool
jobType :: JobType
manifest :: Text
jobId :: Text
aPIVersion :: Maybe Text
$sel:validateOnly:UpdateJob' :: UpdateJob -> Bool
$sel:jobType:UpdateJob' :: UpdateJob -> JobType
$sel:manifest:UpdateJob' :: UpdateJob -> Text
$sel:jobId:UpdateJob' :: UpdateJob -> Text
$sel:aPIVersion:UpdateJob' :: UpdateJob -> Maybe Text
..} =
    forall a. NFData a => a -> ()
Prelude.rnf Maybe Text
aPIVersion
      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
manifest
      seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf JobType
jobType
      seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf Bool
validateOnly

instance Data.ToHeaders UpdateJob where
  toHeaders :: UpdateJob -> ResponseHeaders
toHeaders = forall a b. a -> b -> a
Prelude.const forall a. Monoid a => a
Prelude.mempty

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

instance Data.ToQuery UpdateJob where
  toQuery :: UpdateJob -> QueryString
toQuery UpdateJob' {Bool
Maybe Text
Text
JobType
validateOnly :: Bool
jobType :: JobType
manifest :: Text
jobId :: Text
aPIVersion :: Maybe Text
$sel:validateOnly:UpdateJob' :: UpdateJob -> Bool
$sel:jobType:UpdateJob' :: UpdateJob -> JobType
$sel:manifest:UpdateJob' :: UpdateJob -> Text
$sel:jobId:UpdateJob' :: UpdateJob -> Text
$sel:aPIVersion:UpdateJob' :: UpdateJob -> Maybe Text
..} =
    forall a. Monoid a => [a] -> a
Prelude.mconcat
      [ QueryString
"Operation=UpdateJob",
        ByteString
"Action" forall a. ToQuery a => ByteString -> a -> QueryString
Data.=: (ByteString
"UpdateJob" :: Prelude.ByteString),
        ByteString
"Version"
          forall a. ToQuery a => ByteString -> a -> QueryString
Data.=: (ByteString
"2010-06-01" :: Prelude.ByteString),
        ByteString
"APIVersion" forall a. ToQuery a => ByteString -> a -> QueryString
Data.=: Maybe Text
aPIVersion,
        ByteString
"JobId" forall a. ToQuery a => ByteString -> a -> QueryString
Data.=: Text
jobId,
        ByteString
"Manifest" forall a. ToQuery a => ByteString -> a -> QueryString
Data.=: Text
manifest,
        ByteString
"JobType" forall a. ToQuery a => ByteString -> a -> QueryString
Data.=: JobType
jobType,
        ByteString
"ValidateOnly" forall a. ToQuery a => ByteString -> a -> QueryString
Data.=: Bool
validateOnly
      ]

-- | Output structure for the UpateJob operation.
--
-- /See:/ 'newUpdateJobResponse' smart constructor.
data UpdateJobResponse = UpdateJobResponse'
  { UpdateJobResponse -> Maybe [Artifact]
artifactList :: Prelude.Maybe [Artifact],
    UpdateJobResponse -> Maybe Bool
success :: Prelude.Maybe Prelude.Bool,
    UpdateJobResponse -> Maybe Text
warningMessage :: Prelude.Maybe Prelude.Text,
    -- | The response's http status code.
    UpdateJobResponse -> Int
httpStatus :: Prelude.Int
  }
  deriving (UpdateJobResponse -> UpdateJobResponse -> Bool
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: UpdateJobResponse -> UpdateJobResponse -> Bool
$c/= :: UpdateJobResponse -> UpdateJobResponse -> Bool
== :: UpdateJobResponse -> UpdateJobResponse -> Bool
$c== :: UpdateJobResponse -> UpdateJobResponse -> Bool
Prelude.Eq, ReadPrec [UpdateJobResponse]
ReadPrec UpdateJobResponse
Int -> ReadS UpdateJobResponse
ReadS [UpdateJobResponse]
forall a.
(Int -> ReadS a)
-> ReadS [a] -> ReadPrec a -> ReadPrec [a] -> Read a
readListPrec :: ReadPrec [UpdateJobResponse]
$creadListPrec :: ReadPrec [UpdateJobResponse]
readPrec :: ReadPrec UpdateJobResponse
$creadPrec :: ReadPrec UpdateJobResponse
readList :: ReadS [UpdateJobResponse]
$creadList :: ReadS [UpdateJobResponse]
readsPrec :: Int -> ReadS UpdateJobResponse
$creadsPrec :: Int -> ReadS UpdateJobResponse
Prelude.Read, Int -> UpdateJobResponse -> ShowS
[UpdateJobResponse] -> ShowS
UpdateJobResponse -> String
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [UpdateJobResponse] -> ShowS
$cshowList :: [UpdateJobResponse] -> ShowS
show :: UpdateJobResponse -> String
$cshow :: UpdateJobResponse -> String
showsPrec :: Int -> UpdateJobResponse -> ShowS
$cshowsPrec :: Int -> UpdateJobResponse -> ShowS
Prelude.Show, forall x. Rep UpdateJobResponse x -> UpdateJobResponse
forall x. UpdateJobResponse -> Rep UpdateJobResponse x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cto :: forall x. Rep UpdateJobResponse x -> UpdateJobResponse
$cfrom :: forall x. UpdateJobResponse -> Rep UpdateJobResponse x
Prelude.Generic)

-- |
-- Create a value of 'UpdateJobResponse' 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:
--
-- 'artifactList', 'updateJobResponse_artifactList' - Undocumented member.
--
-- 'success', 'updateJobResponse_success' - Undocumented member.
--
-- 'warningMessage', 'updateJobResponse_warningMessage' - Undocumented member.
--
-- 'httpStatus', 'updateJobResponse_httpStatus' - The response's http status code.
newUpdateJobResponse ::
  -- | 'httpStatus'
  Prelude.Int ->
  UpdateJobResponse
newUpdateJobResponse :: Int -> UpdateJobResponse
newUpdateJobResponse Int
pHttpStatus_ =
  UpdateJobResponse'
    { $sel:artifactList:UpdateJobResponse' :: Maybe [Artifact]
artifactList = forall a. Maybe a
Prelude.Nothing,
      $sel:success:UpdateJobResponse' :: Maybe Bool
success = forall a. Maybe a
Prelude.Nothing,
      $sel:warningMessage:UpdateJobResponse' :: Maybe Text
warningMessage = forall a. Maybe a
Prelude.Nothing,
      $sel:httpStatus:UpdateJobResponse' :: Int
httpStatus = Int
pHttpStatus_
    }

-- | Undocumented member.
updateJobResponse_artifactList :: Lens.Lens' UpdateJobResponse (Prelude.Maybe [Artifact])
updateJobResponse_artifactList :: Lens' UpdateJobResponse (Maybe [Artifact])
updateJobResponse_artifactList = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\UpdateJobResponse' {Maybe [Artifact]
artifactList :: Maybe [Artifact]
$sel:artifactList:UpdateJobResponse' :: UpdateJobResponse -> Maybe [Artifact]
artifactList} -> Maybe [Artifact]
artifactList) (\s :: UpdateJobResponse
s@UpdateJobResponse' {} Maybe [Artifact]
a -> UpdateJobResponse
s {$sel:artifactList:UpdateJobResponse' :: Maybe [Artifact]
artifactList = Maybe [Artifact]
a} :: UpdateJobResponse) 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

-- | Undocumented member.
updateJobResponse_success :: Lens.Lens' UpdateJobResponse (Prelude.Maybe Prelude.Bool)
updateJobResponse_success :: Lens' UpdateJobResponse (Maybe Bool)
updateJobResponse_success = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\UpdateJobResponse' {Maybe Bool
success :: Maybe Bool
$sel:success:UpdateJobResponse' :: UpdateJobResponse -> Maybe Bool
success} -> Maybe Bool
success) (\s :: UpdateJobResponse
s@UpdateJobResponse' {} Maybe Bool
a -> UpdateJobResponse
s {$sel:success:UpdateJobResponse' :: Maybe Bool
success = Maybe Bool
a} :: UpdateJobResponse)

-- | Undocumented member.
updateJobResponse_warningMessage :: Lens.Lens' UpdateJobResponse (Prelude.Maybe Prelude.Text)
updateJobResponse_warningMessage :: Lens' UpdateJobResponse (Maybe Text)
updateJobResponse_warningMessage = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\UpdateJobResponse' {Maybe Text
warningMessage :: Maybe Text
$sel:warningMessage:UpdateJobResponse' :: UpdateJobResponse -> Maybe Text
warningMessage} -> Maybe Text
warningMessage) (\s :: UpdateJobResponse
s@UpdateJobResponse' {} Maybe Text
a -> UpdateJobResponse
s {$sel:warningMessage:UpdateJobResponse' :: Maybe Text
warningMessage = Maybe Text
a} :: UpdateJobResponse)

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

instance Prelude.NFData UpdateJobResponse where
  rnf :: UpdateJobResponse -> ()
rnf UpdateJobResponse' {Int
Maybe Bool
Maybe [Artifact]
Maybe Text
httpStatus :: Int
warningMessage :: Maybe Text
success :: Maybe Bool
artifactList :: Maybe [Artifact]
$sel:httpStatus:UpdateJobResponse' :: UpdateJobResponse -> Int
$sel:warningMessage:UpdateJobResponse' :: UpdateJobResponse -> Maybe Text
$sel:success:UpdateJobResponse' :: UpdateJobResponse -> Maybe Bool
$sel:artifactList:UpdateJobResponse' :: UpdateJobResponse -> Maybe [Artifact]
..} =
    forall a. NFData a => a -> ()
Prelude.rnf Maybe [Artifact]
artifactList
      seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf Maybe Bool
success
      seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf Maybe Text
warningMessage
      seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf Int
httpStatus