{-# 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.Comprehend.DeleteDocumentClassifier
-- 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 previously created document classifier
--
-- Only those classifiers that are in terminated states (IN_ERROR, TRAINED)
-- will be deleted. If an active inference job is using the model, a
-- @ResourceInUseException@ will be returned.
--
-- This is an asynchronous action that puts the classifier into a DELETING
-- state, and it is then removed by a background job. Once removed, the
-- classifier disappears from your account and is no longer available for
-- use.
module Amazonka.Comprehend.DeleteDocumentClassifier
  ( -- * Creating a Request
    DeleteDocumentClassifier (..),
    newDeleteDocumentClassifier,

    -- * Request Lenses
    deleteDocumentClassifier_documentClassifierArn,

    -- * Destructuring the Response
    DeleteDocumentClassifierResponse (..),
    newDeleteDocumentClassifierResponse,

    -- * Response Lenses
    deleteDocumentClassifierResponse_httpStatus,
  )
where

import Amazonka.Comprehend.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:/ 'newDeleteDocumentClassifier' smart constructor.
data DeleteDocumentClassifier = DeleteDocumentClassifier'
  { -- | The Amazon Resource Name (ARN) that identifies the document classifier.
    DeleteDocumentClassifier -> Text
documentClassifierArn :: Prelude.Text
  }
  deriving (DeleteDocumentClassifier -> DeleteDocumentClassifier -> Bool
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: DeleteDocumentClassifier -> DeleteDocumentClassifier -> Bool
$c/= :: DeleteDocumentClassifier -> DeleteDocumentClassifier -> Bool
== :: DeleteDocumentClassifier -> DeleteDocumentClassifier -> Bool
$c== :: DeleteDocumentClassifier -> DeleteDocumentClassifier -> Bool
Prelude.Eq, ReadPrec [DeleteDocumentClassifier]
ReadPrec DeleteDocumentClassifier
Int -> ReadS DeleteDocumentClassifier
ReadS [DeleteDocumentClassifier]
forall a.
(Int -> ReadS a)
-> ReadS [a] -> ReadPrec a -> ReadPrec [a] -> Read a
readListPrec :: ReadPrec [DeleteDocumentClassifier]
$creadListPrec :: ReadPrec [DeleteDocumentClassifier]
readPrec :: ReadPrec DeleteDocumentClassifier
$creadPrec :: ReadPrec DeleteDocumentClassifier
readList :: ReadS [DeleteDocumentClassifier]
$creadList :: ReadS [DeleteDocumentClassifier]
readsPrec :: Int -> ReadS DeleteDocumentClassifier
$creadsPrec :: Int -> ReadS DeleteDocumentClassifier
Prelude.Read, Int -> DeleteDocumentClassifier -> ShowS
[DeleteDocumentClassifier] -> ShowS
DeleteDocumentClassifier -> String
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [DeleteDocumentClassifier] -> ShowS
$cshowList :: [DeleteDocumentClassifier] -> ShowS
show :: DeleteDocumentClassifier -> String
$cshow :: DeleteDocumentClassifier -> String
showsPrec :: Int -> DeleteDocumentClassifier -> ShowS
$cshowsPrec :: Int -> DeleteDocumentClassifier -> ShowS
Prelude.Show, forall x.
Rep DeleteDocumentClassifier x -> DeleteDocumentClassifier
forall x.
DeleteDocumentClassifier -> Rep DeleteDocumentClassifier x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cto :: forall x.
Rep DeleteDocumentClassifier x -> DeleteDocumentClassifier
$cfrom :: forall x.
DeleteDocumentClassifier -> Rep DeleteDocumentClassifier x
Prelude.Generic)

-- |
-- Create a value of 'DeleteDocumentClassifier' 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:
--
-- 'documentClassifierArn', 'deleteDocumentClassifier_documentClassifierArn' - The Amazon Resource Name (ARN) that identifies the document classifier.
newDeleteDocumentClassifier ::
  -- | 'documentClassifierArn'
  Prelude.Text ->
  DeleteDocumentClassifier
newDeleteDocumentClassifier :: Text -> DeleteDocumentClassifier
newDeleteDocumentClassifier Text
pDocumentClassifierArn_ =
  DeleteDocumentClassifier'
    { $sel:documentClassifierArn:DeleteDocumentClassifier' :: Text
documentClassifierArn =
        Text
pDocumentClassifierArn_
    }

-- | The Amazon Resource Name (ARN) that identifies the document classifier.
deleteDocumentClassifier_documentClassifierArn :: Lens.Lens' DeleteDocumentClassifier Prelude.Text
deleteDocumentClassifier_documentClassifierArn :: Lens' DeleteDocumentClassifier Text
deleteDocumentClassifier_documentClassifierArn = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\DeleteDocumentClassifier' {Text
documentClassifierArn :: Text
$sel:documentClassifierArn:DeleteDocumentClassifier' :: DeleteDocumentClassifier -> Text
documentClassifierArn} -> Text
documentClassifierArn) (\s :: DeleteDocumentClassifier
s@DeleteDocumentClassifier' {} Text
a -> DeleteDocumentClassifier
s {$sel:documentClassifierArn:DeleteDocumentClassifier' :: Text
documentClassifierArn = Text
a} :: DeleteDocumentClassifier)

instance Core.AWSRequest DeleteDocumentClassifier where
  type
    AWSResponse DeleteDocumentClassifier =
      DeleteDocumentClassifierResponse
  request :: (Service -> Service)
-> DeleteDocumentClassifier -> Request DeleteDocumentClassifier
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 DeleteDocumentClassifier
-> ClientResponse ClientBody
-> m (Either
        Error (ClientResponse (AWSResponse DeleteDocumentClassifier)))
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 -> DeleteDocumentClassifierResponse
DeleteDocumentClassifierResponse'
            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 DeleteDocumentClassifier where
  hashWithSalt :: Int -> DeleteDocumentClassifier -> Int
hashWithSalt Int
_salt DeleteDocumentClassifier' {Text
documentClassifierArn :: Text
$sel:documentClassifierArn:DeleteDocumentClassifier' :: DeleteDocumentClassifier -> Text
..} =
    Int
_salt forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Text
documentClassifierArn

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

instance Data.ToHeaders DeleteDocumentClassifier where
  toHeaders :: DeleteDocumentClassifier -> ResponseHeaders
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 -> ResponseHeaders
Data.=# ( ByteString
"Comprehend_20171127.DeleteDocumentClassifier" ::
                          Prelude.ByteString
                      ),
            HeaderName
"Content-Type"
              forall a. ToHeader a => HeaderName -> a -> ResponseHeaders
Data.=# ( ByteString
"application/x-amz-json-1.1" ::
                          Prelude.ByteString
                      )
          ]
      )

instance Data.ToJSON DeleteDocumentClassifier where
  toJSON :: DeleteDocumentClassifier -> Value
toJSON DeleteDocumentClassifier' {Text
documentClassifierArn :: Text
$sel:documentClassifierArn:DeleteDocumentClassifier' :: DeleteDocumentClassifier -> Text
..} =
    [Pair] -> Value
Data.object
      ( forall a. [Maybe a] -> [a]
Prelude.catMaybes
          [ forall a. a -> Maybe a
Prelude.Just
              ( Key
"DocumentClassifierArn"
                  forall kv v. (KeyValue kv, ToJSON v) => Key -> v -> kv
Data..= Text
documentClassifierArn
              )
          ]
      )

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

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

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

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

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

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