{-# 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.DeleteIntentVersion
-- 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 specific version of an intent. To delete all versions of a
-- intent, use the DeleteIntent operation.
--
-- This operation requires permissions for the @lex:DeleteIntentVersion@
-- action.
module Amazonka.LexModels.DeleteIntentVersion
  ( -- * Creating a Request
    DeleteIntentVersion (..),
    newDeleteIntentVersion,

    -- * Request Lenses
    deleteIntentVersion_name,
    deleteIntentVersion_version,

    -- * Destructuring the Response
    DeleteIntentVersionResponse (..),
    newDeleteIntentVersionResponse,
  )
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:/ 'newDeleteIntentVersion' smart constructor.
data DeleteIntentVersion = DeleteIntentVersion'
  { -- | The name of the intent.
    DeleteIntentVersion -> Text
name :: Prelude.Text,
    -- | The version of the intent to delete. You cannot delete the @$LATEST@
    -- version of the intent. To delete the @$LATEST@ version, use the
    -- DeleteIntent operation.
    DeleteIntentVersion -> Text
version :: Prelude.Text
  }
  deriving (DeleteIntentVersion -> DeleteIntentVersion -> Bool
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: DeleteIntentVersion -> DeleteIntentVersion -> Bool
$c/= :: DeleteIntentVersion -> DeleteIntentVersion -> Bool
== :: DeleteIntentVersion -> DeleteIntentVersion -> Bool
$c== :: DeleteIntentVersion -> DeleteIntentVersion -> Bool
Prelude.Eq, ReadPrec [DeleteIntentVersion]
ReadPrec DeleteIntentVersion
Int -> ReadS DeleteIntentVersion
ReadS [DeleteIntentVersion]
forall a.
(Int -> ReadS a)
-> ReadS [a] -> ReadPrec a -> ReadPrec [a] -> Read a
readListPrec :: ReadPrec [DeleteIntentVersion]
$creadListPrec :: ReadPrec [DeleteIntentVersion]
readPrec :: ReadPrec DeleteIntentVersion
$creadPrec :: ReadPrec DeleteIntentVersion
readList :: ReadS [DeleteIntentVersion]
$creadList :: ReadS [DeleteIntentVersion]
readsPrec :: Int -> ReadS DeleteIntentVersion
$creadsPrec :: Int -> ReadS DeleteIntentVersion
Prelude.Read, Int -> DeleteIntentVersion -> ShowS
[DeleteIntentVersion] -> ShowS
DeleteIntentVersion -> String
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [DeleteIntentVersion] -> ShowS
$cshowList :: [DeleteIntentVersion] -> ShowS
show :: DeleteIntentVersion -> String
$cshow :: DeleteIntentVersion -> String
showsPrec :: Int -> DeleteIntentVersion -> ShowS
$cshowsPrec :: Int -> DeleteIntentVersion -> ShowS
Prelude.Show, forall x. Rep DeleteIntentVersion x -> DeleteIntentVersion
forall x. DeleteIntentVersion -> Rep DeleteIntentVersion x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cto :: forall x. Rep DeleteIntentVersion x -> DeleteIntentVersion
$cfrom :: forall x. DeleteIntentVersion -> Rep DeleteIntentVersion x
Prelude.Generic)

-- |
-- Create a value of 'DeleteIntentVersion' 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', 'deleteIntentVersion_name' - The name of the intent.
--
-- 'version', 'deleteIntentVersion_version' - The version of the intent to delete. You cannot delete the @$LATEST@
-- version of the intent. To delete the @$LATEST@ version, use the
-- DeleteIntent operation.
newDeleteIntentVersion ::
  -- | 'name'
  Prelude.Text ->
  -- | 'version'
  Prelude.Text ->
  DeleteIntentVersion
newDeleteIntentVersion :: Text -> Text -> DeleteIntentVersion
newDeleteIntentVersion Text
pName_ Text
pVersion_ =
  DeleteIntentVersion'
    { $sel:name:DeleteIntentVersion' :: Text
name = Text
pName_,
      $sel:version:DeleteIntentVersion' :: Text
version = Text
pVersion_
    }

-- | The name of the intent.
deleteIntentVersion_name :: Lens.Lens' DeleteIntentVersion Prelude.Text
deleteIntentVersion_name :: Lens' DeleteIntentVersion Text
deleteIntentVersion_name = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\DeleteIntentVersion' {Text
name :: Text
$sel:name:DeleteIntentVersion' :: DeleteIntentVersion -> Text
name} -> Text
name) (\s :: DeleteIntentVersion
s@DeleteIntentVersion' {} Text
a -> DeleteIntentVersion
s {$sel:name:DeleteIntentVersion' :: Text
name = Text
a} :: DeleteIntentVersion)

-- | The version of the intent to delete. You cannot delete the @$LATEST@
-- version of the intent. To delete the @$LATEST@ version, use the
-- DeleteIntent operation.
deleteIntentVersion_version :: Lens.Lens' DeleteIntentVersion Prelude.Text
deleteIntentVersion_version :: Lens' DeleteIntentVersion Text
deleteIntentVersion_version = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\DeleteIntentVersion' {Text
version :: Text
$sel:version:DeleteIntentVersion' :: DeleteIntentVersion -> Text
version} -> Text
version) (\s :: DeleteIntentVersion
s@DeleteIntentVersion' {} Text
a -> DeleteIntentVersion
s {$sel:version:DeleteIntentVersion' :: Text
version = Text
a} :: DeleteIntentVersion)

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

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

instance Prelude.NFData DeleteIntentVersion where
  rnf :: DeleteIntentVersion -> ()
rnf DeleteIntentVersion' {Text
version :: Text
name :: Text
$sel:version:DeleteIntentVersion' :: DeleteIntentVersion -> Text
$sel:name:DeleteIntentVersion' :: DeleteIntentVersion -> Text
..} =
    forall a. NFData a => a -> ()
Prelude.rnf Text
name seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf Text
version

instance Data.ToHeaders DeleteIntentVersion where
  toHeaders :: DeleteIntentVersion -> [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 DeleteIntentVersion where
  toPath :: DeleteIntentVersion -> ByteString
toPath DeleteIntentVersion' {Text
version :: Text
name :: Text
$sel:version:DeleteIntentVersion' :: DeleteIntentVersion -> Text
$sel:name:DeleteIntentVersion' :: DeleteIntentVersion -> Text
..} =
    forall a. Monoid a => [a] -> a
Prelude.mconcat
      [ ByteString
"/intents/",
        forall a. ToByteString a => a -> ByteString
Data.toBS Text
name,
        ByteString
"/versions/",
        forall a. ToByteString a => a -> ByteString
Data.toBS Text
version
      ]

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

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

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

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