{-# 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.Polly.DeleteLexicon
-- 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 the specified pronunciation lexicon stored in an Amazon Web
-- Services Region. A lexicon which has been deleted is not available for
-- speech synthesis, nor is it possible to retrieve it using either the
-- @GetLexicon@ or @ListLexicon@ APIs.
--
-- For more information, see
-- <https://docs.aws.amazon.com/polly/latest/dg/managing-lexicons.html Managing Lexicons>.
module Amazonka.Polly.DeleteLexicon
  ( -- * Creating a Request
    DeleteLexicon (..),
    newDeleteLexicon,

    -- * Request Lenses
    deleteLexicon_name,

    -- * Destructuring the Response
    DeleteLexiconResponse (..),
    newDeleteLexiconResponse,

    -- * Response Lenses
    deleteLexiconResponse_httpStatus,
  )
where

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

-- | /See:/ 'newDeleteLexicon' smart constructor.
data DeleteLexicon = DeleteLexicon'
  { -- | The name of the lexicon to delete. Must be an existing lexicon in the
    -- region.
    DeleteLexicon -> Text
name :: Prelude.Text
  }
  deriving (DeleteLexicon -> DeleteLexicon -> Bool
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: DeleteLexicon -> DeleteLexicon -> Bool
$c/= :: DeleteLexicon -> DeleteLexicon -> Bool
== :: DeleteLexicon -> DeleteLexicon -> Bool
$c== :: DeleteLexicon -> DeleteLexicon -> Bool
Prelude.Eq, ReadPrec [DeleteLexicon]
ReadPrec DeleteLexicon
Int -> ReadS DeleteLexicon
ReadS [DeleteLexicon]
forall a.
(Int -> ReadS a)
-> ReadS [a] -> ReadPrec a -> ReadPrec [a] -> Read a
readListPrec :: ReadPrec [DeleteLexicon]
$creadListPrec :: ReadPrec [DeleteLexicon]
readPrec :: ReadPrec DeleteLexicon
$creadPrec :: ReadPrec DeleteLexicon
readList :: ReadS [DeleteLexicon]
$creadList :: ReadS [DeleteLexicon]
readsPrec :: Int -> ReadS DeleteLexicon
$creadsPrec :: Int -> ReadS DeleteLexicon
Prelude.Read, Int -> DeleteLexicon -> ShowS
[DeleteLexicon] -> ShowS
DeleteLexicon -> String
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [DeleteLexicon] -> ShowS
$cshowList :: [DeleteLexicon] -> ShowS
show :: DeleteLexicon -> String
$cshow :: DeleteLexicon -> String
showsPrec :: Int -> DeleteLexicon -> ShowS
$cshowsPrec :: Int -> DeleteLexicon -> ShowS
Prelude.Show, forall x. Rep DeleteLexicon x -> DeleteLexicon
forall x. DeleteLexicon -> Rep DeleteLexicon x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cto :: forall x. Rep DeleteLexicon x -> DeleteLexicon
$cfrom :: forall x. DeleteLexicon -> Rep DeleteLexicon x
Prelude.Generic)

-- |
-- Create a value of 'DeleteLexicon' 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:
--
-- 'name', 'deleteLexicon_name' - The name of the lexicon to delete. Must be an existing lexicon in the
-- region.
newDeleteLexicon ::
  -- | 'name'
  Prelude.Text ->
  DeleteLexicon
newDeleteLexicon :: Text -> DeleteLexicon
newDeleteLexicon Text
pName_ =
  DeleteLexicon' {$sel:name:DeleteLexicon' :: Text
name = Text
pName_}

-- | The name of the lexicon to delete. Must be an existing lexicon in the
-- region.
deleteLexicon_name :: Lens.Lens' DeleteLexicon Prelude.Text
deleteLexicon_name :: Lens' DeleteLexicon Text
deleteLexicon_name = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\DeleteLexicon' {Text
name :: Text
$sel:name:DeleteLexicon' :: DeleteLexicon -> Text
name} -> Text
name) (\s :: DeleteLexicon
s@DeleteLexicon' {} Text
a -> DeleteLexicon
s {$sel:name:DeleteLexicon' :: Text
name = Text
a} :: DeleteLexicon)

instance Core.AWSRequest DeleteLexicon where
  type
    AWSResponse DeleteLexicon =
      DeleteLexiconResponse
  request :: (Service -> Service) -> DeleteLexicon -> Request DeleteLexicon
request Service -> Service
overrides =
    forall a. ToRequest a => Service -> a -> Request a
Request.delete (Service -> Service
overrides Service
defaultService)
  response :: forall (m :: * -> *).
MonadResource m =>
(ByteStringLazy -> IO ByteStringLazy)
-> Service
-> Proxy DeleteLexicon
-> ClientResponse ClientBody
-> m (Either Error (ClientResponse (AWSResponse DeleteLexicon)))
response =
    forall (m :: * -> *) a.
MonadResource m =>
(Int -> ResponseHeaders -> () -> Either String (AWSResponse a))
-> (ByteStringLazy -> IO ByteStringLazy)
-> Service
-> Proxy a
-> ClientResponse ClientBody
-> m (Either Error (ClientResponse (AWSResponse a)))
Response.receiveEmpty
      ( \Int
s ResponseHeaders
h ()
x ->
          Int -> DeleteLexiconResponse
DeleteLexiconResponse'
            forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
Prelude.<$> (forall (f :: * -> *) a. Applicative f => a -> f a
Prelude.pure (forall a. Enum a => a -> Int
Prelude.fromEnum Int
s))
      )

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

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

instance Data.ToHeaders DeleteLexicon where
  toHeaders :: DeleteLexicon -> ResponseHeaders
toHeaders = forall a b. a -> b -> a
Prelude.const forall a. Monoid a => a
Prelude.mempty

instance Data.ToPath DeleteLexicon where
  toPath :: DeleteLexicon -> ByteString
toPath DeleteLexicon' {Text
name :: Text
$sel:name:DeleteLexicon' :: DeleteLexicon -> Text
..} =
    forall a. Monoid a => [a] -> a
Prelude.mconcat [ByteString
"/v1/lexicons/", forall a. ToByteString a => a -> ByteString
Data.toBS Text
name]

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

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

-- |
-- Create a value of 'DeleteLexiconResponse' 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:
--
-- 'httpStatus', 'deleteLexiconResponse_httpStatus' - The response's http status code.
newDeleteLexiconResponse ::
  -- | 'httpStatus'
  Prelude.Int ->
  DeleteLexiconResponse
newDeleteLexiconResponse :: Int -> DeleteLexiconResponse
newDeleteLexiconResponse Int
pHttpStatus_ =
  DeleteLexiconResponse' {$sel:httpStatus:DeleteLexiconResponse' :: Int
httpStatus = Int
pHttpStatus_}

-- | The response's http status code.
deleteLexiconResponse_httpStatus :: Lens.Lens' DeleteLexiconResponse Prelude.Int
deleteLexiconResponse_httpStatus :: Lens' DeleteLexiconResponse Int
deleteLexiconResponse_httpStatus = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\DeleteLexiconResponse' {Int
httpStatus :: Int
$sel:httpStatus:DeleteLexiconResponse' :: DeleteLexiconResponse -> Int
httpStatus} -> Int
httpStatus) (\s :: DeleteLexiconResponse
s@DeleteLexiconResponse' {} Int
a -> DeleteLexiconResponse
s {$sel:httpStatus:DeleteLexiconResponse' :: Int
httpStatus = Int
a} :: DeleteLexiconResponse)

instance Prelude.NFData DeleteLexiconResponse where
  rnf :: DeleteLexiconResponse -> ()
rnf DeleteLexiconResponse' {Int
httpStatus :: Int
$sel:httpStatus:DeleteLexiconResponse' :: DeleteLexiconResponse -> Int
..} =
    forall a. NFData a => a -> ()
Prelude.rnf Int
httpStatus