{-# 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.StopLabelingJob
-- 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 running labeling job. A job that is stopped cannot be restarted.
-- Any results obtained before the job is stopped are placed in the Amazon
-- S3 output bucket.
module Amazonka.SageMaker.StopLabelingJob
  ( -- * Creating a Request
    StopLabelingJob (..),
    newStopLabelingJob,

    -- * Request Lenses
    stopLabelingJob_labelingJobName,

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

-- |
-- Create a value of 'StopLabelingJob' 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:
--
-- 'labelingJobName', 'stopLabelingJob_labelingJobName' - The name of the labeling job to stop.
newStopLabelingJob ::
  -- | 'labelingJobName'
  Prelude.Text ->
  StopLabelingJob
newStopLabelingJob :: Text -> StopLabelingJob
newStopLabelingJob Text
pLabelingJobName_ =
  StopLabelingJob'
    { $sel:labelingJobName:StopLabelingJob' :: Text
labelingJobName =
        Text
pLabelingJobName_
    }

-- | The name of the labeling job to stop.
stopLabelingJob_labelingJobName :: Lens.Lens' StopLabelingJob Prelude.Text
stopLabelingJob_labelingJobName :: Lens' StopLabelingJob Text
stopLabelingJob_labelingJobName = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\StopLabelingJob' {Text
labelingJobName :: Text
$sel:labelingJobName:StopLabelingJob' :: StopLabelingJob -> Text
labelingJobName} -> Text
labelingJobName) (\s :: StopLabelingJob
s@StopLabelingJob' {} Text
a -> StopLabelingJob
s {$sel:labelingJobName:StopLabelingJob' :: Text
labelingJobName = Text
a} :: StopLabelingJob)

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

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

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

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

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

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

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

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

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