{-# 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.Transcribe.DeleteCallAnalyticsCategory
-- 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 Call Analytics category. To use this operation, specify the
-- name of the category you want to delete using @CategoryName@. Category
-- names are case sensitive.
module Amazonka.Transcribe.DeleteCallAnalyticsCategory
  ( -- * Creating a Request
    DeleteCallAnalyticsCategory (..),
    newDeleteCallAnalyticsCategory,

    -- * Request Lenses
    deleteCallAnalyticsCategory_categoryName,

    -- * Destructuring the Response
    DeleteCallAnalyticsCategoryResponse (..),
    newDeleteCallAnalyticsCategoryResponse,

    -- * Response Lenses
    deleteCallAnalyticsCategoryResponse_httpStatus,
  )
where

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

-- | /See:/ 'newDeleteCallAnalyticsCategory' smart constructor.
data DeleteCallAnalyticsCategory = DeleteCallAnalyticsCategory'
  { -- | The name of the Call Analytics category you want to delete. Category
    -- names are case sensitive.
    DeleteCallAnalyticsCategory -> Text
categoryName :: Prelude.Text
  }
  deriving (DeleteCallAnalyticsCategory -> DeleteCallAnalyticsCategory -> Bool
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: DeleteCallAnalyticsCategory -> DeleteCallAnalyticsCategory -> Bool
$c/= :: DeleteCallAnalyticsCategory -> DeleteCallAnalyticsCategory -> Bool
== :: DeleteCallAnalyticsCategory -> DeleteCallAnalyticsCategory -> Bool
$c== :: DeleteCallAnalyticsCategory -> DeleteCallAnalyticsCategory -> Bool
Prelude.Eq, ReadPrec [DeleteCallAnalyticsCategory]
ReadPrec DeleteCallAnalyticsCategory
Int -> ReadS DeleteCallAnalyticsCategory
ReadS [DeleteCallAnalyticsCategory]
forall a.
(Int -> ReadS a)
-> ReadS [a] -> ReadPrec a -> ReadPrec [a] -> Read a
readListPrec :: ReadPrec [DeleteCallAnalyticsCategory]
$creadListPrec :: ReadPrec [DeleteCallAnalyticsCategory]
readPrec :: ReadPrec DeleteCallAnalyticsCategory
$creadPrec :: ReadPrec DeleteCallAnalyticsCategory
readList :: ReadS [DeleteCallAnalyticsCategory]
$creadList :: ReadS [DeleteCallAnalyticsCategory]
readsPrec :: Int -> ReadS DeleteCallAnalyticsCategory
$creadsPrec :: Int -> ReadS DeleteCallAnalyticsCategory
Prelude.Read, Int -> DeleteCallAnalyticsCategory -> ShowS
[DeleteCallAnalyticsCategory] -> ShowS
DeleteCallAnalyticsCategory -> String
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [DeleteCallAnalyticsCategory] -> ShowS
$cshowList :: [DeleteCallAnalyticsCategory] -> ShowS
show :: DeleteCallAnalyticsCategory -> String
$cshow :: DeleteCallAnalyticsCategory -> String
showsPrec :: Int -> DeleteCallAnalyticsCategory -> ShowS
$cshowsPrec :: Int -> DeleteCallAnalyticsCategory -> ShowS
Prelude.Show, forall x.
Rep DeleteCallAnalyticsCategory x -> DeleteCallAnalyticsCategory
forall x.
DeleteCallAnalyticsCategory -> Rep DeleteCallAnalyticsCategory x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cto :: forall x.
Rep DeleteCallAnalyticsCategory x -> DeleteCallAnalyticsCategory
$cfrom :: forall x.
DeleteCallAnalyticsCategory -> Rep DeleteCallAnalyticsCategory x
Prelude.Generic)

-- |
-- Create a value of 'DeleteCallAnalyticsCategory' 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:
--
-- 'categoryName', 'deleteCallAnalyticsCategory_categoryName' - The name of the Call Analytics category you want to delete. Category
-- names are case sensitive.
newDeleteCallAnalyticsCategory ::
  -- | 'categoryName'
  Prelude.Text ->
  DeleteCallAnalyticsCategory
newDeleteCallAnalyticsCategory :: Text -> DeleteCallAnalyticsCategory
newDeleteCallAnalyticsCategory Text
pCategoryName_ =
  DeleteCallAnalyticsCategory'
    { $sel:categoryName:DeleteCallAnalyticsCategory' :: Text
categoryName =
        Text
pCategoryName_
    }

-- | The name of the Call Analytics category you want to delete. Category
-- names are case sensitive.
deleteCallAnalyticsCategory_categoryName :: Lens.Lens' DeleteCallAnalyticsCategory Prelude.Text
deleteCallAnalyticsCategory_categoryName :: Lens' DeleteCallAnalyticsCategory Text
deleteCallAnalyticsCategory_categoryName = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\DeleteCallAnalyticsCategory' {Text
categoryName :: Text
$sel:categoryName:DeleteCallAnalyticsCategory' :: DeleteCallAnalyticsCategory -> Text
categoryName} -> Text
categoryName) (\s :: DeleteCallAnalyticsCategory
s@DeleteCallAnalyticsCategory' {} Text
a -> DeleteCallAnalyticsCategory
s {$sel:categoryName:DeleteCallAnalyticsCategory' :: Text
categoryName = Text
a} :: DeleteCallAnalyticsCategory)

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

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

instance Data.ToHeaders DeleteCallAnalyticsCategory where
  toHeaders :: DeleteCallAnalyticsCategory -> 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
"Transcribe.DeleteCallAnalyticsCategory" ::
                          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 DeleteCallAnalyticsCategory where
  toJSON :: DeleteCallAnalyticsCategory -> Value
toJSON DeleteCallAnalyticsCategory' {Text
categoryName :: Text
$sel:categoryName:DeleteCallAnalyticsCategory' :: DeleteCallAnalyticsCategory -> Text
..} =
    [Pair] -> Value
Data.object
      ( forall a. [Maybe a] -> [a]
Prelude.catMaybes
          [forall a. a -> Maybe a
Prelude.Just (Key
"CategoryName" forall kv v. (KeyValue kv, ToJSON v) => Key -> v -> kv
Data..= Text
categoryName)]
      )

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

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

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

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

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

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