{-# 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.Connect.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 the vocabulary that has the given identifier.
module Amazonka.Connect.DeleteVocabulary
  ( -- * Creating a Request
    DeleteVocabulary (..),
    newDeleteVocabulary,

    -- * Request Lenses
    deleteVocabulary_instanceId,
    deleteVocabulary_vocabularyId,

    -- * Destructuring the Response
    DeleteVocabularyResponse (..),
    newDeleteVocabularyResponse,

    -- * Response Lenses
    deleteVocabularyResponse_httpStatus,
    deleteVocabularyResponse_vocabularyArn,
    deleteVocabularyResponse_vocabularyId,
    deleteVocabularyResponse_state,
  )
where

import Amazonka.Connect.Types
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

-- | /See:/ 'newDeleteVocabulary' smart constructor.
data DeleteVocabulary = DeleteVocabulary'
  { -- | The identifier of the Amazon Connect instance. You can find the
    -- instanceId in the ARN of the instance.
    DeleteVocabulary -> Text
instanceId :: Prelude.Text,
    -- | The identifier of the custom vocabulary.
    DeleteVocabulary -> Text
vocabularyId :: 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:
--
-- 'instanceId', 'deleteVocabulary_instanceId' - The identifier of the Amazon Connect instance. You can find the
-- instanceId in the ARN of the instance.
--
-- 'vocabularyId', 'deleteVocabulary_vocabularyId' - The identifier of the custom vocabulary.
newDeleteVocabulary ::
  -- | 'instanceId'
  Prelude.Text ->
  -- | 'vocabularyId'
  Prelude.Text ->
  DeleteVocabulary
newDeleteVocabulary :: Text -> Text -> DeleteVocabulary
newDeleteVocabulary Text
pInstanceId_ Text
pVocabularyId_ =
  DeleteVocabulary'
    { $sel:instanceId:DeleteVocabulary' :: Text
instanceId = Text
pInstanceId_,
      $sel:vocabularyId:DeleteVocabulary' :: Text
vocabularyId = Text
pVocabularyId_
    }

-- | The identifier of the Amazon Connect instance. You can find the
-- instanceId in the ARN of the instance.
deleteVocabulary_instanceId :: Lens.Lens' DeleteVocabulary Prelude.Text
deleteVocabulary_instanceId :: Lens' DeleteVocabulary Text
deleteVocabulary_instanceId = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\DeleteVocabulary' {Text
instanceId :: Text
$sel:instanceId:DeleteVocabulary' :: DeleteVocabulary -> Text
instanceId} -> Text
instanceId) (\s :: DeleteVocabulary
s@DeleteVocabulary' {} Text
a -> DeleteVocabulary
s {$sel:instanceId:DeleteVocabulary' :: Text
instanceId = Text
a} :: DeleteVocabulary)

-- | The identifier of the custom vocabulary.
deleteVocabulary_vocabularyId :: Lens.Lens' DeleteVocabulary Prelude.Text
deleteVocabulary_vocabularyId :: Lens' DeleteVocabulary Text
deleteVocabulary_vocabularyId = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\DeleteVocabulary' {Text
vocabularyId :: Text
$sel:vocabularyId:DeleteVocabulary' :: DeleteVocabulary -> Text
vocabularyId} -> Text
vocabularyId) (\s :: DeleteVocabulary
s@DeleteVocabulary' {} Text
a -> DeleteVocabulary
s {$sel:vocabularyId:DeleteVocabulary' :: Text
vocabularyId = 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 =>
(Int -> ResponseHeaders -> Object -> Either String (AWSResponse a))
-> (ByteStringLazy -> IO ByteStringLazy)
-> Service
-> Proxy a
-> ClientResponse ClientBody
-> m (Either Error (ClientResponse (AWSResponse a)))
Response.receiveJSON
      ( \Int
s ResponseHeaders
h Object
x ->
          Int -> Text -> Text -> VocabularyState -> DeleteVocabularyResponse
DeleteVocabularyResponse'
            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))
            forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
Prelude.<*> (Object
x forall a. FromJSON a => Object -> Key -> Either String a
Data..:> Key
"VocabularyArn")
            forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
Prelude.<*> (Object
x forall a. FromJSON a => Object -> Key -> Either String a
Data..:> Key
"VocabularyId")
            forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
Prelude.<*> (Object
x forall a. FromJSON a => Object -> Key -> Either String a
Data..:> Key
"State")
      )

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

instance Prelude.NFData DeleteVocabulary where
  rnf :: DeleteVocabulary -> ()
rnf DeleteVocabulary' {Text
vocabularyId :: Text
instanceId :: Text
$sel:vocabularyId:DeleteVocabulary' :: DeleteVocabulary -> Text
$sel:instanceId:DeleteVocabulary' :: DeleteVocabulary -> Text
..} =
    forall a. NFData a => a -> ()
Prelude.rnf Text
instanceId
      seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf Text
vocabularyId

instance Data.ToHeaders DeleteVocabulary where
  toHeaders :: DeleteVocabulary -> ResponseHeaders
toHeaders =
    forall a b. a -> b -> a
Prelude.const
      ( forall a. Monoid a => [a] -> a
Prelude.mconcat
          [ HeaderName
"Content-Type"
              forall a. ToHeader a => HeaderName -> a -> ResponseHeaders
Data.=# ( ByteString
"application/x-amz-json-1.1" ::
                          Prelude.ByteString
                      )
          ]
      )

instance Data.ToJSON DeleteVocabulary where
  toJSON :: DeleteVocabulary -> Value
toJSON = forall a b. a -> b -> a
Prelude.const (Object -> Value
Data.Object forall a. Monoid a => a
Prelude.mempty)

instance Data.ToPath DeleteVocabulary where
  toPath :: DeleteVocabulary -> ByteString
toPath DeleteVocabulary' {Text
vocabularyId :: Text
instanceId :: Text
$sel:vocabularyId:DeleteVocabulary' :: DeleteVocabulary -> Text
$sel:instanceId:DeleteVocabulary' :: DeleteVocabulary -> Text
..} =
    forall a. Monoid a => [a] -> a
Prelude.mconcat
      [ ByteString
"/vocabulary-remove/",
        forall a. ToByteString a => a -> ByteString
Data.toBS Text
instanceId,
        ByteString
"/",
        forall a. ToByteString a => a -> ByteString
Data.toBS Text
vocabularyId
      ]

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'
  { -- | The response's http status code.
    DeleteVocabularyResponse -> Int
httpStatus :: Prelude.Int,
    -- | The Amazon Resource Name (ARN) of the custom vocabulary.
    DeleteVocabularyResponse -> Text
vocabularyArn :: Prelude.Text,
    -- | The identifier of the custom vocabulary.
    DeleteVocabularyResponse -> Text
vocabularyId :: Prelude.Text,
    -- | The current state of the custom vocabulary.
    DeleteVocabularyResponse -> VocabularyState
state :: VocabularyState
  }
  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.
--
-- The following record fields are available, with the corresponding lenses provided
-- for backwards compatibility:
--
-- 'httpStatus', 'deleteVocabularyResponse_httpStatus' - The response's http status code.
--
-- 'vocabularyArn', 'deleteVocabularyResponse_vocabularyArn' - The Amazon Resource Name (ARN) of the custom vocabulary.
--
-- 'vocabularyId', 'deleteVocabularyResponse_vocabularyId' - The identifier of the custom vocabulary.
--
-- 'state', 'deleteVocabularyResponse_state' - The current state of the custom vocabulary.
newDeleteVocabularyResponse ::
  -- | 'httpStatus'
  Prelude.Int ->
  -- | 'vocabularyArn'
  Prelude.Text ->
  -- | 'vocabularyId'
  Prelude.Text ->
  -- | 'state'
  VocabularyState ->
  DeleteVocabularyResponse
newDeleteVocabularyResponse :: Int -> Text -> Text -> VocabularyState -> DeleteVocabularyResponse
newDeleteVocabularyResponse
  Int
pHttpStatus_
  Text
pVocabularyArn_
  Text
pVocabularyId_
  VocabularyState
pState_ =
    DeleteVocabularyResponse'
      { $sel:httpStatus:DeleteVocabularyResponse' :: Int
httpStatus =
          Int
pHttpStatus_,
        $sel:vocabularyArn:DeleteVocabularyResponse' :: Text
vocabularyArn = Text
pVocabularyArn_,
        $sel:vocabularyId:DeleteVocabularyResponse' :: Text
vocabularyId = Text
pVocabularyId_,
        $sel:state:DeleteVocabularyResponse' :: VocabularyState
state = VocabularyState
pState_
      }

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

-- | The Amazon Resource Name (ARN) of the custom vocabulary.
deleteVocabularyResponse_vocabularyArn :: Lens.Lens' DeleteVocabularyResponse Prelude.Text
deleteVocabularyResponse_vocabularyArn :: Lens' DeleteVocabularyResponse Text
deleteVocabularyResponse_vocabularyArn = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\DeleteVocabularyResponse' {Text
vocabularyArn :: Text
$sel:vocabularyArn:DeleteVocabularyResponse' :: DeleteVocabularyResponse -> Text
vocabularyArn} -> Text
vocabularyArn) (\s :: DeleteVocabularyResponse
s@DeleteVocabularyResponse' {} Text
a -> DeleteVocabularyResponse
s {$sel:vocabularyArn:DeleteVocabularyResponse' :: Text
vocabularyArn = Text
a} :: DeleteVocabularyResponse)

-- | The identifier of the custom vocabulary.
deleteVocabularyResponse_vocabularyId :: Lens.Lens' DeleteVocabularyResponse Prelude.Text
deleteVocabularyResponse_vocabularyId :: Lens' DeleteVocabularyResponse Text
deleteVocabularyResponse_vocabularyId = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\DeleteVocabularyResponse' {Text
vocabularyId :: Text
$sel:vocabularyId:DeleteVocabularyResponse' :: DeleteVocabularyResponse -> Text
vocabularyId} -> Text
vocabularyId) (\s :: DeleteVocabularyResponse
s@DeleteVocabularyResponse' {} Text
a -> DeleteVocabularyResponse
s {$sel:vocabularyId:DeleteVocabularyResponse' :: Text
vocabularyId = Text
a} :: DeleteVocabularyResponse)

-- | The current state of the custom vocabulary.
deleteVocabularyResponse_state :: Lens.Lens' DeleteVocabularyResponse VocabularyState
deleteVocabularyResponse_state :: Lens' DeleteVocabularyResponse VocabularyState
deleteVocabularyResponse_state = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\DeleteVocabularyResponse' {VocabularyState
state :: VocabularyState
$sel:state:DeleteVocabularyResponse' :: DeleteVocabularyResponse -> VocabularyState
state} -> VocabularyState
state) (\s :: DeleteVocabularyResponse
s@DeleteVocabularyResponse' {} VocabularyState
a -> DeleteVocabularyResponse
s {$sel:state:DeleteVocabularyResponse' :: VocabularyState
state = VocabularyState
a} :: DeleteVocabularyResponse)

instance Prelude.NFData DeleteVocabularyResponse where
  rnf :: DeleteVocabularyResponse -> ()
rnf DeleteVocabularyResponse' {Int
Text
VocabularyState
state :: VocabularyState
vocabularyId :: Text
vocabularyArn :: Text
httpStatus :: Int
$sel:state:DeleteVocabularyResponse' :: DeleteVocabularyResponse -> VocabularyState
$sel:vocabularyId:DeleteVocabularyResponse' :: DeleteVocabularyResponse -> Text
$sel:vocabularyArn:DeleteVocabularyResponse' :: DeleteVocabularyResponse -> Text
$sel:httpStatus:DeleteVocabularyResponse' :: DeleteVocabularyResponse -> Int
..} =
    forall a. NFData a => a -> ()
Prelude.rnf Int
httpStatus
      seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf Text
vocabularyArn
      seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf Text
vocabularyId
      seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf VocabularyState
state