{-# 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.Kafka.UpdateSecurity
-- 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 security settings for the cluster. You can use this
-- operation to specify encryption and authentication on existing clusters.
module Amazonka.Kafka.UpdateSecurity
  ( -- * Creating a Request
    UpdateSecurity (..),
    newUpdateSecurity,

    -- * Request Lenses
    updateSecurity_clientAuthentication,
    updateSecurity_encryptionInfo,
    updateSecurity_clusterArn,
    updateSecurity_currentVersion,

    -- * Destructuring the Response
    UpdateSecurityResponse (..),
    newUpdateSecurityResponse,

    -- * Response Lenses
    updateSecurityResponse_clusterArn,
    updateSecurityResponse_clusterOperationArn,
    updateSecurityResponse_httpStatus,
  )
where

import qualified Amazonka.Core as Core
import qualified Amazonka.Core.Lens.Internal as Lens
import qualified Amazonka.Data as Data
import Amazonka.Kafka.Types
import qualified Amazonka.Prelude as Prelude
import qualified Amazonka.Request as Request
import qualified Amazonka.Response as Response

-- | /See:/ 'newUpdateSecurity' smart constructor.
data UpdateSecurity = UpdateSecurity'
  { -- | Includes all client authentication related information.
    UpdateSecurity -> Maybe ClientAuthentication
clientAuthentication :: Prelude.Maybe ClientAuthentication,
    -- | Includes all encryption-related information.
    UpdateSecurity -> Maybe EncryptionInfo
encryptionInfo :: Prelude.Maybe EncryptionInfo,
    -- | The Amazon Resource Name (ARN) that uniquely identifies the cluster.
    UpdateSecurity -> Text
clusterArn :: Prelude.Text,
    -- | The version of the MSK cluster to update. Cluster versions aren\'t
    -- simple numbers. You can describe an MSK cluster to find its version.
    -- When this update operation is successful, it generates a new cluster
    -- version.
    UpdateSecurity -> Text
currentVersion :: Prelude.Text
  }
  deriving (UpdateSecurity -> UpdateSecurity -> Bool
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: UpdateSecurity -> UpdateSecurity -> Bool
$c/= :: UpdateSecurity -> UpdateSecurity -> Bool
== :: UpdateSecurity -> UpdateSecurity -> Bool
$c== :: UpdateSecurity -> UpdateSecurity -> Bool
Prelude.Eq, ReadPrec [UpdateSecurity]
ReadPrec UpdateSecurity
Int -> ReadS UpdateSecurity
ReadS [UpdateSecurity]
forall a.
(Int -> ReadS a)
-> ReadS [a] -> ReadPrec a -> ReadPrec [a] -> Read a
readListPrec :: ReadPrec [UpdateSecurity]
$creadListPrec :: ReadPrec [UpdateSecurity]
readPrec :: ReadPrec UpdateSecurity
$creadPrec :: ReadPrec UpdateSecurity
readList :: ReadS [UpdateSecurity]
$creadList :: ReadS [UpdateSecurity]
readsPrec :: Int -> ReadS UpdateSecurity
$creadsPrec :: Int -> ReadS UpdateSecurity
Prelude.Read, Int -> UpdateSecurity -> ShowS
[UpdateSecurity] -> ShowS
UpdateSecurity -> String
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [UpdateSecurity] -> ShowS
$cshowList :: [UpdateSecurity] -> ShowS
show :: UpdateSecurity -> String
$cshow :: UpdateSecurity -> String
showsPrec :: Int -> UpdateSecurity -> ShowS
$cshowsPrec :: Int -> UpdateSecurity -> ShowS
Prelude.Show, forall x. Rep UpdateSecurity x -> UpdateSecurity
forall x. UpdateSecurity -> Rep UpdateSecurity x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cto :: forall x. Rep UpdateSecurity x -> UpdateSecurity
$cfrom :: forall x. UpdateSecurity -> Rep UpdateSecurity x
Prelude.Generic)

-- |
-- Create a value of 'UpdateSecurity' 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:
--
-- 'clientAuthentication', 'updateSecurity_clientAuthentication' - Includes all client authentication related information.
--
-- 'encryptionInfo', 'updateSecurity_encryptionInfo' - Includes all encryption-related information.
--
-- 'clusterArn', 'updateSecurity_clusterArn' - The Amazon Resource Name (ARN) that uniquely identifies the cluster.
--
-- 'currentVersion', 'updateSecurity_currentVersion' - The version of the MSK cluster to update. Cluster versions aren\'t
-- simple numbers. You can describe an MSK cluster to find its version.
-- When this update operation is successful, it generates a new cluster
-- version.
newUpdateSecurity ::
  -- | 'clusterArn'
  Prelude.Text ->
  -- | 'currentVersion'
  Prelude.Text ->
  UpdateSecurity
newUpdateSecurity :: Text -> Text -> UpdateSecurity
newUpdateSecurity Text
pClusterArn_ Text
pCurrentVersion_ =
  UpdateSecurity'
    { $sel:clientAuthentication:UpdateSecurity' :: Maybe ClientAuthentication
clientAuthentication =
        forall a. Maybe a
Prelude.Nothing,
      $sel:encryptionInfo:UpdateSecurity' :: Maybe EncryptionInfo
encryptionInfo = forall a. Maybe a
Prelude.Nothing,
      $sel:clusterArn:UpdateSecurity' :: Text
clusterArn = Text
pClusterArn_,
      $sel:currentVersion:UpdateSecurity' :: Text
currentVersion = Text
pCurrentVersion_
    }

-- | Includes all client authentication related information.
updateSecurity_clientAuthentication :: Lens.Lens' UpdateSecurity (Prelude.Maybe ClientAuthentication)
updateSecurity_clientAuthentication :: Lens' UpdateSecurity (Maybe ClientAuthentication)
updateSecurity_clientAuthentication = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\UpdateSecurity' {Maybe ClientAuthentication
clientAuthentication :: Maybe ClientAuthentication
$sel:clientAuthentication:UpdateSecurity' :: UpdateSecurity -> Maybe ClientAuthentication
clientAuthentication} -> Maybe ClientAuthentication
clientAuthentication) (\s :: UpdateSecurity
s@UpdateSecurity' {} Maybe ClientAuthentication
a -> UpdateSecurity
s {$sel:clientAuthentication:UpdateSecurity' :: Maybe ClientAuthentication
clientAuthentication = Maybe ClientAuthentication
a} :: UpdateSecurity)

-- | Includes all encryption-related information.
updateSecurity_encryptionInfo :: Lens.Lens' UpdateSecurity (Prelude.Maybe EncryptionInfo)
updateSecurity_encryptionInfo :: Lens' UpdateSecurity (Maybe EncryptionInfo)
updateSecurity_encryptionInfo = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\UpdateSecurity' {Maybe EncryptionInfo
encryptionInfo :: Maybe EncryptionInfo
$sel:encryptionInfo:UpdateSecurity' :: UpdateSecurity -> Maybe EncryptionInfo
encryptionInfo} -> Maybe EncryptionInfo
encryptionInfo) (\s :: UpdateSecurity
s@UpdateSecurity' {} Maybe EncryptionInfo
a -> UpdateSecurity
s {$sel:encryptionInfo:UpdateSecurity' :: Maybe EncryptionInfo
encryptionInfo = Maybe EncryptionInfo
a} :: UpdateSecurity)

-- | The Amazon Resource Name (ARN) that uniquely identifies the cluster.
updateSecurity_clusterArn :: Lens.Lens' UpdateSecurity Prelude.Text
updateSecurity_clusterArn :: Lens' UpdateSecurity Text
updateSecurity_clusterArn = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\UpdateSecurity' {Text
clusterArn :: Text
$sel:clusterArn:UpdateSecurity' :: UpdateSecurity -> Text
clusterArn} -> Text
clusterArn) (\s :: UpdateSecurity
s@UpdateSecurity' {} Text
a -> UpdateSecurity
s {$sel:clusterArn:UpdateSecurity' :: Text
clusterArn = Text
a} :: UpdateSecurity)

-- | The version of the MSK cluster to update. Cluster versions aren\'t
-- simple numbers. You can describe an MSK cluster to find its version.
-- When this update operation is successful, it generates a new cluster
-- version.
updateSecurity_currentVersion :: Lens.Lens' UpdateSecurity Prelude.Text
updateSecurity_currentVersion :: Lens' UpdateSecurity Text
updateSecurity_currentVersion = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\UpdateSecurity' {Text
currentVersion :: Text
$sel:currentVersion:UpdateSecurity' :: UpdateSecurity -> Text
currentVersion} -> Text
currentVersion) (\s :: UpdateSecurity
s@UpdateSecurity' {} Text
a -> UpdateSecurity
s {$sel:currentVersion:UpdateSecurity' :: Text
currentVersion = Text
a} :: UpdateSecurity)

instance Core.AWSRequest UpdateSecurity where
  type
    AWSResponse UpdateSecurity =
      UpdateSecurityResponse
  request :: (Service -> Service) -> UpdateSecurity -> Request UpdateSecurity
request Service -> Service
overrides =
    forall a. (ToRequest a, ToJSON a) => Service -> a -> Request a
Request.patchJSON (Service -> Service
overrides Service
defaultService)
  response :: forall (m :: * -> *).
MonadResource m =>
(ByteStringLazy -> IO ByteStringLazy)
-> Service
-> Proxy UpdateSecurity
-> ClientResponse ClientBody
-> m (Either Error (ClientResponse (AWSResponse UpdateSecurity)))
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 Text -> Maybe Text -> Int -> UpdateSecurityResponse
UpdateSecurityResponse'
            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
"clusterArn")
            forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
Prelude.<*> (Object
x forall a. FromJSON a => Object -> Key -> Either String (Maybe a)
Data..?> Key
"clusterOperationArn")
            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 UpdateSecurity where
  hashWithSalt :: Int -> UpdateSecurity -> Int
hashWithSalt Int
_salt UpdateSecurity' {Maybe EncryptionInfo
Maybe ClientAuthentication
Text
currentVersion :: Text
clusterArn :: Text
encryptionInfo :: Maybe EncryptionInfo
clientAuthentication :: Maybe ClientAuthentication
$sel:currentVersion:UpdateSecurity' :: UpdateSecurity -> Text
$sel:clusterArn:UpdateSecurity' :: UpdateSecurity -> Text
$sel:encryptionInfo:UpdateSecurity' :: UpdateSecurity -> Maybe EncryptionInfo
$sel:clientAuthentication:UpdateSecurity' :: UpdateSecurity -> Maybe ClientAuthentication
..} =
    Int
_salt
      forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Maybe ClientAuthentication
clientAuthentication
      forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Maybe EncryptionInfo
encryptionInfo
      forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Text
clusterArn
      forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Text
currentVersion

instance Prelude.NFData UpdateSecurity where
  rnf :: UpdateSecurity -> ()
rnf UpdateSecurity' {Maybe EncryptionInfo
Maybe ClientAuthentication
Text
currentVersion :: Text
clusterArn :: Text
encryptionInfo :: Maybe EncryptionInfo
clientAuthentication :: Maybe ClientAuthentication
$sel:currentVersion:UpdateSecurity' :: UpdateSecurity -> Text
$sel:clusterArn:UpdateSecurity' :: UpdateSecurity -> Text
$sel:encryptionInfo:UpdateSecurity' :: UpdateSecurity -> Maybe EncryptionInfo
$sel:clientAuthentication:UpdateSecurity' :: UpdateSecurity -> Maybe ClientAuthentication
..} =
    forall a. NFData a => a -> ()
Prelude.rnf Maybe ClientAuthentication
clientAuthentication
      seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf Maybe EncryptionInfo
encryptionInfo
      seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf Text
clusterArn
      seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf Text
currentVersion

instance Data.ToHeaders UpdateSecurity where
  toHeaders :: UpdateSecurity -> ResponseHeaders
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 -> ResponseHeaders
Data.=# ( ByteString
"application/x-amz-json-1.1" ::
                          Prelude.ByteString
                      )
          ]
      )

instance Data.ToJSON UpdateSecurity where
  toJSON :: UpdateSecurity -> Value
toJSON UpdateSecurity' {Maybe EncryptionInfo
Maybe ClientAuthentication
Text
currentVersion :: Text
clusterArn :: Text
encryptionInfo :: Maybe EncryptionInfo
clientAuthentication :: Maybe ClientAuthentication
$sel:currentVersion:UpdateSecurity' :: UpdateSecurity -> Text
$sel:clusterArn:UpdateSecurity' :: UpdateSecurity -> Text
$sel:encryptionInfo:UpdateSecurity' :: UpdateSecurity -> Maybe EncryptionInfo
$sel:clientAuthentication:UpdateSecurity' :: UpdateSecurity -> Maybe ClientAuthentication
..} =
    [Pair] -> Value
Data.object
      ( forall a. [Maybe a] -> [a]
Prelude.catMaybes
          [ (Key
"clientAuthentication" 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 ClientAuthentication
clientAuthentication,
            (Key
"encryptionInfo" 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 EncryptionInfo
encryptionInfo,
            forall a. a -> Maybe a
Prelude.Just
              (Key
"currentVersion" forall kv v. (KeyValue kv, ToJSON v) => Key -> v -> kv
Data..= Text
currentVersion)
          ]
      )

instance Data.ToPath UpdateSecurity where
  toPath :: UpdateSecurity -> ByteString
toPath UpdateSecurity' {Maybe EncryptionInfo
Maybe ClientAuthentication
Text
currentVersion :: Text
clusterArn :: Text
encryptionInfo :: Maybe EncryptionInfo
clientAuthentication :: Maybe ClientAuthentication
$sel:currentVersion:UpdateSecurity' :: UpdateSecurity -> Text
$sel:clusterArn:UpdateSecurity' :: UpdateSecurity -> Text
$sel:encryptionInfo:UpdateSecurity' :: UpdateSecurity -> Maybe EncryptionInfo
$sel:clientAuthentication:UpdateSecurity' :: UpdateSecurity -> Maybe ClientAuthentication
..} =
    forall a. Monoid a => [a] -> a
Prelude.mconcat
      [ByteString
"/v1/clusters/", forall a. ToByteString a => a -> ByteString
Data.toBS Text
clusterArn, ByteString
"/security"]

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

-- | /See:/ 'newUpdateSecurityResponse' smart constructor.
data UpdateSecurityResponse = UpdateSecurityResponse'
  { -- | The Amazon Resource Name (ARN) of the cluster.
    UpdateSecurityResponse -> Maybe Text
clusterArn :: Prelude.Maybe Prelude.Text,
    -- | The Amazon Resource Name (ARN) of the cluster operation.
    UpdateSecurityResponse -> Maybe Text
clusterOperationArn :: Prelude.Maybe Prelude.Text,
    -- | The response's http status code.
    UpdateSecurityResponse -> Int
httpStatus :: Prelude.Int
  }
  deriving (UpdateSecurityResponse -> UpdateSecurityResponse -> Bool
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: UpdateSecurityResponse -> UpdateSecurityResponse -> Bool
$c/= :: UpdateSecurityResponse -> UpdateSecurityResponse -> Bool
== :: UpdateSecurityResponse -> UpdateSecurityResponse -> Bool
$c== :: UpdateSecurityResponse -> UpdateSecurityResponse -> Bool
Prelude.Eq, ReadPrec [UpdateSecurityResponse]
ReadPrec UpdateSecurityResponse
Int -> ReadS UpdateSecurityResponse
ReadS [UpdateSecurityResponse]
forall a.
(Int -> ReadS a)
-> ReadS [a] -> ReadPrec a -> ReadPrec [a] -> Read a
readListPrec :: ReadPrec [UpdateSecurityResponse]
$creadListPrec :: ReadPrec [UpdateSecurityResponse]
readPrec :: ReadPrec UpdateSecurityResponse
$creadPrec :: ReadPrec UpdateSecurityResponse
readList :: ReadS [UpdateSecurityResponse]
$creadList :: ReadS [UpdateSecurityResponse]
readsPrec :: Int -> ReadS UpdateSecurityResponse
$creadsPrec :: Int -> ReadS UpdateSecurityResponse
Prelude.Read, Int -> UpdateSecurityResponse -> ShowS
[UpdateSecurityResponse] -> ShowS
UpdateSecurityResponse -> String
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [UpdateSecurityResponse] -> ShowS
$cshowList :: [UpdateSecurityResponse] -> ShowS
show :: UpdateSecurityResponse -> String
$cshow :: UpdateSecurityResponse -> String
showsPrec :: Int -> UpdateSecurityResponse -> ShowS
$cshowsPrec :: Int -> UpdateSecurityResponse -> ShowS
Prelude.Show, forall x. Rep UpdateSecurityResponse x -> UpdateSecurityResponse
forall x. UpdateSecurityResponse -> Rep UpdateSecurityResponse x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cto :: forall x. Rep UpdateSecurityResponse x -> UpdateSecurityResponse
$cfrom :: forall x. UpdateSecurityResponse -> Rep UpdateSecurityResponse x
Prelude.Generic)

-- |
-- Create a value of 'UpdateSecurityResponse' 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:
--
-- 'clusterArn', 'updateSecurityResponse_clusterArn' - The Amazon Resource Name (ARN) of the cluster.
--
-- 'clusterOperationArn', 'updateSecurityResponse_clusterOperationArn' - The Amazon Resource Name (ARN) of the cluster operation.
--
-- 'httpStatus', 'updateSecurityResponse_httpStatus' - The response's http status code.
newUpdateSecurityResponse ::
  -- | 'httpStatus'
  Prelude.Int ->
  UpdateSecurityResponse
newUpdateSecurityResponse :: Int -> UpdateSecurityResponse
newUpdateSecurityResponse Int
pHttpStatus_ =
  UpdateSecurityResponse'
    { $sel:clusterArn:UpdateSecurityResponse' :: Maybe Text
clusterArn =
        forall a. Maybe a
Prelude.Nothing,
      $sel:clusterOperationArn:UpdateSecurityResponse' :: Maybe Text
clusterOperationArn = forall a. Maybe a
Prelude.Nothing,
      $sel:httpStatus:UpdateSecurityResponse' :: Int
httpStatus = Int
pHttpStatus_
    }

-- | The Amazon Resource Name (ARN) of the cluster.
updateSecurityResponse_clusterArn :: Lens.Lens' UpdateSecurityResponse (Prelude.Maybe Prelude.Text)
updateSecurityResponse_clusterArn :: Lens' UpdateSecurityResponse (Maybe Text)
updateSecurityResponse_clusterArn = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\UpdateSecurityResponse' {Maybe Text
clusterArn :: Maybe Text
$sel:clusterArn:UpdateSecurityResponse' :: UpdateSecurityResponse -> Maybe Text
clusterArn} -> Maybe Text
clusterArn) (\s :: UpdateSecurityResponse
s@UpdateSecurityResponse' {} Maybe Text
a -> UpdateSecurityResponse
s {$sel:clusterArn:UpdateSecurityResponse' :: Maybe Text
clusterArn = Maybe Text
a} :: UpdateSecurityResponse)

-- | The Amazon Resource Name (ARN) of the cluster operation.
updateSecurityResponse_clusterOperationArn :: Lens.Lens' UpdateSecurityResponse (Prelude.Maybe Prelude.Text)
updateSecurityResponse_clusterOperationArn :: Lens' UpdateSecurityResponse (Maybe Text)
updateSecurityResponse_clusterOperationArn = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\UpdateSecurityResponse' {Maybe Text
clusterOperationArn :: Maybe Text
$sel:clusterOperationArn:UpdateSecurityResponse' :: UpdateSecurityResponse -> Maybe Text
clusterOperationArn} -> Maybe Text
clusterOperationArn) (\s :: UpdateSecurityResponse
s@UpdateSecurityResponse' {} Maybe Text
a -> UpdateSecurityResponse
s {$sel:clusterOperationArn:UpdateSecurityResponse' :: Maybe Text
clusterOperationArn = Maybe Text
a} :: UpdateSecurityResponse)

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

instance Prelude.NFData UpdateSecurityResponse where
  rnf :: UpdateSecurityResponse -> ()
rnf UpdateSecurityResponse' {Int
Maybe Text
httpStatus :: Int
clusterOperationArn :: Maybe Text
clusterArn :: Maybe Text
$sel:httpStatus:UpdateSecurityResponse' :: UpdateSecurityResponse -> Int
$sel:clusterOperationArn:UpdateSecurityResponse' :: UpdateSecurityResponse -> Maybe Text
$sel:clusterArn:UpdateSecurityResponse' :: UpdateSecurityResponse -> Maybe Text
..} =
    forall a. NFData a => a -> ()
Prelude.rnf Maybe Text
clusterArn
      seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf Maybe Text
clusterOperationArn
      seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf Int
httpStatus