{-# 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.CreateCallAnalyticsCategory
-- Copyright   : (c) 2013-2023 Brendan Hay
-- License     : Mozilla Public License, v. 2.0.
-- Maintainer  : Brendan Hay
-- Stability   : auto-generated
-- Portability : non-portable (GHC extensions)
--
-- Creates a new Call Analytics category.
--
-- All categories are automatically applied to your Call Analytics
-- transcriptions. Note that in order to apply categories to your
-- transcriptions, you must create them before submitting your
-- transcription request, as categories cannot be applied retroactively.
--
-- When creating a new category, you can use the @InputType@ parameter to
-- label the category as a batch category (@POST_CALL@) or a streaming
-- category (@REAL_TIME@). Batch categories can only be applied to batch
-- transcriptions and streaming categories can only be applied to streaming
-- transcriptions. If you do not include @InputType@, your category is
-- created as a batch category by default.
--
-- Call Analytics categories are composed of rules. For each category, you
-- must create between 1 and 20 rules. Rules can include these parameters:
-- , , , and .
--
-- To update an existing category, see .
--
-- To learn more about Call Analytics categories, see
-- <https://docs.aws.amazon.com/transcribe/latest/dg/tca-categories-batch.html Creating categories for batch transcriptions>
-- and
-- <https://docs.aws.amazon.com/transcribe/latest/dg/tca-categories-stream.html Creating categories for streaming transcriptions>.
module Amazonka.Transcribe.CreateCallAnalyticsCategory
  ( -- * Creating a Request
    CreateCallAnalyticsCategory (..),
    newCreateCallAnalyticsCategory,

    -- * Request Lenses
    createCallAnalyticsCategory_inputType,
    createCallAnalyticsCategory_categoryName,
    createCallAnalyticsCategory_rules,

    -- * Destructuring the Response
    CreateCallAnalyticsCategoryResponse (..),
    newCreateCallAnalyticsCategoryResponse,

    -- * Response Lenses
    createCallAnalyticsCategoryResponse_categoryProperties,
    createCallAnalyticsCategoryResponse_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:/ 'newCreateCallAnalyticsCategory' smart constructor.
data CreateCallAnalyticsCategory = CreateCallAnalyticsCategory'
  { -- | Choose whether you want to create a streaming or a batch category for
    -- your Call Analytics transcription.
    --
    -- Specifying @POST_CALL@ assigns your category to batch transcriptions;
    -- categories with this input type cannot be applied to streaming
    -- (real-time) transcriptions.
    --
    -- Specifying @REAL_TIME@ assigns your category to streaming
    -- transcriptions; categories with this input type cannot be applied to
    -- batch (post-call) transcriptions.
    --
    -- If you do not include @InputType@, your category is created as a batch
    -- category by default.
    CreateCallAnalyticsCategory -> Maybe InputType
inputType :: Prelude.Maybe InputType,
    -- | A unique name, chosen by you, for your Call Analytics category. It\'s
    -- helpful to use a detailed naming system that will make sense to you in
    -- the future. For example, it\'s better to use
    -- @sentiment-positive-last30seconds@ for a category over a generic name
    -- like @test-category@.
    --
    -- Category names are case sensitive.
    CreateCallAnalyticsCategory -> Text
categoryName :: Prelude.Text,
    -- | Rules define a Call Analytics category. When creating a new category,
    -- you must create between 1 and 20 rules for that category. For each rule,
    -- you specify a filter you want applied to the attributes of a call. For
    -- example, you can choose a sentiment filter that detects if a customer\'s
    -- sentiment was positive during the last 30 seconds of the call.
    CreateCallAnalyticsCategory -> NonEmpty Rule
rules :: Prelude.NonEmpty Rule
  }
  deriving (CreateCallAnalyticsCategory -> CreateCallAnalyticsCategory -> Bool
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: CreateCallAnalyticsCategory -> CreateCallAnalyticsCategory -> Bool
$c/= :: CreateCallAnalyticsCategory -> CreateCallAnalyticsCategory -> Bool
== :: CreateCallAnalyticsCategory -> CreateCallAnalyticsCategory -> Bool
$c== :: CreateCallAnalyticsCategory -> CreateCallAnalyticsCategory -> Bool
Prelude.Eq, ReadPrec [CreateCallAnalyticsCategory]
ReadPrec CreateCallAnalyticsCategory
Int -> ReadS CreateCallAnalyticsCategory
ReadS [CreateCallAnalyticsCategory]
forall a.
(Int -> ReadS a)
-> ReadS [a] -> ReadPrec a -> ReadPrec [a] -> Read a
readListPrec :: ReadPrec [CreateCallAnalyticsCategory]
$creadListPrec :: ReadPrec [CreateCallAnalyticsCategory]
readPrec :: ReadPrec CreateCallAnalyticsCategory
$creadPrec :: ReadPrec CreateCallAnalyticsCategory
readList :: ReadS [CreateCallAnalyticsCategory]
$creadList :: ReadS [CreateCallAnalyticsCategory]
readsPrec :: Int -> ReadS CreateCallAnalyticsCategory
$creadsPrec :: Int -> ReadS CreateCallAnalyticsCategory
Prelude.Read, Int -> CreateCallAnalyticsCategory -> ShowS
[CreateCallAnalyticsCategory] -> ShowS
CreateCallAnalyticsCategory -> String
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [CreateCallAnalyticsCategory] -> ShowS
$cshowList :: [CreateCallAnalyticsCategory] -> ShowS
show :: CreateCallAnalyticsCategory -> String
$cshow :: CreateCallAnalyticsCategory -> String
showsPrec :: Int -> CreateCallAnalyticsCategory -> ShowS
$cshowsPrec :: Int -> CreateCallAnalyticsCategory -> ShowS
Prelude.Show, forall x.
Rep CreateCallAnalyticsCategory x -> CreateCallAnalyticsCategory
forall x.
CreateCallAnalyticsCategory -> Rep CreateCallAnalyticsCategory x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cto :: forall x.
Rep CreateCallAnalyticsCategory x -> CreateCallAnalyticsCategory
$cfrom :: forall x.
CreateCallAnalyticsCategory -> Rep CreateCallAnalyticsCategory x
Prelude.Generic)

-- |
-- Create a value of 'CreateCallAnalyticsCategory' 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:
--
-- 'inputType', 'createCallAnalyticsCategory_inputType' - Choose whether you want to create a streaming or a batch category for
-- your Call Analytics transcription.
--
-- Specifying @POST_CALL@ assigns your category to batch transcriptions;
-- categories with this input type cannot be applied to streaming
-- (real-time) transcriptions.
--
-- Specifying @REAL_TIME@ assigns your category to streaming
-- transcriptions; categories with this input type cannot be applied to
-- batch (post-call) transcriptions.
--
-- If you do not include @InputType@, your category is created as a batch
-- category by default.
--
-- 'categoryName', 'createCallAnalyticsCategory_categoryName' - A unique name, chosen by you, for your Call Analytics category. It\'s
-- helpful to use a detailed naming system that will make sense to you in
-- the future. For example, it\'s better to use
-- @sentiment-positive-last30seconds@ for a category over a generic name
-- like @test-category@.
--
-- Category names are case sensitive.
--
-- 'rules', 'createCallAnalyticsCategory_rules' - Rules define a Call Analytics category. When creating a new category,
-- you must create between 1 and 20 rules for that category. For each rule,
-- you specify a filter you want applied to the attributes of a call. For
-- example, you can choose a sentiment filter that detects if a customer\'s
-- sentiment was positive during the last 30 seconds of the call.
newCreateCallAnalyticsCategory ::
  -- | 'categoryName'
  Prelude.Text ->
  -- | 'rules'
  Prelude.NonEmpty Rule ->
  CreateCallAnalyticsCategory
newCreateCallAnalyticsCategory :: Text -> NonEmpty Rule -> CreateCallAnalyticsCategory
newCreateCallAnalyticsCategory Text
pCategoryName_ NonEmpty Rule
pRules_ =
  CreateCallAnalyticsCategory'
    { $sel:inputType:CreateCallAnalyticsCategory' :: Maybe InputType
inputType =
        forall a. Maybe a
Prelude.Nothing,
      $sel:categoryName:CreateCallAnalyticsCategory' :: Text
categoryName = Text
pCategoryName_,
      $sel:rules:CreateCallAnalyticsCategory' :: NonEmpty Rule
rules = forall s t a b. (Coercible s a, Coercible t b) => Iso s t a b
Lens.coerced forall t b. AReview t b -> b -> t
Lens.# NonEmpty Rule
pRules_
    }

-- | Choose whether you want to create a streaming or a batch category for
-- your Call Analytics transcription.
--
-- Specifying @POST_CALL@ assigns your category to batch transcriptions;
-- categories with this input type cannot be applied to streaming
-- (real-time) transcriptions.
--
-- Specifying @REAL_TIME@ assigns your category to streaming
-- transcriptions; categories with this input type cannot be applied to
-- batch (post-call) transcriptions.
--
-- If you do not include @InputType@, your category is created as a batch
-- category by default.
createCallAnalyticsCategory_inputType :: Lens.Lens' CreateCallAnalyticsCategory (Prelude.Maybe InputType)
createCallAnalyticsCategory_inputType :: Lens' CreateCallAnalyticsCategory (Maybe InputType)
createCallAnalyticsCategory_inputType = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\CreateCallAnalyticsCategory' {Maybe InputType
inputType :: Maybe InputType
$sel:inputType:CreateCallAnalyticsCategory' :: CreateCallAnalyticsCategory -> Maybe InputType
inputType} -> Maybe InputType
inputType) (\s :: CreateCallAnalyticsCategory
s@CreateCallAnalyticsCategory' {} Maybe InputType
a -> CreateCallAnalyticsCategory
s {$sel:inputType:CreateCallAnalyticsCategory' :: Maybe InputType
inputType = Maybe InputType
a} :: CreateCallAnalyticsCategory)

-- | A unique name, chosen by you, for your Call Analytics category. It\'s
-- helpful to use a detailed naming system that will make sense to you in
-- the future. For example, it\'s better to use
-- @sentiment-positive-last30seconds@ for a category over a generic name
-- like @test-category@.
--
-- Category names are case sensitive.
createCallAnalyticsCategory_categoryName :: Lens.Lens' CreateCallAnalyticsCategory Prelude.Text
createCallAnalyticsCategory_categoryName :: Lens' CreateCallAnalyticsCategory Text
createCallAnalyticsCategory_categoryName = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\CreateCallAnalyticsCategory' {Text
categoryName :: Text
$sel:categoryName:CreateCallAnalyticsCategory' :: CreateCallAnalyticsCategory -> Text
categoryName} -> Text
categoryName) (\s :: CreateCallAnalyticsCategory
s@CreateCallAnalyticsCategory' {} Text
a -> CreateCallAnalyticsCategory
s {$sel:categoryName:CreateCallAnalyticsCategory' :: Text
categoryName = Text
a} :: CreateCallAnalyticsCategory)

-- | Rules define a Call Analytics category. When creating a new category,
-- you must create between 1 and 20 rules for that category. For each rule,
-- you specify a filter you want applied to the attributes of a call. For
-- example, you can choose a sentiment filter that detects if a customer\'s
-- sentiment was positive during the last 30 seconds of the call.
createCallAnalyticsCategory_rules :: Lens.Lens' CreateCallAnalyticsCategory (Prelude.NonEmpty Rule)
createCallAnalyticsCategory_rules :: Lens' CreateCallAnalyticsCategory (NonEmpty Rule)
createCallAnalyticsCategory_rules = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\CreateCallAnalyticsCategory' {NonEmpty Rule
rules :: NonEmpty Rule
$sel:rules:CreateCallAnalyticsCategory' :: CreateCallAnalyticsCategory -> NonEmpty Rule
rules} -> NonEmpty Rule
rules) (\s :: CreateCallAnalyticsCategory
s@CreateCallAnalyticsCategory' {} NonEmpty Rule
a -> CreateCallAnalyticsCategory
s {$sel:rules:CreateCallAnalyticsCategory' :: NonEmpty Rule
rules = NonEmpty Rule
a} :: CreateCallAnalyticsCategory) forall b c a. (b -> c) -> (a -> b) -> a -> c
Prelude.. forall s t a b. (Coercible s a, Coercible t b) => Iso s t a b
Lens.coerced

instance Core.AWSRequest CreateCallAnalyticsCategory where
  type
    AWSResponse CreateCallAnalyticsCategory =
      CreateCallAnalyticsCategoryResponse
  request :: (Service -> Service)
-> CreateCallAnalyticsCategory
-> Request CreateCallAnalyticsCategory
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 CreateCallAnalyticsCategory
-> ClientResponse ClientBody
-> m (Either
        Error (ClientResponse (AWSResponse CreateCallAnalyticsCategory)))
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 ->
          Maybe CategoryProperties
-> Int -> CreateCallAnalyticsCategoryResponse
CreateCallAnalyticsCategoryResponse'
            forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
Prelude.<$> (Object
x forall a. FromJSON a => Object -> Key -> Either String (Maybe a)
Data..?> Key
"CategoryProperties")
            forall (f :: * -> *) a b. Applicative f => 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 CreateCallAnalyticsCategory where
  hashWithSalt :: Int -> CreateCallAnalyticsCategory -> Int
hashWithSalt Int
_salt CreateCallAnalyticsCategory' {Maybe InputType
NonEmpty Rule
Text
rules :: NonEmpty Rule
categoryName :: Text
inputType :: Maybe InputType
$sel:rules:CreateCallAnalyticsCategory' :: CreateCallAnalyticsCategory -> NonEmpty Rule
$sel:categoryName:CreateCallAnalyticsCategory' :: CreateCallAnalyticsCategory -> Text
$sel:inputType:CreateCallAnalyticsCategory' :: CreateCallAnalyticsCategory -> Maybe InputType
..} =
    Int
_salt
      forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Maybe InputType
inputType
      forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Text
categoryName
      forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` NonEmpty Rule
rules

instance Prelude.NFData CreateCallAnalyticsCategory where
  rnf :: CreateCallAnalyticsCategory -> ()
rnf CreateCallAnalyticsCategory' {Maybe InputType
NonEmpty Rule
Text
rules :: NonEmpty Rule
categoryName :: Text
inputType :: Maybe InputType
$sel:rules:CreateCallAnalyticsCategory' :: CreateCallAnalyticsCategory -> NonEmpty Rule
$sel:categoryName:CreateCallAnalyticsCategory' :: CreateCallAnalyticsCategory -> Text
$sel:inputType:CreateCallAnalyticsCategory' :: CreateCallAnalyticsCategory -> Maybe InputType
..} =
    forall a. NFData a => a -> ()
Prelude.rnf Maybe InputType
inputType
      seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf Text
categoryName
      seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf NonEmpty Rule
rules

instance Data.ToHeaders CreateCallAnalyticsCategory where
  toHeaders :: CreateCallAnalyticsCategory -> 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.CreateCallAnalyticsCategory" ::
                          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 CreateCallAnalyticsCategory where
  toJSON :: CreateCallAnalyticsCategory -> Value
toJSON CreateCallAnalyticsCategory' {Maybe InputType
NonEmpty Rule
Text
rules :: NonEmpty Rule
categoryName :: Text
inputType :: Maybe InputType
$sel:rules:CreateCallAnalyticsCategory' :: CreateCallAnalyticsCategory -> NonEmpty Rule
$sel:categoryName:CreateCallAnalyticsCategory' :: CreateCallAnalyticsCategory -> Text
$sel:inputType:CreateCallAnalyticsCategory' :: CreateCallAnalyticsCategory -> Maybe InputType
..} =
    [Pair] -> Value
Data.object
      ( forall a. [Maybe a] -> [a]
Prelude.catMaybes
          [ (Key
"InputType" forall kv v. (KeyValue kv, ToJSON v) => Key -> v -> kv
Data..=) forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
Prelude.<$> Maybe InputType
inputType,
            forall a. a -> Maybe a
Prelude.Just (Key
"CategoryName" forall kv v. (KeyValue kv, ToJSON v) => Key -> v -> kv
Data..= Text
categoryName),
            forall a. a -> Maybe a
Prelude.Just (Key
"Rules" forall kv v. (KeyValue kv, ToJSON v) => Key -> v -> kv
Data..= NonEmpty Rule
rules)
          ]
      )

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

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

-- | /See:/ 'newCreateCallAnalyticsCategoryResponse' smart constructor.
data CreateCallAnalyticsCategoryResponse = CreateCallAnalyticsCategoryResponse'
  { -- | Provides you with the properties of your new category, including its
    -- associated rules.
    CreateCallAnalyticsCategoryResponse -> Maybe CategoryProperties
categoryProperties :: Prelude.Maybe CategoryProperties,
    -- | The response's http status code.
    CreateCallAnalyticsCategoryResponse -> Int
httpStatus :: Prelude.Int
  }
  deriving (CreateCallAnalyticsCategoryResponse
-> CreateCallAnalyticsCategoryResponse -> Bool
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: CreateCallAnalyticsCategoryResponse
-> CreateCallAnalyticsCategoryResponse -> Bool
$c/= :: CreateCallAnalyticsCategoryResponse
-> CreateCallAnalyticsCategoryResponse -> Bool
== :: CreateCallAnalyticsCategoryResponse
-> CreateCallAnalyticsCategoryResponse -> Bool
$c== :: CreateCallAnalyticsCategoryResponse
-> CreateCallAnalyticsCategoryResponse -> Bool
Prelude.Eq, ReadPrec [CreateCallAnalyticsCategoryResponse]
ReadPrec CreateCallAnalyticsCategoryResponse
Int -> ReadS CreateCallAnalyticsCategoryResponse
ReadS [CreateCallAnalyticsCategoryResponse]
forall a.
(Int -> ReadS a)
-> ReadS [a] -> ReadPrec a -> ReadPrec [a] -> Read a
readListPrec :: ReadPrec [CreateCallAnalyticsCategoryResponse]
$creadListPrec :: ReadPrec [CreateCallAnalyticsCategoryResponse]
readPrec :: ReadPrec CreateCallAnalyticsCategoryResponse
$creadPrec :: ReadPrec CreateCallAnalyticsCategoryResponse
readList :: ReadS [CreateCallAnalyticsCategoryResponse]
$creadList :: ReadS [CreateCallAnalyticsCategoryResponse]
readsPrec :: Int -> ReadS CreateCallAnalyticsCategoryResponse
$creadsPrec :: Int -> ReadS CreateCallAnalyticsCategoryResponse
Prelude.Read, Int -> CreateCallAnalyticsCategoryResponse -> ShowS
[CreateCallAnalyticsCategoryResponse] -> ShowS
CreateCallAnalyticsCategoryResponse -> String
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [CreateCallAnalyticsCategoryResponse] -> ShowS
$cshowList :: [CreateCallAnalyticsCategoryResponse] -> ShowS
show :: CreateCallAnalyticsCategoryResponse -> String
$cshow :: CreateCallAnalyticsCategoryResponse -> String
showsPrec :: Int -> CreateCallAnalyticsCategoryResponse -> ShowS
$cshowsPrec :: Int -> CreateCallAnalyticsCategoryResponse -> ShowS
Prelude.Show, forall x.
Rep CreateCallAnalyticsCategoryResponse x
-> CreateCallAnalyticsCategoryResponse
forall x.
CreateCallAnalyticsCategoryResponse
-> Rep CreateCallAnalyticsCategoryResponse x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cto :: forall x.
Rep CreateCallAnalyticsCategoryResponse x
-> CreateCallAnalyticsCategoryResponse
$cfrom :: forall x.
CreateCallAnalyticsCategoryResponse
-> Rep CreateCallAnalyticsCategoryResponse x
Prelude.Generic)

-- |
-- Create a value of 'CreateCallAnalyticsCategoryResponse' 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:
--
-- 'categoryProperties', 'createCallAnalyticsCategoryResponse_categoryProperties' - Provides you with the properties of your new category, including its
-- associated rules.
--
-- 'httpStatus', 'createCallAnalyticsCategoryResponse_httpStatus' - The response's http status code.
newCreateCallAnalyticsCategoryResponse ::
  -- | 'httpStatus'
  Prelude.Int ->
  CreateCallAnalyticsCategoryResponse
newCreateCallAnalyticsCategoryResponse :: Int -> CreateCallAnalyticsCategoryResponse
newCreateCallAnalyticsCategoryResponse Int
pHttpStatus_ =
  CreateCallAnalyticsCategoryResponse'
    { $sel:categoryProperties:CreateCallAnalyticsCategoryResponse' :: Maybe CategoryProperties
categoryProperties =
        forall a. Maybe a
Prelude.Nothing,
      $sel:httpStatus:CreateCallAnalyticsCategoryResponse' :: Int
httpStatus = Int
pHttpStatus_
    }

-- | Provides you with the properties of your new category, including its
-- associated rules.
createCallAnalyticsCategoryResponse_categoryProperties :: Lens.Lens' CreateCallAnalyticsCategoryResponse (Prelude.Maybe CategoryProperties)
createCallAnalyticsCategoryResponse_categoryProperties :: Lens'
  CreateCallAnalyticsCategoryResponse (Maybe CategoryProperties)
createCallAnalyticsCategoryResponse_categoryProperties = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\CreateCallAnalyticsCategoryResponse' {Maybe CategoryProperties
categoryProperties :: Maybe CategoryProperties
$sel:categoryProperties:CreateCallAnalyticsCategoryResponse' :: CreateCallAnalyticsCategoryResponse -> Maybe CategoryProperties
categoryProperties} -> Maybe CategoryProperties
categoryProperties) (\s :: CreateCallAnalyticsCategoryResponse
s@CreateCallAnalyticsCategoryResponse' {} Maybe CategoryProperties
a -> CreateCallAnalyticsCategoryResponse
s {$sel:categoryProperties:CreateCallAnalyticsCategoryResponse' :: Maybe CategoryProperties
categoryProperties = Maybe CategoryProperties
a} :: CreateCallAnalyticsCategoryResponse)

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

instance
  Prelude.NFData
    CreateCallAnalyticsCategoryResponse
  where
  rnf :: CreateCallAnalyticsCategoryResponse -> ()
rnf CreateCallAnalyticsCategoryResponse' {Int
Maybe CategoryProperties
httpStatus :: Int
categoryProperties :: Maybe CategoryProperties
$sel:httpStatus:CreateCallAnalyticsCategoryResponse' :: CreateCallAnalyticsCategoryResponse -> Int
$sel:categoryProperties:CreateCallAnalyticsCategoryResponse' :: CreateCallAnalyticsCategoryResponse -> Maybe CategoryProperties
..} =
    forall a. NFData a => a -> ()
Prelude.rnf Maybe CategoryProperties
categoryProperties
      seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf Int
httpStatus