module Stratosphere.Cognito.UserPool (
module Exports, UserPool(..), mkUserPool
) where
import qualified Data.Aeson as JSON
import qualified Stratosphere.Prelude as Prelude
import Stratosphere.Property
import {-# SOURCE #-} Stratosphere.Cognito.UserPool.AccountRecoverySettingProperty as Exports
import {-# SOURCE #-} Stratosphere.Cognito.UserPool.AdminCreateUserConfigProperty as Exports
import {-# SOURCE #-} Stratosphere.Cognito.UserPool.DeviceConfigurationProperty as Exports
import {-# SOURCE #-} Stratosphere.Cognito.UserPool.EmailConfigurationProperty as Exports
import {-# SOURCE #-} Stratosphere.Cognito.UserPool.LambdaConfigProperty as Exports
import {-# SOURCE #-} Stratosphere.Cognito.UserPool.PoliciesProperty as Exports
import {-# SOURCE #-} Stratosphere.Cognito.UserPool.SchemaAttributeProperty as Exports
import {-# SOURCE #-} Stratosphere.Cognito.UserPool.SmsConfigurationProperty as Exports
import {-# SOURCE #-} Stratosphere.Cognito.UserPool.UserAttributeUpdateSettingsProperty as Exports
import {-# SOURCE #-} Stratosphere.Cognito.UserPool.UserPoolAddOnsProperty as Exports
import {-# SOURCE #-} Stratosphere.Cognito.UserPool.UsernameConfigurationProperty as Exports
import {-# SOURCE #-} Stratosphere.Cognito.UserPool.VerificationMessageTemplateProperty as Exports
import Stratosphere.ResourceProperties
import Stratosphere.Value
data UserPool
=
UserPool {UserPool -> ()
haddock_workaround_ :: (),
UserPool -> Maybe AccountRecoverySettingProperty
accountRecoverySetting :: (Prelude.Maybe AccountRecoverySettingProperty),
UserPool -> Maybe AdminCreateUserConfigProperty
adminCreateUserConfig :: (Prelude.Maybe AdminCreateUserConfigProperty),
UserPool -> Maybe (ValueList Text)
aliasAttributes :: (Prelude.Maybe (ValueList Prelude.Text)),
UserPool -> Maybe (ValueList Text)
autoVerifiedAttributes :: (Prelude.Maybe (ValueList Prelude.Text)),
UserPool -> Maybe (Value Text)
deletionProtection :: (Prelude.Maybe (Value Prelude.Text)),
UserPool -> Maybe DeviceConfigurationProperty
deviceConfiguration :: (Prelude.Maybe DeviceConfigurationProperty),
UserPool -> Maybe (Value Text)
emailAuthenticationMessage :: (Prelude.Maybe (Value Prelude.Text)),
UserPool -> Maybe (Value Text)
emailAuthenticationSubject :: (Prelude.Maybe (Value Prelude.Text)),
UserPool -> Maybe EmailConfigurationProperty
emailConfiguration :: (Prelude.Maybe EmailConfigurationProperty),
UserPool -> Maybe (Value Text)
emailVerificationMessage :: (Prelude.Maybe (Value Prelude.Text)),
UserPool -> Maybe (Value Text)
emailVerificationSubject :: (Prelude.Maybe (Value Prelude.Text)),
UserPool -> Maybe (ValueList Text)
enabledMfas :: (Prelude.Maybe (ValueList Prelude.Text)),
UserPool -> Maybe LambdaConfigProperty
lambdaConfig :: (Prelude.Maybe LambdaConfigProperty),
UserPool -> Maybe (Value Text)
mfaConfiguration :: (Prelude.Maybe (Value Prelude.Text)),
UserPool -> Maybe PoliciesProperty
policies :: (Prelude.Maybe PoliciesProperty),
UserPool -> Maybe [SchemaAttributeProperty]
schema :: (Prelude.Maybe [SchemaAttributeProperty]),
UserPool -> Maybe (Value Text)
smsAuthenticationMessage :: (Prelude.Maybe (Value Prelude.Text)),
UserPool -> Maybe SmsConfigurationProperty
smsConfiguration :: (Prelude.Maybe SmsConfigurationProperty),
UserPool -> Maybe (Value Text)
smsVerificationMessage :: (Prelude.Maybe (Value Prelude.Text)),
UserPool -> Maybe UserAttributeUpdateSettingsProperty
userAttributeUpdateSettings :: (Prelude.Maybe UserAttributeUpdateSettingsProperty),
UserPool -> Maybe UserPoolAddOnsProperty
userPoolAddOns :: (Prelude.Maybe UserPoolAddOnsProperty),
UserPool -> Maybe (Value Text)
userPoolName :: (Prelude.Maybe (Value Prelude.Text)),
UserPool -> Maybe (Map Text (Value Text))
userPoolTags :: (Prelude.Maybe (Prelude.Map Prelude.Text (Value Prelude.Text))),
UserPool -> Maybe (Value Text)
userPoolTier :: (Prelude.Maybe (Value Prelude.Text)),
UserPool -> Maybe (ValueList Text)
usernameAttributes :: (Prelude.Maybe (ValueList Prelude.Text)),
UserPool -> Maybe UsernameConfigurationProperty
usernameConfiguration :: (Prelude.Maybe UsernameConfigurationProperty),
UserPool -> Maybe VerificationMessageTemplateProperty
verificationMessageTemplate :: (Prelude.Maybe VerificationMessageTemplateProperty),
UserPool -> Maybe (Value Text)
webAuthnRelyingPartyID :: (Prelude.Maybe (Value Prelude.Text)),
UserPool -> Maybe (Value Text)
webAuthnUserVerification :: (Prelude.Maybe (Value Prelude.Text))}
deriving stock (UserPool -> UserPool -> Bool
(UserPool -> UserPool -> Bool)
-> (UserPool -> UserPool -> Bool) -> Eq UserPool
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
$c== :: UserPool -> UserPool -> Bool
== :: UserPool -> UserPool -> Bool
$c/= :: UserPool -> UserPool -> Bool
/= :: UserPool -> UserPool -> Bool
Prelude.Eq, Int -> UserPool -> ShowS
[UserPool] -> ShowS
UserPool -> String
(Int -> UserPool -> ShowS)
-> (UserPool -> String) -> ([UserPool] -> ShowS) -> Show UserPool
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
$cshowsPrec :: Int -> UserPool -> ShowS
showsPrec :: Int -> UserPool -> ShowS
$cshow :: UserPool -> String
show :: UserPool -> String
$cshowList :: [UserPool] -> ShowS
showList :: [UserPool] -> ShowS
Prelude.Show)
mkUserPool :: UserPool
mkUserPool :: UserPool
mkUserPool
= UserPool
{haddock_workaround_ :: ()
haddock_workaround_ = (),
accountRecoverySetting :: Maybe AccountRecoverySettingProperty
accountRecoverySetting = Maybe AccountRecoverySettingProperty
forall a. Maybe a
Prelude.Nothing,
adminCreateUserConfig :: Maybe AdminCreateUserConfigProperty
adminCreateUserConfig = Maybe AdminCreateUserConfigProperty
forall a. Maybe a
Prelude.Nothing,
aliasAttributes :: Maybe (ValueList Text)
aliasAttributes = Maybe (ValueList Text)
forall a. Maybe a
Prelude.Nothing,
autoVerifiedAttributes :: Maybe (ValueList Text)
autoVerifiedAttributes = Maybe (ValueList Text)
forall a. Maybe a
Prelude.Nothing,
deletionProtection :: Maybe (Value Text)
deletionProtection = Maybe (Value Text)
forall a. Maybe a
Prelude.Nothing,
deviceConfiguration :: Maybe DeviceConfigurationProperty
deviceConfiguration = Maybe DeviceConfigurationProperty
forall a. Maybe a
Prelude.Nothing,
emailAuthenticationMessage :: Maybe (Value Text)
emailAuthenticationMessage = Maybe (Value Text)
forall a. Maybe a
Prelude.Nothing,
emailAuthenticationSubject :: Maybe (Value Text)
emailAuthenticationSubject = Maybe (Value Text)
forall a. Maybe a
Prelude.Nothing,
emailConfiguration :: Maybe EmailConfigurationProperty
emailConfiguration = Maybe EmailConfigurationProperty
forall a. Maybe a
Prelude.Nothing,
emailVerificationMessage :: Maybe (Value Text)
emailVerificationMessage = Maybe (Value Text)
forall a. Maybe a
Prelude.Nothing,
emailVerificationSubject :: Maybe (Value Text)
emailVerificationSubject = Maybe (Value Text)
forall a. Maybe a
Prelude.Nothing,
enabledMfas :: Maybe (ValueList Text)
enabledMfas = Maybe (ValueList Text)
forall a. Maybe a
Prelude.Nothing, lambdaConfig :: Maybe LambdaConfigProperty
lambdaConfig = Maybe LambdaConfigProperty
forall a. Maybe a
Prelude.Nothing,
mfaConfiguration :: Maybe (Value Text)
mfaConfiguration = Maybe (Value Text)
forall a. Maybe a
Prelude.Nothing, policies :: Maybe PoliciesProperty
policies = Maybe PoliciesProperty
forall a. Maybe a
Prelude.Nothing,
schema :: Maybe [SchemaAttributeProperty]
schema = Maybe [SchemaAttributeProperty]
forall a. Maybe a
Prelude.Nothing,
smsAuthenticationMessage :: Maybe (Value Text)
smsAuthenticationMessage = Maybe (Value Text)
forall a. Maybe a
Prelude.Nothing,
smsConfiguration :: Maybe SmsConfigurationProperty
smsConfiguration = Maybe SmsConfigurationProperty
forall a. Maybe a
Prelude.Nothing,
smsVerificationMessage :: Maybe (Value Text)
smsVerificationMessage = Maybe (Value Text)
forall a. Maybe a
Prelude.Nothing,
userAttributeUpdateSettings :: Maybe UserAttributeUpdateSettingsProperty
userAttributeUpdateSettings = Maybe UserAttributeUpdateSettingsProperty
forall a. Maybe a
Prelude.Nothing,
userPoolAddOns :: Maybe UserPoolAddOnsProperty
userPoolAddOns = Maybe UserPoolAddOnsProperty
forall a. Maybe a
Prelude.Nothing, userPoolName :: Maybe (Value Text)
userPoolName = Maybe (Value Text)
forall a. Maybe a
Prelude.Nothing,
userPoolTags :: Maybe (Map Text (Value Text))
userPoolTags = Maybe (Map Text (Value Text))
forall a. Maybe a
Prelude.Nothing, userPoolTier :: Maybe (Value Text)
userPoolTier = Maybe (Value Text)
forall a. Maybe a
Prelude.Nothing,
usernameAttributes :: Maybe (ValueList Text)
usernameAttributes = Maybe (ValueList Text)
forall a. Maybe a
Prelude.Nothing,
usernameConfiguration :: Maybe UsernameConfigurationProperty
usernameConfiguration = Maybe UsernameConfigurationProperty
forall a. Maybe a
Prelude.Nothing,
verificationMessageTemplate :: Maybe VerificationMessageTemplateProperty
verificationMessageTemplate = Maybe VerificationMessageTemplateProperty
forall a. Maybe a
Prelude.Nothing,
webAuthnRelyingPartyID :: Maybe (Value Text)
webAuthnRelyingPartyID = Maybe (Value Text)
forall a. Maybe a
Prelude.Nothing,
webAuthnUserVerification :: Maybe (Value Text)
webAuthnUserVerification = Maybe (Value Text)
forall a. Maybe a
Prelude.Nothing}
instance ToResourceProperties UserPool where
toResourceProperties :: UserPool -> ResourceProperties
toResourceProperties UserPool {Maybe [SchemaAttributeProperty]
Maybe (Map Text (Value Text))
Maybe (ValueList Text)
Maybe (Value Text)
Maybe DeviceConfigurationProperty
Maybe EmailConfigurationProperty
Maybe AdminCreateUserConfigProperty
Maybe LambdaConfigProperty
Maybe AccountRecoverySettingProperty
Maybe PoliciesProperty
Maybe SmsConfigurationProperty
Maybe UserAttributeUpdateSettingsProperty
Maybe UserPoolAddOnsProperty
Maybe UsernameConfigurationProperty
Maybe VerificationMessageTemplateProperty
()
haddock_workaround_ :: UserPool -> ()
accountRecoverySetting :: UserPool -> Maybe AccountRecoverySettingProperty
adminCreateUserConfig :: UserPool -> Maybe AdminCreateUserConfigProperty
aliasAttributes :: UserPool -> Maybe (ValueList Text)
autoVerifiedAttributes :: UserPool -> Maybe (ValueList Text)
deletionProtection :: UserPool -> Maybe (Value Text)
deviceConfiguration :: UserPool -> Maybe DeviceConfigurationProperty
emailAuthenticationMessage :: UserPool -> Maybe (Value Text)
emailAuthenticationSubject :: UserPool -> Maybe (Value Text)
emailConfiguration :: UserPool -> Maybe EmailConfigurationProperty
emailVerificationMessage :: UserPool -> Maybe (Value Text)
emailVerificationSubject :: UserPool -> Maybe (Value Text)
enabledMfas :: UserPool -> Maybe (ValueList Text)
lambdaConfig :: UserPool -> Maybe LambdaConfigProperty
mfaConfiguration :: UserPool -> Maybe (Value Text)
policies :: UserPool -> Maybe PoliciesProperty
schema :: UserPool -> Maybe [SchemaAttributeProperty]
smsAuthenticationMessage :: UserPool -> Maybe (Value Text)
smsConfiguration :: UserPool -> Maybe SmsConfigurationProperty
smsVerificationMessage :: UserPool -> Maybe (Value Text)
userAttributeUpdateSettings :: UserPool -> Maybe UserAttributeUpdateSettingsProperty
userPoolAddOns :: UserPool -> Maybe UserPoolAddOnsProperty
userPoolName :: UserPool -> Maybe (Value Text)
userPoolTags :: UserPool -> Maybe (Map Text (Value Text))
userPoolTier :: UserPool -> Maybe (Value Text)
usernameAttributes :: UserPool -> Maybe (ValueList Text)
usernameConfiguration :: UserPool -> Maybe UsernameConfigurationProperty
verificationMessageTemplate :: UserPool -> Maybe VerificationMessageTemplateProperty
webAuthnRelyingPartyID :: UserPool -> Maybe (Value Text)
webAuthnUserVerification :: UserPool -> Maybe (Value Text)
haddock_workaround_ :: ()
accountRecoverySetting :: Maybe AccountRecoverySettingProperty
adminCreateUserConfig :: Maybe AdminCreateUserConfigProperty
aliasAttributes :: Maybe (ValueList Text)
autoVerifiedAttributes :: Maybe (ValueList Text)
deletionProtection :: Maybe (Value Text)
deviceConfiguration :: Maybe DeviceConfigurationProperty
emailAuthenticationMessage :: Maybe (Value Text)
emailAuthenticationSubject :: Maybe (Value Text)
emailConfiguration :: Maybe EmailConfigurationProperty
emailVerificationMessage :: Maybe (Value Text)
emailVerificationSubject :: Maybe (Value Text)
enabledMfas :: Maybe (ValueList Text)
lambdaConfig :: Maybe LambdaConfigProperty
mfaConfiguration :: Maybe (Value Text)
policies :: Maybe PoliciesProperty
schema :: Maybe [SchemaAttributeProperty]
smsAuthenticationMessage :: Maybe (Value Text)
smsConfiguration :: Maybe SmsConfigurationProperty
smsVerificationMessage :: Maybe (Value Text)
userAttributeUpdateSettings :: Maybe UserAttributeUpdateSettingsProperty
userPoolAddOns :: Maybe UserPoolAddOnsProperty
userPoolName :: Maybe (Value Text)
userPoolTags :: Maybe (Map Text (Value Text))
userPoolTier :: Maybe (Value Text)
usernameAttributes :: Maybe (ValueList Text)
usernameConfiguration :: Maybe UsernameConfigurationProperty
verificationMessageTemplate :: Maybe VerificationMessageTemplateProperty
webAuthnRelyingPartyID :: Maybe (Value Text)
webAuthnUserVerification :: Maybe (Value Text)
..}
= ResourceProperties
{awsType :: Text
awsType = Text
"AWS::Cognito::UserPool", supportsTags :: Bool
supportsTags = Bool
Prelude.False,
properties :: Object
properties = [Item Object] -> Object
forall l. IsList l => [Item l] -> l
Prelude.fromList
([Maybe (Key, Value)] -> [(Key, Value)]
forall a. [Maybe a] -> [a]
Prelude.catMaybes
[Key -> AccountRecoverySettingProperty -> (Key, Value)
forall v. ToJSON v => Key -> v -> (Key, Value)
forall e kv v. (KeyValue e kv, ToJSON v) => Key -> v -> kv
(JSON..=) Key
"AccountRecoverySetting"
(AccountRecoverySettingProperty -> (Key, Value))
-> Maybe AccountRecoverySettingProperty -> Maybe (Key, Value)
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
Prelude.<$> Maybe AccountRecoverySettingProperty
accountRecoverySetting,
Key -> AdminCreateUserConfigProperty -> (Key, Value)
forall v. ToJSON v => Key -> v -> (Key, Value)
forall e kv v. (KeyValue e kv, ToJSON v) => Key -> v -> kv
(JSON..=) Key
"AdminCreateUserConfig"
(AdminCreateUserConfigProperty -> (Key, Value))
-> Maybe AdminCreateUserConfigProperty -> Maybe (Key, Value)
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
Prelude.<$> Maybe AdminCreateUserConfigProperty
adminCreateUserConfig,
Key -> ValueList Text -> (Key, Value)
forall v. ToJSON v => Key -> v -> (Key, Value)
forall e kv v. (KeyValue e kv, ToJSON v) => Key -> v -> kv
(JSON..=) Key
"AliasAttributes" (ValueList Text -> (Key, Value))
-> Maybe (ValueList Text) -> Maybe (Key, Value)
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
Prelude.<$> Maybe (ValueList Text)
aliasAttributes,
Key -> ValueList Text -> (Key, Value)
forall v. ToJSON v => Key -> v -> (Key, Value)
forall e kv v. (KeyValue e kv, ToJSON v) => Key -> v -> kv
(JSON..=) Key
"AutoVerifiedAttributes"
(ValueList Text -> (Key, Value))
-> Maybe (ValueList Text) -> Maybe (Key, Value)
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
Prelude.<$> Maybe (ValueList Text)
autoVerifiedAttributes,
Key -> Value Text -> (Key, Value)
forall v. ToJSON v => Key -> v -> (Key, Value)
forall e kv v. (KeyValue e kv, ToJSON v) => Key -> v -> kv
(JSON..=) Key
"DeletionProtection" (Value Text -> (Key, Value))
-> Maybe (Value Text) -> Maybe (Key, Value)
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
Prelude.<$> Maybe (Value Text)
deletionProtection,
Key -> DeviceConfigurationProperty -> (Key, Value)
forall v. ToJSON v => Key -> v -> (Key, Value)
forall e kv v. (KeyValue e kv, ToJSON v) => Key -> v -> kv
(JSON..=) Key
"DeviceConfiguration" (DeviceConfigurationProperty -> (Key, Value))
-> Maybe DeviceConfigurationProperty -> Maybe (Key, Value)
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
Prelude.<$> Maybe DeviceConfigurationProperty
deviceConfiguration,
Key -> Value Text -> (Key, Value)
forall v. ToJSON v => Key -> v -> (Key, Value)
forall e kv v. (KeyValue e kv, ToJSON v) => Key -> v -> kv
(JSON..=) Key
"EmailAuthenticationMessage"
(Value Text -> (Key, Value))
-> Maybe (Value Text) -> Maybe (Key, Value)
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
Prelude.<$> Maybe (Value Text)
emailAuthenticationMessage,
Key -> Value Text -> (Key, Value)
forall v. ToJSON v => Key -> v -> (Key, Value)
forall e kv v. (KeyValue e kv, ToJSON v) => Key -> v -> kv
(JSON..=) Key
"EmailAuthenticationSubject"
(Value Text -> (Key, Value))
-> Maybe (Value Text) -> Maybe (Key, Value)
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
Prelude.<$> Maybe (Value Text)
emailAuthenticationSubject,
Key -> EmailConfigurationProperty -> (Key, Value)
forall v. ToJSON v => Key -> v -> (Key, Value)
forall e kv v. (KeyValue e kv, ToJSON v) => Key -> v -> kv
(JSON..=) Key
"EmailConfiguration" (EmailConfigurationProperty -> (Key, Value))
-> Maybe EmailConfigurationProperty -> Maybe (Key, Value)
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
Prelude.<$> Maybe EmailConfigurationProperty
emailConfiguration,
Key -> Value Text -> (Key, Value)
forall v. ToJSON v => Key -> v -> (Key, Value)
forall e kv v. (KeyValue e kv, ToJSON v) => Key -> v -> kv
(JSON..=) Key
"EmailVerificationMessage"
(Value Text -> (Key, Value))
-> Maybe (Value Text) -> Maybe (Key, Value)
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
Prelude.<$> Maybe (Value Text)
emailVerificationMessage,
Key -> Value Text -> (Key, Value)
forall v. ToJSON v => Key -> v -> (Key, Value)
forall e kv v. (KeyValue e kv, ToJSON v) => Key -> v -> kv
(JSON..=) Key
"EmailVerificationSubject"
(Value Text -> (Key, Value))
-> Maybe (Value Text) -> Maybe (Key, Value)
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
Prelude.<$> Maybe (Value Text)
emailVerificationSubject,
Key -> ValueList Text -> (Key, Value)
forall v. ToJSON v => Key -> v -> (Key, Value)
forall e kv v. (KeyValue e kv, ToJSON v) => Key -> v -> kv
(JSON..=) Key
"EnabledMfas" (ValueList Text -> (Key, Value))
-> Maybe (ValueList Text) -> Maybe (Key, Value)
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
Prelude.<$> Maybe (ValueList Text)
enabledMfas,
Key -> LambdaConfigProperty -> (Key, Value)
forall v. ToJSON v => Key -> v -> (Key, Value)
forall e kv v. (KeyValue e kv, ToJSON v) => Key -> v -> kv
(JSON..=) Key
"LambdaConfig" (LambdaConfigProperty -> (Key, Value))
-> Maybe LambdaConfigProperty -> Maybe (Key, Value)
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
Prelude.<$> Maybe LambdaConfigProperty
lambdaConfig,
Key -> Value Text -> (Key, Value)
forall v. ToJSON v => Key -> v -> (Key, Value)
forall e kv v. (KeyValue e kv, ToJSON v) => Key -> v -> kv
(JSON..=) Key
"MfaConfiguration" (Value Text -> (Key, Value))
-> Maybe (Value Text) -> Maybe (Key, Value)
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
Prelude.<$> Maybe (Value Text)
mfaConfiguration,
Key -> PoliciesProperty -> (Key, Value)
forall v. ToJSON v => Key -> v -> (Key, Value)
forall e kv v. (KeyValue e kv, ToJSON v) => Key -> v -> kv
(JSON..=) Key
"Policies" (PoliciesProperty -> (Key, Value))
-> Maybe PoliciesProperty -> Maybe (Key, Value)
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
Prelude.<$> Maybe PoliciesProperty
policies,
Key -> [SchemaAttributeProperty] -> (Key, Value)
forall v. ToJSON v => Key -> v -> (Key, Value)
forall e kv v. (KeyValue e kv, ToJSON v) => Key -> v -> kv
(JSON..=) Key
"Schema" ([SchemaAttributeProperty] -> (Key, Value))
-> Maybe [SchemaAttributeProperty] -> Maybe (Key, Value)
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
Prelude.<$> Maybe [SchemaAttributeProperty]
schema,
Key -> Value Text -> (Key, Value)
forall v. ToJSON v => Key -> v -> (Key, Value)
forall e kv v. (KeyValue e kv, ToJSON v) => Key -> v -> kv
(JSON..=) Key
"SmsAuthenticationMessage"
(Value Text -> (Key, Value))
-> Maybe (Value Text) -> Maybe (Key, Value)
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
Prelude.<$> Maybe (Value Text)
smsAuthenticationMessage,
Key -> SmsConfigurationProperty -> (Key, Value)
forall v. ToJSON v => Key -> v -> (Key, Value)
forall e kv v. (KeyValue e kv, ToJSON v) => Key -> v -> kv
(JSON..=) Key
"SmsConfiguration" (SmsConfigurationProperty -> (Key, Value))
-> Maybe SmsConfigurationProperty -> Maybe (Key, Value)
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
Prelude.<$> Maybe SmsConfigurationProperty
smsConfiguration,
Key -> Value Text -> (Key, Value)
forall v. ToJSON v => Key -> v -> (Key, Value)
forall e kv v. (KeyValue e kv, ToJSON v) => Key -> v -> kv
(JSON..=) Key
"SmsVerificationMessage"
(Value Text -> (Key, Value))
-> Maybe (Value Text) -> Maybe (Key, Value)
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
Prelude.<$> Maybe (Value Text)
smsVerificationMessage,
Key -> UserAttributeUpdateSettingsProperty -> (Key, Value)
forall v. ToJSON v => Key -> v -> (Key, Value)
forall e kv v. (KeyValue e kv, ToJSON v) => Key -> v -> kv
(JSON..=) Key
"UserAttributeUpdateSettings"
(UserAttributeUpdateSettingsProperty -> (Key, Value))
-> Maybe UserAttributeUpdateSettingsProperty -> Maybe (Key, Value)
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
Prelude.<$> Maybe UserAttributeUpdateSettingsProperty
userAttributeUpdateSettings,
Key -> UserPoolAddOnsProperty -> (Key, Value)
forall v. ToJSON v => Key -> v -> (Key, Value)
forall e kv v. (KeyValue e kv, ToJSON v) => Key -> v -> kv
(JSON..=) Key
"UserPoolAddOns" (UserPoolAddOnsProperty -> (Key, Value))
-> Maybe UserPoolAddOnsProperty -> Maybe (Key, Value)
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
Prelude.<$> Maybe UserPoolAddOnsProperty
userPoolAddOns,
Key -> Value Text -> (Key, Value)
forall v. ToJSON v => Key -> v -> (Key, Value)
forall e kv v. (KeyValue e kv, ToJSON v) => Key -> v -> kv
(JSON..=) Key
"UserPoolName" (Value Text -> (Key, Value))
-> Maybe (Value Text) -> Maybe (Key, Value)
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
Prelude.<$> Maybe (Value Text)
userPoolName,
Key -> Map Text (Value Text) -> (Key, Value)
forall v. ToJSON v => Key -> v -> (Key, Value)
forall e kv v. (KeyValue e kv, ToJSON v) => Key -> v -> kv
(JSON..=) Key
"UserPoolTags" (Map Text (Value Text) -> (Key, Value))
-> Maybe (Map Text (Value Text)) -> Maybe (Key, Value)
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
Prelude.<$> Maybe (Map Text (Value Text))
userPoolTags,
Key -> Value Text -> (Key, Value)
forall v. ToJSON v => Key -> v -> (Key, Value)
forall e kv v. (KeyValue e kv, ToJSON v) => Key -> v -> kv
(JSON..=) Key
"UserPoolTier" (Value Text -> (Key, Value))
-> Maybe (Value Text) -> Maybe (Key, Value)
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
Prelude.<$> Maybe (Value Text)
userPoolTier,
Key -> ValueList Text -> (Key, Value)
forall v. ToJSON v => Key -> v -> (Key, Value)
forall e kv v. (KeyValue e kv, ToJSON v) => Key -> v -> kv
(JSON..=) Key
"UsernameAttributes" (ValueList Text -> (Key, Value))
-> Maybe (ValueList Text) -> Maybe (Key, Value)
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
Prelude.<$> Maybe (ValueList Text)
usernameAttributes,
Key -> UsernameConfigurationProperty -> (Key, Value)
forall v. ToJSON v => Key -> v -> (Key, Value)
forall e kv v. (KeyValue e kv, ToJSON v) => Key -> v -> kv
(JSON..=) Key
"UsernameConfiguration"
(UsernameConfigurationProperty -> (Key, Value))
-> Maybe UsernameConfigurationProperty -> Maybe (Key, Value)
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
Prelude.<$> Maybe UsernameConfigurationProperty
usernameConfiguration,
Key -> VerificationMessageTemplateProperty -> (Key, Value)
forall v. ToJSON v => Key -> v -> (Key, Value)
forall e kv v. (KeyValue e kv, ToJSON v) => Key -> v -> kv
(JSON..=) Key
"VerificationMessageTemplate"
(VerificationMessageTemplateProperty -> (Key, Value))
-> Maybe VerificationMessageTemplateProperty -> Maybe (Key, Value)
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
Prelude.<$> Maybe VerificationMessageTemplateProperty
verificationMessageTemplate,
Key -> Value Text -> (Key, Value)
forall v. ToJSON v => Key -> v -> (Key, Value)
forall e kv v. (KeyValue e kv, ToJSON v) => Key -> v -> kv
(JSON..=) Key
"WebAuthnRelyingPartyID"
(Value Text -> (Key, Value))
-> Maybe (Value Text) -> Maybe (Key, Value)
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
Prelude.<$> Maybe (Value Text)
webAuthnRelyingPartyID,
Key -> Value Text -> (Key, Value)
forall v. ToJSON v => Key -> v -> (Key, Value)
forall e kv v. (KeyValue e kv, ToJSON v) => Key -> v -> kv
(JSON..=) Key
"WebAuthnUserVerification"
(Value Text -> (Key, Value))
-> Maybe (Value Text) -> Maybe (Key, Value)
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
Prelude.<$> Maybe (Value Text)
webAuthnUserVerification])}
instance JSON.ToJSON UserPool where
toJSON :: UserPool -> Value
toJSON UserPool {Maybe [SchemaAttributeProperty]
Maybe (Map Text (Value Text))
Maybe (ValueList Text)
Maybe (Value Text)
Maybe DeviceConfigurationProperty
Maybe EmailConfigurationProperty
Maybe AdminCreateUserConfigProperty
Maybe LambdaConfigProperty
Maybe AccountRecoverySettingProperty
Maybe PoliciesProperty
Maybe SmsConfigurationProperty
Maybe UserAttributeUpdateSettingsProperty
Maybe UserPoolAddOnsProperty
Maybe UsernameConfigurationProperty
Maybe VerificationMessageTemplateProperty
()
haddock_workaround_ :: UserPool -> ()
accountRecoverySetting :: UserPool -> Maybe AccountRecoverySettingProperty
adminCreateUserConfig :: UserPool -> Maybe AdminCreateUserConfigProperty
aliasAttributes :: UserPool -> Maybe (ValueList Text)
autoVerifiedAttributes :: UserPool -> Maybe (ValueList Text)
deletionProtection :: UserPool -> Maybe (Value Text)
deviceConfiguration :: UserPool -> Maybe DeviceConfigurationProperty
emailAuthenticationMessage :: UserPool -> Maybe (Value Text)
emailAuthenticationSubject :: UserPool -> Maybe (Value Text)
emailConfiguration :: UserPool -> Maybe EmailConfigurationProperty
emailVerificationMessage :: UserPool -> Maybe (Value Text)
emailVerificationSubject :: UserPool -> Maybe (Value Text)
enabledMfas :: UserPool -> Maybe (ValueList Text)
lambdaConfig :: UserPool -> Maybe LambdaConfigProperty
mfaConfiguration :: UserPool -> Maybe (Value Text)
policies :: UserPool -> Maybe PoliciesProperty
schema :: UserPool -> Maybe [SchemaAttributeProperty]
smsAuthenticationMessage :: UserPool -> Maybe (Value Text)
smsConfiguration :: UserPool -> Maybe SmsConfigurationProperty
smsVerificationMessage :: UserPool -> Maybe (Value Text)
userAttributeUpdateSettings :: UserPool -> Maybe UserAttributeUpdateSettingsProperty
userPoolAddOns :: UserPool -> Maybe UserPoolAddOnsProperty
userPoolName :: UserPool -> Maybe (Value Text)
userPoolTags :: UserPool -> Maybe (Map Text (Value Text))
userPoolTier :: UserPool -> Maybe (Value Text)
usernameAttributes :: UserPool -> Maybe (ValueList Text)
usernameConfiguration :: UserPool -> Maybe UsernameConfigurationProperty
verificationMessageTemplate :: UserPool -> Maybe VerificationMessageTemplateProperty
webAuthnRelyingPartyID :: UserPool -> Maybe (Value Text)
webAuthnUserVerification :: UserPool -> Maybe (Value Text)
haddock_workaround_ :: ()
accountRecoverySetting :: Maybe AccountRecoverySettingProperty
adminCreateUserConfig :: Maybe AdminCreateUserConfigProperty
aliasAttributes :: Maybe (ValueList Text)
autoVerifiedAttributes :: Maybe (ValueList Text)
deletionProtection :: Maybe (Value Text)
deviceConfiguration :: Maybe DeviceConfigurationProperty
emailAuthenticationMessage :: Maybe (Value Text)
emailAuthenticationSubject :: Maybe (Value Text)
emailConfiguration :: Maybe EmailConfigurationProperty
emailVerificationMessage :: Maybe (Value Text)
emailVerificationSubject :: Maybe (Value Text)
enabledMfas :: Maybe (ValueList Text)
lambdaConfig :: Maybe LambdaConfigProperty
mfaConfiguration :: Maybe (Value Text)
policies :: Maybe PoliciesProperty
schema :: Maybe [SchemaAttributeProperty]
smsAuthenticationMessage :: Maybe (Value Text)
smsConfiguration :: Maybe SmsConfigurationProperty
smsVerificationMessage :: Maybe (Value Text)
userAttributeUpdateSettings :: Maybe UserAttributeUpdateSettingsProperty
userPoolAddOns :: Maybe UserPoolAddOnsProperty
userPoolName :: Maybe (Value Text)
userPoolTags :: Maybe (Map Text (Value Text))
userPoolTier :: Maybe (Value Text)
usernameAttributes :: Maybe (ValueList Text)
usernameConfiguration :: Maybe UsernameConfigurationProperty
verificationMessageTemplate :: Maybe VerificationMessageTemplateProperty
webAuthnRelyingPartyID :: Maybe (Value Text)
webAuthnUserVerification :: Maybe (Value Text)
..}
= [(Key, Value)] -> Value
JSON.object
([Item [(Key, Value)]] -> [(Key, Value)]
forall l. IsList l => [Item l] -> l
Prelude.fromList
([Maybe (Key, Value)] -> [(Key, Value)]
forall a. [Maybe a] -> [a]
Prelude.catMaybes
[Key -> AccountRecoverySettingProperty -> (Key, Value)
forall v. ToJSON v => Key -> v -> (Key, Value)
forall e kv v. (KeyValue e kv, ToJSON v) => Key -> v -> kv
(JSON..=) Key
"AccountRecoverySetting"
(AccountRecoverySettingProperty -> (Key, Value))
-> Maybe AccountRecoverySettingProperty -> Maybe (Key, Value)
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
Prelude.<$> Maybe AccountRecoverySettingProperty
accountRecoverySetting,
Key -> AdminCreateUserConfigProperty -> (Key, Value)
forall v. ToJSON v => Key -> v -> (Key, Value)
forall e kv v. (KeyValue e kv, ToJSON v) => Key -> v -> kv
(JSON..=) Key
"AdminCreateUserConfig"
(AdminCreateUserConfigProperty -> (Key, Value))
-> Maybe AdminCreateUserConfigProperty -> Maybe (Key, Value)
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
Prelude.<$> Maybe AdminCreateUserConfigProperty
adminCreateUserConfig,
Key -> ValueList Text -> (Key, Value)
forall v. ToJSON v => Key -> v -> (Key, Value)
forall e kv v. (KeyValue e kv, ToJSON v) => Key -> v -> kv
(JSON..=) Key
"AliasAttributes" (ValueList Text -> (Key, Value))
-> Maybe (ValueList Text) -> Maybe (Key, Value)
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
Prelude.<$> Maybe (ValueList Text)
aliasAttributes,
Key -> ValueList Text -> (Key, Value)
forall v. ToJSON v => Key -> v -> (Key, Value)
forall e kv v. (KeyValue e kv, ToJSON v) => Key -> v -> kv
(JSON..=) Key
"AutoVerifiedAttributes"
(ValueList Text -> (Key, Value))
-> Maybe (ValueList Text) -> Maybe (Key, Value)
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
Prelude.<$> Maybe (ValueList Text)
autoVerifiedAttributes,
Key -> Value Text -> (Key, Value)
forall v. ToJSON v => Key -> v -> (Key, Value)
forall e kv v. (KeyValue e kv, ToJSON v) => Key -> v -> kv
(JSON..=) Key
"DeletionProtection" (Value Text -> (Key, Value))
-> Maybe (Value Text) -> Maybe (Key, Value)
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
Prelude.<$> Maybe (Value Text)
deletionProtection,
Key -> DeviceConfigurationProperty -> (Key, Value)
forall v. ToJSON v => Key -> v -> (Key, Value)
forall e kv v. (KeyValue e kv, ToJSON v) => Key -> v -> kv
(JSON..=) Key
"DeviceConfiguration" (DeviceConfigurationProperty -> (Key, Value))
-> Maybe DeviceConfigurationProperty -> Maybe (Key, Value)
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
Prelude.<$> Maybe DeviceConfigurationProperty
deviceConfiguration,
Key -> Value Text -> (Key, Value)
forall v. ToJSON v => Key -> v -> (Key, Value)
forall e kv v. (KeyValue e kv, ToJSON v) => Key -> v -> kv
(JSON..=) Key
"EmailAuthenticationMessage"
(Value Text -> (Key, Value))
-> Maybe (Value Text) -> Maybe (Key, Value)
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
Prelude.<$> Maybe (Value Text)
emailAuthenticationMessage,
Key -> Value Text -> (Key, Value)
forall v. ToJSON v => Key -> v -> (Key, Value)
forall e kv v. (KeyValue e kv, ToJSON v) => Key -> v -> kv
(JSON..=) Key
"EmailAuthenticationSubject"
(Value Text -> (Key, Value))
-> Maybe (Value Text) -> Maybe (Key, Value)
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
Prelude.<$> Maybe (Value Text)
emailAuthenticationSubject,
Key -> EmailConfigurationProperty -> (Key, Value)
forall v. ToJSON v => Key -> v -> (Key, Value)
forall e kv v. (KeyValue e kv, ToJSON v) => Key -> v -> kv
(JSON..=) Key
"EmailConfiguration" (EmailConfigurationProperty -> (Key, Value))
-> Maybe EmailConfigurationProperty -> Maybe (Key, Value)
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
Prelude.<$> Maybe EmailConfigurationProperty
emailConfiguration,
Key -> Value Text -> (Key, Value)
forall v. ToJSON v => Key -> v -> (Key, Value)
forall e kv v. (KeyValue e kv, ToJSON v) => Key -> v -> kv
(JSON..=) Key
"EmailVerificationMessage"
(Value Text -> (Key, Value))
-> Maybe (Value Text) -> Maybe (Key, Value)
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
Prelude.<$> Maybe (Value Text)
emailVerificationMessage,
Key -> Value Text -> (Key, Value)
forall v. ToJSON v => Key -> v -> (Key, Value)
forall e kv v. (KeyValue e kv, ToJSON v) => Key -> v -> kv
(JSON..=) Key
"EmailVerificationSubject"
(Value Text -> (Key, Value))
-> Maybe (Value Text) -> Maybe (Key, Value)
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
Prelude.<$> Maybe (Value Text)
emailVerificationSubject,
Key -> ValueList Text -> (Key, Value)
forall v. ToJSON v => Key -> v -> (Key, Value)
forall e kv v. (KeyValue e kv, ToJSON v) => Key -> v -> kv
(JSON..=) Key
"EnabledMfas" (ValueList Text -> (Key, Value))
-> Maybe (ValueList Text) -> Maybe (Key, Value)
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
Prelude.<$> Maybe (ValueList Text)
enabledMfas,
Key -> LambdaConfigProperty -> (Key, Value)
forall v. ToJSON v => Key -> v -> (Key, Value)
forall e kv v. (KeyValue e kv, ToJSON v) => Key -> v -> kv
(JSON..=) Key
"LambdaConfig" (LambdaConfigProperty -> (Key, Value))
-> Maybe LambdaConfigProperty -> Maybe (Key, Value)
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
Prelude.<$> Maybe LambdaConfigProperty
lambdaConfig,
Key -> Value Text -> (Key, Value)
forall v. ToJSON v => Key -> v -> (Key, Value)
forall e kv v. (KeyValue e kv, ToJSON v) => Key -> v -> kv
(JSON..=) Key
"MfaConfiguration" (Value Text -> (Key, Value))
-> Maybe (Value Text) -> Maybe (Key, Value)
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
Prelude.<$> Maybe (Value Text)
mfaConfiguration,
Key -> PoliciesProperty -> (Key, Value)
forall v. ToJSON v => Key -> v -> (Key, Value)
forall e kv v. (KeyValue e kv, ToJSON v) => Key -> v -> kv
(JSON..=) Key
"Policies" (PoliciesProperty -> (Key, Value))
-> Maybe PoliciesProperty -> Maybe (Key, Value)
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
Prelude.<$> Maybe PoliciesProperty
policies,
Key -> [SchemaAttributeProperty] -> (Key, Value)
forall v. ToJSON v => Key -> v -> (Key, Value)
forall e kv v. (KeyValue e kv, ToJSON v) => Key -> v -> kv
(JSON..=) Key
"Schema" ([SchemaAttributeProperty] -> (Key, Value))
-> Maybe [SchemaAttributeProperty] -> Maybe (Key, Value)
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
Prelude.<$> Maybe [SchemaAttributeProperty]
schema,
Key -> Value Text -> (Key, Value)
forall v. ToJSON v => Key -> v -> (Key, Value)
forall e kv v. (KeyValue e kv, ToJSON v) => Key -> v -> kv
(JSON..=) Key
"SmsAuthenticationMessage"
(Value Text -> (Key, Value))
-> Maybe (Value Text) -> Maybe (Key, Value)
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
Prelude.<$> Maybe (Value Text)
smsAuthenticationMessage,
Key -> SmsConfigurationProperty -> (Key, Value)
forall v. ToJSON v => Key -> v -> (Key, Value)
forall e kv v. (KeyValue e kv, ToJSON v) => Key -> v -> kv
(JSON..=) Key
"SmsConfiguration" (SmsConfigurationProperty -> (Key, Value))
-> Maybe SmsConfigurationProperty -> Maybe (Key, Value)
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
Prelude.<$> Maybe SmsConfigurationProperty
smsConfiguration,
Key -> Value Text -> (Key, Value)
forall v. ToJSON v => Key -> v -> (Key, Value)
forall e kv v. (KeyValue e kv, ToJSON v) => Key -> v -> kv
(JSON..=) Key
"SmsVerificationMessage"
(Value Text -> (Key, Value))
-> Maybe (Value Text) -> Maybe (Key, Value)
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
Prelude.<$> Maybe (Value Text)
smsVerificationMessage,
Key -> UserAttributeUpdateSettingsProperty -> (Key, Value)
forall v. ToJSON v => Key -> v -> (Key, Value)
forall e kv v. (KeyValue e kv, ToJSON v) => Key -> v -> kv
(JSON..=) Key
"UserAttributeUpdateSettings"
(UserAttributeUpdateSettingsProperty -> (Key, Value))
-> Maybe UserAttributeUpdateSettingsProperty -> Maybe (Key, Value)
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
Prelude.<$> Maybe UserAttributeUpdateSettingsProperty
userAttributeUpdateSettings,
Key -> UserPoolAddOnsProperty -> (Key, Value)
forall v. ToJSON v => Key -> v -> (Key, Value)
forall e kv v. (KeyValue e kv, ToJSON v) => Key -> v -> kv
(JSON..=) Key
"UserPoolAddOns" (UserPoolAddOnsProperty -> (Key, Value))
-> Maybe UserPoolAddOnsProperty -> Maybe (Key, Value)
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
Prelude.<$> Maybe UserPoolAddOnsProperty
userPoolAddOns,
Key -> Value Text -> (Key, Value)
forall v. ToJSON v => Key -> v -> (Key, Value)
forall e kv v. (KeyValue e kv, ToJSON v) => Key -> v -> kv
(JSON..=) Key
"UserPoolName" (Value Text -> (Key, Value))
-> Maybe (Value Text) -> Maybe (Key, Value)
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
Prelude.<$> Maybe (Value Text)
userPoolName,
Key -> Map Text (Value Text) -> (Key, Value)
forall v. ToJSON v => Key -> v -> (Key, Value)
forall e kv v. (KeyValue e kv, ToJSON v) => Key -> v -> kv
(JSON..=) Key
"UserPoolTags" (Map Text (Value Text) -> (Key, Value))
-> Maybe (Map Text (Value Text)) -> Maybe (Key, Value)
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
Prelude.<$> Maybe (Map Text (Value Text))
userPoolTags,
Key -> Value Text -> (Key, Value)
forall v. ToJSON v => Key -> v -> (Key, Value)
forall e kv v. (KeyValue e kv, ToJSON v) => Key -> v -> kv
(JSON..=) Key
"UserPoolTier" (Value Text -> (Key, Value))
-> Maybe (Value Text) -> Maybe (Key, Value)
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
Prelude.<$> Maybe (Value Text)
userPoolTier,
Key -> ValueList Text -> (Key, Value)
forall v. ToJSON v => Key -> v -> (Key, Value)
forall e kv v. (KeyValue e kv, ToJSON v) => Key -> v -> kv
(JSON..=) Key
"UsernameAttributes" (ValueList Text -> (Key, Value))
-> Maybe (ValueList Text) -> Maybe (Key, Value)
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
Prelude.<$> Maybe (ValueList Text)
usernameAttributes,
Key -> UsernameConfigurationProperty -> (Key, Value)
forall v. ToJSON v => Key -> v -> (Key, Value)
forall e kv v. (KeyValue e kv, ToJSON v) => Key -> v -> kv
(JSON..=) Key
"UsernameConfiguration"
(UsernameConfigurationProperty -> (Key, Value))
-> Maybe UsernameConfigurationProperty -> Maybe (Key, Value)
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
Prelude.<$> Maybe UsernameConfigurationProperty
usernameConfiguration,
Key -> VerificationMessageTemplateProperty -> (Key, Value)
forall v. ToJSON v => Key -> v -> (Key, Value)
forall e kv v. (KeyValue e kv, ToJSON v) => Key -> v -> kv
(JSON..=) Key
"VerificationMessageTemplate"
(VerificationMessageTemplateProperty -> (Key, Value))
-> Maybe VerificationMessageTemplateProperty -> Maybe (Key, Value)
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
Prelude.<$> Maybe VerificationMessageTemplateProperty
verificationMessageTemplate,
Key -> Value Text -> (Key, Value)
forall v. ToJSON v => Key -> v -> (Key, Value)
forall e kv v. (KeyValue e kv, ToJSON v) => Key -> v -> kv
(JSON..=) Key
"WebAuthnRelyingPartyID"
(Value Text -> (Key, Value))
-> Maybe (Value Text) -> Maybe (Key, Value)
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
Prelude.<$> Maybe (Value Text)
webAuthnRelyingPartyID,
Key -> Value Text -> (Key, Value)
forall v. ToJSON v => Key -> v -> (Key, Value)
forall e kv v. (KeyValue e kv, ToJSON v) => Key -> v -> kv
(JSON..=) Key
"WebAuthnUserVerification"
(Value Text -> (Key, Value))
-> Maybe (Value Text) -> Maybe (Key, Value)
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
Prelude.<$> Maybe (Value Text)
webAuthnUserVerification]))
instance Property "AccountRecoverySetting" UserPool where
type PropertyType "AccountRecoverySetting" UserPool = AccountRecoverySettingProperty
set :: PropertyType "AccountRecoverySetting" UserPool
-> UserPool -> UserPool
set PropertyType "AccountRecoverySetting" UserPool
newValue UserPool {Maybe [SchemaAttributeProperty]
Maybe (Map Text (Value Text))
Maybe (ValueList Text)
Maybe (Value Text)
Maybe DeviceConfigurationProperty
Maybe EmailConfigurationProperty
Maybe AdminCreateUserConfigProperty
Maybe LambdaConfigProperty
Maybe AccountRecoverySettingProperty
Maybe PoliciesProperty
Maybe SmsConfigurationProperty
Maybe UserAttributeUpdateSettingsProperty
Maybe UserPoolAddOnsProperty
Maybe UsernameConfigurationProperty
Maybe VerificationMessageTemplateProperty
()
haddock_workaround_ :: UserPool -> ()
accountRecoverySetting :: UserPool -> Maybe AccountRecoverySettingProperty
adminCreateUserConfig :: UserPool -> Maybe AdminCreateUserConfigProperty
aliasAttributes :: UserPool -> Maybe (ValueList Text)
autoVerifiedAttributes :: UserPool -> Maybe (ValueList Text)
deletionProtection :: UserPool -> Maybe (Value Text)
deviceConfiguration :: UserPool -> Maybe DeviceConfigurationProperty
emailAuthenticationMessage :: UserPool -> Maybe (Value Text)
emailAuthenticationSubject :: UserPool -> Maybe (Value Text)
emailConfiguration :: UserPool -> Maybe EmailConfigurationProperty
emailVerificationMessage :: UserPool -> Maybe (Value Text)
emailVerificationSubject :: UserPool -> Maybe (Value Text)
enabledMfas :: UserPool -> Maybe (ValueList Text)
lambdaConfig :: UserPool -> Maybe LambdaConfigProperty
mfaConfiguration :: UserPool -> Maybe (Value Text)
policies :: UserPool -> Maybe PoliciesProperty
schema :: UserPool -> Maybe [SchemaAttributeProperty]
smsAuthenticationMessage :: UserPool -> Maybe (Value Text)
smsConfiguration :: UserPool -> Maybe SmsConfigurationProperty
smsVerificationMessage :: UserPool -> Maybe (Value Text)
userAttributeUpdateSettings :: UserPool -> Maybe UserAttributeUpdateSettingsProperty
userPoolAddOns :: UserPool -> Maybe UserPoolAddOnsProperty
userPoolName :: UserPool -> Maybe (Value Text)
userPoolTags :: UserPool -> Maybe (Map Text (Value Text))
userPoolTier :: UserPool -> Maybe (Value Text)
usernameAttributes :: UserPool -> Maybe (ValueList Text)
usernameConfiguration :: UserPool -> Maybe UsernameConfigurationProperty
verificationMessageTemplate :: UserPool -> Maybe VerificationMessageTemplateProperty
webAuthnRelyingPartyID :: UserPool -> Maybe (Value Text)
webAuthnUserVerification :: UserPool -> Maybe (Value Text)
haddock_workaround_ :: ()
accountRecoverySetting :: Maybe AccountRecoverySettingProperty
adminCreateUserConfig :: Maybe AdminCreateUserConfigProperty
aliasAttributes :: Maybe (ValueList Text)
autoVerifiedAttributes :: Maybe (ValueList Text)
deletionProtection :: Maybe (Value Text)
deviceConfiguration :: Maybe DeviceConfigurationProperty
emailAuthenticationMessage :: Maybe (Value Text)
emailAuthenticationSubject :: Maybe (Value Text)
emailConfiguration :: Maybe EmailConfigurationProperty
emailVerificationMessage :: Maybe (Value Text)
emailVerificationSubject :: Maybe (Value Text)
enabledMfas :: Maybe (ValueList Text)
lambdaConfig :: Maybe LambdaConfigProperty
mfaConfiguration :: Maybe (Value Text)
policies :: Maybe PoliciesProperty
schema :: Maybe [SchemaAttributeProperty]
smsAuthenticationMessage :: Maybe (Value Text)
smsConfiguration :: Maybe SmsConfigurationProperty
smsVerificationMessage :: Maybe (Value Text)
userAttributeUpdateSettings :: Maybe UserAttributeUpdateSettingsProperty
userPoolAddOns :: Maybe UserPoolAddOnsProperty
userPoolName :: Maybe (Value Text)
userPoolTags :: Maybe (Map Text (Value Text))
userPoolTier :: Maybe (Value Text)
usernameAttributes :: Maybe (ValueList Text)
usernameConfiguration :: Maybe UsernameConfigurationProperty
verificationMessageTemplate :: Maybe VerificationMessageTemplateProperty
webAuthnRelyingPartyID :: Maybe (Value Text)
webAuthnUserVerification :: Maybe (Value Text)
..}
= UserPool {accountRecoverySetting :: Maybe AccountRecoverySettingProperty
accountRecoverySetting = AccountRecoverySettingProperty
-> Maybe AccountRecoverySettingProperty
forall a. a -> Maybe a
forall (f :: * -> *) a. Applicative f => a -> f a
Prelude.pure PropertyType "AccountRecoverySetting" UserPool
AccountRecoverySettingProperty
newValue, Maybe [SchemaAttributeProperty]
Maybe (Map Text (Value Text))
Maybe (ValueList Text)
Maybe (Value Text)
Maybe DeviceConfigurationProperty
Maybe EmailConfigurationProperty
Maybe AdminCreateUserConfigProperty
Maybe LambdaConfigProperty
Maybe PoliciesProperty
Maybe SmsConfigurationProperty
Maybe UserAttributeUpdateSettingsProperty
Maybe UserPoolAddOnsProperty
Maybe UsernameConfigurationProperty
Maybe VerificationMessageTemplateProperty
()
haddock_workaround_ :: ()
adminCreateUserConfig :: Maybe AdminCreateUserConfigProperty
aliasAttributes :: Maybe (ValueList Text)
autoVerifiedAttributes :: Maybe (ValueList Text)
deletionProtection :: Maybe (Value Text)
deviceConfiguration :: Maybe DeviceConfigurationProperty
emailAuthenticationMessage :: Maybe (Value Text)
emailAuthenticationSubject :: Maybe (Value Text)
emailConfiguration :: Maybe EmailConfigurationProperty
emailVerificationMessage :: Maybe (Value Text)
emailVerificationSubject :: Maybe (Value Text)
enabledMfas :: Maybe (ValueList Text)
lambdaConfig :: Maybe LambdaConfigProperty
mfaConfiguration :: Maybe (Value Text)
policies :: Maybe PoliciesProperty
schema :: Maybe [SchemaAttributeProperty]
smsAuthenticationMessage :: Maybe (Value Text)
smsConfiguration :: Maybe SmsConfigurationProperty
smsVerificationMessage :: Maybe (Value Text)
userAttributeUpdateSettings :: Maybe UserAttributeUpdateSettingsProperty
userPoolAddOns :: Maybe UserPoolAddOnsProperty
userPoolName :: Maybe (Value Text)
userPoolTags :: Maybe (Map Text (Value Text))
userPoolTier :: Maybe (Value Text)
usernameAttributes :: Maybe (ValueList Text)
usernameConfiguration :: Maybe UsernameConfigurationProperty
verificationMessageTemplate :: Maybe VerificationMessageTemplateProperty
webAuthnRelyingPartyID :: Maybe (Value Text)
webAuthnUserVerification :: Maybe (Value Text)
haddock_workaround_ :: ()
adminCreateUserConfig :: Maybe AdminCreateUserConfigProperty
aliasAttributes :: Maybe (ValueList Text)
autoVerifiedAttributes :: Maybe (ValueList Text)
deletionProtection :: Maybe (Value Text)
deviceConfiguration :: Maybe DeviceConfigurationProperty
emailAuthenticationMessage :: Maybe (Value Text)
emailAuthenticationSubject :: Maybe (Value Text)
emailConfiguration :: Maybe EmailConfigurationProperty
emailVerificationMessage :: Maybe (Value Text)
emailVerificationSubject :: Maybe (Value Text)
enabledMfas :: Maybe (ValueList Text)
lambdaConfig :: Maybe LambdaConfigProperty
mfaConfiguration :: Maybe (Value Text)
policies :: Maybe PoliciesProperty
schema :: Maybe [SchemaAttributeProperty]
smsAuthenticationMessage :: Maybe (Value Text)
smsConfiguration :: Maybe SmsConfigurationProperty
smsVerificationMessage :: Maybe (Value Text)
userAttributeUpdateSettings :: Maybe UserAttributeUpdateSettingsProperty
userPoolAddOns :: Maybe UserPoolAddOnsProperty
userPoolName :: Maybe (Value Text)
userPoolTags :: Maybe (Map Text (Value Text))
userPoolTier :: Maybe (Value Text)
usernameAttributes :: Maybe (ValueList Text)
usernameConfiguration :: Maybe UsernameConfigurationProperty
verificationMessageTemplate :: Maybe VerificationMessageTemplateProperty
webAuthnRelyingPartyID :: Maybe (Value Text)
webAuthnUserVerification :: Maybe (Value Text)
..}
instance Property "AdminCreateUserConfig" UserPool where
type PropertyType "AdminCreateUserConfig" UserPool = AdminCreateUserConfigProperty
set :: PropertyType "AdminCreateUserConfig" UserPool
-> UserPool -> UserPool
set PropertyType "AdminCreateUserConfig" UserPool
newValue UserPool {Maybe [SchemaAttributeProperty]
Maybe (Map Text (Value Text))
Maybe (ValueList Text)
Maybe (Value Text)
Maybe DeviceConfigurationProperty
Maybe EmailConfigurationProperty
Maybe AdminCreateUserConfigProperty
Maybe LambdaConfigProperty
Maybe AccountRecoverySettingProperty
Maybe PoliciesProperty
Maybe SmsConfigurationProperty
Maybe UserAttributeUpdateSettingsProperty
Maybe UserPoolAddOnsProperty
Maybe UsernameConfigurationProperty
Maybe VerificationMessageTemplateProperty
()
haddock_workaround_ :: UserPool -> ()
accountRecoverySetting :: UserPool -> Maybe AccountRecoverySettingProperty
adminCreateUserConfig :: UserPool -> Maybe AdminCreateUserConfigProperty
aliasAttributes :: UserPool -> Maybe (ValueList Text)
autoVerifiedAttributes :: UserPool -> Maybe (ValueList Text)
deletionProtection :: UserPool -> Maybe (Value Text)
deviceConfiguration :: UserPool -> Maybe DeviceConfigurationProperty
emailAuthenticationMessage :: UserPool -> Maybe (Value Text)
emailAuthenticationSubject :: UserPool -> Maybe (Value Text)
emailConfiguration :: UserPool -> Maybe EmailConfigurationProperty
emailVerificationMessage :: UserPool -> Maybe (Value Text)
emailVerificationSubject :: UserPool -> Maybe (Value Text)
enabledMfas :: UserPool -> Maybe (ValueList Text)
lambdaConfig :: UserPool -> Maybe LambdaConfigProperty
mfaConfiguration :: UserPool -> Maybe (Value Text)
policies :: UserPool -> Maybe PoliciesProperty
schema :: UserPool -> Maybe [SchemaAttributeProperty]
smsAuthenticationMessage :: UserPool -> Maybe (Value Text)
smsConfiguration :: UserPool -> Maybe SmsConfigurationProperty
smsVerificationMessage :: UserPool -> Maybe (Value Text)
userAttributeUpdateSettings :: UserPool -> Maybe UserAttributeUpdateSettingsProperty
userPoolAddOns :: UserPool -> Maybe UserPoolAddOnsProperty
userPoolName :: UserPool -> Maybe (Value Text)
userPoolTags :: UserPool -> Maybe (Map Text (Value Text))
userPoolTier :: UserPool -> Maybe (Value Text)
usernameAttributes :: UserPool -> Maybe (ValueList Text)
usernameConfiguration :: UserPool -> Maybe UsernameConfigurationProperty
verificationMessageTemplate :: UserPool -> Maybe VerificationMessageTemplateProperty
webAuthnRelyingPartyID :: UserPool -> Maybe (Value Text)
webAuthnUserVerification :: UserPool -> Maybe (Value Text)
haddock_workaround_ :: ()
accountRecoverySetting :: Maybe AccountRecoverySettingProperty
adminCreateUserConfig :: Maybe AdminCreateUserConfigProperty
aliasAttributes :: Maybe (ValueList Text)
autoVerifiedAttributes :: Maybe (ValueList Text)
deletionProtection :: Maybe (Value Text)
deviceConfiguration :: Maybe DeviceConfigurationProperty
emailAuthenticationMessage :: Maybe (Value Text)
emailAuthenticationSubject :: Maybe (Value Text)
emailConfiguration :: Maybe EmailConfigurationProperty
emailVerificationMessage :: Maybe (Value Text)
emailVerificationSubject :: Maybe (Value Text)
enabledMfas :: Maybe (ValueList Text)
lambdaConfig :: Maybe LambdaConfigProperty
mfaConfiguration :: Maybe (Value Text)
policies :: Maybe PoliciesProperty
schema :: Maybe [SchemaAttributeProperty]
smsAuthenticationMessage :: Maybe (Value Text)
smsConfiguration :: Maybe SmsConfigurationProperty
smsVerificationMessage :: Maybe (Value Text)
userAttributeUpdateSettings :: Maybe UserAttributeUpdateSettingsProperty
userPoolAddOns :: Maybe UserPoolAddOnsProperty
userPoolName :: Maybe (Value Text)
userPoolTags :: Maybe (Map Text (Value Text))
userPoolTier :: Maybe (Value Text)
usernameAttributes :: Maybe (ValueList Text)
usernameConfiguration :: Maybe UsernameConfigurationProperty
verificationMessageTemplate :: Maybe VerificationMessageTemplateProperty
webAuthnRelyingPartyID :: Maybe (Value Text)
webAuthnUserVerification :: Maybe (Value Text)
..}
= UserPool {adminCreateUserConfig :: Maybe AdminCreateUserConfigProperty
adminCreateUserConfig = AdminCreateUserConfigProperty
-> Maybe AdminCreateUserConfigProperty
forall a. a -> Maybe a
forall (f :: * -> *) a. Applicative f => a -> f a
Prelude.pure PropertyType "AdminCreateUserConfig" UserPool
AdminCreateUserConfigProperty
newValue, Maybe [SchemaAttributeProperty]
Maybe (Map Text (Value Text))
Maybe (ValueList Text)
Maybe (Value Text)
Maybe DeviceConfigurationProperty
Maybe EmailConfigurationProperty
Maybe LambdaConfigProperty
Maybe AccountRecoverySettingProperty
Maybe PoliciesProperty
Maybe SmsConfigurationProperty
Maybe UserAttributeUpdateSettingsProperty
Maybe UserPoolAddOnsProperty
Maybe UsernameConfigurationProperty
Maybe VerificationMessageTemplateProperty
()
haddock_workaround_ :: ()
accountRecoverySetting :: Maybe AccountRecoverySettingProperty
aliasAttributes :: Maybe (ValueList Text)
autoVerifiedAttributes :: Maybe (ValueList Text)
deletionProtection :: Maybe (Value Text)
deviceConfiguration :: Maybe DeviceConfigurationProperty
emailAuthenticationMessage :: Maybe (Value Text)
emailAuthenticationSubject :: Maybe (Value Text)
emailConfiguration :: Maybe EmailConfigurationProperty
emailVerificationMessage :: Maybe (Value Text)
emailVerificationSubject :: Maybe (Value Text)
enabledMfas :: Maybe (ValueList Text)
lambdaConfig :: Maybe LambdaConfigProperty
mfaConfiguration :: Maybe (Value Text)
policies :: Maybe PoliciesProperty
schema :: Maybe [SchemaAttributeProperty]
smsAuthenticationMessage :: Maybe (Value Text)
smsConfiguration :: Maybe SmsConfigurationProperty
smsVerificationMessage :: Maybe (Value Text)
userAttributeUpdateSettings :: Maybe UserAttributeUpdateSettingsProperty
userPoolAddOns :: Maybe UserPoolAddOnsProperty
userPoolName :: Maybe (Value Text)
userPoolTags :: Maybe (Map Text (Value Text))
userPoolTier :: Maybe (Value Text)
usernameAttributes :: Maybe (ValueList Text)
usernameConfiguration :: Maybe UsernameConfigurationProperty
verificationMessageTemplate :: Maybe VerificationMessageTemplateProperty
webAuthnRelyingPartyID :: Maybe (Value Text)
webAuthnUserVerification :: Maybe (Value Text)
haddock_workaround_ :: ()
accountRecoverySetting :: Maybe AccountRecoverySettingProperty
aliasAttributes :: Maybe (ValueList Text)
autoVerifiedAttributes :: Maybe (ValueList Text)
deletionProtection :: Maybe (Value Text)
deviceConfiguration :: Maybe DeviceConfigurationProperty
emailAuthenticationMessage :: Maybe (Value Text)
emailAuthenticationSubject :: Maybe (Value Text)
emailConfiguration :: Maybe EmailConfigurationProperty
emailVerificationMessage :: Maybe (Value Text)
emailVerificationSubject :: Maybe (Value Text)
enabledMfas :: Maybe (ValueList Text)
lambdaConfig :: Maybe LambdaConfigProperty
mfaConfiguration :: Maybe (Value Text)
policies :: Maybe PoliciesProperty
schema :: Maybe [SchemaAttributeProperty]
smsAuthenticationMessage :: Maybe (Value Text)
smsConfiguration :: Maybe SmsConfigurationProperty
smsVerificationMessage :: Maybe (Value Text)
userAttributeUpdateSettings :: Maybe UserAttributeUpdateSettingsProperty
userPoolAddOns :: Maybe UserPoolAddOnsProperty
userPoolName :: Maybe (Value Text)
userPoolTags :: Maybe (Map Text (Value Text))
userPoolTier :: Maybe (Value Text)
usernameAttributes :: Maybe (ValueList Text)
usernameConfiguration :: Maybe UsernameConfigurationProperty
verificationMessageTemplate :: Maybe VerificationMessageTemplateProperty
webAuthnRelyingPartyID :: Maybe (Value Text)
webAuthnUserVerification :: Maybe (Value Text)
..}
instance Property "AliasAttributes" UserPool where
type PropertyType "AliasAttributes" UserPool = ValueList Prelude.Text
set :: PropertyType "AliasAttributes" UserPool -> UserPool -> UserPool
set PropertyType "AliasAttributes" UserPool
newValue UserPool {Maybe [SchemaAttributeProperty]
Maybe (Map Text (Value Text))
Maybe (ValueList Text)
Maybe (Value Text)
Maybe DeviceConfigurationProperty
Maybe EmailConfigurationProperty
Maybe AdminCreateUserConfigProperty
Maybe LambdaConfigProperty
Maybe AccountRecoverySettingProperty
Maybe PoliciesProperty
Maybe SmsConfigurationProperty
Maybe UserAttributeUpdateSettingsProperty
Maybe UserPoolAddOnsProperty
Maybe UsernameConfigurationProperty
Maybe VerificationMessageTemplateProperty
()
haddock_workaround_ :: UserPool -> ()
accountRecoverySetting :: UserPool -> Maybe AccountRecoverySettingProperty
adminCreateUserConfig :: UserPool -> Maybe AdminCreateUserConfigProperty
aliasAttributes :: UserPool -> Maybe (ValueList Text)
autoVerifiedAttributes :: UserPool -> Maybe (ValueList Text)
deletionProtection :: UserPool -> Maybe (Value Text)
deviceConfiguration :: UserPool -> Maybe DeviceConfigurationProperty
emailAuthenticationMessage :: UserPool -> Maybe (Value Text)
emailAuthenticationSubject :: UserPool -> Maybe (Value Text)
emailConfiguration :: UserPool -> Maybe EmailConfigurationProperty
emailVerificationMessage :: UserPool -> Maybe (Value Text)
emailVerificationSubject :: UserPool -> Maybe (Value Text)
enabledMfas :: UserPool -> Maybe (ValueList Text)
lambdaConfig :: UserPool -> Maybe LambdaConfigProperty
mfaConfiguration :: UserPool -> Maybe (Value Text)
policies :: UserPool -> Maybe PoliciesProperty
schema :: UserPool -> Maybe [SchemaAttributeProperty]
smsAuthenticationMessage :: UserPool -> Maybe (Value Text)
smsConfiguration :: UserPool -> Maybe SmsConfigurationProperty
smsVerificationMessage :: UserPool -> Maybe (Value Text)
userAttributeUpdateSettings :: UserPool -> Maybe UserAttributeUpdateSettingsProperty
userPoolAddOns :: UserPool -> Maybe UserPoolAddOnsProperty
userPoolName :: UserPool -> Maybe (Value Text)
userPoolTags :: UserPool -> Maybe (Map Text (Value Text))
userPoolTier :: UserPool -> Maybe (Value Text)
usernameAttributes :: UserPool -> Maybe (ValueList Text)
usernameConfiguration :: UserPool -> Maybe UsernameConfigurationProperty
verificationMessageTemplate :: UserPool -> Maybe VerificationMessageTemplateProperty
webAuthnRelyingPartyID :: UserPool -> Maybe (Value Text)
webAuthnUserVerification :: UserPool -> Maybe (Value Text)
haddock_workaround_ :: ()
accountRecoverySetting :: Maybe AccountRecoverySettingProperty
adminCreateUserConfig :: Maybe AdminCreateUserConfigProperty
aliasAttributes :: Maybe (ValueList Text)
autoVerifiedAttributes :: Maybe (ValueList Text)
deletionProtection :: Maybe (Value Text)
deviceConfiguration :: Maybe DeviceConfigurationProperty
emailAuthenticationMessage :: Maybe (Value Text)
emailAuthenticationSubject :: Maybe (Value Text)
emailConfiguration :: Maybe EmailConfigurationProperty
emailVerificationMessage :: Maybe (Value Text)
emailVerificationSubject :: Maybe (Value Text)
enabledMfas :: Maybe (ValueList Text)
lambdaConfig :: Maybe LambdaConfigProperty
mfaConfiguration :: Maybe (Value Text)
policies :: Maybe PoliciesProperty
schema :: Maybe [SchemaAttributeProperty]
smsAuthenticationMessage :: Maybe (Value Text)
smsConfiguration :: Maybe SmsConfigurationProperty
smsVerificationMessage :: Maybe (Value Text)
userAttributeUpdateSettings :: Maybe UserAttributeUpdateSettingsProperty
userPoolAddOns :: Maybe UserPoolAddOnsProperty
userPoolName :: Maybe (Value Text)
userPoolTags :: Maybe (Map Text (Value Text))
userPoolTier :: Maybe (Value Text)
usernameAttributes :: Maybe (ValueList Text)
usernameConfiguration :: Maybe UsernameConfigurationProperty
verificationMessageTemplate :: Maybe VerificationMessageTemplateProperty
webAuthnRelyingPartyID :: Maybe (Value Text)
webAuthnUserVerification :: Maybe (Value Text)
..}
= UserPool {aliasAttributes :: Maybe (ValueList Text)
aliasAttributes = ValueList Text -> Maybe (ValueList Text)
forall a. a -> Maybe a
forall (f :: * -> *) a. Applicative f => a -> f a
Prelude.pure PropertyType "AliasAttributes" UserPool
ValueList Text
newValue, Maybe [SchemaAttributeProperty]
Maybe (Map Text (Value Text))
Maybe (ValueList Text)
Maybe (Value Text)
Maybe DeviceConfigurationProperty
Maybe EmailConfigurationProperty
Maybe AdminCreateUserConfigProperty
Maybe LambdaConfigProperty
Maybe AccountRecoverySettingProperty
Maybe PoliciesProperty
Maybe SmsConfigurationProperty
Maybe UserAttributeUpdateSettingsProperty
Maybe UserPoolAddOnsProperty
Maybe UsernameConfigurationProperty
Maybe VerificationMessageTemplateProperty
()
haddock_workaround_ :: ()
accountRecoverySetting :: Maybe AccountRecoverySettingProperty
adminCreateUserConfig :: Maybe AdminCreateUserConfigProperty
autoVerifiedAttributes :: Maybe (ValueList Text)
deletionProtection :: Maybe (Value Text)
deviceConfiguration :: Maybe DeviceConfigurationProperty
emailAuthenticationMessage :: Maybe (Value Text)
emailAuthenticationSubject :: Maybe (Value Text)
emailConfiguration :: Maybe EmailConfigurationProperty
emailVerificationMessage :: Maybe (Value Text)
emailVerificationSubject :: Maybe (Value Text)
enabledMfas :: Maybe (ValueList Text)
lambdaConfig :: Maybe LambdaConfigProperty
mfaConfiguration :: Maybe (Value Text)
policies :: Maybe PoliciesProperty
schema :: Maybe [SchemaAttributeProperty]
smsAuthenticationMessage :: Maybe (Value Text)
smsConfiguration :: Maybe SmsConfigurationProperty
smsVerificationMessage :: Maybe (Value Text)
userAttributeUpdateSettings :: Maybe UserAttributeUpdateSettingsProperty
userPoolAddOns :: Maybe UserPoolAddOnsProperty
userPoolName :: Maybe (Value Text)
userPoolTags :: Maybe (Map Text (Value Text))
userPoolTier :: Maybe (Value Text)
usernameAttributes :: Maybe (ValueList Text)
usernameConfiguration :: Maybe UsernameConfigurationProperty
verificationMessageTemplate :: Maybe VerificationMessageTemplateProperty
webAuthnRelyingPartyID :: Maybe (Value Text)
webAuthnUserVerification :: Maybe (Value Text)
haddock_workaround_ :: ()
accountRecoverySetting :: Maybe AccountRecoverySettingProperty
adminCreateUserConfig :: Maybe AdminCreateUserConfigProperty
autoVerifiedAttributes :: Maybe (ValueList Text)
deletionProtection :: Maybe (Value Text)
deviceConfiguration :: Maybe DeviceConfigurationProperty
emailAuthenticationMessage :: Maybe (Value Text)
emailAuthenticationSubject :: Maybe (Value Text)
emailConfiguration :: Maybe EmailConfigurationProperty
emailVerificationMessage :: Maybe (Value Text)
emailVerificationSubject :: Maybe (Value Text)
enabledMfas :: Maybe (ValueList Text)
lambdaConfig :: Maybe LambdaConfigProperty
mfaConfiguration :: Maybe (Value Text)
policies :: Maybe PoliciesProperty
schema :: Maybe [SchemaAttributeProperty]
smsAuthenticationMessage :: Maybe (Value Text)
smsConfiguration :: Maybe SmsConfigurationProperty
smsVerificationMessage :: Maybe (Value Text)
userAttributeUpdateSettings :: Maybe UserAttributeUpdateSettingsProperty
userPoolAddOns :: Maybe UserPoolAddOnsProperty
userPoolName :: Maybe (Value Text)
userPoolTags :: Maybe (Map Text (Value Text))
userPoolTier :: Maybe (Value Text)
usernameAttributes :: Maybe (ValueList Text)
usernameConfiguration :: Maybe UsernameConfigurationProperty
verificationMessageTemplate :: Maybe VerificationMessageTemplateProperty
webAuthnRelyingPartyID :: Maybe (Value Text)
webAuthnUserVerification :: Maybe (Value Text)
..}
instance Property "AutoVerifiedAttributes" UserPool where
type PropertyType "AutoVerifiedAttributes" UserPool = ValueList Prelude.Text
set :: PropertyType "AutoVerifiedAttributes" UserPool
-> UserPool -> UserPool
set PropertyType "AutoVerifiedAttributes" UserPool
newValue UserPool {Maybe [SchemaAttributeProperty]
Maybe (Map Text (Value Text))
Maybe (ValueList Text)
Maybe (Value Text)
Maybe DeviceConfigurationProperty
Maybe EmailConfigurationProperty
Maybe AdminCreateUserConfigProperty
Maybe LambdaConfigProperty
Maybe AccountRecoverySettingProperty
Maybe PoliciesProperty
Maybe SmsConfigurationProperty
Maybe UserAttributeUpdateSettingsProperty
Maybe UserPoolAddOnsProperty
Maybe UsernameConfigurationProperty
Maybe VerificationMessageTemplateProperty
()
haddock_workaround_ :: UserPool -> ()
accountRecoverySetting :: UserPool -> Maybe AccountRecoverySettingProperty
adminCreateUserConfig :: UserPool -> Maybe AdminCreateUserConfigProperty
aliasAttributes :: UserPool -> Maybe (ValueList Text)
autoVerifiedAttributes :: UserPool -> Maybe (ValueList Text)
deletionProtection :: UserPool -> Maybe (Value Text)
deviceConfiguration :: UserPool -> Maybe DeviceConfigurationProperty
emailAuthenticationMessage :: UserPool -> Maybe (Value Text)
emailAuthenticationSubject :: UserPool -> Maybe (Value Text)
emailConfiguration :: UserPool -> Maybe EmailConfigurationProperty
emailVerificationMessage :: UserPool -> Maybe (Value Text)
emailVerificationSubject :: UserPool -> Maybe (Value Text)
enabledMfas :: UserPool -> Maybe (ValueList Text)
lambdaConfig :: UserPool -> Maybe LambdaConfigProperty
mfaConfiguration :: UserPool -> Maybe (Value Text)
policies :: UserPool -> Maybe PoliciesProperty
schema :: UserPool -> Maybe [SchemaAttributeProperty]
smsAuthenticationMessage :: UserPool -> Maybe (Value Text)
smsConfiguration :: UserPool -> Maybe SmsConfigurationProperty
smsVerificationMessage :: UserPool -> Maybe (Value Text)
userAttributeUpdateSettings :: UserPool -> Maybe UserAttributeUpdateSettingsProperty
userPoolAddOns :: UserPool -> Maybe UserPoolAddOnsProperty
userPoolName :: UserPool -> Maybe (Value Text)
userPoolTags :: UserPool -> Maybe (Map Text (Value Text))
userPoolTier :: UserPool -> Maybe (Value Text)
usernameAttributes :: UserPool -> Maybe (ValueList Text)
usernameConfiguration :: UserPool -> Maybe UsernameConfigurationProperty
verificationMessageTemplate :: UserPool -> Maybe VerificationMessageTemplateProperty
webAuthnRelyingPartyID :: UserPool -> Maybe (Value Text)
webAuthnUserVerification :: UserPool -> Maybe (Value Text)
haddock_workaround_ :: ()
accountRecoverySetting :: Maybe AccountRecoverySettingProperty
adminCreateUserConfig :: Maybe AdminCreateUserConfigProperty
aliasAttributes :: Maybe (ValueList Text)
autoVerifiedAttributes :: Maybe (ValueList Text)
deletionProtection :: Maybe (Value Text)
deviceConfiguration :: Maybe DeviceConfigurationProperty
emailAuthenticationMessage :: Maybe (Value Text)
emailAuthenticationSubject :: Maybe (Value Text)
emailConfiguration :: Maybe EmailConfigurationProperty
emailVerificationMessage :: Maybe (Value Text)
emailVerificationSubject :: Maybe (Value Text)
enabledMfas :: Maybe (ValueList Text)
lambdaConfig :: Maybe LambdaConfigProperty
mfaConfiguration :: Maybe (Value Text)
policies :: Maybe PoliciesProperty
schema :: Maybe [SchemaAttributeProperty]
smsAuthenticationMessage :: Maybe (Value Text)
smsConfiguration :: Maybe SmsConfigurationProperty
smsVerificationMessage :: Maybe (Value Text)
userAttributeUpdateSettings :: Maybe UserAttributeUpdateSettingsProperty
userPoolAddOns :: Maybe UserPoolAddOnsProperty
userPoolName :: Maybe (Value Text)
userPoolTags :: Maybe (Map Text (Value Text))
userPoolTier :: Maybe (Value Text)
usernameAttributes :: Maybe (ValueList Text)
usernameConfiguration :: Maybe UsernameConfigurationProperty
verificationMessageTemplate :: Maybe VerificationMessageTemplateProperty
webAuthnRelyingPartyID :: Maybe (Value Text)
webAuthnUserVerification :: Maybe (Value Text)
..}
= UserPool {autoVerifiedAttributes :: Maybe (ValueList Text)
autoVerifiedAttributes = ValueList Text -> Maybe (ValueList Text)
forall a. a -> Maybe a
forall (f :: * -> *) a. Applicative f => a -> f a
Prelude.pure PropertyType "AutoVerifiedAttributes" UserPool
ValueList Text
newValue, Maybe [SchemaAttributeProperty]
Maybe (Map Text (Value Text))
Maybe (ValueList Text)
Maybe (Value Text)
Maybe DeviceConfigurationProperty
Maybe EmailConfigurationProperty
Maybe AdminCreateUserConfigProperty
Maybe LambdaConfigProperty
Maybe AccountRecoverySettingProperty
Maybe PoliciesProperty
Maybe SmsConfigurationProperty
Maybe UserAttributeUpdateSettingsProperty
Maybe UserPoolAddOnsProperty
Maybe UsernameConfigurationProperty
Maybe VerificationMessageTemplateProperty
()
haddock_workaround_ :: ()
accountRecoverySetting :: Maybe AccountRecoverySettingProperty
adminCreateUserConfig :: Maybe AdminCreateUserConfigProperty
aliasAttributes :: Maybe (ValueList Text)
deletionProtection :: Maybe (Value Text)
deviceConfiguration :: Maybe DeviceConfigurationProperty
emailAuthenticationMessage :: Maybe (Value Text)
emailAuthenticationSubject :: Maybe (Value Text)
emailConfiguration :: Maybe EmailConfigurationProperty
emailVerificationMessage :: Maybe (Value Text)
emailVerificationSubject :: Maybe (Value Text)
enabledMfas :: Maybe (ValueList Text)
lambdaConfig :: Maybe LambdaConfigProperty
mfaConfiguration :: Maybe (Value Text)
policies :: Maybe PoliciesProperty
schema :: Maybe [SchemaAttributeProperty]
smsAuthenticationMessage :: Maybe (Value Text)
smsConfiguration :: Maybe SmsConfigurationProperty
smsVerificationMessage :: Maybe (Value Text)
userAttributeUpdateSettings :: Maybe UserAttributeUpdateSettingsProperty
userPoolAddOns :: Maybe UserPoolAddOnsProperty
userPoolName :: Maybe (Value Text)
userPoolTags :: Maybe (Map Text (Value Text))
userPoolTier :: Maybe (Value Text)
usernameAttributes :: Maybe (ValueList Text)
usernameConfiguration :: Maybe UsernameConfigurationProperty
verificationMessageTemplate :: Maybe VerificationMessageTemplateProperty
webAuthnRelyingPartyID :: Maybe (Value Text)
webAuthnUserVerification :: Maybe (Value Text)
haddock_workaround_ :: ()
accountRecoverySetting :: Maybe AccountRecoverySettingProperty
adminCreateUserConfig :: Maybe AdminCreateUserConfigProperty
aliasAttributes :: Maybe (ValueList Text)
deletionProtection :: Maybe (Value Text)
deviceConfiguration :: Maybe DeviceConfigurationProperty
emailAuthenticationMessage :: Maybe (Value Text)
emailAuthenticationSubject :: Maybe (Value Text)
emailConfiguration :: Maybe EmailConfigurationProperty
emailVerificationMessage :: Maybe (Value Text)
emailVerificationSubject :: Maybe (Value Text)
enabledMfas :: Maybe (ValueList Text)
lambdaConfig :: Maybe LambdaConfigProperty
mfaConfiguration :: Maybe (Value Text)
policies :: Maybe PoliciesProperty
schema :: Maybe [SchemaAttributeProperty]
smsAuthenticationMessage :: Maybe (Value Text)
smsConfiguration :: Maybe SmsConfigurationProperty
smsVerificationMessage :: Maybe (Value Text)
userAttributeUpdateSettings :: Maybe UserAttributeUpdateSettingsProperty
userPoolAddOns :: Maybe UserPoolAddOnsProperty
userPoolName :: Maybe (Value Text)
userPoolTags :: Maybe (Map Text (Value Text))
userPoolTier :: Maybe (Value Text)
usernameAttributes :: Maybe (ValueList Text)
usernameConfiguration :: Maybe UsernameConfigurationProperty
verificationMessageTemplate :: Maybe VerificationMessageTemplateProperty
webAuthnRelyingPartyID :: Maybe (Value Text)
webAuthnUserVerification :: Maybe (Value Text)
..}
instance Property "DeletionProtection" UserPool where
type PropertyType "DeletionProtection" UserPool = Value Prelude.Text
set :: PropertyType "DeletionProtection" UserPool -> UserPool -> UserPool
set PropertyType "DeletionProtection" UserPool
newValue UserPool {Maybe [SchemaAttributeProperty]
Maybe (Map Text (Value Text))
Maybe (ValueList Text)
Maybe (Value Text)
Maybe DeviceConfigurationProperty
Maybe EmailConfigurationProperty
Maybe AdminCreateUserConfigProperty
Maybe LambdaConfigProperty
Maybe AccountRecoverySettingProperty
Maybe PoliciesProperty
Maybe SmsConfigurationProperty
Maybe UserAttributeUpdateSettingsProperty
Maybe UserPoolAddOnsProperty
Maybe UsernameConfigurationProperty
Maybe VerificationMessageTemplateProperty
()
haddock_workaround_ :: UserPool -> ()
accountRecoverySetting :: UserPool -> Maybe AccountRecoverySettingProperty
adminCreateUserConfig :: UserPool -> Maybe AdminCreateUserConfigProperty
aliasAttributes :: UserPool -> Maybe (ValueList Text)
autoVerifiedAttributes :: UserPool -> Maybe (ValueList Text)
deletionProtection :: UserPool -> Maybe (Value Text)
deviceConfiguration :: UserPool -> Maybe DeviceConfigurationProperty
emailAuthenticationMessage :: UserPool -> Maybe (Value Text)
emailAuthenticationSubject :: UserPool -> Maybe (Value Text)
emailConfiguration :: UserPool -> Maybe EmailConfigurationProperty
emailVerificationMessage :: UserPool -> Maybe (Value Text)
emailVerificationSubject :: UserPool -> Maybe (Value Text)
enabledMfas :: UserPool -> Maybe (ValueList Text)
lambdaConfig :: UserPool -> Maybe LambdaConfigProperty
mfaConfiguration :: UserPool -> Maybe (Value Text)
policies :: UserPool -> Maybe PoliciesProperty
schema :: UserPool -> Maybe [SchemaAttributeProperty]
smsAuthenticationMessage :: UserPool -> Maybe (Value Text)
smsConfiguration :: UserPool -> Maybe SmsConfigurationProperty
smsVerificationMessage :: UserPool -> Maybe (Value Text)
userAttributeUpdateSettings :: UserPool -> Maybe UserAttributeUpdateSettingsProperty
userPoolAddOns :: UserPool -> Maybe UserPoolAddOnsProperty
userPoolName :: UserPool -> Maybe (Value Text)
userPoolTags :: UserPool -> Maybe (Map Text (Value Text))
userPoolTier :: UserPool -> Maybe (Value Text)
usernameAttributes :: UserPool -> Maybe (ValueList Text)
usernameConfiguration :: UserPool -> Maybe UsernameConfigurationProperty
verificationMessageTemplate :: UserPool -> Maybe VerificationMessageTemplateProperty
webAuthnRelyingPartyID :: UserPool -> Maybe (Value Text)
webAuthnUserVerification :: UserPool -> Maybe (Value Text)
haddock_workaround_ :: ()
accountRecoverySetting :: Maybe AccountRecoverySettingProperty
adminCreateUserConfig :: Maybe AdminCreateUserConfigProperty
aliasAttributes :: Maybe (ValueList Text)
autoVerifiedAttributes :: Maybe (ValueList Text)
deletionProtection :: Maybe (Value Text)
deviceConfiguration :: Maybe DeviceConfigurationProperty
emailAuthenticationMessage :: Maybe (Value Text)
emailAuthenticationSubject :: Maybe (Value Text)
emailConfiguration :: Maybe EmailConfigurationProperty
emailVerificationMessage :: Maybe (Value Text)
emailVerificationSubject :: Maybe (Value Text)
enabledMfas :: Maybe (ValueList Text)
lambdaConfig :: Maybe LambdaConfigProperty
mfaConfiguration :: Maybe (Value Text)
policies :: Maybe PoliciesProperty
schema :: Maybe [SchemaAttributeProperty]
smsAuthenticationMessage :: Maybe (Value Text)
smsConfiguration :: Maybe SmsConfigurationProperty
smsVerificationMessage :: Maybe (Value Text)
userAttributeUpdateSettings :: Maybe UserAttributeUpdateSettingsProperty
userPoolAddOns :: Maybe UserPoolAddOnsProperty
userPoolName :: Maybe (Value Text)
userPoolTags :: Maybe (Map Text (Value Text))
userPoolTier :: Maybe (Value Text)
usernameAttributes :: Maybe (ValueList Text)
usernameConfiguration :: Maybe UsernameConfigurationProperty
verificationMessageTemplate :: Maybe VerificationMessageTemplateProperty
webAuthnRelyingPartyID :: Maybe (Value Text)
webAuthnUserVerification :: Maybe (Value Text)
..}
= UserPool {deletionProtection :: Maybe (Value Text)
deletionProtection = Value Text -> Maybe (Value Text)
forall a. a -> Maybe a
forall (f :: * -> *) a. Applicative f => a -> f a
Prelude.pure PropertyType "DeletionProtection" UserPool
Value Text
newValue, Maybe [SchemaAttributeProperty]
Maybe (Map Text (Value Text))
Maybe (ValueList Text)
Maybe (Value Text)
Maybe DeviceConfigurationProperty
Maybe EmailConfigurationProperty
Maybe AdminCreateUserConfigProperty
Maybe LambdaConfigProperty
Maybe AccountRecoverySettingProperty
Maybe PoliciesProperty
Maybe SmsConfigurationProperty
Maybe UserAttributeUpdateSettingsProperty
Maybe UserPoolAddOnsProperty
Maybe UsernameConfigurationProperty
Maybe VerificationMessageTemplateProperty
()
haddock_workaround_ :: ()
accountRecoverySetting :: Maybe AccountRecoverySettingProperty
adminCreateUserConfig :: Maybe AdminCreateUserConfigProperty
aliasAttributes :: Maybe (ValueList Text)
autoVerifiedAttributes :: Maybe (ValueList Text)
deviceConfiguration :: Maybe DeviceConfigurationProperty
emailAuthenticationMessage :: Maybe (Value Text)
emailAuthenticationSubject :: Maybe (Value Text)
emailConfiguration :: Maybe EmailConfigurationProperty
emailVerificationMessage :: Maybe (Value Text)
emailVerificationSubject :: Maybe (Value Text)
enabledMfas :: Maybe (ValueList Text)
lambdaConfig :: Maybe LambdaConfigProperty
mfaConfiguration :: Maybe (Value Text)
policies :: Maybe PoliciesProperty
schema :: Maybe [SchemaAttributeProperty]
smsAuthenticationMessage :: Maybe (Value Text)
smsConfiguration :: Maybe SmsConfigurationProperty
smsVerificationMessage :: Maybe (Value Text)
userAttributeUpdateSettings :: Maybe UserAttributeUpdateSettingsProperty
userPoolAddOns :: Maybe UserPoolAddOnsProperty
userPoolName :: Maybe (Value Text)
userPoolTags :: Maybe (Map Text (Value Text))
userPoolTier :: Maybe (Value Text)
usernameAttributes :: Maybe (ValueList Text)
usernameConfiguration :: Maybe UsernameConfigurationProperty
verificationMessageTemplate :: Maybe VerificationMessageTemplateProperty
webAuthnRelyingPartyID :: Maybe (Value Text)
webAuthnUserVerification :: Maybe (Value Text)
haddock_workaround_ :: ()
accountRecoverySetting :: Maybe AccountRecoverySettingProperty
adminCreateUserConfig :: Maybe AdminCreateUserConfigProperty
aliasAttributes :: Maybe (ValueList Text)
autoVerifiedAttributes :: Maybe (ValueList Text)
deviceConfiguration :: Maybe DeviceConfigurationProperty
emailAuthenticationMessage :: Maybe (Value Text)
emailAuthenticationSubject :: Maybe (Value Text)
emailConfiguration :: Maybe EmailConfigurationProperty
emailVerificationMessage :: Maybe (Value Text)
emailVerificationSubject :: Maybe (Value Text)
enabledMfas :: Maybe (ValueList Text)
lambdaConfig :: Maybe LambdaConfigProperty
mfaConfiguration :: Maybe (Value Text)
policies :: Maybe PoliciesProperty
schema :: Maybe [SchemaAttributeProperty]
smsAuthenticationMessage :: Maybe (Value Text)
smsConfiguration :: Maybe SmsConfigurationProperty
smsVerificationMessage :: Maybe (Value Text)
userAttributeUpdateSettings :: Maybe UserAttributeUpdateSettingsProperty
userPoolAddOns :: Maybe UserPoolAddOnsProperty
userPoolName :: Maybe (Value Text)
userPoolTags :: Maybe (Map Text (Value Text))
userPoolTier :: Maybe (Value Text)
usernameAttributes :: Maybe (ValueList Text)
usernameConfiguration :: Maybe UsernameConfigurationProperty
verificationMessageTemplate :: Maybe VerificationMessageTemplateProperty
webAuthnRelyingPartyID :: Maybe (Value Text)
webAuthnUserVerification :: Maybe (Value Text)
..}
instance Property "DeviceConfiguration" UserPool where
type PropertyType "DeviceConfiguration" UserPool = DeviceConfigurationProperty
set :: PropertyType "DeviceConfiguration" UserPool -> UserPool -> UserPool
set PropertyType "DeviceConfiguration" UserPool
newValue UserPool {Maybe [SchemaAttributeProperty]
Maybe (Map Text (Value Text))
Maybe (ValueList Text)
Maybe (Value Text)
Maybe DeviceConfigurationProperty
Maybe EmailConfigurationProperty
Maybe AdminCreateUserConfigProperty
Maybe LambdaConfigProperty
Maybe AccountRecoverySettingProperty
Maybe PoliciesProperty
Maybe SmsConfigurationProperty
Maybe UserAttributeUpdateSettingsProperty
Maybe UserPoolAddOnsProperty
Maybe UsernameConfigurationProperty
Maybe VerificationMessageTemplateProperty
()
haddock_workaround_ :: UserPool -> ()
accountRecoverySetting :: UserPool -> Maybe AccountRecoverySettingProperty
adminCreateUserConfig :: UserPool -> Maybe AdminCreateUserConfigProperty
aliasAttributes :: UserPool -> Maybe (ValueList Text)
autoVerifiedAttributes :: UserPool -> Maybe (ValueList Text)
deletionProtection :: UserPool -> Maybe (Value Text)
deviceConfiguration :: UserPool -> Maybe DeviceConfigurationProperty
emailAuthenticationMessage :: UserPool -> Maybe (Value Text)
emailAuthenticationSubject :: UserPool -> Maybe (Value Text)
emailConfiguration :: UserPool -> Maybe EmailConfigurationProperty
emailVerificationMessage :: UserPool -> Maybe (Value Text)
emailVerificationSubject :: UserPool -> Maybe (Value Text)
enabledMfas :: UserPool -> Maybe (ValueList Text)
lambdaConfig :: UserPool -> Maybe LambdaConfigProperty
mfaConfiguration :: UserPool -> Maybe (Value Text)
policies :: UserPool -> Maybe PoliciesProperty
schema :: UserPool -> Maybe [SchemaAttributeProperty]
smsAuthenticationMessage :: UserPool -> Maybe (Value Text)
smsConfiguration :: UserPool -> Maybe SmsConfigurationProperty
smsVerificationMessage :: UserPool -> Maybe (Value Text)
userAttributeUpdateSettings :: UserPool -> Maybe UserAttributeUpdateSettingsProperty
userPoolAddOns :: UserPool -> Maybe UserPoolAddOnsProperty
userPoolName :: UserPool -> Maybe (Value Text)
userPoolTags :: UserPool -> Maybe (Map Text (Value Text))
userPoolTier :: UserPool -> Maybe (Value Text)
usernameAttributes :: UserPool -> Maybe (ValueList Text)
usernameConfiguration :: UserPool -> Maybe UsernameConfigurationProperty
verificationMessageTemplate :: UserPool -> Maybe VerificationMessageTemplateProperty
webAuthnRelyingPartyID :: UserPool -> Maybe (Value Text)
webAuthnUserVerification :: UserPool -> Maybe (Value Text)
haddock_workaround_ :: ()
accountRecoverySetting :: Maybe AccountRecoverySettingProperty
adminCreateUserConfig :: Maybe AdminCreateUserConfigProperty
aliasAttributes :: Maybe (ValueList Text)
autoVerifiedAttributes :: Maybe (ValueList Text)
deletionProtection :: Maybe (Value Text)
deviceConfiguration :: Maybe DeviceConfigurationProperty
emailAuthenticationMessage :: Maybe (Value Text)
emailAuthenticationSubject :: Maybe (Value Text)
emailConfiguration :: Maybe EmailConfigurationProperty
emailVerificationMessage :: Maybe (Value Text)
emailVerificationSubject :: Maybe (Value Text)
enabledMfas :: Maybe (ValueList Text)
lambdaConfig :: Maybe LambdaConfigProperty
mfaConfiguration :: Maybe (Value Text)
policies :: Maybe PoliciesProperty
schema :: Maybe [SchemaAttributeProperty]
smsAuthenticationMessage :: Maybe (Value Text)
smsConfiguration :: Maybe SmsConfigurationProperty
smsVerificationMessage :: Maybe (Value Text)
userAttributeUpdateSettings :: Maybe UserAttributeUpdateSettingsProperty
userPoolAddOns :: Maybe UserPoolAddOnsProperty
userPoolName :: Maybe (Value Text)
userPoolTags :: Maybe (Map Text (Value Text))
userPoolTier :: Maybe (Value Text)
usernameAttributes :: Maybe (ValueList Text)
usernameConfiguration :: Maybe UsernameConfigurationProperty
verificationMessageTemplate :: Maybe VerificationMessageTemplateProperty
webAuthnRelyingPartyID :: Maybe (Value Text)
webAuthnUserVerification :: Maybe (Value Text)
..}
= UserPool {deviceConfiguration :: Maybe DeviceConfigurationProperty
deviceConfiguration = DeviceConfigurationProperty -> Maybe DeviceConfigurationProperty
forall a. a -> Maybe a
forall (f :: * -> *) a. Applicative f => a -> f a
Prelude.pure PropertyType "DeviceConfiguration" UserPool
DeviceConfigurationProperty
newValue, Maybe [SchemaAttributeProperty]
Maybe (Map Text (Value Text))
Maybe (ValueList Text)
Maybe (Value Text)
Maybe EmailConfigurationProperty
Maybe AdminCreateUserConfigProperty
Maybe LambdaConfigProperty
Maybe AccountRecoverySettingProperty
Maybe PoliciesProperty
Maybe SmsConfigurationProperty
Maybe UserAttributeUpdateSettingsProperty
Maybe UserPoolAddOnsProperty
Maybe UsernameConfigurationProperty
Maybe VerificationMessageTemplateProperty
()
haddock_workaround_ :: ()
accountRecoverySetting :: Maybe AccountRecoverySettingProperty
adminCreateUserConfig :: Maybe AdminCreateUserConfigProperty
aliasAttributes :: Maybe (ValueList Text)
autoVerifiedAttributes :: Maybe (ValueList Text)
deletionProtection :: Maybe (Value Text)
emailAuthenticationMessage :: Maybe (Value Text)
emailAuthenticationSubject :: Maybe (Value Text)
emailConfiguration :: Maybe EmailConfigurationProperty
emailVerificationMessage :: Maybe (Value Text)
emailVerificationSubject :: Maybe (Value Text)
enabledMfas :: Maybe (ValueList Text)
lambdaConfig :: Maybe LambdaConfigProperty
mfaConfiguration :: Maybe (Value Text)
policies :: Maybe PoliciesProperty
schema :: Maybe [SchemaAttributeProperty]
smsAuthenticationMessage :: Maybe (Value Text)
smsConfiguration :: Maybe SmsConfigurationProperty
smsVerificationMessage :: Maybe (Value Text)
userAttributeUpdateSettings :: Maybe UserAttributeUpdateSettingsProperty
userPoolAddOns :: Maybe UserPoolAddOnsProperty
userPoolName :: Maybe (Value Text)
userPoolTags :: Maybe (Map Text (Value Text))
userPoolTier :: Maybe (Value Text)
usernameAttributes :: Maybe (ValueList Text)
usernameConfiguration :: Maybe UsernameConfigurationProperty
verificationMessageTemplate :: Maybe VerificationMessageTemplateProperty
webAuthnRelyingPartyID :: Maybe (Value Text)
webAuthnUserVerification :: Maybe (Value Text)
haddock_workaround_ :: ()
accountRecoverySetting :: Maybe AccountRecoverySettingProperty
adminCreateUserConfig :: Maybe AdminCreateUserConfigProperty
aliasAttributes :: Maybe (ValueList Text)
autoVerifiedAttributes :: Maybe (ValueList Text)
deletionProtection :: Maybe (Value Text)
emailAuthenticationMessage :: Maybe (Value Text)
emailAuthenticationSubject :: Maybe (Value Text)
emailConfiguration :: Maybe EmailConfigurationProperty
emailVerificationMessage :: Maybe (Value Text)
emailVerificationSubject :: Maybe (Value Text)
enabledMfas :: Maybe (ValueList Text)
lambdaConfig :: Maybe LambdaConfigProperty
mfaConfiguration :: Maybe (Value Text)
policies :: Maybe PoliciesProperty
schema :: Maybe [SchemaAttributeProperty]
smsAuthenticationMessage :: Maybe (Value Text)
smsConfiguration :: Maybe SmsConfigurationProperty
smsVerificationMessage :: Maybe (Value Text)
userAttributeUpdateSettings :: Maybe UserAttributeUpdateSettingsProperty
userPoolAddOns :: Maybe UserPoolAddOnsProperty
userPoolName :: Maybe (Value Text)
userPoolTags :: Maybe (Map Text (Value Text))
userPoolTier :: Maybe (Value Text)
usernameAttributes :: Maybe (ValueList Text)
usernameConfiguration :: Maybe UsernameConfigurationProperty
verificationMessageTemplate :: Maybe VerificationMessageTemplateProperty
webAuthnRelyingPartyID :: Maybe (Value Text)
webAuthnUserVerification :: Maybe (Value Text)
..}
instance Property "EmailAuthenticationMessage" UserPool where
type PropertyType "EmailAuthenticationMessage" UserPool = Value Prelude.Text
set :: PropertyType "EmailAuthenticationMessage" UserPool
-> UserPool -> UserPool
set PropertyType "EmailAuthenticationMessage" UserPool
newValue UserPool {Maybe [SchemaAttributeProperty]
Maybe (Map Text (Value Text))
Maybe (ValueList Text)
Maybe (Value Text)
Maybe DeviceConfigurationProperty
Maybe EmailConfigurationProperty
Maybe AdminCreateUserConfigProperty
Maybe LambdaConfigProperty
Maybe AccountRecoverySettingProperty
Maybe PoliciesProperty
Maybe SmsConfigurationProperty
Maybe UserAttributeUpdateSettingsProperty
Maybe UserPoolAddOnsProperty
Maybe UsernameConfigurationProperty
Maybe VerificationMessageTemplateProperty
()
haddock_workaround_ :: UserPool -> ()
accountRecoverySetting :: UserPool -> Maybe AccountRecoverySettingProperty
adminCreateUserConfig :: UserPool -> Maybe AdminCreateUserConfigProperty
aliasAttributes :: UserPool -> Maybe (ValueList Text)
autoVerifiedAttributes :: UserPool -> Maybe (ValueList Text)
deletionProtection :: UserPool -> Maybe (Value Text)
deviceConfiguration :: UserPool -> Maybe DeviceConfigurationProperty
emailAuthenticationMessage :: UserPool -> Maybe (Value Text)
emailAuthenticationSubject :: UserPool -> Maybe (Value Text)
emailConfiguration :: UserPool -> Maybe EmailConfigurationProperty
emailVerificationMessage :: UserPool -> Maybe (Value Text)
emailVerificationSubject :: UserPool -> Maybe (Value Text)
enabledMfas :: UserPool -> Maybe (ValueList Text)
lambdaConfig :: UserPool -> Maybe LambdaConfigProperty
mfaConfiguration :: UserPool -> Maybe (Value Text)
policies :: UserPool -> Maybe PoliciesProperty
schema :: UserPool -> Maybe [SchemaAttributeProperty]
smsAuthenticationMessage :: UserPool -> Maybe (Value Text)
smsConfiguration :: UserPool -> Maybe SmsConfigurationProperty
smsVerificationMessage :: UserPool -> Maybe (Value Text)
userAttributeUpdateSettings :: UserPool -> Maybe UserAttributeUpdateSettingsProperty
userPoolAddOns :: UserPool -> Maybe UserPoolAddOnsProperty
userPoolName :: UserPool -> Maybe (Value Text)
userPoolTags :: UserPool -> Maybe (Map Text (Value Text))
userPoolTier :: UserPool -> Maybe (Value Text)
usernameAttributes :: UserPool -> Maybe (ValueList Text)
usernameConfiguration :: UserPool -> Maybe UsernameConfigurationProperty
verificationMessageTemplate :: UserPool -> Maybe VerificationMessageTemplateProperty
webAuthnRelyingPartyID :: UserPool -> Maybe (Value Text)
webAuthnUserVerification :: UserPool -> Maybe (Value Text)
haddock_workaround_ :: ()
accountRecoverySetting :: Maybe AccountRecoverySettingProperty
adminCreateUserConfig :: Maybe AdminCreateUserConfigProperty
aliasAttributes :: Maybe (ValueList Text)
autoVerifiedAttributes :: Maybe (ValueList Text)
deletionProtection :: Maybe (Value Text)
deviceConfiguration :: Maybe DeviceConfigurationProperty
emailAuthenticationMessage :: Maybe (Value Text)
emailAuthenticationSubject :: Maybe (Value Text)
emailConfiguration :: Maybe EmailConfigurationProperty
emailVerificationMessage :: Maybe (Value Text)
emailVerificationSubject :: Maybe (Value Text)
enabledMfas :: Maybe (ValueList Text)
lambdaConfig :: Maybe LambdaConfigProperty
mfaConfiguration :: Maybe (Value Text)
policies :: Maybe PoliciesProperty
schema :: Maybe [SchemaAttributeProperty]
smsAuthenticationMessage :: Maybe (Value Text)
smsConfiguration :: Maybe SmsConfigurationProperty
smsVerificationMessage :: Maybe (Value Text)
userAttributeUpdateSettings :: Maybe UserAttributeUpdateSettingsProperty
userPoolAddOns :: Maybe UserPoolAddOnsProperty
userPoolName :: Maybe (Value Text)
userPoolTags :: Maybe (Map Text (Value Text))
userPoolTier :: Maybe (Value Text)
usernameAttributes :: Maybe (ValueList Text)
usernameConfiguration :: Maybe UsernameConfigurationProperty
verificationMessageTemplate :: Maybe VerificationMessageTemplateProperty
webAuthnRelyingPartyID :: Maybe (Value Text)
webAuthnUserVerification :: Maybe (Value Text)
..}
= UserPool {emailAuthenticationMessage :: Maybe (Value Text)
emailAuthenticationMessage = Value Text -> Maybe (Value Text)
forall a. a -> Maybe a
forall (f :: * -> *) a. Applicative f => a -> f a
Prelude.pure PropertyType "EmailAuthenticationMessage" UserPool
Value Text
newValue, Maybe [SchemaAttributeProperty]
Maybe (Map Text (Value Text))
Maybe (ValueList Text)
Maybe (Value Text)
Maybe DeviceConfigurationProperty
Maybe EmailConfigurationProperty
Maybe AdminCreateUserConfigProperty
Maybe LambdaConfigProperty
Maybe AccountRecoverySettingProperty
Maybe PoliciesProperty
Maybe SmsConfigurationProperty
Maybe UserAttributeUpdateSettingsProperty
Maybe UserPoolAddOnsProperty
Maybe UsernameConfigurationProperty
Maybe VerificationMessageTemplateProperty
()
haddock_workaround_ :: ()
accountRecoverySetting :: Maybe AccountRecoverySettingProperty
adminCreateUserConfig :: Maybe AdminCreateUserConfigProperty
aliasAttributes :: Maybe (ValueList Text)
autoVerifiedAttributes :: Maybe (ValueList Text)
deletionProtection :: Maybe (Value Text)
deviceConfiguration :: Maybe DeviceConfigurationProperty
emailAuthenticationSubject :: Maybe (Value Text)
emailConfiguration :: Maybe EmailConfigurationProperty
emailVerificationMessage :: Maybe (Value Text)
emailVerificationSubject :: Maybe (Value Text)
enabledMfas :: Maybe (ValueList Text)
lambdaConfig :: Maybe LambdaConfigProperty
mfaConfiguration :: Maybe (Value Text)
policies :: Maybe PoliciesProperty
schema :: Maybe [SchemaAttributeProperty]
smsAuthenticationMessage :: Maybe (Value Text)
smsConfiguration :: Maybe SmsConfigurationProperty
smsVerificationMessage :: Maybe (Value Text)
userAttributeUpdateSettings :: Maybe UserAttributeUpdateSettingsProperty
userPoolAddOns :: Maybe UserPoolAddOnsProperty
userPoolName :: Maybe (Value Text)
userPoolTags :: Maybe (Map Text (Value Text))
userPoolTier :: Maybe (Value Text)
usernameAttributes :: Maybe (ValueList Text)
usernameConfiguration :: Maybe UsernameConfigurationProperty
verificationMessageTemplate :: Maybe VerificationMessageTemplateProperty
webAuthnRelyingPartyID :: Maybe (Value Text)
webAuthnUserVerification :: Maybe (Value Text)
haddock_workaround_ :: ()
accountRecoverySetting :: Maybe AccountRecoverySettingProperty
adminCreateUserConfig :: Maybe AdminCreateUserConfigProperty
aliasAttributes :: Maybe (ValueList Text)
autoVerifiedAttributes :: Maybe (ValueList Text)
deletionProtection :: Maybe (Value Text)
deviceConfiguration :: Maybe DeviceConfigurationProperty
emailAuthenticationSubject :: Maybe (Value Text)
emailConfiguration :: Maybe EmailConfigurationProperty
emailVerificationMessage :: Maybe (Value Text)
emailVerificationSubject :: Maybe (Value Text)
enabledMfas :: Maybe (ValueList Text)
lambdaConfig :: Maybe LambdaConfigProperty
mfaConfiguration :: Maybe (Value Text)
policies :: Maybe PoliciesProperty
schema :: Maybe [SchemaAttributeProperty]
smsAuthenticationMessage :: Maybe (Value Text)
smsConfiguration :: Maybe SmsConfigurationProperty
smsVerificationMessage :: Maybe (Value Text)
userAttributeUpdateSettings :: Maybe UserAttributeUpdateSettingsProperty
userPoolAddOns :: Maybe UserPoolAddOnsProperty
userPoolName :: Maybe (Value Text)
userPoolTags :: Maybe (Map Text (Value Text))
userPoolTier :: Maybe (Value Text)
usernameAttributes :: Maybe (ValueList Text)
usernameConfiguration :: Maybe UsernameConfigurationProperty
verificationMessageTemplate :: Maybe VerificationMessageTemplateProperty
webAuthnRelyingPartyID :: Maybe (Value Text)
webAuthnUserVerification :: Maybe (Value Text)
..}
instance Property "EmailAuthenticationSubject" UserPool where
type PropertyType "EmailAuthenticationSubject" UserPool = Value Prelude.Text
set :: PropertyType "EmailAuthenticationSubject" UserPool
-> UserPool -> UserPool
set PropertyType "EmailAuthenticationSubject" UserPool
newValue UserPool {Maybe [SchemaAttributeProperty]
Maybe (Map Text (Value Text))
Maybe (ValueList Text)
Maybe (Value Text)
Maybe DeviceConfigurationProperty
Maybe EmailConfigurationProperty
Maybe AdminCreateUserConfigProperty
Maybe LambdaConfigProperty
Maybe AccountRecoverySettingProperty
Maybe PoliciesProperty
Maybe SmsConfigurationProperty
Maybe UserAttributeUpdateSettingsProperty
Maybe UserPoolAddOnsProperty
Maybe UsernameConfigurationProperty
Maybe VerificationMessageTemplateProperty
()
haddock_workaround_ :: UserPool -> ()
accountRecoverySetting :: UserPool -> Maybe AccountRecoverySettingProperty
adminCreateUserConfig :: UserPool -> Maybe AdminCreateUserConfigProperty
aliasAttributes :: UserPool -> Maybe (ValueList Text)
autoVerifiedAttributes :: UserPool -> Maybe (ValueList Text)
deletionProtection :: UserPool -> Maybe (Value Text)
deviceConfiguration :: UserPool -> Maybe DeviceConfigurationProperty
emailAuthenticationMessage :: UserPool -> Maybe (Value Text)
emailAuthenticationSubject :: UserPool -> Maybe (Value Text)
emailConfiguration :: UserPool -> Maybe EmailConfigurationProperty
emailVerificationMessage :: UserPool -> Maybe (Value Text)
emailVerificationSubject :: UserPool -> Maybe (Value Text)
enabledMfas :: UserPool -> Maybe (ValueList Text)
lambdaConfig :: UserPool -> Maybe LambdaConfigProperty
mfaConfiguration :: UserPool -> Maybe (Value Text)
policies :: UserPool -> Maybe PoliciesProperty
schema :: UserPool -> Maybe [SchemaAttributeProperty]
smsAuthenticationMessage :: UserPool -> Maybe (Value Text)
smsConfiguration :: UserPool -> Maybe SmsConfigurationProperty
smsVerificationMessage :: UserPool -> Maybe (Value Text)
userAttributeUpdateSettings :: UserPool -> Maybe UserAttributeUpdateSettingsProperty
userPoolAddOns :: UserPool -> Maybe UserPoolAddOnsProperty
userPoolName :: UserPool -> Maybe (Value Text)
userPoolTags :: UserPool -> Maybe (Map Text (Value Text))
userPoolTier :: UserPool -> Maybe (Value Text)
usernameAttributes :: UserPool -> Maybe (ValueList Text)
usernameConfiguration :: UserPool -> Maybe UsernameConfigurationProperty
verificationMessageTemplate :: UserPool -> Maybe VerificationMessageTemplateProperty
webAuthnRelyingPartyID :: UserPool -> Maybe (Value Text)
webAuthnUserVerification :: UserPool -> Maybe (Value Text)
haddock_workaround_ :: ()
accountRecoverySetting :: Maybe AccountRecoverySettingProperty
adminCreateUserConfig :: Maybe AdminCreateUserConfigProperty
aliasAttributes :: Maybe (ValueList Text)
autoVerifiedAttributes :: Maybe (ValueList Text)
deletionProtection :: Maybe (Value Text)
deviceConfiguration :: Maybe DeviceConfigurationProperty
emailAuthenticationMessage :: Maybe (Value Text)
emailAuthenticationSubject :: Maybe (Value Text)
emailConfiguration :: Maybe EmailConfigurationProperty
emailVerificationMessage :: Maybe (Value Text)
emailVerificationSubject :: Maybe (Value Text)
enabledMfas :: Maybe (ValueList Text)
lambdaConfig :: Maybe LambdaConfigProperty
mfaConfiguration :: Maybe (Value Text)
policies :: Maybe PoliciesProperty
schema :: Maybe [SchemaAttributeProperty]
smsAuthenticationMessage :: Maybe (Value Text)
smsConfiguration :: Maybe SmsConfigurationProperty
smsVerificationMessage :: Maybe (Value Text)
userAttributeUpdateSettings :: Maybe UserAttributeUpdateSettingsProperty
userPoolAddOns :: Maybe UserPoolAddOnsProperty
userPoolName :: Maybe (Value Text)
userPoolTags :: Maybe (Map Text (Value Text))
userPoolTier :: Maybe (Value Text)
usernameAttributes :: Maybe (ValueList Text)
usernameConfiguration :: Maybe UsernameConfigurationProperty
verificationMessageTemplate :: Maybe VerificationMessageTemplateProperty
webAuthnRelyingPartyID :: Maybe (Value Text)
webAuthnUserVerification :: Maybe (Value Text)
..}
= UserPool {emailAuthenticationSubject :: Maybe (Value Text)
emailAuthenticationSubject = Value Text -> Maybe (Value Text)
forall a. a -> Maybe a
forall (f :: * -> *) a. Applicative f => a -> f a
Prelude.pure PropertyType "EmailAuthenticationSubject" UserPool
Value Text
newValue, Maybe [SchemaAttributeProperty]
Maybe (Map Text (Value Text))
Maybe (ValueList Text)
Maybe (Value Text)
Maybe DeviceConfigurationProperty
Maybe EmailConfigurationProperty
Maybe AdminCreateUserConfigProperty
Maybe LambdaConfigProperty
Maybe AccountRecoverySettingProperty
Maybe PoliciesProperty
Maybe SmsConfigurationProperty
Maybe UserAttributeUpdateSettingsProperty
Maybe UserPoolAddOnsProperty
Maybe UsernameConfigurationProperty
Maybe VerificationMessageTemplateProperty
()
haddock_workaround_ :: ()
accountRecoverySetting :: Maybe AccountRecoverySettingProperty
adminCreateUserConfig :: Maybe AdminCreateUserConfigProperty
aliasAttributes :: Maybe (ValueList Text)
autoVerifiedAttributes :: Maybe (ValueList Text)
deletionProtection :: Maybe (Value Text)
deviceConfiguration :: Maybe DeviceConfigurationProperty
emailAuthenticationMessage :: Maybe (Value Text)
emailConfiguration :: Maybe EmailConfigurationProperty
emailVerificationMessage :: Maybe (Value Text)
emailVerificationSubject :: Maybe (Value Text)
enabledMfas :: Maybe (ValueList Text)
lambdaConfig :: Maybe LambdaConfigProperty
mfaConfiguration :: Maybe (Value Text)
policies :: Maybe PoliciesProperty
schema :: Maybe [SchemaAttributeProperty]
smsAuthenticationMessage :: Maybe (Value Text)
smsConfiguration :: Maybe SmsConfigurationProperty
smsVerificationMessage :: Maybe (Value Text)
userAttributeUpdateSettings :: Maybe UserAttributeUpdateSettingsProperty
userPoolAddOns :: Maybe UserPoolAddOnsProperty
userPoolName :: Maybe (Value Text)
userPoolTags :: Maybe (Map Text (Value Text))
userPoolTier :: Maybe (Value Text)
usernameAttributes :: Maybe (ValueList Text)
usernameConfiguration :: Maybe UsernameConfigurationProperty
verificationMessageTemplate :: Maybe VerificationMessageTemplateProperty
webAuthnRelyingPartyID :: Maybe (Value Text)
webAuthnUserVerification :: Maybe (Value Text)
haddock_workaround_ :: ()
accountRecoverySetting :: Maybe AccountRecoverySettingProperty
adminCreateUserConfig :: Maybe AdminCreateUserConfigProperty
aliasAttributes :: Maybe (ValueList Text)
autoVerifiedAttributes :: Maybe (ValueList Text)
deletionProtection :: Maybe (Value Text)
deviceConfiguration :: Maybe DeviceConfigurationProperty
emailAuthenticationMessage :: Maybe (Value Text)
emailConfiguration :: Maybe EmailConfigurationProperty
emailVerificationMessage :: Maybe (Value Text)
emailVerificationSubject :: Maybe (Value Text)
enabledMfas :: Maybe (ValueList Text)
lambdaConfig :: Maybe LambdaConfigProperty
mfaConfiguration :: Maybe (Value Text)
policies :: Maybe PoliciesProperty
schema :: Maybe [SchemaAttributeProperty]
smsAuthenticationMessage :: Maybe (Value Text)
smsConfiguration :: Maybe SmsConfigurationProperty
smsVerificationMessage :: Maybe (Value Text)
userAttributeUpdateSettings :: Maybe UserAttributeUpdateSettingsProperty
userPoolAddOns :: Maybe UserPoolAddOnsProperty
userPoolName :: Maybe (Value Text)
userPoolTags :: Maybe (Map Text (Value Text))
userPoolTier :: Maybe (Value Text)
usernameAttributes :: Maybe (ValueList Text)
usernameConfiguration :: Maybe UsernameConfigurationProperty
verificationMessageTemplate :: Maybe VerificationMessageTemplateProperty
webAuthnRelyingPartyID :: Maybe (Value Text)
webAuthnUserVerification :: Maybe (Value Text)
..}
instance Property "EmailConfiguration" UserPool where
type PropertyType "EmailConfiguration" UserPool = EmailConfigurationProperty
set :: PropertyType "EmailConfiguration" UserPool -> UserPool -> UserPool
set PropertyType "EmailConfiguration" UserPool
newValue UserPool {Maybe [SchemaAttributeProperty]
Maybe (Map Text (Value Text))
Maybe (ValueList Text)
Maybe (Value Text)
Maybe DeviceConfigurationProperty
Maybe EmailConfigurationProperty
Maybe AdminCreateUserConfigProperty
Maybe LambdaConfigProperty
Maybe AccountRecoverySettingProperty
Maybe PoliciesProperty
Maybe SmsConfigurationProperty
Maybe UserAttributeUpdateSettingsProperty
Maybe UserPoolAddOnsProperty
Maybe UsernameConfigurationProperty
Maybe VerificationMessageTemplateProperty
()
haddock_workaround_ :: UserPool -> ()
accountRecoverySetting :: UserPool -> Maybe AccountRecoverySettingProperty
adminCreateUserConfig :: UserPool -> Maybe AdminCreateUserConfigProperty
aliasAttributes :: UserPool -> Maybe (ValueList Text)
autoVerifiedAttributes :: UserPool -> Maybe (ValueList Text)
deletionProtection :: UserPool -> Maybe (Value Text)
deviceConfiguration :: UserPool -> Maybe DeviceConfigurationProperty
emailAuthenticationMessage :: UserPool -> Maybe (Value Text)
emailAuthenticationSubject :: UserPool -> Maybe (Value Text)
emailConfiguration :: UserPool -> Maybe EmailConfigurationProperty
emailVerificationMessage :: UserPool -> Maybe (Value Text)
emailVerificationSubject :: UserPool -> Maybe (Value Text)
enabledMfas :: UserPool -> Maybe (ValueList Text)
lambdaConfig :: UserPool -> Maybe LambdaConfigProperty
mfaConfiguration :: UserPool -> Maybe (Value Text)
policies :: UserPool -> Maybe PoliciesProperty
schema :: UserPool -> Maybe [SchemaAttributeProperty]
smsAuthenticationMessage :: UserPool -> Maybe (Value Text)
smsConfiguration :: UserPool -> Maybe SmsConfigurationProperty
smsVerificationMessage :: UserPool -> Maybe (Value Text)
userAttributeUpdateSettings :: UserPool -> Maybe UserAttributeUpdateSettingsProperty
userPoolAddOns :: UserPool -> Maybe UserPoolAddOnsProperty
userPoolName :: UserPool -> Maybe (Value Text)
userPoolTags :: UserPool -> Maybe (Map Text (Value Text))
userPoolTier :: UserPool -> Maybe (Value Text)
usernameAttributes :: UserPool -> Maybe (ValueList Text)
usernameConfiguration :: UserPool -> Maybe UsernameConfigurationProperty
verificationMessageTemplate :: UserPool -> Maybe VerificationMessageTemplateProperty
webAuthnRelyingPartyID :: UserPool -> Maybe (Value Text)
webAuthnUserVerification :: UserPool -> Maybe (Value Text)
haddock_workaround_ :: ()
accountRecoverySetting :: Maybe AccountRecoverySettingProperty
adminCreateUserConfig :: Maybe AdminCreateUserConfigProperty
aliasAttributes :: Maybe (ValueList Text)
autoVerifiedAttributes :: Maybe (ValueList Text)
deletionProtection :: Maybe (Value Text)
deviceConfiguration :: Maybe DeviceConfigurationProperty
emailAuthenticationMessage :: Maybe (Value Text)
emailAuthenticationSubject :: Maybe (Value Text)
emailConfiguration :: Maybe EmailConfigurationProperty
emailVerificationMessage :: Maybe (Value Text)
emailVerificationSubject :: Maybe (Value Text)
enabledMfas :: Maybe (ValueList Text)
lambdaConfig :: Maybe LambdaConfigProperty
mfaConfiguration :: Maybe (Value Text)
policies :: Maybe PoliciesProperty
schema :: Maybe [SchemaAttributeProperty]
smsAuthenticationMessage :: Maybe (Value Text)
smsConfiguration :: Maybe SmsConfigurationProperty
smsVerificationMessage :: Maybe (Value Text)
userAttributeUpdateSettings :: Maybe UserAttributeUpdateSettingsProperty
userPoolAddOns :: Maybe UserPoolAddOnsProperty
userPoolName :: Maybe (Value Text)
userPoolTags :: Maybe (Map Text (Value Text))
userPoolTier :: Maybe (Value Text)
usernameAttributes :: Maybe (ValueList Text)
usernameConfiguration :: Maybe UsernameConfigurationProperty
verificationMessageTemplate :: Maybe VerificationMessageTemplateProperty
webAuthnRelyingPartyID :: Maybe (Value Text)
webAuthnUserVerification :: Maybe (Value Text)
..}
= UserPool {emailConfiguration :: Maybe EmailConfigurationProperty
emailConfiguration = EmailConfigurationProperty -> Maybe EmailConfigurationProperty
forall a. a -> Maybe a
forall (f :: * -> *) a. Applicative f => a -> f a
Prelude.pure PropertyType "EmailConfiguration" UserPool
EmailConfigurationProperty
newValue, Maybe [SchemaAttributeProperty]
Maybe (Map Text (Value Text))
Maybe (ValueList Text)
Maybe (Value Text)
Maybe DeviceConfigurationProperty
Maybe AdminCreateUserConfigProperty
Maybe LambdaConfigProperty
Maybe AccountRecoverySettingProperty
Maybe PoliciesProperty
Maybe SmsConfigurationProperty
Maybe UserAttributeUpdateSettingsProperty
Maybe UserPoolAddOnsProperty
Maybe UsernameConfigurationProperty
Maybe VerificationMessageTemplateProperty
()
haddock_workaround_ :: ()
accountRecoverySetting :: Maybe AccountRecoverySettingProperty
adminCreateUserConfig :: Maybe AdminCreateUserConfigProperty
aliasAttributes :: Maybe (ValueList Text)
autoVerifiedAttributes :: Maybe (ValueList Text)
deletionProtection :: Maybe (Value Text)
deviceConfiguration :: Maybe DeviceConfigurationProperty
emailAuthenticationMessage :: Maybe (Value Text)
emailAuthenticationSubject :: Maybe (Value Text)
emailVerificationMessage :: Maybe (Value Text)
emailVerificationSubject :: Maybe (Value Text)
enabledMfas :: Maybe (ValueList Text)
lambdaConfig :: Maybe LambdaConfigProperty
mfaConfiguration :: Maybe (Value Text)
policies :: Maybe PoliciesProperty
schema :: Maybe [SchemaAttributeProperty]
smsAuthenticationMessage :: Maybe (Value Text)
smsConfiguration :: Maybe SmsConfigurationProperty
smsVerificationMessage :: Maybe (Value Text)
userAttributeUpdateSettings :: Maybe UserAttributeUpdateSettingsProperty
userPoolAddOns :: Maybe UserPoolAddOnsProperty
userPoolName :: Maybe (Value Text)
userPoolTags :: Maybe (Map Text (Value Text))
userPoolTier :: Maybe (Value Text)
usernameAttributes :: Maybe (ValueList Text)
usernameConfiguration :: Maybe UsernameConfigurationProperty
verificationMessageTemplate :: Maybe VerificationMessageTemplateProperty
webAuthnRelyingPartyID :: Maybe (Value Text)
webAuthnUserVerification :: Maybe (Value Text)
haddock_workaround_ :: ()
accountRecoverySetting :: Maybe AccountRecoverySettingProperty
adminCreateUserConfig :: Maybe AdminCreateUserConfigProperty
aliasAttributes :: Maybe (ValueList Text)
autoVerifiedAttributes :: Maybe (ValueList Text)
deletionProtection :: Maybe (Value Text)
deviceConfiguration :: Maybe DeviceConfigurationProperty
emailAuthenticationMessage :: Maybe (Value Text)
emailAuthenticationSubject :: Maybe (Value Text)
emailVerificationMessage :: Maybe (Value Text)
emailVerificationSubject :: Maybe (Value Text)
enabledMfas :: Maybe (ValueList Text)
lambdaConfig :: Maybe LambdaConfigProperty
mfaConfiguration :: Maybe (Value Text)
policies :: Maybe PoliciesProperty
schema :: Maybe [SchemaAttributeProperty]
smsAuthenticationMessage :: Maybe (Value Text)
smsConfiguration :: Maybe SmsConfigurationProperty
smsVerificationMessage :: Maybe (Value Text)
userAttributeUpdateSettings :: Maybe UserAttributeUpdateSettingsProperty
userPoolAddOns :: Maybe UserPoolAddOnsProperty
userPoolName :: Maybe (Value Text)
userPoolTags :: Maybe (Map Text (Value Text))
userPoolTier :: Maybe (Value Text)
usernameAttributes :: Maybe (ValueList Text)
usernameConfiguration :: Maybe UsernameConfigurationProperty
verificationMessageTemplate :: Maybe VerificationMessageTemplateProperty
webAuthnRelyingPartyID :: Maybe (Value Text)
webAuthnUserVerification :: Maybe (Value Text)
..}
instance Property "EmailVerificationMessage" UserPool where
type PropertyType "EmailVerificationMessage" UserPool = Value Prelude.Text
set :: PropertyType "EmailVerificationMessage" UserPool
-> UserPool -> UserPool
set PropertyType "EmailVerificationMessage" UserPool
newValue UserPool {Maybe [SchemaAttributeProperty]
Maybe (Map Text (Value Text))
Maybe (ValueList Text)
Maybe (Value Text)
Maybe DeviceConfigurationProperty
Maybe EmailConfigurationProperty
Maybe AdminCreateUserConfigProperty
Maybe LambdaConfigProperty
Maybe AccountRecoverySettingProperty
Maybe PoliciesProperty
Maybe SmsConfigurationProperty
Maybe UserAttributeUpdateSettingsProperty
Maybe UserPoolAddOnsProperty
Maybe UsernameConfigurationProperty
Maybe VerificationMessageTemplateProperty
()
haddock_workaround_ :: UserPool -> ()
accountRecoverySetting :: UserPool -> Maybe AccountRecoverySettingProperty
adminCreateUserConfig :: UserPool -> Maybe AdminCreateUserConfigProperty
aliasAttributes :: UserPool -> Maybe (ValueList Text)
autoVerifiedAttributes :: UserPool -> Maybe (ValueList Text)
deletionProtection :: UserPool -> Maybe (Value Text)
deviceConfiguration :: UserPool -> Maybe DeviceConfigurationProperty
emailAuthenticationMessage :: UserPool -> Maybe (Value Text)
emailAuthenticationSubject :: UserPool -> Maybe (Value Text)
emailConfiguration :: UserPool -> Maybe EmailConfigurationProperty
emailVerificationMessage :: UserPool -> Maybe (Value Text)
emailVerificationSubject :: UserPool -> Maybe (Value Text)
enabledMfas :: UserPool -> Maybe (ValueList Text)
lambdaConfig :: UserPool -> Maybe LambdaConfigProperty
mfaConfiguration :: UserPool -> Maybe (Value Text)
policies :: UserPool -> Maybe PoliciesProperty
schema :: UserPool -> Maybe [SchemaAttributeProperty]
smsAuthenticationMessage :: UserPool -> Maybe (Value Text)
smsConfiguration :: UserPool -> Maybe SmsConfigurationProperty
smsVerificationMessage :: UserPool -> Maybe (Value Text)
userAttributeUpdateSettings :: UserPool -> Maybe UserAttributeUpdateSettingsProperty
userPoolAddOns :: UserPool -> Maybe UserPoolAddOnsProperty
userPoolName :: UserPool -> Maybe (Value Text)
userPoolTags :: UserPool -> Maybe (Map Text (Value Text))
userPoolTier :: UserPool -> Maybe (Value Text)
usernameAttributes :: UserPool -> Maybe (ValueList Text)
usernameConfiguration :: UserPool -> Maybe UsernameConfigurationProperty
verificationMessageTemplate :: UserPool -> Maybe VerificationMessageTemplateProperty
webAuthnRelyingPartyID :: UserPool -> Maybe (Value Text)
webAuthnUserVerification :: UserPool -> Maybe (Value Text)
haddock_workaround_ :: ()
accountRecoverySetting :: Maybe AccountRecoverySettingProperty
adminCreateUserConfig :: Maybe AdminCreateUserConfigProperty
aliasAttributes :: Maybe (ValueList Text)
autoVerifiedAttributes :: Maybe (ValueList Text)
deletionProtection :: Maybe (Value Text)
deviceConfiguration :: Maybe DeviceConfigurationProperty
emailAuthenticationMessage :: Maybe (Value Text)
emailAuthenticationSubject :: Maybe (Value Text)
emailConfiguration :: Maybe EmailConfigurationProperty
emailVerificationMessage :: Maybe (Value Text)
emailVerificationSubject :: Maybe (Value Text)
enabledMfas :: Maybe (ValueList Text)
lambdaConfig :: Maybe LambdaConfigProperty
mfaConfiguration :: Maybe (Value Text)
policies :: Maybe PoliciesProperty
schema :: Maybe [SchemaAttributeProperty]
smsAuthenticationMessage :: Maybe (Value Text)
smsConfiguration :: Maybe SmsConfigurationProperty
smsVerificationMessage :: Maybe (Value Text)
userAttributeUpdateSettings :: Maybe UserAttributeUpdateSettingsProperty
userPoolAddOns :: Maybe UserPoolAddOnsProperty
userPoolName :: Maybe (Value Text)
userPoolTags :: Maybe (Map Text (Value Text))
userPoolTier :: Maybe (Value Text)
usernameAttributes :: Maybe (ValueList Text)
usernameConfiguration :: Maybe UsernameConfigurationProperty
verificationMessageTemplate :: Maybe VerificationMessageTemplateProperty
webAuthnRelyingPartyID :: Maybe (Value Text)
webAuthnUserVerification :: Maybe (Value Text)
..}
= UserPool {emailVerificationMessage :: Maybe (Value Text)
emailVerificationMessage = Value Text -> Maybe (Value Text)
forall a. a -> Maybe a
forall (f :: * -> *) a. Applicative f => a -> f a
Prelude.pure PropertyType "EmailVerificationMessage" UserPool
Value Text
newValue, Maybe [SchemaAttributeProperty]
Maybe (Map Text (Value Text))
Maybe (ValueList Text)
Maybe (Value Text)
Maybe DeviceConfigurationProperty
Maybe EmailConfigurationProperty
Maybe AdminCreateUserConfigProperty
Maybe LambdaConfigProperty
Maybe AccountRecoverySettingProperty
Maybe PoliciesProperty
Maybe SmsConfigurationProperty
Maybe UserAttributeUpdateSettingsProperty
Maybe UserPoolAddOnsProperty
Maybe UsernameConfigurationProperty
Maybe VerificationMessageTemplateProperty
()
haddock_workaround_ :: ()
accountRecoverySetting :: Maybe AccountRecoverySettingProperty
adminCreateUserConfig :: Maybe AdminCreateUserConfigProperty
aliasAttributes :: Maybe (ValueList Text)
autoVerifiedAttributes :: Maybe (ValueList Text)
deletionProtection :: Maybe (Value Text)
deviceConfiguration :: Maybe DeviceConfigurationProperty
emailAuthenticationMessage :: Maybe (Value Text)
emailAuthenticationSubject :: Maybe (Value Text)
emailConfiguration :: Maybe EmailConfigurationProperty
emailVerificationSubject :: Maybe (Value Text)
enabledMfas :: Maybe (ValueList Text)
lambdaConfig :: Maybe LambdaConfigProperty
mfaConfiguration :: Maybe (Value Text)
policies :: Maybe PoliciesProperty
schema :: Maybe [SchemaAttributeProperty]
smsAuthenticationMessage :: Maybe (Value Text)
smsConfiguration :: Maybe SmsConfigurationProperty
smsVerificationMessage :: Maybe (Value Text)
userAttributeUpdateSettings :: Maybe UserAttributeUpdateSettingsProperty
userPoolAddOns :: Maybe UserPoolAddOnsProperty
userPoolName :: Maybe (Value Text)
userPoolTags :: Maybe (Map Text (Value Text))
userPoolTier :: Maybe (Value Text)
usernameAttributes :: Maybe (ValueList Text)
usernameConfiguration :: Maybe UsernameConfigurationProperty
verificationMessageTemplate :: Maybe VerificationMessageTemplateProperty
webAuthnRelyingPartyID :: Maybe (Value Text)
webAuthnUserVerification :: Maybe (Value Text)
haddock_workaround_ :: ()
accountRecoverySetting :: Maybe AccountRecoverySettingProperty
adminCreateUserConfig :: Maybe AdminCreateUserConfigProperty
aliasAttributes :: Maybe (ValueList Text)
autoVerifiedAttributes :: Maybe (ValueList Text)
deletionProtection :: Maybe (Value Text)
deviceConfiguration :: Maybe DeviceConfigurationProperty
emailAuthenticationMessage :: Maybe (Value Text)
emailAuthenticationSubject :: Maybe (Value Text)
emailConfiguration :: Maybe EmailConfigurationProperty
emailVerificationSubject :: Maybe (Value Text)
enabledMfas :: Maybe (ValueList Text)
lambdaConfig :: Maybe LambdaConfigProperty
mfaConfiguration :: Maybe (Value Text)
policies :: Maybe PoliciesProperty
schema :: Maybe [SchemaAttributeProperty]
smsAuthenticationMessage :: Maybe (Value Text)
smsConfiguration :: Maybe SmsConfigurationProperty
smsVerificationMessage :: Maybe (Value Text)
userAttributeUpdateSettings :: Maybe UserAttributeUpdateSettingsProperty
userPoolAddOns :: Maybe UserPoolAddOnsProperty
userPoolName :: Maybe (Value Text)
userPoolTags :: Maybe (Map Text (Value Text))
userPoolTier :: Maybe (Value Text)
usernameAttributes :: Maybe (ValueList Text)
usernameConfiguration :: Maybe UsernameConfigurationProperty
verificationMessageTemplate :: Maybe VerificationMessageTemplateProperty
webAuthnRelyingPartyID :: Maybe (Value Text)
webAuthnUserVerification :: Maybe (Value Text)
..}
instance Property "EmailVerificationSubject" UserPool where
type PropertyType "EmailVerificationSubject" UserPool = Value Prelude.Text
set :: PropertyType "EmailVerificationSubject" UserPool
-> UserPool -> UserPool
set PropertyType "EmailVerificationSubject" UserPool
newValue UserPool {Maybe [SchemaAttributeProperty]
Maybe (Map Text (Value Text))
Maybe (ValueList Text)
Maybe (Value Text)
Maybe DeviceConfigurationProperty
Maybe EmailConfigurationProperty
Maybe AdminCreateUserConfigProperty
Maybe LambdaConfigProperty
Maybe AccountRecoverySettingProperty
Maybe PoliciesProperty
Maybe SmsConfigurationProperty
Maybe UserAttributeUpdateSettingsProperty
Maybe UserPoolAddOnsProperty
Maybe UsernameConfigurationProperty
Maybe VerificationMessageTemplateProperty
()
haddock_workaround_ :: UserPool -> ()
accountRecoverySetting :: UserPool -> Maybe AccountRecoverySettingProperty
adminCreateUserConfig :: UserPool -> Maybe AdminCreateUserConfigProperty
aliasAttributes :: UserPool -> Maybe (ValueList Text)
autoVerifiedAttributes :: UserPool -> Maybe (ValueList Text)
deletionProtection :: UserPool -> Maybe (Value Text)
deviceConfiguration :: UserPool -> Maybe DeviceConfigurationProperty
emailAuthenticationMessage :: UserPool -> Maybe (Value Text)
emailAuthenticationSubject :: UserPool -> Maybe (Value Text)
emailConfiguration :: UserPool -> Maybe EmailConfigurationProperty
emailVerificationMessage :: UserPool -> Maybe (Value Text)
emailVerificationSubject :: UserPool -> Maybe (Value Text)
enabledMfas :: UserPool -> Maybe (ValueList Text)
lambdaConfig :: UserPool -> Maybe LambdaConfigProperty
mfaConfiguration :: UserPool -> Maybe (Value Text)
policies :: UserPool -> Maybe PoliciesProperty
schema :: UserPool -> Maybe [SchemaAttributeProperty]
smsAuthenticationMessage :: UserPool -> Maybe (Value Text)
smsConfiguration :: UserPool -> Maybe SmsConfigurationProperty
smsVerificationMessage :: UserPool -> Maybe (Value Text)
userAttributeUpdateSettings :: UserPool -> Maybe UserAttributeUpdateSettingsProperty
userPoolAddOns :: UserPool -> Maybe UserPoolAddOnsProperty
userPoolName :: UserPool -> Maybe (Value Text)
userPoolTags :: UserPool -> Maybe (Map Text (Value Text))
userPoolTier :: UserPool -> Maybe (Value Text)
usernameAttributes :: UserPool -> Maybe (ValueList Text)
usernameConfiguration :: UserPool -> Maybe UsernameConfigurationProperty
verificationMessageTemplate :: UserPool -> Maybe VerificationMessageTemplateProperty
webAuthnRelyingPartyID :: UserPool -> Maybe (Value Text)
webAuthnUserVerification :: UserPool -> Maybe (Value Text)
haddock_workaround_ :: ()
accountRecoverySetting :: Maybe AccountRecoverySettingProperty
adminCreateUserConfig :: Maybe AdminCreateUserConfigProperty
aliasAttributes :: Maybe (ValueList Text)
autoVerifiedAttributes :: Maybe (ValueList Text)
deletionProtection :: Maybe (Value Text)
deviceConfiguration :: Maybe DeviceConfigurationProperty
emailAuthenticationMessage :: Maybe (Value Text)
emailAuthenticationSubject :: Maybe (Value Text)
emailConfiguration :: Maybe EmailConfigurationProperty
emailVerificationMessage :: Maybe (Value Text)
emailVerificationSubject :: Maybe (Value Text)
enabledMfas :: Maybe (ValueList Text)
lambdaConfig :: Maybe LambdaConfigProperty
mfaConfiguration :: Maybe (Value Text)
policies :: Maybe PoliciesProperty
schema :: Maybe [SchemaAttributeProperty]
smsAuthenticationMessage :: Maybe (Value Text)
smsConfiguration :: Maybe SmsConfigurationProperty
smsVerificationMessage :: Maybe (Value Text)
userAttributeUpdateSettings :: Maybe UserAttributeUpdateSettingsProperty
userPoolAddOns :: Maybe UserPoolAddOnsProperty
userPoolName :: Maybe (Value Text)
userPoolTags :: Maybe (Map Text (Value Text))
userPoolTier :: Maybe (Value Text)
usernameAttributes :: Maybe (ValueList Text)
usernameConfiguration :: Maybe UsernameConfigurationProperty
verificationMessageTemplate :: Maybe VerificationMessageTemplateProperty
webAuthnRelyingPartyID :: Maybe (Value Text)
webAuthnUserVerification :: Maybe (Value Text)
..}
= UserPool {emailVerificationSubject :: Maybe (Value Text)
emailVerificationSubject = Value Text -> Maybe (Value Text)
forall a. a -> Maybe a
forall (f :: * -> *) a. Applicative f => a -> f a
Prelude.pure PropertyType "EmailVerificationSubject" UserPool
Value Text
newValue, Maybe [SchemaAttributeProperty]
Maybe (Map Text (Value Text))
Maybe (ValueList Text)
Maybe (Value Text)
Maybe DeviceConfigurationProperty
Maybe EmailConfigurationProperty
Maybe AdminCreateUserConfigProperty
Maybe LambdaConfigProperty
Maybe AccountRecoverySettingProperty
Maybe PoliciesProperty
Maybe SmsConfigurationProperty
Maybe UserAttributeUpdateSettingsProperty
Maybe UserPoolAddOnsProperty
Maybe UsernameConfigurationProperty
Maybe VerificationMessageTemplateProperty
()
haddock_workaround_ :: ()
accountRecoverySetting :: Maybe AccountRecoverySettingProperty
adminCreateUserConfig :: Maybe AdminCreateUserConfigProperty
aliasAttributes :: Maybe (ValueList Text)
autoVerifiedAttributes :: Maybe (ValueList Text)
deletionProtection :: Maybe (Value Text)
deviceConfiguration :: Maybe DeviceConfigurationProperty
emailAuthenticationMessage :: Maybe (Value Text)
emailAuthenticationSubject :: Maybe (Value Text)
emailConfiguration :: Maybe EmailConfigurationProperty
emailVerificationMessage :: Maybe (Value Text)
enabledMfas :: Maybe (ValueList Text)
lambdaConfig :: Maybe LambdaConfigProperty
mfaConfiguration :: Maybe (Value Text)
policies :: Maybe PoliciesProperty
schema :: Maybe [SchemaAttributeProperty]
smsAuthenticationMessage :: Maybe (Value Text)
smsConfiguration :: Maybe SmsConfigurationProperty
smsVerificationMessage :: Maybe (Value Text)
userAttributeUpdateSettings :: Maybe UserAttributeUpdateSettingsProperty
userPoolAddOns :: Maybe UserPoolAddOnsProperty
userPoolName :: Maybe (Value Text)
userPoolTags :: Maybe (Map Text (Value Text))
userPoolTier :: Maybe (Value Text)
usernameAttributes :: Maybe (ValueList Text)
usernameConfiguration :: Maybe UsernameConfigurationProperty
verificationMessageTemplate :: Maybe VerificationMessageTemplateProperty
webAuthnRelyingPartyID :: Maybe (Value Text)
webAuthnUserVerification :: Maybe (Value Text)
haddock_workaround_ :: ()
accountRecoverySetting :: Maybe AccountRecoverySettingProperty
adminCreateUserConfig :: Maybe AdminCreateUserConfigProperty
aliasAttributes :: Maybe (ValueList Text)
autoVerifiedAttributes :: Maybe (ValueList Text)
deletionProtection :: Maybe (Value Text)
deviceConfiguration :: Maybe DeviceConfigurationProperty
emailAuthenticationMessage :: Maybe (Value Text)
emailAuthenticationSubject :: Maybe (Value Text)
emailConfiguration :: Maybe EmailConfigurationProperty
emailVerificationMessage :: Maybe (Value Text)
enabledMfas :: Maybe (ValueList Text)
lambdaConfig :: Maybe LambdaConfigProperty
mfaConfiguration :: Maybe (Value Text)
policies :: Maybe PoliciesProperty
schema :: Maybe [SchemaAttributeProperty]
smsAuthenticationMessage :: Maybe (Value Text)
smsConfiguration :: Maybe SmsConfigurationProperty
smsVerificationMessage :: Maybe (Value Text)
userAttributeUpdateSettings :: Maybe UserAttributeUpdateSettingsProperty
userPoolAddOns :: Maybe UserPoolAddOnsProperty
userPoolName :: Maybe (Value Text)
userPoolTags :: Maybe (Map Text (Value Text))
userPoolTier :: Maybe (Value Text)
usernameAttributes :: Maybe (ValueList Text)
usernameConfiguration :: Maybe UsernameConfigurationProperty
verificationMessageTemplate :: Maybe VerificationMessageTemplateProperty
webAuthnRelyingPartyID :: Maybe (Value Text)
webAuthnUserVerification :: Maybe (Value Text)
..}
instance Property "EnabledMfas" UserPool where
type PropertyType "EnabledMfas" UserPool = ValueList Prelude.Text
set :: PropertyType "EnabledMfas" UserPool -> UserPool -> UserPool
set PropertyType "EnabledMfas" UserPool
newValue UserPool {Maybe [SchemaAttributeProperty]
Maybe (Map Text (Value Text))
Maybe (ValueList Text)
Maybe (Value Text)
Maybe DeviceConfigurationProperty
Maybe EmailConfigurationProperty
Maybe AdminCreateUserConfigProperty
Maybe LambdaConfigProperty
Maybe AccountRecoverySettingProperty
Maybe PoliciesProperty
Maybe SmsConfigurationProperty
Maybe UserAttributeUpdateSettingsProperty
Maybe UserPoolAddOnsProperty
Maybe UsernameConfigurationProperty
Maybe VerificationMessageTemplateProperty
()
haddock_workaround_ :: UserPool -> ()
accountRecoverySetting :: UserPool -> Maybe AccountRecoverySettingProperty
adminCreateUserConfig :: UserPool -> Maybe AdminCreateUserConfigProperty
aliasAttributes :: UserPool -> Maybe (ValueList Text)
autoVerifiedAttributes :: UserPool -> Maybe (ValueList Text)
deletionProtection :: UserPool -> Maybe (Value Text)
deviceConfiguration :: UserPool -> Maybe DeviceConfigurationProperty
emailAuthenticationMessage :: UserPool -> Maybe (Value Text)
emailAuthenticationSubject :: UserPool -> Maybe (Value Text)
emailConfiguration :: UserPool -> Maybe EmailConfigurationProperty
emailVerificationMessage :: UserPool -> Maybe (Value Text)
emailVerificationSubject :: UserPool -> Maybe (Value Text)
enabledMfas :: UserPool -> Maybe (ValueList Text)
lambdaConfig :: UserPool -> Maybe LambdaConfigProperty
mfaConfiguration :: UserPool -> Maybe (Value Text)
policies :: UserPool -> Maybe PoliciesProperty
schema :: UserPool -> Maybe [SchemaAttributeProperty]
smsAuthenticationMessage :: UserPool -> Maybe (Value Text)
smsConfiguration :: UserPool -> Maybe SmsConfigurationProperty
smsVerificationMessage :: UserPool -> Maybe (Value Text)
userAttributeUpdateSettings :: UserPool -> Maybe UserAttributeUpdateSettingsProperty
userPoolAddOns :: UserPool -> Maybe UserPoolAddOnsProperty
userPoolName :: UserPool -> Maybe (Value Text)
userPoolTags :: UserPool -> Maybe (Map Text (Value Text))
userPoolTier :: UserPool -> Maybe (Value Text)
usernameAttributes :: UserPool -> Maybe (ValueList Text)
usernameConfiguration :: UserPool -> Maybe UsernameConfigurationProperty
verificationMessageTemplate :: UserPool -> Maybe VerificationMessageTemplateProperty
webAuthnRelyingPartyID :: UserPool -> Maybe (Value Text)
webAuthnUserVerification :: UserPool -> Maybe (Value Text)
haddock_workaround_ :: ()
accountRecoverySetting :: Maybe AccountRecoverySettingProperty
adminCreateUserConfig :: Maybe AdminCreateUserConfigProperty
aliasAttributes :: Maybe (ValueList Text)
autoVerifiedAttributes :: Maybe (ValueList Text)
deletionProtection :: Maybe (Value Text)
deviceConfiguration :: Maybe DeviceConfigurationProperty
emailAuthenticationMessage :: Maybe (Value Text)
emailAuthenticationSubject :: Maybe (Value Text)
emailConfiguration :: Maybe EmailConfigurationProperty
emailVerificationMessage :: Maybe (Value Text)
emailVerificationSubject :: Maybe (Value Text)
enabledMfas :: Maybe (ValueList Text)
lambdaConfig :: Maybe LambdaConfigProperty
mfaConfiguration :: Maybe (Value Text)
policies :: Maybe PoliciesProperty
schema :: Maybe [SchemaAttributeProperty]
smsAuthenticationMessage :: Maybe (Value Text)
smsConfiguration :: Maybe SmsConfigurationProperty
smsVerificationMessage :: Maybe (Value Text)
userAttributeUpdateSettings :: Maybe UserAttributeUpdateSettingsProperty
userPoolAddOns :: Maybe UserPoolAddOnsProperty
userPoolName :: Maybe (Value Text)
userPoolTags :: Maybe (Map Text (Value Text))
userPoolTier :: Maybe (Value Text)
usernameAttributes :: Maybe (ValueList Text)
usernameConfiguration :: Maybe UsernameConfigurationProperty
verificationMessageTemplate :: Maybe VerificationMessageTemplateProperty
webAuthnRelyingPartyID :: Maybe (Value Text)
webAuthnUserVerification :: Maybe (Value Text)
..}
= UserPool {enabledMfas :: Maybe (ValueList Text)
enabledMfas = ValueList Text -> Maybe (ValueList Text)
forall a. a -> Maybe a
forall (f :: * -> *) a. Applicative f => a -> f a
Prelude.pure PropertyType "EnabledMfas" UserPool
ValueList Text
newValue, Maybe [SchemaAttributeProperty]
Maybe (Map Text (Value Text))
Maybe (ValueList Text)
Maybe (Value Text)
Maybe DeviceConfigurationProperty
Maybe EmailConfigurationProperty
Maybe AdminCreateUserConfigProperty
Maybe LambdaConfigProperty
Maybe AccountRecoverySettingProperty
Maybe PoliciesProperty
Maybe SmsConfigurationProperty
Maybe UserAttributeUpdateSettingsProperty
Maybe UserPoolAddOnsProperty
Maybe UsernameConfigurationProperty
Maybe VerificationMessageTemplateProperty
()
haddock_workaround_ :: ()
accountRecoverySetting :: Maybe AccountRecoverySettingProperty
adminCreateUserConfig :: Maybe AdminCreateUserConfigProperty
aliasAttributes :: Maybe (ValueList Text)
autoVerifiedAttributes :: Maybe (ValueList Text)
deletionProtection :: Maybe (Value Text)
deviceConfiguration :: Maybe DeviceConfigurationProperty
emailAuthenticationMessage :: Maybe (Value Text)
emailAuthenticationSubject :: Maybe (Value Text)
emailConfiguration :: Maybe EmailConfigurationProperty
emailVerificationMessage :: Maybe (Value Text)
emailVerificationSubject :: Maybe (Value Text)
lambdaConfig :: Maybe LambdaConfigProperty
mfaConfiguration :: Maybe (Value Text)
policies :: Maybe PoliciesProperty
schema :: Maybe [SchemaAttributeProperty]
smsAuthenticationMessage :: Maybe (Value Text)
smsConfiguration :: Maybe SmsConfigurationProperty
smsVerificationMessage :: Maybe (Value Text)
userAttributeUpdateSettings :: Maybe UserAttributeUpdateSettingsProperty
userPoolAddOns :: Maybe UserPoolAddOnsProperty
userPoolName :: Maybe (Value Text)
userPoolTags :: Maybe (Map Text (Value Text))
userPoolTier :: Maybe (Value Text)
usernameAttributes :: Maybe (ValueList Text)
usernameConfiguration :: Maybe UsernameConfigurationProperty
verificationMessageTemplate :: Maybe VerificationMessageTemplateProperty
webAuthnRelyingPartyID :: Maybe (Value Text)
webAuthnUserVerification :: Maybe (Value Text)
haddock_workaround_ :: ()
accountRecoverySetting :: Maybe AccountRecoverySettingProperty
adminCreateUserConfig :: Maybe AdminCreateUserConfigProperty
aliasAttributes :: Maybe (ValueList Text)
autoVerifiedAttributes :: Maybe (ValueList Text)
deletionProtection :: Maybe (Value Text)
deviceConfiguration :: Maybe DeviceConfigurationProperty
emailAuthenticationMessage :: Maybe (Value Text)
emailAuthenticationSubject :: Maybe (Value Text)
emailConfiguration :: Maybe EmailConfigurationProperty
emailVerificationMessage :: Maybe (Value Text)
emailVerificationSubject :: Maybe (Value Text)
lambdaConfig :: Maybe LambdaConfigProperty
mfaConfiguration :: Maybe (Value Text)
policies :: Maybe PoliciesProperty
schema :: Maybe [SchemaAttributeProperty]
smsAuthenticationMessage :: Maybe (Value Text)
smsConfiguration :: Maybe SmsConfigurationProperty
smsVerificationMessage :: Maybe (Value Text)
userAttributeUpdateSettings :: Maybe UserAttributeUpdateSettingsProperty
userPoolAddOns :: Maybe UserPoolAddOnsProperty
userPoolName :: Maybe (Value Text)
userPoolTags :: Maybe (Map Text (Value Text))
userPoolTier :: Maybe (Value Text)
usernameAttributes :: Maybe (ValueList Text)
usernameConfiguration :: Maybe UsernameConfigurationProperty
verificationMessageTemplate :: Maybe VerificationMessageTemplateProperty
webAuthnRelyingPartyID :: Maybe (Value Text)
webAuthnUserVerification :: Maybe (Value Text)
..}
instance Property "LambdaConfig" UserPool where
type PropertyType "LambdaConfig" UserPool = LambdaConfigProperty
set :: PropertyType "LambdaConfig" UserPool -> UserPool -> UserPool
set PropertyType "LambdaConfig" UserPool
newValue UserPool {Maybe [SchemaAttributeProperty]
Maybe (Map Text (Value Text))
Maybe (ValueList Text)
Maybe (Value Text)
Maybe DeviceConfigurationProperty
Maybe EmailConfigurationProperty
Maybe AdminCreateUserConfigProperty
Maybe LambdaConfigProperty
Maybe AccountRecoverySettingProperty
Maybe PoliciesProperty
Maybe SmsConfigurationProperty
Maybe UserAttributeUpdateSettingsProperty
Maybe UserPoolAddOnsProperty
Maybe UsernameConfigurationProperty
Maybe VerificationMessageTemplateProperty
()
haddock_workaround_ :: UserPool -> ()
accountRecoverySetting :: UserPool -> Maybe AccountRecoverySettingProperty
adminCreateUserConfig :: UserPool -> Maybe AdminCreateUserConfigProperty
aliasAttributes :: UserPool -> Maybe (ValueList Text)
autoVerifiedAttributes :: UserPool -> Maybe (ValueList Text)
deletionProtection :: UserPool -> Maybe (Value Text)
deviceConfiguration :: UserPool -> Maybe DeviceConfigurationProperty
emailAuthenticationMessage :: UserPool -> Maybe (Value Text)
emailAuthenticationSubject :: UserPool -> Maybe (Value Text)
emailConfiguration :: UserPool -> Maybe EmailConfigurationProperty
emailVerificationMessage :: UserPool -> Maybe (Value Text)
emailVerificationSubject :: UserPool -> Maybe (Value Text)
enabledMfas :: UserPool -> Maybe (ValueList Text)
lambdaConfig :: UserPool -> Maybe LambdaConfigProperty
mfaConfiguration :: UserPool -> Maybe (Value Text)
policies :: UserPool -> Maybe PoliciesProperty
schema :: UserPool -> Maybe [SchemaAttributeProperty]
smsAuthenticationMessage :: UserPool -> Maybe (Value Text)
smsConfiguration :: UserPool -> Maybe SmsConfigurationProperty
smsVerificationMessage :: UserPool -> Maybe (Value Text)
userAttributeUpdateSettings :: UserPool -> Maybe UserAttributeUpdateSettingsProperty
userPoolAddOns :: UserPool -> Maybe UserPoolAddOnsProperty
userPoolName :: UserPool -> Maybe (Value Text)
userPoolTags :: UserPool -> Maybe (Map Text (Value Text))
userPoolTier :: UserPool -> Maybe (Value Text)
usernameAttributes :: UserPool -> Maybe (ValueList Text)
usernameConfiguration :: UserPool -> Maybe UsernameConfigurationProperty
verificationMessageTemplate :: UserPool -> Maybe VerificationMessageTemplateProperty
webAuthnRelyingPartyID :: UserPool -> Maybe (Value Text)
webAuthnUserVerification :: UserPool -> Maybe (Value Text)
haddock_workaround_ :: ()
accountRecoverySetting :: Maybe AccountRecoverySettingProperty
adminCreateUserConfig :: Maybe AdminCreateUserConfigProperty
aliasAttributes :: Maybe (ValueList Text)
autoVerifiedAttributes :: Maybe (ValueList Text)
deletionProtection :: Maybe (Value Text)
deviceConfiguration :: Maybe DeviceConfigurationProperty
emailAuthenticationMessage :: Maybe (Value Text)
emailAuthenticationSubject :: Maybe (Value Text)
emailConfiguration :: Maybe EmailConfigurationProperty
emailVerificationMessage :: Maybe (Value Text)
emailVerificationSubject :: Maybe (Value Text)
enabledMfas :: Maybe (ValueList Text)
lambdaConfig :: Maybe LambdaConfigProperty
mfaConfiguration :: Maybe (Value Text)
policies :: Maybe PoliciesProperty
schema :: Maybe [SchemaAttributeProperty]
smsAuthenticationMessage :: Maybe (Value Text)
smsConfiguration :: Maybe SmsConfigurationProperty
smsVerificationMessage :: Maybe (Value Text)
userAttributeUpdateSettings :: Maybe UserAttributeUpdateSettingsProperty
userPoolAddOns :: Maybe UserPoolAddOnsProperty
userPoolName :: Maybe (Value Text)
userPoolTags :: Maybe (Map Text (Value Text))
userPoolTier :: Maybe (Value Text)
usernameAttributes :: Maybe (ValueList Text)
usernameConfiguration :: Maybe UsernameConfigurationProperty
verificationMessageTemplate :: Maybe VerificationMessageTemplateProperty
webAuthnRelyingPartyID :: Maybe (Value Text)
webAuthnUserVerification :: Maybe (Value Text)
..}
= UserPool {lambdaConfig :: Maybe LambdaConfigProperty
lambdaConfig = LambdaConfigProperty -> Maybe LambdaConfigProperty
forall a. a -> Maybe a
forall (f :: * -> *) a. Applicative f => a -> f a
Prelude.pure PropertyType "LambdaConfig" UserPool
LambdaConfigProperty
newValue, Maybe [SchemaAttributeProperty]
Maybe (Map Text (Value Text))
Maybe (ValueList Text)
Maybe (Value Text)
Maybe DeviceConfigurationProperty
Maybe EmailConfigurationProperty
Maybe AdminCreateUserConfigProperty
Maybe AccountRecoverySettingProperty
Maybe PoliciesProperty
Maybe SmsConfigurationProperty
Maybe UserAttributeUpdateSettingsProperty
Maybe UserPoolAddOnsProperty
Maybe UsernameConfigurationProperty
Maybe VerificationMessageTemplateProperty
()
haddock_workaround_ :: ()
accountRecoverySetting :: Maybe AccountRecoverySettingProperty
adminCreateUserConfig :: Maybe AdminCreateUserConfigProperty
aliasAttributes :: Maybe (ValueList Text)
autoVerifiedAttributes :: Maybe (ValueList Text)
deletionProtection :: Maybe (Value Text)
deviceConfiguration :: Maybe DeviceConfigurationProperty
emailAuthenticationMessage :: Maybe (Value Text)
emailAuthenticationSubject :: Maybe (Value Text)
emailConfiguration :: Maybe EmailConfigurationProperty
emailVerificationMessage :: Maybe (Value Text)
emailVerificationSubject :: Maybe (Value Text)
enabledMfas :: Maybe (ValueList Text)
mfaConfiguration :: Maybe (Value Text)
policies :: Maybe PoliciesProperty
schema :: Maybe [SchemaAttributeProperty]
smsAuthenticationMessage :: Maybe (Value Text)
smsConfiguration :: Maybe SmsConfigurationProperty
smsVerificationMessage :: Maybe (Value Text)
userAttributeUpdateSettings :: Maybe UserAttributeUpdateSettingsProperty
userPoolAddOns :: Maybe UserPoolAddOnsProperty
userPoolName :: Maybe (Value Text)
userPoolTags :: Maybe (Map Text (Value Text))
userPoolTier :: Maybe (Value Text)
usernameAttributes :: Maybe (ValueList Text)
usernameConfiguration :: Maybe UsernameConfigurationProperty
verificationMessageTemplate :: Maybe VerificationMessageTemplateProperty
webAuthnRelyingPartyID :: Maybe (Value Text)
webAuthnUserVerification :: Maybe (Value Text)
haddock_workaround_ :: ()
accountRecoverySetting :: Maybe AccountRecoverySettingProperty
adminCreateUserConfig :: Maybe AdminCreateUserConfigProperty
aliasAttributes :: Maybe (ValueList Text)
autoVerifiedAttributes :: Maybe (ValueList Text)
deletionProtection :: Maybe (Value Text)
deviceConfiguration :: Maybe DeviceConfigurationProperty
emailAuthenticationMessage :: Maybe (Value Text)
emailAuthenticationSubject :: Maybe (Value Text)
emailConfiguration :: Maybe EmailConfigurationProperty
emailVerificationMessage :: Maybe (Value Text)
emailVerificationSubject :: Maybe (Value Text)
enabledMfas :: Maybe (ValueList Text)
mfaConfiguration :: Maybe (Value Text)
policies :: Maybe PoliciesProperty
schema :: Maybe [SchemaAttributeProperty]
smsAuthenticationMessage :: Maybe (Value Text)
smsConfiguration :: Maybe SmsConfigurationProperty
smsVerificationMessage :: Maybe (Value Text)
userAttributeUpdateSettings :: Maybe UserAttributeUpdateSettingsProperty
userPoolAddOns :: Maybe UserPoolAddOnsProperty
userPoolName :: Maybe (Value Text)
userPoolTags :: Maybe (Map Text (Value Text))
userPoolTier :: Maybe (Value Text)
usernameAttributes :: Maybe (ValueList Text)
usernameConfiguration :: Maybe UsernameConfigurationProperty
verificationMessageTemplate :: Maybe VerificationMessageTemplateProperty
webAuthnRelyingPartyID :: Maybe (Value Text)
webAuthnUserVerification :: Maybe (Value Text)
..}
instance Property "MfaConfiguration" UserPool where
type PropertyType "MfaConfiguration" UserPool = Value Prelude.Text
set :: PropertyType "MfaConfiguration" UserPool -> UserPool -> UserPool
set PropertyType "MfaConfiguration" UserPool
newValue UserPool {Maybe [SchemaAttributeProperty]
Maybe (Map Text (Value Text))
Maybe (ValueList Text)
Maybe (Value Text)
Maybe DeviceConfigurationProperty
Maybe EmailConfigurationProperty
Maybe AdminCreateUserConfigProperty
Maybe LambdaConfigProperty
Maybe AccountRecoverySettingProperty
Maybe PoliciesProperty
Maybe SmsConfigurationProperty
Maybe UserAttributeUpdateSettingsProperty
Maybe UserPoolAddOnsProperty
Maybe UsernameConfigurationProperty
Maybe VerificationMessageTemplateProperty
()
haddock_workaround_ :: UserPool -> ()
accountRecoverySetting :: UserPool -> Maybe AccountRecoverySettingProperty
adminCreateUserConfig :: UserPool -> Maybe AdminCreateUserConfigProperty
aliasAttributes :: UserPool -> Maybe (ValueList Text)
autoVerifiedAttributes :: UserPool -> Maybe (ValueList Text)
deletionProtection :: UserPool -> Maybe (Value Text)
deviceConfiguration :: UserPool -> Maybe DeviceConfigurationProperty
emailAuthenticationMessage :: UserPool -> Maybe (Value Text)
emailAuthenticationSubject :: UserPool -> Maybe (Value Text)
emailConfiguration :: UserPool -> Maybe EmailConfigurationProperty
emailVerificationMessage :: UserPool -> Maybe (Value Text)
emailVerificationSubject :: UserPool -> Maybe (Value Text)
enabledMfas :: UserPool -> Maybe (ValueList Text)
lambdaConfig :: UserPool -> Maybe LambdaConfigProperty
mfaConfiguration :: UserPool -> Maybe (Value Text)
policies :: UserPool -> Maybe PoliciesProperty
schema :: UserPool -> Maybe [SchemaAttributeProperty]
smsAuthenticationMessage :: UserPool -> Maybe (Value Text)
smsConfiguration :: UserPool -> Maybe SmsConfigurationProperty
smsVerificationMessage :: UserPool -> Maybe (Value Text)
userAttributeUpdateSettings :: UserPool -> Maybe UserAttributeUpdateSettingsProperty
userPoolAddOns :: UserPool -> Maybe UserPoolAddOnsProperty
userPoolName :: UserPool -> Maybe (Value Text)
userPoolTags :: UserPool -> Maybe (Map Text (Value Text))
userPoolTier :: UserPool -> Maybe (Value Text)
usernameAttributes :: UserPool -> Maybe (ValueList Text)
usernameConfiguration :: UserPool -> Maybe UsernameConfigurationProperty
verificationMessageTemplate :: UserPool -> Maybe VerificationMessageTemplateProperty
webAuthnRelyingPartyID :: UserPool -> Maybe (Value Text)
webAuthnUserVerification :: UserPool -> Maybe (Value Text)
haddock_workaround_ :: ()
accountRecoverySetting :: Maybe AccountRecoverySettingProperty
adminCreateUserConfig :: Maybe AdminCreateUserConfigProperty
aliasAttributes :: Maybe (ValueList Text)
autoVerifiedAttributes :: Maybe (ValueList Text)
deletionProtection :: Maybe (Value Text)
deviceConfiguration :: Maybe DeviceConfigurationProperty
emailAuthenticationMessage :: Maybe (Value Text)
emailAuthenticationSubject :: Maybe (Value Text)
emailConfiguration :: Maybe EmailConfigurationProperty
emailVerificationMessage :: Maybe (Value Text)
emailVerificationSubject :: Maybe (Value Text)
enabledMfas :: Maybe (ValueList Text)
lambdaConfig :: Maybe LambdaConfigProperty
mfaConfiguration :: Maybe (Value Text)
policies :: Maybe PoliciesProperty
schema :: Maybe [SchemaAttributeProperty]
smsAuthenticationMessage :: Maybe (Value Text)
smsConfiguration :: Maybe SmsConfigurationProperty
smsVerificationMessage :: Maybe (Value Text)
userAttributeUpdateSettings :: Maybe UserAttributeUpdateSettingsProperty
userPoolAddOns :: Maybe UserPoolAddOnsProperty
userPoolName :: Maybe (Value Text)
userPoolTags :: Maybe (Map Text (Value Text))
userPoolTier :: Maybe (Value Text)
usernameAttributes :: Maybe (ValueList Text)
usernameConfiguration :: Maybe UsernameConfigurationProperty
verificationMessageTemplate :: Maybe VerificationMessageTemplateProperty
webAuthnRelyingPartyID :: Maybe (Value Text)
webAuthnUserVerification :: Maybe (Value Text)
..}
= UserPool {mfaConfiguration :: Maybe (Value Text)
mfaConfiguration = Value Text -> Maybe (Value Text)
forall a. a -> Maybe a
forall (f :: * -> *) a. Applicative f => a -> f a
Prelude.pure PropertyType "MfaConfiguration" UserPool
Value Text
newValue, Maybe [SchemaAttributeProperty]
Maybe (Map Text (Value Text))
Maybe (ValueList Text)
Maybe (Value Text)
Maybe DeviceConfigurationProperty
Maybe EmailConfigurationProperty
Maybe AdminCreateUserConfigProperty
Maybe LambdaConfigProperty
Maybe AccountRecoverySettingProperty
Maybe PoliciesProperty
Maybe SmsConfigurationProperty
Maybe UserAttributeUpdateSettingsProperty
Maybe UserPoolAddOnsProperty
Maybe UsernameConfigurationProperty
Maybe VerificationMessageTemplateProperty
()
haddock_workaround_ :: ()
accountRecoverySetting :: Maybe AccountRecoverySettingProperty
adminCreateUserConfig :: Maybe AdminCreateUserConfigProperty
aliasAttributes :: Maybe (ValueList Text)
autoVerifiedAttributes :: Maybe (ValueList Text)
deletionProtection :: Maybe (Value Text)
deviceConfiguration :: Maybe DeviceConfigurationProperty
emailAuthenticationMessage :: Maybe (Value Text)
emailAuthenticationSubject :: Maybe (Value Text)
emailConfiguration :: Maybe EmailConfigurationProperty
emailVerificationMessage :: Maybe (Value Text)
emailVerificationSubject :: Maybe (Value Text)
enabledMfas :: Maybe (ValueList Text)
lambdaConfig :: Maybe LambdaConfigProperty
policies :: Maybe PoliciesProperty
schema :: Maybe [SchemaAttributeProperty]
smsAuthenticationMessage :: Maybe (Value Text)
smsConfiguration :: Maybe SmsConfigurationProperty
smsVerificationMessage :: Maybe (Value Text)
userAttributeUpdateSettings :: Maybe UserAttributeUpdateSettingsProperty
userPoolAddOns :: Maybe UserPoolAddOnsProperty
userPoolName :: Maybe (Value Text)
userPoolTags :: Maybe (Map Text (Value Text))
userPoolTier :: Maybe (Value Text)
usernameAttributes :: Maybe (ValueList Text)
usernameConfiguration :: Maybe UsernameConfigurationProperty
verificationMessageTemplate :: Maybe VerificationMessageTemplateProperty
webAuthnRelyingPartyID :: Maybe (Value Text)
webAuthnUserVerification :: Maybe (Value Text)
haddock_workaround_ :: ()
accountRecoverySetting :: Maybe AccountRecoverySettingProperty
adminCreateUserConfig :: Maybe AdminCreateUserConfigProperty
aliasAttributes :: Maybe (ValueList Text)
autoVerifiedAttributes :: Maybe (ValueList Text)
deletionProtection :: Maybe (Value Text)
deviceConfiguration :: Maybe DeviceConfigurationProperty
emailAuthenticationMessage :: Maybe (Value Text)
emailAuthenticationSubject :: Maybe (Value Text)
emailConfiguration :: Maybe EmailConfigurationProperty
emailVerificationMessage :: Maybe (Value Text)
emailVerificationSubject :: Maybe (Value Text)
enabledMfas :: Maybe (ValueList Text)
lambdaConfig :: Maybe LambdaConfigProperty
policies :: Maybe PoliciesProperty
schema :: Maybe [SchemaAttributeProperty]
smsAuthenticationMessage :: Maybe (Value Text)
smsConfiguration :: Maybe SmsConfigurationProperty
smsVerificationMessage :: Maybe (Value Text)
userAttributeUpdateSettings :: Maybe UserAttributeUpdateSettingsProperty
userPoolAddOns :: Maybe UserPoolAddOnsProperty
userPoolName :: Maybe (Value Text)
userPoolTags :: Maybe (Map Text (Value Text))
userPoolTier :: Maybe (Value Text)
usernameAttributes :: Maybe (ValueList Text)
usernameConfiguration :: Maybe UsernameConfigurationProperty
verificationMessageTemplate :: Maybe VerificationMessageTemplateProperty
webAuthnRelyingPartyID :: Maybe (Value Text)
webAuthnUserVerification :: Maybe (Value Text)
..}
instance Property "Policies" UserPool where
type PropertyType "Policies" UserPool = PoliciesProperty
set :: PropertyType "Policies" UserPool -> UserPool -> UserPool
set PropertyType "Policies" UserPool
newValue UserPool {Maybe [SchemaAttributeProperty]
Maybe (Map Text (Value Text))
Maybe (ValueList Text)
Maybe (Value Text)
Maybe DeviceConfigurationProperty
Maybe EmailConfigurationProperty
Maybe AdminCreateUserConfigProperty
Maybe LambdaConfigProperty
Maybe AccountRecoverySettingProperty
Maybe PoliciesProperty
Maybe SmsConfigurationProperty
Maybe UserAttributeUpdateSettingsProperty
Maybe UserPoolAddOnsProperty
Maybe UsernameConfigurationProperty
Maybe VerificationMessageTemplateProperty
()
haddock_workaround_ :: UserPool -> ()
accountRecoverySetting :: UserPool -> Maybe AccountRecoverySettingProperty
adminCreateUserConfig :: UserPool -> Maybe AdminCreateUserConfigProperty
aliasAttributes :: UserPool -> Maybe (ValueList Text)
autoVerifiedAttributes :: UserPool -> Maybe (ValueList Text)
deletionProtection :: UserPool -> Maybe (Value Text)
deviceConfiguration :: UserPool -> Maybe DeviceConfigurationProperty
emailAuthenticationMessage :: UserPool -> Maybe (Value Text)
emailAuthenticationSubject :: UserPool -> Maybe (Value Text)
emailConfiguration :: UserPool -> Maybe EmailConfigurationProperty
emailVerificationMessage :: UserPool -> Maybe (Value Text)
emailVerificationSubject :: UserPool -> Maybe (Value Text)
enabledMfas :: UserPool -> Maybe (ValueList Text)
lambdaConfig :: UserPool -> Maybe LambdaConfigProperty
mfaConfiguration :: UserPool -> Maybe (Value Text)
policies :: UserPool -> Maybe PoliciesProperty
schema :: UserPool -> Maybe [SchemaAttributeProperty]
smsAuthenticationMessage :: UserPool -> Maybe (Value Text)
smsConfiguration :: UserPool -> Maybe SmsConfigurationProperty
smsVerificationMessage :: UserPool -> Maybe (Value Text)
userAttributeUpdateSettings :: UserPool -> Maybe UserAttributeUpdateSettingsProperty
userPoolAddOns :: UserPool -> Maybe UserPoolAddOnsProperty
userPoolName :: UserPool -> Maybe (Value Text)
userPoolTags :: UserPool -> Maybe (Map Text (Value Text))
userPoolTier :: UserPool -> Maybe (Value Text)
usernameAttributes :: UserPool -> Maybe (ValueList Text)
usernameConfiguration :: UserPool -> Maybe UsernameConfigurationProperty
verificationMessageTemplate :: UserPool -> Maybe VerificationMessageTemplateProperty
webAuthnRelyingPartyID :: UserPool -> Maybe (Value Text)
webAuthnUserVerification :: UserPool -> Maybe (Value Text)
haddock_workaround_ :: ()
accountRecoverySetting :: Maybe AccountRecoverySettingProperty
adminCreateUserConfig :: Maybe AdminCreateUserConfigProperty
aliasAttributes :: Maybe (ValueList Text)
autoVerifiedAttributes :: Maybe (ValueList Text)
deletionProtection :: Maybe (Value Text)
deviceConfiguration :: Maybe DeviceConfigurationProperty
emailAuthenticationMessage :: Maybe (Value Text)
emailAuthenticationSubject :: Maybe (Value Text)
emailConfiguration :: Maybe EmailConfigurationProperty
emailVerificationMessage :: Maybe (Value Text)
emailVerificationSubject :: Maybe (Value Text)
enabledMfas :: Maybe (ValueList Text)
lambdaConfig :: Maybe LambdaConfigProperty
mfaConfiguration :: Maybe (Value Text)
policies :: Maybe PoliciesProperty
schema :: Maybe [SchemaAttributeProperty]
smsAuthenticationMessage :: Maybe (Value Text)
smsConfiguration :: Maybe SmsConfigurationProperty
smsVerificationMessage :: Maybe (Value Text)
userAttributeUpdateSettings :: Maybe UserAttributeUpdateSettingsProperty
userPoolAddOns :: Maybe UserPoolAddOnsProperty
userPoolName :: Maybe (Value Text)
userPoolTags :: Maybe (Map Text (Value Text))
userPoolTier :: Maybe (Value Text)
usernameAttributes :: Maybe (ValueList Text)
usernameConfiguration :: Maybe UsernameConfigurationProperty
verificationMessageTemplate :: Maybe VerificationMessageTemplateProperty
webAuthnRelyingPartyID :: Maybe (Value Text)
webAuthnUserVerification :: Maybe (Value Text)
..}
= UserPool {policies :: Maybe PoliciesProperty
policies = PoliciesProperty -> Maybe PoliciesProperty
forall a. a -> Maybe a
forall (f :: * -> *) a. Applicative f => a -> f a
Prelude.pure PropertyType "Policies" UserPool
PoliciesProperty
newValue, Maybe [SchemaAttributeProperty]
Maybe (Map Text (Value Text))
Maybe (ValueList Text)
Maybe (Value Text)
Maybe DeviceConfigurationProperty
Maybe EmailConfigurationProperty
Maybe AdminCreateUserConfigProperty
Maybe LambdaConfigProperty
Maybe AccountRecoverySettingProperty
Maybe SmsConfigurationProperty
Maybe UserAttributeUpdateSettingsProperty
Maybe UserPoolAddOnsProperty
Maybe UsernameConfigurationProperty
Maybe VerificationMessageTemplateProperty
()
haddock_workaround_ :: ()
accountRecoverySetting :: Maybe AccountRecoverySettingProperty
adminCreateUserConfig :: Maybe AdminCreateUserConfigProperty
aliasAttributes :: Maybe (ValueList Text)
autoVerifiedAttributes :: Maybe (ValueList Text)
deletionProtection :: Maybe (Value Text)
deviceConfiguration :: Maybe DeviceConfigurationProperty
emailAuthenticationMessage :: Maybe (Value Text)
emailAuthenticationSubject :: Maybe (Value Text)
emailConfiguration :: Maybe EmailConfigurationProperty
emailVerificationMessage :: Maybe (Value Text)
emailVerificationSubject :: Maybe (Value Text)
enabledMfas :: Maybe (ValueList Text)
lambdaConfig :: Maybe LambdaConfigProperty
mfaConfiguration :: Maybe (Value Text)
schema :: Maybe [SchemaAttributeProperty]
smsAuthenticationMessage :: Maybe (Value Text)
smsConfiguration :: Maybe SmsConfigurationProperty
smsVerificationMessage :: Maybe (Value Text)
userAttributeUpdateSettings :: Maybe UserAttributeUpdateSettingsProperty
userPoolAddOns :: Maybe UserPoolAddOnsProperty
userPoolName :: Maybe (Value Text)
userPoolTags :: Maybe (Map Text (Value Text))
userPoolTier :: Maybe (Value Text)
usernameAttributes :: Maybe (ValueList Text)
usernameConfiguration :: Maybe UsernameConfigurationProperty
verificationMessageTemplate :: Maybe VerificationMessageTemplateProperty
webAuthnRelyingPartyID :: Maybe (Value Text)
webAuthnUserVerification :: Maybe (Value Text)
haddock_workaround_ :: ()
accountRecoverySetting :: Maybe AccountRecoverySettingProperty
adminCreateUserConfig :: Maybe AdminCreateUserConfigProperty
aliasAttributes :: Maybe (ValueList Text)
autoVerifiedAttributes :: Maybe (ValueList Text)
deletionProtection :: Maybe (Value Text)
deviceConfiguration :: Maybe DeviceConfigurationProperty
emailAuthenticationMessage :: Maybe (Value Text)
emailAuthenticationSubject :: Maybe (Value Text)
emailConfiguration :: Maybe EmailConfigurationProperty
emailVerificationMessage :: Maybe (Value Text)
emailVerificationSubject :: Maybe (Value Text)
enabledMfas :: Maybe (ValueList Text)
lambdaConfig :: Maybe LambdaConfigProperty
mfaConfiguration :: Maybe (Value Text)
schema :: Maybe [SchemaAttributeProperty]
smsAuthenticationMessage :: Maybe (Value Text)
smsConfiguration :: Maybe SmsConfigurationProperty
smsVerificationMessage :: Maybe (Value Text)
userAttributeUpdateSettings :: Maybe UserAttributeUpdateSettingsProperty
userPoolAddOns :: Maybe UserPoolAddOnsProperty
userPoolName :: Maybe (Value Text)
userPoolTags :: Maybe (Map Text (Value Text))
userPoolTier :: Maybe (Value Text)
usernameAttributes :: Maybe (ValueList Text)
usernameConfiguration :: Maybe UsernameConfigurationProperty
verificationMessageTemplate :: Maybe VerificationMessageTemplateProperty
webAuthnRelyingPartyID :: Maybe (Value Text)
webAuthnUserVerification :: Maybe (Value Text)
..}
instance Property "Schema" UserPool where
type PropertyType "Schema" UserPool = [SchemaAttributeProperty]
set :: PropertyType "Schema" UserPool -> UserPool -> UserPool
set PropertyType "Schema" UserPool
newValue UserPool {Maybe [SchemaAttributeProperty]
Maybe (Map Text (Value Text))
Maybe (ValueList Text)
Maybe (Value Text)
Maybe DeviceConfigurationProperty
Maybe EmailConfigurationProperty
Maybe AdminCreateUserConfigProperty
Maybe LambdaConfigProperty
Maybe AccountRecoverySettingProperty
Maybe PoliciesProperty
Maybe SmsConfigurationProperty
Maybe UserAttributeUpdateSettingsProperty
Maybe UserPoolAddOnsProperty
Maybe UsernameConfigurationProperty
Maybe VerificationMessageTemplateProperty
()
haddock_workaround_ :: UserPool -> ()
accountRecoverySetting :: UserPool -> Maybe AccountRecoverySettingProperty
adminCreateUserConfig :: UserPool -> Maybe AdminCreateUserConfigProperty
aliasAttributes :: UserPool -> Maybe (ValueList Text)
autoVerifiedAttributes :: UserPool -> Maybe (ValueList Text)
deletionProtection :: UserPool -> Maybe (Value Text)
deviceConfiguration :: UserPool -> Maybe DeviceConfigurationProperty
emailAuthenticationMessage :: UserPool -> Maybe (Value Text)
emailAuthenticationSubject :: UserPool -> Maybe (Value Text)
emailConfiguration :: UserPool -> Maybe EmailConfigurationProperty
emailVerificationMessage :: UserPool -> Maybe (Value Text)
emailVerificationSubject :: UserPool -> Maybe (Value Text)
enabledMfas :: UserPool -> Maybe (ValueList Text)
lambdaConfig :: UserPool -> Maybe LambdaConfigProperty
mfaConfiguration :: UserPool -> Maybe (Value Text)
policies :: UserPool -> Maybe PoliciesProperty
schema :: UserPool -> Maybe [SchemaAttributeProperty]
smsAuthenticationMessage :: UserPool -> Maybe (Value Text)
smsConfiguration :: UserPool -> Maybe SmsConfigurationProperty
smsVerificationMessage :: UserPool -> Maybe (Value Text)
userAttributeUpdateSettings :: UserPool -> Maybe UserAttributeUpdateSettingsProperty
userPoolAddOns :: UserPool -> Maybe UserPoolAddOnsProperty
userPoolName :: UserPool -> Maybe (Value Text)
userPoolTags :: UserPool -> Maybe (Map Text (Value Text))
userPoolTier :: UserPool -> Maybe (Value Text)
usernameAttributes :: UserPool -> Maybe (ValueList Text)
usernameConfiguration :: UserPool -> Maybe UsernameConfigurationProperty
verificationMessageTemplate :: UserPool -> Maybe VerificationMessageTemplateProperty
webAuthnRelyingPartyID :: UserPool -> Maybe (Value Text)
webAuthnUserVerification :: UserPool -> Maybe (Value Text)
haddock_workaround_ :: ()
accountRecoverySetting :: Maybe AccountRecoverySettingProperty
adminCreateUserConfig :: Maybe AdminCreateUserConfigProperty
aliasAttributes :: Maybe (ValueList Text)
autoVerifiedAttributes :: Maybe (ValueList Text)
deletionProtection :: Maybe (Value Text)
deviceConfiguration :: Maybe DeviceConfigurationProperty
emailAuthenticationMessage :: Maybe (Value Text)
emailAuthenticationSubject :: Maybe (Value Text)
emailConfiguration :: Maybe EmailConfigurationProperty
emailVerificationMessage :: Maybe (Value Text)
emailVerificationSubject :: Maybe (Value Text)
enabledMfas :: Maybe (ValueList Text)
lambdaConfig :: Maybe LambdaConfigProperty
mfaConfiguration :: Maybe (Value Text)
policies :: Maybe PoliciesProperty
schema :: Maybe [SchemaAttributeProperty]
smsAuthenticationMessage :: Maybe (Value Text)
smsConfiguration :: Maybe SmsConfigurationProperty
smsVerificationMessage :: Maybe (Value Text)
userAttributeUpdateSettings :: Maybe UserAttributeUpdateSettingsProperty
userPoolAddOns :: Maybe UserPoolAddOnsProperty
userPoolName :: Maybe (Value Text)
userPoolTags :: Maybe (Map Text (Value Text))
userPoolTier :: Maybe (Value Text)
usernameAttributes :: Maybe (ValueList Text)
usernameConfiguration :: Maybe UsernameConfigurationProperty
verificationMessageTemplate :: Maybe VerificationMessageTemplateProperty
webAuthnRelyingPartyID :: Maybe (Value Text)
webAuthnUserVerification :: Maybe (Value Text)
..}
= UserPool {schema :: Maybe [SchemaAttributeProperty]
schema = [SchemaAttributeProperty] -> Maybe [SchemaAttributeProperty]
forall a. a -> Maybe a
forall (f :: * -> *) a. Applicative f => a -> f a
Prelude.pure [SchemaAttributeProperty]
PropertyType "Schema" UserPool
newValue, Maybe (Map Text (Value Text))
Maybe (ValueList Text)
Maybe (Value Text)
Maybe DeviceConfigurationProperty
Maybe EmailConfigurationProperty
Maybe AdminCreateUserConfigProperty
Maybe LambdaConfigProperty
Maybe AccountRecoverySettingProperty
Maybe PoliciesProperty
Maybe SmsConfigurationProperty
Maybe UserAttributeUpdateSettingsProperty
Maybe UserPoolAddOnsProperty
Maybe UsernameConfigurationProperty
Maybe VerificationMessageTemplateProperty
()
haddock_workaround_ :: ()
accountRecoverySetting :: Maybe AccountRecoverySettingProperty
adminCreateUserConfig :: Maybe AdminCreateUserConfigProperty
aliasAttributes :: Maybe (ValueList Text)
autoVerifiedAttributes :: Maybe (ValueList Text)
deletionProtection :: Maybe (Value Text)
deviceConfiguration :: Maybe DeviceConfigurationProperty
emailAuthenticationMessage :: Maybe (Value Text)
emailAuthenticationSubject :: Maybe (Value Text)
emailConfiguration :: Maybe EmailConfigurationProperty
emailVerificationMessage :: Maybe (Value Text)
emailVerificationSubject :: Maybe (Value Text)
enabledMfas :: Maybe (ValueList Text)
lambdaConfig :: Maybe LambdaConfigProperty
mfaConfiguration :: Maybe (Value Text)
policies :: Maybe PoliciesProperty
smsAuthenticationMessage :: Maybe (Value Text)
smsConfiguration :: Maybe SmsConfigurationProperty
smsVerificationMessage :: Maybe (Value Text)
userAttributeUpdateSettings :: Maybe UserAttributeUpdateSettingsProperty
userPoolAddOns :: Maybe UserPoolAddOnsProperty
userPoolName :: Maybe (Value Text)
userPoolTags :: Maybe (Map Text (Value Text))
userPoolTier :: Maybe (Value Text)
usernameAttributes :: Maybe (ValueList Text)
usernameConfiguration :: Maybe UsernameConfigurationProperty
verificationMessageTemplate :: Maybe VerificationMessageTemplateProperty
webAuthnRelyingPartyID :: Maybe (Value Text)
webAuthnUserVerification :: Maybe (Value Text)
haddock_workaround_ :: ()
accountRecoverySetting :: Maybe AccountRecoverySettingProperty
adminCreateUserConfig :: Maybe AdminCreateUserConfigProperty
aliasAttributes :: Maybe (ValueList Text)
autoVerifiedAttributes :: Maybe (ValueList Text)
deletionProtection :: Maybe (Value Text)
deviceConfiguration :: Maybe DeviceConfigurationProperty
emailAuthenticationMessage :: Maybe (Value Text)
emailAuthenticationSubject :: Maybe (Value Text)
emailConfiguration :: Maybe EmailConfigurationProperty
emailVerificationMessage :: Maybe (Value Text)
emailVerificationSubject :: Maybe (Value Text)
enabledMfas :: Maybe (ValueList Text)
lambdaConfig :: Maybe LambdaConfigProperty
mfaConfiguration :: Maybe (Value Text)
policies :: Maybe PoliciesProperty
smsAuthenticationMessage :: Maybe (Value Text)
smsConfiguration :: Maybe SmsConfigurationProperty
smsVerificationMessage :: Maybe (Value Text)
userAttributeUpdateSettings :: Maybe UserAttributeUpdateSettingsProperty
userPoolAddOns :: Maybe UserPoolAddOnsProperty
userPoolName :: Maybe (Value Text)
userPoolTags :: Maybe (Map Text (Value Text))
userPoolTier :: Maybe (Value Text)
usernameAttributes :: Maybe (ValueList Text)
usernameConfiguration :: Maybe UsernameConfigurationProperty
verificationMessageTemplate :: Maybe VerificationMessageTemplateProperty
webAuthnRelyingPartyID :: Maybe (Value Text)
webAuthnUserVerification :: Maybe (Value Text)
..}
instance Property "SmsAuthenticationMessage" UserPool where
type PropertyType "SmsAuthenticationMessage" UserPool = Value Prelude.Text
set :: PropertyType "SmsAuthenticationMessage" UserPool
-> UserPool -> UserPool
set PropertyType "SmsAuthenticationMessage" UserPool
newValue UserPool {Maybe [SchemaAttributeProperty]
Maybe (Map Text (Value Text))
Maybe (ValueList Text)
Maybe (Value Text)
Maybe DeviceConfigurationProperty
Maybe EmailConfigurationProperty
Maybe AdminCreateUserConfigProperty
Maybe LambdaConfigProperty
Maybe AccountRecoverySettingProperty
Maybe PoliciesProperty
Maybe SmsConfigurationProperty
Maybe UserAttributeUpdateSettingsProperty
Maybe UserPoolAddOnsProperty
Maybe UsernameConfigurationProperty
Maybe VerificationMessageTemplateProperty
()
haddock_workaround_ :: UserPool -> ()
accountRecoverySetting :: UserPool -> Maybe AccountRecoverySettingProperty
adminCreateUserConfig :: UserPool -> Maybe AdminCreateUserConfigProperty
aliasAttributes :: UserPool -> Maybe (ValueList Text)
autoVerifiedAttributes :: UserPool -> Maybe (ValueList Text)
deletionProtection :: UserPool -> Maybe (Value Text)
deviceConfiguration :: UserPool -> Maybe DeviceConfigurationProperty
emailAuthenticationMessage :: UserPool -> Maybe (Value Text)
emailAuthenticationSubject :: UserPool -> Maybe (Value Text)
emailConfiguration :: UserPool -> Maybe EmailConfigurationProperty
emailVerificationMessage :: UserPool -> Maybe (Value Text)
emailVerificationSubject :: UserPool -> Maybe (Value Text)
enabledMfas :: UserPool -> Maybe (ValueList Text)
lambdaConfig :: UserPool -> Maybe LambdaConfigProperty
mfaConfiguration :: UserPool -> Maybe (Value Text)
policies :: UserPool -> Maybe PoliciesProperty
schema :: UserPool -> Maybe [SchemaAttributeProperty]
smsAuthenticationMessage :: UserPool -> Maybe (Value Text)
smsConfiguration :: UserPool -> Maybe SmsConfigurationProperty
smsVerificationMessage :: UserPool -> Maybe (Value Text)
userAttributeUpdateSettings :: UserPool -> Maybe UserAttributeUpdateSettingsProperty
userPoolAddOns :: UserPool -> Maybe UserPoolAddOnsProperty
userPoolName :: UserPool -> Maybe (Value Text)
userPoolTags :: UserPool -> Maybe (Map Text (Value Text))
userPoolTier :: UserPool -> Maybe (Value Text)
usernameAttributes :: UserPool -> Maybe (ValueList Text)
usernameConfiguration :: UserPool -> Maybe UsernameConfigurationProperty
verificationMessageTemplate :: UserPool -> Maybe VerificationMessageTemplateProperty
webAuthnRelyingPartyID :: UserPool -> Maybe (Value Text)
webAuthnUserVerification :: UserPool -> Maybe (Value Text)
haddock_workaround_ :: ()
accountRecoverySetting :: Maybe AccountRecoverySettingProperty
adminCreateUserConfig :: Maybe AdminCreateUserConfigProperty
aliasAttributes :: Maybe (ValueList Text)
autoVerifiedAttributes :: Maybe (ValueList Text)
deletionProtection :: Maybe (Value Text)
deviceConfiguration :: Maybe DeviceConfigurationProperty
emailAuthenticationMessage :: Maybe (Value Text)
emailAuthenticationSubject :: Maybe (Value Text)
emailConfiguration :: Maybe EmailConfigurationProperty
emailVerificationMessage :: Maybe (Value Text)
emailVerificationSubject :: Maybe (Value Text)
enabledMfas :: Maybe (ValueList Text)
lambdaConfig :: Maybe LambdaConfigProperty
mfaConfiguration :: Maybe (Value Text)
policies :: Maybe PoliciesProperty
schema :: Maybe [SchemaAttributeProperty]
smsAuthenticationMessage :: Maybe (Value Text)
smsConfiguration :: Maybe SmsConfigurationProperty
smsVerificationMessage :: Maybe (Value Text)
userAttributeUpdateSettings :: Maybe UserAttributeUpdateSettingsProperty
userPoolAddOns :: Maybe UserPoolAddOnsProperty
userPoolName :: Maybe (Value Text)
userPoolTags :: Maybe (Map Text (Value Text))
userPoolTier :: Maybe (Value Text)
usernameAttributes :: Maybe (ValueList Text)
usernameConfiguration :: Maybe UsernameConfigurationProperty
verificationMessageTemplate :: Maybe VerificationMessageTemplateProperty
webAuthnRelyingPartyID :: Maybe (Value Text)
webAuthnUserVerification :: Maybe (Value Text)
..}
= UserPool {smsAuthenticationMessage :: Maybe (Value Text)
smsAuthenticationMessage = Value Text -> Maybe (Value Text)
forall a. a -> Maybe a
forall (f :: * -> *) a. Applicative f => a -> f a
Prelude.pure PropertyType "SmsAuthenticationMessage" UserPool
Value Text
newValue, Maybe [SchemaAttributeProperty]
Maybe (Map Text (Value Text))
Maybe (ValueList Text)
Maybe (Value Text)
Maybe DeviceConfigurationProperty
Maybe EmailConfigurationProperty
Maybe AdminCreateUserConfigProperty
Maybe LambdaConfigProperty
Maybe AccountRecoverySettingProperty
Maybe PoliciesProperty
Maybe SmsConfigurationProperty
Maybe UserAttributeUpdateSettingsProperty
Maybe UserPoolAddOnsProperty
Maybe UsernameConfigurationProperty
Maybe VerificationMessageTemplateProperty
()
haddock_workaround_ :: ()
accountRecoverySetting :: Maybe AccountRecoverySettingProperty
adminCreateUserConfig :: Maybe AdminCreateUserConfigProperty
aliasAttributes :: Maybe (ValueList Text)
autoVerifiedAttributes :: Maybe (ValueList Text)
deletionProtection :: Maybe (Value Text)
deviceConfiguration :: Maybe DeviceConfigurationProperty
emailAuthenticationMessage :: Maybe (Value Text)
emailAuthenticationSubject :: Maybe (Value Text)
emailConfiguration :: Maybe EmailConfigurationProperty
emailVerificationMessage :: Maybe (Value Text)
emailVerificationSubject :: Maybe (Value Text)
enabledMfas :: Maybe (ValueList Text)
lambdaConfig :: Maybe LambdaConfigProperty
mfaConfiguration :: Maybe (Value Text)
policies :: Maybe PoliciesProperty
schema :: Maybe [SchemaAttributeProperty]
smsConfiguration :: Maybe SmsConfigurationProperty
smsVerificationMessage :: Maybe (Value Text)
userAttributeUpdateSettings :: Maybe UserAttributeUpdateSettingsProperty
userPoolAddOns :: Maybe UserPoolAddOnsProperty
userPoolName :: Maybe (Value Text)
userPoolTags :: Maybe (Map Text (Value Text))
userPoolTier :: Maybe (Value Text)
usernameAttributes :: Maybe (ValueList Text)
usernameConfiguration :: Maybe UsernameConfigurationProperty
verificationMessageTemplate :: Maybe VerificationMessageTemplateProperty
webAuthnRelyingPartyID :: Maybe (Value Text)
webAuthnUserVerification :: Maybe (Value Text)
haddock_workaround_ :: ()
accountRecoverySetting :: Maybe AccountRecoverySettingProperty
adminCreateUserConfig :: Maybe AdminCreateUserConfigProperty
aliasAttributes :: Maybe (ValueList Text)
autoVerifiedAttributes :: Maybe (ValueList Text)
deletionProtection :: Maybe (Value Text)
deviceConfiguration :: Maybe DeviceConfigurationProperty
emailAuthenticationMessage :: Maybe (Value Text)
emailAuthenticationSubject :: Maybe (Value Text)
emailConfiguration :: Maybe EmailConfigurationProperty
emailVerificationMessage :: Maybe (Value Text)
emailVerificationSubject :: Maybe (Value Text)
enabledMfas :: Maybe (ValueList Text)
lambdaConfig :: Maybe LambdaConfigProperty
mfaConfiguration :: Maybe (Value Text)
policies :: Maybe PoliciesProperty
schema :: Maybe [SchemaAttributeProperty]
smsConfiguration :: Maybe SmsConfigurationProperty
smsVerificationMessage :: Maybe (Value Text)
userAttributeUpdateSettings :: Maybe UserAttributeUpdateSettingsProperty
userPoolAddOns :: Maybe UserPoolAddOnsProperty
userPoolName :: Maybe (Value Text)
userPoolTags :: Maybe (Map Text (Value Text))
userPoolTier :: Maybe (Value Text)
usernameAttributes :: Maybe (ValueList Text)
usernameConfiguration :: Maybe UsernameConfigurationProperty
verificationMessageTemplate :: Maybe VerificationMessageTemplateProperty
webAuthnRelyingPartyID :: Maybe (Value Text)
webAuthnUserVerification :: Maybe (Value Text)
..}
instance Property "SmsConfiguration" UserPool where
type PropertyType "SmsConfiguration" UserPool = SmsConfigurationProperty
set :: PropertyType "SmsConfiguration" UserPool -> UserPool -> UserPool
set PropertyType "SmsConfiguration" UserPool
newValue UserPool {Maybe [SchemaAttributeProperty]
Maybe (Map Text (Value Text))
Maybe (ValueList Text)
Maybe (Value Text)
Maybe DeviceConfigurationProperty
Maybe EmailConfigurationProperty
Maybe AdminCreateUserConfigProperty
Maybe LambdaConfigProperty
Maybe AccountRecoverySettingProperty
Maybe PoliciesProperty
Maybe SmsConfigurationProperty
Maybe UserAttributeUpdateSettingsProperty
Maybe UserPoolAddOnsProperty
Maybe UsernameConfigurationProperty
Maybe VerificationMessageTemplateProperty
()
haddock_workaround_ :: UserPool -> ()
accountRecoverySetting :: UserPool -> Maybe AccountRecoverySettingProperty
adminCreateUserConfig :: UserPool -> Maybe AdminCreateUserConfigProperty
aliasAttributes :: UserPool -> Maybe (ValueList Text)
autoVerifiedAttributes :: UserPool -> Maybe (ValueList Text)
deletionProtection :: UserPool -> Maybe (Value Text)
deviceConfiguration :: UserPool -> Maybe DeviceConfigurationProperty
emailAuthenticationMessage :: UserPool -> Maybe (Value Text)
emailAuthenticationSubject :: UserPool -> Maybe (Value Text)
emailConfiguration :: UserPool -> Maybe EmailConfigurationProperty
emailVerificationMessage :: UserPool -> Maybe (Value Text)
emailVerificationSubject :: UserPool -> Maybe (Value Text)
enabledMfas :: UserPool -> Maybe (ValueList Text)
lambdaConfig :: UserPool -> Maybe LambdaConfigProperty
mfaConfiguration :: UserPool -> Maybe (Value Text)
policies :: UserPool -> Maybe PoliciesProperty
schema :: UserPool -> Maybe [SchemaAttributeProperty]
smsAuthenticationMessage :: UserPool -> Maybe (Value Text)
smsConfiguration :: UserPool -> Maybe SmsConfigurationProperty
smsVerificationMessage :: UserPool -> Maybe (Value Text)
userAttributeUpdateSettings :: UserPool -> Maybe UserAttributeUpdateSettingsProperty
userPoolAddOns :: UserPool -> Maybe UserPoolAddOnsProperty
userPoolName :: UserPool -> Maybe (Value Text)
userPoolTags :: UserPool -> Maybe (Map Text (Value Text))
userPoolTier :: UserPool -> Maybe (Value Text)
usernameAttributes :: UserPool -> Maybe (ValueList Text)
usernameConfiguration :: UserPool -> Maybe UsernameConfigurationProperty
verificationMessageTemplate :: UserPool -> Maybe VerificationMessageTemplateProperty
webAuthnRelyingPartyID :: UserPool -> Maybe (Value Text)
webAuthnUserVerification :: UserPool -> Maybe (Value Text)
haddock_workaround_ :: ()
accountRecoverySetting :: Maybe AccountRecoverySettingProperty
adminCreateUserConfig :: Maybe AdminCreateUserConfigProperty
aliasAttributes :: Maybe (ValueList Text)
autoVerifiedAttributes :: Maybe (ValueList Text)
deletionProtection :: Maybe (Value Text)
deviceConfiguration :: Maybe DeviceConfigurationProperty
emailAuthenticationMessage :: Maybe (Value Text)
emailAuthenticationSubject :: Maybe (Value Text)
emailConfiguration :: Maybe EmailConfigurationProperty
emailVerificationMessage :: Maybe (Value Text)
emailVerificationSubject :: Maybe (Value Text)
enabledMfas :: Maybe (ValueList Text)
lambdaConfig :: Maybe LambdaConfigProperty
mfaConfiguration :: Maybe (Value Text)
policies :: Maybe PoliciesProperty
schema :: Maybe [SchemaAttributeProperty]
smsAuthenticationMessage :: Maybe (Value Text)
smsConfiguration :: Maybe SmsConfigurationProperty
smsVerificationMessage :: Maybe (Value Text)
userAttributeUpdateSettings :: Maybe UserAttributeUpdateSettingsProperty
userPoolAddOns :: Maybe UserPoolAddOnsProperty
userPoolName :: Maybe (Value Text)
userPoolTags :: Maybe (Map Text (Value Text))
userPoolTier :: Maybe (Value Text)
usernameAttributes :: Maybe (ValueList Text)
usernameConfiguration :: Maybe UsernameConfigurationProperty
verificationMessageTemplate :: Maybe VerificationMessageTemplateProperty
webAuthnRelyingPartyID :: Maybe (Value Text)
webAuthnUserVerification :: Maybe (Value Text)
..}
= UserPool {smsConfiguration :: Maybe SmsConfigurationProperty
smsConfiguration = SmsConfigurationProperty -> Maybe SmsConfigurationProperty
forall a. a -> Maybe a
forall (f :: * -> *) a. Applicative f => a -> f a
Prelude.pure PropertyType "SmsConfiguration" UserPool
SmsConfigurationProperty
newValue, Maybe [SchemaAttributeProperty]
Maybe (Map Text (Value Text))
Maybe (ValueList Text)
Maybe (Value Text)
Maybe DeviceConfigurationProperty
Maybe EmailConfigurationProperty
Maybe AdminCreateUserConfigProperty
Maybe LambdaConfigProperty
Maybe AccountRecoverySettingProperty
Maybe PoliciesProperty
Maybe UserAttributeUpdateSettingsProperty
Maybe UserPoolAddOnsProperty
Maybe UsernameConfigurationProperty
Maybe VerificationMessageTemplateProperty
()
haddock_workaround_ :: ()
accountRecoverySetting :: Maybe AccountRecoverySettingProperty
adminCreateUserConfig :: Maybe AdminCreateUserConfigProperty
aliasAttributes :: Maybe (ValueList Text)
autoVerifiedAttributes :: Maybe (ValueList Text)
deletionProtection :: Maybe (Value Text)
deviceConfiguration :: Maybe DeviceConfigurationProperty
emailAuthenticationMessage :: Maybe (Value Text)
emailAuthenticationSubject :: Maybe (Value Text)
emailConfiguration :: Maybe EmailConfigurationProperty
emailVerificationMessage :: Maybe (Value Text)
emailVerificationSubject :: Maybe (Value Text)
enabledMfas :: Maybe (ValueList Text)
lambdaConfig :: Maybe LambdaConfigProperty
mfaConfiguration :: Maybe (Value Text)
policies :: Maybe PoliciesProperty
schema :: Maybe [SchemaAttributeProperty]
smsAuthenticationMessage :: Maybe (Value Text)
smsVerificationMessage :: Maybe (Value Text)
userAttributeUpdateSettings :: Maybe UserAttributeUpdateSettingsProperty
userPoolAddOns :: Maybe UserPoolAddOnsProperty
userPoolName :: Maybe (Value Text)
userPoolTags :: Maybe (Map Text (Value Text))
userPoolTier :: Maybe (Value Text)
usernameAttributes :: Maybe (ValueList Text)
usernameConfiguration :: Maybe UsernameConfigurationProperty
verificationMessageTemplate :: Maybe VerificationMessageTemplateProperty
webAuthnRelyingPartyID :: Maybe (Value Text)
webAuthnUserVerification :: Maybe (Value Text)
haddock_workaround_ :: ()
accountRecoverySetting :: Maybe AccountRecoverySettingProperty
adminCreateUserConfig :: Maybe AdminCreateUserConfigProperty
aliasAttributes :: Maybe (ValueList Text)
autoVerifiedAttributes :: Maybe (ValueList Text)
deletionProtection :: Maybe (Value Text)
deviceConfiguration :: Maybe DeviceConfigurationProperty
emailAuthenticationMessage :: Maybe (Value Text)
emailAuthenticationSubject :: Maybe (Value Text)
emailConfiguration :: Maybe EmailConfigurationProperty
emailVerificationMessage :: Maybe (Value Text)
emailVerificationSubject :: Maybe (Value Text)
enabledMfas :: Maybe (ValueList Text)
lambdaConfig :: Maybe LambdaConfigProperty
mfaConfiguration :: Maybe (Value Text)
policies :: Maybe PoliciesProperty
schema :: Maybe [SchemaAttributeProperty]
smsAuthenticationMessage :: Maybe (Value Text)
smsVerificationMessage :: Maybe (Value Text)
userAttributeUpdateSettings :: Maybe UserAttributeUpdateSettingsProperty
userPoolAddOns :: Maybe UserPoolAddOnsProperty
userPoolName :: Maybe (Value Text)
userPoolTags :: Maybe (Map Text (Value Text))
userPoolTier :: Maybe (Value Text)
usernameAttributes :: Maybe (ValueList Text)
usernameConfiguration :: Maybe UsernameConfigurationProperty
verificationMessageTemplate :: Maybe VerificationMessageTemplateProperty
webAuthnRelyingPartyID :: Maybe (Value Text)
webAuthnUserVerification :: Maybe (Value Text)
..}
instance Property "SmsVerificationMessage" UserPool where
type PropertyType "SmsVerificationMessage" UserPool = Value Prelude.Text
set :: PropertyType "SmsVerificationMessage" UserPool
-> UserPool -> UserPool
set PropertyType "SmsVerificationMessage" UserPool
newValue UserPool {Maybe [SchemaAttributeProperty]
Maybe (Map Text (Value Text))
Maybe (ValueList Text)
Maybe (Value Text)
Maybe DeviceConfigurationProperty
Maybe EmailConfigurationProperty
Maybe AdminCreateUserConfigProperty
Maybe LambdaConfigProperty
Maybe AccountRecoverySettingProperty
Maybe PoliciesProperty
Maybe SmsConfigurationProperty
Maybe UserAttributeUpdateSettingsProperty
Maybe UserPoolAddOnsProperty
Maybe UsernameConfigurationProperty
Maybe VerificationMessageTemplateProperty
()
haddock_workaround_ :: UserPool -> ()
accountRecoverySetting :: UserPool -> Maybe AccountRecoverySettingProperty
adminCreateUserConfig :: UserPool -> Maybe AdminCreateUserConfigProperty
aliasAttributes :: UserPool -> Maybe (ValueList Text)
autoVerifiedAttributes :: UserPool -> Maybe (ValueList Text)
deletionProtection :: UserPool -> Maybe (Value Text)
deviceConfiguration :: UserPool -> Maybe DeviceConfigurationProperty
emailAuthenticationMessage :: UserPool -> Maybe (Value Text)
emailAuthenticationSubject :: UserPool -> Maybe (Value Text)
emailConfiguration :: UserPool -> Maybe EmailConfigurationProperty
emailVerificationMessage :: UserPool -> Maybe (Value Text)
emailVerificationSubject :: UserPool -> Maybe (Value Text)
enabledMfas :: UserPool -> Maybe (ValueList Text)
lambdaConfig :: UserPool -> Maybe LambdaConfigProperty
mfaConfiguration :: UserPool -> Maybe (Value Text)
policies :: UserPool -> Maybe PoliciesProperty
schema :: UserPool -> Maybe [SchemaAttributeProperty]
smsAuthenticationMessage :: UserPool -> Maybe (Value Text)
smsConfiguration :: UserPool -> Maybe SmsConfigurationProperty
smsVerificationMessage :: UserPool -> Maybe (Value Text)
userAttributeUpdateSettings :: UserPool -> Maybe UserAttributeUpdateSettingsProperty
userPoolAddOns :: UserPool -> Maybe UserPoolAddOnsProperty
userPoolName :: UserPool -> Maybe (Value Text)
userPoolTags :: UserPool -> Maybe (Map Text (Value Text))
userPoolTier :: UserPool -> Maybe (Value Text)
usernameAttributes :: UserPool -> Maybe (ValueList Text)
usernameConfiguration :: UserPool -> Maybe UsernameConfigurationProperty
verificationMessageTemplate :: UserPool -> Maybe VerificationMessageTemplateProperty
webAuthnRelyingPartyID :: UserPool -> Maybe (Value Text)
webAuthnUserVerification :: UserPool -> Maybe (Value Text)
haddock_workaround_ :: ()
accountRecoverySetting :: Maybe AccountRecoverySettingProperty
adminCreateUserConfig :: Maybe AdminCreateUserConfigProperty
aliasAttributes :: Maybe (ValueList Text)
autoVerifiedAttributes :: Maybe (ValueList Text)
deletionProtection :: Maybe (Value Text)
deviceConfiguration :: Maybe DeviceConfigurationProperty
emailAuthenticationMessage :: Maybe (Value Text)
emailAuthenticationSubject :: Maybe (Value Text)
emailConfiguration :: Maybe EmailConfigurationProperty
emailVerificationMessage :: Maybe (Value Text)
emailVerificationSubject :: Maybe (Value Text)
enabledMfas :: Maybe (ValueList Text)
lambdaConfig :: Maybe LambdaConfigProperty
mfaConfiguration :: Maybe (Value Text)
policies :: Maybe PoliciesProperty
schema :: Maybe [SchemaAttributeProperty]
smsAuthenticationMessage :: Maybe (Value Text)
smsConfiguration :: Maybe SmsConfigurationProperty
smsVerificationMessage :: Maybe (Value Text)
userAttributeUpdateSettings :: Maybe UserAttributeUpdateSettingsProperty
userPoolAddOns :: Maybe UserPoolAddOnsProperty
userPoolName :: Maybe (Value Text)
userPoolTags :: Maybe (Map Text (Value Text))
userPoolTier :: Maybe (Value Text)
usernameAttributes :: Maybe (ValueList Text)
usernameConfiguration :: Maybe UsernameConfigurationProperty
verificationMessageTemplate :: Maybe VerificationMessageTemplateProperty
webAuthnRelyingPartyID :: Maybe (Value Text)
webAuthnUserVerification :: Maybe (Value Text)
..}
= UserPool {smsVerificationMessage :: Maybe (Value Text)
smsVerificationMessage = Value Text -> Maybe (Value Text)
forall a. a -> Maybe a
forall (f :: * -> *) a. Applicative f => a -> f a
Prelude.pure PropertyType "SmsVerificationMessage" UserPool
Value Text
newValue, Maybe [SchemaAttributeProperty]
Maybe (Map Text (Value Text))
Maybe (ValueList Text)
Maybe (Value Text)
Maybe DeviceConfigurationProperty
Maybe EmailConfigurationProperty
Maybe AdminCreateUserConfigProperty
Maybe LambdaConfigProperty
Maybe AccountRecoverySettingProperty
Maybe PoliciesProperty
Maybe SmsConfigurationProperty
Maybe UserAttributeUpdateSettingsProperty
Maybe UserPoolAddOnsProperty
Maybe UsernameConfigurationProperty
Maybe VerificationMessageTemplateProperty
()
haddock_workaround_ :: ()
accountRecoverySetting :: Maybe AccountRecoverySettingProperty
adminCreateUserConfig :: Maybe AdminCreateUserConfigProperty
aliasAttributes :: Maybe (ValueList Text)
autoVerifiedAttributes :: Maybe (ValueList Text)
deletionProtection :: Maybe (Value Text)
deviceConfiguration :: Maybe DeviceConfigurationProperty
emailAuthenticationMessage :: Maybe (Value Text)
emailAuthenticationSubject :: Maybe (Value Text)
emailConfiguration :: Maybe EmailConfigurationProperty
emailVerificationMessage :: Maybe (Value Text)
emailVerificationSubject :: Maybe (Value Text)
enabledMfas :: Maybe (ValueList Text)
lambdaConfig :: Maybe LambdaConfigProperty
mfaConfiguration :: Maybe (Value Text)
policies :: Maybe PoliciesProperty
schema :: Maybe [SchemaAttributeProperty]
smsAuthenticationMessage :: Maybe (Value Text)
smsConfiguration :: Maybe SmsConfigurationProperty
userAttributeUpdateSettings :: Maybe UserAttributeUpdateSettingsProperty
userPoolAddOns :: Maybe UserPoolAddOnsProperty
userPoolName :: Maybe (Value Text)
userPoolTags :: Maybe (Map Text (Value Text))
userPoolTier :: Maybe (Value Text)
usernameAttributes :: Maybe (ValueList Text)
usernameConfiguration :: Maybe UsernameConfigurationProperty
verificationMessageTemplate :: Maybe VerificationMessageTemplateProperty
webAuthnRelyingPartyID :: Maybe (Value Text)
webAuthnUserVerification :: Maybe (Value Text)
haddock_workaround_ :: ()
accountRecoverySetting :: Maybe AccountRecoverySettingProperty
adminCreateUserConfig :: Maybe AdminCreateUserConfigProperty
aliasAttributes :: Maybe (ValueList Text)
autoVerifiedAttributes :: Maybe (ValueList Text)
deletionProtection :: Maybe (Value Text)
deviceConfiguration :: Maybe DeviceConfigurationProperty
emailAuthenticationMessage :: Maybe (Value Text)
emailAuthenticationSubject :: Maybe (Value Text)
emailConfiguration :: Maybe EmailConfigurationProperty
emailVerificationMessage :: Maybe (Value Text)
emailVerificationSubject :: Maybe (Value Text)
enabledMfas :: Maybe (ValueList Text)
lambdaConfig :: Maybe LambdaConfigProperty
mfaConfiguration :: Maybe (Value Text)
policies :: Maybe PoliciesProperty
schema :: Maybe [SchemaAttributeProperty]
smsAuthenticationMessage :: Maybe (Value Text)
smsConfiguration :: Maybe SmsConfigurationProperty
userAttributeUpdateSettings :: Maybe UserAttributeUpdateSettingsProperty
userPoolAddOns :: Maybe UserPoolAddOnsProperty
userPoolName :: Maybe (Value Text)
userPoolTags :: Maybe (Map Text (Value Text))
userPoolTier :: Maybe (Value Text)
usernameAttributes :: Maybe (ValueList Text)
usernameConfiguration :: Maybe UsernameConfigurationProperty
verificationMessageTemplate :: Maybe VerificationMessageTemplateProperty
webAuthnRelyingPartyID :: Maybe (Value Text)
webAuthnUserVerification :: Maybe (Value Text)
..}
instance Property "UserAttributeUpdateSettings" UserPool where
type PropertyType "UserAttributeUpdateSettings" UserPool = UserAttributeUpdateSettingsProperty
set :: PropertyType "UserAttributeUpdateSettings" UserPool
-> UserPool -> UserPool
set PropertyType "UserAttributeUpdateSettings" UserPool
newValue UserPool {Maybe [SchemaAttributeProperty]
Maybe (Map Text (Value Text))
Maybe (ValueList Text)
Maybe (Value Text)
Maybe DeviceConfigurationProperty
Maybe EmailConfigurationProperty
Maybe AdminCreateUserConfigProperty
Maybe LambdaConfigProperty
Maybe AccountRecoverySettingProperty
Maybe PoliciesProperty
Maybe SmsConfigurationProperty
Maybe UserAttributeUpdateSettingsProperty
Maybe UserPoolAddOnsProperty
Maybe UsernameConfigurationProperty
Maybe VerificationMessageTemplateProperty
()
haddock_workaround_ :: UserPool -> ()
accountRecoverySetting :: UserPool -> Maybe AccountRecoverySettingProperty
adminCreateUserConfig :: UserPool -> Maybe AdminCreateUserConfigProperty
aliasAttributes :: UserPool -> Maybe (ValueList Text)
autoVerifiedAttributes :: UserPool -> Maybe (ValueList Text)
deletionProtection :: UserPool -> Maybe (Value Text)
deviceConfiguration :: UserPool -> Maybe DeviceConfigurationProperty
emailAuthenticationMessage :: UserPool -> Maybe (Value Text)
emailAuthenticationSubject :: UserPool -> Maybe (Value Text)
emailConfiguration :: UserPool -> Maybe EmailConfigurationProperty
emailVerificationMessage :: UserPool -> Maybe (Value Text)
emailVerificationSubject :: UserPool -> Maybe (Value Text)
enabledMfas :: UserPool -> Maybe (ValueList Text)
lambdaConfig :: UserPool -> Maybe LambdaConfigProperty
mfaConfiguration :: UserPool -> Maybe (Value Text)
policies :: UserPool -> Maybe PoliciesProperty
schema :: UserPool -> Maybe [SchemaAttributeProperty]
smsAuthenticationMessage :: UserPool -> Maybe (Value Text)
smsConfiguration :: UserPool -> Maybe SmsConfigurationProperty
smsVerificationMessage :: UserPool -> Maybe (Value Text)
userAttributeUpdateSettings :: UserPool -> Maybe UserAttributeUpdateSettingsProperty
userPoolAddOns :: UserPool -> Maybe UserPoolAddOnsProperty
userPoolName :: UserPool -> Maybe (Value Text)
userPoolTags :: UserPool -> Maybe (Map Text (Value Text))
userPoolTier :: UserPool -> Maybe (Value Text)
usernameAttributes :: UserPool -> Maybe (ValueList Text)
usernameConfiguration :: UserPool -> Maybe UsernameConfigurationProperty
verificationMessageTemplate :: UserPool -> Maybe VerificationMessageTemplateProperty
webAuthnRelyingPartyID :: UserPool -> Maybe (Value Text)
webAuthnUserVerification :: UserPool -> Maybe (Value Text)
haddock_workaround_ :: ()
accountRecoverySetting :: Maybe AccountRecoverySettingProperty
adminCreateUserConfig :: Maybe AdminCreateUserConfigProperty
aliasAttributes :: Maybe (ValueList Text)
autoVerifiedAttributes :: Maybe (ValueList Text)
deletionProtection :: Maybe (Value Text)
deviceConfiguration :: Maybe DeviceConfigurationProperty
emailAuthenticationMessage :: Maybe (Value Text)
emailAuthenticationSubject :: Maybe (Value Text)
emailConfiguration :: Maybe EmailConfigurationProperty
emailVerificationMessage :: Maybe (Value Text)
emailVerificationSubject :: Maybe (Value Text)
enabledMfas :: Maybe (ValueList Text)
lambdaConfig :: Maybe LambdaConfigProperty
mfaConfiguration :: Maybe (Value Text)
policies :: Maybe PoliciesProperty
schema :: Maybe [SchemaAttributeProperty]
smsAuthenticationMessage :: Maybe (Value Text)
smsConfiguration :: Maybe SmsConfigurationProperty
smsVerificationMessage :: Maybe (Value Text)
userAttributeUpdateSettings :: Maybe UserAttributeUpdateSettingsProperty
userPoolAddOns :: Maybe UserPoolAddOnsProperty
userPoolName :: Maybe (Value Text)
userPoolTags :: Maybe (Map Text (Value Text))
userPoolTier :: Maybe (Value Text)
usernameAttributes :: Maybe (ValueList Text)
usernameConfiguration :: Maybe UsernameConfigurationProperty
verificationMessageTemplate :: Maybe VerificationMessageTemplateProperty
webAuthnRelyingPartyID :: Maybe (Value Text)
webAuthnUserVerification :: Maybe (Value Text)
..}
= UserPool
{userAttributeUpdateSettings :: Maybe UserAttributeUpdateSettingsProperty
userAttributeUpdateSettings = UserAttributeUpdateSettingsProperty
-> Maybe UserAttributeUpdateSettingsProperty
forall a. a -> Maybe a
forall (f :: * -> *) a. Applicative f => a -> f a
Prelude.pure PropertyType "UserAttributeUpdateSettings" UserPool
UserAttributeUpdateSettingsProperty
newValue, Maybe [SchemaAttributeProperty]
Maybe (Map Text (Value Text))
Maybe (ValueList Text)
Maybe (Value Text)
Maybe DeviceConfigurationProperty
Maybe EmailConfigurationProperty
Maybe AdminCreateUserConfigProperty
Maybe LambdaConfigProperty
Maybe AccountRecoverySettingProperty
Maybe PoliciesProperty
Maybe SmsConfigurationProperty
Maybe UserPoolAddOnsProperty
Maybe UsernameConfigurationProperty
Maybe VerificationMessageTemplateProperty
()
haddock_workaround_ :: ()
accountRecoverySetting :: Maybe AccountRecoverySettingProperty
adminCreateUserConfig :: Maybe AdminCreateUserConfigProperty
aliasAttributes :: Maybe (ValueList Text)
autoVerifiedAttributes :: Maybe (ValueList Text)
deletionProtection :: Maybe (Value Text)
deviceConfiguration :: Maybe DeviceConfigurationProperty
emailAuthenticationMessage :: Maybe (Value Text)
emailAuthenticationSubject :: Maybe (Value Text)
emailConfiguration :: Maybe EmailConfigurationProperty
emailVerificationMessage :: Maybe (Value Text)
emailVerificationSubject :: Maybe (Value Text)
enabledMfas :: Maybe (ValueList Text)
lambdaConfig :: Maybe LambdaConfigProperty
mfaConfiguration :: Maybe (Value Text)
policies :: Maybe PoliciesProperty
schema :: Maybe [SchemaAttributeProperty]
smsAuthenticationMessage :: Maybe (Value Text)
smsConfiguration :: Maybe SmsConfigurationProperty
smsVerificationMessage :: Maybe (Value Text)
userPoolAddOns :: Maybe UserPoolAddOnsProperty
userPoolName :: Maybe (Value Text)
userPoolTags :: Maybe (Map Text (Value Text))
userPoolTier :: Maybe (Value Text)
usernameAttributes :: Maybe (ValueList Text)
usernameConfiguration :: Maybe UsernameConfigurationProperty
verificationMessageTemplate :: Maybe VerificationMessageTemplateProperty
webAuthnRelyingPartyID :: Maybe (Value Text)
webAuthnUserVerification :: Maybe (Value Text)
haddock_workaround_ :: ()
accountRecoverySetting :: Maybe AccountRecoverySettingProperty
adminCreateUserConfig :: Maybe AdminCreateUserConfigProperty
aliasAttributes :: Maybe (ValueList Text)
autoVerifiedAttributes :: Maybe (ValueList Text)
deletionProtection :: Maybe (Value Text)
deviceConfiguration :: Maybe DeviceConfigurationProperty
emailAuthenticationMessage :: Maybe (Value Text)
emailAuthenticationSubject :: Maybe (Value Text)
emailConfiguration :: Maybe EmailConfigurationProperty
emailVerificationMessage :: Maybe (Value Text)
emailVerificationSubject :: Maybe (Value Text)
enabledMfas :: Maybe (ValueList Text)
lambdaConfig :: Maybe LambdaConfigProperty
mfaConfiguration :: Maybe (Value Text)
policies :: Maybe PoliciesProperty
schema :: Maybe [SchemaAttributeProperty]
smsAuthenticationMessage :: Maybe (Value Text)
smsConfiguration :: Maybe SmsConfigurationProperty
smsVerificationMessage :: Maybe (Value Text)
userPoolAddOns :: Maybe UserPoolAddOnsProperty
userPoolName :: Maybe (Value Text)
userPoolTags :: Maybe (Map Text (Value Text))
userPoolTier :: Maybe (Value Text)
usernameAttributes :: Maybe (ValueList Text)
usernameConfiguration :: Maybe UsernameConfigurationProperty
verificationMessageTemplate :: Maybe VerificationMessageTemplateProperty
webAuthnRelyingPartyID :: Maybe (Value Text)
webAuthnUserVerification :: Maybe (Value Text)
..}
instance Property "UserPoolAddOns" UserPool where
type PropertyType "UserPoolAddOns" UserPool = UserPoolAddOnsProperty
set :: PropertyType "UserPoolAddOns" UserPool -> UserPool -> UserPool
set PropertyType "UserPoolAddOns" UserPool
newValue UserPool {Maybe [SchemaAttributeProperty]
Maybe (Map Text (Value Text))
Maybe (ValueList Text)
Maybe (Value Text)
Maybe DeviceConfigurationProperty
Maybe EmailConfigurationProperty
Maybe AdminCreateUserConfigProperty
Maybe LambdaConfigProperty
Maybe AccountRecoverySettingProperty
Maybe PoliciesProperty
Maybe SmsConfigurationProperty
Maybe UserAttributeUpdateSettingsProperty
Maybe UserPoolAddOnsProperty
Maybe UsernameConfigurationProperty
Maybe VerificationMessageTemplateProperty
()
haddock_workaround_ :: UserPool -> ()
accountRecoverySetting :: UserPool -> Maybe AccountRecoverySettingProperty
adminCreateUserConfig :: UserPool -> Maybe AdminCreateUserConfigProperty
aliasAttributes :: UserPool -> Maybe (ValueList Text)
autoVerifiedAttributes :: UserPool -> Maybe (ValueList Text)
deletionProtection :: UserPool -> Maybe (Value Text)
deviceConfiguration :: UserPool -> Maybe DeviceConfigurationProperty
emailAuthenticationMessage :: UserPool -> Maybe (Value Text)
emailAuthenticationSubject :: UserPool -> Maybe (Value Text)
emailConfiguration :: UserPool -> Maybe EmailConfigurationProperty
emailVerificationMessage :: UserPool -> Maybe (Value Text)
emailVerificationSubject :: UserPool -> Maybe (Value Text)
enabledMfas :: UserPool -> Maybe (ValueList Text)
lambdaConfig :: UserPool -> Maybe LambdaConfigProperty
mfaConfiguration :: UserPool -> Maybe (Value Text)
policies :: UserPool -> Maybe PoliciesProperty
schema :: UserPool -> Maybe [SchemaAttributeProperty]
smsAuthenticationMessage :: UserPool -> Maybe (Value Text)
smsConfiguration :: UserPool -> Maybe SmsConfigurationProperty
smsVerificationMessage :: UserPool -> Maybe (Value Text)
userAttributeUpdateSettings :: UserPool -> Maybe UserAttributeUpdateSettingsProperty
userPoolAddOns :: UserPool -> Maybe UserPoolAddOnsProperty
userPoolName :: UserPool -> Maybe (Value Text)
userPoolTags :: UserPool -> Maybe (Map Text (Value Text))
userPoolTier :: UserPool -> Maybe (Value Text)
usernameAttributes :: UserPool -> Maybe (ValueList Text)
usernameConfiguration :: UserPool -> Maybe UsernameConfigurationProperty
verificationMessageTemplate :: UserPool -> Maybe VerificationMessageTemplateProperty
webAuthnRelyingPartyID :: UserPool -> Maybe (Value Text)
webAuthnUserVerification :: UserPool -> Maybe (Value Text)
haddock_workaround_ :: ()
accountRecoverySetting :: Maybe AccountRecoverySettingProperty
adminCreateUserConfig :: Maybe AdminCreateUserConfigProperty
aliasAttributes :: Maybe (ValueList Text)
autoVerifiedAttributes :: Maybe (ValueList Text)
deletionProtection :: Maybe (Value Text)
deviceConfiguration :: Maybe DeviceConfigurationProperty
emailAuthenticationMessage :: Maybe (Value Text)
emailAuthenticationSubject :: Maybe (Value Text)
emailConfiguration :: Maybe EmailConfigurationProperty
emailVerificationMessage :: Maybe (Value Text)
emailVerificationSubject :: Maybe (Value Text)
enabledMfas :: Maybe (ValueList Text)
lambdaConfig :: Maybe LambdaConfigProperty
mfaConfiguration :: Maybe (Value Text)
policies :: Maybe PoliciesProperty
schema :: Maybe [SchemaAttributeProperty]
smsAuthenticationMessage :: Maybe (Value Text)
smsConfiguration :: Maybe SmsConfigurationProperty
smsVerificationMessage :: Maybe (Value Text)
userAttributeUpdateSettings :: Maybe UserAttributeUpdateSettingsProperty
userPoolAddOns :: Maybe UserPoolAddOnsProperty
userPoolName :: Maybe (Value Text)
userPoolTags :: Maybe (Map Text (Value Text))
userPoolTier :: Maybe (Value Text)
usernameAttributes :: Maybe (ValueList Text)
usernameConfiguration :: Maybe UsernameConfigurationProperty
verificationMessageTemplate :: Maybe VerificationMessageTemplateProperty
webAuthnRelyingPartyID :: Maybe (Value Text)
webAuthnUserVerification :: Maybe (Value Text)
..}
= UserPool {userPoolAddOns :: Maybe UserPoolAddOnsProperty
userPoolAddOns = UserPoolAddOnsProperty -> Maybe UserPoolAddOnsProperty
forall a. a -> Maybe a
forall (f :: * -> *) a. Applicative f => a -> f a
Prelude.pure PropertyType "UserPoolAddOns" UserPool
UserPoolAddOnsProperty
newValue, Maybe [SchemaAttributeProperty]
Maybe (Map Text (Value Text))
Maybe (ValueList Text)
Maybe (Value Text)
Maybe DeviceConfigurationProperty
Maybe EmailConfigurationProperty
Maybe AdminCreateUserConfigProperty
Maybe LambdaConfigProperty
Maybe AccountRecoverySettingProperty
Maybe PoliciesProperty
Maybe SmsConfigurationProperty
Maybe UserAttributeUpdateSettingsProperty
Maybe UsernameConfigurationProperty
Maybe VerificationMessageTemplateProperty
()
haddock_workaround_ :: ()
accountRecoverySetting :: Maybe AccountRecoverySettingProperty
adminCreateUserConfig :: Maybe AdminCreateUserConfigProperty
aliasAttributes :: Maybe (ValueList Text)
autoVerifiedAttributes :: Maybe (ValueList Text)
deletionProtection :: Maybe (Value Text)
deviceConfiguration :: Maybe DeviceConfigurationProperty
emailAuthenticationMessage :: Maybe (Value Text)
emailAuthenticationSubject :: Maybe (Value Text)
emailConfiguration :: Maybe EmailConfigurationProperty
emailVerificationMessage :: Maybe (Value Text)
emailVerificationSubject :: Maybe (Value Text)
enabledMfas :: Maybe (ValueList Text)
lambdaConfig :: Maybe LambdaConfigProperty
mfaConfiguration :: Maybe (Value Text)
policies :: Maybe PoliciesProperty
schema :: Maybe [SchemaAttributeProperty]
smsAuthenticationMessage :: Maybe (Value Text)
smsConfiguration :: Maybe SmsConfigurationProperty
smsVerificationMessage :: Maybe (Value Text)
userAttributeUpdateSettings :: Maybe UserAttributeUpdateSettingsProperty
userPoolName :: Maybe (Value Text)
userPoolTags :: Maybe (Map Text (Value Text))
userPoolTier :: Maybe (Value Text)
usernameAttributes :: Maybe (ValueList Text)
usernameConfiguration :: Maybe UsernameConfigurationProperty
verificationMessageTemplate :: Maybe VerificationMessageTemplateProperty
webAuthnRelyingPartyID :: Maybe (Value Text)
webAuthnUserVerification :: Maybe (Value Text)
haddock_workaround_ :: ()
accountRecoverySetting :: Maybe AccountRecoverySettingProperty
adminCreateUserConfig :: Maybe AdminCreateUserConfigProperty
aliasAttributes :: Maybe (ValueList Text)
autoVerifiedAttributes :: Maybe (ValueList Text)
deletionProtection :: Maybe (Value Text)
deviceConfiguration :: Maybe DeviceConfigurationProperty
emailAuthenticationMessage :: Maybe (Value Text)
emailAuthenticationSubject :: Maybe (Value Text)
emailConfiguration :: Maybe EmailConfigurationProperty
emailVerificationMessage :: Maybe (Value Text)
emailVerificationSubject :: Maybe (Value Text)
enabledMfas :: Maybe (ValueList Text)
lambdaConfig :: Maybe LambdaConfigProperty
mfaConfiguration :: Maybe (Value Text)
policies :: Maybe PoliciesProperty
schema :: Maybe [SchemaAttributeProperty]
smsAuthenticationMessage :: Maybe (Value Text)
smsConfiguration :: Maybe SmsConfigurationProperty
smsVerificationMessage :: Maybe (Value Text)
userAttributeUpdateSettings :: Maybe UserAttributeUpdateSettingsProperty
userPoolName :: Maybe (Value Text)
userPoolTags :: Maybe (Map Text (Value Text))
userPoolTier :: Maybe (Value Text)
usernameAttributes :: Maybe (ValueList Text)
usernameConfiguration :: Maybe UsernameConfigurationProperty
verificationMessageTemplate :: Maybe VerificationMessageTemplateProperty
webAuthnRelyingPartyID :: Maybe (Value Text)
webAuthnUserVerification :: Maybe (Value Text)
..}
instance Property "UserPoolName" UserPool where
type PropertyType "UserPoolName" UserPool = Value Prelude.Text
set :: PropertyType "UserPoolName" UserPool -> UserPool -> UserPool
set PropertyType "UserPoolName" UserPool
newValue UserPool {Maybe [SchemaAttributeProperty]
Maybe (Map Text (Value Text))
Maybe (ValueList Text)
Maybe (Value Text)
Maybe DeviceConfigurationProperty
Maybe EmailConfigurationProperty
Maybe AdminCreateUserConfigProperty
Maybe LambdaConfigProperty
Maybe AccountRecoverySettingProperty
Maybe PoliciesProperty
Maybe SmsConfigurationProperty
Maybe UserAttributeUpdateSettingsProperty
Maybe UserPoolAddOnsProperty
Maybe UsernameConfigurationProperty
Maybe VerificationMessageTemplateProperty
()
haddock_workaround_ :: UserPool -> ()
accountRecoverySetting :: UserPool -> Maybe AccountRecoverySettingProperty
adminCreateUserConfig :: UserPool -> Maybe AdminCreateUserConfigProperty
aliasAttributes :: UserPool -> Maybe (ValueList Text)
autoVerifiedAttributes :: UserPool -> Maybe (ValueList Text)
deletionProtection :: UserPool -> Maybe (Value Text)
deviceConfiguration :: UserPool -> Maybe DeviceConfigurationProperty
emailAuthenticationMessage :: UserPool -> Maybe (Value Text)
emailAuthenticationSubject :: UserPool -> Maybe (Value Text)
emailConfiguration :: UserPool -> Maybe EmailConfigurationProperty
emailVerificationMessage :: UserPool -> Maybe (Value Text)
emailVerificationSubject :: UserPool -> Maybe (Value Text)
enabledMfas :: UserPool -> Maybe (ValueList Text)
lambdaConfig :: UserPool -> Maybe LambdaConfigProperty
mfaConfiguration :: UserPool -> Maybe (Value Text)
policies :: UserPool -> Maybe PoliciesProperty
schema :: UserPool -> Maybe [SchemaAttributeProperty]
smsAuthenticationMessage :: UserPool -> Maybe (Value Text)
smsConfiguration :: UserPool -> Maybe SmsConfigurationProperty
smsVerificationMessage :: UserPool -> Maybe (Value Text)
userAttributeUpdateSettings :: UserPool -> Maybe UserAttributeUpdateSettingsProperty
userPoolAddOns :: UserPool -> Maybe UserPoolAddOnsProperty
userPoolName :: UserPool -> Maybe (Value Text)
userPoolTags :: UserPool -> Maybe (Map Text (Value Text))
userPoolTier :: UserPool -> Maybe (Value Text)
usernameAttributes :: UserPool -> Maybe (ValueList Text)
usernameConfiguration :: UserPool -> Maybe UsernameConfigurationProperty
verificationMessageTemplate :: UserPool -> Maybe VerificationMessageTemplateProperty
webAuthnRelyingPartyID :: UserPool -> Maybe (Value Text)
webAuthnUserVerification :: UserPool -> Maybe (Value Text)
haddock_workaround_ :: ()
accountRecoverySetting :: Maybe AccountRecoverySettingProperty
adminCreateUserConfig :: Maybe AdminCreateUserConfigProperty
aliasAttributes :: Maybe (ValueList Text)
autoVerifiedAttributes :: Maybe (ValueList Text)
deletionProtection :: Maybe (Value Text)
deviceConfiguration :: Maybe DeviceConfigurationProperty
emailAuthenticationMessage :: Maybe (Value Text)
emailAuthenticationSubject :: Maybe (Value Text)
emailConfiguration :: Maybe EmailConfigurationProperty
emailVerificationMessage :: Maybe (Value Text)
emailVerificationSubject :: Maybe (Value Text)
enabledMfas :: Maybe (ValueList Text)
lambdaConfig :: Maybe LambdaConfigProperty
mfaConfiguration :: Maybe (Value Text)
policies :: Maybe PoliciesProperty
schema :: Maybe [SchemaAttributeProperty]
smsAuthenticationMessage :: Maybe (Value Text)
smsConfiguration :: Maybe SmsConfigurationProperty
smsVerificationMessage :: Maybe (Value Text)
userAttributeUpdateSettings :: Maybe UserAttributeUpdateSettingsProperty
userPoolAddOns :: Maybe UserPoolAddOnsProperty
userPoolName :: Maybe (Value Text)
userPoolTags :: Maybe (Map Text (Value Text))
userPoolTier :: Maybe (Value Text)
usernameAttributes :: Maybe (ValueList Text)
usernameConfiguration :: Maybe UsernameConfigurationProperty
verificationMessageTemplate :: Maybe VerificationMessageTemplateProperty
webAuthnRelyingPartyID :: Maybe (Value Text)
webAuthnUserVerification :: Maybe (Value Text)
..}
= UserPool {userPoolName :: Maybe (Value Text)
userPoolName = Value Text -> Maybe (Value Text)
forall a. a -> Maybe a
forall (f :: * -> *) a. Applicative f => a -> f a
Prelude.pure PropertyType "UserPoolName" UserPool
Value Text
newValue, Maybe [SchemaAttributeProperty]
Maybe (Map Text (Value Text))
Maybe (ValueList Text)
Maybe (Value Text)
Maybe DeviceConfigurationProperty
Maybe EmailConfigurationProperty
Maybe AdminCreateUserConfigProperty
Maybe LambdaConfigProperty
Maybe AccountRecoverySettingProperty
Maybe PoliciesProperty
Maybe SmsConfigurationProperty
Maybe UserAttributeUpdateSettingsProperty
Maybe UserPoolAddOnsProperty
Maybe UsernameConfigurationProperty
Maybe VerificationMessageTemplateProperty
()
haddock_workaround_ :: ()
accountRecoverySetting :: Maybe AccountRecoverySettingProperty
adminCreateUserConfig :: Maybe AdminCreateUserConfigProperty
aliasAttributes :: Maybe (ValueList Text)
autoVerifiedAttributes :: Maybe (ValueList Text)
deletionProtection :: Maybe (Value Text)
deviceConfiguration :: Maybe DeviceConfigurationProperty
emailAuthenticationMessage :: Maybe (Value Text)
emailAuthenticationSubject :: Maybe (Value Text)
emailConfiguration :: Maybe EmailConfigurationProperty
emailVerificationMessage :: Maybe (Value Text)
emailVerificationSubject :: Maybe (Value Text)
enabledMfas :: Maybe (ValueList Text)
lambdaConfig :: Maybe LambdaConfigProperty
mfaConfiguration :: Maybe (Value Text)
policies :: Maybe PoliciesProperty
schema :: Maybe [SchemaAttributeProperty]
smsAuthenticationMessage :: Maybe (Value Text)
smsConfiguration :: Maybe SmsConfigurationProperty
smsVerificationMessage :: Maybe (Value Text)
userAttributeUpdateSettings :: Maybe UserAttributeUpdateSettingsProperty
userPoolAddOns :: Maybe UserPoolAddOnsProperty
userPoolTags :: Maybe (Map Text (Value Text))
userPoolTier :: Maybe (Value Text)
usernameAttributes :: Maybe (ValueList Text)
usernameConfiguration :: Maybe UsernameConfigurationProperty
verificationMessageTemplate :: Maybe VerificationMessageTemplateProperty
webAuthnRelyingPartyID :: Maybe (Value Text)
webAuthnUserVerification :: Maybe (Value Text)
haddock_workaround_ :: ()
accountRecoverySetting :: Maybe AccountRecoverySettingProperty
adminCreateUserConfig :: Maybe AdminCreateUserConfigProperty
aliasAttributes :: Maybe (ValueList Text)
autoVerifiedAttributes :: Maybe (ValueList Text)
deletionProtection :: Maybe (Value Text)
deviceConfiguration :: Maybe DeviceConfigurationProperty
emailAuthenticationMessage :: Maybe (Value Text)
emailAuthenticationSubject :: Maybe (Value Text)
emailConfiguration :: Maybe EmailConfigurationProperty
emailVerificationMessage :: Maybe (Value Text)
emailVerificationSubject :: Maybe (Value Text)
enabledMfas :: Maybe (ValueList Text)
lambdaConfig :: Maybe LambdaConfigProperty
mfaConfiguration :: Maybe (Value Text)
policies :: Maybe PoliciesProperty
schema :: Maybe [SchemaAttributeProperty]
smsAuthenticationMessage :: Maybe (Value Text)
smsConfiguration :: Maybe SmsConfigurationProperty
smsVerificationMessage :: Maybe (Value Text)
userAttributeUpdateSettings :: Maybe UserAttributeUpdateSettingsProperty
userPoolAddOns :: Maybe UserPoolAddOnsProperty
userPoolTags :: Maybe (Map Text (Value Text))
userPoolTier :: Maybe (Value Text)
usernameAttributes :: Maybe (ValueList Text)
usernameConfiguration :: Maybe UsernameConfigurationProperty
verificationMessageTemplate :: Maybe VerificationMessageTemplateProperty
webAuthnRelyingPartyID :: Maybe (Value Text)
webAuthnUserVerification :: Maybe (Value Text)
..}
instance Property "UserPoolTags" UserPool where
type PropertyType "UserPoolTags" UserPool = Prelude.Map Prelude.Text (Value Prelude.Text)
set :: PropertyType "UserPoolTags" UserPool -> UserPool -> UserPool
set PropertyType "UserPoolTags" UserPool
newValue UserPool {Maybe [SchemaAttributeProperty]
Maybe (Map Text (Value Text))
Maybe (ValueList Text)
Maybe (Value Text)
Maybe DeviceConfigurationProperty
Maybe EmailConfigurationProperty
Maybe AdminCreateUserConfigProperty
Maybe LambdaConfigProperty
Maybe AccountRecoverySettingProperty
Maybe PoliciesProperty
Maybe SmsConfigurationProperty
Maybe UserAttributeUpdateSettingsProperty
Maybe UserPoolAddOnsProperty
Maybe UsernameConfigurationProperty
Maybe VerificationMessageTemplateProperty
()
haddock_workaround_ :: UserPool -> ()
accountRecoverySetting :: UserPool -> Maybe AccountRecoverySettingProperty
adminCreateUserConfig :: UserPool -> Maybe AdminCreateUserConfigProperty
aliasAttributes :: UserPool -> Maybe (ValueList Text)
autoVerifiedAttributes :: UserPool -> Maybe (ValueList Text)
deletionProtection :: UserPool -> Maybe (Value Text)
deviceConfiguration :: UserPool -> Maybe DeviceConfigurationProperty
emailAuthenticationMessage :: UserPool -> Maybe (Value Text)
emailAuthenticationSubject :: UserPool -> Maybe (Value Text)
emailConfiguration :: UserPool -> Maybe EmailConfigurationProperty
emailVerificationMessage :: UserPool -> Maybe (Value Text)
emailVerificationSubject :: UserPool -> Maybe (Value Text)
enabledMfas :: UserPool -> Maybe (ValueList Text)
lambdaConfig :: UserPool -> Maybe LambdaConfigProperty
mfaConfiguration :: UserPool -> Maybe (Value Text)
policies :: UserPool -> Maybe PoliciesProperty
schema :: UserPool -> Maybe [SchemaAttributeProperty]
smsAuthenticationMessage :: UserPool -> Maybe (Value Text)
smsConfiguration :: UserPool -> Maybe SmsConfigurationProperty
smsVerificationMessage :: UserPool -> Maybe (Value Text)
userAttributeUpdateSettings :: UserPool -> Maybe UserAttributeUpdateSettingsProperty
userPoolAddOns :: UserPool -> Maybe UserPoolAddOnsProperty
userPoolName :: UserPool -> Maybe (Value Text)
userPoolTags :: UserPool -> Maybe (Map Text (Value Text))
userPoolTier :: UserPool -> Maybe (Value Text)
usernameAttributes :: UserPool -> Maybe (ValueList Text)
usernameConfiguration :: UserPool -> Maybe UsernameConfigurationProperty
verificationMessageTemplate :: UserPool -> Maybe VerificationMessageTemplateProperty
webAuthnRelyingPartyID :: UserPool -> Maybe (Value Text)
webAuthnUserVerification :: UserPool -> Maybe (Value Text)
haddock_workaround_ :: ()
accountRecoverySetting :: Maybe AccountRecoverySettingProperty
adminCreateUserConfig :: Maybe AdminCreateUserConfigProperty
aliasAttributes :: Maybe (ValueList Text)
autoVerifiedAttributes :: Maybe (ValueList Text)
deletionProtection :: Maybe (Value Text)
deviceConfiguration :: Maybe DeviceConfigurationProperty
emailAuthenticationMessage :: Maybe (Value Text)
emailAuthenticationSubject :: Maybe (Value Text)
emailConfiguration :: Maybe EmailConfigurationProperty
emailVerificationMessage :: Maybe (Value Text)
emailVerificationSubject :: Maybe (Value Text)
enabledMfas :: Maybe (ValueList Text)
lambdaConfig :: Maybe LambdaConfigProperty
mfaConfiguration :: Maybe (Value Text)
policies :: Maybe PoliciesProperty
schema :: Maybe [SchemaAttributeProperty]
smsAuthenticationMessage :: Maybe (Value Text)
smsConfiguration :: Maybe SmsConfigurationProperty
smsVerificationMessage :: Maybe (Value Text)
userAttributeUpdateSettings :: Maybe UserAttributeUpdateSettingsProperty
userPoolAddOns :: Maybe UserPoolAddOnsProperty
userPoolName :: Maybe (Value Text)
userPoolTags :: Maybe (Map Text (Value Text))
userPoolTier :: Maybe (Value Text)
usernameAttributes :: Maybe (ValueList Text)
usernameConfiguration :: Maybe UsernameConfigurationProperty
verificationMessageTemplate :: Maybe VerificationMessageTemplateProperty
webAuthnRelyingPartyID :: Maybe (Value Text)
webAuthnUserVerification :: Maybe (Value Text)
..}
= UserPool {userPoolTags :: Maybe (Map Text (Value Text))
userPoolTags = Map Text (Value Text) -> Maybe (Map Text (Value Text))
forall a. a -> Maybe a
forall (f :: * -> *) a. Applicative f => a -> f a
Prelude.pure Map Text (Value Text)
PropertyType "UserPoolTags" UserPool
newValue, Maybe [SchemaAttributeProperty]
Maybe (ValueList Text)
Maybe (Value Text)
Maybe DeviceConfigurationProperty
Maybe EmailConfigurationProperty
Maybe AdminCreateUserConfigProperty
Maybe LambdaConfigProperty
Maybe AccountRecoverySettingProperty
Maybe PoliciesProperty
Maybe SmsConfigurationProperty
Maybe UserAttributeUpdateSettingsProperty
Maybe UserPoolAddOnsProperty
Maybe UsernameConfigurationProperty
Maybe VerificationMessageTemplateProperty
()
haddock_workaround_ :: ()
accountRecoverySetting :: Maybe AccountRecoverySettingProperty
adminCreateUserConfig :: Maybe AdminCreateUserConfigProperty
aliasAttributes :: Maybe (ValueList Text)
autoVerifiedAttributes :: Maybe (ValueList Text)
deletionProtection :: Maybe (Value Text)
deviceConfiguration :: Maybe DeviceConfigurationProperty
emailAuthenticationMessage :: Maybe (Value Text)
emailAuthenticationSubject :: Maybe (Value Text)
emailConfiguration :: Maybe EmailConfigurationProperty
emailVerificationMessage :: Maybe (Value Text)
emailVerificationSubject :: Maybe (Value Text)
enabledMfas :: Maybe (ValueList Text)
lambdaConfig :: Maybe LambdaConfigProperty
mfaConfiguration :: Maybe (Value Text)
policies :: Maybe PoliciesProperty
schema :: Maybe [SchemaAttributeProperty]
smsAuthenticationMessage :: Maybe (Value Text)
smsConfiguration :: Maybe SmsConfigurationProperty
smsVerificationMessage :: Maybe (Value Text)
userAttributeUpdateSettings :: Maybe UserAttributeUpdateSettingsProperty
userPoolAddOns :: Maybe UserPoolAddOnsProperty
userPoolName :: Maybe (Value Text)
userPoolTier :: Maybe (Value Text)
usernameAttributes :: Maybe (ValueList Text)
usernameConfiguration :: Maybe UsernameConfigurationProperty
verificationMessageTemplate :: Maybe VerificationMessageTemplateProperty
webAuthnRelyingPartyID :: Maybe (Value Text)
webAuthnUserVerification :: Maybe (Value Text)
haddock_workaround_ :: ()
accountRecoverySetting :: Maybe AccountRecoverySettingProperty
adminCreateUserConfig :: Maybe AdminCreateUserConfigProperty
aliasAttributes :: Maybe (ValueList Text)
autoVerifiedAttributes :: Maybe (ValueList Text)
deletionProtection :: Maybe (Value Text)
deviceConfiguration :: Maybe DeviceConfigurationProperty
emailAuthenticationMessage :: Maybe (Value Text)
emailAuthenticationSubject :: Maybe (Value Text)
emailConfiguration :: Maybe EmailConfigurationProperty
emailVerificationMessage :: Maybe (Value Text)
emailVerificationSubject :: Maybe (Value Text)
enabledMfas :: Maybe (ValueList Text)
lambdaConfig :: Maybe LambdaConfigProperty
mfaConfiguration :: Maybe (Value Text)
policies :: Maybe PoliciesProperty
schema :: Maybe [SchemaAttributeProperty]
smsAuthenticationMessage :: Maybe (Value Text)
smsConfiguration :: Maybe SmsConfigurationProperty
smsVerificationMessage :: Maybe (Value Text)
userAttributeUpdateSettings :: Maybe UserAttributeUpdateSettingsProperty
userPoolAddOns :: Maybe UserPoolAddOnsProperty
userPoolName :: Maybe (Value Text)
userPoolTier :: Maybe (Value Text)
usernameAttributes :: Maybe (ValueList Text)
usernameConfiguration :: Maybe UsernameConfigurationProperty
verificationMessageTemplate :: Maybe VerificationMessageTemplateProperty
webAuthnRelyingPartyID :: Maybe (Value Text)
webAuthnUserVerification :: Maybe (Value Text)
..}
instance Property "UserPoolTier" UserPool where
type PropertyType "UserPoolTier" UserPool = Value Prelude.Text
set :: PropertyType "UserPoolTier" UserPool -> UserPool -> UserPool
set PropertyType "UserPoolTier" UserPool
newValue UserPool {Maybe [SchemaAttributeProperty]
Maybe (Map Text (Value Text))
Maybe (ValueList Text)
Maybe (Value Text)
Maybe DeviceConfigurationProperty
Maybe EmailConfigurationProperty
Maybe AdminCreateUserConfigProperty
Maybe LambdaConfigProperty
Maybe AccountRecoverySettingProperty
Maybe PoliciesProperty
Maybe SmsConfigurationProperty
Maybe UserAttributeUpdateSettingsProperty
Maybe UserPoolAddOnsProperty
Maybe UsernameConfigurationProperty
Maybe VerificationMessageTemplateProperty
()
haddock_workaround_ :: UserPool -> ()
accountRecoverySetting :: UserPool -> Maybe AccountRecoverySettingProperty
adminCreateUserConfig :: UserPool -> Maybe AdminCreateUserConfigProperty
aliasAttributes :: UserPool -> Maybe (ValueList Text)
autoVerifiedAttributes :: UserPool -> Maybe (ValueList Text)
deletionProtection :: UserPool -> Maybe (Value Text)
deviceConfiguration :: UserPool -> Maybe DeviceConfigurationProperty
emailAuthenticationMessage :: UserPool -> Maybe (Value Text)
emailAuthenticationSubject :: UserPool -> Maybe (Value Text)
emailConfiguration :: UserPool -> Maybe EmailConfigurationProperty
emailVerificationMessage :: UserPool -> Maybe (Value Text)
emailVerificationSubject :: UserPool -> Maybe (Value Text)
enabledMfas :: UserPool -> Maybe (ValueList Text)
lambdaConfig :: UserPool -> Maybe LambdaConfigProperty
mfaConfiguration :: UserPool -> Maybe (Value Text)
policies :: UserPool -> Maybe PoliciesProperty
schema :: UserPool -> Maybe [SchemaAttributeProperty]
smsAuthenticationMessage :: UserPool -> Maybe (Value Text)
smsConfiguration :: UserPool -> Maybe SmsConfigurationProperty
smsVerificationMessage :: UserPool -> Maybe (Value Text)
userAttributeUpdateSettings :: UserPool -> Maybe UserAttributeUpdateSettingsProperty
userPoolAddOns :: UserPool -> Maybe UserPoolAddOnsProperty
userPoolName :: UserPool -> Maybe (Value Text)
userPoolTags :: UserPool -> Maybe (Map Text (Value Text))
userPoolTier :: UserPool -> Maybe (Value Text)
usernameAttributes :: UserPool -> Maybe (ValueList Text)
usernameConfiguration :: UserPool -> Maybe UsernameConfigurationProperty
verificationMessageTemplate :: UserPool -> Maybe VerificationMessageTemplateProperty
webAuthnRelyingPartyID :: UserPool -> Maybe (Value Text)
webAuthnUserVerification :: UserPool -> Maybe (Value Text)
haddock_workaround_ :: ()
accountRecoverySetting :: Maybe AccountRecoverySettingProperty
adminCreateUserConfig :: Maybe AdminCreateUserConfigProperty
aliasAttributes :: Maybe (ValueList Text)
autoVerifiedAttributes :: Maybe (ValueList Text)
deletionProtection :: Maybe (Value Text)
deviceConfiguration :: Maybe DeviceConfigurationProperty
emailAuthenticationMessage :: Maybe (Value Text)
emailAuthenticationSubject :: Maybe (Value Text)
emailConfiguration :: Maybe EmailConfigurationProperty
emailVerificationMessage :: Maybe (Value Text)
emailVerificationSubject :: Maybe (Value Text)
enabledMfas :: Maybe (ValueList Text)
lambdaConfig :: Maybe LambdaConfigProperty
mfaConfiguration :: Maybe (Value Text)
policies :: Maybe PoliciesProperty
schema :: Maybe [SchemaAttributeProperty]
smsAuthenticationMessage :: Maybe (Value Text)
smsConfiguration :: Maybe SmsConfigurationProperty
smsVerificationMessage :: Maybe (Value Text)
userAttributeUpdateSettings :: Maybe UserAttributeUpdateSettingsProperty
userPoolAddOns :: Maybe UserPoolAddOnsProperty
userPoolName :: Maybe (Value Text)
userPoolTags :: Maybe (Map Text (Value Text))
userPoolTier :: Maybe (Value Text)
usernameAttributes :: Maybe (ValueList Text)
usernameConfiguration :: Maybe UsernameConfigurationProperty
verificationMessageTemplate :: Maybe VerificationMessageTemplateProperty
webAuthnRelyingPartyID :: Maybe (Value Text)
webAuthnUserVerification :: Maybe (Value Text)
..}
= UserPool {userPoolTier :: Maybe (Value Text)
userPoolTier = Value Text -> Maybe (Value Text)
forall a. a -> Maybe a
forall (f :: * -> *) a. Applicative f => a -> f a
Prelude.pure PropertyType "UserPoolTier" UserPool
Value Text
newValue, Maybe [SchemaAttributeProperty]
Maybe (Map Text (Value Text))
Maybe (ValueList Text)
Maybe (Value Text)
Maybe DeviceConfigurationProperty
Maybe EmailConfigurationProperty
Maybe AdminCreateUserConfigProperty
Maybe LambdaConfigProperty
Maybe AccountRecoverySettingProperty
Maybe PoliciesProperty
Maybe SmsConfigurationProperty
Maybe UserAttributeUpdateSettingsProperty
Maybe UserPoolAddOnsProperty
Maybe UsernameConfigurationProperty
Maybe VerificationMessageTemplateProperty
()
haddock_workaround_ :: ()
accountRecoverySetting :: Maybe AccountRecoverySettingProperty
adminCreateUserConfig :: Maybe AdminCreateUserConfigProperty
aliasAttributes :: Maybe (ValueList Text)
autoVerifiedAttributes :: Maybe (ValueList Text)
deletionProtection :: Maybe (Value Text)
deviceConfiguration :: Maybe DeviceConfigurationProperty
emailAuthenticationMessage :: Maybe (Value Text)
emailAuthenticationSubject :: Maybe (Value Text)
emailConfiguration :: Maybe EmailConfigurationProperty
emailVerificationMessage :: Maybe (Value Text)
emailVerificationSubject :: Maybe (Value Text)
enabledMfas :: Maybe (ValueList Text)
lambdaConfig :: Maybe LambdaConfigProperty
mfaConfiguration :: Maybe (Value Text)
policies :: Maybe PoliciesProperty
schema :: Maybe [SchemaAttributeProperty]
smsAuthenticationMessage :: Maybe (Value Text)
smsConfiguration :: Maybe SmsConfigurationProperty
smsVerificationMessage :: Maybe (Value Text)
userAttributeUpdateSettings :: Maybe UserAttributeUpdateSettingsProperty
userPoolAddOns :: Maybe UserPoolAddOnsProperty
userPoolName :: Maybe (Value Text)
userPoolTags :: Maybe (Map Text (Value Text))
usernameAttributes :: Maybe (ValueList Text)
usernameConfiguration :: Maybe UsernameConfigurationProperty
verificationMessageTemplate :: Maybe VerificationMessageTemplateProperty
webAuthnRelyingPartyID :: Maybe (Value Text)
webAuthnUserVerification :: Maybe (Value Text)
haddock_workaround_ :: ()
accountRecoverySetting :: Maybe AccountRecoverySettingProperty
adminCreateUserConfig :: Maybe AdminCreateUserConfigProperty
aliasAttributes :: Maybe (ValueList Text)
autoVerifiedAttributes :: Maybe (ValueList Text)
deletionProtection :: Maybe (Value Text)
deviceConfiguration :: Maybe DeviceConfigurationProperty
emailAuthenticationMessage :: Maybe (Value Text)
emailAuthenticationSubject :: Maybe (Value Text)
emailConfiguration :: Maybe EmailConfigurationProperty
emailVerificationMessage :: Maybe (Value Text)
emailVerificationSubject :: Maybe (Value Text)
enabledMfas :: Maybe (ValueList Text)
lambdaConfig :: Maybe LambdaConfigProperty
mfaConfiguration :: Maybe (Value Text)
policies :: Maybe PoliciesProperty
schema :: Maybe [SchemaAttributeProperty]
smsAuthenticationMessage :: Maybe (Value Text)
smsConfiguration :: Maybe SmsConfigurationProperty
smsVerificationMessage :: Maybe (Value Text)
userAttributeUpdateSettings :: Maybe UserAttributeUpdateSettingsProperty
userPoolAddOns :: Maybe UserPoolAddOnsProperty
userPoolName :: Maybe (Value Text)
userPoolTags :: Maybe (Map Text (Value Text))
usernameAttributes :: Maybe (ValueList Text)
usernameConfiguration :: Maybe UsernameConfigurationProperty
verificationMessageTemplate :: Maybe VerificationMessageTemplateProperty
webAuthnRelyingPartyID :: Maybe (Value Text)
webAuthnUserVerification :: Maybe (Value Text)
..}
instance Property "UsernameAttributes" UserPool where
type PropertyType "UsernameAttributes" UserPool = ValueList Prelude.Text
set :: PropertyType "UsernameAttributes" UserPool -> UserPool -> UserPool
set PropertyType "UsernameAttributes" UserPool
newValue UserPool {Maybe [SchemaAttributeProperty]
Maybe (Map Text (Value Text))
Maybe (ValueList Text)
Maybe (Value Text)
Maybe DeviceConfigurationProperty
Maybe EmailConfigurationProperty
Maybe AdminCreateUserConfigProperty
Maybe LambdaConfigProperty
Maybe AccountRecoverySettingProperty
Maybe PoliciesProperty
Maybe SmsConfigurationProperty
Maybe UserAttributeUpdateSettingsProperty
Maybe UserPoolAddOnsProperty
Maybe UsernameConfigurationProperty
Maybe VerificationMessageTemplateProperty
()
haddock_workaround_ :: UserPool -> ()
accountRecoverySetting :: UserPool -> Maybe AccountRecoverySettingProperty
adminCreateUserConfig :: UserPool -> Maybe AdminCreateUserConfigProperty
aliasAttributes :: UserPool -> Maybe (ValueList Text)
autoVerifiedAttributes :: UserPool -> Maybe (ValueList Text)
deletionProtection :: UserPool -> Maybe (Value Text)
deviceConfiguration :: UserPool -> Maybe DeviceConfigurationProperty
emailAuthenticationMessage :: UserPool -> Maybe (Value Text)
emailAuthenticationSubject :: UserPool -> Maybe (Value Text)
emailConfiguration :: UserPool -> Maybe EmailConfigurationProperty
emailVerificationMessage :: UserPool -> Maybe (Value Text)
emailVerificationSubject :: UserPool -> Maybe (Value Text)
enabledMfas :: UserPool -> Maybe (ValueList Text)
lambdaConfig :: UserPool -> Maybe LambdaConfigProperty
mfaConfiguration :: UserPool -> Maybe (Value Text)
policies :: UserPool -> Maybe PoliciesProperty
schema :: UserPool -> Maybe [SchemaAttributeProperty]
smsAuthenticationMessage :: UserPool -> Maybe (Value Text)
smsConfiguration :: UserPool -> Maybe SmsConfigurationProperty
smsVerificationMessage :: UserPool -> Maybe (Value Text)
userAttributeUpdateSettings :: UserPool -> Maybe UserAttributeUpdateSettingsProperty
userPoolAddOns :: UserPool -> Maybe UserPoolAddOnsProperty
userPoolName :: UserPool -> Maybe (Value Text)
userPoolTags :: UserPool -> Maybe (Map Text (Value Text))
userPoolTier :: UserPool -> Maybe (Value Text)
usernameAttributes :: UserPool -> Maybe (ValueList Text)
usernameConfiguration :: UserPool -> Maybe UsernameConfigurationProperty
verificationMessageTemplate :: UserPool -> Maybe VerificationMessageTemplateProperty
webAuthnRelyingPartyID :: UserPool -> Maybe (Value Text)
webAuthnUserVerification :: UserPool -> Maybe (Value Text)
haddock_workaround_ :: ()
accountRecoverySetting :: Maybe AccountRecoverySettingProperty
adminCreateUserConfig :: Maybe AdminCreateUserConfigProperty
aliasAttributes :: Maybe (ValueList Text)
autoVerifiedAttributes :: Maybe (ValueList Text)
deletionProtection :: Maybe (Value Text)
deviceConfiguration :: Maybe DeviceConfigurationProperty
emailAuthenticationMessage :: Maybe (Value Text)
emailAuthenticationSubject :: Maybe (Value Text)
emailConfiguration :: Maybe EmailConfigurationProperty
emailVerificationMessage :: Maybe (Value Text)
emailVerificationSubject :: Maybe (Value Text)
enabledMfas :: Maybe (ValueList Text)
lambdaConfig :: Maybe LambdaConfigProperty
mfaConfiguration :: Maybe (Value Text)
policies :: Maybe PoliciesProperty
schema :: Maybe [SchemaAttributeProperty]
smsAuthenticationMessage :: Maybe (Value Text)
smsConfiguration :: Maybe SmsConfigurationProperty
smsVerificationMessage :: Maybe (Value Text)
userAttributeUpdateSettings :: Maybe UserAttributeUpdateSettingsProperty
userPoolAddOns :: Maybe UserPoolAddOnsProperty
userPoolName :: Maybe (Value Text)
userPoolTags :: Maybe (Map Text (Value Text))
userPoolTier :: Maybe (Value Text)
usernameAttributes :: Maybe (ValueList Text)
usernameConfiguration :: Maybe UsernameConfigurationProperty
verificationMessageTemplate :: Maybe VerificationMessageTemplateProperty
webAuthnRelyingPartyID :: Maybe (Value Text)
webAuthnUserVerification :: Maybe (Value Text)
..}
= UserPool {usernameAttributes :: Maybe (ValueList Text)
usernameAttributes = ValueList Text -> Maybe (ValueList Text)
forall a. a -> Maybe a
forall (f :: * -> *) a. Applicative f => a -> f a
Prelude.pure PropertyType "UsernameAttributes" UserPool
ValueList Text
newValue, Maybe [SchemaAttributeProperty]
Maybe (Map Text (Value Text))
Maybe (ValueList Text)
Maybe (Value Text)
Maybe DeviceConfigurationProperty
Maybe EmailConfigurationProperty
Maybe AdminCreateUserConfigProperty
Maybe LambdaConfigProperty
Maybe AccountRecoverySettingProperty
Maybe PoliciesProperty
Maybe SmsConfigurationProperty
Maybe UserAttributeUpdateSettingsProperty
Maybe UserPoolAddOnsProperty
Maybe UsernameConfigurationProperty
Maybe VerificationMessageTemplateProperty
()
haddock_workaround_ :: ()
accountRecoverySetting :: Maybe AccountRecoverySettingProperty
adminCreateUserConfig :: Maybe AdminCreateUserConfigProperty
aliasAttributes :: Maybe (ValueList Text)
autoVerifiedAttributes :: Maybe (ValueList Text)
deletionProtection :: Maybe (Value Text)
deviceConfiguration :: Maybe DeviceConfigurationProperty
emailAuthenticationMessage :: Maybe (Value Text)
emailAuthenticationSubject :: Maybe (Value Text)
emailConfiguration :: Maybe EmailConfigurationProperty
emailVerificationMessage :: Maybe (Value Text)
emailVerificationSubject :: Maybe (Value Text)
enabledMfas :: Maybe (ValueList Text)
lambdaConfig :: Maybe LambdaConfigProperty
mfaConfiguration :: Maybe (Value Text)
policies :: Maybe PoliciesProperty
schema :: Maybe [SchemaAttributeProperty]
smsAuthenticationMessage :: Maybe (Value Text)
smsConfiguration :: Maybe SmsConfigurationProperty
smsVerificationMessage :: Maybe (Value Text)
userAttributeUpdateSettings :: Maybe UserAttributeUpdateSettingsProperty
userPoolAddOns :: Maybe UserPoolAddOnsProperty
userPoolName :: Maybe (Value Text)
userPoolTags :: Maybe (Map Text (Value Text))
userPoolTier :: Maybe (Value Text)
usernameConfiguration :: Maybe UsernameConfigurationProperty
verificationMessageTemplate :: Maybe VerificationMessageTemplateProperty
webAuthnRelyingPartyID :: Maybe (Value Text)
webAuthnUserVerification :: Maybe (Value Text)
haddock_workaround_ :: ()
accountRecoverySetting :: Maybe AccountRecoverySettingProperty
adminCreateUserConfig :: Maybe AdminCreateUserConfigProperty
aliasAttributes :: Maybe (ValueList Text)
autoVerifiedAttributes :: Maybe (ValueList Text)
deletionProtection :: Maybe (Value Text)
deviceConfiguration :: Maybe DeviceConfigurationProperty
emailAuthenticationMessage :: Maybe (Value Text)
emailAuthenticationSubject :: Maybe (Value Text)
emailConfiguration :: Maybe EmailConfigurationProperty
emailVerificationMessage :: Maybe (Value Text)
emailVerificationSubject :: Maybe (Value Text)
enabledMfas :: Maybe (ValueList Text)
lambdaConfig :: Maybe LambdaConfigProperty
mfaConfiguration :: Maybe (Value Text)
policies :: Maybe PoliciesProperty
schema :: Maybe [SchemaAttributeProperty]
smsAuthenticationMessage :: Maybe (Value Text)
smsConfiguration :: Maybe SmsConfigurationProperty
smsVerificationMessage :: Maybe (Value Text)
userAttributeUpdateSettings :: Maybe UserAttributeUpdateSettingsProperty
userPoolAddOns :: Maybe UserPoolAddOnsProperty
userPoolName :: Maybe (Value Text)
userPoolTags :: Maybe (Map Text (Value Text))
userPoolTier :: Maybe (Value Text)
usernameConfiguration :: Maybe UsernameConfigurationProperty
verificationMessageTemplate :: Maybe VerificationMessageTemplateProperty
webAuthnRelyingPartyID :: Maybe (Value Text)
webAuthnUserVerification :: Maybe (Value Text)
..}
instance Property "UsernameConfiguration" UserPool where
type PropertyType "UsernameConfiguration" UserPool = UsernameConfigurationProperty
set :: PropertyType "UsernameConfiguration" UserPool
-> UserPool -> UserPool
set PropertyType "UsernameConfiguration" UserPool
newValue UserPool {Maybe [SchemaAttributeProperty]
Maybe (Map Text (Value Text))
Maybe (ValueList Text)
Maybe (Value Text)
Maybe DeviceConfigurationProperty
Maybe EmailConfigurationProperty
Maybe AdminCreateUserConfigProperty
Maybe LambdaConfigProperty
Maybe AccountRecoverySettingProperty
Maybe PoliciesProperty
Maybe SmsConfigurationProperty
Maybe UserAttributeUpdateSettingsProperty
Maybe UserPoolAddOnsProperty
Maybe UsernameConfigurationProperty
Maybe VerificationMessageTemplateProperty
()
haddock_workaround_ :: UserPool -> ()
accountRecoverySetting :: UserPool -> Maybe AccountRecoverySettingProperty
adminCreateUserConfig :: UserPool -> Maybe AdminCreateUserConfigProperty
aliasAttributes :: UserPool -> Maybe (ValueList Text)
autoVerifiedAttributes :: UserPool -> Maybe (ValueList Text)
deletionProtection :: UserPool -> Maybe (Value Text)
deviceConfiguration :: UserPool -> Maybe DeviceConfigurationProperty
emailAuthenticationMessage :: UserPool -> Maybe (Value Text)
emailAuthenticationSubject :: UserPool -> Maybe (Value Text)
emailConfiguration :: UserPool -> Maybe EmailConfigurationProperty
emailVerificationMessage :: UserPool -> Maybe (Value Text)
emailVerificationSubject :: UserPool -> Maybe (Value Text)
enabledMfas :: UserPool -> Maybe (ValueList Text)
lambdaConfig :: UserPool -> Maybe LambdaConfigProperty
mfaConfiguration :: UserPool -> Maybe (Value Text)
policies :: UserPool -> Maybe PoliciesProperty
schema :: UserPool -> Maybe [SchemaAttributeProperty]
smsAuthenticationMessage :: UserPool -> Maybe (Value Text)
smsConfiguration :: UserPool -> Maybe SmsConfigurationProperty
smsVerificationMessage :: UserPool -> Maybe (Value Text)
userAttributeUpdateSettings :: UserPool -> Maybe UserAttributeUpdateSettingsProperty
userPoolAddOns :: UserPool -> Maybe UserPoolAddOnsProperty
userPoolName :: UserPool -> Maybe (Value Text)
userPoolTags :: UserPool -> Maybe (Map Text (Value Text))
userPoolTier :: UserPool -> Maybe (Value Text)
usernameAttributes :: UserPool -> Maybe (ValueList Text)
usernameConfiguration :: UserPool -> Maybe UsernameConfigurationProperty
verificationMessageTemplate :: UserPool -> Maybe VerificationMessageTemplateProperty
webAuthnRelyingPartyID :: UserPool -> Maybe (Value Text)
webAuthnUserVerification :: UserPool -> Maybe (Value Text)
haddock_workaround_ :: ()
accountRecoverySetting :: Maybe AccountRecoverySettingProperty
adminCreateUserConfig :: Maybe AdminCreateUserConfigProperty
aliasAttributes :: Maybe (ValueList Text)
autoVerifiedAttributes :: Maybe (ValueList Text)
deletionProtection :: Maybe (Value Text)
deviceConfiguration :: Maybe DeviceConfigurationProperty
emailAuthenticationMessage :: Maybe (Value Text)
emailAuthenticationSubject :: Maybe (Value Text)
emailConfiguration :: Maybe EmailConfigurationProperty
emailVerificationMessage :: Maybe (Value Text)
emailVerificationSubject :: Maybe (Value Text)
enabledMfas :: Maybe (ValueList Text)
lambdaConfig :: Maybe LambdaConfigProperty
mfaConfiguration :: Maybe (Value Text)
policies :: Maybe PoliciesProperty
schema :: Maybe [SchemaAttributeProperty]
smsAuthenticationMessage :: Maybe (Value Text)
smsConfiguration :: Maybe SmsConfigurationProperty
smsVerificationMessage :: Maybe (Value Text)
userAttributeUpdateSettings :: Maybe UserAttributeUpdateSettingsProperty
userPoolAddOns :: Maybe UserPoolAddOnsProperty
userPoolName :: Maybe (Value Text)
userPoolTags :: Maybe (Map Text (Value Text))
userPoolTier :: Maybe (Value Text)
usernameAttributes :: Maybe (ValueList Text)
usernameConfiguration :: Maybe UsernameConfigurationProperty
verificationMessageTemplate :: Maybe VerificationMessageTemplateProperty
webAuthnRelyingPartyID :: Maybe (Value Text)
webAuthnUserVerification :: Maybe (Value Text)
..}
= UserPool {usernameConfiguration :: Maybe UsernameConfigurationProperty
usernameConfiguration = UsernameConfigurationProperty
-> Maybe UsernameConfigurationProperty
forall a. a -> Maybe a
forall (f :: * -> *) a. Applicative f => a -> f a
Prelude.pure PropertyType "UsernameConfiguration" UserPool
UsernameConfigurationProperty
newValue, Maybe [SchemaAttributeProperty]
Maybe (Map Text (Value Text))
Maybe (ValueList Text)
Maybe (Value Text)
Maybe DeviceConfigurationProperty
Maybe EmailConfigurationProperty
Maybe AdminCreateUserConfigProperty
Maybe LambdaConfigProperty
Maybe AccountRecoverySettingProperty
Maybe PoliciesProperty
Maybe SmsConfigurationProperty
Maybe UserAttributeUpdateSettingsProperty
Maybe UserPoolAddOnsProperty
Maybe VerificationMessageTemplateProperty
()
haddock_workaround_ :: ()
accountRecoverySetting :: Maybe AccountRecoverySettingProperty
adminCreateUserConfig :: Maybe AdminCreateUserConfigProperty
aliasAttributes :: Maybe (ValueList Text)
autoVerifiedAttributes :: Maybe (ValueList Text)
deletionProtection :: Maybe (Value Text)
deviceConfiguration :: Maybe DeviceConfigurationProperty
emailAuthenticationMessage :: Maybe (Value Text)
emailAuthenticationSubject :: Maybe (Value Text)
emailConfiguration :: Maybe EmailConfigurationProperty
emailVerificationMessage :: Maybe (Value Text)
emailVerificationSubject :: Maybe (Value Text)
enabledMfas :: Maybe (ValueList Text)
lambdaConfig :: Maybe LambdaConfigProperty
mfaConfiguration :: Maybe (Value Text)
policies :: Maybe PoliciesProperty
schema :: Maybe [SchemaAttributeProperty]
smsAuthenticationMessage :: Maybe (Value Text)
smsConfiguration :: Maybe SmsConfigurationProperty
smsVerificationMessage :: Maybe (Value Text)
userAttributeUpdateSettings :: Maybe UserAttributeUpdateSettingsProperty
userPoolAddOns :: Maybe UserPoolAddOnsProperty
userPoolName :: Maybe (Value Text)
userPoolTags :: Maybe (Map Text (Value Text))
userPoolTier :: Maybe (Value Text)
usernameAttributes :: Maybe (ValueList Text)
verificationMessageTemplate :: Maybe VerificationMessageTemplateProperty
webAuthnRelyingPartyID :: Maybe (Value Text)
webAuthnUserVerification :: Maybe (Value Text)
haddock_workaround_ :: ()
accountRecoverySetting :: Maybe AccountRecoverySettingProperty
adminCreateUserConfig :: Maybe AdminCreateUserConfigProperty
aliasAttributes :: Maybe (ValueList Text)
autoVerifiedAttributes :: Maybe (ValueList Text)
deletionProtection :: Maybe (Value Text)
deviceConfiguration :: Maybe DeviceConfigurationProperty
emailAuthenticationMessage :: Maybe (Value Text)
emailAuthenticationSubject :: Maybe (Value Text)
emailConfiguration :: Maybe EmailConfigurationProperty
emailVerificationMessage :: Maybe (Value Text)
emailVerificationSubject :: Maybe (Value Text)
enabledMfas :: Maybe (ValueList Text)
lambdaConfig :: Maybe LambdaConfigProperty
mfaConfiguration :: Maybe (Value Text)
policies :: Maybe PoliciesProperty
schema :: Maybe [SchemaAttributeProperty]
smsAuthenticationMessage :: Maybe (Value Text)
smsConfiguration :: Maybe SmsConfigurationProperty
smsVerificationMessage :: Maybe (Value Text)
userAttributeUpdateSettings :: Maybe UserAttributeUpdateSettingsProperty
userPoolAddOns :: Maybe UserPoolAddOnsProperty
userPoolName :: Maybe (Value Text)
userPoolTags :: Maybe (Map Text (Value Text))
userPoolTier :: Maybe (Value Text)
usernameAttributes :: Maybe (ValueList Text)
verificationMessageTemplate :: Maybe VerificationMessageTemplateProperty
webAuthnRelyingPartyID :: Maybe (Value Text)
webAuthnUserVerification :: Maybe (Value Text)
..}
instance Property "VerificationMessageTemplate" UserPool where
type PropertyType "VerificationMessageTemplate" UserPool = VerificationMessageTemplateProperty
set :: PropertyType "VerificationMessageTemplate" UserPool
-> UserPool -> UserPool
set PropertyType "VerificationMessageTemplate" UserPool
newValue UserPool {Maybe [SchemaAttributeProperty]
Maybe (Map Text (Value Text))
Maybe (ValueList Text)
Maybe (Value Text)
Maybe DeviceConfigurationProperty
Maybe EmailConfigurationProperty
Maybe AdminCreateUserConfigProperty
Maybe LambdaConfigProperty
Maybe AccountRecoverySettingProperty
Maybe PoliciesProperty
Maybe SmsConfigurationProperty
Maybe UserAttributeUpdateSettingsProperty
Maybe UserPoolAddOnsProperty
Maybe UsernameConfigurationProperty
Maybe VerificationMessageTemplateProperty
()
haddock_workaround_ :: UserPool -> ()
accountRecoverySetting :: UserPool -> Maybe AccountRecoverySettingProperty
adminCreateUserConfig :: UserPool -> Maybe AdminCreateUserConfigProperty
aliasAttributes :: UserPool -> Maybe (ValueList Text)
autoVerifiedAttributes :: UserPool -> Maybe (ValueList Text)
deletionProtection :: UserPool -> Maybe (Value Text)
deviceConfiguration :: UserPool -> Maybe DeviceConfigurationProperty
emailAuthenticationMessage :: UserPool -> Maybe (Value Text)
emailAuthenticationSubject :: UserPool -> Maybe (Value Text)
emailConfiguration :: UserPool -> Maybe EmailConfigurationProperty
emailVerificationMessage :: UserPool -> Maybe (Value Text)
emailVerificationSubject :: UserPool -> Maybe (Value Text)
enabledMfas :: UserPool -> Maybe (ValueList Text)
lambdaConfig :: UserPool -> Maybe LambdaConfigProperty
mfaConfiguration :: UserPool -> Maybe (Value Text)
policies :: UserPool -> Maybe PoliciesProperty
schema :: UserPool -> Maybe [SchemaAttributeProperty]
smsAuthenticationMessage :: UserPool -> Maybe (Value Text)
smsConfiguration :: UserPool -> Maybe SmsConfigurationProperty
smsVerificationMessage :: UserPool -> Maybe (Value Text)
userAttributeUpdateSettings :: UserPool -> Maybe UserAttributeUpdateSettingsProperty
userPoolAddOns :: UserPool -> Maybe UserPoolAddOnsProperty
userPoolName :: UserPool -> Maybe (Value Text)
userPoolTags :: UserPool -> Maybe (Map Text (Value Text))
userPoolTier :: UserPool -> Maybe (Value Text)
usernameAttributes :: UserPool -> Maybe (ValueList Text)
usernameConfiguration :: UserPool -> Maybe UsernameConfigurationProperty
verificationMessageTemplate :: UserPool -> Maybe VerificationMessageTemplateProperty
webAuthnRelyingPartyID :: UserPool -> Maybe (Value Text)
webAuthnUserVerification :: UserPool -> Maybe (Value Text)
haddock_workaround_ :: ()
accountRecoverySetting :: Maybe AccountRecoverySettingProperty
adminCreateUserConfig :: Maybe AdminCreateUserConfigProperty
aliasAttributes :: Maybe (ValueList Text)
autoVerifiedAttributes :: Maybe (ValueList Text)
deletionProtection :: Maybe (Value Text)
deviceConfiguration :: Maybe DeviceConfigurationProperty
emailAuthenticationMessage :: Maybe (Value Text)
emailAuthenticationSubject :: Maybe (Value Text)
emailConfiguration :: Maybe EmailConfigurationProperty
emailVerificationMessage :: Maybe (Value Text)
emailVerificationSubject :: Maybe (Value Text)
enabledMfas :: Maybe (ValueList Text)
lambdaConfig :: Maybe LambdaConfigProperty
mfaConfiguration :: Maybe (Value Text)
policies :: Maybe PoliciesProperty
schema :: Maybe [SchemaAttributeProperty]
smsAuthenticationMessage :: Maybe (Value Text)
smsConfiguration :: Maybe SmsConfigurationProperty
smsVerificationMessage :: Maybe (Value Text)
userAttributeUpdateSettings :: Maybe UserAttributeUpdateSettingsProperty
userPoolAddOns :: Maybe UserPoolAddOnsProperty
userPoolName :: Maybe (Value Text)
userPoolTags :: Maybe (Map Text (Value Text))
userPoolTier :: Maybe (Value Text)
usernameAttributes :: Maybe (ValueList Text)
usernameConfiguration :: Maybe UsernameConfigurationProperty
verificationMessageTemplate :: Maybe VerificationMessageTemplateProperty
webAuthnRelyingPartyID :: Maybe (Value Text)
webAuthnUserVerification :: Maybe (Value Text)
..}
= UserPool
{verificationMessageTemplate :: Maybe VerificationMessageTemplateProperty
verificationMessageTemplate = VerificationMessageTemplateProperty
-> Maybe VerificationMessageTemplateProperty
forall a. a -> Maybe a
forall (f :: * -> *) a. Applicative f => a -> f a
Prelude.pure PropertyType "VerificationMessageTemplate" UserPool
VerificationMessageTemplateProperty
newValue, Maybe [SchemaAttributeProperty]
Maybe (Map Text (Value Text))
Maybe (ValueList Text)
Maybe (Value Text)
Maybe DeviceConfigurationProperty
Maybe EmailConfigurationProperty
Maybe AdminCreateUserConfigProperty
Maybe LambdaConfigProperty
Maybe AccountRecoverySettingProperty
Maybe PoliciesProperty
Maybe SmsConfigurationProperty
Maybe UserAttributeUpdateSettingsProperty
Maybe UserPoolAddOnsProperty
Maybe UsernameConfigurationProperty
()
haddock_workaround_ :: ()
accountRecoverySetting :: Maybe AccountRecoverySettingProperty
adminCreateUserConfig :: Maybe AdminCreateUserConfigProperty
aliasAttributes :: Maybe (ValueList Text)
autoVerifiedAttributes :: Maybe (ValueList Text)
deletionProtection :: Maybe (Value Text)
deviceConfiguration :: Maybe DeviceConfigurationProperty
emailAuthenticationMessage :: Maybe (Value Text)
emailAuthenticationSubject :: Maybe (Value Text)
emailConfiguration :: Maybe EmailConfigurationProperty
emailVerificationMessage :: Maybe (Value Text)
emailVerificationSubject :: Maybe (Value Text)
enabledMfas :: Maybe (ValueList Text)
lambdaConfig :: Maybe LambdaConfigProperty
mfaConfiguration :: Maybe (Value Text)
policies :: Maybe PoliciesProperty
schema :: Maybe [SchemaAttributeProperty]
smsAuthenticationMessage :: Maybe (Value Text)
smsConfiguration :: Maybe SmsConfigurationProperty
smsVerificationMessage :: Maybe (Value Text)
userAttributeUpdateSettings :: Maybe UserAttributeUpdateSettingsProperty
userPoolAddOns :: Maybe UserPoolAddOnsProperty
userPoolName :: Maybe (Value Text)
userPoolTags :: Maybe (Map Text (Value Text))
userPoolTier :: Maybe (Value Text)
usernameAttributes :: Maybe (ValueList Text)
usernameConfiguration :: Maybe UsernameConfigurationProperty
webAuthnRelyingPartyID :: Maybe (Value Text)
webAuthnUserVerification :: Maybe (Value Text)
haddock_workaround_ :: ()
accountRecoverySetting :: Maybe AccountRecoverySettingProperty
adminCreateUserConfig :: Maybe AdminCreateUserConfigProperty
aliasAttributes :: Maybe (ValueList Text)
autoVerifiedAttributes :: Maybe (ValueList Text)
deletionProtection :: Maybe (Value Text)
deviceConfiguration :: Maybe DeviceConfigurationProperty
emailAuthenticationMessage :: Maybe (Value Text)
emailAuthenticationSubject :: Maybe (Value Text)
emailConfiguration :: Maybe EmailConfigurationProperty
emailVerificationMessage :: Maybe (Value Text)
emailVerificationSubject :: Maybe (Value Text)
enabledMfas :: Maybe (ValueList Text)
lambdaConfig :: Maybe LambdaConfigProperty
mfaConfiguration :: Maybe (Value Text)
policies :: Maybe PoliciesProperty
schema :: Maybe [SchemaAttributeProperty]
smsAuthenticationMessage :: Maybe (Value Text)
smsConfiguration :: Maybe SmsConfigurationProperty
smsVerificationMessage :: Maybe (Value Text)
userAttributeUpdateSettings :: Maybe UserAttributeUpdateSettingsProperty
userPoolAddOns :: Maybe UserPoolAddOnsProperty
userPoolName :: Maybe (Value Text)
userPoolTags :: Maybe (Map Text (Value Text))
userPoolTier :: Maybe (Value Text)
usernameAttributes :: Maybe (ValueList Text)
usernameConfiguration :: Maybe UsernameConfigurationProperty
webAuthnRelyingPartyID :: Maybe (Value Text)
webAuthnUserVerification :: Maybe (Value Text)
..}
instance Property "WebAuthnRelyingPartyID" UserPool where
type PropertyType "WebAuthnRelyingPartyID" UserPool = Value Prelude.Text
set :: PropertyType "WebAuthnRelyingPartyID" UserPool
-> UserPool -> UserPool
set PropertyType "WebAuthnRelyingPartyID" UserPool
newValue UserPool {Maybe [SchemaAttributeProperty]
Maybe (Map Text (Value Text))
Maybe (ValueList Text)
Maybe (Value Text)
Maybe DeviceConfigurationProperty
Maybe EmailConfigurationProperty
Maybe AdminCreateUserConfigProperty
Maybe LambdaConfigProperty
Maybe AccountRecoverySettingProperty
Maybe PoliciesProperty
Maybe SmsConfigurationProperty
Maybe UserAttributeUpdateSettingsProperty
Maybe UserPoolAddOnsProperty
Maybe UsernameConfigurationProperty
Maybe VerificationMessageTemplateProperty
()
haddock_workaround_ :: UserPool -> ()
accountRecoverySetting :: UserPool -> Maybe AccountRecoverySettingProperty
adminCreateUserConfig :: UserPool -> Maybe AdminCreateUserConfigProperty
aliasAttributes :: UserPool -> Maybe (ValueList Text)
autoVerifiedAttributes :: UserPool -> Maybe (ValueList Text)
deletionProtection :: UserPool -> Maybe (Value Text)
deviceConfiguration :: UserPool -> Maybe DeviceConfigurationProperty
emailAuthenticationMessage :: UserPool -> Maybe (Value Text)
emailAuthenticationSubject :: UserPool -> Maybe (Value Text)
emailConfiguration :: UserPool -> Maybe EmailConfigurationProperty
emailVerificationMessage :: UserPool -> Maybe (Value Text)
emailVerificationSubject :: UserPool -> Maybe (Value Text)
enabledMfas :: UserPool -> Maybe (ValueList Text)
lambdaConfig :: UserPool -> Maybe LambdaConfigProperty
mfaConfiguration :: UserPool -> Maybe (Value Text)
policies :: UserPool -> Maybe PoliciesProperty
schema :: UserPool -> Maybe [SchemaAttributeProperty]
smsAuthenticationMessage :: UserPool -> Maybe (Value Text)
smsConfiguration :: UserPool -> Maybe SmsConfigurationProperty
smsVerificationMessage :: UserPool -> Maybe (Value Text)
userAttributeUpdateSettings :: UserPool -> Maybe UserAttributeUpdateSettingsProperty
userPoolAddOns :: UserPool -> Maybe UserPoolAddOnsProperty
userPoolName :: UserPool -> Maybe (Value Text)
userPoolTags :: UserPool -> Maybe (Map Text (Value Text))
userPoolTier :: UserPool -> Maybe (Value Text)
usernameAttributes :: UserPool -> Maybe (ValueList Text)
usernameConfiguration :: UserPool -> Maybe UsernameConfigurationProperty
verificationMessageTemplate :: UserPool -> Maybe VerificationMessageTemplateProperty
webAuthnRelyingPartyID :: UserPool -> Maybe (Value Text)
webAuthnUserVerification :: UserPool -> Maybe (Value Text)
haddock_workaround_ :: ()
accountRecoverySetting :: Maybe AccountRecoverySettingProperty
adminCreateUserConfig :: Maybe AdminCreateUserConfigProperty
aliasAttributes :: Maybe (ValueList Text)
autoVerifiedAttributes :: Maybe (ValueList Text)
deletionProtection :: Maybe (Value Text)
deviceConfiguration :: Maybe DeviceConfigurationProperty
emailAuthenticationMessage :: Maybe (Value Text)
emailAuthenticationSubject :: Maybe (Value Text)
emailConfiguration :: Maybe EmailConfigurationProperty
emailVerificationMessage :: Maybe (Value Text)
emailVerificationSubject :: Maybe (Value Text)
enabledMfas :: Maybe (ValueList Text)
lambdaConfig :: Maybe LambdaConfigProperty
mfaConfiguration :: Maybe (Value Text)
policies :: Maybe PoliciesProperty
schema :: Maybe [SchemaAttributeProperty]
smsAuthenticationMessage :: Maybe (Value Text)
smsConfiguration :: Maybe SmsConfigurationProperty
smsVerificationMessage :: Maybe (Value Text)
userAttributeUpdateSettings :: Maybe UserAttributeUpdateSettingsProperty
userPoolAddOns :: Maybe UserPoolAddOnsProperty
userPoolName :: Maybe (Value Text)
userPoolTags :: Maybe (Map Text (Value Text))
userPoolTier :: Maybe (Value Text)
usernameAttributes :: Maybe (ValueList Text)
usernameConfiguration :: Maybe UsernameConfigurationProperty
verificationMessageTemplate :: Maybe VerificationMessageTemplateProperty
webAuthnRelyingPartyID :: Maybe (Value Text)
webAuthnUserVerification :: Maybe (Value Text)
..}
= UserPool {webAuthnRelyingPartyID :: Maybe (Value Text)
webAuthnRelyingPartyID = Value Text -> Maybe (Value Text)
forall a. a -> Maybe a
forall (f :: * -> *) a. Applicative f => a -> f a
Prelude.pure PropertyType "WebAuthnRelyingPartyID" UserPool
Value Text
newValue, Maybe [SchemaAttributeProperty]
Maybe (Map Text (Value Text))
Maybe (ValueList Text)
Maybe (Value Text)
Maybe DeviceConfigurationProperty
Maybe EmailConfigurationProperty
Maybe AdminCreateUserConfigProperty
Maybe LambdaConfigProperty
Maybe AccountRecoverySettingProperty
Maybe PoliciesProperty
Maybe SmsConfigurationProperty
Maybe UserAttributeUpdateSettingsProperty
Maybe UserPoolAddOnsProperty
Maybe UsernameConfigurationProperty
Maybe VerificationMessageTemplateProperty
()
haddock_workaround_ :: ()
accountRecoverySetting :: Maybe AccountRecoverySettingProperty
adminCreateUserConfig :: Maybe AdminCreateUserConfigProperty
aliasAttributes :: Maybe (ValueList Text)
autoVerifiedAttributes :: Maybe (ValueList Text)
deletionProtection :: Maybe (Value Text)
deviceConfiguration :: Maybe DeviceConfigurationProperty
emailAuthenticationMessage :: Maybe (Value Text)
emailAuthenticationSubject :: Maybe (Value Text)
emailConfiguration :: Maybe EmailConfigurationProperty
emailVerificationMessage :: Maybe (Value Text)
emailVerificationSubject :: Maybe (Value Text)
enabledMfas :: Maybe (ValueList Text)
lambdaConfig :: Maybe LambdaConfigProperty
mfaConfiguration :: Maybe (Value Text)
policies :: Maybe PoliciesProperty
schema :: Maybe [SchemaAttributeProperty]
smsAuthenticationMessage :: Maybe (Value Text)
smsConfiguration :: Maybe SmsConfigurationProperty
smsVerificationMessage :: Maybe (Value Text)
userAttributeUpdateSettings :: Maybe UserAttributeUpdateSettingsProperty
userPoolAddOns :: Maybe UserPoolAddOnsProperty
userPoolName :: Maybe (Value Text)
userPoolTags :: Maybe (Map Text (Value Text))
userPoolTier :: Maybe (Value Text)
usernameAttributes :: Maybe (ValueList Text)
usernameConfiguration :: Maybe UsernameConfigurationProperty
verificationMessageTemplate :: Maybe VerificationMessageTemplateProperty
webAuthnUserVerification :: Maybe (Value Text)
haddock_workaround_ :: ()
accountRecoverySetting :: Maybe AccountRecoverySettingProperty
adminCreateUserConfig :: Maybe AdminCreateUserConfigProperty
aliasAttributes :: Maybe (ValueList Text)
autoVerifiedAttributes :: Maybe (ValueList Text)
deletionProtection :: Maybe (Value Text)
deviceConfiguration :: Maybe DeviceConfigurationProperty
emailAuthenticationMessage :: Maybe (Value Text)
emailAuthenticationSubject :: Maybe (Value Text)
emailConfiguration :: Maybe EmailConfigurationProperty
emailVerificationMessage :: Maybe (Value Text)
emailVerificationSubject :: Maybe (Value Text)
enabledMfas :: Maybe (ValueList Text)
lambdaConfig :: Maybe LambdaConfigProperty
mfaConfiguration :: Maybe (Value Text)
policies :: Maybe PoliciesProperty
schema :: Maybe [SchemaAttributeProperty]
smsAuthenticationMessage :: Maybe (Value Text)
smsConfiguration :: Maybe SmsConfigurationProperty
smsVerificationMessage :: Maybe (Value Text)
userAttributeUpdateSettings :: Maybe UserAttributeUpdateSettingsProperty
userPoolAddOns :: Maybe UserPoolAddOnsProperty
userPoolName :: Maybe (Value Text)
userPoolTags :: Maybe (Map Text (Value Text))
userPoolTier :: Maybe (Value Text)
usernameAttributes :: Maybe (ValueList Text)
usernameConfiguration :: Maybe UsernameConfigurationProperty
verificationMessageTemplate :: Maybe VerificationMessageTemplateProperty
webAuthnUserVerification :: Maybe (Value Text)
..}
instance Property "WebAuthnUserVerification" UserPool where
type PropertyType "WebAuthnUserVerification" UserPool = Value Prelude.Text
set :: PropertyType "WebAuthnUserVerification" UserPool
-> UserPool -> UserPool
set PropertyType "WebAuthnUserVerification" UserPool
newValue UserPool {Maybe [SchemaAttributeProperty]
Maybe (Map Text (Value Text))
Maybe (ValueList Text)
Maybe (Value Text)
Maybe DeviceConfigurationProperty
Maybe EmailConfigurationProperty
Maybe AdminCreateUserConfigProperty
Maybe LambdaConfigProperty
Maybe AccountRecoverySettingProperty
Maybe PoliciesProperty
Maybe SmsConfigurationProperty
Maybe UserAttributeUpdateSettingsProperty
Maybe UserPoolAddOnsProperty
Maybe UsernameConfigurationProperty
Maybe VerificationMessageTemplateProperty
()
haddock_workaround_ :: UserPool -> ()
accountRecoverySetting :: UserPool -> Maybe AccountRecoverySettingProperty
adminCreateUserConfig :: UserPool -> Maybe AdminCreateUserConfigProperty
aliasAttributes :: UserPool -> Maybe (ValueList Text)
autoVerifiedAttributes :: UserPool -> Maybe (ValueList Text)
deletionProtection :: UserPool -> Maybe (Value Text)
deviceConfiguration :: UserPool -> Maybe DeviceConfigurationProperty
emailAuthenticationMessage :: UserPool -> Maybe (Value Text)
emailAuthenticationSubject :: UserPool -> Maybe (Value Text)
emailConfiguration :: UserPool -> Maybe EmailConfigurationProperty
emailVerificationMessage :: UserPool -> Maybe (Value Text)
emailVerificationSubject :: UserPool -> Maybe (Value Text)
enabledMfas :: UserPool -> Maybe (ValueList Text)
lambdaConfig :: UserPool -> Maybe LambdaConfigProperty
mfaConfiguration :: UserPool -> Maybe (Value Text)
policies :: UserPool -> Maybe PoliciesProperty
schema :: UserPool -> Maybe [SchemaAttributeProperty]
smsAuthenticationMessage :: UserPool -> Maybe (Value Text)
smsConfiguration :: UserPool -> Maybe SmsConfigurationProperty
smsVerificationMessage :: UserPool -> Maybe (Value Text)
userAttributeUpdateSettings :: UserPool -> Maybe UserAttributeUpdateSettingsProperty
userPoolAddOns :: UserPool -> Maybe UserPoolAddOnsProperty
userPoolName :: UserPool -> Maybe (Value Text)
userPoolTags :: UserPool -> Maybe (Map Text (Value Text))
userPoolTier :: UserPool -> Maybe (Value Text)
usernameAttributes :: UserPool -> Maybe (ValueList Text)
usernameConfiguration :: UserPool -> Maybe UsernameConfigurationProperty
verificationMessageTemplate :: UserPool -> Maybe VerificationMessageTemplateProperty
webAuthnRelyingPartyID :: UserPool -> Maybe (Value Text)
webAuthnUserVerification :: UserPool -> Maybe (Value Text)
haddock_workaround_ :: ()
accountRecoverySetting :: Maybe AccountRecoverySettingProperty
adminCreateUserConfig :: Maybe AdminCreateUserConfigProperty
aliasAttributes :: Maybe (ValueList Text)
autoVerifiedAttributes :: Maybe (ValueList Text)
deletionProtection :: Maybe (Value Text)
deviceConfiguration :: Maybe DeviceConfigurationProperty
emailAuthenticationMessage :: Maybe (Value Text)
emailAuthenticationSubject :: Maybe (Value Text)
emailConfiguration :: Maybe EmailConfigurationProperty
emailVerificationMessage :: Maybe (Value Text)
emailVerificationSubject :: Maybe (Value Text)
enabledMfas :: Maybe (ValueList Text)
lambdaConfig :: Maybe LambdaConfigProperty
mfaConfiguration :: Maybe (Value Text)
policies :: Maybe PoliciesProperty
schema :: Maybe [SchemaAttributeProperty]
smsAuthenticationMessage :: Maybe (Value Text)
smsConfiguration :: Maybe SmsConfigurationProperty
smsVerificationMessage :: Maybe (Value Text)
userAttributeUpdateSettings :: Maybe UserAttributeUpdateSettingsProperty
userPoolAddOns :: Maybe UserPoolAddOnsProperty
userPoolName :: Maybe (Value Text)
userPoolTags :: Maybe (Map Text (Value Text))
userPoolTier :: Maybe (Value Text)
usernameAttributes :: Maybe (ValueList Text)
usernameConfiguration :: Maybe UsernameConfigurationProperty
verificationMessageTemplate :: Maybe VerificationMessageTemplateProperty
webAuthnRelyingPartyID :: Maybe (Value Text)
webAuthnUserVerification :: Maybe (Value Text)
..}
= UserPool {webAuthnUserVerification :: Maybe (Value Text)
webAuthnUserVerification = Value Text -> Maybe (Value Text)
forall a. a -> Maybe a
forall (f :: * -> *) a. Applicative f => a -> f a
Prelude.pure PropertyType "WebAuthnUserVerification" UserPool
Value Text
newValue, Maybe [SchemaAttributeProperty]
Maybe (Map Text (Value Text))
Maybe (ValueList Text)
Maybe (Value Text)
Maybe DeviceConfigurationProperty
Maybe EmailConfigurationProperty
Maybe AdminCreateUserConfigProperty
Maybe LambdaConfigProperty
Maybe AccountRecoverySettingProperty
Maybe PoliciesProperty
Maybe SmsConfigurationProperty
Maybe UserAttributeUpdateSettingsProperty
Maybe UserPoolAddOnsProperty
Maybe UsernameConfigurationProperty
Maybe VerificationMessageTemplateProperty
()
haddock_workaround_ :: ()
accountRecoverySetting :: Maybe AccountRecoverySettingProperty
adminCreateUserConfig :: Maybe AdminCreateUserConfigProperty
aliasAttributes :: Maybe (ValueList Text)
autoVerifiedAttributes :: Maybe (ValueList Text)
deletionProtection :: Maybe (Value Text)
deviceConfiguration :: Maybe DeviceConfigurationProperty
emailAuthenticationMessage :: Maybe (Value Text)
emailAuthenticationSubject :: Maybe (Value Text)
emailConfiguration :: Maybe EmailConfigurationProperty
emailVerificationMessage :: Maybe (Value Text)
emailVerificationSubject :: Maybe (Value Text)
enabledMfas :: Maybe (ValueList Text)
lambdaConfig :: Maybe LambdaConfigProperty
mfaConfiguration :: Maybe (Value Text)
policies :: Maybe PoliciesProperty
schema :: Maybe [SchemaAttributeProperty]
smsAuthenticationMessage :: Maybe (Value Text)
smsConfiguration :: Maybe SmsConfigurationProperty
smsVerificationMessage :: Maybe (Value Text)
userAttributeUpdateSettings :: Maybe UserAttributeUpdateSettingsProperty
userPoolAddOns :: Maybe UserPoolAddOnsProperty
userPoolName :: Maybe (Value Text)
userPoolTags :: Maybe (Map Text (Value Text))
userPoolTier :: Maybe (Value Text)
usernameAttributes :: Maybe (ValueList Text)
usernameConfiguration :: Maybe UsernameConfigurationProperty
verificationMessageTemplate :: Maybe VerificationMessageTemplateProperty
webAuthnRelyingPartyID :: Maybe (Value Text)
haddock_workaround_ :: ()
accountRecoverySetting :: Maybe AccountRecoverySettingProperty
adminCreateUserConfig :: Maybe AdminCreateUserConfigProperty
aliasAttributes :: Maybe (ValueList Text)
autoVerifiedAttributes :: Maybe (ValueList Text)
deletionProtection :: Maybe (Value Text)
deviceConfiguration :: Maybe DeviceConfigurationProperty
emailAuthenticationMessage :: Maybe (Value Text)
emailAuthenticationSubject :: Maybe (Value Text)
emailConfiguration :: Maybe EmailConfigurationProperty
emailVerificationMessage :: Maybe (Value Text)
emailVerificationSubject :: Maybe (Value Text)
enabledMfas :: Maybe (ValueList Text)
lambdaConfig :: Maybe LambdaConfigProperty
mfaConfiguration :: Maybe (Value Text)
policies :: Maybe PoliciesProperty
schema :: Maybe [SchemaAttributeProperty]
smsAuthenticationMessage :: Maybe (Value Text)
smsConfiguration :: Maybe SmsConfigurationProperty
smsVerificationMessage :: Maybe (Value Text)
userAttributeUpdateSettings :: Maybe UserAttributeUpdateSettingsProperty
userPoolAddOns :: Maybe UserPoolAddOnsProperty
userPoolName :: Maybe (Value Text)
userPoolTags :: Maybe (Map Text (Value Text))
userPoolTier :: Maybe (Value Text)
usernameAttributes :: Maybe (ValueList Text)
usernameConfiguration :: Maybe UsernameConfigurationProperty
verificationMessageTemplate :: Maybe VerificationMessageTemplateProperty
webAuthnRelyingPartyID :: Maybe (Value Text)
..}