{-# 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.OpenSearchServerless.UpdateSecurityConfig
-- 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 a security configuration for OpenSearch Serverless. For more
-- information, see
-- <https://docs.aws.amazon.com/opensearch-service/latest/developerguide/serverless-saml.html SAML authentication for Amazon OpenSearch Serverless>.
module Amazonka.OpenSearchServerless.UpdateSecurityConfig
  ( -- * Creating a Request
    UpdateSecurityConfig (..),
    newUpdateSecurityConfig,

    -- * Request Lenses
    updateSecurityConfig_clientToken,
    updateSecurityConfig_description,
    updateSecurityConfig_samlOptions,
    updateSecurityConfig_configVersion,
    updateSecurityConfig_id,

    -- * Destructuring the Response
    UpdateSecurityConfigResponse (..),
    newUpdateSecurityConfigResponse,

    -- * Response Lenses
    updateSecurityConfigResponse_securityConfigDetail,
    updateSecurityConfigResponse_httpStatus,
  )
where

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

-- | /See:/ 'newUpdateSecurityConfig' smart constructor.
data UpdateSecurityConfig = UpdateSecurityConfig'
  { -- | Unique, case-sensitive identifier to ensure idempotency of the request.
    UpdateSecurityConfig -> Maybe Text
clientToken :: Prelude.Maybe Prelude.Text,
    -- | A description of the security configuration.
    UpdateSecurityConfig -> Maybe Text
description :: Prelude.Maybe Prelude.Text,
    -- | SAML options in in the form of a key-value map.
    UpdateSecurityConfig -> Maybe SamlConfigOptions
samlOptions :: Prelude.Maybe SamlConfigOptions,
    -- | The version of the security configuration to be updated. You can find
    -- the most recent version of a security configuration using the
    -- @GetSecurityPolicy@ command.
    UpdateSecurityConfig -> Text
configVersion :: Prelude.Text,
    -- | The security configuration identifier. For SAML the ID will be
    -- @saml\/\<accountId>\/\<idpProviderName>@. For example,
    -- @saml\/123456789123\/OKTADev@.
    UpdateSecurityConfig -> Text
id :: Prelude.Text
  }
  deriving (UpdateSecurityConfig -> UpdateSecurityConfig -> Bool
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: UpdateSecurityConfig -> UpdateSecurityConfig -> Bool
$c/= :: UpdateSecurityConfig -> UpdateSecurityConfig -> Bool
== :: UpdateSecurityConfig -> UpdateSecurityConfig -> Bool
$c== :: UpdateSecurityConfig -> UpdateSecurityConfig -> Bool
Prelude.Eq, ReadPrec [UpdateSecurityConfig]
ReadPrec UpdateSecurityConfig
Int -> ReadS UpdateSecurityConfig
ReadS [UpdateSecurityConfig]
forall a.
(Int -> ReadS a)
-> ReadS [a] -> ReadPrec a -> ReadPrec [a] -> Read a
readListPrec :: ReadPrec [UpdateSecurityConfig]
$creadListPrec :: ReadPrec [UpdateSecurityConfig]
readPrec :: ReadPrec UpdateSecurityConfig
$creadPrec :: ReadPrec UpdateSecurityConfig
readList :: ReadS [UpdateSecurityConfig]
$creadList :: ReadS [UpdateSecurityConfig]
readsPrec :: Int -> ReadS UpdateSecurityConfig
$creadsPrec :: Int -> ReadS UpdateSecurityConfig
Prelude.Read, Int -> UpdateSecurityConfig -> ShowS
[UpdateSecurityConfig] -> ShowS
UpdateSecurityConfig -> String
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [UpdateSecurityConfig] -> ShowS
$cshowList :: [UpdateSecurityConfig] -> ShowS
show :: UpdateSecurityConfig -> String
$cshow :: UpdateSecurityConfig -> String
showsPrec :: Int -> UpdateSecurityConfig -> ShowS
$cshowsPrec :: Int -> UpdateSecurityConfig -> ShowS
Prelude.Show, forall x. Rep UpdateSecurityConfig x -> UpdateSecurityConfig
forall x. UpdateSecurityConfig -> Rep UpdateSecurityConfig x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cto :: forall x. Rep UpdateSecurityConfig x -> UpdateSecurityConfig
$cfrom :: forall x. UpdateSecurityConfig -> Rep UpdateSecurityConfig x
Prelude.Generic)

-- |
-- Create a value of 'UpdateSecurityConfig' 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:
--
-- 'clientToken', 'updateSecurityConfig_clientToken' - Unique, case-sensitive identifier to ensure idempotency of the request.
--
-- 'description', 'updateSecurityConfig_description' - A description of the security configuration.
--
-- 'samlOptions', 'updateSecurityConfig_samlOptions' - SAML options in in the form of a key-value map.
--
-- 'configVersion', 'updateSecurityConfig_configVersion' - The version of the security configuration to be updated. You can find
-- the most recent version of a security configuration using the
-- @GetSecurityPolicy@ command.
--
-- 'id', 'updateSecurityConfig_id' - The security configuration identifier. For SAML the ID will be
-- @saml\/\<accountId>\/\<idpProviderName>@. For example,
-- @saml\/123456789123\/OKTADev@.
newUpdateSecurityConfig ::
  -- | 'configVersion'
  Prelude.Text ->
  -- | 'id'
  Prelude.Text ->
  UpdateSecurityConfig
newUpdateSecurityConfig :: Text -> Text -> UpdateSecurityConfig
newUpdateSecurityConfig Text
pConfigVersion_ Text
pId_ =
  UpdateSecurityConfig'
    { $sel:clientToken:UpdateSecurityConfig' :: Maybe Text
clientToken =
        forall a. Maybe a
Prelude.Nothing,
      $sel:description:UpdateSecurityConfig' :: Maybe Text
description = forall a. Maybe a
Prelude.Nothing,
      $sel:samlOptions:UpdateSecurityConfig' :: Maybe SamlConfigOptions
samlOptions = forall a. Maybe a
Prelude.Nothing,
      $sel:configVersion:UpdateSecurityConfig' :: Text
configVersion = Text
pConfigVersion_,
      $sel:id:UpdateSecurityConfig' :: Text
id = Text
pId_
    }

-- | Unique, case-sensitive identifier to ensure idempotency of the request.
updateSecurityConfig_clientToken :: Lens.Lens' UpdateSecurityConfig (Prelude.Maybe Prelude.Text)
updateSecurityConfig_clientToken :: Lens' UpdateSecurityConfig (Maybe Text)
updateSecurityConfig_clientToken = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\UpdateSecurityConfig' {Maybe Text
clientToken :: Maybe Text
$sel:clientToken:UpdateSecurityConfig' :: UpdateSecurityConfig -> Maybe Text
clientToken} -> Maybe Text
clientToken) (\s :: UpdateSecurityConfig
s@UpdateSecurityConfig' {} Maybe Text
a -> UpdateSecurityConfig
s {$sel:clientToken:UpdateSecurityConfig' :: Maybe Text
clientToken = Maybe Text
a} :: UpdateSecurityConfig)

-- | A description of the security configuration.
updateSecurityConfig_description :: Lens.Lens' UpdateSecurityConfig (Prelude.Maybe Prelude.Text)
updateSecurityConfig_description :: Lens' UpdateSecurityConfig (Maybe Text)
updateSecurityConfig_description = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\UpdateSecurityConfig' {Maybe Text
description :: Maybe Text
$sel:description:UpdateSecurityConfig' :: UpdateSecurityConfig -> Maybe Text
description} -> Maybe Text
description) (\s :: UpdateSecurityConfig
s@UpdateSecurityConfig' {} Maybe Text
a -> UpdateSecurityConfig
s {$sel:description:UpdateSecurityConfig' :: Maybe Text
description = Maybe Text
a} :: UpdateSecurityConfig)

-- | SAML options in in the form of a key-value map.
updateSecurityConfig_samlOptions :: Lens.Lens' UpdateSecurityConfig (Prelude.Maybe SamlConfigOptions)
updateSecurityConfig_samlOptions :: Lens' UpdateSecurityConfig (Maybe SamlConfigOptions)
updateSecurityConfig_samlOptions = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\UpdateSecurityConfig' {Maybe SamlConfigOptions
samlOptions :: Maybe SamlConfigOptions
$sel:samlOptions:UpdateSecurityConfig' :: UpdateSecurityConfig -> Maybe SamlConfigOptions
samlOptions} -> Maybe SamlConfigOptions
samlOptions) (\s :: UpdateSecurityConfig
s@UpdateSecurityConfig' {} Maybe SamlConfigOptions
a -> UpdateSecurityConfig
s {$sel:samlOptions:UpdateSecurityConfig' :: Maybe SamlConfigOptions
samlOptions = Maybe SamlConfigOptions
a} :: UpdateSecurityConfig)

-- | The version of the security configuration to be updated. You can find
-- the most recent version of a security configuration using the
-- @GetSecurityPolicy@ command.
updateSecurityConfig_configVersion :: Lens.Lens' UpdateSecurityConfig Prelude.Text
updateSecurityConfig_configVersion :: Lens' UpdateSecurityConfig Text
updateSecurityConfig_configVersion = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\UpdateSecurityConfig' {Text
configVersion :: Text
$sel:configVersion:UpdateSecurityConfig' :: UpdateSecurityConfig -> Text
configVersion} -> Text
configVersion) (\s :: UpdateSecurityConfig
s@UpdateSecurityConfig' {} Text
a -> UpdateSecurityConfig
s {$sel:configVersion:UpdateSecurityConfig' :: Text
configVersion = Text
a} :: UpdateSecurityConfig)

-- | The security configuration identifier. For SAML the ID will be
-- @saml\/\<accountId>\/\<idpProviderName>@. For example,
-- @saml\/123456789123\/OKTADev@.
updateSecurityConfig_id :: Lens.Lens' UpdateSecurityConfig Prelude.Text
updateSecurityConfig_id :: Lens' UpdateSecurityConfig Text
updateSecurityConfig_id = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\UpdateSecurityConfig' {Text
id :: Text
$sel:id:UpdateSecurityConfig' :: UpdateSecurityConfig -> Text
id} -> Text
id) (\s :: UpdateSecurityConfig
s@UpdateSecurityConfig' {} Text
a -> UpdateSecurityConfig
s {$sel:id:UpdateSecurityConfig' :: Text
id = Text
a} :: UpdateSecurityConfig)

instance Core.AWSRequest UpdateSecurityConfig where
  type
    AWSResponse UpdateSecurityConfig =
      UpdateSecurityConfigResponse
  request :: (Service -> Service)
-> UpdateSecurityConfig -> Request UpdateSecurityConfig
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 UpdateSecurityConfig
-> ClientResponse ClientBody
-> m (Either
        Error (ClientResponse (AWSResponse UpdateSecurityConfig)))
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 SecurityConfigDetail -> Int -> UpdateSecurityConfigResponse
UpdateSecurityConfigResponse'
            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
"securityConfigDetail")
            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 UpdateSecurityConfig where
  hashWithSalt :: Int -> UpdateSecurityConfig -> Int
hashWithSalt Int
_salt UpdateSecurityConfig' {Maybe Text
Maybe SamlConfigOptions
Text
id :: Text
configVersion :: Text
samlOptions :: Maybe SamlConfigOptions
description :: Maybe Text
clientToken :: Maybe Text
$sel:id:UpdateSecurityConfig' :: UpdateSecurityConfig -> Text
$sel:configVersion:UpdateSecurityConfig' :: UpdateSecurityConfig -> Text
$sel:samlOptions:UpdateSecurityConfig' :: UpdateSecurityConfig -> Maybe SamlConfigOptions
$sel:description:UpdateSecurityConfig' :: UpdateSecurityConfig -> Maybe Text
$sel:clientToken:UpdateSecurityConfig' :: UpdateSecurityConfig -> Maybe Text
..} =
    Int
_salt
      forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Maybe Text
clientToken
      forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Maybe Text
description
      forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Maybe SamlConfigOptions
samlOptions
      forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Text
configVersion
      forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Text
id

instance Prelude.NFData UpdateSecurityConfig where
  rnf :: UpdateSecurityConfig -> ()
rnf UpdateSecurityConfig' {Maybe Text
Maybe SamlConfigOptions
Text
id :: Text
configVersion :: Text
samlOptions :: Maybe SamlConfigOptions
description :: Maybe Text
clientToken :: Maybe Text
$sel:id:UpdateSecurityConfig' :: UpdateSecurityConfig -> Text
$sel:configVersion:UpdateSecurityConfig' :: UpdateSecurityConfig -> Text
$sel:samlOptions:UpdateSecurityConfig' :: UpdateSecurityConfig -> Maybe SamlConfigOptions
$sel:description:UpdateSecurityConfig' :: UpdateSecurityConfig -> Maybe Text
$sel:clientToken:UpdateSecurityConfig' :: UpdateSecurityConfig -> Maybe Text
..} =
    forall a. NFData a => a -> ()
Prelude.rnf Maybe Text
clientToken
      seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf Maybe Text
description
      seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf Maybe SamlConfigOptions
samlOptions
      seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf Text
configVersion
      seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf Text
id

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

instance Data.ToJSON UpdateSecurityConfig where
  toJSON :: UpdateSecurityConfig -> Value
toJSON UpdateSecurityConfig' {Maybe Text
Maybe SamlConfigOptions
Text
id :: Text
configVersion :: Text
samlOptions :: Maybe SamlConfigOptions
description :: Maybe Text
clientToken :: Maybe Text
$sel:id:UpdateSecurityConfig' :: UpdateSecurityConfig -> Text
$sel:configVersion:UpdateSecurityConfig' :: UpdateSecurityConfig -> Text
$sel:samlOptions:UpdateSecurityConfig' :: UpdateSecurityConfig -> Maybe SamlConfigOptions
$sel:description:UpdateSecurityConfig' :: UpdateSecurityConfig -> Maybe Text
$sel:clientToken:UpdateSecurityConfig' :: UpdateSecurityConfig -> Maybe Text
..} =
    [Pair] -> Value
Data.object
      ( forall a. [Maybe a] -> [a]
Prelude.catMaybes
          [ (Key
"clientToken" 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 Text
clientToken,
            (Key
"description" 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 Text
description,
            (Key
"samlOptions" 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 SamlConfigOptions
samlOptions,
            forall a. a -> Maybe a
Prelude.Just (Key
"configVersion" forall kv v. (KeyValue kv, ToJSON v) => Key -> v -> kv
Data..= Text
configVersion),
            forall a. a -> Maybe a
Prelude.Just (Key
"id" forall kv v. (KeyValue kv, ToJSON v) => Key -> v -> kv
Data..= Text
id)
          ]
      )

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

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

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

-- |
-- Create a value of 'UpdateSecurityConfigResponse' 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:
--
-- 'securityConfigDetail', 'updateSecurityConfigResponse_securityConfigDetail' - Details about the updated security configuration.
--
-- 'httpStatus', 'updateSecurityConfigResponse_httpStatus' - The response's http status code.
newUpdateSecurityConfigResponse ::
  -- | 'httpStatus'
  Prelude.Int ->
  UpdateSecurityConfigResponse
newUpdateSecurityConfigResponse :: Int -> UpdateSecurityConfigResponse
newUpdateSecurityConfigResponse Int
pHttpStatus_ =
  UpdateSecurityConfigResponse'
    { $sel:securityConfigDetail:UpdateSecurityConfigResponse' :: Maybe SecurityConfigDetail
securityConfigDetail =
        forall a. Maybe a
Prelude.Nothing,
      $sel:httpStatus:UpdateSecurityConfigResponse' :: Int
httpStatus = Int
pHttpStatus_
    }

-- | Details about the updated security configuration.
updateSecurityConfigResponse_securityConfigDetail :: Lens.Lens' UpdateSecurityConfigResponse (Prelude.Maybe SecurityConfigDetail)
updateSecurityConfigResponse_securityConfigDetail :: Lens' UpdateSecurityConfigResponse (Maybe SecurityConfigDetail)
updateSecurityConfigResponse_securityConfigDetail = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\UpdateSecurityConfigResponse' {Maybe SecurityConfigDetail
securityConfigDetail :: Maybe SecurityConfigDetail
$sel:securityConfigDetail:UpdateSecurityConfigResponse' :: UpdateSecurityConfigResponse -> Maybe SecurityConfigDetail
securityConfigDetail} -> Maybe SecurityConfigDetail
securityConfigDetail) (\s :: UpdateSecurityConfigResponse
s@UpdateSecurityConfigResponse' {} Maybe SecurityConfigDetail
a -> UpdateSecurityConfigResponse
s {$sel:securityConfigDetail:UpdateSecurityConfigResponse' :: Maybe SecurityConfigDetail
securityConfigDetail = Maybe SecurityConfigDetail
a} :: UpdateSecurityConfigResponse)

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

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