{-# 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.Transcribe.DeleteTranscriptionJob
-- Copyright   : (c) 2013-2023 Brendan Hay
-- License     : Mozilla Public License, v. 2.0.
-- Maintainer  : Brendan Hay
-- Stability   : auto-generated
-- Portability : non-portable (GHC extensions)
--
-- Deletes a transcription job. To use this operation, specify the name of
-- the job you want to delete using @TranscriptionJobName@. Job names are
-- case sensitive.
module Amazonka.Transcribe.DeleteTranscriptionJob
  ( -- * Creating a Request
    DeleteTranscriptionJob (..),
    newDeleteTranscriptionJob,

    -- * Request Lenses
    deleteTranscriptionJob_transcriptionJobName,

    -- * Destructuring the Response
    DeleteTranscriptionJobResponse (..),
    newDeleteTranscriptionJobResponse,
  )
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.Transcribe.Types

-- | /See:/ 'newDeleteTranscriptionJob' smart constructor.
data DeleteTranscriptionJob = DeleteTranscriptionJob'
  { -- | The name of the transcription job you want to delete. Job names are case
    -- sensitive.
    DeleteTranscriptionJob -> Text
transcriptionJobName :: Prelude.Text
  }
  deriving (DeleteTranscriptionJob -> DeleteTranscriptionJob -> Bool
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: DeleteTranscriptionJob -> DeleteTranscriptionJob -> Bool
$c/= :: DeleteTranscriptionJob -> DeleteTranscriptionJob -> Bool
== :: DeleteTranscriptionJob -> DeleteTranscriptionJob -> Bool
$c== :: DeleteTranscriptionJob -> DeleteTranscriptionJob -> Bool
Prelude.Eq, ReadPrec [DeleteTranscriptionJob]
ReadPrec DeleteTranscriptionJob
Int -> ReadS DeleteTranscriptionJob
ReadS [DeleteTranscriptionJob]
forall a.
(Int -> ReadS a)
-> ReadS [a] -> ReadPrec a -> ReadPrec [a] -> Read a
readListPrec :: ReadPrec [DeleteTranscriptionJob]
$creadListPrec :: ReadPrec [DeleteTranscriptionJob]
readPrec :: ReadPrec DeleteTranscriptionJob
$creadPrec :: ReadPrec DeleteTranscriptionJob
readList :: ReadS [DeleteTranscriptionJob]
$creadList :: ReadS [DeleteTranscriptionJob]
readsPrec :: Int -> ReadS DeleteTranscriptionJob
$creadsPrec :: Int -> ReadS DeleteTranscriptionJob
Prelude.Read, Int -> DeleteTranscriptionJob -> ShowS
[DeleteTranscriptionJob] -> ShowS
DeleteTranscriptionJob -> String
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [DeleteTranscriptionJob] -> ShowS
$cshowList :: [DeleteTranscriptionJob] -> ShowS
show :: DeleteTranscriptionJob -> String
$cshow :: DeleteTranscriptionJob -> String
showsPrec :: Int -> DeleteTranscriptionJob -> ShowS
$cshowsPrec :: Int -> DeleteTranscriptionJob -> ShowS
Prelude.Show, forall x. Rep DeleteTranscriptionJob x -> DeleteTranscriptionJob
forall x. DeleteTranscriptionJob -> Rep DeleteTranscriptionJob x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cto :: forall x. Rep DeleteTranscriptionJob x -> DeleteTranscriptionJob
$cfrom :: forall x. DeleteTranscriptionJob -> Rep DeleteTranscriptionJob x
Prelude.Generic)

-- |
-- Create a value of 'DeleteTranscriptionJob' 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:
--
-- 'transcriptionJobName', 'deleteTranscriptionJob_transcriptionJobName' - The name of the transcription job you want to delete. Job names are case
-- sensitive.
newDeleteTranscriptionJob ::
  -- | 'transcriptionJobName'
  Prelude.Text ->
  DeleteTranscriptionJob
newDeleteTranscriptionJob :: Text -> DeleteTranscriptionJob
newDeleteTranscriptionJob Text
pTranscriptionJobName_ =
  DeleteTranscriptionJob'
    { $sel:transcriptionJobName:DeleteTranscriptionJob' :: Text
transcriptionJobName =
        Text
pTranscriptionJobName_
    }

-- | The name of the transcription job you want to delete. Job names are case
-- sensitive.
deleteTranscriptionJob_transcriptionJobName :: Lens.Lens' DeleteTranscriptionJob Prelude.Text
deleteTranscriptionJob_transcriptionJobName :: Lens' DeleteTranscriptionJob Text
deleteTranscriptionJob_transcriptionJobName = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\DeleteTranscriptionJob' {Text
transcriptionJobName :: Text
$sel:transcriptionJobName:DeleteTranscriptionJob' :: DeleteTranscriptionJob -> Text
transcriptionJobName} -> Text
transcriptionJobName) (\s :: DeleteTranscriptionJob
s@DeleteTranscriptionJob' {} Text
a -> DeleteTranscriptionJob
s {$sel:transcriptionJobName:DeleteTranscriptionJob' :: Text
transcriptionJobName = Text
a} :: DeleteTranscriptionJob)

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

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

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

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

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

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

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

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

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