{-# 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.IoTJobsData.StartNextPendingJobExecution
-- Copyright   : (c) 2013-2023 Brendan Hay
-- License     : Mozilla Public License, v. 2.0.
-- Maintainer  : Brendan Hay
-- Stability   : auto-generated
-- Portability : non-portable (GHC extensions)
--
-- Gets and starts the next pending (status IN_PROGRESS or QUEUED) job
-- execution for a thing.
module Amazonka.IoTJobsData.StartNextPendingJobExecution
  ( -- * Creating a Request
    StartNextPendingJobExecution (..),
    newStartNextPendingJobExecution,

    -- * Request Lenses
    startNextPendingJobExecution_statusDetails,
    startNextPendingJobExecution_stepTimeoutInMinutes,
    startNextPendingJobExecution_thingName,

    -- * Destructuring the Response
    StartNextPendingJobExecutionResponse (..),
    newStartNextPendingJobExecutionResponse,

    -- * Response Lenses
    startNextPendingJobExecutionResponse_execution,
    startNextPendingJobExecutionResponse_httpStatus,
  )
where

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

-- | /See:/ 'newStartNextPendingJobExecution' smart constructor.
data StartNextPendingJobExecution = StartNextPendingJobExecution'
  { -- | A collection of name\/value pairs that describe the status of the job
    -- execution. If not specified, the statusDetails are unchanged.
    StartNextPendingJobExecution -> Maybe (HashMap Text Text)
statusDetails :: Prelude.Maybe (Prelude.HashMap Prelude.Text Prelude.Text),
    -- | Specifies the amount of time this device has to finish execution of this
    -- job. If the job execution status is not set to a terminal state before
    -- this timer expires, or before the timer is reset (by calling
    -- @UpdateJobExecution@, setting the status to @IN_PROGRESS@ and specifying
    -- a new timeout value in field @stepTimeoutInMinutes@) the job execution
    -- status will be automatically set to @TIMED_OUT@. Note that setting this
    -- timeout has no effect on that job execution timeout which may have been
    -- specified when the job was created (@CreateJob@ using field
    -- @timeoutConfig@).
    StartNextPendingJobExecution -> Maybe Integer
stepTimeoutInMinutes :: Prelude.Maybe Prelude.Integer,
    -- | The name of the thing associated with the device.
    StartNextPendingJobExecution -> Text
thingName :: Prelude.Text
  }
  deriving (StartNextPendingJobExecution
-> StartNextPendingJobExecution -> Bool
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: StartNextPendingJobExecution
-> StartNextPendingJobExecution -> Bool
$c/= :: StartNextPendingJobExecution
-> StartNextPendingJobExecution -> Bool
== :: StartNextPendingJobExecution
-> StartNextPendingJobExecution -> Bool
$c== :: StartNextPendingJobExecution
-> StartNextPendingJobExecution -> Bool
Prelude.Eq, ReadPrec [StartNextPendingJobExecution]
ReadPrec StartNextPendingJobExecution
Int -> ReadS StartNextPendingJobExecution
ReadS [StartNextPendingJobExecution]
forall a.
(Int -> ReadS a)
-> ReadS [a] -> ReadPrec a -> ReadPrec [a] -> Read a
readListPrec :: ReadPrec [StartNextPendingJobExecution]
$creadListPrec :: ReadPrec [StartNextPendingJobExecution]
readPrec :: ReadPrec StartNextPendingJobExecution
$creadPrec :: ReadPrec StartNextPendingJobExecution
readList :: ReadS [StartNextPendingJobExecution]
$creadList :: ReadS [StartNextPendingJobExecution]
readsPrec :: Int -> ReadS StartNextPendingJobExecution
$creadsPrec :: Int -> ReadS StartNextPendingJobExecution
Prelude.Read, Int -> StartNextPendingJobExecution -> ShowS
[StartNextPendingJobExecution] -> ShowS
StartNextPendingJobExecution -> String
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [StartNextPendingJobExecution] -> ShowS
$cshowList :: [StartNextPendingJobExecution] -> ShowS
show :: StartNextPendingJobExecution -> String
$cshow :: StartNextPendingJobExecution -> String
showsPrec :: Int -> StartNextPendingJobExecution -> ShowS
$cshowsPrec :: Int -> StartNextPendingJobExecution -> ShowS
Prelude.Show, forall x.
Rep StartNextPendingJobExecution x -> StartNextPendingJobExecution
forall x.
StartNextPendingJobExecution -> Rep StartNextPendingJobExecution x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cto :: forall x.
Rep StartNextPendingJobExecution x -> StartNextPendingJobExecution
$cfrom :: forall x.
StartNextPendingJobExecution -> Rep StartNextPendingJobExecution x
Prelude.Generic)

-- |
-- Create a value of 'StartNextPendingJobExecution' 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:
--
-- 'statusDetails', 'startNextPendingJobExecution_statusDetails' - A collection of name\/value pairs that describe the status of the job
-- execution. If not specified, the statusDetails are unchanged.
--
-- 'stepTimeoutInMinutes', 'startNextPendingJobExecution_stepTimeoutInMinutes' - Specifies the amount of time this device has to finish execution of this
-- job. If the job execution status is not set to a terminal state before
-- this timer expires, or before the timer is reset (by calling
-- @UpdateJobExecution@, setting the status to @IN_PROGRESS@ and specifying
-- a new timeout value in field @stepTimeoutInMinutes@) the job execution
-- status will be automatically set to @TIMED_OUT@. Note that setting this
-- timeout has no effect on that job execution timeout which may have been
-- specified when the job was created (@CreateJob@ using field
-- @timeoutConfig@).
--
-- 'thingName', 'startNextPendingJobExecution_thingName' - The name of the thing associated with the device.
newStartNextPendingJobExecution ::
  -- | 'thingName'
  Prelude.Text ->
  StartNextPendingJobExecution
newStartNextPendingJobExecution :: Text -> StartNextPendingJobExecution
newStartNextPendingJobExecution Text
pThingName_ =
  StartNextPendingJobExecution'
    { $sel:statusDetails:StartNextPendingJobExecution' :: Maybe (HashMap Text Text)
statusDetails =
        forall a. Maybe a
Prelude.Nothing,
      $sel:stepTimeoutInMinutes:StartNextPendingJobExecution' :: Maybe Integer
stepTimeoutInMinutes = forall a. Maybe a
Prelude.Nothing,
      $sel:thingName:StartNextPendingJobExecution' :: Text
thingName = Text
pThingName_
    }

-- | A collection of name\/value pairs that describe the status of the job
-- execution. If not specified, the statusDetails are unchanged.
startNextPendingJobExecution_statusDetails :: Lens.Lens' StartNextPendingJobExecution (Prelude.Maybe (Prelude.HashMap Prelude.Text Prelude.Text))
startNextPendingJobExecution_statusDetails :: Lens' StartNextPendingJobExecution (Maybe (HashMap Text Text))
startNextPendingJobExecution_statusDetails = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\StartNextPendingJobExecution' {Maybe (HashMap Text Text)
statusDetails :: Maybe (HashMap Text Text)
$sel:statusDetails:StartNextPendingJobExecution' :: StartNextPendingJobExecution -> Maybe (HashMap Text Text)
statusDetails} -> Maybe (HashMap Text Text)
statusDetails) (\s :: StartNextPendingJobExecution
s@StartNextPendingJobExecution' {} Maybe (HashMap Text Text)
a -> StartNextPendingJobExecution
s {$sel:statusDetails:StartNextPendingJobExecution' :: Maybe (HashMap Text Text)
statusDetails = Maybe (HashMap Text Text)
a} :: StartNextPendingJobExecution) 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

-- | Specifies the amount of time this device has to finish execution of this
-- job. If the job execution status is not set to a terminal state before
-- this timer expires, or before the timer is reset (by calling
-- @UpdateJobExecution@, setting the status to @IN_PROGRESS@ and specifying
-- a new timeout value in field @stepTimeoutInMinutes@) the job execution
-- status will be automatically set to @TIMED_OUT@. Note that setting this
-- timeout has no effect on that job execution timeout which may have been
-- specified when the job was created (@CreateJob@ using field
-- @timeoutConfig@).
startNextPendingJobExecution_stepTimeoutInMinutes :: Lens.Lens' StartNextPendingJobExecution (Prelude.Maybe Prelude.Integer)
startNextPendingJobExecution_stepTimeoutInMinutes :: Lens' StartNextPendingJobExecution (Maybe Integer)
startNextPendingJobExecution_stepTimeoutInMinutes = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\StartNextPendingJobExecution' {Maybe Integer
stepTimeoutInMinutes :: Maybe Integer
$sel:stepTimeoutInMinutes:StartNextPendingJobExecution' :: StartNextPendingJobExecution -> Maybe Integer
stepTimeoutInMinutes} -> Maybe Integer
stepTimeoutInMinutes) (\s :: StartNextPendingJobExecution
s@StartNextPendingJobExecution' {} Maybe Integer
a -> StartNextPendingJobExecution
s {$sel:stepTimeoutInMinutes:StartNextPendingJobExecution' :: Maybe Integer
stepTimeoutInMinutes = Maybe Integer
a} :: StartNextPendingJobExecution)

-- | The name of the thing associated with the device.
startNextPendingJobExecution_thingName :: Lens.Lens' StartNextPendingJobExecution Prelude.Text
startNextPendingJobExecution_thingName :: Lens' StartNextPendingJobExecution Text
startNextPendingJobExecution_thingName = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\StartNextPendingJobExecution' {Text
thingName :: Text
$sel:thingName:StartNextPendingJobExecution' :: StartNextPendingJobExecution -> Text
thingName} -> Text
thingName) (\s :: StartNextPendingJobExecution
s@StartNextPendingJobExecution' {} Text
a -> StartNextPendingJobExecution
s {$sel:thingName:StartNextPendingJobExecution' :: Text
thingName = Text
a} :: StartNextPendingJobExecution)

instance Core.AWSRequest StartNextPendingJobExecution where
  type
    AWSResponse StartNextPendingJobExecution =
      StartNextPendingJobExecutionResponse
  request :: (Service -> Service)
-> StartNextPendingJobExecution
-> Request StartNextPendingJobExecution
request Service -> Service
overrides =
    forall a. (ToRequest a, ToJSON a) => Service -> a -> Request a
Request.putJSON (Service -> Service
overrides Service
defaultService)
  response :: forall (m :: * -> *).
MonadResource m =>
(ByteStringLazy -> IO ByteStringLazy)
-> Service
-> Proxy StartNextPendingJobExecution
-> ClientResponse ClientBody
-> m (Either
        Error (ClientResponse (AWSResponse StartNextPendingJobExecution)))
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 JobExecution -> Int -> StartNextPendingJobExecutionResponse
StartNextPendingJobExecutionResponse'
            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
"execution")
            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
    StartNextPendingJobExecution
  where
  hashWithSalt :: Int -> StartNextPendingJobExecution -> Int
hashWithSalt Int
_salt StartNextPendingJobExecution' {Maybe Integer
Maybe (HashMap Text Text)
Text
thingName :: Text
stepTimeoutInMinutes :: Maybe Integer
statusDetails :: Maybe (HashMap Text Text)
$sel:thingName:StartNextPendingJobExecution' :: StartNextPendingJobExecution -> Text
$sel:stepTimeoutInMinutes:StartNextPendingJobExecution' :: StartNextPendingJobExecution -> Maybe Integer
$sel:statusDetails:StartNextPendingJobExecution' :: StartNextPendingJobExecution -> Maybe (HashMap Text Text)
..} =
    Int
_salt
      forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Maybe (HashMap Text Text)
statusDetails
      forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Maybe Integer
stepTimeoutInMinutes
      forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Text
thingName

instance Prelude.NFData StartNextPendingJobExecution where
  rnf :: StartNextPendingJobExecution -> ()
rnf StartNextPendingJobExecution' {Maybe Integer
Maybe (HashMap Text Text)
Text
thingName :: Text
stepTimeoutInMinutes :: Maybe Integer
statusDetails :: Maybe (HashMap Text Text)
$sel:thingName:StartNextPendingJobExecution' :: StartNextPendingJobExecution -> Text
$sel:stepTimeoutInMinutes:StartNextPendingJobExecution' :: StartNextPendingJobExecution -> Maybe Integer
$sel:statusDetails:StartNextPendingJobExecution' :: StartNextPendingJobExecution -> Maybe (HashMap Text Text)
..} =
    forall a. NFData a => a -> ()
Prelude.rnf Maybe (HashMap Text Text)
statusDetails
      seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf Maybe Integer
stepTimeoutInMinutes
      seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf Text
thingName

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

instance Data.ToJSON StartNextPendingJobExecution where
  toJSON :: StartNextPendingJobExecution -> Value
toJSON StartNextPendingJobExecution' {Maybe Integer
Maybe (HashMap Text Text)
Text
thingName :: Text
stepTimeoutInMinutes :: Maybe Integer
statusDetails :: Maybe (HashMap Text Text)
$sel:thingName:StartNextPendingJobExecution' :: StartNextPendingJobExecution -> Text
$sel:stepTimeoutInMinutes:StartNextPendingJobExecution' :: StartNextPendingJobExecution -> Maybe Integer
$sel:statusDetails:StartNextPendingJobExecution' :: StartNextPendingJobExecution -> Maybe (HashMap Text Text)
..} =
    [Pair] -> Value
Data.object
      ( forall a. [Maybe a] -> [a]
Prelude.catMaybes
          [ (Key
"statusDetails" 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)
statusDetails,
            (Key
"stepTimeoutInMinutes" 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 Integer
stepTimeoutInMinutes
          ]
      )

instance Data.ToPath StartNextPendingJobExecution where
  toPath :: StartNextPendingJobExecution -> ByteString
toPath StartNextPendingJobExecution' {Maybe Integer
Maybe (HashMap Text Text)
Text
thingName :: Text
stepTimeoutInMinutes :: Maybe Integer
statusDetails :: Maybe (HashMap Text Text)
$sel:thingName:StartNextPendingJobExecution' :: StartNextPendingJobExecution -> Text
$sel:stepTimeoutInMinutes:StartNextPendingJobExecution' :: StartNextPendingJobExecution -> Maybe Integer
$sel:statusDetails:StartNextPendingJobExecution' :: StartNextPendingJobExecution -> Maybe (HashMap Text Text)
..} =
    forall a. Monoid a => [a] -> a
Prelude.mconcat
      [ByteString
"/things/", forall a. ToByteString a => a -> ByteString
Data.toBS Text
thingName, ByteString
"/jobs/$next"]

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

-- | /See:/ 'newStartNextPendingJobExecutionResponse' smart constructor.
data StartNextPendingJobExecutionResponse = StartNextPendingJobExecutionResponse'
  { -- | A JobExecution object.
    StartNextPendingJobExecutionResponse -> Maybe JobExecution
execution :: Prelude.Maybe JobExecution,
    -- | The response's http status code.
    StartNextPendingJobExecutionResponse -> Int
httpStatus :: Prelude.Int
  }
  deriving (StartNextPendingJobExecutionResponse
-> StartNextPendingJobExecutionResponse -> Bool
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: StartNextPendingJobExecutionResponse
-> StartNextPendingJobExecutionResponse -> Bool
$c/= :: StartNextPendingJobExecutionResponse
-> StartNextPendingJobExecutionResponse -> Bool
== :: StartNextPendingJobExecutionResponse
-> StartNextPendingJobExecutionResponse -> Bool
$c== :: StartNextPendingJobExecutionResponse
-> StartNextPendingJobExecutionResponse -> Bool
Prelude.Eq, ReadPrec [StartNextPendingJobExecutionResponse]
ReadPrec StartNextPendingJobExecutionResponse
Int -> ReadS StartNextPendingJobExecutionResponse
ReadS [StartNextPendingJobExecutionResponse]
forall a.
(Int -> ReadS a)
-> ReadS [a] -> ReadPrec a -> ReadPrec [a] -> Read a
readListPrec :: ReadPrec [StartNextPendingJobExecutionResponse]
$creadListPrec :: ReadPrec [StartNextPendingJobExecutionResponse]
readPrec :: ReadPrec StartNextPendingJobExecutionResponse
$creadPrec :: ReadPrec StartNextPendingJobExecutionResponse
readList :: ReadS [StartNextPendingJobExecutionResponse]
$creadList :: ReadS [StartNextPendingJobExecutionResponse]
readsPrec :: Int -> ReadS StartNextPendingJobExecutionResponse
$creadsPrec :: Int -> ReadS StartNextPendingJobExecutionResponse
Prelude.Read, Int -> StartNextPendingJobExecutionResponse -> ShowS
[StartNextPendingJobExecutionResponse] -> ShowS
StartNextPendingJobExecutionResponse -> String
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [StartNextPendingJobExecutionResponse] -> ShowS
$cshowList :: [StartNextPendingJobExecutionResponse] -> ShowS
show :: StartNextPendingJobExecutionResponse -> String
$cshow :: StartNextPendingJobExecutionResponse -> String
showsPrec :: Int -> StartNextPendingJobExecutionResponse -> ShowS
$cshowsPrec :: Int -> StartNextPendingJobExecutionResponse -> ShowS
Prelude.Show, forall x.
Rep StartNextPendingJobExecutionResponse x
-> StartNextPendingJobExecutionResponse
forall x.
StartNextPendingJobExecutionResponse
-> Rep StartNextPendingJobExecutionResponse x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cto :: forall x.
Rep StartNextPendingJobExecutionResponse x
-> StartNextPendingJobExecutionResponse
$cfrom :: forall x.
StartNextPendingJobExecutionResponse
-> Rep StartNextPendingJobExecutionResponse x
Prelude.Generic)

-- |
-- Create a value of 'StartNextPendingJobExecutionResponse' 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:
--
-- 'execution', 'startNextPendingJobExecutionResponse_execution' - A JobExecution object.
--
-- 'httpStatus', 'startNextPendingJobExecutionResponse_httpStatus' - The response's http status code.
newStartNextPendingJobExecutionResponse ::
  -- | 'httpStatus'
  Prelude.Int ->
  StartNextPendingJobExecutionResponse
newStartNextPendingJobExecutionResponse :: Int -> StartNextPendingJobExecutionResponse
newStartNextPendingJobExecutionResponse Int
pHttpStatus_ =
  StartNextPendingJobExecutionResponse'
    { $sel:execution:StartNextPendingJobExecutionResponse' :: Maybe JobExecution
execution =
        forall a. Maybe a
Prelude.Nothing,
      $sel:httpStatus:StartNextPendingJobExecutionResponse' :: Int
httpStatus = Int
pHttpStatus_
    }

-- | A JobExecution object.
startNextPendingJobExecutionResponse_execution :: Lens.Lens' StartNextPendingJobExecutionResponse (Prelude.Maybe JobExecution)
startNextPendingJobExecutionResponse_execution :: Lens' StartNextPendingJobExecutionResponse (Maybe JobExecution)
startNextPendingJobExecutionResponse_execution = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\StartNextPendingJobExecutionResponse' {Maybe JobExecution
execution :: Maybe JobExecution
$sel:execution:StartNextPendingJobExecutionResponse' :: StartNextPendingJobExecutionResponse -> Maybe JobExecution
execution} -> Maybe JobExecution
execution) (\s :: StartNextPendingJobExecutionResponse
s@StartNextPendingJobExecutionResponse' {} Maybe JobExecution
a -> StartNextPendingJobExecutionResponse
s {$sel:execution:StartNextPendingJobExecutionResponse' :: Maybe JobExecution
execution = Maybe JobExecution
a} :: StartNextPendingJobExecutionResponse)

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

instance
  Prelude.NFData
    StartNextPendingJobExecutionResponse
  where
  rnf :: StartNextPendingJobExecutionResponse -> ()
rnf StartNextPendingJobExecutionResponse' {Int
Maybe JobExecution
httpStatus :: Int
execution :: Maybe JobExecution
$sel:httpStatus:StartNextPendingJobExecutionResponse' :: StartNextPendingJobExecutionResponse -> Int
$sel:execution:StartNextPendingJobExecutionResponse' :: StartNextPendingJobExecutionResponse -> Maybe JobExecution
..} =
    forall a. NFData a => a -> ()
Prelude.rnf Maybe JobExecution
execution
      seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf Int
httpStatus