{-# 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.LexModels.DeleteSlotType
-- 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 all versions of the slot type, including the @$LATEST@ version.
-- To delete a specific version of the slot type, use the
-- DeleteSlotTypeVersion operation.
--
-- You can delete a version of a slot type only if it is not referenced. To
-- delete a slot type that is referred to in one or more intents, you must
-- remove those references first.
--
-- If you get the @ResourceInUseException@ exception, the exception
-- provides an example reference that shows the intent where the slot type
-- is referenced. To remove the reference to the slot type, either update
-- the intent or delete it. If you get the same exception when you attempt
-- to delete the slot type again, repeat until the slot type has no
-- references and the @DeleteSlotType@ call is successful.
--
-- This operation requires permission for the @lex:DeleteSlotType@ action.
module Amazonka.LexModels.DeleteSlotType
  ( -- * Creating a Request
    DeleteSlotType (..),
    newDeleteSlotType,

    -- * Request Lenses
    deleteSlotType_name,

    -- * Destructuring the Response
    DeleteSlotTypeResponse (..),
    newDeleteSlotTypeResponse,
  )
where

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

-- | /See:/ 'newDeleteSlotType' smart constructor.
data DeleteSlotType = DeleteSlotType'
  { -- | The name of the slot type. The name is case sensitive.
    DeleteSlotType -> Text
name :: Prelude.Text
  }
  deriving (DeleteSlotType -> DeleteSlotType -> Bool
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: DeleteSlotType -> DeleteSlotType -> Bool
$c/= :: DeleteSlotType -> DeleteSlotType -> Bool
== :: DeleteSlotType -> DeleteSlotType -> Bool
$c== :: DeleteSlotType -> DeleteSlotType -> Bool
Prelude.Eq, ReadPrec [DeleteSlotType]
ReadPrec DeleteSlotType
Int -> ReadS DeleteSlotType
ReadS [DeleteSlotType]
forall a.
(Int -> ReadS a)
-> ReadS [a] -> ReadPrec a -> ReadPrec [a] -> Read a
readListPrec :: ReadPrec [DeleteSlotType]
$creadListPrec :: ReadPrec [DeleteSlotType]
readPrec :: ReadPrec DeleteSlotType
$creadPrec :: ReadPrec DeleteSlotType
readList :: ReadS [DeleteSlotType]
$creadList :: ReadS [DeleteSlotType]
readsPrec :: Int -> ReadS DeleteSlotType
$creadsPrec :: Int -> ReadS DeleteSlotType
Prelude.Read, Int -> DeleteSlotType -> ShowS
[DeleteSlotType] -> ShowS
DeleteSlotType -> String
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [DeleteSlotType] -> ShowS
$cshowList :: [DeleteSlotType] -> ShowS
show :: DeleteSlotType -> String
$cshow :: DeleteSlotType -> String
showsPrec :: Int -> DeleteSlotType -> ShowS
$cshowsPrec :: Int -> DeleteSlotType -> ShowS
Prelude.Show, forall x. Rep DeleteSlotType x -> DeleteSlotType
forall x. DeleteSlotType -> Rep DeleteSlotType x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cto :: forall x. Rep DeleteSlotType x -> DeleteSlotType
$cfrom :: forall x. DeleteSlotType -> Rep DeleteSlotType x
Prelude.Generic)

-- |
-- Create a value of 'DeleteSlotType' 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', 'deleteSlotType_name' - The name of the slot type. The name is case sensitive.
newDeleteSlotType ::
  -- | 'name'
  Prelude.Text ->
  DeleteSlotType
newDeleteSlotType :: Text -> DeleteSlotType
newDeleteSlotType Text
pName_ =
  DeleteSlotType' {$sel:name:DeleteSlotType' :: Text
name = Text
pName_}

-- | The name of the slot type. The name is case sensitive.
deleteSlotType_name :: Lens.Lens' DeleteSlotType Prelude.Text
deleteSlotType_name :: Lens' DeleteSlotType Text
deleteSlotType_name = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\DeleteSlotType' {Text
name :: Text
$sel:name:DeleteSlotType' :: DeleteSlotType -> Text
name} -> Text
name) (\s :: DeleteSlotType
s@DeleteSlotType' {} Text
a -> DeleteSlotType
s {$sel:name:DeleteSlotType' :: Text
name = Text
a} :: DeleteSlotType)

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

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

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

instance Data.ToHeaders DeleteSlotType where
  toHeaders :: DeleteSlotType -> [Header]
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 -> [Header]
Data.=# ( ByteString
"application/x-amz-json-1.1" ::
                          Prelude.ByteString
                      )
          ]
      )

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

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

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

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

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