{-# 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.DeleteVocabulary
-- 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 custom vocabulary. To use this operation, specify the name of
-- the custom vocabulary you want to delete using @VocabularyName@. Custom
-- vocabulary names are case sensitive.
module Amazonka.Transcribe.DeleteVocabulary
  ( -- * Creating a Request
    DeleteVocabulary (..),
    newDeleteVocabulary,

    -- * Request Lenses
    deleteVocabulary_vocabularyName,

    -- * Destructuring the Response
    DeleteVocabularyResponse (..),
    newDeleteVocabularyResponse,
  )
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:/ 'newDeleteVocabulary' smart constructor.
data DeleteVocabulary = DeleteVocabulary'
  { -- | The name of the custom vocabulary you want to delete. Custom vocabulary
    -- names are case sensitive.
    DeleteVocabulary -> Text
vocabularyName :: Prelude.Text
  }
  deriving (DeleteVocabulary -> DeleteVocabulary -> Bool
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: DeleteVocabulary -> DeleteVocabulary -> Bool
$c/= :: DeleteVocabulary -> DeleteVocabulary -> Bool
== :: DeleteVocabulary -> DeleteVocabulary -> Bool
$c== :: DeleteVocabulary -> DeleteVocabulary -> Bool
Prelude.Eq, ReadPrec [DeleteVocabulary]
ReadPrec DeleteVocabulary
Int -> ReadS DeleteVocabulary
ReadS [DeleteVocabulary]
forall a.
(Int -> ReadS a)
-> ReadS [a] -> ReadPrec a -> ReadPrec [a] -> Read a
readListPrec :: ReadPrec [DeleteVocabulary]
$creadListPrec :: ReadPrec [DeleteVocabulary]
readPrec :: ReadPrec DeleteVocabulary
$creadPrec :: ReadPrec DeleteVocabulary
readList :: ReadS [DeleteVocabulary]
$creadList :: ReadS [DeleteVocabulary]
readsPrec :: Int -> ReadS DeleteVocabulary
$creadsPrec :: Int -> ReadS DeleteVocabulary
Prelude.Read, Int -> DeleteVocabulary -> ShowS
[DeleteVocabulary] -> ShowS
DeleteVocabulary -> String
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [DeleteVocabulary] -> ShowS
$cshowList :: [DeleteVocabulary] -> ShowS
show :: DeleteVocabulary -> String
$cshow :: DeleteVocabulary -> String
showsPrec :: Int -> DeleteVocabulary -> ShowS
$cshowsPrec :: Int -> DeleteVocabulary -> ShowS
Prelude.Show, forall x. Rep DeleteVocabulary x -> DeleteVocabulary
forall x. DeleteVocabulary -> Rep DeleteVocabulary x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cto :: forall x. Rep DeleteVocabulary x -> DeleteVocabulary
$cfrom :: forall x. DeleteVocabulary -> Rep DeleteVocabulary x
Prelude.Generic)

-- |
-- Create a value of 'DeleteVocabulary' 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:
--
-- 'vocabularyName', 'deleteVocabulary_vocabularyName' - The name of the custom vocabulary you want to delete. Custom vocabulary
-- names are case sensitive.
newDeleteVocabulary ::
  -- | 'vocabularyName'
  Prelude.Text ->
  DeleteVocabulary
newDeleteVocabulary :: Text -> DeleteVocabulary
newDeleteVocabulary Text
pVocabularyName_ =
  DeleteVocabulary'
    { $sel:vocabularyName:DeleteVocabulary' :: Text
vocabularyName =
        Text
pVocabularyName_
    }

-- | The name of the custom vocabulary you want to delete. Custom vocabulary
-- names are case sensitive.
deleteVocabulary_vocabularyName :: Lens.Lens' DeleteVocabulary Prelude.Text
deleteVocabulary_vocabularyName :: Lens' DeleteVocabulary Text
deleteVocabulary_vocabularyName = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\DeleteVocabulary' {Text
vocabularyName :: Text
$sel:vocabularyName:DeleteVocabulary' :: DeleteVocabulary -> Text
vocabularyName} -> Text
vocabularyName) (\s :: DeleteVocabulary
s@DeleteVocabulary' {} Text
a -> DeleteVocabulary
s {$sel:vocabularyName:DeleteVocabulary' :: Text
vocabularyName = Text
a} :: DeleteVocabulary)

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

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

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

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

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

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

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

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

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