{-# 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.StopTrainingJob
-- 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 training job. To stop a job, SageMaker sends the algorithm the
-- @SIGTERM@ signal, which delays job termination for 120 seconds.
-- Algorithms might use this 120-second window to save the model artifacts,
-- so the results of the training is not lost.
--
-- When it receives a @StopTrainingJob@ request, SageMaker changes the
-- status of the job to @Stopping@. After SageMaker stops the job, it sets
-- the status to @Stopped@.
module Amazonka.SageMaker.StopTrainingJob
  ( -- * Creating a Request
    StopTrainingJob (..),
    newStopTrainingJob,

    -- * Request Lenses
    stopTrainingJob_trainingJobName,

    -- * Destructuring the Response
    StopTrainingJobResponse (..),
    newStopTrainingJobResponse,
  )
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:/ 'newStopTrainingJob' smart constructor.
data StopTrainingJob = StopTrainingJob'
  { -- | The name of the training job to stop.
    StopTrainingJob -> Text
trainingJobName :: Prelude.Text
  }
  deriving (StopTrainingJob -> StopTrainingJob -> Bool
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: StopTrainingJob -> StopTrainingJob -> Bool
$c/= :: StopTrainingJob -> StopTrainingJob -> Bool
== :: StopTrainingJob -> StopTrainingJob -> Bool
$c== :: StopTrainingJob -> StopTrainingJob -> Bool
Prelude.Eq, ReadPrec [StopTrainingJob]
ReadPrec StopTrainingJob
Int -> ReadS StopTrainingJob
ReadS [StopTrainingJob]
forall a.
(Int -> ReadS a)
-> ReadS [a] -> ReadPrec a -> ReadPrec [a] -> Read a
readListPrec :: ReadPrec [StopTrainingJob]
$creadListPrec :: ReadPrec [StopTrainingJob]
readPrec :: ReadPrec StopTrainingJob
$creadPrec :: ReadPrec StopTrainingJob
readList :: ReadS [StopTrainingJob]
$creadList :: ReadS [StopTrainingJob]
readsPrec :: Int -> ReadS StopTrainingJob
$creadsPrec :: Int -> ReadS StopTrainingJob
Prelude.Read, Int -> StopTrainingJob -> ShowS
[StopTrainingJob] -> ShowS
StopTrainingJob -> String
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [StopTrainingJob] -> ShowS
$cshowList :: [StopTrainingJob] -> ShowS
show :: StopTrainingJob -> String
$cshow :: StopTrainingJob -> String
showsPrec :: Int -> StopTrainingJob -> ShowS
$cshowsPrec :: Int -> StopTrainingJob -> ShowS
Prelude.Show, forall x. Rep StopTrainingJob x -> StopTrainingJob
forall x. StopTrainingJob -> Rep StopTrainingJob x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cto :: forall x. Rep StopTrainingJob x -> StopTrainingJob
$cfrom :: forall x. StopTrainingJob -> Rep StopTrainingJob x
Prelude.Generic)

-- |
-- Create a value of 'StopTrainingJob' 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:
--
-- 'trainingJobName', 'stopTrainingJob_trainingJobName' - The name of the training job to stop.
newStopTrainingJob ::
  -- | 'trainingJobName'
  Prelude.Text ->
  StopTrainingJob
newStopTrainingJob :: Text -> StopTrainingJob
newStopTrainingJob Text
pTrainingJobName_ =
  StopTrainingJob'
    { $sel:trainingJobName:StopTrainingJob' :: Text
trainingJobName =
        Text
pTrainingJobName_
    }

-- | The name of the training job to stop.
stopTrainingJob_trainingJobName :: Lens.Lens' StopTrainingJob Prelude.Text
stopTrainingJob_trainingJobName :: Lens' StopTrainingJob Text
stopTrainingJob_trainingJobName = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\StopTrainingJob' {Text
trainingJobName :: Text
$sel:trainingJobName:StopTrainingJob' :: StopTrainingJob -> Text
trainingJobName} -> Text
trainingJobName) (\s :: StopTrainingJob
s@StopTrainingJob' {} Text
a -> StopTrainingJob
s {$sel:trainingJobName:StopTrainingJob' :: Text
trainingJobName = Text
a} :: StopTrainingJob)

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

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

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

instance Data.ToHeaders StopTrainingJob where
  toHeaders :: StopTrainingJob -> [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.StopTrainingJob" :: 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 StopTrainingJob where
  toJSON :: StopTrainingJob -> Value
toJSON StopTrainingJob' {Text
trainingJobName :: Text
$sel:trainingJobName:StopTrainingJob' :: StopTrainingJob -> Text
..} =
    [Pair] -> Value
Data.object
      ( forall a. [Maybe a] -> [a]
Prelude.catMaybes
          [ forall a. a -> Maybe a
Prelude.Just
              (Key
"TrainingJobName" forall kv v. (KeyValue kv, ToJSON v) => Key -> v -> kv
Data..= Text
trainingJobName)
          ]
      )

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

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

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

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

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