{-# 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.SageMaker.StopProcessingJob
-- Copyright   : (c) 2013-2023 Brendan Hay
-- License     : Mozilla Public License, v. 2.0.
-- Maintainer  : Brendan Hay
-- Stability   : auto-generated
-- Portability : non-portable (GHC extensions)
--
-- Stops a processing job.
module Amazonka.SageMaker.StopProcessingJob
  ( -- * Creating a Request
    StopProcessingJob (..),
    newStopProcessingJob,

    -- * Request Lenses
    stopProcessingJob_processingJobName,

    -- * Destructuring the Response
    StopProcessingJobResponse (..),
    newStopProcessingJobResponse,
  )
where

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

-- | /See:/ 'newStopProcessingJob' smart constructor.
data StopProcessingJob = StopProcessingJob'
  { -- | The name of the processing job to stop.
    StopProcessingJob -> Text
processingJobName :: Prelude.Text
  }
  deriving (StopProcessingJob -> StopProcessingJob -> Bool
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: StopProcessingJob -> StopProcessingJob -> Bool
$c/= :: StopProcessingJob -> StopProcessingJob -> Bool
== :: StopProcessingJob -> StopProcessingJob -> Bool
$c== :: StopProcessingJob -> StopProcessingJob -> Bool
Prelude.Eq, ReadPrec [StopProcessingJob]
ReadPrec StopProcessingJob
Int -> ReadS StopProcessingJob
ReadS [StopProcessingJob]
forall a.
(Int -> ReadS a)
-> ReadS [a] -> ReadPrec a -> ReadPrec [a] -> Read a
readListPrec :: ReadPrec [StopProcessingJob]
$creadListPrec :: ReadPrec [StopProcessingJob]
readPrec :: ReadPrec StopProcessingJob
$creadPrec :: ReadPrec StopProcessingJob
readList :: ReadS [StopProcessingJob]
$creadList :: ReadS [StopProcessingJob]
readsPrec :: Int -> ReadS StopProcessingJob
$creadsPrec :: Int -> ReadS StopProcessingJob
Prelude.Read, Int -> StopProcessingJob -> ShowS
[StopProcessingJob] -> ShowS
StopProcessingJob -> String
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [StopProcessingJob] -> ShowS
$cshowList :: [StopProcessingJob] -> ShowS
show :: StopProcessingJob -> String
$cshow :: StopProcessingJob -> String
showsPrec :: Int -> StopProcessingJob -> ShowS
$cshowsPrec :: Int -> StopProcessingJob -> ShowS
Prelude.Show, forall x. Rep StopProcessingJob x -> StopProcessingJob
forall x. StopProcessingJob -> Rep StopProcessingJob x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cto :: forall x. Rep StopProcessingJob x -> StopProcessingJob
$cfrom :: forall x. StopProcessingJob -> Rep StopProcessingJob x
Prelude.Generic)

-- |
-- Create a value of 'StopProcessingJob' 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:
--
-- 'processingJobName', 'stopProcessingJob_processingJobName' - The name of the processing job to stop.
newStopProcessingJob ::
  -- | 'processingJobName'
  Prelude.Text ->
  StopProcessingJob
newStopProcessingJob :: Text -> StopProcessingJob
newStopProcessingJob Text
pProcessingJobName_ =
  StopProcessingJob'
    { $sel:processingJobName:StopProcessingJob' :: Text
processingJobName =
        Text
pProcessingJobName_
    }

-- | The name of the processing job to stop.
stopProcessingJob_processingJobName :: Lens.Lens' StopProcessingJob Prelude.Text
stopProcessingJob_processingJobName :: Lens' StopProcessingJob Text
stopProcessingJob_processingJobName = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\StopProcessingJob' {Text
processingJobName :: Text
$sel:processingJobName:StopProcessingJob' :: StopProcessingJob -> Text
processingJobName} -> Text
processingJobName) (\s :: StopProcessingJob
s@StopProcessingJob' {} Text
a -> StopProcessingJob
s {$sel:processingJobName:StopProcessingJob' :: Text
processingJobName = Text
a} :: StopProcessingJob)

instance Core.AWSRequest StopProcessingJob where
  type
    AWSResponse StopProcessingJob =
      StopProcessingJobResponse
  request :: (Service -> Service)
-> StopProcessingJob -> Request StopProcessingJob
request Service -> Service
overrides =
    forall a. (ToRequest a, ToJSON a) => Service -> a -> Request a
Request.postJSON (Service -> Service
overrides Service
defaultService)
  response :: forall (m :: * -> *).
MonadResource m =>
(ByteStringLazy -> IO ByteStringLazy)
-> Service
-> Proxy StopProcessingJob
-> ClientResponse ClientBody
-> m (Either
        Error (ClientResponse (AWSResponse StopProcessingJob)))
response =
    forall (m :: * -> *) a.
MonadResource m =>
AWSResponse a
-> (ByteStringLazy -> IO ByteStringLazy)
-> Service
-> Proxy a
-> ClientResponse ClientBody
-> m (Either Error (ClientResponse (AWSResponse a)))
Response.receiveNull StopProcessingJobResponse
StopProcessingJobResponse'

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

instance Prelude.NFData StopProcessingJob where
  rnf :: StopProcessingJob -> ()
rnf StopProcessingJob' {Text
processingJobName :: Text
$sel:processingJobName:StopProcessingJob' :: StopProcessingJob -> Text
..} =
    forall a. NFData a => a -> ()
Prelude.rnf Text
processingJobName

instance Data.ToHeaders StopProcessingJob where
  toHeaders :: StopProcessingJob -> [Header]
toHeaders =
    forall a b. a -> b -> a
Prelude.const
      ( forall a. Monoid a => [a] -> a
Prelude.mconcat
          [ HeaderName
"X-Amz-Target"
              forall a. ToHeader a => HeaderName -> a -> [Header]
Data.=# ( ByteString
"SageMaker.StopProcessingJob" ::
                          Prelude.ByteString
                      ),
            HeaderName
"Content-Type"
              forall a. ToHeader a => HeaderName -> a -> [Header]
Data.=# ( ByteString
"application/x-amz-json-1.1" ::
                          Prelude.ByteString
                      )
          ]
      )

instance Data.ToJSON StopProcessingJob where
  toJSON :: StopProcessingJob -> Value
toJSON StopProcessingJob' {Text
processingJobName :: Text
$sel:processingJobName:StopProcessingJob' :: StopProcessingJob -> Text
..} =
    [Pair] -> Value
Data.object
      ( forall a. [Maybe a] -> [a]
Prelude.catMaybes
          [ forall a. a -> Maybe a
Prelude.Just
              (Key
"ProcessingJobName" forall kv v. (KeyValue kv, ToJSON v) => Key -> v -> kv
Data..= Text
processingJobName)
          ]
      )

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

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

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

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

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