{-# 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.CognitoIdentityProvider.UpdateUserPool
-- 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 user pool with the specified attributes. You can
-- get a list of the current user pool settings using
-- <https://docs.aws.amazon.com/cognito-user-identity-pools/latest/APIReference/API_DescribeUserPool.html DescribeUserPool>.
-- If you don\'t provide a value for an attribute, it will be set to the
-- default value.
--
-- This action might generate an SMS text message. Starting June 1, 2021,
-- US telecom carriers require you to register an origination phone number
-- before you can send SMS messages to US phone numbers. If you use SMS
-- text messages in Amazon Cognito, you must register a phone number with
-- <https://console.aws.amazon.com/pinpoint/home/ Amazon Pinpoint>. Amazon
-- Cognito uses the registered number automatically. Otherwise, Amazon
-- Cognito users who must receive SMS messages might not be able to sign
-- up, activate their accounts, or sign in.
--
-- If you have never used SMS text messages with Amazon Cognito or any
-- other Amazon Web Service, Amazon Simple Notification Service might place
-- your account in the SMS sandbox. In
-- /<https://docs.aws.amazon.com/sns/latest/dg/sns-sms-sandbox.html sandbox mode>/
-- , you can send messages only to verified phone numbers. After you test
-- your app while in the sandbox environment, you can move out of the
-- sandbox and into production. For more information, see
-- <https://docs.aws.amazon.com/cognito/latest/developerguide/cognito-user-identity-pools-sms-userpool-settings.html SMS message settings for Amazon Cognito user pools>
-- in the /Amazon Cognito Developer Guide/.
module Amazonka.CognitoIdentityProvider.UpdateUserPool
  ( -- * Creating a Request
    UpdateUserPool (..),
    newUpdateUserPool,

    -- * Request Lenses
    updateUserPool_accountRecoverySetting,
    updateUserPool_adminCreateUserConfig,
    updateUserPool_autoVerifiedAttributes,
    updateUserPool_deletionProtection,
    updateUserPool_deviceConfiguration,
    updateUserPool_emailConfiguration,
    updateUserPool_emailVerificationMessage,
    updateUserPool_emailVerificationSubject,
    updateUserPool_lambdaConfig,
    updateUserPool_mfaConfiguration,
    updateUserPool_policies,
    updateUserPool_smsAuthenticationMessage,
    updateUserPool_smsConfiguration,
    updateUserPool_smsVerificationMessage,
    updateUserPool_userAttributeUpdateSettings,
    updateUserPool_userPoolAddOns,
    updateUserPool_userPoolTags,
    updateUserPool_verificationMessageTemplate,
    updateUserPool_userPoolId,

    -- * Destructuring the Response
    UpdateUserPoolResponse (..),
    newUpdateUserPoolResponse,

    -- * Response Lenses
    updateUserPoolResponse_httpStatus,
  )
where

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

-- | Represents the request to update the user pool.
--
-- /See:/ 'newUpdateUserPool' smart constructor.
data UpdateUserPool = UpdateUserPool'
  { -- | The available verified method a user can use to recover their password
    -- when they call @ForgotPassword@. You can use this setting to define a
    -- preferred method when a user has more than one method available. With
    -- this setting, SMS doesn\'t qualify for a valid password recovery
    -- mechanism if the user also has SMS multi-factor authentication (MFA)
    -- activated. In the absence of this setting, Amazon Cognito uses the
    -- legacy behavior to determine the recovery method where SMS is preferred
    -- through email.
    UpdateUserPool -> Maybe AccountRecoverySettingType
accountRecoverySetting :: Prelude.Maybe AccountRecoverySettingType,
    -- | The configuration for @AdminCreateUser@ requests.
    UpdateUserPool -> Maybe AdminCreateUserConfigType
adminCreateUserConfig :: Prelude.Maybe AdminCreateUserConfigType,
    -- | The attributes that are automatically verified when Amazon Cognito
    -- requests to update user pools.
    UpdateUserPool -> Maybe [VerifiedAttributeType]
autoVerifiedAttributes :: Prelude.Maybe [VerifiedAttributeType],
    -- | When active, @DeletionProtection@ prevents accidental deletion of your
    -- user pool. Before you can delete a user pool that you have protected
    -- against deletion, you must deactivate this feature.
    --
    -- When you try to delete a protected user pool in a @DeleteUserPool@ API
    -- request, Amazon Cognito returns an @InvalidParameterException@ error. To
    -- delete a protected user pool, send a new @DeleteUserPool@ request after
    -- you deactivate deletion protection in an @UpdateUserPool@ API request.
    UpdateUserPool -> Maybe DeletionProtectionType
deletionProtection :: Prelude.Maybe DeletionProtectionType,
    -- | The device-remembering configuration for a user pool. A null value
    -- indicates that you have deactivated device remembering in your user
    -- pool.
    --
    -- When you provide a value for any @DeviceConfiguration@ field, you
    -- activate the Amazon Cognito device-remembering feature.
    UpdateUserPool -> Maybe DeviceConfigurationType
deviceConfiguration :: Prelude.Maybe DeviceConfigurationType,
    -- | The email configuration of your user pool. The email configuration type
    -- sets your preferred sending method, Amazon Web Services Region, and
    -- sender for email invitation and verification messages from your user
    -- pool.
    UpdateUserPool -> Maybe EmailConfigurationType
emailConfiguration :: Prelude.Maybe EmailConfigurationType,
    -- | This parameter is no longer used. See
    -- <https://docs.aws.amazon.com/cognito-user-identity-pools/latest/APIReference/API_VerificationMessageTemplateType.html VerificationMessageTemplateType>.
    UpdateUserPool -> Maybe Text
emailVerificationMessage :: Prelude.Maybe Prelude.Text,
    -- | This parameter is no longer used. See
    -- <https://docs.aws.amazon.com/cognito-user-identity-pools/latest/APIReference/API_VerificationMessageTemplateType.html VerificationMessageTemplateType>.
    UpdateUserPool -> Maybe Text
emailVerificationSubject :: Prelude.Maybe Prelude.Text,
    -- | The Lambda configuration information from the request to update the user
    -- pool.
    UpdateUserPool -> Maybe LambdaConfigType
lambdaConfig :: Prelude.Maybe LambdaConfigType,
    -- | Possible values include:
    --
    -- -   @OFF@ - MFA tokens aren\'t required and can\'t be specified during
    --     user registration.
    --
    -- -   @ON@ - MFA tokens are required for all user registrations. You can
    --     only specify ON when you\'re initially creating a user pool. You can
    --     use the
    --     <https://docs.aws.amazon.com/cognito-user-identity-pools/latest/APIReference/API_SetUserPoolMfaConfig.html SetUserPoolMfaConfig>
    --     API operation to turn MFA \"ON\" for existing user pools.
    --
    -- -   @OPTIONAL@ - Users have the option when registering to create an MFA
    --     token.
    UpdateUserPool -> Maybe UserPoolMfaType
mfaConfiguration :: Prelude.Maybe UserPoolMfaType,
    -- | A container with the policies you want to update in a user pool.
    UpdateUserPool -> Maybe UserPoolPolicyType
policies :: Prelude.Maybe UserPoolPolicyType,
    -- | The contents of the SMS authentication message.
    UpdateUserPool -> Maybe Text
smsAuthenticationMessage :: Prelude.Maybe Prelude.Text,
    -- | The SMS configuration with the settings that your Amazon Cognito user
    -- pool must use to send an SMS message from your Amazon Web Services
    -- account through Amazon Simple Notification Service. To send SMS messages
    -- with Amazon SNS in the Amazon Web Services Region that you want, the
    -- Amazon Cognito user pool uses an Identity and Access Management (IAM)
    -- role in your Amazon Web Services account.
    UpdateUserPool -> Maybe SmsConfigurationType
smsConfiguration :: Prelude.Maybe SmsConfigurationType,
    -- | This parameter is no longer used. See
    -- <https://docs.aws.amazon.com/cognito-user-identity-pools/latest/APIReference/API_VerificationMessageTemplateType.html VerificationMessageTemplateType>.
    UpdateUserPool -> Maybe Text
smsVerificationMessage :: Prelude.Maybe Prelude.Text,
    -- | The settings for updates to user attributes. These settings include the
    -- property @AttributesRequireVerificationBeforeUpdate@, a user-pool
    -- setting that tells Amazon Cognito how to handle changes to the value of
    -- your users\' email address and phone number attributes. For more
    -- information, see
    -- <https://docs.aws.amazon.com/cognito/latest/developerguide/user-pool-settings-email-phone-verification.html#user-pool-settings-verifications-verify-attribute-updates Verifying updates to email addresses and phone numbers>.
    UpdateUserPool -> Maybe UserAttributeUpdateSettingsType
userAttributeUpdateSettings :: Prelude.Maybe UserAttributeUpdateSettingsType,
    -- | Enables advanced security risk detection. Set the key
    -- @AdvancedSecurityMode@ to the value \"AUDIT\".
    UpdateUserPool -> Maybe UserPoolAddOnsType
userPoolAddOns :: Prelude.Maybe UserPoolAddOnsType,
    -- | The tag keys and values to assign to the user pool. A tag is a label
    -- that you can use to categorize and manage user pools in different ways,
    -- such as by purpose, owner, environment, or other criteria.
    UpdateUserPool -> Maybe (HashMap Text Text)
userPoolTags :: Prelude.Maybe (Prelude.HashMap Prelude.Text Prelude.Text),
    -- | The template for verification messages.
    UpdateUserPool -> Maybe VerificationMessageTemplateType
verificationMessageTemplate :: Prelude.Maybe VerificationMessageTemplateType,
    -- | The user pool ID for the user pool you want to update.
    UpdateUserPool -> Text
userPoolId :: Prelude.Text
  }
  deriving (UpdateUserPool -> UpdateUserPool -> Bool
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: UpdateUserPool -> UpdateUserPool -> Bool
$c/= :: UpdateUserPool -> UpdateUserPool -> Bool
== :: UpdateUserPool -> UpdateUserPool -> Bool
$c== :: UpdateUserPool -> UpdateUserPool -> Bool
Prelude.Eq, ReadPrec [UpdateUserPool]
ReadPrec UpdateUserPool
Int -> ReadS UpdateUserPool
ReadS [UpdateUserPool]
forall a.
(Int -> ReadS a)
-> ReadS [a] -> ReadPrec a -> ReadPrec [a] -> Read a
readListPrec :: ReadPrec [UpdateUserPool]
$creadListPrec :: ReadPrec [UpdateUserPool]
readPrec :: ReadPrec UpdateUserPool
$creadPrec :: ReadPrec UpdateUserPool
readList :: ReadS [UpdateUserPool]
$creadList :: ReadS [UpdateUserPool]
readsPrec :: Int -> ReadS UpdateUserPool
$creadsPrec :: Int -> ReadS UpdateUserPool
Prelude.Read, Int -> UpdateUserPool -> ShowS
[UpdateUserPool] -> ShowS
UpdateUserPool -> String
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [UpdateUserPool] -> ShowS
$cshowList :: [UpdateUserPool] -> ShowS
show :: UpdateUserPool -> String
$cshow :: UpdateUserPool -> String
showsPrec :: Int -> UpdateUserPool -> ShowS
$cshowsPrec :: Int -> UpdateUserPool -> ShowS
Prelude.Show, forall x. Rep UpdateUserPool x -> UpdateUserPool
forall x. UpdateUserPool -> Rep UpdateUserPool x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cto :: forall x. Rep UpdateUserPool x -> UpdateUserPool
$cfrom :: forall x. UpdateUserPool -> Rep UpdateUserPool x
Prelude.Generic)

-- |
-- Create a value of 'UpdateUserPool' 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:
--
-- 'accountRecoverySetting', 'updateUserPool_accountRecoverySetting' - The available verified method a user can use to recover their password
-- when they call @ForgotPassword@. You can use this setting to define a
-- preferred method when a user has more than one method available. With
-- this setting, SMS doesn\'t qualify for a valid password recovery
-- mechanism if the user also has SMS multi-factor authentication (MFA)
-- activated. In the absence of this setting, Amazon Cognito uses the
-- legacy behavior to determine the recovery method where SMS is preferred
-- through email.
--
-- 'adminCreateUserConfig', 'updateUserPool_adminCreateUserConfig' - The configuration for @AdminCreateUser@ requests.
--
-- 'autoVerifiedAttributes', 'updateUserPool_autoVerifiedAttributes' - The attributes that are automatically verified when Amazon Cognito
-- requests to update user pools.
--
-- 'deletionProtection', 'updateUserPool_deletionProtection' - When active, @DeletionProtection@ prevents accidental deletion of your
-- user pool. Before you can delete a user pool that you have protected
-- against deletion, you must deactivate this feature.
--
-- When you try to delete a protected user pool in a @DeleteUserPool@ API
-- request, Amazon Cognito returns an @InvalidParameterException@ error. To
-- delete a protected user pool, send a new @DeleteUserPool@ request after
-- you deactivate deletion protection in an @UpdateUserPool@ API request.
--
-- 'deviceConfiguration', 'updateUserPool_deviceConfiguration' - The device-remembering configuration for a user pool. A null value
-- indicates that you have deactivated device remembering in your user
-- pool.
--
-- When you provide a value for any @DeviceConfiguration@ field, you
-- activate the Amazon Cognito device-remembering feature.
--
-- 'emailConfiguration', 'updateUserPool_emailConfiguration' - The email configuration of your user pool. The email configuration type
-- sets your preferred sending method, Amazon Web Services Region, and
-- sender for email invitation and verification messages from your user
-- pool.
--
-- 'emailVerificationMessage', 'updateUserPool_emailVerificationMessage' - This parameter is no longer used. See
-- <https://docs.aws.amazon.com/cognito-user-identity-pools/latest/APIReference/API_VerificationMessageTemplateType.html VerificationMessageTemplateType>.
--
-- 'emailVerificationSubject', 'updateUserPool_emailVerificationSubject' - This parameter is no longer used. See
-- <https://docs.aws.amazon.com/cognito-user-identity-pools/latest/APIReference/API_VerificationMessageTemplateType.html VerificationMessageTemplateType>.
--
-- 'lambdaConfig', 'updateUserPool_lambdaConfig' - The Lambda configuration information from the request to update the user
-- pool.
--
-- 'mfaConfiguration', 'updateUserPool_mfaConfiguration' - Possible values include:
--
-- -   @OFF@ - MFA tokens aren\'t required and can\'t be specified during
--     user registration.
--
-- -   @ON@ - MFA tokens are required for all user registrations. You can
--     only specify ON when you\'re initially creating a user pool. You can
--     use the
--     <https://docs.aws.amazon.com/cognito-user-identity-pools/latest/APIReference/API_SetUserPoolMfaConfig.html SetUserPoolMfaConfig>
--     API operation to turn MFA \"ON\" for existing user pools.
--
-- -   @OPTIONAL@ - Users have the option when registering to create an MFA
--     token.
--
-- 'policies', 'updateUserPool_policies' - A container with the policies you want to update in a user pool.
--
-- 'smsAuthenticationMessage', 'updateUserPool_smsAuthenticationMessage' - The contents of the SMS authentication message.
--
-- 'smsConfiguration', 'updateUserPool_smsConfiguration' - The SMS configuration with the settings that your Amazon Cognito user
-- pool must use to send an SMS message from your Amazon Web Services
-- account through Amazon Simple Notification Service. To send SMS messages
-- with Amazon SNS in the Amazon Web Services Region that you want, the
-- Amazon Cognito user pool uses an Identity and Access Management (IAM)
-- role in your Amazon Web Services account.
--
-- 'smsVerificationMessage', 'updateUserPool_smsVerificationMessage' - This parameter is no longer used. See
-- <https://docs.aws.amazon.com/cognito-user-identity-pools/latest/APIReference/API_VerificationMessageTemplateType.html VerificationMessageTemplateType>.
--
-- 'userAttributeUpdateSettings', 'updateUserPool_userAttributeUpdateSettings' - The settings for updates to user attributes. These settings include the
-- property @AttributesRequireVerificationBeforeUpdate@, a user-pool
-- setting that tells Amazon Cognito how to handle changes to the value of
-- your users\' email address and phone number attributes. For more
-- information, see
-- <https://docs.aws.amazon.com/cognito/latest/developerguide/user-pool-settings-email-phone-verification.html#user-pool-settings-verifications-verify-attribute-updates Verifying updates to email addresses and phone numbers>.
--
-- 'userPoolAddOns', 'updateUserPool_userPoolAddOns' - Enables advanced security risk detection. Set the key
-- @AdvancedSecurityMode@ to the value \"AUDIT\".
--
-- 'userPoolTags', 'updateUserPool_userPoolTags' - The tag keys and values to assign to the user pool. A tag is a label
-- that you can use to categorize and manage user pools in different ways,
-- such as by purpose, owner, environment, or other criteria.
--
-- 'verificationMessageTemplate', 'updateUserPool_verificationMessageTemplate' - The template for verification messages.
--
-- 'userPoolId', 'updateUserPool_userPoolId' - The user pool ID for the user pool you want to update.
newUpdateUserPool ::
  -- | 'userPoolId'
  Prelude.Text ->
  UpdateUserPool
newUpdateUserPool :: Text -> UpdateUserPool
newUpdateUserPool Text
pUserPoolId_ =
  UpdateUserPool'
    { $sel:accountRecoverySetting:UpdateUserPool' :: Maybe AccountRecoverySettingType
accountRecoverySetting =
        forall a. Maybe a
Prelude.Nothing,
      $sel:adminCreateUserConfig:UpdateUserPool' :: Maybe AdminCreateUserConfigType
adminCreateUserConfig = forall a. Maybe a
Prelude.Nothing,
      $sel:autoVerifiedAttributes:UpdateUserPool' :: Maybe [VerifiedAttributeType]
autoVerifiedAttributes = forall a. Maybe a
Prelude.Nothing,
      $sel:deletionProtection:UpdateUserPool' :: Maybe DeletionProtectionType
deletionProtection = forall a. Maybe a
Prelude.Nothing,
      $sel:deviceConfiguration:UpdateUserPool' :: Maybe DeviceConfigurationType
deviceConfiguration = forall a. Maybe a
Prelude.Nothing,
      $sel:emailConfiguration:UpdateUserPool' :: Maybe EmailConfigurationType
emailConfiguration = forall a. Maybe a
Prelude.Nothing,
      $sel:emailVerificationMessage:UpdateUserPool' :: Maybe Text
emailVerificationMessage = forall a. Maybe a
Prelude.Nothing,
      $sel:emailVerificationSubject:UpdateUserPool' :: Maybe Text
emailVerificationSubject = forall a. Maybe a
Prelude.Nothing,
      $sel:lambdaConfig:UpdateUserPool' :: Maybe LambdaConfigType
lambdaConfig = forall a. Maybe a
Prelude.Nothing,
      $sel:mfaConfiguration:UpdateUserPool' :: Maybe UserPoolMfaType
mfaConfiguration = forall a. Maybe a
Prelude.Nothing,
      $sel:policies:UpdateUserPool' :: Maybe UserPoolPolicyType
policies = forall a. Maybe a
Prelude.Nothing,
      $sel:smsAuthenticationMessage:UpdateUserPool' :: Maybe Text
smsAuthenticationMessage = forall a. Maybe a
Prelude.Nothing,
      $sel:smsConfiguration:UpdateUserPool' :: Maybe SmsConfigurationType
smsConfiguration = forall a. Maybe a
Prelude.Nothing,
      $sel:smsVerificationMessage:UpdateUserPool' :: Maybe Text
smsVerificationMessage = forall a. Maybe a
Prelude.Nothing,
      $sel:userAttributeUpdateSettings:UpdateUserPool' :: Maybe UserAttributeUpdateSettingsType
userAttributeUpdateSettings = forall a. Maybe a
Prelude.Nothing,
      $sel:userPoolAddOns:UpdateUserPool' :: Maybe UserPoolAddOnsType
userPoolAddOns = forall a. Maybe a
Prelude.Nothing,
      $sel:userPoolTags:UpdateUserPool' :: Maybe (HashMap Text Text)
userPoolTags = forall a. Maybe a
Prelude.Nothing,
      $sel:verificationMessageTemplate:UpdateUserPool' :: Maybe VerificationMessageTemplateType
verificationMessageTemplate = forall a. Maybe a
Prelude.Nothing,
      $sel:userPoolId:UpdateUserPool' :: Text
userPoolId = Text
pUserPoolId_
    }

-- | The available verified method a user can use to recover their password
-- when they call @ForgotPassword@. You can use this setting to define a
-- preferred method when a user has more than one method available. With
-- this setting, SMS doesn\'t qualify for a valid password recovery
-- mechanism if the user also has SMS multi-factor authentication (MFA)
-- activated. In the absence of this setting, Amazon Cognito uses the
-- legacy behavior to determine the recovery method where SMS is preferred
-- through email.
updateUserPool_accountRecoverySetting :: Lens.Lens' UpdateUserPool (Prelude.Maybe AccountRecoverySettingType)
updateUserPool_accountRecoverySetting :: Lens' UpdateUserPool (Maybe AccountRecoverySettingType)
updateUserPool_accountRecoverySetting = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\UpdateUserPool' {Maybe AccountRecoverySettingType
accountRecoverySetting :: Maybe AccountRecoverySettingType
$sel:accountRecoverySetting:UpdateUserPool' :: UpdateUserPool -> Maybe AccountRecoverySettingType
accountRecoverySetting} -> Maybe AccountRecoverySettingType
accountRecoverySetting) (\s :: UpdateUserPool
s@UpdateUserPool' {} Maybe AccountRecoverySettingType
a -> UpdateUserPool
s {$sel:accountRecoverySetting:UpdateUserPool' :: Maybe AccountRecoverySettingType
accountRecoverySetting = Maybe AccountRecoverySettingType
a} :: UpdateUserPool)

-- | The configuration for @AdminCreateUser@ requests.
updateUserPool_adminCreateUserConfig :: Lens.Lens' UpdateUserPool (Prelude.Maybe AdminCreateUserConfigType)
updateUserPool_adminCreateUserConfig :: Lens' UpdateUserPool (Maybe AdminCreateUserConfigType)
updateUserPool_adminCreateUserConfig = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\UpdateUserPool' {Maybe AdminCreateUserConfigType
adminCreateUserConfig :: Maybe AdminCreateUserConfigType
$sel:adminCreateUserConfig:UpdateUserPool' :: UpdateUserPool -> Maybe AdminCreateUserConfigType
adminCreateUserConfig} -> Maybe AdminCreateUserConfigType
adminCreateUserConfig) (\s :: UpdateUserPool
s@UpdateUserPool' {} Maybe AdminCreateUserConfigType
a -> UpdateUserPool
s {$sel:adminCreateUserConfig:UpdateUserPool' :: Maybe AdminCreateUserConfigType
adminCreateUserConfig = Maybe AdminCreateUserConfigType
a} :: UpdateUserPool)

-- | The attributes that are automatically verified when Amazon Cognito
-- requests to update user pools.
updateUserPool_autoVerifiedAttributes :: Lens.Lens' UpdateUserPool (Prelude.Maybe [VerifiedAttributeType])
updateUserPool_autoVerifiedAttributes :: Lens' UpdateUserPool (Maybe [VerifiedAttributeType])
updateUserPool_autoVerifiedAttributes = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\UpdateUserPool' {Maybe [VerifiedAttributeType]
autoVerifiedAttributes :: Maybe [VerifiedAttributeType]
$sel:autoVerifiedAttributes:UpdateUserPool' :: UpdateUserPool -> Maybe [VerifiedAttributeType]
autoVerifiedAttributes} -> Maybe [VerifiedAttributeType]
autoVerifiedAttributes) (\s :: UpdateUserPool
s@UpdateUserPool' {} Maybe [VerifiedAttributeType]
a -> UpdateUserPool
s {$sel:autoVerifiedAttributes:UpdateUserPool' :: Maybe [VerifiedAttributeType]
autoVerifiedAttributes = Maybe [VerifiedAttributeType]
a} :: UpdateUserPool) forall b c a. (b -> c) -> (a -> b) -> a -> c
Prelude.. forall (f :: * -> *) (g :: * -> *) s t a b.
(Functor f, Functor g) =>
AnIso s t a b -> Iso (f s) (g t) (f a) (g b)
Lens.mapping forall s t a b. (Coercible s a, Coercible t b) => Iso s t a b
Lens.coerced

-- | When active, @DeletionProtection@ prevents accidental deletion of your
-- user pool. Before you can delete a user pool that you have protected
-- against deletion, you must deactivate this feature.
--
-- When you try to delete a protected user pool in a @DeleteUserPool@ API
-- request, Amazon Cognito returns an @InvalidParameterException@ error. To
-- delete a protected user pool, send a new @DeleteUserPool@ request after
-- you deactivate deletion protection in an @UpdateUserPool@ API request.
updateUserPool_deletionProtection :: Lens.Lens' UpdateUserPool (Prelude.Maybe DeletionProtectionType)
updateUserPool_deletionProtection :: Lens' UpdateUserPool (Maybe DeletionProtectionType)
updateUserPool_deletionProtection = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\UpdateUserPool' {Maybe DeletionProtectionType
deletionProtection :: Maybe DeletionProtectionType
$sel:deletionProtection:UpdateUserPool' :: UpdateUserPool -> Maybe DeletionProtectionType
deletionProtection} -> Maybe DeletionProtectionType
deletionProtection) (\s :: UpdateUserPool
s@UpdateUserPool' {} Maybe DeletionProtectionType
a -> UpdateUserPool
s {$sel:deletionProtection:UpdateUserPool' :: Maybe DeletionProtectionType
deletionProtection = Maybe DeletionProtectionType
a} :: UpdateUserPool)

-- | The device-remembering configuration for a user pool. A null value
-- indicates that you have deactivated device remembering in your user
-- pool.
--
-- When you provide a value for any @DeviceConfiguration@ field, you
-- activate the Amazon Cognito device-remembering feature.
updateUserPool_deviceConfiguration :: Lens.Lens' UpdateUserPool (Prelude.Maybe DeviceConfigurationType)
updateUserPool_deviceConfiguration :: Lens' UpdateUserPool (Maybe DeviceConfigurationType)
updateUserPool_deviceConfiguration = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\UpdateUserPool' {Maybe DeviceConfigurationType
deviceConfiguration :: Maybe DeviceConfigurationType
$sel:deviceConfiguration:UpdateUserPool' :: UpdateUserPool -> Maybe DeviceConfigurationType
deviceConfiguration} -> Maybe DeviceConfigurationType
deviceConfiguration) (\s :: UpdateUserPool
s@UpdateUserPool' {} Maybe DeviceConfigurationType
a -> UpdateUserPool
s {$sel:deviceConfiguration:UpdateUserPool' :: Maybe DeviceConfigurationType
deviceConfiguration = Maybe DeviceConfigurationType
a} :: UpdateUserPool)

-- | The email configuration of your user pool. The email configuration type
-- sets your preferred sending method, Amazon Web Services Region, and
-- sender for email invitation and verification messages from your user
-- pool.
updateUserPool_emailConfiguration :: Lens.Lens' UpdateUserPool (Prelude.Maybe EmailConfigurationType)
updateUserPool_emailConfiguration :: Lens' UpdateUserPool (Maybe EmailConfigurationType)
updateUserPool_emailConfiguration = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\UpdateUserPool' {Maybe EmailConfigurationType
emailConfiguration :: Maybe EmailConfigurationType
$sel:emailConfiguration:UpdateUserPool' :: UpdateUserPool -> Maybe EmailConfigurationType
emailConfiguration} -> Maybe EmailConfigurationType
emailConfiguration) (\s :: UpdateUserPool
s@UpdateUserPool' {} Maybe EmailConfigurationType
a -> UpdateUserPool
s {$sel:emailConfiguration:UpdateUserPool' :: Maybe EmailConfigurationType
emailConfiguration = Maybe EmailConfigurationType
a} :: UpdateUserPool)

-- | This parameter is no longer used. See
-- <https://docs.aws.amazon.com/cognito-user-identity-pools/latest/APIReference/API_VerificationMessageTemplateType.html VerificationMessageTemplateType>.
updateUserPool_emailVerificationMessage :: Lens.Lens' UpdateUserPool (Prelude.Maybe Prelude.Text)
updateUserPool_emailVerificationMessage :: Lens' UpdateUserPool (Maybe Text)
updateUserPool_emailVerificationMessage = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\UpdateUserPool' {Maybe Text
emailVerificationMessage :: Maybe Text
$sel:emailVerificationMessage:UpdateUserPool' :: UpdateUserPool -> Maybe Text
emailVerificationMessage} -> Maybe Text
emailVerificationMessage) (\s :: UpdateUserPool
s@UpdateUserPool' {} Maybe Text
a -> UpdateUserPool
s {$sel:emailVerificationMessage:UpdateUserPool' :: Maybe Text
emailVerificationMessage = Maybe Text
a} :: UpdateUserPool)

-- | This parameter is no longer used. See
-- <https://docs.aws.amazon.com/cognito-user-identity-pools/latest/APIReference/API_VerificationMessageTemplateType.html VerificationMessageTemplateType>.
updateUserPool_emailVerificationSubject :: Lens.Lens' UpdateUserPool (Prelude.Maybe Prelude.Text)
updateUserPool_emailVerificationSubject :: Lens' UpdateUserPool (Maybe Text)
updateUserPool_emailVerificationSubject = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\UpdateUserPool' {Maybe Text
emailVerificationSubject :: Maybe Text
$sel:emailVerificationSubject:UpdateUserPool' :: UpdateUserPool -> Maybe Text
emailVerificationSubject} -> Maybe Text
emailVerificationSubject) (\s :: UpdateUserPool
s@UpdateUserPool' {} Maybe Text
a -> UpdateUserPool
s {$sel:emailVerificationSubject:UpdateUserPool' :: Maybe Text
emailVerificationSubject = Maybe Text
a} :: UpdateUserPool)

-- | The Lambda configuration information from the request to update the user
-- pool.
updateUserPool_lambdaConfig :: Lens.Lens' UpdateUserPool (Prelude.Maybe LambdaConfigType)
updateUserPool_lambdaConfig :: Lens' UpdateUserPool (Maybe LambdaConfigType)
updateUserPool_lambdaConfig = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\UpdateUserPool' {Maybe LambdaConfigType
lambdaConfig :: Maybe LambdaConfigType
$sel:lambdaConfig:UpdateUserPool' :: UpdateUserPool -> Maybe LambdaConfigType
lambdaConfig} -> Maybe LambdaConfigType
lambdaConfig) (\s :: UpdateUserPool
s@UpdateUserPool' {} Maybe LambdaConfigType
a -> UpdateUserPool
s {$sel:lambdaConfig:UpdateUserPool' :: Maybe LambdaConfigType
lambdaConfig = Maybe LambdaConfigType
a} :: UpdateUserPool)

-- | Possible values include:
--
-- -   @OFF@ - MFA tokens aren\'t required and can\'t be specified during
--     user registration.
--
-- -   @ON@ - MFA tokens are required for all user registrations. You can
--     only specify ON when you\'re initially creating a user pool. You can
--     use the
--     <https://docs.aws.amazon.com/cognito-user-identity-pools/latest/APIReference/API_SetUserPoolMfaConfig.html SetUserPoolMfaConfig>
--     API operation to turn MFA \"ON\" for existing user pools.
--
-- -   @OPTIONAL@ - Users have the option when registering to create an MFA
--     token.
updateUserPool_mfaConfiguration :: Lens.Lens' UpdateUserPool (Prelude.Maybe UserPoolMfaType)
updateUserPool_mfaConfiguration :: Lens' UpdateUserPool (Maybe UserPoolMfaType)
updateUserPool_mfaConfiguration = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\UpdateUserPool' {Maybe UserPoolMfaType
mfaConfiguration :: Maybe UserPoolMfaType
$sel:mfaConfiguration:UpdateUserPool' :: UpdateUserPool -> Maybe UserPoolMfaType
mfaConfiguration} -> Maybe UserPoolMfaType
mfaConfiguration) (\s :: UpdateUserPool
s@UpdateUserPool' {} Maybe UserPoolMfaType
a -> UpdateUserPool
s {$sel:mfaConfiguration:UpdateUserPool' :: Maybe UserPoolMfaType
mfaConfiguration = Maybe UserPoolMfaType
a} :: UpdateUserPool)

-- | A container with the policies you want to update in a user pool.
updateUserPool_policies :: Lens.Lens' UpdateUserPool (Prelude.Maybe UserPoolPolicyType)
updateUserPool_policies :: Lens' UpdateUserPool (Maybe UserPoolPolicyType)
updateUserPool_policies = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\UpdateUserPool' {Maybe UserPoolPolicyType
policies :: Maybe UserPoolPolicyType
$sel:policies:UpdateUserPool' :: UpdateUserPool -> Maybe UserPoolPolicyType
policies} -> Maybe UserPoolPolicyType
policies) (\s :: UpdateUserPool
s@UpdateUserPool' {} Maybe UserPoolPolicyType
a -> UpdateUserPool
s {$sel:policies:UpdateUserPool' :: Maybe UserPoolPolicyType
policies = Maybe UserPoolPolicyType
a} :: UpdateUserPool)

-- | The contents of the SMS authentication message.
updateUserPool_smsAuthenticationMessage :: Lens.Lens' UpdateUserPool (Prelude.Maybe Prelude.Text)
updateUserPool_smsAuthenticationMessage :: Lens' UpdateUserPool (Maybe Text)
updateUserPool_smsAuthenticationMessage = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\UpdateUserPool' {Maybe Text
smsAuthenticationMessage :: Maybe Text
$sel:smsAuthenticationMessage:UpdateUserPool' :: UpdateUserPool -> Maybe Text
smsAuthenticationMessage} -> Maybe Text
smsAuthenticationMessage) (\s :: UpdateUserPool
s@UpdateUserPool' {} Maybe Text
a -> UpdateUserPool
s {$sel:smsAuthenticationMessage:UpdateUserPool' :: Maybe Text
smsAuthenticationMessage = Maybe Text
a} :: UpdateUserPool)

-- | The SMS configuration with the settings that your Amazon Cognito user
-- pool must use to send an SMS message from your Amazon Web Services
-- account through Amazon Simple Notification Service. To send SMS messages
-- with Amazon SNS in the Amazon Web Services Region that you want, the
-- Amazon Cognito user pool uses an Identity and Access Management (IAM)
-- role in your Amazon Web Services account.
updateUserPool_smsConfiguration :: Lens.Lens' UpdateUserPool (Prelude.Maybe SmsConfigurationType)
updateUserPool_smsConfiguration :: Lens' UpdateUserPool (Maybe SmsConfigurationType)
updateUserPool_smsConfiguration = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\UpdateUserPool' {Maybe SmsConfigurationType
smsConfiguration :: Maybe SmsConfigurationType
$sel:smsConfiguration:UpdateUserPool' :: UpdateUserPool -> Maybe SmsConfigurationType
smsConfiguration} -> Maybe SmsConfigurationType
smsConfiguration) (\s :: UpdateUserPool
s@UpdateUserPool' {} Maybe SmsConfigurationType
a -> UpdateUserPool
s {$sel:smsConfiguration:UpdateUserPool' :: Maybe SmsConfigurationType
smsConfiguration = Maybe SmsConfigurationType
a} :: UpdateUserPool)

-- | This parameter is no longer used. See
-- <https://docs.aws.amazon.com/cognito-user-identity-pools/latest/APIReference/API_VerificationMessageTemplateType.html VerificationMessageTemplateType>.
updateUserPool_smsVerificationMessage :: Lens.Lens' UpdateUserPool (Prelude.Maybe Prelude.Text)
updateUserPool_smsVerificationMessage :: Lens' UpdateUserPool (Maybe Text)
updateUserPool_smsVerificationMessage = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\UpdateUserPool' {Maybe Text
smsVerificationMessage :: Maybe Text
$sel:smsVerificationMessage:UpdateUserPool' :: UpdateUserPool -> Maybe Text
smsVerificationMessage} -> Maybe Text
smsVerificationMessage) (\s :: UpdateUserPool
s@UpdateUserPool' {} Maybe Text
a -> UpdateUserPool
s {$sel:smsVerificationMessage:UpdateUserPool' :: Maybe Text
smsVerificationMessage = Maybe Text
a} :: UpdateUserPool)

-- | The settings for updates to user attributes. These settings include the
-- property @AttributesRequireVerificationBeforeUpdate@, a user-pool
-- setting that tells Amazon Cognito how to handle changes to the value of
-- your users\' email address and phone number attributes. For more
-- information, see
-- <https://docs.aws.amazon.com/cognito/latest/developerguide/user-pool-settings-email-phone-verification.html#user-pool-settings-verifications-verify-attribute-updates Verifying updates to email addresses and phone numbers>.
updateUserPool_userAttributeUpdateSettings :: Lens.Lens' UpdateUserPool (Prelude.Maybe UserAttributeUpdateSettingsType)
updateUserPool_userAttributeUpdateSettings :: Lens' UpdateUserPool (Maybe UserAttributeUpdateSettingsType)
updateUserPool_userAttributeUpdateSettings = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\UpdateUserPool' {Maybe UserAttributeUpdateSettingsType
userAttributeUpdateSettings :: Maybe UserAttributeUpdateSettingsType
$sel:userAttributeUpdateSettings:UpdateUserPool' :: UpdateUserPool -> Maybe UserAttributeUpdateSettingsType
userAttributeUpdateSettings} -> Maybe UserAttributeUpdateSettingsType
userAttributeUpdateSettings) (\s :: UpdateUserPool
s@UpdateUserPool' {} Maybe UserAttributeUpdateSettingsType
a -> UpdateUserPool
s {$sel:userAttributeUpdateSettings:UpdateUserPool' :: Maybe UserAttributeUpdateSettingsType
userAttributeUpdateSettings = Maybe UserAttributeUpdateSettingsType
a} :: UpdateUserPool)

-- | Enables advanced security risk detection. Set the key
-- @AdvancedSecurityMode@ to the value \"AUDIT\".
updateUserPool_userPoolAddOns :: Lens.Lens' UpdateUserPool (Prelude.Maybe UserPoolAddOnsType)
updateUserPool_userPoolAddOns :: Lens' UpdateUserPool (Maybe UserPoolAddOnsType)
updateUserPool_userPoolAddOns = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\UpdateUserPool' {Maybe UserPoolAddOnsType
userPoolAddOns :: Maybe UserPoolAddOnsType
$sel:userPoolAddOns:UpdateUserPool' :: UpdateUserPool -> Maybe UserPoolAddOnsType
userPoolAddOns} -> Maybe UserPoolAddOnsType
userPoolAddOns) (\s :: UpdateUserPool
s@UpdateUserPool' {} Maybe UserPoolAddOnsType
a -> UpdateUserPool
s {$sel:userPoolAddOns:UpdateUserPool' :: Maybe UserPoolAddOnsType
userPoolAddOns = Maybe UserPoolAddOnsType
a} :: UpdateUserPool)

-- | The tag keys and values to assign to the user pool. A tag is a label
-- that you can use to categorize and manage user pools in different ways,
-- such as by purpose, owner, environment, or other criteria.
updateUserPool_userPoolTags :: Lens.Lens' UpdateUserPool (Prelude.Maybe (Prelude.HashMap Prelude.Text Prelude.Text))
updateUserPool_userPoolTags :: Lens' UpdateUserPool (Maybe (HashMap Text Text))
updateUserPool_userPoolTags = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\UpdateUserPool' {Maybe (HashMap Text Text)
userPoolTags :: Maybe (HashMap Text Text)
$sel:userPoolTags:UpdateUserPool' :: UpdateUserPool -> Maybe (HashMap Text Text)
userPoolTags} -> Maybe (HashMap Text Text)
userPoolTags) (\s :: UpdateUserPool
s@UpdateUserPool' {} Maybe (HashMap Text Text)
a -> UpdateUserPool
s {$sel:userPoolTags:UpdateUserPool' :: Maybe (HashMap Text Text)
userPoolTags = Maybe (HashMap Text Text)
a} :: UpdateUserPool) forall b c a. (b -> c) -> (a -> b) -> a -> c
Prelude.. forall (f :: * -> *) (g :: * -> *) s t a b.
(Functor f, Functor g) =>
AnIso s t a b -> Iso (f s) (g t) (f a) (g b)
Lens.mapping forall s t a b. (Coercible s a, Coercible t b) => Iso s t a b
Lens.coerced

-- | The template for verification messages.
updateUserPool_verificationMessageTemplate :: Lens.Lens' UpdateUserPool (Prelude.Maybe VerificationMessageTemplateType)
updateUserPool_verificationMessageTemplate :: Lens' UpdateUserPool (Maybe VerificationMessageTemplateType)
updateUserPool_verificationMessageTemplate = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\UpdateUserPool' {Maybe VerificationMessageTemplateType
verificationMessageTemplate :: Maybe VerificationMessageTemplateType
$sel:verificationMessageTemplate:UpdateUserPool' :: UpdateUserPool -> Maybe VerificationMessageTemplateType
verificationMessageTemplate} -> Maybe VerificationMessageTemplateType
verificationMessageTemplate) (\s :: UpdateUserPool
s@UpdateUserPool' {} Maybe VerificationMessageTemplateType
a -> UpdateUserPool
s {$sel:verificationMessageTemplate:UpdateUserPool' :: Maybe VerificationMessageTemplateType
verificationMessageTemplate = Maybe VerificationMessageTemplateType
a} :: UpdateUserPool)

-- | The user pool ID for the user pool you want to update.
updateUserPool_userPoolId :: Lens.Lens' UpdateUserPool Prelude.Text
updateUserPool_userPoolId :: Lens' UpdateUserPool Text
updateUserPool_userPoolId = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\UpdateUserPool' {Text
userPoolId :: Text
$sel:userPoolId:UpdateUserPool' :: UpdateUserPool -> Text
userPoolId} -> Text
userPoolId) (\s :: UpdateUserPool
s@UpdateUserPool' {} Text
a -> UpdateUserPool
s {$sel:userPoolId:UpdateUserPool' :: Text
userPoolId = Text
a} :: UpdateUserPool)

instance Core.AWSRequest UpdateUserPool where
  type
    AWSResponse UpdateUserPool =
      UpdateUserPoolResponse
  request :: (Service -> Service) -> UpdateUserPool -> Request UpdateUserPool
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 UpdateUserPool
-> ClientResponse ClientBody
-> m (Either Error (ClientResponse (AWSResponse UpdateUserPool)))
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 -> UpdateUserPoolResponse
UpdateUserPoolResponse'
            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 UpdateUserPool where
  hashWithSalt :: Int -> UpdateUserPool -> Int
hashWithSalt Int
_salt UpdateUserPool' {Maybe [VerifiedAttributeType]
Maybe Text
Maybe (HashMap Text Text)
Maybe DeletionProtectionType
Maybe DeviceConfigurationType
Maybe EmailConfigurationType
Maybe LambdaConfigType
Maybe AdminCreateUserConfigType
Maybe AccountRecoverySettingType
Maybe SmsConfigurationType
Maybe UserPoolAddOnsType
Maybe UserPoolMfaType
Maybe UserPoolPolicyType
Maybe VerificationMessageTemplateType
Maybe UserAttributeUpdateSettingsType
Text
userPoolId :: Text
verificationMessageTemplate :: Maybe VerificationMessageTemplateType
userPoolTags :: Maybe (HashMap Text Text)
userPoolAddOns :: Maybe UserPoolAddOnsType
userAttributeUpdateSettings :: Maybe UserAttributeUpdateSettingsType
smsVerificationMessage :: Maybe Text
smsConfiguration :: Maybe SmsConfigurationType
smsAuthenticationMessage :: Maybe Text
policies :: Maybe UserPoolPolicyType
mfaConfiguration :: Maybe UserPoolMfaType
lambdaConfig :: Maybe LambdaConfigType
emailVerificationSubject :: Maybe Text
emailVerificationMessage :: Maybe Text
emailConfiguration :: Maybe EmailConfigurationType
deviceConfiguration :: Maybe DeviceConfigurationType
deletionProtection :: Maybe DeletionProtectionType
autoVerifiedAttributes :: Maybe [VerifiedAttributeType]
adminCreateUserConfig :: Maybe AdminCreateUserConfigType
accountRecoverySetting :: Maybe AccountRecoverySettingType
$sel:userPoolId:UpdateUserPool' :: UpdateUserPool -> Text
$sel:verificationMessageTemplate:UpdateUserPool' :: UpdateUserPool -> Maybe VerificationMessageTemplateType
$sel:userPoolTags:UpdateUserPool' :: UpdateUserPool -> Maybe (HashMap Text Text)
$sel:userPoolAddOns:UpdateUserPool' :: UpdateUserPool -> Maybe UserPoolAddOnsType
$sel:userAttributeUpdateSettings:UpdateUserPool' :: UpdateUserPool -> Maybe UserAttributeUpdateSettingsType
$sel:smsVerificationMessage:UpdateUserPool' :: UpdateUserPool -> Maybe Text
$sel:smsConfiguration:UpdateUserPool' :: UpdateUserPool -> Maybe SmsConfigurationType
$sel:smsAuthenticationMessage:UpdateUserPool' :: UpdateUserPool -> Maybe Text
$sel:policies:UpdateUserPool' :: UpdateUserPool -> Maybe UserPoolPolicyType
$sel:mfaConfiguration:UpdateUserPool' :: UpdateUserPool -> Maybe UserPoolMfaType
$sel:lambdaConfig:UpdateUserPool' :: UpdateUserPool -> Maybe LambdaConfigType
$sel:emailVerificationSubject:UpdateUserPool' :: UpdateUserPool -> Maybe Text
$sel:emailVerificationMessage:UpdateUserPool' :: UpdateUserPool -> Maybe Text
$sel:emailConfiguration:UpdateUserPool' :: UpdateUserPool -> Maybe EmailConfigurationType
$sel:deviceConfiguration:UpdateUserPool' :: UpdateUserPool -> Maybe DeviceConfigurationType
$sel:deletionProtection:UpdateUserPool' :: UpdateUserPool -> Maybe DeletionProtectionType
$sel:autoVerifiedAttributes:UpdateUserPool' :: UpdateUserPool -> Maybe [VerifiedAttributeType]
$sel:adminCreateUserConfig:UpdateUserPool' :: UpdateUserPool -> Maybe AdminCreateUserConfigType
$sel:accountRecoverySetting:UpdateUserPool' :: UpdateUserPool -> Maybe AccountRecoverySettingType
..} =
    Int
_salt
      forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Maybe AccountRecoverySettingType
accountRecoverySetting
      forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Maybe AdminCreateUserConfigType
adminCreateUserConfig
      forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Maybe [VerifiedAttributeType]
autoVerifiedAttributes
      forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Maybe DeletionProtectionType
deletionProtection
      forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Maybe DeviceConfigurationType
deviceConfiguration
      forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Maybe EmailConfigurationType
emailConfiguration
      forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Maybe Text
emailVerificationMessage
      forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Maybe Text
emailVerificationSubject
      forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Maybe LambdaConfigType
lambdaConfig
      forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Maybe UserPoolMfaType
mfaConfiguration
      forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Maybe UserPoolPolicyType
policies
      forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Maybe Text
smsAuthenticationMessage
      forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Maybe SmsConfigurationType
smsConfiguration
      forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Maybe Text
smsVerificationMessage
      forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Maybe UserAttributeUpdateSettingsType
userAttributeUpdateSettings
      forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Maybe UserPoolAddOnsType
userPoolAddOns
      forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Maybe (HashMap Text Text)
userPoolTags
      forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Maybe VerificationMessageTemplateType
verificationMessageTemplate
      forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Text
userPoolId

instance Prelude.NFData UpdateUserPool where
  rnf :: UpdateUserPool -> ()
rnf UpdateUserPool' {Maybe [VerifiedAttributeType]
Maybe Text
Maybe (HashMap Text Text)
Maybe DeletionProtectionType
Maybe DeviceConfigurationType
Maybe EmailConfigurationType
Maybe LambdaConfigType
Maybe AdminCreateUserConfigType
Maybe AccountRecoverySettingType
Maybe SmsConfigurationType
Maybe UserPoolAddOnsType
Maybe UserPoolMfaType
Maybe UserPoolPolicyType
Maybe VerificationMessageTemplateType
Maybe UserAttributeUpdateSettingsType
Text
userPoolId :: Text
verificationMessageTemplate :: Maybe VerificationMessageTemplateType
userPoolTags :: Maybe (HashMap Text Text)
userPoolAddOns :: Maybe UserPoolAddOnsType
userAttributeUpdateSettings :: Maybe UserAttributeUpdateSettingsType
smsVerificationMessage :: Maybe Text
smsConfiguration :: Maybe SmsConfigurationType
smsAuthenticationMessage :: Maybe Text
policies :: Maybe UserPoolPolicyType
mfaConfiguration :: Maybe UserPoolMfaType
lambdaConfig :: Maybe LambdaConfigType
emailVerificationSubject :: Maybe Text
emailVerificationMessage :: Maybe Text
emailConfiguration :: Maybe EmailConfigurationType
deviceConfiguration :: Maybe DeviceConfigurationType
deletionProtection :: Maybe DeletionProtectionType
autoVerifiedAttributes :: Maybe [VerifiedAttributeType]
adminCreateUserConfig :: Maybe AdminCreateUserConfigType
accountRecoverySetting :: Maybe AccountRecoverySettingType
$sel:userPoolId:UpdateUserPool' :: UpdateUserPool -> Text
$sel:verificationMessageTemplate:UpdateUserPool' :: UpdateUserPool -> Maybe VerificationMessageTemplateType
$sel:userPoolTags:UpdateUserPool' :: UpdateUserPool -> Maybe (HashMap Text Text)
$sel:userPoolAddOns:UpdateUserPool' :: UpdateUserPool -> Maybe UserPoolAddOnsType
$sel:userAttributeUpdateSettings:UpdateUserPool' :: UpdateUserPool -> Maybe UserAttributeUpdateSettingsType
$sel:smsVerificationMessage:UpdateUserPool' :: UpdateUserPool -> Maybe Text
$sel:smsConfiguration:UpdateUserPool' :: UpdateUserPool -> Maybe SmsConfigurationType
$sel:smsAuthenticationMessage:UpdateUserPool' :: UpdateUserPool -> Maybe Text
$sel:policies:UpdateUserPool' :: UpdateUserPool -> Maybe UserPoolPolicyType
$sel:mfaConfiguration:UpdateUserPool' :: UpdateUserPool -> Maybe UserPoolMfaType
$sel:lambdaConfig:UpdateUserPool' :: UpdateUserPool -> Maybe LambdaConfigType
$sel:emailVerificationSubject:UpdateUserPool' :: UpdateUserPool -> Maybe Text
$sel:emailVerificationMessage:UpdateUserPool' :: UpdateUserPool -> Maybe Text
$sel:emailConfiguration:UpdateUserPool' :: UpdateUserPool -> Maybe EmailConfigurationType
$sel:deviceConfiguration:UpdateUserPool' :: UpdateUserPool -> Maybe DeviceConfigurationType
$sel:deletionProtection:UpdateUserPool' :: UpdateUserPool -> Maybe DeletionProtectionType
$sel:autoVerifiedAttributes:UpdateUserPool' :: UpdateUserPool -> Maybe [VerifiedAttributeType]
$sel:adminCreateUserConfig:UpdateUserPool' :: UpdateUserPool -> Maybe AdminCreateUserConfigType
$sel:accountRecoverySetting:UpdateUserPool' :: UpdateUserPool -> Maybe AccountRecoverySettingType
..} =
    forall a. NFData a => a -> ()
Prelude.rnf Maybe AccountRecoverySettingType
accountRecoverySetting
      seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf Maybe AdminCreateUserConfigType
adminCreateUserConfig
      seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf Maybe [VerifiedAttributeType]
autoVerifiedAttributes
      seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf Maybe DeletionProtectionType
deletionProtection
      seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf Maybe DeviceConfigurationType
deviceConfiguration
      seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf Maybe EmailConfigurationType
emailConfiguration
      seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf Maybe Text
emailVerificationMessage
      seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf Maybe Text
emailVerificationSubject
      seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf Maybe LambdaConfigType
lambdaConfig
      seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf Maybe UserPoolMfaType
mfaConfiguration
      seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf Maybe UserPoolPolicyType
policies
      seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf Maybe Text
smsAuthenticationMessage
      seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf Maybe SmsConfigurationType
smsConfiguration
      seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf Maybe Text
smsVerificationMessage
      seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf Maybe UserAttributeUpdateSettingsType
userAttributeUpdateSettings
      seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf Maybe UserPoolAddOnsType
userPoolAddOns
      seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf Maybe (HashMap Text Text)
userPoolTags
      seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf
        Maybe VerificationMessageTemplateType
verificationMessageTemplate
      seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf Text
userPoolId

instance Data.ToHeaders UpdateUserPool where
  toHeaders :: UpdateUserPool -> 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
"AWSCognitoIdentityProviderService.UpdateUserPool" ::
                          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 UpdateUserPool where
  toJSON :: UpdateUserPool -> Value
toJSON UpdateUserPool' {Maybe [VerifiedAttributeType]
Maybe Text
Maybe (HashMap Text Text)
Maybe DeletionProtectionType
Maybe DeviceConfigurationType
Maybe EmailConfigurationType
Maybe LambdaConfigType
Maybe AdminCreateUserConfigType
Maybe AccountRecoverySettingType
Maybe SmsConfigurationType
Maybe UserPoolAddOnsType
Maybe UserPoolMfaType
Maybe UserPoolPolicyType
Maybe VerificationMessageTemplateType
Maybe UserAttributeUpdateSettingsType
Text
userPoolId :: Text
verificationMessageTemplate :: Maybe VerificationMessageTemplateType
userPoolTags :: Maybe (HashMap Text Text)
userPoolAddOns :: Maybe UserPoolAddOnsType
userAttributeUpdateSettings :: Maybe UserAttributeUpdateSettingsType
smsVerificationMessage :: Maybe Text
smsConfiguration :: Maybe SmsConfigurationType
smsAuthenticationMessage :: Maybe Text
policies :: Maybe UserPoolPolicyType
mfaConfiguration :: Maybe UserPoolMfaType
lambdaConfig :: Maybe LambdaConfigType
emailVerificationSubject :: Maybe Text
emailVerificationMessage :: Maybe Text
emailConfiguration :: Maybe EmailConfigurationType
deviceConfiguration :: Maybe DeviceConfigurationType
deletionProtection :: Maybe DeletionProtectionType
autoVerifiedAttributes :: Maybe [VerifiedAttributeType]
adminCreateUserConfig :: Maybe AdminCreateUserConfigType
accountRecoverySetting :: Maybe AccountRecoverySettingType
$sel:userPoolId:UpdateUserPool' :: UpdateUserPool -> Text
$sel:verificationMessageTemplate:UpdateUserPool' :: UpdateUserPool -> Maybe VerificationMessageTemplateType
$sel:userPoolTags:UpdateUserPool' :: UpdateUserPool -> Maybe (HashMap Text Text)
$sel:userPoolAddOns:UpdateUserPool' :: UpdateUserPool -> Maybe UserPoolAddOnsType
$sel:userAttributeUpdateSettings:UpdateUserPool' :: UpdateUserPool -> Maybe UserAttributeUpdateSettingsType
$sel:smsVerificationMessage:UpdateUserPool' :: UpdateUserPool -> Maybe Text
$sel:smsConfiguration:UpdateUserPool' :: UpdateUserPool -> Maybe SmsConfigurationType
$sel:smsAuthenticationMessage:UpdateUserPool' :: UpdateUserPool -> Maybe Text
$sel:policies:UpdateUserPool' :: UpdateUserPool -> Maybe UserPoolPolicyType
$sel:mfaConfiguration:UpdateUserPool' :: UpdateUserPool -> Maybe UserPoolMfaType
$sel:lambdaConfig:UpdateUserPool' :: UpdateUserPool -> Maybe LambdaConfigType
$sel:emailVerificationSubject:UpdateUserPool' :: UpdateUserPool -> Maybe Text
$sel:emailVerificationMessage:UpdateUserPool' :: UpdateUserPool -> Maybe Text
$sel:emailConfiguration:UpdateUserPool' :: UpdateUserPool -> Maybe EmailConfigurationType
$sel:deviceConfiguration:UpdateUserPool' :: UpdateUserPool -> Maybe DeviceConfigurationType
$sel:deletionProtection:UpdateUserPool' :: UpdateUserPool -> Maybe DeletionProtectionType
$sel:autoVerifiedAttributes:UpdateUserPool' :: UpdateUserPool -> Maybe [VerifiedAttributeType]
$sel:adminCreateUserConfig:UpdateUserPool' :: UpdateUserPool -> Maybe AdminCreateUserConfigType
$sel:accountRecoverySetting:UpdateUserPool' :: UpdateUserPool -> Maybe AccountRecoverySettingType
..} =
    [Pair] -> Value
Data.object
      ( forall a. [Maybe a] -> [a]
Prelude.catMaybes
          [ (Key
"AccountRecoverySetting" 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 AccountRecoverySettingType
accountRecoverySetting,
            (Key
"AdminCreateUserConfig" 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 AdminCreateUserConfigType
adminCreateUserConfig,
            (Key
"AutoVerifiedAttributes" 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 [VerifiedAttributeType]
autoVerifiedAttributes,
            (Key
"DeletionProtection" 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 DeletionProtectionType
deletionProtection,
            (Key
"DeviceConfiguration" 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 DeviceConfigurationType
deviceConfiguration,
            (Key
"EmailConfiguration" 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 EmailConfigurationType
emailConfiguration,
            (Key
"EmailVerificationMessage" 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
emailVerificationMessage,
            (Key
"EmailVerificationSubject" 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
emailVerificationSubject,
            (Key
"LambdaConfig" 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 LambdaConfigType
lambdaConfig,
            (Key
"MfaConfiguration" 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 UserPoolMfaType
mfaConfiguration,
            (Key
"Policies" 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 UserPoolPolicyType
policies,
            (Key
"SmsAuthenticationMessage" 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
smsAuthenticationMessage,
            (Key
"SmsConfiguration" 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 SmsConfigurationType
smsConfiguration,
            (Key
"SmsVerificationMessage" 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
smsVerificationMessage,
            (Key
"UserAttributeUpdateSettings" 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 UserAttributeUpdateSettingsType
userAttributeUpdateSettings,
            (Key
"UserPoolAddOns" 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 UserPoolAddOnsType
userPoolAddOns,
            (Key
"UserPoolTags" 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 (HashMap Text Text)
userPoolTags,
            (Key
"VerificationMessageTemplate" 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 VerificationMessageTemplateType
verificationMessageTemplate,
            forall a. a -> Maybe a
Prelude.Just (Key
"UserPoolId" forall kv v. (KeyValue kv, ToJSON v) => Key -> v -> kv
Data..= Text
userPoolId)
          ]
      )

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

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

-- | Represents the response from the server when you make a request to
-- update the user pool.
--
-- /See:/ 'newUpdateUserPoolResponse' smart constructor.
data UpdateUserPoolResponse = UpdateUserPoolResponse'
  { -- | The response's http status code.
    UpdateUserPoolResponse -> Int
httpStatus :: Prelude.Int
  }
  deriving (UpdateUserPoolResponse -> UpdateUserPoolResponse -> Bool
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: UpdateUserPoolResponse -> UpdateUserPoolResponse -> Bool
$c/= :: UpdateUserPoolResponse -> UpdateUserPoolResponse -> Bool
== :: UpdateUserPoolResponse -> UpdateUserPoolResponse -> Bool
$c== :: UpdateUserPoolResponse -> UpdateUserPoolResponse -> Bool
Prelude.Eq, ReadPrec [UpdateUserPoolResponse]
ReadPrec UpdateUserPoolResponse
Int -> ReadS UpdateUserPoolResponse
ReadS [UpdateUserPoolResponse]
forall a.
(Int -> ReadS a)
-> ReadS [a] -> ReadPrec a -> ReadPrec [a] -> Read a
readListPrec :: ReadPrec [UpdateUserPoolResponse]
$creadListPrec :: ReadPrec [UpdateUserPoolResponse]
readPrec :: ReadPrec UpdateUserPoolResponse
$creadPrec :: ReadPrec UpdateUserPoolResponse
readList :: ReadS [UpdateUserPoolResponse]
$creadList :: ReadS [UpdateUserPoolResponse]
readsPrec :: Int -> ReadS UpdateUserPoolResponse
$creadsPrec :: Int -> ReadS UpdateUserPoolResponse
Prelude.Read, Int -> UpdateUserPoolResponse -> ShowS
[UpdateUserPoolResponse] -> ShowS
UpdateUserPoolResponse -> String
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [UpdateUserPoolResponse] -> ShowS
$cshowList :: [UpdateUserPoolResponse] -> ShowS
show :: UpdateUserPoolResponse -> String
$cshow :: UpdateUserPoolResponse -> String
showsPrec :: Int -> UpdateUserPoolResponse -> ShowS
$cshowsPrec :: Int -> UpdateUserPoolResponse -> ShowS
Prelude.Show, forall x. Rep UpdateUserPoolResponse x -> UpdateUserPoolResponse
forall x. UpdateUserPoolResponse -> Rep UpdateUserPoolResponse x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cto :: forall x. Rep UpdateUserPoolResponse x -> UpdateUserPoolResponse
$cfrom :: forall x. UpdateUserPoolResponse -> Rep UpdateUserPoolResponse x
Prelude.Generic)

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

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

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