{-# 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.EMRContainers.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. A job run is a unit of work, such as a Spark jar,
-- PySpark script, or SparkSQL query, that you submit to Amazon EMR on EKS.
module Amazonka.EMRContainers.CancelJobRun
  ( -- * Creating a Request
    CancelJobRun (..),
    newCancelJobRun,

    -- * Request Lenses
    cancelJobRun_id,
    cancelJobRun_virtualClusterId,

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

    -- * Response Lenses
    cancelJobRunResponse_id,
    cancelJobRunResponse_virtualClusterId,
    cancelJobRunResponse_httpStatus,
  )
where

import qualified Amazonka.Core as Core
import qualified Amazonka.Core.Lens.Internal as Lens
import qualified Amazonka.Data as Data
import Amazonka.EMRContainers.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 job run to cancel.
    CancelJobRun -> Text
id :: Prelude.Text,
    -- | The ID of the virtual cluster for which the job run will be canceled.
    CancelJobRun -> Text
virtualClusterId :: 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:
--
-- 'id', 'cancelJobRun_id' - The ID of the job run to cancel.
--
-- 'virtualClusterId', 'cancelJobRun_virtualClusterId' - The ID of the virtual cluster for which the job run will be canceled.
newCancelJobRun ::
  -- | 'id'
  Prelude.Text ->
  -- | 'virtualClusterId'
  Prelude.Text ->
  CancelJobRun
newCancelJobRun :: Text -> Text -> CancelJobRun
newCancelJobRun Text
pId_ Text
pVirtualClusterId_ =
  CancelJobRun'
    { $sel:id:CancelJobRun' :: Text
id = Text
pId_,
      $sel:virtualClusterId:CancelJobRun' :: Text
virtualClusterId = Text
pVirtualClusterId_
    }

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

-- | The ID of the virtual cluster for which the job run will be canceled.
cancelJobRun_virtualClusterId :: Lens.Lens' CancelJobRun Prelude.Text
cancelJobRun_virtualClusterId :: Lens' CancelJobRun Text
cancelJobRun_virtualClusterId = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\CancelJobRun' {Text
virtualClusterId :: Text
$sel:virtualClusterId:CancelJobRun' :: CancelJobRun -> Text
virtualClusterId} -> Text
virtualClusterId) (\s :: CancelJobRun
s@CancelJobRun' {} Text
a -> CancelJobRun
s {$sel:virtualClusterId:CancelJobRun' :: Text
virtualClusterId = 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 ->
          Maybe Text -> Maybe Text -> Int -> CancelJobRunResponse
CancelJobRunResponse'
            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
"id")
            forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
Prelude.<*> (Object
x forall a. FromJSON a => Object -> Key -> Either String (Maybe a)
Data..?> Key
"virtualClusterId")
            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 CancelJobRun where
  hashWithSalt :: Int -> CancelJobRun -> Int
hashWithSalt Int
_salt CancelJobRun' {Text
virtualClusterId :: Text
id :: Text
$sel:virtualClusterId:CancelJobRun' :: CancelJobRun -> Text
$sel:id:CancelJobRun' :: CancelJobRun -> Text
..} =
    Int
_salt
      forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Text
id
      forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Text
virtualClusterId

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

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
virtualClusterId :: Text
id :: Text
$sel:virtualClusterId:CancelJobRun' :: CancelJobRun -> Text
$sel:id:CancelJobRun' :: CancelJobRun -> Text
..} =
    forall a. Monoid a => [a] -> a
Prelude.mconcat
      [ ByteString
"/virtualclusters/",
        forall a. ToByteString a => a -> ByteString
Data.toBS Text
virtualClusterId,
        ByteString
"/jobruns/",
        forall a. ToByteString a => a -> ByteString
Data.toBS Text
id
      ]

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 output contains the ID of the cancelled job run.
    CancelJobRunResponse -> Maybe Text
id :: Prelude.Maybe Prelude.Text,
    -- | The output contains the virtual cluster ID for which the job run is
    -- cancelled.
    CancelJobRunResponse -> Maybe Text
virtualClusterId :: Prelude.Maybe Prelude.Text,
    -- | The response's http status code.
    CancelJobRunResponse -> Int
httpStatus :: Prelude.Int
  }
  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:
--
-- 'id', 'cancelJobRunResponse_id' - The output contains the ID of the cancelled job run.
--
-- 'virtualClusterId', 'cancelJobRunResponse_virtualClusterId' - The output contains the virtual cluster ID for which the job run is
-- cancelled.
--
-- 'httpStatus', 'cancelJobRunResponse_httpStatus' - The response's http status code.
newCancelJobRunResponse ::
  -- | 'httpStatus'
  Prelude.Int ->
  CancelJobRunResponse
newCancelJobRunResponse :: Int -> CancelJobRunResponse
newCancelJobRunResponse Int
pHttpStatus_ =
  CancelJobRunResponse'
    { $sel:id:CancelJobRunResponse' :: Maybe Text
id = forall a. Maybe a
Prelude.Nothing,
      $sel:virtualClusterId:CancelJobRunResponse' :: Maybe Text
virtualClusterId = forall a. Maybe a
Prelude.Nothing,
      $sel:httpStatus:CancelJobRunResponse' :: Int
httpStatus = Int
pHttpStatus_
    }

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

-- | The output contains the virtual cluster ID for which the job run is
-- cancelled.
cancelJobRunResponse_virtualClusterId :: Lens.Lens' CancelJobRunResponse (Prelude.Maybe Prelude.Text)
cancelJobRunResponse_virtualClusterId :: Lens' CancelJobRunResponse (Maybe Text)
cancelJobRunResponse_virtualClusterId = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\CancelJobRunResponse' {Maybe Text
virtualClusterId :: Maybe Text
$sel:virtualClusterId:CancelJobRunResponse' :: CancelJobRunResponse -> Maybe Text
virtualClusterId} -> Maybe Text
virtualClusterId) (\s :: CancelJobRunResponse
s@CancelJobRunResponse' {} Maybe Text
a -> CancelJobRunResponse
s {$sel:virtualClusterId:CancelJobRunResponse' :: Maybe Text
virtualClusterId = Maybe Text
a} :: CancelJobRunResponse)

-- | 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)

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