{-# 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.IoT.CancelJobExecution
-- Copyright   : (c) 2013-2023 Brendan Hay
-- License     : Mozilla Public License, v. 2.0.
-- Maintainer  : Brendan Hay
-- Stability   : auto-generated
-- Portability : non-portable (GHC extensions)
--
-- Cancels the execution of a job for a given thing.
--
-- Requires permission to access the
-- <https://docs.aws.amazon.com/service-authorization/latest/reference/list_awsiot.html#awsiot-actions-as-permissions CancelJobExecution>
-- action.
module Amazonka.IoT.CancelJobExecution
  ( -- * Creating a Request
    CancelJobExecution (..),
    newCancelJobExecution,

    -- * Request Lenses
    cancelJobExecution_expectedVersion,
    cancelJobExecution_force,
    cancelJobExecution_statusDetails,
    cancelJobExecution_jobId,
    cancelJobExecution_thingName,

    -- * Destructuring the Response
    CancelJobExecutionResponse (..),
    newCancelJobExecutionResponse,
  )
where

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

-- | /See:/ 'newCancelJobExecution' smart constructor.
data CancelJobExecution = CancelJobExecution'
  { -- | (Optional) The expected current version of the job execution. Each time
    -- you update the job execution, its version is incremented. If the version
    -- of the job execution stored in Jobs does not match, the update is
    -- rejected with a VersionMismatch error, and an ErrorResponse that
    -- contains the current job execution status data is returned. (This makes
    -- it unnecessary to perform a separate DescribeJobExecution request in
    -- order to obtain the job execution status data.)
    CancelJobExecution -> Maybe Integer
expectedVersion :: Prelude.Maybe Prelude.Integer,
    -- | (Optional) If @true@ the job execution will be canceled if it has status
    -- IN_PROGRESS or QUEUED, otherwise the job execution will be canceled only
    -- if it has status QUEUED. If you attempt to cancel a job execution that
    -- is IN_PROGRESS, and you do not set @force@ to @true@, then an
    -- @InvalidStateTransitionException@ will be thrown. The default is
    -- @false@.
    --
    -- Canceling a job execution which is \"IN_PROGRESS\", will cause the
    -- device to be unable to update the job execution status. Use caution and
    -- ensure that the device is able to recover to a valid state.
    CancelJobExecution -> Maybe Bool
force :: Prelude.Maybe Prelude.Bool,
    -- | A collection of name\/value pairs that describe the status of the job
    -- execution. If not specified, the statusDetails are unchanged. You can
    -- specify at most 10 name\/value pairs.
    CancelJobExecution -> Maybe (HashMap Text Text)
statusDetails :: Prelude.Maybe (Prelude.HashMap Prelude.Text Prelude.Text),
    -- | The ID of the job to be canceled.
    CancelJobExecution -> Text
jobId :: Prelude.Text,
    -- | The name of the thing whose execution of the job will be canceled.
    CancelJobExecution -> Text
thingName :: Prelude.Text
  }
  deriving (CancelJobExecution -> CancelJobExecution -> Bool
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: CancelJobExecution -> CancelJobExecution -> Bool
$c/= :: CancelJobExecution -> CancelJobExecution -> Bool
== :: CancelJobExecution -> CancelJobExecution -> Bool
$c== :: CancelJobExecution -> CancelJobExecution -> Bool
Prelude.Eq, ReadPrec [CancelJobExecution]
ReadPrec CancelJobExecution
Int -> ReadS CancelJobExecution
ReadS [CancelJobExecution]
forall a.
(Int -> ReadS a)
-> ReadS [a] -> ReadPrec a -> ReadPrec [a] -> Read a
readListPrec :: ReadPrec [CancelJobExecution]
$creadListPrec :: ReadPrec [CancelJobExecution]
readPrec :: ReadPrec CancelJobExecution
$creadPrec :: ReadPrec CancelJobExecution
readList :: ReadS [CancelJobExecution]
$creadList :: ReadS [CancelJobExecution]
readsPrec :: Int -> ReadS CancelJobExecution
$creadsPrec :: Int -> ReadS CancelJobExecution
Prelude.Read, Int -> CancelJobExecution -> ShowS
[CancelJobExecution] -> ShowS
CancelJobExecution -> String
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [CancelJobExecution] -> ShowS
$cshowList :: [CancelJobExecution] -> ShowS
show :: CancelJobExecution -> String
$cshow :: CancelJobExecution -> String
showsPrec :: Int -> CancelJobExecution -> ShowS
$cshowsPrec :: Int -> CancelJobExecution -> ShowS
Prelude.Show, forall x. Rep CancelJobExecution x -> CancelJobExecution
forall x. CancelJobExecution -> Rep CancelJobExecution x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cto :: forall x. Rep CancelJobExecution x -> CancelJobExecution
$cfrom :: forall x. CancelJobExecution -> Rep CancelJobExecution x
Prelude.Generic)

-- |
-- Create a value of 'CancelJobExecution' 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:
--
-- 'expectedVersion', 'cancelJobExecution_expectedVersion' - (Optional) The expected current version of the job execution. Each time
-- you update the job execution, its version is incremented. If the version
-- of the job execution stored in Jobs does not match, the update is
-- rejected with a VersionMismatch error, and an ErrorResponse that
-- contains the current job execution status data is returned. (This makes
-- it unnecessary to perform a separate DescribeJobExecution request in
-- order to obtain the job execution status data.)
--
-- 'force', 'cancelJobExecution_force' - (Optional) If @true@ the job execution will be canceled if it has status
-- IN_PROGRESS or QUEUED, otherwise the job execution will be canceled only
-- if it has status QUEUED. If you attempt to cancel a job execution that
-- is IN_PROGRESS, and you do not set @force@ to @true@, then an
-- @InvalidStateTransitionException@ will be thrown. The default is
-- @false@.
--
-- Canceling a job execution which is \"IN_PROGRESS\", will cause the
-- device to be unable to update the job execution status. Use caution and
-- ensure that the device is able to recover to a valid state.
--
-- 'statusDetails', 'cancelJobExecution_statusDetails' - A collection of name\/value pairs that describe the status of the job
-- execution. If not specified, the statusDetails are unchanged. You can
-- specify at most 10 name\/value pairs.
--
-- 'jobId', 'cancelJobExecution_jobId' - The ID of the job to be canceled.
--
-- 'thingName', 'cancelJobExecution_thingName' - The name of the thing whose execution of the job will be canceled.
newCancelJobExecution ::
  -- | 'jobId'
  Prelude.Text ->
  -- | 'thingName'
  Prelude.Text ->
  CancelJobExecution
newCancelJobExecution :: Text -> Text -> CancelJobExecution
newCancelJobExecution Text
pJobId_ Text
pThingName_ =
  CancelJobExecution'
    { $sel:expectedVersion:CancelJobExecution' :: Maybe Integer
expectedVersion =
        forall a. Maybe a
Prelude.Nothing,
      $sel:force:CancelJobExecution' :: Maybe Bool
force = forall a. Maybe a
Prelude.Nothing,
      $sel:statusDetails:CancelJobExecution' :: Maybe (HashMap Text Text)
statusDetails = forall a. Maybe a
Prelude.Nothing,
      $sel:jobId:CancelJobExecution' :: Text
jobId = Text
pJobId_,
      $sel:thingName:CancelJobExecution' :: Text
thingName = Text
pThingName_
    }

-- | (Optional) The expected current version of the job execution. Each time
-- you update the job execution, its version is incremented. If the version
-- of the job execution stored in Jobs does not match, the update is
-- rejected with a VersionMismatch error, and an ErrorResponse that
-- contains the current job execution status data is returned. (This makes
-- it unnecessary to perform a separate DescribeJobExecution request in
-- order to obtain the job execution status data.)
cancelJobExecution_expectedVersion :: Lens.Lens' CancelJobExecution (Prelude.Maybe Prelude.Integer)
cancelJobExecution_expectedVersion :: Lens' CancelJobExecution (Maybe Integer)
cancelJobExecution_expectedVersion = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\CancelJobExecution' {Maybe Integer
expectedVersion :: Maybe Integer
$sel:expectedVersion:CancelJobExecution' :: CancelJobExecution -> Maybe Integer
expectedVersion} -> Maybe Integer
expectedVersion) (\s :: CancelJobExecution
s@CancelJobExecution' {} Maybe Integer
a -> CancelJobExecution
s {$sel:expectedVersion:CancelJobExecution' :: Maybe Integer
expectedVersion = Maybe Integer
a} :: CancelJobExecution)

-- | (Optional) If @true@ the job execution will be canceled if it has status
-- IN_PROGRESS or QUEUED, otherwise the job execution will be canceled only
-- if it has status QUEUED. If you attempt to cancel a job execution that
-- is IN_PROGRESS, and you do not set @force@ to @true@, then an
-- @InvalidStateTransitionException@ will be thrown. The default is
-- @false@.
--
-- Canceling a job execution which is \"IN_PROGRESS\", will cause the
-- device to be unable to update the job execution status. Use caution and
-- ensure that the device is able to recover to a valid state.
cancelJobExecution_force :: Lens.Lens' CancelJobExecution (Prelude.Maybe Prelude.Bool)
cancelJobExecution_force :: Lens' CancelJobExecution (Maybe Bool)
cancelJobExecution_force = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\CancelJobExecution' {Maybe Bool
force :: Maybe Bool
$sel:force:CancelJobExecution' :: CancelJobExecution -> Maybe Bool
force} -> Maybe Bool
force) (\s :: CancelJobExecution
s@CancelJobExecution' {} Maybe Bool
a -> CancelJobExecution
s {$sel:force:CancelJobExecution' :: Maybe Bool
force = Maybe Bool
a} :: CancelJobExecution)

-- | A collection of name\/value pairs that describe the status of the job
-- execution. If not specified, the statusDetails are unchanged. You can
-- specify at most 10 name\/value pairs.
cancelJobExecution_statusDetails :: Lens.Lens' CancelJobExecution (Prelude.Maybe (Prelude.HashMap Prelude.Text Prelude.Text))
cancelJobExecution_statusDetails :: Lens' CancelJobExecution (Maybe (HashMap Text Text))
cancelJobExecution_statusDetails = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\CancelJobExecution' {Maybe (HashMap Text Text)
statusDetails :: Maybe (HashMap Text Text)
$sel:statusDetails:CancelJobExecution' :: CancelJobExecution -> Maybe (HashMap Text Text)
statusDetails} -> Maybe (HashMap Text Text)
statusDetails) (\s :: CancelJobExecution
s@CancelJobExecution' {} Maybe (HashMap Text Text)
a -> CancelJobExecution
s {$sel:statusDetails:CancelJobExecution' :: Maybe (HashMap Text Text)
statusDetails = Maybe (HashMap Text Text)
a} :: CancelJobExecution) 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 ID of the job to be canceled.
cancelJobExecution_jobId :: Lens.Lens' CancelJobExecution Prelude.Text
cancelJobExecution_jobId :: Lens' CancelJobExecution Text
cancelJobExecution_jobId = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\CancelJobExecution' {Text
jobId :: Text
$sel:jobId:CancelJobExecution' :: CancelJobExecution -> Text
jobId} -> Text
jobId) (\s :: CancelJobExecution
s@CancelJobExecution' {} Text
a -> CancelJobExecution
s {$sel:jobId:CancelJobExecution' :: Text
jobId = Text
a} :: CancelJobExecution)

-- | The name of the thing whose execution of the job will be canceled.
cancelJobExecution_thingName :: Lens.Lens' CancelJobExecution Prelude.Text
cancelJobExecution_thingName :: Lens' CancelJobExecution Text
cancelJobExecution_thingName = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\CancelJobExecution' {Text
thingName :: Text
$sel:thingName:CancelJobExecution' :: CancelJobExecution -> Text
thingName} -> Text
thingName) (\s :: CancelJobExecution
s@CancelJobExecution' {} Text
a -> CancelJobExecution
s {$sel:thingName:CancelJobExecution' :: Text
thingName = Text
a} :: CancelJobExecution)

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

instance Prelude.Hashable CancelJobExecution where
  hashWithSalt :: Int -> CancelJobExecution -> Int
hashWithSalt Int
_salt CancelJobExecution' {Maybe Bool
Maybe Integer
Maybe (HashMap Text Text)
Text
thingName :: Text
jobId :: Text
statusDetails :: Maybe (HashMap Text Text)
force :: Maybe Bool
expectedVersion :: Maybe Integer
$sel:thingName:CancelJobExecution' :: CancelJobExecution -> Text
$sel:jobId:CancelJobExecution' :: CancelJobExecution -> Text
$sel:statusDetails:CancelJobExecution' :: CancelJobExecution -> Maybe (HashMap Text Text)
$sel:force:CancelJobExecution' :: CancelJobExecution -> Maybe Bool
$sel:expectedVersion:CancelJobExecution' :: CancelJobExecution -> Maybe Integer
..} =
    Int
_salt
      forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Maybe Integer
expectedVersion
      forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Maybe Bool
force
      forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Maybe (HashMap Text Text)
statusDetails
      forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Text
jobId
      forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Text
thingName

instance Prelude.NFData CancelJobExecution where
  rnf :: CancelJobExecution -> ()
rnf CancelJobExecution' {Maybe Bool
Maybe Integer
Maybe (HashMap Text Text)
Text
thingName :: Text
jobId :: Text
statusDetails :: Maybe (HashMap Text Text)
force :: Maybe Bool
expectedVersion :: Maybe Integer
$sel:thingName:CancelJobExecution' :: CancelJobExecution -> Text
$sel:jobId:CancelJobExecution' :: CancelJobExecution -> Text
$sel:statusDetails:CancelJobExecution' :: CancelJobExecution -> Maybe (HashMap Text Text)
$sel:force:CancelJobExecution' :: CancelJobExecution -> Maybe Bool
$sel:expectedVersion:CancelJobExecution' :: CancelJobExecution -> Maybe Integer
..} =
    forall a. NFData a => a -> ()
Prelude.rnf Maybe Integer
expectedVersion
      seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf Maybe Bool
force
      seq :: forall a b. a -> b -> b
`Prelude.seq` 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 Text
jobId
      seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf Text
thingName

instance Data.ToHeaders CancelJobExecution where
  toHeaders :: CancelJobExecution -> [Header]
toHeaders = forall a b. a -> b -> a
Prelude.const forall a. Monoid a => a
Prelude.mempty

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

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

instance Data.ToQuery CancelJobExecution where
  toQuery :: CancelJobExecution -> QueryString
toQuery CancelJobExecution' {Maybe Bool
Maybe Integer
Maybe (HashMap Text Text)
Text
thingName :: Text
jobId :: Text
statusDetails :: Maybe (HashMap Text Text)
force :: Maybe Bool
expectedVersion :: Maybe Integer
$sel:thingName:CancelJobExecution' :: CancelJobExecution -> Text
$sel:jobId:CancelJobExecution' :: CancelJobExecution -> Text
$sel:statusDetails:CancelJobExecution' :: CancelJobExecution -> Maybe (HashMap Text Text)
$sel:force:CancelJobExecution' :: CancelJobExecution -> Maybe Bool
$sel:expectedVersion:CancelJobExecution' :: CancelJobExecution -> Maybe Integer
..} =
    forall a. Monoid a => [a] -> a
Prelude.mconcat [ByteString
"force" forall a. ToQuery a => ByteString -> a -> QueryString
Data.=: Maybe Bool
force]

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

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

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