{-# 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.EMRServerless.CancelJobRun
-- 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 a job run.
module Amazonka.EMRServerless.CancelJobRun
  ( -- * Creating a Request
    CancelJobRun (..),
    newCancelJobRun,

    -- * Request Lenses
    cancelJobRun_applicationId,
    cancelJobRun_jobRunId,

    -- * Destructuring the Response
    CancelJobRunResponse (..),
    newCancelJobRunResponse,

    -- * Response Lenses
    cancelJobRunResponse_httpStatus,
    cancelJobRunResponse_applicationId,
    cancelJobRunResponse_jobRunId,
  )
where

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

-- | /See:/ 'newCancelJobRun' smart constructor.
data CancelJobRun = CancelJobRun'
  { -- | The ID of the application on which the job run will be canceled.
    CancelJobRun -> Text
applicationId :: Prelude.Text,
    -- | The ID of the job run to cancel.
    CancelJobRun -> Text
jobRunId :: Prelude.Text
  }
  deriving (CancelJobRun -> CancelJobRun -> Bool
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: CancelJobRun -> CancelJobRun -> Bool
$c/= :: CancelJobRun -> CancelJobRun -> Bool
== :: CancelJobRun -> CancelJobRun -> Bool
$c== :: CancelJobRun -> CancelJobRun -> Bool
Prelude.Eq, ReadPrec [CancelJobRun]
ReadPrec CancelJobRun
Int -> ReadS CancelJobRun
ReadS [CancelJobRun]
forall a.
(Int -> ReadS a)
-> ReadS [a] -> ReadPrec a -> ReadPrec [a] -> Read a
readListPrec :: ReadPrec [CancelJobRun]
$creadListPrec :: ReadPrec [CancelJobRun]
readPrec :: ReadPrec CancelJobRun
$creadPrec :: ReadPrec CancelJobRun
readList :: ReadS [CancelJobRun]
$creadList :: ReadS [CancelJobRun]
readsPrec :: Int -> ReadS CancelJobRun
$creadsPrec :: Int -> ReadS CancelJobRun
Prelude.Read, Int -> CancelJobRun -> ShowS
[CancelJobRun] -> ShowS
CancelJobRun -> String
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [CancelJobRun] -> ShowS
$cshowList :: [CancelJobRun] -> ShowS
show :: CancelJobRun -> String
$cshow :: CancelJobRun -> String
showsPrec :: Int -> CancelJobRun -> ShowS
$cshowsPrec :: Int -> CancelJobRun -> ShowS
Prelude.Show, forall x. Rep CancelJobRun x -> CancelJobRun
forall x. CancelJobRun -> Rep CancelJobRun x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cto :: forall x. Rep CancelJobRun x -> CancelJobRun
$cfrom :: forall x. CancelJobRun -> Rep CancelJobRun x
Prelude.Generic)

-- |
-- Create a value of 'CancelJobRun' 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:
--
-- 'applicationId', 'cancelJobRun_applicationId' - The ID of the application on which the job run will be canceled.
--
-- 'jobRunId', 'cancelJobRun_jobRunId' - The ID of the job run to cancel.
newCancelJobRun ::
  -- | 'applicationId'
  Prelude.Text ->
  -- | 'jobRunId'
  Prelude.Text ->
  CancelJobRun
newCancelJobRun :: Text -> Text -> CancelJobRun
newCancelJobRun Text
pApplicationId_ Text
pJobRunId_ =
  CancelJobRun'
    { $sel:applicationId:CancelJobRun' :: Text
applicationId = Text
pApplicationId_,
      $sel:jobRunId:CancelJobRun' :: Text
jobRunId = Text
pJobRunId_
    }

-- | The ID of the application on which the job run will be canceled.
cancelJobRun_applicationId :: Lens.Lens' CancelJobRun Prelude.Text
cancelJobRun_applicationId :: Lens' CancelJobRun Text
cancelJobRun_applicationId = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\CancelJobRun' {Text
applicationId :: Text
$sel:applicationId:CancelJobRun' :: CancelJobRun -> Text
applicationId} -> Text
applicationId) (\s :: CancelJobRun
s@CancelJobRun' {} Text
a -> CancelJobRun
s {$sel:applicationId:CancelJobRun' :: Text
applicationId = Text
a} :: CancelJobRun)

-- | The ID of the job run to cancel.
cancelJobRun_jobRunId :: Lens.Lens' CancelJobRun Prelude.Text
cancelJobRun_jobRunId :: Lens' CancelJobRun Text
cancelJobRun_jobRunId = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\CancelJobRun' {Text
jobRunId :: Text
$sel:jobRunId:CancelJobRun' :: CancelJobRun -> Text
jobRunId} -> Text
jobRunId) (\s :: CancelJobRun
s@CancelJobRun' {} Text
a -> CancelJobRun
s {$sel:jobRunId:CancelJobRun' :: Text
jobRunId = Text
a} :: CancelJobRun)

instance Core.AWSRequest CancelJobRun where
  type AWSResponse CancelJobRun = CancelJobRunResponse
  request :: (Service -> Service) -> CancelJobRun -> Request CancelJobRun
request Service -> Service
overrides =
    forall a. ToRequest a => Service -> a -> Request a
Request.delete (Service -> Service
overrides Service
defaultService)
  response :: forall (m :: * -> *).
MonadResource m =>
(ByteStringLazy -> IO ByteStringLazy)
-> Service
-> Proxy CancelJobRun
-> ClientResponse ClientBody
-> m (Either Error (ClientResponse (AWSResponse CancelJobRun)))
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 ->
          Int -> Text -> Text -> CancelJobRunResponse
CancelJobRunResponse'
            forall (f :: * -> *) a b. Functor 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))
            forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
Prelude.<*> (Object
x forall a. FromJSON a => Object -> Key -> Either String a
Data..:> Key
"applicationId")
            forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
Prelude.<*> (Object
x forall a. FromJSON a => Object -> Key -> Either String a
Data..:> Key
"jobRunId")
      )

instance Prelude.Hashable CancelJobRun where
  hashWithSalt :: Int -> CancelJobRun -> Int
hashWithSalt Int
_salt CancelJobRun' {Text
jobRunId :: Text
applicationId :: Text
$sel:jobRunId:CancelJobRun' :: CancelJobRun -> Text
$sel:applicationId:CancelJobRun' :: CancelJobRun -> Text
..} =
    Int
_salt
      forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Text
applicationId
      forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Text
jobRunId

instance Prelude.NFData CancelJobRun where
  rnf :: CancelJobRun -> ()
rnf CancelJobRun' {Text
jobRunId :: Text
applicationId :: Text
$sel:jobRunId:CancelJobRun' :: CancelJobRun -> Text
$sel:applicationId:CancelJobRun' :: CancelJobRun -> Text
..} =
    forall a. NFData a => a -> ()
Prelude.rnf Text
applicationId
      seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf Text
jobRunId

instance Data.ToHeaders CancelJobRun where
  toHeaders :: CancelJobRun -> ResponseHeaders
toHeaders =
    forall a b. a -> b -> a
Prelude.const
      ( forall a. Monoid a => [a] -> a
Prelude.mconcat
          [ HeaderName
"Content-Type"
              forall a. ToHeader a => HeaderName -> a -> ResponseHeaders
Data.=# ( ByteString
"application/x-amz-json-1.1" ::
                          Prelude.ByteString
                      )
          ]
      )

instance Data.ToPath CancelJobRun where
  toPath :: CancelJobRun -> ByteString
toPath CancelJobRun' {Text
jobRunId :: Text
applicationId :: Text
$sel:jobRunId:CancelJobRun' :: CancelJobRun -> Text
$sel:applicationId:CancelJobRun' :: CancelJobRun -> Text
..} =
    forall a. Monoid a => [a] -> a
Prelude.mconcat
      [ ByteString
"/applications/",
        forall a. ToByteString a => a -> ByteString
Data.toBS Text
applicationId,
        ByteString
"/jobruns/",
        forall a. ToByteString a => a -> ByteString
Data.toBS Text
jobRunId
      ]

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

-- | /See:/ 'newCancelJobRunResponse' smart constructor.
data CancelJobRunResponse = CancelJobRunResponse'
  { -- | The response's http status code.
    CancelJobRunResponse -> Int
httpStatus :: Prelude.Int,
    -- | The output contains the application ID on which the job run is
    -- cancelled.
    CancelJobRunResponse -> Text
applicationId :: Prelude.Text,
    -- | The output contains the ID of the cancelled job run.
    CancelJobRunResponse -> Text
jobRunId :: Prelude.Text
  }
  deriving (CancelJobRunResponse -> CancelJobRunResponse -> Bool
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: CancelJobRunResponse -> CancelJobRunResponse -> Bool
$c/= :: CancelJobRunResponse -> CancelJobRunResponse -> Bool
== :: CancelJobRunResponse -> CancelJobRunResponse -> Bool
$c== :: CancelJobRunResponse -> CancelJobRunResponse -> Bool
Prelude.Eq, ReadPrec [CancelJobRunResponse]
ReadPrec CancelJobRunResponse
Int -> ReadS CancelJobRunResponse
ReadS [CancelJobRunResponse]
forall a.
(Int -> ReadS a)
-> ReadS [a] -> ReadPrec a -> ReadPrec [a] -> Read a
readListPrec :: ReadPrec [CancelJobRunResponse]
$creadListPrec :: ReadPrec [CancelJobRunResponse]
readPrec :: ReadPrec CancelJobRunResponse
$creadPrec :: ReadPrec CancelJobRunResponse
readList :: ReadS [CancelJobRunResponse]
$creadList :: ReadS [CancelJobRunResponse]
readsPrec :: Int -> ReadS CancelJobRunResponse
$creadsPrec :: Int -> ReadS CancelJobRunResponse
Prelude.Read, Int -> CancelJobRunResponse -> ShowS
[CancelJobRunResponse] -> ShowS
CancelJobRunResponse -> String
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [CancelJobRunResponse] -> ShowS
$cshowList :: [CancelJobRunResponse] -> ShowS
show :: CancelJobRunResponse -> String
$cshow :: CancelJobRunResponse -> String
showsPrec :: Int -> CancelJobRunResponse -> ShowS
$cshowsPrec :: Int -> CancelJobRunResponse -> ShowS
Prelude.Show, forall x. Rep CancelJobRunResponse x -> CancelJobRunResponse
forall x. CancelJobRunResponse -> Rep CancelJobRunResponse x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cto :: forall x. Rep CancelJobRunResponse x -> CancelJobRunResponse
$cfrom :: forall x. CancelJobRunResponse -> Rep CancelJobRunResponse x
Prelude.Generic)

-- |
-- Create a value of 'CancelJobRunResponse' 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:
--
-- 'httpStatus', 'cancelJobRunResponse_httpStatus' - The response's http status code.
--
-- 'applicationId', 'cancelJobRunResponse_applicationId' - The output contains the application ID on which the job run is
-- cancelled.
--
-- 'jobRunId', 'cancelJobRunResponse_jobRunId' - The output contains the ID of the cancelled job run.
newCancelJobRunResponse ::
  -- | 'httpStatus'
  Prelude.Int ->
  -- | 'applicationId'
  Prelude.Text ->
  -- | 'jobRunId'
  Prelude.Text ->
  CancelJobRunResponse
newCancelJobRunResponse :: Int -> Text -> Text -> CancelJobRunResponse
newCancelJobRunResponse
  Int
pHttpStatus_
  Text
pApplicationId_
  Text
pJobRunId_ =
    CancelJobRunResponse'
      { $sel:httpStatus:CancelJobRunResponse' :: Int
httpStatus = Int
pHttpStatus_,
        $sel:applicationId:CancelJobRunResponse' :: Text
applicationId = Text
pApplicationId_,
        $sel:jobRunId:CancelJobRunResponse' :: Text
jobRunId = Text
pJobRunId_
      }

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

-- | The output contains the application ID on which the job run is
-- cancelled.
cancelJobRunResponse_applicationId :: Lens.Lens' CancelJobRunResponse Prelude.Text
cancelJobRunResponse_applicationId :: Lens' CancelJobRunResponse Text
cancelJobRunResponse_applicationId = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\CancelJobRunResponse' {Text
applicationId :: Text
$sel:applicationId:CancelJobRunResponse' :: CancelJobRunResponse -> Text
applicationId} -> Text
applicationId) (\s :: CancelJobRunResponse
s@CancelJobRunResponse' {} Text
a -> CancelJobRunResponse
s {$sel:applicationId:CancelJobRunResponse' :: Text
applicationId = Text
a} :: CancelJobRunResponse)

-- | The output contains the ID of the cancelled job run.
cancelJobRunResponse_jobRunId :: Lens.Lens' CancelJobRunResponse Prelude.Text
cancelJobRunResponse_jobRunId :: Lens' CancelJobRunResponse Text
cancelJobRunResponse_jobRunId = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\CancelJobRunResponse' {Text
jobRunId :: Text
$sel:jobRunId:CancelJobRunResponse' :: CancelJobRunResponse -> Text
jobRunId} -> Text
jobRunId) (\s :: CancelJobRunResponse
s@CancelJobRunResponse' {} Text
a -> CancelJobRunResponse
s {$sel:jobRunId:CancelJobRunResponse' :: Text
jobRunId = Text
a} :: CancelJobRunResponse)

instance Prelude.NFData CancelJobRunResponse where
  rnf :: CancelJobRunResponse -> ()
rnf CancelJobRunResponse' {Int
Text
jobRunId :: Text
applicationId :: Text
httpStatus :: Int
$sel:jobRunId:CancelJobRunResponse' :: CancelJobRunResponse -> Text
$sel:applicationId:CancelJobRunResponse' :: CancelJobRunResponse -> Text
$sel:httpStatus:CancelJobRunResponse' :: CancelJobRunResponse -> Int
..} =
    forall a. NFData a => a -> ()
Prelude.rnf Int
httpStatus
      seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf Text
applicationId
      seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf Text
jobRunId