{-# 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.UpdateCallAnalyticsCategory
-- Copyright   : (c) 2013-2023 Brendan Hay
-- License     : Mozilla Public License, v. 2.0.
-- Maintainer  : Brendan Hay
-- Stability   : auto-generated
-- Portability : non-portable (GHC extensions)
--
-- Updates the specified Call Analytics category with new rules. Note that
-- the @UpdateCallAnalyticsCategory@ operation overwrites all existing
-- rules contained in the specified category. You cannot append additional
-- rules onto an existing category.
--
-- To create a new category, see .
module Amazonka.Transcribe.UpdateCallAnalyticsCategory
  ( -- * Creating a Request
    UpdateCallAnalyticsCategory (..),
    newUpdateCallAnalyticsCategory,

    -- * Request Lenses
    updateCallAnalyticsCategory_inputType,
    updateCallAnalyticsCategory_categoryName,
    updateCallAnalyticsCategory_rules,

    -- * Destructuring the Response
    UpdateCallAnalyticsCategoryResponse (..),
    newUpdateCallAnalyticsCategoryResponse,

    -- * Response Lenses
    updateCallAnalyticsCategoryResponse_categoryProperties,
    updateCallAnalyticsCategoryResponse_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:/ 'newUpdateCallAnalyticsCategory' smart constructor.
data UpdateCallAnalyticsCategory = UpdateCallAnalyticsCategory'
  { -- | Choose whether you want to update a streaming or a batch Call Analytics
    -- category. The input type you specify must match the input type specified
    -- when the category was created. For example, if you created a category
    -- with the @POST_CALL@ input type, you must use @POST_CALL@ as the input
    -- type when updating this category.
    UpdateCallAnalyticsCategory -> Maybe InputType
inputType :: Prelude.Maybe InputType,
    -- | The name of the Call Analytics category you want to update. Category
    -- names are case sensitive.
    UpdateCallAnalyticsCategory -> Text
categoryName :: Prelude.Text,
    -- | The rules used for the updated Call Analytics category. The rules you
    -- provide in this field replace the ones that are currently being used in
    -- the specified category.
    UpdateCallAnalyticsCategory -> NonEmpty Rule
rules :: Prelude.NonEmpty Rule
  }
  deriving (UpdateCallAnalyticsCategory -> UpdateCallAnalyticsCategory -> Bool
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: UpdateCallAnalyticsCategory -> UpdateCallAnalyticsCategory -> Bool
$c/= :: UpdateCallAnalyticsCategory -> UpdateCallAnalyticsCategory -> Bool
== :: UpdateCallAnalyticsCategory -> UpdateCallAnalyticsCategory -> Bool
$c== :: UpdateCallAnalyticsCategory -> UpdateCallAnalyticsCategory -> Bool
Prelude.Eq, ReadPrec [UpdateCallAnalyticsCategory]
ReadPrec UpdateCallAnalyticsCategory
Int -> ReadS UpdateCallAnalyticsCategory
ReadS [UpdateCallAnalyticsCategory]
forall a.
(Int -> ReadS a)
-> ReadS [a] -> ReadPrec a -> ReadPrec [a] -> Read a
readListPrec :: ReadPrec [UpdateCallAnalyticsCategory]
$creadListPrec :: ReadPrec [UpdateCallAnalyticsCategory]
readPrec :: ReadPrec UpdateCallAnalyticsCategory
$creadPrec :: ReadPrec UpdateCallAnalyticsCategory
readList :: ReadS [UpdateCallAnalyticsCategory]
$creadList :: ReadS [UpdateCallAnalyticsCategory]
readsPrec :: Int -> ReadS UpdateCallAnalyticsCategory
$creadsPrec :: Int -> ReadS UpdateCallAnalyticsCategory
Prelude.Read, Int -> UpdateCallAnalyticsCategory -> ShowS
[UpdateCallAnalyticsCategory] -> ShowS
UpdateCallAnalyticsCategory -> String
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [UpdateCallAnalyticsCategory] -> ShowS
$cshowList :: [UpdateCallAnalyticsCategory] -> ShowS
show :: UpdateCallAnalyticsCategory -> String
$cshow :: UpdateCallAnalyticsCategory -> String
showsPrec :: Int -> UpdateCallAnalyticsCategory -> ShowS
$cshowsPrec :: Int -> UpdateCallAnalyticsCategory -> ShowS
Prelude.Show, forall x.
Rep UpdateCallAnalyticsCategory x -> UpdateCallAnalyticsCategory
forall x.
UpdateCallAnalyticsCategory -> Rep UpdateCallAnalyticsCategory x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cto :: forall x.
Rep UpdateCallAnalyticsCategory x -> UpdateCallAnalyticsCategory
$cfrom :: forall x.
UpdateCallAnalyticsCategory -> Rep UpdateCallAnalyticsCategory x
Prelude.Generic)

-- |
-- Create a value of 'UpdateCallAnalyticsCategory' 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', 'updateCallAnalyticsCategory_inputType' - Choose whether you want to update a streaming or a batch Call Analytics
-- category. The input type you specify must match the input type specified
-- when the category was created. For example, if you created a category
-- with the @POST_CALL@ input type, you must use @POST_CALL@ as the input
-- type when updating this category.
--
-- 'categoryName', 'updateCallAnalyticsCategory_categoryName' - The name of the Call Analytics category you want to update. Category
-- names are case sensitive.
--
-- 'rules', 'updateCallAnalyticsCategory_rules' - The rules used for the updated Call Analytics category. The rules you
-- provide in this field replace the ones that are currently being used in
-- the specified category.
newUpdateCallAnalyticsCategory ::
  -- | 'categoryName'
  Prelude.Text ->
  -- | 'rules'
  Prelude.NonEmpty Rule ->
  UpdateCallAnalyticsCategory
newUpdateCallAnalyticsCategory :: Text -> NonEmpty Rule -> UpdateCallAnalyticsCategory
newUpdateCallAnalyticsCategory Text
pCategoryName_ NonEmpty Rule
pRules_ =
  UpdateCallAnalyticsCategory'
    { $sel:inputType:UpdateCallAnalyticsCategory' :: Maybe InputType
inputType =
        forall a. Maybe a
Prelude.Nothing,
      $sel:categoryName:UpdateCallAnalyticsCategory' :: Text
categoryName = Text
pCategoryName_,
      $sel:rules:UpdateCallAnalyticsCategory' :: 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 update a streaming or a batch Call Analytics
-- category. The input type you specify must match the input type specified
-- when the category was created. For example, if you created a category
-- with the @POST_CALL@ input type, you must use @POST_CALL@ as the input
-- type when updating this category.
updateCallAnalyticsCategory_inputType :: Lens.Lens' UpdateCallAnalyticsCategory (Prelude.Maybe InputType)
updateCallAnalyticsCategory_inputType :: Lens' UpdateCallAnalyticsCategory (Maybe InputType)
updateCallAnalyticsCategory_inputType = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\UpdateCallAnalyticsCategory' {Maybe InputType
inputType :: Maybe InputType
$sel:inputType:UpdateCallAnalyticsCategory' :: UpdateCallAnalyticsCategory -> Maybe InputType
inputType} -> Maybe InputType
inputType) (\s :: UpdateCallAnalyticsCategory
s@UpdateCallAnalyticsCategory' {} Maybe InputType
a -> UpdateCallAnalyticsCategory
s {$sel:inputType:UpdateCallAnalyticsCategory' :: Maybe InputType
inputType = Maybe InputType
a} :: UpdateCallAnalyticsCategory)

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

-- | The rules used for the updated Call Analytics category. The rules you
-- provide in this field replace the ones that are currently being used in
-- the specified category.
updateCallAnalyticsCategory_rules :: Lens.Lens' UpdateCallAnalyticsCategory (Prelude.NonEmpty Rule)
updateCallAnalyticsCategory_rules :: Lens' UpdateCallAnalyticsCategory (NonEmpty Rule)
updateCallAnalyticsCategory_rules = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\UpdateCallAnalyticsCategory' {NonEmpty Rule
rules :: NonEmpty Rule
$sel:rules:UpdateCallAnalyticsCategory' :: UpdateCallAnalyticsCategory -> NonEmpty Rule
rules} -> NonEmpty Rule
rules) (\s :: UpdateCallAnalyticsCategory
s@UpdateCallAnalyticsCategory' {} NonEmpty Rule
a -> UpdateCallAnalyticsCategory
s {$sel:rules:UpdateCallAnalyticsCategory' :: NonEmpty Rule
rules = NonEmpty Rule
a} :: UpdateCallAnalyticsCategory) 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 UpdateCallAnalyticsCategory where
  type
    AWSResponse UpdateCallAnalyticsCategory =
      UpdateCallAnalyticsCategoryResponse
  request :: (Service -> Service)
-> UpdateCallAnalyticsCategory
-> Request UpdateCallAnalyticsCategory
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 UpdateCallAnalyticsCategory
-> ClientResponse ClientBody
-> m (Either
        Error (ClientResponse (AWSResponse UpdateCallAnalyticsCategory)))
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 -> UpdateCallAnalyticsCategoryResponse
UpdateCallAnalyticsCategoryResponse'
            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 UpdateCallAnalyticsCategory where
  hashWithSalt :: Int -> UpdateCallAnalyticsCategory -> Int
hashWithSalt Int
_salt UpdateCallAnalyticsCategory' {Maybe InputType
NonEmpty Rule
Text
rules :: NonEmpty Rule
categoryName :: Text
inputType :: Maybe InputType
$sel:rules:UpdateCallAnalyticsCategory' :: UpdateCallAnalyticsCategory -> NonEmpty Rule
$sel:categoryName:UpdateCallAnalyticsCategory' :: UpdateCallAnalyticsCategory -> Text
$sel:inputType:UpdateCallAnalyticsCategory' :: UpdateCallAnalyticsCategory -> 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 UpdateCallAnalyticsCategory where
  rnf :: UpdateCallAnalyticsCategory -> ()
rnf UpdateCallAnalyticsCategory' {Maybe InputType
NonEmpty Rule
Text
rules :: NonEmpty Rule
categoryName :: Text
inputType :: Maybe InputType
$sel:rules:UpdateCallAnalyticsCategory' :: UpdateCallAnalyticsCategory -> NonEmpty Rule
$sel:categoryName:UpdateCallAnalyticsCategory' :: UpdateCallAnalyticsCategory -> Text
$sel:inputType:UpdateCallAnalyticsCategory' :: UpdateCallAnalyticsCategory -> 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 UpdateCallAnalyticsCategory where
  toHeaders :: UpdateCallAnalyticsCategory -> 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.UpdateCallAnalyticsCategory" ::
                          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 UpdateCallAnalyticsCategory where
  toJSON :: UpdateCallAnalyticsCategory -> Value
toJSON UpdateCallAnalyticsCategory' {Maybe InputType
NonEmpty Rule
Text
rules :: NonEmpty Rule
categoryName :: Text
inputType :: Maybe InputType
$sel:rules:UpdateCallAnalyticsCategory' :: UpdateCallAnalyticsCategory -> NonEmpty Rule
$sel:categoryName:UpdateCallAnalyticsCategory' :: UpdateCallAnalyticsCategory -> Text
$sel:inputType:UpdateCallAnalyticsCategory' :: UpdateCallAnalyticsCategory -> 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 UpdateCallAnalyticsCategory where
  toPath :: UpdateCallAnalyticsCategory -> ByteString
toPath = forall a b. a -> b -> a
Prelude.const ByteString
"/"

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

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

-- |
-- Create a value of 'UpdateCallAnalyticsCategoryResponse' 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', 'updateCallAnalyticsCategoryResponse_categoryProperties' - Provides you with the properties of the Call Analytics category you
-- specified in your @UpdateCallAnalyticsCategory@ request.
--
-- 'httpStatus', 'updateCallAnalyticsCategoryResponse_httpStatus' - The response's http status code.
newUpdateCallAnalyticsCategoryResponse ::
  -- | 'httpStatus'
  Prelude.Int ->
  UpdateCallAnalyticsCategoryResponse
newUpdateCallAnalyticsCategoryResponse :: Int -> UpdateCallAnalyticsCategoryResponse
newUpdateCallAnalyticsCategoryResponse Int
pHttpStatus_ =
  UpdateCallAnalyticsCategoryResponse'
    { $sel:categoryProperties:UpdateCallAnalyticsCategoryResponse' :: Maybe CategoryProperties
categoryProperties =
        forall a. Maybe a
Prelude.Nothing,
      $sel:httpStatus:UpdateCallAnalyticsCategoryResponse' :: Int
httpStatus = Int
pHttpStatus_
    }

-- | Provides you with the properties of the Call Analytics category you
-- specified in your @UpdateCallAnalyticsCategory@ request.
updateCallAnalyticsCategoryResponse_categoryProperties :: Lens.Lens' UpdateCallAnalyticsCategoryResponse (Prelude.Maybe CategoryProperties)
updateCallAnalyticsCategoryResponse_categoryProperties :: Lens'
  UpdateCallAnalyticsCategoryResponse (Maybe CategoryProperties)
updateCallAnalyticsCategoryResponse_categoryProperties = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\UpdateCallAnalyticsCategoryResponse' {Maybe CategoryProperties
categoryProperties :: Maybe CategoryProperties
$sel:categoryProperties:UpdateCallAnalyticsCategoryResponse' :: UpdateCallAnalyticsCategoryResponse -> Maybe CategoryProperties
categoryProperties} -> Maybe CategoryProperties
categoryProperties) (\s :: UpdateCallAnalyticsCategoryResponse
s@UpdateCallAnalyticsCategoryResponse' {} Maybe CategoryProperties
a -> UpdateCallAnalyticsCategoryResponse
s {$sel:categoryProperties:UpdateCallAnalyticsCategoryResponse' :: Maybe CategoryProperties
categoryProperties = Maybe CategoryProperties
a} :: UpdateCallAnalyticsCategoryResponse)

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

instance
  Prelude.NFData
    UpdateCallAnalyticsCategoryResponse
  where
  rnf :: UpdateCallAnalyticsCategoryResponse -> ()
rnf UpdateCallAnalyticsCategoryResponse' {Int
Maybe CategoryProperties
httpStatus :: Int
categoryProperties :: Maybe CategoryProperties
$sel:httpStatus:UpdateCallAnalyticsCategoryResponse' :: UpdateCallAnalyticsCategoryResponse -> Int
$sel:categoryProperties:UpdateCallAnalyticsCategoryResponse' :: UpdateCallAnalyticsCategoryResponse -> 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