{-# LANGUAGE DeriveGeneric #-}
{-# LANGUAGE DuplicateRecordFields #-}
{-# LANGUAGE NamedFieldPuns #-}
{-# LANGUAGE OverloadedStrings #-}
{-# LANGUAGE RecordWildCards #-}
{-# LANGUAGE StrictData #-}
{-# LANGUAGE TypeFamilies #-}
{-# LANGUAGE NoImplicitPrelude #-}
{-# OPTIONS_GHC -fno-warn-unused-binds #-}
{-# OPTIONS_GHC -fno-warn-unused-imports #-}
{-# OPTIONS_GHC -fno-warn-unused-matches #-}

-- Derived from AWS service descriptions, licensed under Apache 2.0.

-- |
-- Module      : Amazonka.RDS.RestoreDBClusterFromS3
-- Copyright   : (c) 2013-2023 Brendan Hay
-- License     : Mozilla Public License, v. 2.0.
-- Maintainer  : Brendan Hay
-- Stability   : auto-generated
-- Portability : non-portable (GHC extensions)
--
-- Creates an Amazon Aurora DB cluster from MySQL data stored in an Amazon
-- S3 bucket. Amazon RDS must be authorized to access the Amazon S3 bucket
-- and the data must be created using the Percona XtraBackup utility as
-- described in
-- <https://docs.aws.amazon.com/AmazonRDS/latest/AuroraUserGuide/AuroraMySQL.Migrating.ExtMySQL.html#AuroraMySQL.Migrating.ExtMySQL.S3 Migrating Data from MySQL by Using an Amazon S3 Bucket>
-- in the /Amazon Aurora User Guide/.
--
-- This action only restores the DB cluster, not the DB instances for that
-- DB cluster. You must invoke the @CreateDBInstance@ action to create DB
-- instances for the restored DB cluster, specifying the identifier of the
-- restored DB cluster in @DBClusterIdentifier@. You can create DB
-- instances only after the @RestoreDBClusterFromS3@ action has completed
-- and the DB cluster is available.
--
-- For more information on Amazon Aurora, see
-- <https://docs.aws.amazon.com/AmazonRDS/latest/AuroraUserGuide/CHAP_AuroraOverview.html What is Amazon Aurora?>
-- in the /Amazon Aurora User Guide/.
--
-- This action only applies to Aurora DB clusters. The source DB engine
-- must be MySQL.
module Amazonka.RDS.RestoreDBClusterFromS3
  ( -- * Creating a Request
    RestoreDBClusterFromS3 (..),
    newRestoreDBClusterFromS3,

    -- * Request Lenses
    restoreDBClusterFromS3_availabilityZones,
    restoreDBClusterFromS3_backtrackWindow,
    restoreDBClusterFromS3_backupRetentionPeriod,
    restoreDBClusterFromS3_characterSetName,
    restoreDBClusterFromS3_copyTagsToSnapshot,
    restoreDBClusterFromS3_dbClusterParameterGroupName,
    restoreDBClusterFromS3_dbSubnetGroupName,
    restoreDBClusterFromS3_databaseName,
    restoreDBClusterFromS3_deletionProtection,
    restoreDBClusterFromS3_domain,
    restoreDBClusterFromS3_domainIAMRoleName,
    restoreDBClusterFromS3_enableCloudwatchLogsExports,
    restoreDBClusterFromS3_enableIAMDatabaseAuthentication,
    restoreDBClusterFromS3_engineVersion,
    restoreDBClusterFromS3_kmsKeyId,
    restoreDBClusterFromS3_manageMasterUserPassword,
    restoreDBClusterFromS3_masterUserPassword,
    restoreDBClusterFromS3_masterUserSecretKmsKeyId,
    restoreDBClusterFromS3_networkType,
    restoreDBClusterFromS3_optionGroupName,
    restoreDBClusterFromS3_port,
    restoreDBClusterFromS3_preferredBackupWindow,
    restoreDBClusterFromS3_preferredMaintenanceWindow,
    restoreDBClusterFromS3_s3Prefix,
    restoreDBClusterFromS3_serverlessV2ScalingConfiguration,
    restoreDBClusterFromS3_storageEncrypted,
    restoreDBClusterFromS3_tags,
    restoreDBClusterFromS3_vpcSecurityGroupIds,
    restoreDBClusterFromS3_dbClusterIdentifier,
    restoreDBClusterFromS3_engine,
    restoreDBClusterFromS3_masterUsername,
    restoreDBClusterFromS3_sourceEngine,
    restoreDBClusterFromS3_sourceEngineVersion,
    restoreDBClusterFromS3_s3BucketName,
    restoreDBClusterFromS3_s3IngestionRoleArn,

    -- * Destructuring the Response
    RestoreDBClusterFromS3Response (..),
    newRestoreDBClusterFromS3Response,

    -- * Response Lenses
    restoreDBClusterFromS3Response_dbCluster,
    restoreDBClusterFromS3Response_httpStatus,
  )
where

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

-- | /See:/ 'newRestoreDBClusterFromS3' smart constructor.
data RestoreDBClusterFromS3 = RestoreDBClusterFromS3'
  { -- | A list of Availability Zones (AZs) where instances in the restored DB
    -- cluster can be created.
    RestoreDBClusterFromS3 -> Maybe [Text]
availabilityZones :: Prelude.Maybe [Prelude.Text],
    -- | The target backtrack window, in seconds. To disable backtracking, set
    -- this value to 0.
    --
    -- Currently, Backtrack is only supported for Aurora MySQL DB clusters.
    --
    -- Default: 0
    --
    -- Constraints:
    --
    -- -   If specified, this value must be set to a number from 0 to 259,200
    --     (72 hours).
    RestoreDBClusterFromS3 -> Maybe Integer
backtrackWindow :: Prelude.Maybe Prelude.Integer,
    -- | The number of days for which automated backups of the restored DB
    -- cluster are retained. You must specify a minimum value of 1.
    --
    -- Default: 1
    --
    -- Constraints:
    --
    -- -   Must be a value from 1 to 35
    RestoreDBClusterFromS3 -> Maybe Int
backupRetentionPeriod :: Prelude.Maybe Prelude.Int,
    -- | A value that indicates that the restored DB cluster should be associated
    -- with the specified CharacterSet.
    RestoreDBClusterFromS3 -> Maybe Text
characterSetName :: Prelude.Maybe Prelude.Text,
    -- | A value that indicates whether to copy all tags from the restored DB
    -- cluster to snapshots of the restored DB cluster. The default is not to
    -- copy them.
    RestoreDBClusterFromS3 -> Maybe Bool
copyTagsToSnapshot :: Prelude.Maybe Prelude.Bool,
    -- | The name of the DB cluster parameter group to associate with the
    -- restored DB cluster. If this argument is omitted, @default.aurora5.6@ is
    -- used.
    --
    -- Constraints:
    --
    -- -   If supplied, must match the name of an existing
    --     DBClusterParameterGroup.
    RestoreDBClusterFromS3 -> Maybe Text
dbClusterParameterGroupName :: Prelude.Maybe Prelude.Text,
    -- | A DB subnet group to associate with the restored DB cluster.
    --
    -- Constraints: If supplied, must match the name of an existing
    -- DBSubnetGroup.
    --
    -- Example: @mydbsubnetgroup@
    RestoreDBClusterFromS3 -> Maybe Text
dbSubnetGroupName :: Prelude.Maybe Prelude.Text,
    -- | The database name for the restored DB cluster.
    RestoreDBClusterFromS3 -> Maybe Text
databaseName :: Prelude.Maybe Prelude.Text,
    -- | A value that indicates whether the DB cluster has deletion protection
    -- enabled. The database can\'t be deleted when deletion protection is
    -- enabled. By default, deletion protection isn\'t enabled.
    RestoreDBClusterFromS3 -> Maybe Bool
deletionProtection :: Prelude.Maybe Prelude.Bool,
    -- | Specify the Active Directory directory ID to restore the DB cluster in.
    -- The domain must be created prior to this operation.
    --
    -- For Amazon Aurora DB clusters, Amazon RDS can use Kerberos
    -- Authentication to authenticate users that connect to the DB cluster. For
    -- more information, see
    -- <https://docs.aws.amazon.com/AmazonRDS/latest/AuroraUserGuide/kerberos-authentication.html Kerberos Authentication>
    -- in the /Amazon Aurora User Guide/.
    RestoreDBClusterFromS3 -> Maybe Text
domain :: Prelude.Maybe Prelude.Text,
    -- | Specify the name of the IAM role to be used when making API calls to the
    -- Directory Service.
    RestoreDBClusterFromS3 -> Maybe Text
domainIAMRoleName :: Prelude.Maybe Prelude.Text,
    -- | The list of logs that the restored DB cluster is to export to CloudWatch
    -- Logs. The values in the list depend on the DB engine being used.
    --
    -- __Aurora MySQL__
    --
    -- Possible values are @audit@, @error@, @general@, and @slowquery@.
    --
    -- __Aurora PostgreSQL__
    --
    -- Possible value is @postgresql@.
    --
    -- For more information about exporting CloudWatch Logs for Amazon Aurora,
    -- see
    -- <https://docs.aws.amazon.com/AmazonRDS/latest/AuroraUserGuide/USER_LogAccess.html#USER_LogAccess.Procedural.UploadtoCloudWatch Publishing Database Logs to Amazon CloudWatch Logs>
    -- in the /Amazon Aurora User Guide/.
    RestoreDBClusterFromS3 -> Maybe [Text]
enableCloudwatchLogsExports :: Prelude.Maybe [Prelude.Text],
    -- | A value that indicates whether to enable mapping of Amazon Web Services
    -- Identity and Access Management (IAM) accounts to database accounts. By
    -- default, mapping isn\'t enabled.
    --
    -- For more information, see
    -- <https://docs.aws.amazon.com/AmazonRDS/latest/AuroraUserGuide/UsingWithRDS.IAMDBAuth.html IAM Database Authentication>
    -- in the /Amazon Aurora User Guide/.
    RestoreDBClusterFromS3 -> Maybe Bool
enableIAMDatabaseAuthentication :: Prelude.Maybe Prelude.Bool,
    -- | The version number of the database engine to use.
    --
    -- To list all of the available engine versions for @aurora@ (for MySQL
    -- 5.6-compatible Aurora), use the following command:
    --
    -- @aws rds describe-db-engine-versions --engine aurora --query \"DBEngineVersions[].EngineVersion\"@
    --
    -- To list all of the available engine versions for @aurora-mysql@ (for
    -- MySQL 5.7-compatible and MySQL 8.0-compatible Aurora), use the following
    -- command:
    --
    -- @aws rds describe-db-engine-versions --engine aurora-mysql --query \"DBEngineVersions[].EngineVersion\"@
    --
    -- __Aurora MySQL__
    --
    -- Example: @5.6.10a@, @5.6.mysql_aurora.1.19.2@,
    -- @5.7.mysql_aurora.2.07.1@, @8.0.mysql_aurora.3.02.0@
    RestoreDBClusterFromS3 -> Maybe Text
engineVersion :: Prelude.Maybe Prelude.Text,
    -- | The Amazon Web Services KMS key identifier for an encrypted DB cluster.
    --
    -- The Amazon Web Services KMS key identifier is the key ARN, key ID, alias
    -- ARN, or alias name for the KMS key. To use a KMS key in a different
    -- Amazon Web Services account, specify the key ARN or alias ARN.
    --
    -- If the StorageEncrypted parameter is enabled, and you do not specify a
    -- value for the @KmsKeyId@ parameter, then Amazon RDS will use your
    -- default KMS key. There is a default KMS key for your Amazon Web Services
    -- account. Your Amazon Web Services account has a different default KMS
    -- key for each Amazon Web Services Region.
    RestoreDBClusterFromS3 -> Maybe Text
kmsKeyId :: Prelude.Maybe Prelude.Text,
    -- | A value that indicates whether to manage the master user password with
    -- Amazon Web Services Secrets Manager.
    --
    -- For more information, see
    -- <https://docs.aws.amazon.com/AmazonRDS/latest/UserGuide/rds-secrets-manager.html Password management with Amazon Web Services Secrets Manager>
    -- in the /Amazon RDS User Guide/ and
    -- <https://docs.aws.amazon.com/AmazonRDS/latest/AuroraUserGuide/rds-secrets-manager.html Password management with Amazon Web Services Secrets Manager>
    -- in the /Amazon Aurora User Guide./
    --
    -- Constraints:
    --
    -- -   Can\'t manage the master user password with Amazon Web Services
    --     Secrets Manager if @MasterUserPassword@ is specified.
    RestoreDBClusterFromS3 -> Maybe Bool
manageMasterUserPassword :: Prelude.Maybe Prelude.Bool,
    -- | The password for the master database user. This password can contain any
    -- printable ASCII character except \"\/\", \"\"\", or \"\@\".
    --
    -- Constraints:
    --
    -- -   Must contain from 8 to 41 characters.
    --
    -- -   Can\'t be specified if @ManageMasterUserPassword@ is turned on.
    RestoreDBClusterFromS3 -> Maybe Text
masterUserPassword :: Prelude.Maybe Prelude.Text,
    -- | The Amazon Web Services KMS key identifier to encrypt a secret that is
    -- automatically generated and managed in Amazon Web Services Secrets
    -- Manager.
    --
    -- This setting is valid only if the master user password is managed by RDS
    -- in Amazon Web Services Secrets Manager for the DB cluster.
    --
    -- The Amazon Web Services KMS key identifier is the key ARN, key ID, alias
    -- ARN, or alias name for the KMS key. To use a KMS key in a different
    -- Amazon Web Services account, specify the key ARN or alias ARN.
    --
    -- If you don\'t specify @MasterUserSecretKmsKeyId@, then the
    -- @aws\/secretsmanager@ KMS key is used to encrypt the secret. If the
    -- secret is in a different Amazon Web Services account, then you can\'t
    -- use the @aws\/secretsmanager@ KMS key to encrypt the secret, and you
    -- must use a customer managed KMS key.
    --
    -- There is a default KMS key for your Amazon Web Services account. Your
    -- Amazon Web Services account has a different default KMS key for each
    -- Amazon Web Services Region.
    RestoreDBClusterFromS3 -> Maybe Text
masterUserSecretKmsKeyId :: Prelude.Maybe Prelude.Text,
    -- | The network type of the DB cluster.
    --
    -- Valid values:
    --
    -- -   @IPV4@
    --
    -- -   @DUAL@
    --
    -- The network type is determined by the @DBSubnetGroup@ specified for the
    -- DB cluster. A @DBSubnetGroup@ can support only the IPv4 protocol or the
    -- IPv4 and the IPv6 protocols (@DUAL@).
    --
    -- For more information, see
    -- <https://docs.aws.amazon.com/AmazonRDS/latest/AuroraUserGuide/USER_VPC.WorkingWithRDSInstanceinaVPC.html Working with a DB instance in a VPC>
    -- in the /Amazon Aurora User Guide./
    RestoreDBClusterFromS3 -> Maybe Text
networkType :: Prelude.Maybe Prelude.Text,
    -- | A value that indicates that the restored DB cluster should be associated
    -- with the specified option group.
    --
    -- Permanent options can\'t be removed from an option group. An option
    -- group can\'t be removed from a DB cluster once it is associated with a
    -- DB cluster.
    RestoreDBClusterFromS3 -> Maybe Text
optionGroupName :: Prelude.Maybe Prelude.Text,
    -- | The port number on which the instances in the restored DB cluster accept
    -- connections.
    --
    -- Default: @3306@
    RestoreDBClusterFromS3 -> Maybe Int
port :: Prelude.Maybe Prelude.Int,
    -- | The daily time range during which automated backups are created if
    -- automated backups are enabled using the @BackupRetentionPeriod@
    -- parameter.
    --
    -- The default is a 30-minute window selected at random from an 8-hour
    -- block of time for each Amazon Web Services Region. To view the time
    -- blocks available, see
    -- <https://docs.aws.amazon.com/AmazonRDS/latest/AuroraUserGuide/Aurora.Managing.Backups.html#Aurora.Managing.Backups.BackupWindow Backup window>
    -- in the /Amazon Aurora User Guide/.
    --
    -- Constraints:
    --
    -- -   Must be in the format @hh24:mi-hh24:mi@.
    --
    -- -   Must be in Universal Coordinated Time (UTC).
    --
    -- -   Must not conflict with the preferred maintenance window.
    --
    -- -   Must be at least 30 minutes.
    RestoreDBClusterFromS3 -> Maybe Text
preferredBackupWindow :: Prelude.Maybe Prelude.Text,
    -- | The weekly time range during which system maintenance can occur, in
    -- Universal Coordinated Time (UTC).
    --
    -- Format: @ddd:hh24:mi-ddd:hh24:mi@
    --
    -- The default is a 30-minute window selected at random from an 8-hour
    -- block of time for each Amazon Web Services Region, occurring on a random
    -- day of the week. To see the time blocks available, see
    -- <https://docs.aws.amazon.com/AmazonRDS/latest/AuroraUserGuide/USER_UpgradeDBInstance.Maintenance.html#AdjustingTheMaintenanceWindow.Aurora Adjusting the Preferred Maintenance Window>
    -- in the /Amazon Aurora User Guide/.
    --
    -- Valid Days: Mon, Tue, Wed, Thu, Fri, Sat, Sun.
    --
    -- Constraints: Minimum 30-minute window.
    RestoreDBClusterFromS3 -> Maybe Text
preferredMaintenanceWindow :: Prelude.Maybe Prelude.Text,
    -- | The prefix for all of the file names that contain the data used to
    -- create the Amazon Aurora DB cluster. If you do not specify a
    -- __SourceS3Prefix__ value, then the Amazon Aurora DB cluster is created
    -- by using all of the files in the Amazon S3 bucket.
    RestoreDBClusterFromS3 -> Maybe Text
s3Prefix :: Prelude.Maybe Prelude.Text,
    RestoreDBClusterFromS3 -> Maybe ServerlessV2ScalingConfiguration
serverlessV2ScalingConfiguration :: Prelude.Maybe ServerlessV2ScalingConfiguration,
    -- | A value that indicates whether the restored DB cluster is encrypted.
    RestoreDBClusterFromS3 -> Maybe Bool
storageEncrypted :: Prelude.Maybe Prelude.Bool,
    RestoreDBClusterFromS3 -> Maybe [Tag]
tags :: Prelude.Maybe [Tag],
    -- | A list of EC2 VPC security groups to associate with the restored DB
    -- cluster.
    RestoreDBClusterFromS3 -> Maybe [Text]
vpcSecurityGroupIds :: Prelude.Maybe [Prelude.Text],
    -- | The name of the DB cluster to create from the source data in the Amazon
    -- S3 bucket. This parameter isn\'t case-sensitive.
    --
    -- Constraints:
    --
    -- -   Must contain from 1 to 63 letters, numbers, or hyphens.
    --
    -- -   First character must be a letter.
    --
    -- -   Can\'t end with a hyphen or contain two consecutive hyphens.
    --
    -- Example: @my-cluster1@
    RestoreDBClusterFromS3 -> Text
dbClusterIdentifier :: Prelude.Text,
    -- | The name of the database engine to be used for this DB cluster.
    --
    -- Valid Values: @aurora@ (for MySQL 5.6-compatible Aurora) and
    -- @aurora-mysql@ (for MySQL 5.7-compatible and MySQL 8.0-compatible
    -- Aurora)
    RestoreDBClusterFromS3 -> Text
engine :: Prelude.Text,
    -- | The name of the master user for the restored DB cluster.
    --
    -- Constraints:
    --
    -- -   Must be 1 to 16 letters or numbers.
    --
    -- -   First character must be a letter.
    --
    -- -   Can\'t be a reserved word for the chosen database engine.
    RestoreDBClusterFromS3 -> Text
masterUsername :: Prelude.Text,
    -- | The identifier for the database engine that was backed up to create the
    -- files stored in the Amazon S3 bucket.
    --
    -- Valid values: @mysql@
    RestoreDBClusterFromS3 -> Text
sourceEngine :: Prelude.Text,
    -- | The version of the database that the backup files were created from.
    --
    -- MySQL versions 5.5, 5.6, and 5.7 are supported.
    --
    -- Example: @5.6.40@, @5.7.28@
    RestoreDBClusterFromS3 -> Text
sourceEngineVersion :: Prelude.Text,
    -- | The name of the Amazon S3 bucket that contains the data used to create
    -- the Amazon Aurora DB cluster.
    RestoreDBClusterFromS3 -> Text
s3BucketName :: Prelude.Text,
    -- | The Amazon Resource Name (ARN) of the Amazon Web Services Identity and
    -- Access Management (IAM) role that authorizes Amazon RDS to access the
    -- Amazon S3 bucket on your behalf.
    RestoreDBClusterFromS3 -> Text
s3IngestionRoleArn :: Prelude.Text
  }
  deriving (RestoreDBClusterFromS3 -> RestoreDBClusterFromS3 -> Bool
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: RestoreDBClusterFromS3 -> RestoreDBClusterFromS3 -> Bool
$c/= :: RestoreDBClusterFromS3 -> RestoreDBClusterFromS3 -> Bool
== :: RestoreDBClusterFromS3 -> RestoreDBClusterFromS3 -> Bool
$c== :: RestoreDBClusterFromS3 -> RestoreDBClusterFromS3 -> Bool
Prelude.Eq, ReadPrec [RestoreDBClusterFromS3]
ReadPrec RestoreDBClusterFromS3
Int -> ReadS RestoreDBClusterFromS3
ReadS [RestoreDBClusterFromS3]
forall a.
(Int -> ReadS a)
-> ReadS [a] -> ReadPrec a -> ReadPrec [a] -> Read a
readListPrec :: ReadPrec [RestoreDBClusterFromS3]
$creadListPrec :: ReadPrec [RestoreDBClusterFromS3]
readPrec :: ReadPrec RestoreDBClusterFromS3
$creadPrec :: ReadPrec RestoreDBClusterFromS3
readList :: ReadS [RestoreDBClusterFromS3]
$creadList :: ReadS [RestoreDBClusterFromS3]
readsPrec :: Int -> ReadS RestoreDBClusterFromS3
$creadsPrec :: Int -> ReadS RestoreDBClusterFromS3
Prelude.Read, Int -> RestoreDBClusterFromS3 -> ShowS
[RestoreDBClusterFromS3] -> ShowS
RestoreDBClusterFromS3 -> String
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [RestoreDBClusterFromS3] -> ShowS
$cshowList :: [RestoreDBClusterFromS3] -> ShowS
show :: RestoreDBClusterFromS3 -> String
$cshow :: RestoreDBClusterFromS3 -> String
showsPrec :: Int -> RestoreDBClusterFromS3 -> ShowS
$cshowsPrec :: Int -> RestoreDBClusterFromS3 -> ShowS
Prelude.Show, forall x. Rep RestoreDBClusterFromS3 x -> RestoreDBClusterFromS3
forall x. RestoreDBClusterFromS3 -> Rep RestoreDBClusterFromS3 x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cto :: forall x. Rep RestoreDBClusterFromS3 x -> RestoreDBClusterFromS3
$cfrom :: forall x. RestoreDBClusterFromS3 -> Rep RestoreDBClusterFromS3 x
Prelude.Generic)

-- |
-- Create a value of 'RestoreDBClusterFromS3' with all optional fields omitted.
--
-- Use <https://hackage.haskell.org/package/generic-lens generic-lens> or <https://hackage.haskell.org/package/optics optics> to modify other optional fields.
--
-- The following record fields are available, with the corresponding lenses provided
-- for backwards compatibility:
--
-- 'availabilityZones', 'restoreDBClusterFromS3_availabilityZones' - A list of Availability Zones (AZs) where instances in the restored DB
-- cluster can be created.
--
-- 'backtrackWindow', 'restoreDBClusterFromS3_backtrackWindow' - The target backtrack window, in seconds. To disable backtracking, set
-- this value to 0.
--
-- Currently, Backtrack is only supported for Aurora MySQL DB clusters.
--
-- Default: 0
--
-- Constraints:
--
-- -   If specified, this value must be set to a number from 0 to 259,200
--     (72 hours).
--
-- 'backupRetentionPeriod', 'restoreDBClusterFromS3_backupRetentionPeriod' - The number of days for which automated backups of the restored DB
-- cluster are retained. You must specify a minimum value of 1.
--
-- Default: 1
--
-- Constraints:
--
-- -   Must be a value from 1 to 35
--
-- 'characterSetName', 'restoreDBClusterFromS3_characterSetName' - A value that indicates that the restored DB cluster should be associated
-- with the specified CharacterSet.
--
-- 'copyTagsToSnapshot', 'restoreDBClusterFromS3_copyTagsToSnapshot' - A value that indicates whether to copy all tags from the restored DB
-- cluster to snapshots of the restored DB cluster. The default is not to
-- copy them.
--
-- 'dbClusterParameterGroupName', 'restoreDBClusterFromS3_dbClusterParameterGroupName' - The name of the DB cluster parameter group to associate with the
-- restored DB cluster. If this argument is omitted, @default.aurora5.6@ is
-- used.
--
-- Constraints:
--
-- -   If supplied, must match the name of an existing
--     DBClusterParameterGroup.
--
-- 'dbSubnetGroupName', 'restoreDBClusterFromS3_dbSubnetGroupName' - A DB subnet group to associate with the restored DB cluster.
--
-- Constraints: If supplied, must match the name of an existing
-- DBSubnetGroup.
--
-- Example: @mydbsubnetgroup@
--
-- 'databaseName', 'restoreDBClusterFromS3_databaseName' - The database name for the restored DB cluster.
--
-- 'deletionProtection', 'restoreDBClusterFromS3_deletionProtection' - A value that indicates whether the DB cluster has deletion protection
-- enabled. The database can\'t be deleted when deletion protection is
-- enabled. By default, deletion protection isn\'t enabled.
--
-- 'domain', 'restoreDBClusterFromS3_domain' - Specify the Active Directory directory ID to restore the DB cluster in.
-- The domain must be created prior to this operation.
--
-- For Amazon Aurora DB clusters, Amazon RDS can use Kerberos
-- Authentication to authenticate users that connect to the DB cluster. For
-- more information, see
-- <https://docs.aws.amazon.com/AmazonRDS/latest/AuroraUserGuide/kerberos-authentication.html Kerberos Authentication>
-- in the /Amazon Aurora User Guide/.
--
-- 'domainIAMRoleName', 'restoreDBClusterFromS3_domainIAMRoleName' - Specify the name of the IAM role to be used when making API calls to the
-- Directory Service.
--
-- 'enableCloudwatchLogsExports', 'restoreDBClusterFromS3_enableCloudwatchLogsExports' - The list of logs that the restored DB cluster is to export to CloudWatch
-- Logs. The values in the list depend on the DB engine being used.
--
-- __Aurora MySQL__
--
-- Possible values are @audit@, @error@, @general@, and @slowquery@.
--
-- __Aurora PostgreSQL__
--
-- Possible value is @postgresql@.
--
-- For more information about exporting CloudWatch Logs for Amazon Aurora,
-- see
-- <https://docs.aws.amazon.com/AmazonRDS/latest/AuroraUserGuide/USER_LogAccess.html#USER_LogAccess.Procedural.UploadtoCloudWatch Publishing Database Logs to Amazon CloudWatch Logs>
-- in the /Amazon Aurora User Guide/.
--
-- 'enableIAMDatabaseAuthentication', 'restoreDBClusterFromS3_enableIAMDatabaseAuthentication' - A value that indicates whether to enable mapping of Amazon Web Services
-- Identity and Access Management (IAM) accounts to database accounts. By
-- default, mapping isn\'t enabled.
--
-- For more information, see
-- <https://docs.aws.amazon.com/AmazonRDS/latest/AuroraUserGuide/UsingWithRDS.IAMDBAuth.html IAM Database Authentication>
-- in the /Amazon Aurora User Guide/.
--
-- 'engineVersion', 'restoreDBClusterFromS3_engineVersion' - The version number of the database engine to use.
--
-- To list all of the available engine versions for @aurora@ (for MySQL
-- 5.6-compatible Aurora), use the following command:
--
-- @aws rds describe-db-engine-versions --engine aurora --query \"DBEngineVersions[].EngineVersion\"@
--
-- To list all of the available engine versions for @aurora-mysql@ (for
-- MySQL 5.7-compatible and MySQL 8.0-compatible Aurora), use the following
-- command:
--
-- @aws rds describe-db-engine-versions --engine aurora-mysql --query \"DBEngineVersions[].EngineVersion\"@
--
-- __Aurora MySQL__
--
-- Example: @5.6.10a@, @5.6.mysql_aurora.1.19.2@,
-- @5.7.mysql_aurora.2.07.1@, @8.0.mysql_aurora.3.02.0@
--
-- 'kmsKeyId', 'restoreDBClusterFromS3_kmsKeyId' - The Amazon Web Services KMS key identifier for an encrypted DB cluster.
--
-- The Amazon Web Services KMS key identifier is the key ARN, key ID, alias
-- ARN, or alias name for the KMS key. To use a KMS key in a different
-- Amazon Web Services account, specify the key ARN or alias ARN.
--
-- If the StorageEncrypted parameter is enabled, and you do not specify a
-- value for the @KmsKeyId@ parameter, then Amazon RDS will use your
-- default KMS key. There is a default KMS key for your Amazon Web Services
-- account. Your Amazon Web Services account has a different default KMS
-- key for each Amazon Web Services Region.
--
-- 'manageMasterUserPassword', 'restoreDBClusterFromS3_manageMasterUserPassword' - A value that indicates whether to manage the master user password with
-- Amazon Web Services Secrets Manager.
--
-- For more information, see
-- <https://docs.aws.amazon.com/AmazonRDS/latest/UserGuide/rds-secrets-manager.html Password management with Amazon Web Services Secrets Manager>
-- in the /Amazon RDS User Guide/ and
-- <https://docs.aws.amazon.com/AmazonRDS/latest/AuroraUserGuide/rds-secrets-manager.html Password management with Amazon Web Services Secrets Manager>
-- in the /Amazon Aurora User Guide./
--
-- Constraints:
--
-- -   Can\'t manage the master user password with Amazon Web Services
--     Secrets Manager if @MasterUserPassword@ is specified.
--
-- 'masterUserPassword', 'restoreDBClusterFromS3_masterUserPassword' - The password for the master database user. This password can contain any
-- printable ASCII character except \"\/\", \"\"\", or \"\@\".
--
-- Constraints:
--
-- -   Must contain from 8 to 41 characters.
--
-- -   Can\'t be specified if @ManageMasterUserPassword@ is turned on.
--
-- 'masterUserSecretKmsKeyId', 'restoreDBClusterFromS3_masterUserSecretKmsKeyId' - The Amazon Web Services KMS key identifier to encrypt a secret that is
-- automatically generated and managed in Amazon Web Services Secrets
-- Manager.
--
-- This setting is valid only if the master user password is managed by RDS
-- in Amazon Web Services Secrets Manager for the DB cluster.
--
-- The Amazon Web Services KMS key identifier is the key ARN, key ID, alias
-- ARN, or alias name for the KMS key. To use a KMS key in a different
-- Amazon Web Services account, specify the key ARN or alias ARN.
--
-- If you don\'t specify @MasterUserSecretKmsKeyId@, then the
-- @aws\/secretsmanager@ KMS key is used to encrypt the secret. If the
-- secret is in a different Amazon Web Services account, then you can\'t
-- use the @aws\/secretsmanager@ KMS key to encrypt the secret, and you
-- must use a customer managed KMS key.
--
-- There is a default KMS key for your Amazon Web Services account. Your
-- Amazon Web Services account has a different default KMS key for each
-- Amazon Web Services Region.
--
-- 'networkType', 'restoreDBClusterFromS3_networkType' - The network type of the DB cluster.
--
-- Valid values:
--
-- -   @IPV4@
--
-- -   @DUAL@
--
-- The network type is determined by the @DBSubnetGroup@ specified for the
-- DB cluster. A @DBSubnetGroup@ can support only the IPv4 protocol or the
-- IPv4 and the IPv6 protocols (@DUAL@).
--
-- For more information, see
-- <https://docs.aws.amazon.com/AmazonRDS/latest/AuroraUserGuide/USER_VPC.WorkingWithRDSInstanceinaVPC.html Working with a DB instance in a VPC>
-- in the /Amazon Aurora User Guide./
--
-- 'optionGroupName', 'restoreDBClusterFromS3_optionGroupName' - A value that indicates that the restored DB cluster should be associated
-- with the specified option group.
--
-- Permanent options can\'t be removed from an option group. An option
-- group can\'t be removed from a DB cluster once it is associated with a
-- DB cluster.
--
-- 'port', 'restoreDBClusterFromS3_port' - The port number on which the instances in the restored DB cluster accept
-- connections.
--
-- Default: @3306@
--
-- 'preferredBackupWindow', 'restoreDBClusterFromS3_preferredBackupWindow' - The daily time range during which automated backups are created if
-- automated backups are enabled using the @BackupRetentionPeriod@
-- parameter.
--
-- The default is a 30-minute window selected at random from an 8-hour
-- block of time for each Amazon Web Services Region. To view the time
-- blocks available, see
-- <https://docs.aws.amazon.com/AmazonRDS/latest/AuroraUserGuide/Aurora.Managing.Backups.html#Aurora.Managing.Backups.BackupWindow Backup window>
-- in the /Amazon Aurora User Guide/.
--
-- Constraints:
--
-- -   Must be in the format @hh24:mi-hh24:mi@.
--
-- -   Must be in Universal Coordinated Time (UTC).
--
-- -   Must not conflict with the preferred maintenance window.
--
-- -   Must be at least 30 minutes.
--
-- 'preferredMaintenanceWindow', 'restoreDBClusterFromS3_preferredMaintenanceWindow' - The weekly time range during which system maintenance can occur, in
-- Universal Coordinated Time (UTC).
--
-- Format: @ddd:hh24:mi-ddd:hh24:mi@
--
-- The default is a 30-minute window selected at random from an 8-hour
-- block of time for each Amazon Web Services Region, occurring on a random
-- day of the week. To see the time blocks available, see
-- <https://docs.aws.amazon.com/AmazonRDS/latest/AuroraUserGuide/USER_UpgradeDBInstance.Maintenance.html#AdjustingTheMaintenanceWindow.Aurora Adjusting the Preferred Maintenance Window>
-- in the /Amazon Aurora User Guide/.
--
-- Valid Days: Mon, Tue, Wed, Thu, Fri, Sat, Sun.
--
-- Constraints: Minimum 30-minute window.
--
-- 's3Prefix', 'restoreDBClusterFromS3_s3Prefix' - The prefix for all of the file names that contain the data used to
-- create the Amazon Aurora DB cluster. If you do not specify a
-- __SourceS3Prefix__ value, then the Amazon Aurora DB cluster is created
-- by using all of the files in the Amazon S3 bucket.
--
-- 'serverlessV2ScalingConfiguration', 'restoreDBClusterFromS3_serverlessV2ScalingConfiguration' - Undocumented member.
--
-- 'storageEncrypted', 'restoreDBClusterFromS3_storageEncrypted' - A value that indicates whether the restored DB cluster is encrypted.
--
-- 'tags', 'restoreDBClusterFromS3_tags' - Undocumented member.
--
-- 'vpcSecurityGroupIds', 'restoreDBClusterFromS3_vpcSecurityGroupIds' - A list of EC2 VPC security groups to associate with the restored DB
-- cluster.
--
-- 'dbClusterIdentifier', 'restoreDBClusterFromS3_dbClusterIdentifier' - The name of the DB cluster to create from the source data in the Amazon
-- S3 bucket. This parameter isn\'t case-sensitive.
--
-- Constraints:
--
-- -   Must contain from 1 to 63 letters, numbers, or hyphens.
--
-- -   First character must be a letter.
--
-- -   Can\'t end with a hyphen or contain two consecutive hyphens.
--
-- Example: @my-cluster1@
--
-- 'engine', 'restoreDBClusterFromS3_engine' - The name of the database engine to be used for this DB cluster.
--
-- Valid Values: @aurora@ (for MySQL 5.6-compatible Aurora) and
-- @aurora-mysql@ (for MySQL 5.7-compatible and MySQL 8.0-compatible
-- Aurora)
--
-- 'masterUsername', 'restoreDBClusterFromS3_masterUsername' - The name of the master user for the restored DB cluster.
--
-- Constraints:
--
-- -   Must be 1 to 16 letters or numbers.
--
-- -   First character must be a letter.
--
-- -   Can\'t be a reserved word for the chosen database engine.
--
-- 'sourceEngine', 'restoreDBClusterFromS3_sourceEngine' - The identifier for the database engine that was backed up to create the
-- files stored in the Amazon S3 bucket.
--
-- Valid values: @mysql@
--
-- 'sourceEngineVersion', 'restoreDBClusterFromS3_sourceEngineVersion' - The version of the database that the backup files were created from.
--
-- MySQL versions 5.5, 5.6, and 5.7 are supported.
--
-- Example: @5.6.40@, @5.7.28@
--
-- 's3BucketName', 'restoreDBClusterFromS3_s3BucketName' - The name of the Amazon S3 bucket that contains the data used to create
-- the Amazon Aurora DB cluster.
--
-- 's3IngestionRoleArn', 'restoreDBClusterFromS3_s3IngestionRoleArn' - The Amazon Resource Name (ARN) of the Amazon Web Services Identity and
-- Access Management (IAM) role that authorizes Amazon RDS to access the
-- Amazon S3 bucket on your behalf.
newRestoreDBClusterFromS3 ::
  -- | 'dbClusterIdentifier'
  Prelude.Text ->
  -- | 'engine'
  Prelude.Text ->
  -- | 'masterUsername'
  Prelude.Text ->
  -- | 'sourceEngine'
  Prelude.Text ->
  -- | 'sourceEngineVersion'
  Prelude.Text ->
  -- | 's3BucketName'
  Prelude.Text ->
  -- | 's3IngestionRoleArn'
  Prelude.Text ->
  RestoreDBClusterFromS3
newRestoreDBClusterFromS3 :: Text
-> Text
-> Text
-> Text
-> Text
-> Text
-> Text
-> RestoreDBClusterFromS3
newRestoreDBClusterFromS3
  Text
pDBClusterIdentifier_
  Text
pEngine_
  Text
pMasterUsername_
  Text
pSourceEngine_
  Text
pSourceEngineVersion_
  Text
pS3BucketName_
  Text
pS3IngestionRoleArn_ =
    RestoreDBClusterFromS3'
      { $sel:availabilityZones:RestoreDBClusterFromS3' :: Maybe [Text]
availabilityZones =
          forall a. Maybe a
Prelude.Nothing,
        $sel:backtrackWindow:RestoreDBClusterFromS3' :: Maybe Integer
backtrackWindow = forall a. Maybe a
Prelude.Nothing,
        $sel:backupRetentionPeriod:RestoreDBClusterFromS3' :: Maybe Int
backupRetentionPeriod = forall a. Maybe a
Prelude.Nothing,
        $sel:characterSetName:RestoreDBClusterFromS3' :: Maybe Text
characterSetName = forall a. Maybe a
Prelude.Nothing,
        $sel:copyTagsToSnapshot:RestoreDBClusterFromS3' :: Maybe Bool
copyTagsToSnapshot = forall a. Maybe a
Prelude.Nothing,
        $sel:dbClusterParameterGroupName:RestoreDBClusterFromS3' :: Maybe Text
dbClusterParameterGroupName = forall a. Maybe a
Prelude.Nothing,
        $sel:dbSubnetGroupName:RestoreDBClusterFromS3' :: Maybe Text
dbSubnetGroupName = forall a. Maybe a
Prelude.Nothing,
        $sel:databaseName:RestoreDBClusterFromS3' :: Maybe Text
databaseName = forall a. Maybe a
Prelude.Nothing,
        $sel:deletionProtection:RestoreDBClusterFromS3' :: Maybe Bool
deletionProtection = forall a. Maybe a
Prelude.Nothing,
        $sel:domain:RestoreDBClusterFromS3' :: Maybe Text
domain = forall a. Maybe a
Prelude.Nothing,
        $sel:domainIAMRoleName:RestoreDBClusterFromS3' :: Maybe Text
domainIAMRoleName = forall a. Maybe a
Prelude.Nothing,
        $sel:enableCloudwatchLogsExports:RestoreDBClusterFromS3' :: Maybe [Text]
enableCloudwatchLogsExports = forall a. Maybe a
Prelude.Nothing,
        $sel:enableIAMDatabaseAuthentication:RestoreDBClusterFromS3' :: Maybe Bool
enableIAMDatabaseAuthentication = forall a. Maybe a
Prelude.Nothing,
        $sel:engineVersion:RestoreDBClusterFromS3' :: Maybe Text
engineVersion = forall a. Maybe a
Prelude.Nothing,
        $sel:kmsKeyId:RestoreDBClusterFromS3' :: Maybe Text
kmsKeyId = forall a. Maybe a
Prelude.Nothing,
        $sel:manageMasterUserPassword:RestoreDBClusterFromS3' :: Maybe Bool
manageMasterUserPassword = forall a. Maybe a
Prelude.Nothing,
        $sel:masterUserPassword:RestoreDBClusterFromS3' :: Maybe Text
masterUserPassword = forall a. Maybe a
Prelude.Nothing,
        $sel:masterUserSecretKmsKeyId:RestoreDBClusterFromS3' :: Maybe Text
masterUserSecretKmsKeyId = forall a. Maybe a
Prelude.Nothing,
        $sel:networkType:RestoreDBClusterFromS3' :: Maybe Text
networkType = forall a. Maybe a
Prelude.Nothing,
        $sel:optionGroupName:RestoreDBClusterFromS3' :: Maybe Text
optionGroupName = forall a. Maybe a
Prelude.Nothing,
        $sel:port:RestoreDBClusterFromS3' :: Maybe Int
port = forall a. Maybe a
Prelude.Nothing,
        $sel:preferredBackupWindow:RestoreDBClusterFromS3' :: Maybe Text
preferredBackupWindow = forall a. Maybe a
Prelude.Nothing,
        $sel:preferredMaintenanceWindow:RestoreDBClusterFromS3' :: Maybe Text
preferredMaintenanceWindow = forall a. Maybe a
Prelude.Nothing,
        $sel:s3Prefix:RestoreDBClusterFromS3' :: Maybe Text
s3Prefix = forall a. Maybe a
Prelude.Nothing,
        $sel:serverlessV2ScalingConfiguration:RestoreDBClusterFromS3' :: Maybe ServerlessV2ScalingConfiguration
serverlessV2ScalingConfiguration = forall a. Maybe a
Prelude.Nothing,
        $sel:storageEncrypted:RestoreDBClusterFromS3' :: Maybe Bool
storageEncrypted = forall a. Maybe a
Prelude.Nothing,
        $sel:tags:RestoreDBClusterFromS3' :: Maybe [Tag]
tags = forall a. Maybe a
Prelude.Nothing,
        $sel:vpcSecurityGroupIds:RestoreDBClusterFromS3' :: Maybe [Text]
vpcSecurityGroupIds = forall a. Maybe a
Prelude.Nothing,
        $sel:dbClusterIdentifier:RestoreDBClusterFromS3' :: Text
dbClusterIdentifier = Text
pDBClusterIdentifier_,
        $sel:engine:RestoreDBClusterFromS3' :: Text
engine = Text
pEngine_,
        $sel:masterUsername:RestoreDBClusterFromS3' :: Text
masterUsername = Text
pMasterUsername_,
        $sel:sourceEngine:RestoreDBClusterFromS3' :: Text
sourceEngine = Text
pSourceEngine_,
        $sel:sourceEngineVersion:RestoreDBClusterFromS3' :: Text
sourceEngineVersion = Text
pSourceEngineVersion_,
        $sel:s3BucketName:RestoreDBClusterFromS3' :: Text
s3BucketName = Text
pS3BucketName_,
        $sel:s3IngestionRoleArn:RestoreDBClusterFromS3' :: Text
s3IngestionRoleArn = Text
pS3IngestionRoleArn_
      }

-- | A list of Availability Zones (AZs) where instances in the restored DB
-- cluster can be created.
restoreDBClusterFromS3_availabilityZones :: Lens.Lens' RestoreDBClusterFromS3 (Prelude.Maybe [Prelude.Text])
restoreDBClusterFromS3_availabilityZones :: Lens' RestoreDBClusterFromS3 (Maybe [Text])
restoreDBClusterFromS3_availabilityZones = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\RestoreDBClusterFromS3' {Maybe [Text]
availabilityZones :: Maybe [Text]
$sel:availabilityZones:RestoreDBClusterFromS3' :: RestoreDBClusterFromS3 -> Maybe [Text]
availabilityZones} -> Maybe [Text]
availabilityZones) (\s :: RestoreDBClusterFromS3
s@RestoreDBClusterFromS3' {} Maybe [Text]
a -> RestoreDBClusterFromS3
s {$sel:availabilityZones:RestoreDBClusterFromS3' :: Maybe [Text]
availabilityZones = Maybe [Text]
a} :: RestoreDBClusterFromS3) forall b c a. (b -> c) -> (a -> b) -> a -> c
Prelude.. forall (f :: * -> *) (g :: * -> *) s t a b.
(Functor f, Functor g) =>
AnIso s t a b -> Iso (f s) (g t) (f a) (g b)
Lens.mapping forall s t a b. (Coercible s a, Coercible t b) => Iso s t a b
Lens.coerced

-- | The target backtrack window, in seconds. To disable backtracking, set
-- this value to 0.
--
-- Currently, Backtrack is only supported for Aurora MySQL DB clusters.
--
-- Default: 0
--
-- Constraints:
--
-- -   If specified, this value must be set to a number from 0 to 259,200
--     (72 hours).
restoreDBClusterFromS3_backtrackWindow :: Lens.Lens' RestoreDBClusterFromS3 (Prelude.Maybe Prelude.Integer)
restoreDBClusterFromS3_backtrackWindow :: Lens' RestoreDBClusterFromS3 (Maybe Integer)
restoreDBClusterFromS3_backtrackWindow = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\RestoreDBClusterFromS3' {Maybe Integer
backtrackWindow :: Maybe Integer
$sel:backtrackWindow:RestoreDBClusterFromS3' :: RestoreDBClusterFromS3 -> Maybe Integer
backtrackWindow} -> Maybe Integer
backtrackWindow) (\s :: RestoreDBClusterFromS3
s@RestoreDBClusterFromS3' {} Maybe Integer
a -> RestoreDBClusterFromS3
s {$sel:backtrackWindow:RestoreDBClusterFromS3' :: Maybe Integer
backtrackWindow = Maybe Integer
a} :: RestoreDBClusterFromS3)

-- | The number of days for which automated backups of the restored DB
-- cluster are retained. You must specify a minimum value of 1.
--
-- Default: 1
--
-- Constraints:
--
-- -   Must be a value from 1 to 35
restoreDBClusterFromS3_backupRetentionPeriod :: Lens.Lens' RestoreDBClusterFromS3 (Prelude.Maybe Prelude.Int)
restoreDBClusterFromS3_backupRetentionPeriod :: Lens' RestoreDBClusterFromS3 (Maybe Int)
restoreDBClusterFromS3_backupRetentionPeriod = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\RestoreDBClusterFromS3' {Maybe Int
backupRetentionPeriod :: Maybe Int
$sel:backupRetentionPeriod:RestoreDBClusterFromS3' :: RestoreDBClusterFromS3 -> Maybe Int
backupRetentionPeriod} -> Maybe Int
backupRetentionPeriod) (\s :: RestoreDBClusterFromS3
s@RestoreDBClusterFromS3' {} Maybe Int
a -> RestoreDBClusterFromS3
s {$sel:backupRetentionPeriod:RestoreDBClusterFromS3' :: Maybe Int
backupRetentionPeriod = Maybe Int
a} :: RestoreDBClusterFromS3)

-- | A value that indicates that the restored DB cluster should be associated
-- with the specified CharacterSet.
restoreDBClusterFromS3_characterSetName :: Lens.Lens' RestoreDBClusterFromS3 (Prelude.Maybe Prelude.Text)
restoreDBClusterFromS3_characterSetName :: Lens' RestoreDBClusterFromS3 (Maybe Text)
restoreDBClusterFromS3_characterSetName = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\RestoreDBClusterFromS3' {Maybe Text
characterSetName :: Maybe Text
$sel:characterSetName:RestoreDBClusterFromS3' :: RestoreDBClusterFromS3 -> Maybe Text
characterSetName} -> Maybe Text
characterSetName) (\s :: RestoreDBClusterFromS3
s@RestoreDBClusterFromS3' {} Maybe Text
a -> RestoreDBClusterFromS3
s {$sel:characterSetName:RestoreDBClusterFromS3' :: Maybe Text
characterSetName = Maybe Text
a} :: RestoreDBClusterFromS3)

-- | A value that indicates whether to copy all tags from the restored DB
-- cluster to snapshots of the restored DB cluster. The default is not to
-- copy them.
restoreDBClusterFromS3_copyTagsToSnapshot :: Lens.Lens' RestoreDBClusterFromS3 (Prelude.Maybe Prelude.Bool)
restoreDBClusterFromS3_copyTagsToSnapshot :: Lens' RestoreDBClusterFromS3 (Maybe Bool)
restoreDBClusterFromS3_copyTagsToSnapshot = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\RestoreDBClusterFromS3' {Maybe Bool
copyTagsToSnapshot :: Maybe Bool
$sel:copyTagsToSnapshot:RestoreDBClusterFromS3' :: RestoreDBClusterFromS3 -> Maybe Bool
copyTagsToSnapshot} -> Maybe Bool
copyTagsToSnapshot) (\s :: RestoreDBClusterFromS3
s@RestoreDBClusterFromS3' {} Maybe Bool
a -> RestoreDBClusterFromS3
s {$sel:copyTagsToSnapshot:RestoreDBClusterFromS3' :: Maybe Bool
copyTagsToSnapshot = Maybe Bool
a} :: RestoreDBClusterFromS3)

-- | The name of the DB cluster parameter group to associate with the
-- restored DB cluster. If this argument is omitted, @default.aurora5.6@ is
-- used.
--
-- Constraints:
--
-- -   If supplied, must match the name of an existing
--     DBClusterParameterGroup.
restoreDBClusterFromS3_dbClusterParameterGroupName :: Lens.Lens' RestoreDBClusterFromS3 (Prelude.Maybe Prelude.Text)
restoreDBClusterFromS3_dbClusterParameterGroupName :: Lens' RestoreDBClusterFromS3 (Maybe Text)
restoreDBClusterFromS3_dbClusterParameterGroupName = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\RestoreDBClusterFromS3' {Maybe Text
dbClusterParameterGroupName :: Maybe Text
$sel:dbClusterParameterGroupName:RestoreDBClusterFromS3' :: RestoreDBClusterFromS3 -> Maybe Text
dbClusterParameterGroupName} -> Maybe Text
dbClusterParameterGroupName) (\s :: RestoreDBClusterFromS3
s@RestoreDBClusterFromS3' {} Maybe Text
a -> RestoreDBClusterFromS3
s {$sel:dbClusterParameterGroupName:RestoreDBClusterFromS3' :: Maybe Text
dbClusterParameterGroupName = Maybe Text
a} :: RestoreDBClusterFromS3)

-- | A DB subnet group to associate with the restored DB cluster.
--
-- Constraints: If supplied, must match the name of an existing
-- DBSubnetGroup.
--
-- Example: @mydbsubnetgroup@
restoreDBClusterFromS3_dbSubnetGroupName :: Lens.Lens' RestoreDBClusterFromS3 (Prelude.Maybe Prelude.Text)
restoreDBClusterFromS3_dbSubnetGroupName :: Lens' RestoreDBClusterFromS3 (Maybe Text)
restoreDBClusterFromS3_dbSubnetGroupName = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\RestoreDBClusterFromS3' {Maybe Text
dbSubnetGroupName :: Maybe Text
$sel:dbSubnetGroupName:RestoreDBClusterFromS3' :: RestoreDBClusterFromS3 -> Maybe Text
dbSubnetGroupName} -> Maybe Text
dbSubnetGroupName) (\s :: RestoreDBClusterFromS3
s@RestoreDBClusterFromS3' {} Maybe Text
a -> RestoreDBClusterFromS3
s {$sel:dbSubnetGroupName:RestoreDBClusterFromS3' :: Maybe Text
dbSubnetGroupName = Maybe Text
a} :: RestoreDBClusterFromS3)

-- | The database name for the restored DB cluster.
restoreDBClusterFromS3_databaseName :: Lens.Lens' RestoreDBClusterFromS3 (Prelude.Maybe Prelude.Text)
restoreDBClusterFromS3_databaseName :: Lens' RestoreDBClusterFromS3 (Maybe Text)
restoreDBClusterFromS3_databaseName = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\RestoreDBClusterFromS3' {Maybe Text
databaseName :: Maybe Text
$sel:databaseName:RestoreDBClusterFromS3' :: RestoreDBClusterFromS3 -> Maybe Text
databaseName} -> Maybe Text
databaseName) (\s :: RestoreDBClusterFromS3
s@RestoreDBClusterFromS3' {} Maybe Text
a -> RestoreDBClusterFromS3
s {$sel:databaseName:RestoreDBClusterFromS3' :: Maybe Text
databaseName = Maybe Text
a} :: RestoreDBClusterFromS3)

-- | A value that indicates whether the DB cluster has deletion protection
-- enabled. The database can\'t be deleted when deletion protection is
-- enabled. By default, deletion protection isn\'t enabled.
restoreDBClusterFromS3_deletionProtection :: Lens.Lens' RestoreDBClusterFromS3 (Prelude.Maybe Prelude.Bool)
restoreDBClusterFromS3_deletionProtection :: Lens' RestoreDBClusterFromS3 (Maybe Bool)
restoreDBClusterFromS3_deletionProtection = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\RestoreDBClusterFromS3' {Maybe Bool
deletionProtection :: Maybe Bool
$sel:deletionProtection:RestoreDBClusterFromS3' :: RestoreDBClusterFromS3 -> Maybe Bool
deletionProtection} -> Maybe Bool
deletionProtection) (\s :: RestoreDBClusterFromS3
s@RestoreDBClusterFromS3' {} Maybe Bool
a -> RestoreDBClusterFromS3
s {$sel:deletionProtection:RestoreDBClusterFromS3' :: Maybe Bool
deletionProtection = Maybe Bool
a} :: RestoreDBClusterFromS3)

-- | Specify the Active Directory directory ID to restore the DB cluster in.
-- The domain must be created prior to this operation.
--
-- For Amazon Aurora DB clusters, Amazon RDS can use Kerberos
-- Authentication to authenticate users that connect to the DB cluster. For
-- more information, see
-- <https://docs.aws.amazon.com/AmazonRDS/latest/AuroraUserGuide/kerberos-authentication.html Kerberos Authentication>
-- in the /Amazon Aurora User Guide/.
restoreDBClusterFromS3_domain :: Lens.Lens' RestoreDBClusterFromS3 (Prelude.Maybe Prelude.Text)
restoreDBClusterFromS3_domain :: Lens' RestoreDBClusterFromS3 (Maybe Text)
restoreDBClusterFromS3_domain = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\RestoreDBClusterFromS3' {Maybe Text
domain :: Maybe Text
$sel:domain:RestoreDBClusterFromS3' :: RestoreDBClusterFromS3 -> Maybe Text
domain} -> Maybe Text
domain) (\s :: RestoreDBClusterFromS3
s@RestoreDBClusterFromS3' {} Maybe Text
a -> RestoreDBClusterFromS3
s {$sel:domain:RestoreDBClusterFromS3' :: Maybe Text
domain = Maybe Text
a} :: RestoreDBClusterFromS3)

-- | Specify the name of the IAM role to be used when making API calls to the
-- Directory Service.
restoreDBClusterFromS3_domainIAMRoleName :: Lens.Lens' RestoreDBClusterFromS3 (Prelude.Maybe Prelude.Text)
restoreDBClusterFromS3_domainIAMRoleName :: Lens' RestoreDBClusterFromS3 (Maybe Text)
restoreDBClusterFromS3_domainIAMRoleName = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\RestoreDBClusterFromS3' {Maybe Text
domainIAMRoleName :: Maybe Text
$sel:domainIAMRoleName:RestoreDBClusterFromS3' :: RestoreDBClusterFromS3 -> Maybe Text
domainIAMRoleName} -> Maybe Text
domainIAMRoleName) (\s :: RestoreDBClusterFromS3
s@RestoreDBClusterFromS3' {} Maybe Text
a -> RestoreDBClusterFromS3
s {$sel:domainIAMRoleName:RestoreDBClusterFromS3' :: Maybe Text
domainIAMRoleName = Maybe Text
a} :: RestoreDBClusterFromS3)

-- | The list of logs that the restored DB cluster is to export to CloudWatch
-- Logs. The values in the list depend on the DB engine being used.
--
-- __Aurora MySQL__
--
-- Possible values are @audit@, @error@, @general@, and @slowquery@.
--
-- __Aurora PostgreSQL__
--
-- Possible value is @postgresql@.
--
-- For more information about exporting CloudWatch Logs for Amazon Aurora,
-- see
-- <https://docs.aws.amazon.com/AmazonRDS/latest/AuroraUserGuide/USER_LogAccess.html#USER_LogAccess.Procedural.UploadtoCloudWatch Publishing Database Logs to Amazon CloudWatch Logs>
-- in the /Amazon Aurora User Guide/.
restoreDBClusterFromS3_enableCloudwatchLogsExports :: Lens.Lens' RestoreDBClusterFromS3 (Prelude.Maybe [Prelude.Text])
restoreDBClusterFromS3_enableCloudwatchLogsExports :: Lens' RestoreDBClusterFromS3 (Maybe [Text])
restoreDBClusterFromS3_enableCloudwatchLogsExports = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\RestoreDBClusterFromS3' {Maybe [Text]
enableCloudwatchLogsExports :: Maybe [Text]
$sel:enableCloudwatchLogsExports:RestoreDBClusterFromS3' :: RestoreDBClusterFromS3 -> Maybe [Text]
enableCloudwatchLogsExports} -> Maybe [Text]
enableCloudwatchLogsExports) (\s :: RestoreDBClusterFromS3
s@RestoreDBClusterFromS3' {} Maybe [Text]
a -> RestoreDBClusterFromS3
s {$sel:enableCloudwatchLogsExports:RestoreDBClusterFromS3' :: Maybe [Text]
enableCloudwatchLogsExports = Maybe [Text]
a} :: RestoreDBClusterFromS3) forall b c a. (b -> c) -> (a -> b) -> a -> c
Prelude.. forall (f :: * -> *) (g :: * -> *) s t a b.
(Functor f, Functor g) =>
AnIso s t a b -> Iso (f s) (g t) (f a) (g b)
Lens.mapping forall s t a b. (Coercible s a, Coercible t b) => Iso s t a b
Lens.coerced

-- | A value that indicates whether to enable mapping of Amazon Web Services
-- Identity and Access Management (IAM) accounts to database accounts. By
-- default, mapping isn\'t enabled.
--
-- For more information, see
-- <https://docs.aws.amazon.com/AmazonRDS/latest/AuroraUserGuide/UsingWithRDS.IAMDBAuth.html IAM Database Authentication>
-- in the /Amazon Aurora User Guide/.
restoreDBClusterFromS3_enableIAMDatabaseAuthentication :: Lens.Lens' RestoreDBClusterFromS3 (Prelude.Maybe Prelude.Bool)
restoreDBClusterFromS3_enableIAMDatabaseAuthentication :: Lens' RestoreDBClusterFromS3 (Maybe Bool)
restoreDBClusterFromS3_enableIAMDatabaseAuthentication = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\RestoreDBClusterFromS3' {Maybe Bool
enableIAMDatabaseAuthentication :: Maybe Bool
$sel:enableIAMDatabaseAuthentication:RestoreDBClusterFromS3' :: RestoreDBClusterFromS3 -> Maybe Bool
enableIAMDatabaseAuthentication} -> Maybe Bool
enableIAMDatabaseAuthentication) (\s :: RestoreDBClusterFromS3
s@RestoreDBClusterFromS3' {} Maybe Bool
a -> RestoreDBClusterFromS3
s {$sel:enableIAMDatabaseAuthentication:RestoreDBClusterFromS3' :: Maybe Bool
enableIAMDatabaseAuthentication = Maybe Bool
a} :: RestoreDBClusterFromS3)

-- | The version number of the database engine to use.
--
-- To list all of the available engine versions for @aurora@ (for MySQL
-- 5.6-compatible Aurora), use the following command:
--
-- @aws rds describe-db-engine-versions --engine aurora --query \"DBEngineVersions[].EngineVersion\"@
--
-- To list all of the available engine versions for @aurora-mysql@ (for
-- MySQL 5.7-compatible and MySQL 8.0-compatible Aurora), use the following
-- command:
--
-- @aws rds describe-db-engine-versions --engine aurora-mysql --query \"DBEngineVersions[].EngineVersion\"@
--
-- __Aurora MySQL__
--
-- Example: @5.6.10a@, @5.6.mysql_aurora.1.19.2@,
-- @5.7.mysql_aurora.2.07.1@, @8.0.mysql_aurora.3.02.0@
restoreDBClusterFromS3_engineVersion :: Lens.Lens' RestoreDBClusterFromS3 (Prelude.Maybe Prelude.Text)
restoreDBClusterFromS3_engineVersion :: Lens' RestoreDBClusterFromS3 (Maybe Text)
restoreDBClusterFromS3_engineVersion = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\RestoreDBClusterFromS3' {Maybe Text
engineVersion :: Maybe Text
$sel:engineVersion:RestoreDBClusterFromS3' :: RestoreDBClusterFromS3 -> Maybe Text
engineVersion} -> Maybe Text
engineVersion) (\s :: RestoreDBClusterFromS3
s@RestoreDBClusterFromS3' {} Maybe Text
a -> RestoreDBClusterFromS3
s {$sel:engineVersion:RestoreDBClusterFromS3' :: Maybe Text
engineVersion = Maybe Text
a} :: RestoreDBClusterFromS3)

-- | The Amazon Web Services KMS key identifier for an encrypted DB cluster.
--
-- The Amazon Web Services KMS key identifier is the key ARN, key ID, alias
-- ARN, or alias name for the KMS key. To use a KMS key in a different
-- Amazon Web Services account, specify the key ARN or alias ARN.
--
-- If the StorageEncrypted parameter is enabled, and you do not specify a
-- value for the @KmsKeyId@ parameter, then Amazon RDS will use your
-- default KMS key. There is a default KMS key for your Amazon Web Services
-- account. Your Amazon Web Services account has a different default KMS
-- key for each Amazon Web Services Region.
restoreDBClusterFromS3_kmsKeyId :: Lens.Lens' RestoreDBClusterFromS3 (Prelude.Maybe Prelude.Text)
restoreDBClusterFromS3_kmsKeyId :: Lens' RestoreDBClusterFromS3 (Maybe Text)
restoreDBClusterFromS3_kmsKeyId = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\RestoreDBClusterFromS3' {Maybe Text
kmsKeyId :: Maybe Text
$sel:kmsKeyId:RestoreDBClusterFromS3' :: RestoreDBClusterFromS3 -> Maybe Text
kmsKeyId} -> Maybe Text
kmsKeyId) (\s :: RestoreDBClusterFromS3
s@RestoreDBClusterFromS3' {} Maybe Text
a -> RestoreDBClusterFromS3
s {$sel:kmsKeyId:RestoreDBClusterFromS3' :: Maybe Text
kmsKeyId = Maybe Text
a} :: RestoreDBClusterFromS3)

-- | A value that indicates whether to manage the master user password with
-- Amazon Web Services Secrets Manager.
--
-- For more information, see
-- <https://docs.aws.amazon.com/AmazonRDS/latest/UserGuide/rds-secrets-manager.html Password management with Amazon Web Services Secrets Manager>
-- in the /Amazon RDS User Guide/ and
-- <https://docs.aws.amazon.com/AmazonRDS/latest/AuroraUserGuide/rds-secrets-manager.html Password management with Amazon Web Services Secrets Manager>
-- in the /Amazon Aurora User Guide./
--
-- Constraints:
--
-- -   Can\'t manage the master user password with Amazon Web Services
--     Secrets Manager if @MasterUserPassword@ is specified.
restoreDBClusterFromS3_manageMasterUserPassword :: Lens.Lens' RestoreDBClusterFromS3 (Prelude.Maybe Prelude.Bool)
restoreDBClusterFromS3_manageMasterUserPassword :: Lens' RestoreDBClusterFromS3 (Maybe Bool)
restoreDBClusterFromS3_manageMasterUserPassword = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\RestoreDBClusterFromS3' {Maybe Bool
manageMasterUserPassword :: Maybe Bool
$sel:manageMasterUserPassword:RestoreDBClusterFromS3' :: RestoreDBClusterFromS3 -> Maybe Bool
manageMasterUserPassword} -> Maybe Bool
manageMasterUserPassword) (\s :: RestoreDBClusterFromS3
s@RestoreDBClusterFromS3' {} Maybe Bool
a -> RestoreDBClusterFromS3
s {$sel:manageMasterUserPassword:RestoreDBClusterFromS3' :: Maybe Bool
manageMasterUserPassword = Maybe Bool
a} :: RestoreDBClusterFromS3)

-- | The password for the master database user. This password can contain any
-- printable ASCII character except \"\/\", \"\"\", or \"\@\".
--
-- Constraints:
--
-- -   Must contain from 8 to 41 characters.
--
-- -   Can\'t be specified if @ManageMasterUserPassword@ is turned on.
restoreDBClusterFromS3_masterUserPassword :: Lens.Lens' RestoreDBClusterFromS3 (Prelude.Maybe Prelude.Text)
restoreDBClusterFromS3_masterUserPassword :: Lens' RestoreDBClusterFromS3 (Maybe Text)
restoreDBClusterFromS3_masterUserPassword = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\RestoreDBClusterFromS3' {Maybe Text
masterUserPassword :: Maybe Text
$sel:masterUserPassword:RestoreDBClusterFromS3' :: RestoreDBClusterFromS3 -> Maybe Text
masterUserPassword} -> Maybe Text
masterUserPassword) (\s :: RestoreDBClusterFromS3
s@RestoreDBClusterFromS3' {} Maybe Text
a -> RestoreDBClusterFromS3
s {$sel:masterUserPassword:RestoreDBClusterFromS3' :: Maybe Text
masterUserPassword = Maybe Text
a} :: RestoreDBClusterFromS3)

-- | The Amazon Web Services KMS key identifier to encrypt a secret that is
-- automatically generated and managed in Amazon Web Services Secrets
-- Manager.
--
-- This setting is valid only if the master user password is managed by RDS
-- in Amazon Web Services Secrets Manager for the DB cluster.
--
-- The Amazon Web Services KMS key identifier is the key ARN, key ID, alias
-- ARN, or alias name for the KMS key. To use a KMS key in a different
-- Amazon Web Services account, specify the key ARN or alias ARN.
--
-- If you don\'t specify @MasterUserSecretKmsKeyId@, then the
-- @aws\/secretsmanager@ KMS key is used to encrypt the secret. If the
-- secret is in a different Amazon Web Services account, then you can\'t
-- use the @aws\/secretsmanager@ KMS key to encrypt the secret, and you
-- must use a customer managed KMS key.
--
-- There is a default KMS key for your Amazon Web Services account. Your
-- Amazon Web Services account has a different default KMS key for each
-- Amazon Web Services Region.
restoreDBClusterFromS3_masterUserSecretKmsKeyId :: Lens.Lens' RestoreDBClusterFromS3 (Prelude.Maybe Prelude.Text)
restoreDBClusterFromS3_masterUserSecretKmsKeyId :: Lens' RestoreDBClusterFromS3 (Maybe Text)
restoreDBClusterFromS3_masterUserSecretKmsKeyId = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\RestoreDBClusterFromS3' {Maybe Text
masterUserSecretKmsKeyId :: Maybe Text
$sel:masterUserSecretKmsKeyId:RestoreDBClusterFromS3' :: RestoreDBClusterFromS3 -> Maybe Text
masterUserSecretKmsKeyId} -> Maybe Text
masterUserSecretKmsKeyId) (\s :: RestoreDBClusterFromS3
s@RestoreDBClusterFromS3' {} Maybe Text
a -> RestoreDBClusterFromS3
s {$sel:masterUserSecretKmsKeyId:RestoreDBClusterFromS3' :: Maybe Text
masterUserSecretKmsKeyId = Maybe Text
a} :: RestoreDBClusterFromS3)

-- | The network type of the DB cluster.
--
-- Valid values:
--
-- -   @IPV4@
--
-- -   @DUAL@
--
-- The network type is determined by the @DBSubnetGroup@ specified for the
-- DB cluster. A @DBSubnetGroup@ can support only the IPv4 protocol or the
-- IPv4 and the IPv6 protocols (@DUAL@).
--
-- For more information, see
-- <https://docs.aws.amazon.com/AmazonRDS/latest/AuroraUserGuide/USER_VPC.WorkingWithRDSInstanceinaVPC.html Working with a DB instance in a VPC>
-- in the /Amazon Aurora User Guide./
restoreDBClusterFromS3_networkType :: Lens.Lens' RestoreDBClusterFromS3 (Prelude.Maybe Prelude.Text)
restoreDBClusterFromS3_networkType :: Lens' RestoreDBClusterFromS3 (Maybe Text)
restoreDBClusterFromS3_networkType = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\RestoreDBClusterFromS3' {Maybe Text
networkType :: Maybe Text
$sel:networkType:RestoreDBClusterFromS3' :: RestoreDBClusterFromS3 -> Maybe Text
networkType} -> Maybe Text
networkType) (\s :: RestoreDBClusterFromS3
s@RestoreDBClusterFromS3' {} Maybe Text
a -> RestoreDBClusterFromS3
s {$sel:networkType:RestoreDBClusterFromS3' :: Maybe Text
networkType = Maybe Text
a} :: RestoreDBClusterFromS3)

-- | A value that indicates that the restored DB cluster should be associated
-- with the specified option group.
--
-- Permanent options can\'t be removed from an option group. An option
-- group can\'t be removed from a DB cluster once it is associated with a
-- DB cluster.
restoreDBClusterFromS3_optionGroupName :: Lens.Lens' RestoreDBClusterFromS3 (Prelude.Maybe Prelude.Text)
restoreDBClusterFromS3_optionGroupName :: Lens' RestoreDBClusterFromS3 (Maybe Text)
restoreDBClusterFromS3_optionGroupName = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\RestoreDBClusterFromS3' {Maybe Text
optionGroupName :: Maybe Text
$sel:optionGroupName:RestoreDBClusterFromS3' :: RestoreDBClusterFromS3 -> Maybe Text
optionGroupName} -> Maybe Text
optionGroupName) (\s :: RestoreDBClusterFromS3
s@RestoreDBClusterFromS3' {} Maybe Text
a -> RestoreDBClusterFromS3
s {$sel:optionGroupName:RestoreDBClusterFromS3' :: Maybe Text
optionGroupName = Maybe Text
a} :: RestoreDBClusterFromS3)

-- | The port number on which the instances in the restored DB cluster accept
-- connections.
--
-- Default: @3306@
restoreDBClusterFromS3_port :: Lens.Lens' RestoreDBClusterFromS3 (Prelude.Maybe Prelude.Int)
restoreDBClusterFromS3_port :: Lens' RestoreDBClusterFromS3 (Maybe Int)
restoreDBClusterFromS3_port = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\RestoreDBClusterFromS3' {Maybe Int
port :: Maybe Int
$sel:port:RestoreDBClusterFromS3' :: RestoreDBClusterFromS3 -> Maybe Int
port} -> Maybe Int
port) (\s :: RestoreDBClusterFromS3
s@RestoreDBClusterFromS3' {} Maybe Int
a -> RestoreDBClusterFromS3
s {$sel:port:RestoreDBClusterFromS3' :: Maybe Int
port = Maybe Int
a} :: RestoreDBClusterFromS3)

-- | The daily time range during which automated backups are created if
-- automated backups are enabled using the @BackupRetentionPeriod@
-- parameter.
--
-- The default is a 30-minute window selected at random from an 8-hour
-- block of time for each Amazon Web Services Region. To view the time
-- blocks available, see
-- <https://docs.aws.amazon.com/AmazonRDS/latest/AuroraUserGuide/Aurora.Managing.Backups.html#Aurora.Managing.Backups.BackupWindow Backup window>
-- in the /Amazon Aurora User Guide/.
--
-- Constraints:
--
-- -   Must be in the format @hh24:mi-hh24:mi@.
--
-- -   Must be in Universal Coordinated Time (UTC).
--
-- -   Must not conflict with the preferred maintenance window.
--
-- -   Must be at least 30 minutes.
restoreDBClusterFromS3_preferredBackupWindow :: Lens.Lens' RestoreDBClusterFromS3 (Prelude.Maybe Prelude.Text)
restoreDBClusterFromS3_preferredBackupWindow :: Lens' RestoreDBClusterFromS3 (Maybe Text)
restoreDBClusterFromS3_preferredBackupWindow = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\RestoreDBClusterFromS3' {Maybe Text
preferredBackupWindow :: Maybe Text
$sel:preferredBackupWindow:RestoreDBClusterFromS3' :: RestoreDBClusterFromS3 -> Maybe Text
preferredBackupWindow} -> Maybe Text
preferredBackupWindow) (\s :: RestoreDBClusterFromS3
s@RestoreDBClusterFromS3' {} Maybe Text
a -> RestoreDBClusterFromS3
s {$sel:preferredBackupWindow:RestoreDBClusterFromS3' :: Maybe Text
preferredBackupWindow = Maybe Text
a} :: RestoreDBClusterFromS3)

-- | The weekly time range during which system maintenance can occur, in
-- Universal Coordinated Time (UTC).
--
-- Format: @ddd:hh24:mi-ddd:hh24:mi@
--
-- The default is a 30-minute window selected at random from an 8-hour
-- block of time for each Amazon Web Services Region, occurring on a random
-- day of the week. To see the time blocks available, see
-- <https://docs.aws.amazon.com/AmazonRDS/latest/AuroraUserGuide/USER_UpgradeDBInstance.Maintenance.html#AdjustingTheMaintenanceWindow.Aurora Adjusting the Preferred Maintenance Window>
-- in the /Amazon Aurora User Guide/.
--
-- Valid Days: Mon, Tue, Wed, Thu, Fri, Sat, Sun.
--
-- Constraints: Minimum 30-minute window.
restoreDBClusterFromS3_preferredMaintenanceWindow :: Lens.Lens' RestoreDBClusterFromS3 (Prelude.Maybe Prelude.Text)
restoreDBClusterFromS3_preferredMaintenanceWindow :: Lens' RestoreDBClusterFromS3 (Maybe Text)
restoreDBClusterFromS3_preferredMaintenanceWindow = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\RestoreDBClusterFromS3' {Maybe Text
preferredMaintenanceWindow :: Maybe Text
$sel:preferredMaintenanceWindow:RestoreDBClusterFromS3' :: RestoreDBClusterFromS3 -> Maybe Text
preferredMaintenanceWindow} -> Maybe Text
preferredMaintenanceWindow) (\s :: RestoreDBClusterFromS3
s@RestoreDBClusterFromS3' {} Maybe Text
a -> RestoreDBClusterFromS3
s {$sel:preferredMaintenanceWindow:RestoreDBClusterFromS3' :: Maybe Text
preferredMaintenanceWindow = Maybe Text
a} :: RestoreDBClusterFromS3)

-- | The prefix for all of the file names that contain the data used to
-- create the Amazon Aurora DB cluster. If you do not specify a
-- __SourceS3Prefix__ value, then the Amazon Aurora DB cluster is created
-- by using all of the files in the Amazon S3 bucket.
restoreDBClusterFromS3_s3Prefix :: Lens.Lens' RestoreDBClusterFromS3 (Prelude.Maybe Prelude.Text)
restoreDBClusterFromS3_s3Prefix :: Lens' RestoreDBClusterFromS3 (Maybe Text)
restoreDBClusterFromS3_s3Prefix = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\RestoreDBClusterFromS3' {Maybe Text
s3Prefix :: Maybe Text
$sel:s3Prefix:RestoreDBClusterFromS3' :: RestoreDBClusterFromS3 -> Maybe Text
s3Prefix} -> Maybe Text
s3Prefix) (\s :: RestoreDBClusterFromS3
s@RestoreDBClusterFromS3' {} Maybe Text
a -> RestoreDBClusterFromS3
s {$sel:s3Prefix:RestoreDBClusterFromS3' :: Maybe Text
s3Prefix = Maybe Text
a} :: RestoreDBClusterFromS3)

-- | Undocumented member.
restoreDBClusterFromS3_serverlessV2ScalingConfiguration :: Lens.Lens' RestoreDBClusterFromS3 (Prelude.Maybe ServerlessV2ScalingConfiguration)
restoreDBClusterFromS3_serverlessV2ScalingConfiguration :: Lens'
  RestoreDBClusterFromS3 (Maybe ServerlessV2ScalingConfiguration)
restoreDBClusterFromS3_serverlessV2ScalingConfiguration = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\RestoreDBClusterFromS3' {Maybe ServerlessV2ScalingConfiguration
serverlessV2ScalingConfiguration :: Maybe ServerlessV2ScalingConfiguration
$sel:serverlessV2ScalingConfiguration:RestoreDBClusterFromS3' :: RestoreDBClusterFromS3 -> Maybe ServerlessV2ScalingConfiguration
serverlessV2ScalingConfiguration} -> Maybe ServerlessV2ScalingConfiguration
serverlessV2ScalingConfiguration) (\s :: RestoreDBClusterFromS3
s@RestoreDBClusterFromS3' {} Maybe ServerlessV2ScalingConfiguration
a -> RestoreDBClusterFromS3
s {$sel:serverlessV2ScalingConfiguration:RestoreDBClusterFromS3' :: Maybe ServerlessV2ScalingConfiguration
serverlessV2ScalingConfiguration = Maybe ServerlessV2ScalingConfiguration
a} :: RestoreDBClusterFromS3)

-- | A value that indicates whether the restored DB cluster is encrypted.
restoreDBClusterFromS3_storageEncrypted :: Lens.Lens' RestoreDBClusterFromS3 (Prelude.Maybe Prelude.Bool)
restoreDBClusterFromS3_storageEncrypted :: Lens' RestoreDBClusterFromS3 (Maybe Bool)
restoreDBClusterFromS3_storageEncrypted = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\RestoreDBClusterFromS3' {Maybe Bool
storageEncrypted :: Maybe Bool
$sel:storageEncrypted:RestoreDBClusterFromS3' :: RestoreDBClusterFromS3 -> Maybe Bool
storageEncrypted} -> Maybe Bool
storageEncrypted) (\s :: RestoreDBClusterFromS3
s@RestoreDBClusterFromS3' {} Maybe Bool
a -> RestoreDBClusterFromS3
s {$sel:storageEncrypted:RestoreDBClusterFromS3' :: Maybe Bool
storageEncrypted = Maybe Bool
a} :: RestoreDBClusterFromS3)

-- | Undocumented member.
restoreDBClusterFromS3_tags :: Lens.Lens' RestoreDBClusterFromS3 (Prelude.Maybe [Tag])
restoreDBClusterFromS3_tags :: Lens' RestoreDBClusterFromS3 (Maybe [Tag])
restoreDBClusterFromS3_tags = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\RestoreDBClusterFromS3' {Maybe [Tag]
tags :: Maybe [Tag]
$sel:tags:RestoreDBClusterFromS3' :: RestoreDBClusterFromS3 -> Maybe [Tag]
tags} -> Maybe [Tag]
tags) (\s :: RestoreDBClusterFromS3
s@RestoreDBClusterFromS3' {} Maybe [Tag]
a -> RestoreDBClusterFromS3
s {$sel:tags:RestoreDBClusterFromS3' :: Maybe [Tag]
tags = Maybe [Tag]
a} :: RestoreDBClusterFromS3) forall b c a. (b -> c) -> (a -> b) -> a -> c
Prelude.. forall (f :: * -> *) (g :: * -> *) s t a b.
(Functor f, Functor g) =>
AnIso s t a b -> Iso (f s) (g t) (f a) (g b)
Lens.mapping forall s t a b. (Coercible s a, Coercible t b) => Iso s t a b
Lens.coerced

-- | A list of EC2 VPC security groups to associate with the restored DB
-- cluster.
restoreDBClusterFromS3_vpcSecurityGroupIds :: Lens.Lens' RestoreDBClusterFromS3 (Prelude.Maybe [Prelude.Text])
restoreDBClusterFromS3_vpcSecurityGroupIds :: Lens' RestoreDBClusterFromS3 (Maybe [Text])
restoreDBClusterFromS3_vpcSecurityGroupIds = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\RestoreDBClusterFromS3' {Maybe [Text]
vpcSecurityGroupIds :: Maybe [Text]
$sel:vpcSecurityGroupIds:RestoreDBClusterFromS3' :: RestoreDBClusterFromS3 -> Maybe [Text]
vpcSecurityGroupIds} -> Maybe [Text]
vpcSecurityGroupIds) (\s :: RestoreDBClusterFromS3
s@RestoreDBClusterFromS3' {} Maybe [Text]
a -> RestoreDBClusterFromS3
s {$sel:vpcSecurityGroupIds:RestoreDBClusterFromS3' :: Maybe [Text]
vpcSecurityGroupIds = Maybe [Text]
a} :: RestoreDBClusterFromS3) forall b c a. (b -> c) -> (a -> b) -> a -> c
Prelude.. forall (f :: * -> *) (g :: * -> *) s t a b.
(Functor f, Functor g) =>
AnIso s t a b -> Iso (f s) (g t) (f a) (g b)
Lens.mapping forall s t a b. (Coercible s a, Coercible t b) => Iso s t a b
Lens.coerced

-- | The name of the DB cluster to create from the source data in the Amazon
-- S3 bucket. This parameter isn\'t case-sensitive.
--
-- Constraints:
--
-- -   Must contain from 1 to 63 letters, numbers, or hyphens.
--
-- -   First character must be a letter.
--
-- -   Can\'t end with a hyphen or contain two consecutive hyphens.
--
-- Example: @my-cluster1@
restoreDBClusterFromS3_dbClusterIdentifier :: Lens.Lens' RestoreDBClusterFromS3 Prelude.Text
restoreDBClusterFromS3_dbClusterIdentifier :: Lens' RestoreDBClusterFromS3 Text
restoreDBClusterFromS3_dbClusterIdentifier = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\RestoreDBClusterFromS3' {Text
dbClusterIdentifier :: Text
$sel:dbClusterIdentifier:RestoreDBClusterFromS3' :: RestoreDBClusterFromS3 -> Text
dbClusterIdentifier} -> Text
dbClusterIdentifier) (\s :: RestoreDBClusterFromS3
s@RestoreDBClusterFromS3' {} Text
a -> RestoreDBClusterFromS3
s {$sel:dbClusterIdentifier:RestoreDBClusterFromS3' :: Text
dbClusterIdentifier = Text
a} :: RestoreDBClusterFromS3)

-- | The name of the database engine to be used for this DB cluster.
--
-- Valid Values: @aurora@ (for MySQL 5.6-compatible Aurora) and
-- @aurora-mysql@ (for MySQL 5.7-compatible and MySQL 8.0-compatible
-- Aurora)
restoreDBClusterFromS3_engine :: Lens.Lens' RestoreDBClusterFromS3 Prelude.Text
restoreDBClusterFromS3_engine :: Lens' RestoreDBClusterFromS3 Text
restoreDBClusterFromS3_engine = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\RestoreDBClusterFromS3' {Text
engine :: Text
$sel:engine:RestoreDBClusterFromS3' :: RestoreDBClusterFromS3 -> Text
engine} -> Text
engine) (\s :: RestoreDBClusterFromS3
s@RestoreDBClusterFromS3' {} Text
a -> RestoreDBClusterFromS3
s {$sel:engine:RestoreDBClusterFromS3' :: Text
engine = Text
a} :: RestoreDBClusterFromS3)

-- | The name of the master user for the restored DB cluster.
--
-- Constraints:
--
-- -   Must be 1 to 16 letters or numbers.
--
-- -   First character must be a letter.
--
-- -   Can\'t be a reserved word for the chosen database engine.
restoreDBClusterFromS3_masterUsername :: Lens.Lens' RestoreDBClusterFromS3 Prelude.Text
restoreDBClusterFromS3_masterUsername :: Lens' RestoreDBClusterFromS3 Text
restoreDBClusterFromS3_masterUsername = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\RestoreDBClusterFromS3' {Text
masterUsername :: Text
$sel:masterUsername:RestoreDBClusterFromS3' :: RestoreDBClusterFromS3 -> Text
masterUsername} -> Text
masterUsername) (\s :: RestoreDBClusterFromS3
s@RestoreDBClusterFromS3' {} Text
a -> RestoreDBClusterFromS3
s {$sel:masterUsername:RestoreDBClusterFromS3' :: Text
masterUsername = Text
a} :: RestoreDBClusterFromS3)

-- | The identifier for the database engine that was backed up to create the
-- files stored in the Amazon S3 bucket.
--
-- Valid values: @mysql@
restoreDBClusterFromS3_sourceEngine :: Lens.Lens' RestoreDBClusterFromS3 Prelude.Text
restoreDBClusterFromS3_sourceEngine :: Lens' RestoreDBClusterFromS3 Text
restoreDBClusterFromS3_sourceEngine = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\RestoreDBClusterFromS3' {Text
sourceEngine :: Text
$sel:sourceEngine:RestoreDBClusterFromS3' :: RestoreDBClusterFromS3 -> Text
sourceEngine} -> Text
sourceEngine) (\s :: RestoreDBClusterFromS3
s@RestoreDBClusterFromS3' {} Text
a -> RestoreDBClusterFromS3
s {$sel:sourceEngine:RestoreDBClusterFromS3' :: Text
sourceEngine = Text
a} :: RestoreDBClusterFromS3)

-- | The version of the database that the backup files were created from.
--
-- MySQL versions 5.5, 5.6, and 5.7 are supported.
--
-- Example: @5.6.40@, @5.7.28@
restoreDBClusterFromS3_sourceEngineVersion :: Lens.Lens' RestoreDBClusterFromS3 Prelude.Text
restoreDBClusterFromS3_sourceEngineVersion :: Lens' RestoreDBClusterFromS3 Text
restoreDBClusterFromS3_sourceEngineVersion = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\RestoreDBClusterFromS3' {Text
sourceEngineVersion :: Text
$sel:sourceEngineVersion:RestoreDBClusterFromS3' :: RestoreDBClusterFromS3 -> Text
sourceEngineVersion} -> Text
sourceEngineVersion) (\s :: RestoreDBClusterFromS3
s@RestoreDBClusterFromS3' {} Text
a -> RestoreDBClusterFromS3
s {$sel:sourceEngineVersion:RestoreDBClusterFromS3' :: Text
sourceEngineVersion = Text
a} :: RestoreDBClusterFromS3)

-- | The name of the Amazon S3 bucket that contains the data used to create
-- the Amazon Aurora DB cluster.
restoreDBClusterFromS3_s3BucketName :: Lens.Lens' RestoreDBClusterFromS3 Prelude.Text
restoreDBClusterFromS3_s3BucketName :: Lens' RestoreDBClusterFromS3 Text
restoreDBClusterFromS3_s3BucketName = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\RestoreDBClusterFromS3' {Text
s3BucketName :: Text
$sel:s3BucketName:RestoreDBClusterFromS3' :: RestoreDBClusterFromS3 -> Text
s3BucketName} -> Text
s3BucketName) (\s :: RestoreDBClusterFromS3
s@RestoreDBClusterFromS3' {} Text
a -> RestoreDBClusterFromS3
s {$sel:s3BucketName:RestoreDBClusterFromS3' :: Text
s3BucketName = Text
a} :: RestoreDBClusterFromS3)

-- | The Amazon Resource Name (ARN) of the Amazon Web Services Identity and
-- Access Management (IAM) role that authorizes Amazon RDS to access the
-- Amazon S3 bucket on your behalf.
restoreDBClusterFromS3_s3IngestionRoleArn :: Lens.Lens' RestoreDBClusterFromS3 Prelude.Text
restoreDBClusterFromS3_s3IngestionRoleArn :: Lens' RestoreDBClusterFromS3 Text
restoreDBClusterFromS3_s3IngestionRoleArn = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\RestoreDBClusterFromS3' {Text
s3IngestionRoleArn :: Text
$sel:s3IngestionRoleArn:RestoreDBClusterFromS3' :: RestoreDBClusterFromS3 -> Text
s3IngestionRoleArn} -> Text
s3IngestionRoleArn) (\s :: RestoreDBClusterFromS3
s@RestoreDBClusterFromS3' {} Text
a -> RestoreDBClusterFromS3
s {$sel:s3IngestionRoleArn:RestoreDBClusterFromS3' :: Text
s3IngestionRoleArn = Text
a} :: RestoreDBClusterFromS3)

instance Core.AWSRequest RestoreDBClusterFromS3 where
  type
    AWSResponse RestoreDBClusterFromS3 =
      RestoreDBClusterFromS3Response
  request :: (Service -> Service)
-> RestoreDBClusterFromS3 -> Request RestoreDBClusterFromS3
request Service -> Service
overrides =
    forall a. ToRequest a => Service -> a -> Request a
Request.postQuery (Service -> Service
overrides Service
defaultService)
  response :: forall (m :: * -> *).
MonadResource m =>
(ByteStringLazy -> IO ByteStringLazy)
-> Service
-> Proxy RestoreDBClusterFromS3
-> ClientResponse ClientBody
-> m (Either
        Error (ClientResponse (AWSResponse RestoreDBClusterFromS3)))
response =
    forall (m :: * -> *) a.
MonadResource m =>
Text
-> (Int
    -> ResponseHeaders -> [Node] -> Either String (AWSResponse a))
-> (ByteStringLazy -> IO ByteStringLazy)
-> Service
-> Proxy a
-> ClientResponse ClientBody
-> m (Either Error (ClientResponse (AWSResponse a)))
Response.receiveXMLWrapper
      Text
"RestoreDBClusterFromS3Result"
      ( \Int
s ResponseHeaders
h [Node]
x ->
          Maybe DBCluster -> Int -> RestoreDBClusterFromS3Response
RestoreDBClusterFromS3Response'
            forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
Prelude.<$> ([Node]
x forall a. FromXML a => [Node] -> Text -> Either String (Maybe a)
Data..@? Text
"DBCluster")
            forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
Prelude.<*> (forall (f :: * -> *) a. Applicative f => a -> f a
Prelude.pure (forall a. Enum a => a -> Int
Prelude.fromEnum Int
s))
      )

instance Prelude.Hashable RestoreDBClusterFromS3 where
  hashWithSalt :: Int -> RestoreDBClusterFromS3 -> Int
hashWithSalt Int
_salt RestoreDBClusterFromS3' {Maybe Bool
Maybe Int
Maybe Integer
Maybe [Text]
Maybe [Tag]
Maybe Text
Maybe ServerlessV2ScalingConfiguration
Text
s3IngestionRoleArn :: Text
s3BucketName :: Text
sourceEngineVersion :: Text
sourceEngine :: Text
masterUsername :: Text
engine :: Text
dbClusterIdentifier :: Text
vpcSecurityGroupIds :: Maybe [Text]
tags :: Maybe [Tag]
storageEncrypted :: Maybe Bool
serverlessV2ScalingConfiguration :: Maybe ServerlessV2ScalingConfiguration
s3Prefix :: Maybe Text
preferredMaintenanceWindow :: Maybe Text
preferredBackupWindow :: Maybe Text
port :: Maybe Int
optionGroupName :: Maybe Text
networkType :: Maybe Text
masterUserSecretKmsKeyId :: Maybe Text
masterUserPassword :: Maybe Text
manageMasterUserPassword :: Maybe Bool
kmsKeyId :: Maybe Text
engineVersion :: Maybe Text
enableIAMDatabaseAuthentication :: Maybe Bool
enableCloudwatchLogsExports :: Maybe [Text]
domainIAMRoleName :: Maybe Text
domain :: Maybe Text
deletionProtection :: Maybe Bool
databaseName :: Maybe Text
dbSubnetGroupName :: Maybe Text
dbClusterParameterGroupName :: Maybe Text
copyTagsToSnapshot :: Maybe Bool
characterSetName :: Maybe Text
backupRetentionPeriod :: Maybe Int
backtrackWindow :: Maybe Integer
availabilityZones :: Maybe [Text]
$sel:s3IngestionRoleArn:RestoreDBClusterFromS3' :: RestoreDBClusterFromS3 -> Text
$sel:s3BucketName:RestoreDBClusterFromS3' :: RestoreDBClusterFromS3 -> Text
$sel:sourceEngineVersion:RestoreDBClusterFromS3' :: RestoreDBClusterFromS3 -> Text
$sel:sourceEngine:RestoreDBClusterFromS3' :: RestoreDBClusterFromS3 -> Text
$sel:masterUsername:RestoreDBClusterFromS3' :: RestoreDBClusterFromS3 -> Text
$sel:engine:RestoreDBClusterFromS3' :: RestoreDBClusterFromS3 -> Text
$sel:dbClusterIdentifier:RestoreDBClusterFromS3' :: RestoreDBClusterFromS3 -> Text
$sel:vpcSecurityGroupIds:RestoreDBClusterFromS3' :: RestoreDBClusterFromS3 -> Maybe [Text]
$sel:tags:RestoreDBClusterFromS3' :: RestoreDBClusterFromS3 -> Maybe [Tag]
$sel:storageEncrypted:RestoreDBClusterFromS3' :: RestoreDBClusterFromS3 -> Maybe Bool
$sel:serverlessV2ScalingConfiguration:RestoreDBClusterFromS3' :: RestoreDBClusterFromS3 -> Maybe ServerlessV2ScalingConfiguration
$sel:s3Prefix:RestoreDBClusterFromS3' :: RestoreDBClusterFromS3 -> Maybe Text
$sel:preferredMaintenanceWindow:RestoreDBClusterFromS3' :: RestoreDBClusterFromS3 -> Maybe Text
$sel:preferredBackupWindow:RestoreDBClusterFromS3' :: RestoreDBClusterFromS3 -> Maybe Text
$sel:port:RestoreDBClusterFromS3' :: RestoreDBClusterFromS3 -> Maybe Int
$sel:optionGroupName:RestoreDBClusterFromS3' :: RestoreDBClusterFromS3 -> Maybe Text
$sel:networkType:RestoreDBClusterFromS3' :: RestoreDBClusterFromS3 -> Maybe Text
$sel:masterUserSecretKmsKeyId:RestoreDBClusterFromS3' :: RestoreDBClusterFromS3 -> Maybe Text
$sel:masterUserPassword:RestoreDBClusterFromS3' :: RestoreDBClusterFromS3 -> Maybe Text
$sel:manageMasterUserPassword:RestoreDBClusterFromS3' :: RestoreDBClusterFromS3 -> Maybe Bool
$sel:kmsKeyId:RestoreDBClusterFromS3' :: RestoreDBClusterFromS3 -> Maybe Text
$sel:engineVersion:RestoreDBClusterFromS3' :: RestoreDBClusterFromS3 -> Maybe Text
$sel:enableIAMDatabaseAuthentication:RestoreDBClusterFromS3' :: RestoreDBClusterFromS3 -> Maybe Bool
$sel:enableCloudwatchLogsExports:RestoreDBClusterFromS3' :: RestoreDBClusterFromS3 -> Maybe [Text]
$sel:domainIAMRoleName:RestoreDBClusterFromS3' :: RestoreDBClusterFromS3 -> Maybe Text
$sel:domain:RestoreDBClusterFromS3' :: RestoreDBClusterFromS3 -> Maybe Text
$sel:deletionProtection:RestoreDBClusterFromS3' :: RestoreDBClusterFromS3 -> Maybe Bool
$sel:databaseName:RestoreDBClusterFromS3' :: RestoreDBClusterFromS3 -> Maybe Text
$sel:dbSubnetGroupName:RestoreDBClusterFromS3' :: RestoreDBClusterFromS3 -> Maybe Text
$sel:dbClusterParameterGroupName:RestoreDBClusterFromS3' :: RestoreDBClusterFromS3 -> Maybe Text
$sel:copyTagsToSnapshot:RestoreDBClusterFromS3' :: RestoreDBClusterFromS3 -> Maybe Bool
$sel:characterSetName:RestoreDBClusterFromS3' :: RestoreDBClusterFromS3 -> Maybe Text
$sel:backupRetentionPeriod:RestoreDBClusterFromS3' :: RestoreDBClusterFromS3 -> Maybe Int
$sel:backtrackWindow:RestoreDBClusterFromS3' :: RestoreDBClusterFromS3 -> Maybe Integer
$sel:availabilityZones:RestoreDBClusterFromS3' :: RestoreDBClusterFromS3 -> Maybe [Text]
..} =
    Int
_salt
      forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Maybe [Text]
availabilityZones
      forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Maybe Integer
backtrackWindow
      forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Maybe Int
backupRetentionPeriod
      forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Maybe Text
characterSetName
      forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Maybe Bool
copyTagsToSnapshot
      forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Maybe Text
dbClusterParameterGroupName
      forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Maybe Text
dbSubnetGroupName
      forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Maybe Text
databaseName
      forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Maybe Bool
deletionProtection
      forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Maybe Text
domain
      forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Maybe Text
domainIAMRoleName
      forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Maybe [Text]
enableCloudwatchLogsExports
      forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Maybe Bool
enableIAMDatabaseAuthentication
      forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Maybe Text
engineVersion
      forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Maybe Text
kmsKeyId
      forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Maybe Bool
manageMasterUserPassword
      forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Maybe Text
masterUserPassword
      forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Maybe Text
masterUserSecretKmsKeyId
      forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Maybe Text
networkType
      forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Maybe Text
optionGroupName
      forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Maybe Int
port
      forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Maybe Text
preferredBackupWindow
      forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Maybe Text
preferredMaintenanceWindow
      forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Maybe Text
s3Prefix
      forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Maybe ServerlessV2ScalingConfiguration
serverlessV2ScalingConfiguration
      forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Maybe Bool
storageEncrypted
      forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Maybe [Tag]
tags
      forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Maybe [Text]
vpcSecurityGroupIds
      forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Text
dbClusterIdentifier
      forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Text
engine
      forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Text
masterUsername
      forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Text
sourceEngine
      forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Text
sourceEngineVersion
      forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Text
s3BucketName
      forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Text
s3IngestionRoleArn

instance Prelude.NFData RestoreDBClusterFromS3 where
  rnf :: RestoreDBClusterFromS3 -> ()
rnf RestoreDBClusterFromS3' {Maybe Bool
Maybe Int
Maybe Integer
Maybe [Text]
Maybe [Tag]
Maybe Text
Maybe ServerlessV2ScalingConfiguration
Text
s3IngestionRoleArn :: Text
s3BucketName :: Text
sourceEngineVersion :: Text
sourceEngine :: Text
masterUsername :: Text
engine :: Text
dbClusterIdentifier :: Text
vpcSecurityGroupIds :: Maybe [Text]
tags :: Maybe [Tag]
storageEncrypted :: Maybe Bool
serverlessV2ScalingConfiguration :: Maybe ServerlessV2ScalingConfiguration
s3Prefix :: Maybe Text
preferredMaintenanceWindow :: Maybe Text
preferredBackupWindow :: Maybe Text
port :: Maybe Int
optionGroupName :: Maybe Text
networkType :: Maybe Text
masterUserSecretKmsKeyId :: Maybe Text
masterUserPassword :: Maybe Text
manageMasterUserPassword :: Maybe Bool
kmsKeyId :: Maybe Text
engineVersion :: Maybe Text
enableIAMDatabaseAuthentication :: Maybe Bool
enableCloudwatchLogsExports :: Maybe [Text]
domainIAMRoleName :: Maybe Text
domain :: Maybe Text
deletionProtection :: Maybe Bool
databaseName :: Maybe Text
dbSubnetGroupName :: Maybe Text
dbClusterParameterGroupName :: Maybe Text
copyTagsToSnapshot :: Maybe Bool
characterSetName :: Maybe Text
backupRetentionPeriod :: Maybe Int
backtrackWindow :: Maybe Integer
availabilityZones :: Maybe [Text]
$sel:s3IngestionRoleArn:RestoreDBClusterFromS3' :: RestoreDBClusterFromS3 -> Text
$sel:s3BucketName:RestoreDBClusterFromS3' :: RestoreDBClusterFromS3 -> Text
$sel:sourceEngineVersion:RestoreDBClusterFromS3' :: RestoreDBClusterFromS3 -> Text
$sel:sourceEngine:RestoreDBClusterFromS3' :: RestoreDBClusterFromS3 -> Text
$sel:masterUsername:RestoreDBClusterFromS3' :: RestoreDBClusterFromS3 -> Text
$sel:engine:RestoreDBClusterFromS3' :: RestoreDBClusterFromS3 -> Text
$sel:dbClusterIdentifier:RestoreDBClusterFromS3' :: RestoreDBClusterFromS3 -> Text
$sel:vpcSecurityGroupIds:RestoreDBClusterFromS3' :: RestoreDBClusterFromS3 -> Maybe [Text]
$sel:tags:RestoreDBClusterFromS3' :: RestoreDBClusterFromS3 -> Maybe [Tag]
$sel:storageEncrypted:RestoreDBClusterFromS3' :: RestoreDBClusterFromS3 -> Maybe Bool
$sel:serverlessV2ScalingConfiguration:RestoreDBClusterFromS3' :: RestoreDBClusterFromS3 -> Maybe ServerlessV2ScalingConfiguration
$sel:s3Prefix:RestoreDBClusterFromS3' :: RestoreDBClusterFromS3 -> Maybe Text
$sel:preferredMaintenanceWindow:RestoreDBClusterFromS3' :: RestoreDBClusterFromS3 -> Maybe Text
$sel:preferredBackupWindow:RestoreDBClusterFromS3' :: RestoreDBClusterFromS3 -> Maybe Text
$sel:port:RestoreDBClusterFromS3' :: RestoreDBClusterFromS3 -> Maybe Int
$sel:optionGroupName:RestoreDBClusterFromS3' :: RestoreDBClusterFromS3 -> Maybe Text
$sel:networkType:RestoreDBClusterFromS3' :: RestoreDBClusterFromS3 -> Maybe Text
$sel:masterUserSecretKmsKeyId:RestoreDBClusterFromS3' :: RestoreDBClusterFromS3 -> Maybe Text
$sel:masterUserPassword:RestoreDBClusterFromS3' :: RestoreDBClusterFromS3 -> Maybe Text
$sel:manageMasterUserPassword:RestoreDBClusterFromS3' :: RestoreDBClusterFromS3 -> Maybe Bool
$sel:kmsKeyId:RestoreDBClusterFromS3' :: RestoreDBClusterFromS3 -> Maybe Text
$sel:engineVersion:RestoreDBClusterFromS3' :: RestoreDBClusterFromS3 -> Maybe Text
$sel:enableIAMDatabaseAuthentication:RestoreDBClusterFromS3' :: RestoreDBClusterFromS3 -> Maybe Bool
$sel:enableCloudwatchLogsExports:RestoreDBClusterFromS3' :: RestoreDBClusterFromS3 -> Maybe [Text]
$sel:domainIAMRoleName:RestoreDBClusterFromS3' :: RestoreDBClusterFromS3 -> Maybe Text
$sel:domain:RestoreDBClusterFromS3' :: RestoreDBClusterFromS3 -> Maybe Text
$sel:deletionProtection:RestoreDBClusterFromS3' :: RestoreDBClusterFromS3 -> Maybe Bool
$sel:databaseName:RestoreDBClusterFromS3' :: RestoreDBClusterFromS3 -> Maybe Text
$sel:dbSubnetGroupName:RestoreDBClusterFromS3' :: RestoreDBClusterFromS3 -> Maybe Text
$sel:dbClusterParameterGroupName:RestoreDBClusterFromS3' :: RestoreDBClusterFromS3 -> Maybe Text
$sel:copyTagsToSnapshot:RestoreDBClusterFromS3' :: RestoreDBClusterFromS3 -> Maybe Bool
$sel:characterSetName:RestoreDBClusterFromS3' :: RestoreDBClusterFromS3 -> Maybe Text
$sel:backupRetentionPeriod:RestoreDBClusterFromS3' :: RestoreDBClusterFromS3 -> Maybe Int
$sel:backtrackWindow:RestoreDBClusterFromS3' :: RestoreDBClusterFromS3 -> Maybe Integer
$sel:availabilityZones:RestoreDBClusterFromS3' :: RestoreDBClusterFromS3 -> Maybe [Text]
..} =
    forall a. NFData a => a -> ()
Prelude.rnf Maybe [Text]
availabilityZones
      seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf Maybe Integer
backtrackWindow
      seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf Maybe Int
backupRetentionPeriod
      seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf Maybe Text
characterSetName
      seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf Maybe Bool
copyTagsToSnapshot
      seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf Maybe Text
dbClusterParameterGroupName
      seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf Maybe Text
dbSubnetGroupName
      seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf Maybe Text
databaseName
      seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf Maybe Bool
deletionProtection
      seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf Maybe Text
domain
      seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf Maybe Text
domainIAMRoleName
      seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf Maybe [Text]
enableCloudwatchLogsExports
      seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf Maybe Bool
enableIAMDatabaseAuthentication
      seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf Maybe Text
engineVersion
      seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf Maybe Text
kmsKeyId
      seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf Maybe Bool
manageMasterUserPassword
      seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf Maybe Text
masterUserPassword
      seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf
        Maybe Text
masterUserSecretKmsKeyId
      seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf Maybe Text
networkType
      seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf Maybe Text
optionGroupName
      seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf Maybe Int
port
      seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf
        Maybe Text
preferredBackupWindow
      seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf
        Maybe Text
preferredMaintenanceWindow
      seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf Maybe Text
s3Prefix
      seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf
        Maybe ServerlessV2ScalingConfiguration
serverlessV2ScalingConfiguration
      seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf
        Maybe Bool
storageEncrypted
      seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf Maybe [Tag]
tags
      seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf
        Maybe [Text]
vpcSecurityGroupIds
      seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf
        Text
dbClusterIdentifier
      seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf
        Text
engine
      seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf
        Text
masterUsername
      seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf
        Text
sourceEngine
      seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf
        Text
sourceEngineVersion
      seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf
        Text
s3BucketName
      seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf
        Text
s3IngestionRoleArn

instance Data.ToHeaders RestoreDBClusterFromS3 where
  toHeaders :: RestoreDBClusterFromS3 -> ResponseHeaders
toHeaders = forall a b. a -> b -> a
Prelude.const forall a. Monoid a => a
Prelude.mempty

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

instance Data.ToQuery RestoreDBClusterFromS3 where
  toQuery :: RestoreDBClusterFromS3 -> QueryString
toQuery RestoreDBClusterFromS3' {Maybe Bool
Maybe Int
Maybe Integer
Maybe [Text]
Maybe [Tag]
Maybe Text
Maybe ServerlessV2ScalingConfiguration
Text
s3IngestionRoleArn :: Text
s3BucketName :: Text
sourceEngineVersion :: Text
sourceEngine :: Text
masterUsername :: Text
engine :: Text
dbClusterIdentifier :: Text
vpcSecurityGroupIds :: Maybe [Text]
tags :: Maybe [Tag]
storageEncrypted :: Maybe Bool
serverlessV2ScalingConfiguration :: Maybe ServerlessV2ScalingConfiguration
s3Prefix :: Maybe Text
preferredMaintenanceWindow :: Maybe Text
preferredBackupWindow :: Maybe Text
port :: Maybe Int
optionGroupName :: Maybe Text
networkType :: Maybe Text
masterUserSecretKmsKeyId :: Maybe Text
masterUserPassword :: Maybe Text
manageMasterUserPassword :: Maybe Bool
kmsKeyId :: Maybe Text
engineVersion :: Maybe Text
enableIAMDatabaseAuthentication :: Maybe Bool
enableCloudwatchLogsExports :: Maybe [Text]
domainIAMRoleName :: Maybe Text
domain :: Maybe Text
deletionProtection :: Maybe Bool
databaseName :: Maybe Text
dbSubnetGroupName :: Maybe Text
dbClusterParameterGroupName :: Maybe Text
copyTagsToSnapshot :: Maybe Bool
characterSetName :: Maybe Text
backupRetentionPeriod :: Maybe Int
backtrackWindow :: Maybe Integer
availabilityZones :: Maybe [Text]
$sel:s3IngestionRoleArn:RestoreDBClusterFromS3' :: RestoreDBClusterFromS3 -> Text
$sel:s3BucketName:RestoreDBClusterFromS3' :: RestoreDBClusterFromS3 -> Text
$sel:sourceEngineVersion:RestoreDBClusterFromS3' :: RestoreDBClusterFromS3 -> Text
$sel:sourceEngine:RestoreDBClusterFromS3' :: RestoreDBClusterFromS3 -> Text
$sel:masterUsername:RestoreDBClusterFromS3' :: RestoreDBClusterFromS3 -> Text
$sel:engine:RestoreDBClusterFromS3' :: RestoreDBClusterFromS3 -> Text
$sel:dbClusterIdentifier:RestoreDBClusterFromS3' :: RestoreDBClusterFromS3 -> Text
$sel:vpcSecurityGroupIds:RestoreDBClusterFromS3' :: RestoreDBClusterFromS3 -> Maybe [Text]
$sel:tags:RestoreDBClusterFromS3' :: RestoreDBClusterFromS3 -> Maybe [Tag]
$sel:storageEncrypted:RestoreDBClusterFromS3' :: RestoreDBClusterFromS3 -> Maybe Bool
$sel:serverlessV2ScalingConfiguration:RestoreDBClusterFromS3' :: RestoreDBClusterFromS3 -> Maybe ServerlessV2ScalingConfiguration
$sel:s3Prefix:RestoreDBClusterFromS3' :: RestoreDBClusterFromS3 -> Maybe Text
$sel:preferredMaintenanceWindow:RestoreDBClusterFromS3' :: RestoreDBClusterFromS3 -> Maybe Text
$sel:preferredBackupWindow:RestoreDBClusterFromS3' :: RestoreDBClusterFromS3 -> Maybe Text
$sel:port:RestoreDBClusterFromS3' :: RestoreDBClusterFromS3 -> Maybe Int
$sel:optionGroupName:RestoreDBClusterFromS3' :: RestoreDBClusterFromS3 -> Maybe Text
$sel:networkType:RestoreDBClusterFromS3' :: RestoreDBClusterFromS3 -> Maybe Text
$sel:masterUserSecretKmsKeyId:RestoreDBClusterFromS3' :: RestoreDBClusterFromS3 -> Maybe Text
$sel:masterUserPassword:RestoreDBClusterFromS3' :: RestoreDBClusterFromS3 -> Maybe Text
$sel:manageMasterUserPassword:RestoreDBClusterFromS3' :: RestoreDBClusterFromS3 -> Maybe Bool
$sel:kmsKeyId:RestoreDBClusterFromS3' :: RestoreDBClusterFromS3 -> Maybe Text
$sel:engineVersion:RestoreDBClusterFromS3' :: RestoreDBClusterFromS3 -> Maybe Text
$sel:enableIAMDatabaseAuthentication:RestoreDBClusterFromS3' :: RestoreDBClusterFromS3 -> Maybe Bool
$sel:enableCloudwatchLogsExports:RestoreDBClusterFromS3' :: RestoreDBClusterFromS3 -> Maybe [Text]
$sel:domainIAMRoleName:RestoreDBClusterFromS3' :: RestoreDBClusterFromS3 -> Maybe Text
$sel:domain:RestoreDBClusterFromS3' :: RestoreDBClusterFromS3 -> Maybe Text
$sel:deletionProtection:RestoreDBClusterFromS3' :: RestoreDBClusterFromS3 -> Maybe Bool
$sel:databaseName:RestoreDBClusterFromS3' :: RestoreDBClusterFromS3 -> Maybe Text
$sel:dbSubnetGroupName:RestoreDBClusterFromS3' :: RestoreDBClusterFromS3 -> Maybe Text
$sel:dbClusterParameterGroupName:RestoreDBClusterFromS3' :: RestoreDBClusterFromS3 -> Maybe Text
$sel:copyTagsToSnapshot:RestoreDBClusterFromS3' :: RestoreDBClusterFromS3 -> Maybe Bool
$sel:characterSetName:RestoreDBClusterFromS3' :: RestoreDBClusterFromS3 -> Maybe Text
$sel:backupRetentionPeriod:RestoreDBClusterFromS3' :: RestoreDBClusterFromS3 -> Maybe Int
$sel:backtrackWindow:RestoreDBClusterFromS3' :: RestoreDBClusterFromS3 -> Maybe Integer
$sel:availabilityZones:RestoreDBClusterFromS3' :: RestoreDBClusterFromS3 -> Maybe [Text]
..} =
    forall a. Monoid a => [a] -> a
Prelude.mconcat
      [ ByteString
"Action"
          forall a. ToQuery a => ByteString -> a -> QueryString
Data.=: (ByteString
"RestoreDBClusterFromS3" :: Prelude.ByteString),
        ByteString
"Version"
          forall a. ToQuery a => ByteString -> a -> QueryString
Data.=: (ByteString
"2014-10-31" :: Prelude.ByteString),
        ByteString
"AvailabilityZones"
          forall a. ToQuery a => ByteString -> a -> QueryString
Data.=: forall a. ToQuery a => a -> QueryString
Data.toQuery
            ( forall a.
(IsList a, ToQuery (Item a)) =>
ByteString -> a -> QueryString
Data.toQueryList ByteString
"AvailabilityZone"
                forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
Prelude.<$> Maybe [Text]
availabilityZones
            ),
        ByteString
"BacktrackWindow" forall a. ToQuery a => ByteString -> a -> QueryString
Data.=: Maybe Integer
backtrackWindow,
        ByteString
"BackupRetentionPeriod"
          forall a. ToQuery a => ByteString -> a -> QueryString
Data.=: Maybe Int
backupRetentionPeriod,
        ByteString
"CharacterSetName" forall a. ToQuery a => ByteString -> a -> QueryString
Data.=: Maybe Text
characterSetName,
        ByteString
"CopyTagsToSnapshot" forall a. ToQuery a => ByteString -> a -> QueryString
Data.=: Maybe Bool
copyTagsToSnapshot,
        ByteString
"DBClusterParameterGroupName"
          forall a. ToQuery a => ByteString -> a -> QueryString
Data.=: Maybe Text
dbClusterParameterGroupName,
        ByteString
"DBSubnetGroupName" forall a. ToQuery a => ByteString -> a -> QueryString
Data.=: Maybe Text
dbSubnetGroupName,
        ByteString
"DatabaseName" forall a. ToQuery a => ByteString -> a -> QueryString
Data.=: Maybe Text
databaseName,
        ByteString
"DeletionProtection" forall a. ToQuery a => ByteString -> a -> QueryString
Data.=: Maybe Bool
deletionProtection,
        ByteString
"Domain" forall a. ToQuery a => ByteString -> a -> QueryString
Data.=: Maybe Text
domain,
        ByteString
"DomainIAMRoleName" forall a. ToQuery a => ByteString -> a -> QueryString
Data.=: Maybe Text
domainIAMRoleName,
        ByteString
"EnableCloudwatchLogsExports"
          forall a. ToQuery a => ByteString -> a -> QueryString
Data.=: forall a. ToQuery a => a -> QueryString
Data.toQuery
            ( forall a.
(IsList a, ToQuery (Item a)) =>
ByteString -> a -> QueryString
Data.toQueryList ByteString
"member"
                forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
Prelude.<$> Maybe [Text]
enableCloudwatchLogsExports
            ),
        ByteString
"EnableIAMDatabaseAuthentication"
          forall a. ToQuery a => ByteString -> a -> QueryString
Data.=: Maybe Bool
enableIAMDatabaseAuthentication,
        ByteString
"EngineVersion" forall a. ToQuery a => ByteString -> a -> QueryString
Data.=: Maybe Text
engineVersion,
        ByteString
"KmsKeyId" forall a. ToQuery a => ByteString -> a -> QueryString
Data.=: Maybe Text
kmsKeyId,
        ByteString
"ManageMasterUserPassword"
          forall a. ToQuery a => ByteString -> a -> QueryString
Data.=: Maybe Bool
manageMasterUserPassword,
        ByteString
"MasterUserPassword" forall a. ToQuery a => ByteString -> a -> QueryString
Data.=: Maybe Text
masterUserPassword,
        ByteString
"MasterUserSecretKmsKeyId"
          forall a. ToQuery a => ByteString -> a -> QueryString
Data.=: Maybe Text
masterUserSecretKmsKeyId,
        ByteString
"NetworkType" forall a. ToQuery a => ByteString -> a -> QueryString
Data.=: Maybe Text
networkType,
        ByteString
"OptionGroupName" forall a. ToQuery a => ByteString -> a -> QueryString
Data.=: Maybe Text
optionGroupName,
        ByteString
"Port" forall a. ToQuery a => ByteString -> a -> QueryString
Data.=: Maybe Int
port,
        ByteString
"PreferredBackupWindow"
          forall a. ToQuery a => ByteString -> a -> QueryString
Data.=: Maybe Text
preferredBackupWindow,
        ByteString
"PreferredMaintenanceWindow"
          forall a. ToQuery a => ByteString -> a -> QueryString
Data.=: Maybe Text
preferredMaintenanceWindow,
        ByteString
"S3Prefix" forall a. ToQuery a => ByteString -> a -> QueryString
Data.=: Maybe Text
s3Prefix,
        ByteString
"ServerlessV2ScalingConfiguration"
          forall a. ToQuery a => ByteString -> a -> QueryString
Data.=: Maybe ServerlessV2ScalingConfiguration
serverlessV2ScalingConfiguration,
        ByteString
"StorageEncrypted" forall a. ToQuery a => ByteString -> a -> QueryString
Data.=: Maybe Bool
storageEncrypted,
        ByteString
"Tags"
          forall a. ToQuery a => ByteString -> a -> QueryString
Data.=: forall a. ToQuery a => a -> QueryString
Data.toQuery
            (forall a.
(IsList a, ToQuery (Item a)) =>
ByteString -> a -> QueryString
Data.toQueryList ByteString
"Tag" forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
Prelude.<$> Maybe [Tag]
tags),
        ByteString
"VpcSecurityGroupIds"
          forall a. ToQuery a => ByteString -> a -> QueryString
Data.=: forall a. ToQuery a => a -> QueryString
Data.toQuery
            ( forall a.
(IsList a, ToQuery (Item a)) =>
ByteString -> a -> QueryString
Data.toQueryList ByteString
"VpcSecurityGroupId"
                forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
Prelude.<$> Maybe [Text]
vpcSecurityGroupIds
            ),
        ByteString
"DBClusterIdentifier" forall a. ToQuery a => ByteString -> a -> QueryString
Data.=: Text
dbClusterIdentifier,
        ByteString
"Engine" forall a. ToQuery a => ByteString -> a -> QueryString
Data.=: Text
engine,
        ByteString
"MasterUsername" forall a. ToQuery a => ByteString -> a -> QueryString
Data.=: Text
masterUsername,
        ByteString
"SourceEngine" forall a. ToQuery a => ByteString -> a -> QueryString
Data.=: Text
sourceEngine,
        ByteString
"SourceEngineVersion" forall a. ToQuery a => ByteString -> a -> QueryString
Data.=: Text
sourceEngineVersion,
        ByteString
"S3BucketName" forall a. ToQuery a => ByteString -> a -> QueryString
Data.=: Text
s3BucketName,
        ByteString
"S3IngestionRoleArn" forall a. ToQuery a => ByteString -> a -> QueryString
Data.=: Text
s3IngestionRoleArn
      ]

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

-- |
-- Create a value of 'RestoreDBClusterFromS3Response' with all optional fields omitted.
--
-- Use <https://hackage.haskell.org/package/generic-lens generic-lens> or <https://hackage.haskell.org/package/optics optics> to modify other optional fields.
--
-- The following record fields are available, with the corresponding lenses provided
-- for backwards compatibility:
--
-- 'dbCluster', 'restoreDBClusterFromS3Response_dbCluster' - Undocumented member.
--
-- 'httpStatus', 'restoreDBClusterFromS3Response_httpStatus' - The response's http status code.
newRestoreDBClusterFromS3Response ::
  -- | 'httpStatus'
  Prelude.Int ->
  RestoreDBClusterFromS3Response
newRestoreDBClusterFromS3Response :: Int -> RestoreDBClusterFromS3Response
newRestoreDBClusterFromS3Response Int
pHttpStatus_ =
  RestoreDBClusterFromS3Response'
    { $sel:dbCluster:RestoreDBClusterFromS3Response' :: Maybe DBCluster
dbCluster =
        forall a. Maybe a
Prelude.Nothing,
      $sel:httpStatus:RestoreDBClusterFromS3Response' :: Int
httpStatus = Int
pHttpStatus_
    }

-- | Undocumented member.
restoreDBClusterFromS3Response_dbCluster :: Lens.Lens' RestoreDBClusterFromS3Response (Prelude.Maybe DBCluster)
restoreDBClusterFromS3Response_dbCluster :: Lens' RestoreDBClusterFromS3Response (Maybe DBCluster)
restoreDBClusterFromS3Response_dbCluster = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\RestoreDBClusterFromS3Response' {Maybe DBCluster
dbCluster :: Maybe DBCluster
$sel:dbCluster:RestoreDBClusterFromS3Response' :: RestoreDBClusterFromS3Response -> Maybe DBCluster
dbCluster} -> Maybe DBCluster
dbCluster) (\s :: RestoreDBClusterFromS3Response
s@RestoreDBClusterFromS3Response' {} Maybe DBCluster
a -> RestoreDBClusterFromS3Response
s {$sel:dbCluster:RestoreDBClusterFromS3Response' :: Maybe DBCluster
dbCluster = Maybe DBCluster
a} :: RestoreDBClusterFromS3Response)

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

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