{-# 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.RestoreDBInstanceFromS3
-- Copyright   : (c) 2013-2023 Brendan Hay
-- License     : Mozilla Public License, v. 2.0.
-- Maintainer  : Brendan Hay
-- Stability   : auto-generated
-- Portability : non-portable (GHC extensions)
--
-- Amazon Relational Database Service (Amazon RDS) supports importing MySQL
-- databases by using backup files. You can create a backup of your
-- on-premises database, store it on Amazon Simple Storage Service (Amazon
-- S3), and then restore the backup file onto a new Amazon RDS DB instance
-- running MySQL. For more information, see
-- <https://docs.aws.amazon.com/AmazonRDS/latest/UserGuide/MySQL.Procedural.Importing.html Importing Data into an Amazon RDS MySQL DB Instance>
-- in the /Amazon RDS User Guide./
--
-- This command doesn\'t apply to RDS Custom.
module Amazonka.RDS.RestoreDBInstanceFromS3
  ( -- * Creating a Request
    RestoreDBInstanceFromS3 (..),
    newRestoreDBInstanceFromS3,

    -- * Request Lenses
    restoreDBInstanceFromS3_allocatedStorage,
    restoreDBInstanceFromS3_autoMinorVersionUpgrade,
    restoreDBInstanceFromS3_availabilityZone,
    restoreDBInstanceFromS3_backupRetentionPeriod,
    restoreDBInstanceFromS3_copyTagsToSnapshot,
    restoreDBInstanceFromS3_dbName,
    restoreDBInstanceFromS3_dbParameterGroupName,
    restoreDBInstanceFromS3_dbSecurityGroups,
    restoreDBInstanceFromS3_dbSubnetGroupName,
    restoreDBInstanceFromS3_deletionProtection,
    restoreDBInstanceFromS3_enableCloudwatchLogsExports,
    restoreDBInstanceFromS3_enableIAMDatabaseAuthentication,
    restoreDBInstanceFromS3_enablePerformanceInsights,
    restoreDBInstanceFromS3_engineVersion,
    restoreDBInstanceFromS3_iops,
    restoreDBInstanceFromS3_kmsKeyId,
    restoreDBInstanceFromS3_licenseModel,
    restoreDBInstanceFromS3_manageMasterUserPassword,
    restoreDBInstanceFromS3_masterUserPassword,
    restoreDBInstanceFromS3_masterUserSecretKmsKeyId,
    restoreDBInstanceFromS3_masterUsername,
    restoreDBInstanceFromS3_maxAllocatedStorage,
    restoreDBInstanceFromS3_monitoringInterval,
    restoreDBInstanceFromS3_monitoringRoleArn,
    restoreDBInstanceFromS3_multiAZ,
    restoreDBInstanceFromS3_networkType,
    restoreDBInstanceFromS3_optionGroupName,
    restoreDBInstanceFromS3_performanceInsightsKMSKeyId,
    restoreDBInstanceFromS3_performanceInsightsRetentionPeriod,
    restoreDBInstanceFromS3_port,
    restoreDBInstanceFromS3_preferredBackupWindow,
    restoreDBInstanceFromS3_preferredMaintenanceWindow,
    restoreDBInstanceFromS3_processorFeatures,
    restoreDBInstanceFromS3_publiclyAccessible,
    restoreDBInstanceFromS3_s3Prefix,
    restoreDBInstanceFromS3_storageEncrypted,
    restoreDBInstanceFromS3_storageThroughput,
    restoreDBInstanceFromS3_storageType,
    restoreDBInstanceFromS3_tags,
    restoreDBInstanceFromS3_useDefaultProcessorFeatures,
    restoreDBInstanceFromS3_vpcSecurityGroupIds,
    restoreDBInstanceFromS3_dbInstanceIdentifier,
    restoreDBInstanceFromS3_dbInstanceClass,
    restoreDBInstanceFromS3_engine,
    restoreDBInstanceFromS3_sourceEngine,
    restoreDBInstanceFromS3_sourceEngineVersion,
    restoreDBInstanceFromS3_s3BucketName,
    restoreDBInstanceFromS3_s3IngestionRoleArn,

    -- * Destructuring the Response
    RestoreDBInstanceFromS3Response (..),
    newRestoreDBInstanceFromS3Response,

    -- * Response Lenses
    restoreDBInstanceFromS3Response_dbInstance,
    restoreDBInstanceFromS3Response_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:/ 'newRestoreDBInstanceFromS3' smart constructor.
data RestoreDBInstanceFromS3 = RestoreDBInstanceFromS3'
  { -- | The amount of storage (in gigabytes) to allocate initially for the DB
    -- instance. Follow the allocation rules specified in @CreateDBInstance@.
    --
    -- Be sure to allocate enough memory for your new DB instance so that the
    -- restore operation can succeed. You can also allocate additional memory
    -- for future growth.
    RestoreDBInstanceFromS3 -> Maybe Int
allocatedStorage :: Prelude.Maybe Prelude.Int,
    -- | A value that indicates whether minor engine upgrades are applied
    -- automatically to the DB instance during the maintenance window. By
    -- default, minor engine upgrades are not applied automatically.
    RestoreDBInstanceFromS3 -> Maybe Bool
autoMinorVersionUpgrade :: Prelude.Maybe Prelude.Bool,
    -- | The Availability Zone that the DB instance is created in. For
    -- information about Amazon Web Services Regions and Availability Zones,
    -- see
    -- <https://docs.aws.amazon.com/AmazonRDS/latest/UserGuide/Concepts.RegionsAndAvailabilityZones.html Regions and Availability Zones>
    -- in the /Amazon RDS User Guide./
    --
    -- Default: A random, system-chosen Availability Zone in the endpoint\'s
    -- Amazon Web Services Region.
    --
    -- Example: @us-east-1d@
    --
    -- Constraint: The @AvailabilityZone@ parameter can\'t be specified if the
    -- DB instance is a Multi-AZ deployment. The specified Availability Zone
    -- must be in the same Amazon Web Services Region as the current endpoint.
    RestoreDBInstanceFromS3 -> Maybe Text
availabilityZone :: Prelude.Maybe Prelude.Text,
    -- | The number of days for which automated backups are retained. Setting
    -- this parameter to a positive number enables backups. For more
    -- information, see @CreateDBInstance@.
    RestoreDBInstanceFromS3 -> Maybe Int
backupRetentionPeriod :: Prelude.Maybe Prelude.Int,
    -- | A value that indicates whether to copy all tags from the DB instance to
    -- snapshots of the DB instance. By default, tags are not copied.
    RestoreDBInstanceFromS3 -> Maybe Bool
copyTagsToSnapshot :: Prelude.Maybe Prelude.Bool,
    -- | The name of the database to create when the DB instance is created.
    -- Follow the naming rules specified in @CreateDBInstance@.
    RestoreDBInstanceFromS3 -> Maybe Text
dbName :: Prelude.Maybe Prelude.Text,
    -- | The name of the DB parameter group to associate with this DB instance.
    --
    -- If you do not specify a value for @DBParameterGroupName@, then the
    -- default @DBParameterGroup@ for the specified DB engine is used.
    RestoreDBInstanceFromS3 -> Maybe Text
dbParameterGroupName :: Prelude.Maybe Prelude.Text,
    -- | A list of DB security groups to associate with this DB instance.
    --
    -- Default: The default DB security group for the database engine.
    RestoreDBInstanceFromS3 -> Maybe [Text]
dbSecurityGroups :: Prelude.Maybe [Prelude.Text],
    -- | A DB subnet group to associate with this DB instance.
    --
    -- Constraints: If supplied, must match the name of an existing
    -- DBSubnetGroup.
    --
    -- Example: @mydbsubnetgroup@
    RestoreDBInstanceFromS3 -> Maybe Text
dbSubnetGroupName :: Prelude.Maybe Prelude.Text,
    -- | A value that indicates whether the DB instance has deletion protection
    -- enabled. The database can\'t be deleted when deletion protection is
    -- enabled. By default, deletion protection isn\'t enabled. For more
    -- information, see
    -- <https://docs.aws.amazon.com/AmazonRDS/latest/UserGuide/USER_DeleteInstance.html Deleting a DB Instance>.
    RestoreDBInstanceFromS3 -> Maybe Bool
deletionProtection :: Prelude.Maybe Prelude.Bool,
    -- | The list of logs that the restored DB instance is to export to
    -- CloudWatch Logs. The values in the list depend on the DB engine being
    -- used. For more information, see
    -- <https://docs.aws.amazon.com/AmazonRDS/latest/UserGuide/USER_LogAccess.html#USER_LogAccess.Procedural.UploadtoCloudWatch Publishing Database Logs to Amazon CloudWatch Logs>
    -- in the /Amazon RDS User Guide/.
    RestoreDBInstanceFromS3 -> 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 about IAM database authentication, see
    -- <https://docs.aws.amazon.com/AmazonRDS/latest/UserGuide/UsingWithRDS.IAMDBAuth.html IAM Database Authentication for MySQL and PostgreSQL>
    -- in the /Amazon RDS User Guide./
    RestoreDBInstanceFromS3 -> Maybe Bool
enableIAMDatabaseAuthentication :: Prelude.Maybe Prelude.Bool,
    -- | A value that indicates whether to enable Performance Insights for the DB
    -- instance.
    --
    -- For more information, see
    -- <https://docs.aws.amazon.com/AmazonRDS/latest/UserGuide/USER_PerfInsights.html Using Amazon Performance Insights>
    -- in the /Amazon RDS User Guide/.
    RestoreDBInstanceFromS3 -> Maybe Bool
enablePerformanceInsights :: Prelude.Maybe Prelude.Bool,
    -- | The version number of the database engine to use. Choose the latest
    -- minor version of your database engine. For information about engine
    -- versions, see @CreateDBInstance@, or call @DescribeDBEngineVersions@.
    RestoreDBInstanceFromS3 -> Maybe Text
engineVersion :: Prelude.Maybe Prelude.Text,
    -- | The amount of Provisioned IOPS (input\/output operations per second) to
    -- allocate initially for the DB instance. For information about valid IOPS
    -- values, see
    -- <https://docs.aws.amazon.com/AmazonRDS/latest/UserGuide/CHAP_Storage.html#USER_PIOPS Amazon RDS Provisioned IOPS storage>
    -- in the /Amazon RDS User Guide./
    RestoreDBInstanceFromS3 -> Maybe Int
iops :: Prelude.Maybe Prelude.Int,
    -- | The Amazon Web Services KMS key identifier for an encrypted DB instance.
    --
    -- 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.
    RestoreDBInstanceFromS3 -> Maybe Text
kmsKeyId :: Prelude.Maybe Prelude.Text,
    -- | The license model for this DB instance. Use @general-public-license@.
    RestoreDBInstanceFromS3 -> Maybe Text
licenseModel :: 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./
    --
    -- Constraints:
    --
    -- -   Can\'t manage the master user password with Amazon Web Services
    --     Secrets Manager if @MasterUserPassword@ is specified.
    RestoreDBInstanceFromS3 -> Maybe Bool
manageMasterUserPassword :: Prelude.Maybe Prelude.Bool,
    -- | The password for the master user. The password can include any printable
    -- ASCII character except \"\/\", \"\"\", or \"\@\".
    --
    -- Constraints: Can\'t be specified if @ManageMasterUserPassword@ is turned
    -- on.
    --
    -- __MariaDB__
    --
    -- Constraints: Must contain from 8 to 41 characters.
    --
    -- __Microsoft SQL Server__
    --
    -- Constraints: Must contain from 8 to 128 characters.
    --
    -- __MySQL__
    --
    -- Constraints: Must contain from 8 to 41 characters.
    --
    -- __Oracle__
    --
    -- Constraints: Must contain from 8 to 30 characters.
    --
    -- __PostgreSQL__
    --
    -- Constraints: Must contain from 8 to 128 characters.
    RestoreDBInstanceFromS3 -> 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 instance.
    --
    -- 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.
    RestoreDBInstanceFromS3 -> Maybe Text
masterUserSecretKmsKeyId :: Prelude.Maybe Prelude.Text,
    -- | The name for the master user.
    --
    -- 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.
    RestoreDBInstanceFromS3 -> Maybe Text
masterUsername :: Prelude.Maybe Prelude.Text,
    -- | The upper limit in gibibytes (GiB) to which Amazon RDS can automatically
    -- scale the storage of the DB instance.
    --
    -- For more information about this setting, including limitations that
    -- apply to it, see
    -- <https://docs.aws.amazon.com/AmazonRDS/latest/UserGuide/USER_PIOPS.StorageTypes.html#USER_PIOPS.Autoscaling Managing capacity automatically with Amazon RDS storage autoscaling>
    -- in the /Amazon RDS User Guide/.
    RestoreDBInstanceFromS3 -> Maybe Int
maxAllocatedStorage :: Prelude.Maybe Prelude.Int,
    -- | The interval, in seconds, between points when Enhanced Monitoring
    -- metrics are collected for the DB instance. To disable collecting
    -- Enhanced Monitoring metrics, specify 0.
    --
    -- If @MonitoringRoleArn@ is specified, then you must also set
    -- @MonitoringInterval@ to a value other than 0.
    --
    -- Valid Values: 0, 1, 5, 10, 15, 30, 60
    --
    -- Default: @0@
    RestoreDBInstanceFromS3 -> Maybe Int
monitoringInterval :: Prelude.Maybe Prelude.Int,
    -- | The ARN for the IAM role that permits RDS to send enhanced monitoring
    -- metrics to Amazon CloudWatch Logs. For example,
    -- @arn:aws:iam:123456789012:role\/emaccess@. For information on creating a
    -- monitoring role, see
    -- <https://docs.aws.amazon.com/AmazonRDS/latest/UserGuide/USER_Monitoring.OS.html#USER_Monitoring.OS.Enabling Setting Up and Enabling Enhanced Monitoring>
    -- in the /Amazon RDS User Guide./
    --
    -- If @MonitoringInterval@ is set to a value other than 0, then you must
    -- supply a @MonitoringRoleArn@ value.
    RestoreDBInstanceFromS3 -> Maybe Text
monitoringRoleArn :: Prelude.Maybe Prelude.Text,
    -- | A value that indicates whether the DB instance is a Multi-AZ deployment.
    -- If the DB instance is a Multi-AZ deployment, you can\'t set the
    -- @AvailabilityZone@ parameter.
    RestoreDBInstanceFromS3 -> Maybe Bool
multiAZ :: Prelude.Maybe Prelude.Bool,
    -- | The network type of the DB instance.
    --
    -- Valid values:
    --
    -- -   @IPV4@
    --
    -- -   @DUAL@
    --
    -- The network type is determined by the @DBSubnetGroup@ specified for the
    -- DB instance. 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/UserGuide/USER_VPC.WorkingWithRDSInstanceinaVPC.html Working with a DB instance in a VPC>
    -- in the /Amazon RDS User Guide./
    RestoreDBInstanceFromS3 -> Maybe Text
networkType :: Prelude.Maybe Prelude.Text,
    -- | The name of the option group to associate with this DB instance. If this
    -- argument is omitted, the default option group for the specified engine
    -- is used.
    RestoreDBInstanceFromS3 -> Maybe Text
optionGroupName :: Prelude.Maybe Prelude.Text,
    -- | The Amazon Web Services KMS key identifier for encryption of Performance
    -- Insights data.
    --
    -- The Amazon Web Services KMS key identifier is the key ARN, key ID, alias
    -- ARN, or alias name for the KMS key.
    --
    -- If you do not specify a value for @PerformanceInsightsKMSKeyId@, then
    -- Amazon RDS uses 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.
    RestoreDBInstanceFromS3 -> Maybe Text
performanceInsightsKMSKeyId :: Prelude.Maybe Prelude.Text,
    -- | The number of days to retain Performance Insights data. The default is 7
    -- days. The following values are valid:
    --
    -- -   7
    --
    -- -   /month/ * 31, where /month/ is a number of months from 1-23
    --
    -- -   731
    --
    -- For example, the following values are valid:
    --
    -- -   93 (3 months * 31)
    --
    -- -   341 (11 months * 31)
    --
    -- -   589 (19 months * 31)
    --
    -- -   731
    --
    -- If you specify a retention period such as 94, which isn\'t a valid
    -- value, RDS issues an error.
    RestoreDBInstanceFromS3 -> Maybe Int
performanceInsightsRetentionPeriod :: Prelude.Maybe Prelude.Int,
    -- | The port number on which the database accepts connections.
    --
    -- Type: Integer
    --
    -- Valid Values: @1150@-@65535@
    --
    -- Default: @3306@
    RestoreDBInstanceFromS3 -> Maybe Int
port :: Prelude.Maybe Prelude.Int,
    -- | The time range each day during which automated backups are created if
    -- automated backups are enabled. For more information, see
    -- <https://docs.aws.amazon.com/AmazonRDS/latest/UserGuide/USER_WorkingWithAutomatedBackups.html#USER_WorkingWithAutomatedBackups.BackupWindow Backup window>
    -- in the /Amazon RDS 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.
    RestoreDBInstanceFromS3 -> Maybe Text
preferredBackupWindow :: Prelude.Maybe Prelude.Text,
    -- | The time range each week during which system maintenance can occur, in
    -- Universal Coordinated Time (UTC). For more information, see
    -- <https://docs.aws.amazon.com/AmazonRDS/latest/UserGuide/USER_UpgradeDBInstance.Maintenance.html#Concepts.DBMaintenance Amazon RDS Maintenance Window>
    -- in the /Amazon RDS User Guide./
    --
    -- Constraints:
    --
    -- -   Must be in the format @ddd:hh24:mi-ddd:hh24:mi@.
    --
    -- -   Valid Days: Mon, Tue, Wed, Thu, Fri, Sat, Sun.
    --
    -- -   Must be in Universal Coordinated Time (UTC).
    --
    -- -   Must not conflict with the preferred backup window.
    --
    -- -   Must be at least 30 minutes.
    RestoreDBInstanceFromS3 -> Maybe Text
preferredMaintenanceWindow :: Prelude.Maybe Prelude.Text,
    -- | The number of CPU cores and the number of threads per core for the DB
    -- instance class of the DB instance.
    RestoreDBInstanceFromS3 -> Maybe [ProcessorFeature]
processorFeatures :: Prelude.Maybe [ProcessorFeature],
    -- | A value that indicates whether the DB instance is publicly accessible.
    --
    -- When the DB instance is publicly accessible, its Domain Name System
    -- (DNS) endpoint resolves to the private IP address from within the DB
    -- instance\'s virtual private cloud (VPC). It resolves to the public IP
    -- address from outside of the DB instance\'s VPC. Access to the DB
    -- instance is ultimately controlled by the security group it uses. That
    -- public access is not permitted if the security group assigned to the DB
    -- instance doesn\'t permit it.
    --
    -- When the DB instance isn\'t publicly accessible, it is an internal DB
    -- instance with a DNS name that resolves to a private IP address.
    --
    -- For more information, see CreateDBInstance.
    RestoreDBInstanceFromS3 -> Maybe Bool
publiclyAccessible :: Prelude.Maybe Prelude.Bool,
    -- | The prefix of your Amazon S3 bucket.
    RestoreDBInstanceFromS3 -> Maybe Text
s3Prefix :: Prelude.Maybe Prelude.Text,
    -- | A value that indicates whether the new DB instance is encrypted or not.
    RestoreDBInstanceFromS3 -> Maybe Bool
storageEncrypted :: Prelude.Maybe Prelude.Bool,
    -- | Specifies the storage throughput value for the DB instance.
    --
    -- This setting doesn\'t apply to RDS Custom or Amazon Aurora.
    RestoreDBInstanceFromS3 -> Maybe Int
storageThroughput :: Prelude.Maybe Prelude.Int,
    -- | Specifies the storage type to be associated with the DB instance.
    --
    -- Valid values: @gp2 | gp3 | io1 | standard@
    --
    -- If you specify @io1@ or @gp3@, you must also include a value for the
    -- @Iops@ parameter.
    --
    -- Default: @io1@ if the @Iops@ parameter is specified; otherwise @gp2@
    RestoreDBInstanceFromS3 -> Maybe Text
storageType :: Prelude.Maybe Prelude.Text,
    -- | A list of tags to associate with this DB instance. For more information,
    -- see
    -- <https://docs.aws.amazon.com/AmazonRDS/latest/UserGuide/USER_Tagging.html Tagging Amazon RDS Resources>
    -- in the /Amazon RDS User Guide./
    RestoreDBInstanceFromS3 -> Maybe [Tag]
tags :: Prelude.Maybe [Tag],
    -- | A value that indicates whether the DB instance class of the DB instance
    -- uses its default processor features.
    RestoreDBInstanceFromS3 -> Maybe Bool
useDefaultProcessorFeatures :: Prelude.Maybe Prelude.Bool,
    -- | A list of VPC security groups to associate with this DB instance.
    RestoreDBInstanceFromS3 -> Maybe [Text]
vpcSecurityGroupIds :: Prelude.Maybe [Prelude.Text],
    -- | The DB instance identifier. This parameter is stored as a lowercase
    -- string.
    --
    -- 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: @mydbinstance@
    RestoreDBInstanceFromS3 -> Text
dbInstanceIdentifier :: Prelude.Text,
    -- | The compute and memory capacity of the DB instance, for example
    -- db.m4.large. Not all DB instance classes are available in all Amazon Web
    -- Services Regions, or for all database engines. For the full list of DB
    -- instance classes, and availability for your engine, see
    -- <https://docs.aws.amazon.com/AmazonRDS/latest/UserGuide/Concepts.DBInstanceClass.html DB Instance Class>
    -- in the /Amazon RDS User Guide./
    --
    -- Importing from Amazon S3 isn\'t supported on the db.t2.micro DB instance
    -- class.
    RestoreDBInstanceFromS3 -> Text
dbInstanceClass :: Prelude.Text,
    -- | The name of the database engine to be used for this instance.
    --
    -- Valid Values: @mysql@
    RestoreDBInstanceFromS3 -> Text
engine :: Prelude.Text,
    -- | The name of the engine of your source database.
    --
    -- Valid Values: @mysql@
    RestoreDBInstanceFromS3 -> Text
sourceEngine :: Prelude.Text,
    -- | The version of the database that the backup files were created from.
    --
    -- MySQL versions 5.6 and 5.7 are supported.
    --
    -- Example: @5.6.40@
    RestoreDBInstanceFromS3 -> Text
sourceEngineVersion :: Prelude.Text,
    -- | The name of your Amazon S3 bucket that contains your database backup
    -- file.
    RestoreDBInstanceFromS3 -> Text
s3BucketName :: Prelude.Text,
    -- | An Amazon Web Services Identity and Access Management (IAM) role to
    -- allow Amazon RDS to access your Amazon S3 bucket.
    RestoreDBInstanceFromS3 -> Text
s3IngestionRoleArn :: Prelude.Text
  }
  deriving (RestoreDBInstanceFromS3 -> RestoreDBInstanceFromS3 -> Bool
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: RestoreDBInstanceFromS3 -> RestoreDBInstanceFromS3 -> Bool
$c/= :: RestoreDBInstanceFromS3 -> RestoreDBInstanceFromS3 -> Bool
== :: RestoreDBInstanceFromS3 -> RestoreDBInstanceFromS3 -> Bool
$c== :: RestoreDBInstanceFromS3 -> RestoreDBInstanceFromS3 -> Bool
Prelude.Eq, ReadPrec [RestoreDBInstanceFromS3]
ReadPrec RestoreDBInstanceFromS3
Int -> ReadS RestoreDBInstanceFromS3
ReadS [RestoreDBInstanceFromS3]
forall a.
(Int -> ReadS a)
-> ReadS [a] -> ReadPrec a -> ReadPrec [a] -> Read a
readListPrec :: ReadPrec [RestoreDBInstanceFromS3]
$creadListPrec :: ReadPrec [RestoreDBInstanceFromS3]
readPrec :: ReadPrec RestoreDBInstanceFromS3
$creadPrec :: ReadPrec RestoreDBInstanceFromS3
readList :: ReadS [RestoreDBInstanceFromS3]
$creadList :: ReadS [RestoreDBInstanceFromS3]
readsPrec :: Int -> ReadS RestoreDBInstanceFromS3
$creadsPrec :: Int -> ReadS RestoreDBInstanceFromS3
Prelude.Read, Int -> RestoreDBInstanceFromS3 -> ShowS
[RestoreDBInstanceFromS3] -> ShowS
RestoreDBInstanceFromS3 -> String
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [RestoreDBInstanceFromS3] -> ShowS
$cshowList :: [RestoreDBInstanceFromS3] -> ShowS
show :: RestoreDBInstanceFromS3 -> String
$cshow :: RestoreDBInstanceFromS3 -> String
showsPrec :: Int -> RestoreDBInstanceFromS3 -> ShowS
$cshowsPrec :: Int -> RestoreDBInstanceFromS3 -> ShowS
Prelude.Show, forall x. Rep RestoreDBInstanceFromS3 x -> RestoreDBInstanceFromS3
forall x. RestoreDBInstanceFromS3 -> Rep RestoreDBInstanceFromS3 x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cto :: forall x. Rep RestoreDBInstanceFromS3 x -> RestoreDBInstanceFromS3
$cfrom :: forall x. RestoreDBInstanceFromS3 -> Rep RestoreDBInstanceFromS3 x
Prelude.Generic)

-- |
-- Create a value of 'RestoreDBInstanceFromS3' 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:
--
-- 'allocatedStorage', 'restoreDBInstanceFromS3_allocatedStorage' - The amount of storage (in gigabytes) to allocate initially for the DB
-- instance. Follow the allocation rules specified in @CreateDBInstance@.
--
-- Be sure to allocate enough memory for your new DB instance so that the
-- restore operation can succeed. You can also allocate additional memory
-- for future growth.
--
-- 'autoMinorVersionUpgrade', 'restoreDBInstanceFromS3_autoMinorVersionUpgrade' - A value that indicates whether minor engine upgrades are applied
-- automatically to the DB instance during the maintenance window. By
-- default, minor engine upgrades are not applied automatically.
--
-- 'availabilityZone', 'restoreDBInstanceFromS3_availabilityZone' - The Availability Zone that the DB instance is created in. For
-- information about Amazon Web Services Regions and Availability Zones,
-- see
-- <https://docs.aws.amazon.com/AmazonRDS/latest/UserGuide/Concepts.RegionsAndAvailabilityZones.html Regions and Availability Zones>
-- in the /Amazon RDS User Guide./
--
-- Default: A random, system-chosen Availability Zone in the endpoint\'s
-- Amazon Web Services Region.
--
-- Example: @us-east-1d@
--
-- Constraint: The @AvailabilityZone@ parameter can\'t be specified if the
-- DB instance is a Multi-AZ deployment. The specified Availability Zone
-- must be in the same Amazon Web Services Region as the current endpoint.
--
-- 'backupRetentionPeriod', 'restoreDBInstanceFromS3_backupRetentionPeriod' - The number of days for which automated backups are retained. Setting
-- this parameter to a positive number enables backups. For more
-- information, see @CreateDBInstance@.
--
-- 'copyTagsToSnapshot', 'restoreDBInstanceFromS3_copyTagsToSnapshot' - A value that indicates whether to copy all tags from the DB instance to
-- snapshots of the DB instance. By default, tags are not copied.
--
-- 'dbName', 'restoreDBInstanceFromS3_dbName' - The name of the database to create when the DB instance is created.
-- Follow the naming rules specified in @CreateDBInstance@.
--
-- 'dbParameterGroupName', 'restoreDBInstanceFromS3_dbParameterGroupName' - The name of the DB parameter group to associate with this DB instance.
--
-- If you do not specify a value for @DBParameterGroupName@, then the
-- default @DBParameterGroup@ for the specified DB engine is used.
--
-- 'dbSecurityGroups', 'restoreDBInstanceFromS3_dbSecurityGroups' - A list of DB security groups to associate with this DB instance.
--
-- Default: The default DB security group for the database engine.
--
-- 'dbSubnetGroupName', 'restoreDBInstanceFromS3_dbSubnetGroupName' - A DB subnet group to associate with this DB instance.
--
-- Constraints: If supplied, must match the name of an existing
-- DBSubnetGroup.
--
-- Example: @mydbsubnetgroup@
--
-- 'deletionProtection', 'restoreDBInstanceFromS3_deletionProtection' - A value that indicates whether the DB instance has deletion protection
-- enabled. The database can\'t be deleted when deletion protection is
-- enabled. By default, deletion protection isn\'t enabled. For more
-- information, see
-- <https://docs.aws.amazon.com/AmazonRDS/latest/UserGuide/USER_DeleteInstance.html Deleting a DB Instance>.
--
-- 'enableCloudwatchLogsExports', 'restoreDBInstanceFromS3_enableCloudwatchLogsExports' - The list of logs that the restored DB instance is to export to
-- CloudWatch Logs. The values in the list depend on the DB engine being
-- used. For more information, see
-- <https://docs.aws.amazon.com/AmazonRDS/latest/UserGuide/USER_LogAccess.html#USER_LogAccess.Procedural.UploadtoCloudWatch Publishing Database Logs to Amazon CloudWatch Logs>
-- in the /Amazon RDS User Guide/.
--
-- 'enableIAMDatabaseAuthentication', 'restoreDBInstanceFromS3_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 about IAM database authentication, see
-- <https://docs.aws.amazon.com/AmazonRDS/latest/UserGuide/UsingWithRDS.IAMDBAuth.html IAM Database Authentication for MySQL and PostgreSQL>
-- in the /Amazon RDS User Guide./
--
-- 'enablePerformanceInsights', 'restoreDBInstanceFromS3_enablePerformanceInsights' - A value that indicates whether to enable Performance Insights for the DB
-- instance.
--
-- For more information, see
-- <https://docs.aws.amazon.com/AmazonRDS/latest/UserGuide/USER_PerfInsights.html Using Amazon Performance Insights>
-- in the /Amazon RDS User Guide/.
--
-- 'engineVersion', 'restoreDBInstanceFromS3_engineVersion' - The version number of the database engine to use. Choose the latest
-- minor version of your database engine. For information about engine
-- versions, see @CreateDBInstance@, or call @DescribeDBEngineVersions@.
--
-- 'iops', 'restoreDBInstanceFromS3_iops' - The amount of Provisioned IOPS (input\/output operations per second) to
-- allocate initially for the DB instance. For information about valid IOPS
-- values, see
-- <https://docs.aws.amazon.com/AmazonRDS/latest/UserGuide/CHAP_Storage.html#USER_PIOPS Amazon RDS Provisioned IOPS storage>
-- in the /Amazon RDS User Guide./
--
-- 'kmsKeyId', 'restoreDBInstanceFromS3_kmsKeyId' - The Amazon Web Services KMS key identifier for an encrypted DB instance.
--
-- 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.
--
-- 'licenseModel', 'restoreDBInstanceFromS3_licenseModel' - The license model for this DB instance. Use @general-public-license@.
--
-- 'manageMasterUserPassword', 'restoreDBInstanceFromS3_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./
--
-- Constraints:
--
-- -   Can\'t manage the master user password with Amazon Web Services
--     Secrets Manager if @MasterUserPassword@ is specified.
--
-- 'masterUserPassword', 'restoreDBInstanceFromS3_masterUserPassword' - The password for the master user. The password can include any printable
-- ASCII character except \"\/\", \"\"\", or \"\@\".
--
-- Constraints: Can\'t be specified if @ManageMasterUserPassword@ is turned
-- on.
--
-- __MariaDB__
--
-- Constraints: Must contain from 8 to 41 characters.
--
-- __Microsoft SQL Server__
--
-- Constraints: Must contain from 8 to 128 characters.
--
-- __MySQL__
--
-- Constraints: Must contain from 8 to 41 characters.
--
-- __Oracle__
--
-- Constraints: Must contain from 8 to 30 characters.
--
-- __PostgreSQL__
--
-- Constraints: Must contain from 8 to 128 characters.
--
-- 'masterUserSecretKmsKeyId', 'restoreDBInstanceFromS3_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 instance.
--
-- 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.
--
-- 'masterUsername', 'restoreDBInstanceFromS3_masterUsername' - The name for the master user.
--
-- 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.
--
-- 'maxAllocatedStorage', 'restoreDBInstanceFromS3_maxAllocatedStorage' - The upper limit in gibibytes (GiB) to which Amazon RDS can automatically
-- scale the storage of the DB instance.
--
-- For more information about this setting, including limitations that
-- apply to it, see
-- <https://docs.aws.amazon.com/AmazonRDS/latest/UserGuide/USER_PIOPS.StorageTypes.html#USER_PIOPS.Autoscaling Managing capacity automatically with Amazon RDS storage autoscaling>
-- in the /Amazon RDS User Guide/.
--
-- 'monitoringInterval', 'restoreDBInstanceFromS3_monitoringInterval' - The interval, in seconds, between points when Enhanced Monitoring
-- metrics are collected for the DB instance. To disable collecting
-- Enhanced Monitoring metrics, specify 0.
--
-- If @MonitoringRoleArn@ is specified, then you must also set
-- @MonitoringInterval@ to a value other than 0.
--
-- Valid Values: 0, 1, 5, 10, 15, 30, 60
--
-- Default: @0@
--
-- 'monitoringRoleArn', 'restoreDBInstanceFromS3_monitoringRoleArn' - The ARN for the IAM role that permits RDS to send enhanced monitoring
-- metrics to Amazon CloudWatch Logs. For example,
-- @arn:aws:iam:123456789012:role\/emaccess@. For information on creating a
-- monitoring role, see
-- <https://docs.aws.amazon.com/AmazonRDS/latest/UserGuide/USER_Monitoring.OS.html#USER_Monitoring.OS.Enabling Setting Up and Enabling Enhanced Monitoring>
-- in the /Amazon RDS User Guide./
--
-- If @MonitoringInterval@ is set to a value other than 0, then you must
-- supply a @MonitoringRoleArn@ value.
--
-- 'multiAZ', 'restoreDBInstanceFromS3_multiAZ' - A value that indicates whether the DB instance is a Multi-AZ deployment.
-- If the DB instance is a Multi-AZ deployment, you can\'t set the
-- @AvailabilityZone@ parameter.
--
-- 'networkType', 'restoreDBInstanceFromS3_networkType' - The network type of the DB instance.
--
-- Valid values:
--
-- -   @IPV4@
--
-- -   @DUAL@
--
-- The network type is determined by the @DBSubnetGroup@ specified for the
-- DB instance. 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/UserGuide/USER_VPC.WorkingWithRDSInstanceinaVPC.html Working with a DB instance in a VPC>
-- in the /Amazon RDS User Guide./
--
-- 'optionGroupName', 'restoreDBInstanceFromS3_optionGroupName' - The name of the option group to associate with this DB instance. If this
-- argument is omitted, the default option group for the specified engine
-- is used.
--
-- 'performanceInsightsKMSKeyId', 'restoreDBInstanceFromS3_performanceInsightsKMSKeyId' - The Amazon Web Services KMS key identifier for encryption of Performance
-- Insights data.
--
-- The Amazon Web Services KMS key identifier is the key ARN, key ID, alias
-- ARN, or alias name for the KMS key.
--
-- If you do not specify a value for @PerformanceInsightsKMSKeyId@, then
-- Amazon RDS uses 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.
--
-- 'performanceInsightsRetentionPeriod', 'restoreDBInstanceFromS3_performanceInsightsRetentionPeriod' - The number of days to retain Performance Insights data. The default is 7
-- days. The following values are valid:
--
-- -   7
--
-- -   /month/ * 31, where /month/ is a number of months from 1-23
--
-- -   731
--
-- For example, the following values are valid:
--
-- -   93 (3 months * 31)
--
-- -   341 (11 months * 31)
--
-- -   589 (19 months * 31)
--
-- -   731
--
-- If you specify a retention period such as 94, which isn\'t a valid
-- value, RDS issues an error.
--
-- 'port', 'restoreDBInstanceFromS3_port' - The port number on which the database accepts connections.
--
-- Type: Integer
--
-- Valid Values: @1150@-@65535@
--
-- Default: @3306@
--
-- 'preferredBackupWindow', 'restoreDBInstanceFromS3_preferredBackupWindow' - The time range each day during which automated backups are created if
-- automated backups are enabled. For more information, see
-- <https://docs.aws.amazon.com/AmazonRDS/latest/UserGuide/USER_WorkingWithAutomatedBackups.html#USER_WorkingWithAutomatedBackups.BackupWindow Backup window>
-- in the /Amazon RDS 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', 'restoreDBInstanceFromS3_preferredMaintenanceWindow' - The time range each week during which system maintenance can occur, in
-- Universal Coordinated Time (UTC). For more information, see
-- <https://docs.aws.amazon.com/AmazonRDS/latest/UserGuide/USER_UpgradeDBInstance.Maintenance.html#Concepts.DBMaintenance Amazon RDS Maintenance Window>
-- in the /Amazon RDS User Guide./
--
-- Constraints:
--
-- -   Must be in the format @ddd:hh24:mi-ddd:hh24:mi@.
--
-- -   Valid Days: Mon, Tue, Wed, Thu, Fri, Sat, Sun.
--
-- -   Must be in Universal Coordinated Time (UTC).
--
-- -   Must not conflict with the preferred backup window.
--
-- -   Must be at least 30 minutes.
--
-- 'processorFeatures', 'restoreDBInstanceFromS3_processorFeatures' - The number of CPU cores and the number of threads per core for the DB
-- instance class of the DB instance.
--
-- 'publiclyAccessible', 'restoreDBInstanceFromS3_publiclyAccessible' - A value that indicates whether the DB instance is publicly accessible.
--
-- When the DB instance is publicly accessible, its Domain Name System
-- (DNS) endpoint resolves to the private IP address from within the DB
-- instance\'s virtual private cloud (VPC). It resolves to the public IP
-- address from outside of the DB instance\'s VPC. Access to the DB
-- instance is ultimately controlled by the security group it uses. That
-- public access is not permitted if the security group assigned to the DB
-- instance doesn\'t permit it.
--
-- When the DB instance isn\'t publicly accessible, it is an internal DB
-- instance with a DNS name that resolves to a private IP address.
--
-- For more information, see CreateDBInstance.
--
-- 's3Prefix', 'restoreDBInstanceFromS3_s3Prefix' - The prefix of your Amazon S3 bucket.
--
-- 'storageEncrypted', 'restoreDBInstanceFromS3_storageEncrypted' - A value that indicates whether the new DB instance is encrypted or not.
--
-- 'storageThroughput', 'restoreDBInstanceFromS3_storageThroughput' - Specifies the storage throughput value for the DB instance.
--
-- This setting doesn\'t apply to RDS Custom or Amazon Aurora.
--
-- 'storageType', 'restoreDBInstanceFromS3_storageType' - Specifies the storage type to be associated with the DB instance.
--
-- Valid values: @gp2 | gp3 | io1 | standard@
--
-- If you specify @io1@ or @gp3@, you must also include a value for the
-- @Iops@ parameter.
--
-- Default: @io1@ if the @Iops@ parameter is specified; otherwise @gp2@
--
-- 'tags', 'restoreDBInstanceFromS3_tags' - A list of tags to associate with this DB instance. For more information,
-- see
-- <https://docs.aws.amazon.com/AmazonRDS/latest/UserGuide/USER_Tagging.html Tagging Amazon RDS Resources>
-- in the /Amazon RDS User Guide./
--
-- 'useDefaultProcessorFeatures', 'restoreDBInstanceFromS3_useDefaultProcessorFeatures' - A value that indicates whether the DB instance class of the DB instance
-- uses its default processor features.
--
-- 'vpcSecurityGroupIds', 'restoreDBInstanceFromS3_vpcSecurityGroupIds' - A list of VPC security groups to associate with this DB instance.
--
-- 'dbInstanceIdentifier', 'restoreDBInstanceFromS3_dbInstanceIdentifier' - The DB instance identifier. This parameter is stored as a lowercase
-- string.
--
-- 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: @mydbinstance@
--
-- 'dbInstanceClass', 'restoreDBInstanceFromS3_dbInstanceClass' - The compute and memory capacity of the DB instance, for example
-- db.m4.large. Not all DB instance classes are available in all Amazon Web
-- Services Regions, or for all database engines. For the full list of DB
-- instance classes, and availability for your engine, see
-- <https://docs.aws.amazon.com/AmazonRDS/latest/UserGuide/Concepts.DBInstanceClass.html DB Instance Class>
-- in the /Amazon RDS User Guide./
--
-- Importing from Amazon S3 isn\'t supported on the db.t2.micro DB instance
-- class.
--
-- 'engine', 'restoreDBInstanceFromS3_engine' - The name of the database engine to be used for this instance.
--
-- Valid Values: @mysql@
--
-- 'sourceEngine', 'restoreDBInstanceFromS3_sourceEngine' - The name of the engine of your source database.
--
-- Valid Values: @mysql@
--
-- 'sourceEngineVersion', 'restoreDBInstanceFromS3_sourceEngineVersion' - The version of the database that the backup files were created from.
--
-- MySQL versions 5.6 and 5.7 are supported.
--
-- Example: @5.6.40@
--
-- 's3BucketName', 'restoreDBInstanceFromS3_s3BucketName' - The name of your Amazon S3 bucket that contains your database backup
-- file.
--
-- 's3IngestionRoleArn', 'restoreDBInstanceFromS3_s3IngestionRoleArn' - An Amazon Web Services Identity and Access Management (IAM) role to
-- allow Amazon RDS to access your Amazon S3 bucket.
newRestoreDBInstanceFromS3 ::
  -- | 'dbInstanceIdentifier'
  Prelude.Text ->
  -- | 'dbInstanceClass'
  Prelude.Text ->
  -- | 'engine'
  Prelude.Text ->
  -- | 'sourceEngine'
  Prelude.Text ->
  -- | 'sourceEngineVersion'
  Prelude.Text ->
  -- | 's3BucketName'
  Prelude.Text ->
  -- | 's3IngestionRoleArn'
  Prelude.Text ->
  RestoreDBInstanceFromS3
newRestoreDBInstanceFromS3 :: Text
-> Text
-> Text
-> Text
-> Text
-> Text
-> Text
-> RestoreDBInstanceFromS3
newRestoreDBInstanceFromS3
  Text
pDBInstanceIdentifier_
  Text
pDBInstanceClass_
  Text
pEngine_
  Text
pSourceEngine_
  Text
pSourceEngineVersion_
  Text
pS3BucketName_
  Text
pS3IngestionRoleArn_ =
    RestoreDBInstanceFromS3'
      { $sel:allocatedStorage:RestoreDBInstanceFromS3' :: Maybe Int
allocatedStorage =
          forall a. Maybe a
Prelude.Nothing,
        $sel:autoMinorVersionUpgrade:RestoreDBInstanceFromS3' :: Maybe Bool
autoMinorVersionUpgrade = forall a. Maybe a
Prelude.Nothing,
        $sel:availabilityZone:RestoreDBInstanceFromS3' :: Maybe Text
availabilityZone = forall a. Maybe a
Prelude.Nothing,
        $sel:backupRetentionPeriod:RestoreDBInstanceFromS3' :: Maybe Int
backupRetentionPeriod = forall a. Maybe a
Prelude.Nothing,
        $sel:copyTagsToSnapshot:RestoreDBInstanceFromS3' :: Maybe Bool
copyTagsToSnapshot = forall a. Maybe a
Prelude.Nothing,
        $sel:dbName:RestoreDBInstanceFromS3' :: Maybe Text
dbName = forall a. Maybe a
Prelude.Nothing,
        $sel:dbParameterGroupName:RestoreDBInstanceFromS3' :: Maybe Text
dbParameterGroupName = forall a. Maybe a
Prelude.Nothing,
        $sel:dbSecurityGroups:RestoreDBInstanceFromS3' :: Maybe [Text]
dbSecurityGroups = forall a. Maybe a
Prelude.Nothing,
        $sel:dbSubnetGroupName:RestoreDBInstanceFromS3' :: Maybe Text
dbSubnetGroupName = forall a. Maybe a
Prelude.Nothing,
        $sel:deletionProtection:RestoreDBInstanceFromS3' :: Maybe Bool
deletionProtection = forall a. Maybe a
Prelude.Nothing,
        $sel:enableCloudwatchLogsExports:RestoreDBInstanceFromS3' :: Maybe [Text]
enableCloudwatchLogsExports = forall a. Maybe a
Prelude.Nothing,
        $sel:enableIAMDatabaseAuthentication:RestoreDBInstanceFromS3' :: Maybe Bool
enableIAMDatabaseAuthentication = forall a. Maybe a
Prelude.Nothing,
        $sel:enablePerformanceInsights:RestoreDBInstanceFromS3' :: Maybe Bool
enablePerformanceInsights = forall a. Maybe a
Prelude.Nothing,
        $sel:engineVersion:RestoreDBInstanceFromS3' :: Maybe Text
engineVersion = forall a. Maybe a
Prelude.Nothing,
        $sel:iops:RestoreDBInstanceFromS3' :: Maybe Int
iops = forall a. Maybe a
Prelude.Nothing,
        $sel:kmsKeyId:RestoreDBInstanceFromS3' :: Maybe Text
kmsKeyId = forall a. Maybe a
Prelude.Nothing,
        $sel:licenseModel:RestoreDBInstanceFromS3' :: Maybe Text
licenseModel = forall a. Maybe a
Prelude.Nothing,
        $sel:manageMasterUserPassword:RestoreDBInstanceFromS3' :: Maybe Bool
manageMasterUserPassword = forall a. Maybe a
Prelude.Nothing,
        $sel:masterUserPassword:RestoreDBInstanceFromS3' :: Maybe Text
masterUserPassword = forall a. Maybe a
Prelude.Nothing,
        $sel:masterUserSecretKmsKeyId:RestoreDBInstanceFromS3' :: Maybe Text
masterUserSecretKmsKeyId = forall a. Maybe a
Prelude.Nothing,
        $sel:masterUsername:RestoreDBInstanceFromS3' :: Maybe Text
masterUsername = forall a. Maybe a
Prelude.Nothing,
        $sel:maxAllocatedStorage:RestoreDBInstanceFromS3' :: Maybe Int
maxAllocatedStorage = forall a. Maybe a
Prelude.Nothing,
        $sel:monitoringInterval:RestoreDBInstanceFromS3' :: Maybe Int
monitoringInterval = forall a. Maybe a
Prelude.Nothing,
        $sel:monitoringRoleArn:RestoreDBInstanceFromS3' :: Maybe Text
monitoringRoleArn = forall a. Maybe a
Prelude.Nothing,
        $sel:multiAZ:RestoreDBInstanceFromS3' :: Maybe Bool
multiAZ = forall a. Maybe a
Prelude.Nothing,
        $sel:networkType:RestoreDBInstanceFromS3' :: Maybe Text
networkType = forall a. Maybe a
Prelude.Nothing,
        $sel:optionGroupName:RestoreDBInstanceFromS3' :: Maybe Text
optionGroupName = forall a. Maybe a
Prelude.Nothing,
        $sel:performanceInsightsKMSKeyId:RestoreDBInstanceFromS3' :: Maybe Text
performanceInsightsKMSKeyId = forall a. Maybe a
Prelude.Nothing,
        $sel:performanceInsightsRetentionPeriod:RestoreDBInstanceFromS3' :: Maybe Int
performanceInsightsRetentionPeriod =
          forall a. Maybe a
Prelude.Nothing,
        $sel:port:RestoreDBInstanceFromS3' :: Maybe Int
port = forall a. Maybe a
Prelude.Nothing,
        $sel:preferredBackupWindow:RestoreDBInstanceFromS3' :: Maybe Text
preferredBackupWindow = forall a. Maybe a
Prelude.Nothing,
        $sel:preferredMaintenanceWindow:RestoreDBInstanceFromS3' :: Maybe Text
preferredMaintenanceWindow = forall a. Maybe a
Prelude.Nothing,
        $sel:processorFeatures:RestoreDBInstanceFromS3' :: Maybe [ProcessorFeature]
processorFeatures = forall a. Maybe a
Prelude.Nothing,
        $sel:publiclyAccessible:RestoreDBInstanceFromS3' :: Maybe Bool
publiclyAccessible = forall a. Maybe a
Prelude.Nothing,
        $sel:s3Prefix:RestoreDBInstanceFromS3' :: Maybe Text
s3Prefix = forall a. Maybe a
Prelude.Nothing,
        $sel:storageEncrypted:RestoreDBInstanceFromS3' :: Maybe Bool
storageEncrypted = forall a. Maybe a
Prelude.Nothing,
        $sel:storageThroughput:RestoreDBInstanceFromS3' :: Maybe Int
storageThroughput = forall a. Maybe a
Prelude.Nothing,
        $sel:storageType:RestoreDBInstanceFromS3' :: Maybe Text
storageType = forall a. Maybe a
Prelude.Nothing,
        $sel:tags:RestoreDBInstanceFromS3' :: Maybe [Tag]
tags = forall a. Maybe a
Prelude.Nothing,
        $sel:useDefaultProcessorFeatures:RestoreDBInstanceFromS3' :: Maybe Bool
useDefaultProcessorFeatures = forall a. Maybe a
Prelude.Nothing,
        $sel:vpcSecurityGroupIds:RestoreDBInstanceFromS3' :: Maybe [Text]
vpcSecurityGroupIds = forall a. Maybe a
Prelude.Nothing,
        $sel:dbInstanceIdentifier:RestoreDBInstanceFromS3' :: Text
dbInstanceIdentifier = Text
pDBInstanceIdentifier_,
        $sel:dbInstanceClass:RestoreDBInstanceFromS3' :: Text
dbInstanceClass = Text
pDBInstanceClass_,
        $sel:engine:RestoreDBInstanceFromS3' :: Text
engine = Text
pEngine_,
        $sel:sourceEngine:RestoreDBInstanceFromS3' :: Text
sourceEngine = Text
pSourceEngine_,
        $sel:sourceEngineVersion:RestoreDBInstanceFromS3' :: Text
sourceEngineVersion = Text
pSourceEngineVersion_,
        $sel:s3BucketName:RestoreDBInstanceFromS3' :: Text
s3BucketName = Text
pS3BucketName_,
        $sel:s3IngestionRoleArn:RestoreDBInstanceFromS3' :: Text
s3IngestionRoleArn = Text
pS3IngestionRoleArn_
      }

-- | The amount of storage (in gigabytes) to allocate initially for the DB
-- instance. Follow the allocation rules specified in @CreateDBInstance@.
--
-- Be sure to allocate enough memory for your new DB instance so that the
-- restore operation can succeed. You can also allocate additional memory
-- for future growth.
restoreDBInstanceFromS3_allocatedStorage :: Lens.Lens' RestoreDBInstanceFromS3 (Prelude.Maybe Prelude.Int)
restoreDBInstanceFromS3_allocatedStorage :: Lens' RestoreDBInstanceFromS3 (Maybe Int)
restoreDBInstanceFromS3_allocatedStorage = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\RestoreDBInstanceFromS3' {Maybe Int
allocatedStorage :: Maybe Int
$sel:allocatedStorage:RestoreDBInstanceFromS3' :: RestoreDBInstanceFromS3 -> Maybe Int
allocatedStorage} -> Maybe Int
allocatedStorage) (\s :: RestoreDBInstanceFromS3
s@RestoreDBInstanceFromS3' {} Maybe Int
a -> RestoreDBInstanceFromS3
s {$sel:allocatedStorage:RestoreDBInstanceFromS3' :: Maybe Int
allocatedStorage = Maybe Int
a} :: RestoreDBInstanceFromS3)

-- | A value that indicates whether minor engine upgrades are applied
-- automatically to the DB instance during the maintenance window. By
-- default, minor engine upgrades are not applied automatically.
restoreDBInstanceFromS3_autoMinorVersionUpgrade :: Lens.Lens' RestoreDBInstanceFromS3 (Prelude.Maybe Prelude.Bool)
restoreDBInstanceFromS3_autoMinorVersionUpgrade :: Lens' RestoreDBInstanceFromS3 (Maybe Bool)
restoreDBInstanceFromS3_autoMinorVersionUpgrade = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\RestoreDBInstanceFromS3' {Maybe Bool
autoMinorVersionUpgrade :: Maybe Bool
$sel:autoMinorVersionUpgrade:RestoreDBInstanceFromS3' :: RestoreDBInstanceFromS3 -> Maybe Bool
autoMinorVersionUpgrade} -> Maybe Bool
autoMinorVersionUpgrade) (\s :: RestoreDBInstanceFromS3
s@RestoreDBInstanceFromS3' {} Maybe Bool
a -> RestoreDBInstanceFromS3
s {$sel:autoMinorVersionUpgrade:RestoreDBInstanceFromS3' :: Maybe Bool
autoMinorVersionUpgrade = Maybe Bool
a} :: RestoreDBInstanceFromS3)

-- | The Availability Zone that the DB instance is created in. For
-- information about Amazon Web Services Regions and Availability Zones,
-- see
-- <https://docs.aws.amazon.com/AmazonRDS/latest/UserGuide/Concepts.RegionsAndAvailabilityZones.html Regions and Availability Zones>
-- in the /Amazon RDS User Guide./
--
-- Default: A random, system-chosen Availability Zone in the endpoint\'s
-- Amazon Web Services Region.
--
-- Example: @us-east-1d@
--
-- Constraint: The @AvailabilityZone@ parameter can\'t be specified if the
-- DB instance is a Multi-AZ deployment. The specified Availability Zone
-- must be in the same Amazon Web Services Region as the current endpoint.
restoreDBInstanceFromS3_availabilityZone :: Lens.Lens' RestoreDBInstanceFromS3 (Prelude.Maybe Prelude.Text)
restoreDBInstanceFromS3_availabilityZone :: Lens' RestoreDBInstanceFromS3 (Maybe Text)
restoreDBInstanceFromS3_availabilityZone = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\RestoreDBInstanceFromS3' {Maybe Text
availabilityZone :: Maybe Text
$sel:availabilityZone:RestoreDBInstanceFromS3' :: RestoreDBInstanceFromS3 -> Maybe Text
availabilityZone} -> Maybe Text
availabilityZone) (\s :: RestoreDBInstanceFromS3
s@RestoreDBInstanceFromS3' {} Maybe Text
a -> RestoreDBInstanceFromS3
s {$sel:availabilityZone:RestoreDBInstanceFromS3' :: Maybe Text
availabilityZone = Maybe Text
a} :: RestoreDBInstanceFromS3)

-- | The number of days for which automated backups are retained. Setting
-- this parameter to a positive number enables backups. For more
-- information, see @CreateDBInstance@.
restoreDBInstanceFromS3_backupRetentionPeriod :: Lens.Lens' RestoreDBInstanceFromS3 (Prelude.Maybe Prelude.Int)
restoreDBInstanceFromS3_backupRetentionPeriod :: Lens' RestoreDBInstanceFromS3 (Maybe Int)
restoreDBInstanceFromS3_backupRetentionPeriod = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\RestoreDBInstanceFromS3' {Maybe Int
backupRetentionPeriod :: Maybe Int
$sel:backupRetentionPeriod:RestoreDBInstanceFromS3' :: RestoreDBInstanceFromS3 -> Maybe Int
backupRetentionPeriod} -> Maybe Int
backupRetentionPeriod) (\s :: RestoreDBInstanceFromS3
s@RestoreDBInstanceFromS3' {} Maybe Int
a -> RestoreDBInstanceFromS3
s {$sel:backupRetentionPeriod:RestoreDBInstanceFromS3' :: Maybe Int
backupRetentionPeriod = Maybe Int
a} :: RestoreDBInstanceFromS3)

-- | A value that indicates whether to copy all tags from the DB instance to
-- snapshots of the DB instance. By default, tags are not copied.
restoreDBInstanceFromS3_copyTagsToSnapshot :: Lens.Lens' RestoreDBInstanceFromS3 (Prelude.Maybe Prelude.Bool)
restoreDBInstanceFromS3_copyTagsToSnapshot :: Lens' RestoreDBInstanceFromS3 (Maybe Bool)
restoreDBInstanceFromS3_copyTagsToSnapshot = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\RestoreDBInstanceFromS3' {Maybe Bool
copyTagsToSnapshot :: Maybe Bool
$sel:copyTagsToSnapshot:RestoreDBInstanceFromS3' :: RestoreDBInstanceFromS3 -> Maybe Bool
copyTagsToSnapshot} -> Maybe Bool
copyTagsToSnapshot) (\s :: RestoreDBInstanceFromS3
s@RestoreDBInstanceFromS3' {} Maybe Bool
a -> RestoreDBInstanceFromS3
s {$sel:copyTagsToSnapshot:RestoreDBInstanceFromS3' :: Maybe Bool
copyTagsToSnapshot = Maybe Bool
a} :: RestoreDBInstanceFromS3)

-- | The name of the database to create when the DB instance is created.
-- Follow the naming rules specified in @CreateDBInstance@.
restoreDBInstanceFromS3_dbName :: Lens.Lens' RestoreDBInstanceFromS3 (Prelude.Maybe Prelude.Text)
restoreDBInstanceFromS3_dbName :: Lens' RestoreDBInstanceFromS3 (Maybe Text)
restoreDBInstanceFromS3_dbName = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\RestoreDBInstanceFromS3' {Maybe Text
dbName :: Maybe Text
$sel:dbName:RestoreDBInstanceFromS3' :: RestoreDBInstanceFromS3 -> Maybe Text
dbName} -> Maybe Text
dbName) (\s :: RestoreDBInstanceFromS3
s@RestoreDBInstanceFromS3' {} Maybe Text
a -> RestoreDBInstanceFromS3
s {$sel:dbName:RestoreDBInstanceFromS3' :: Maybe Text
dbName = Maybe Text
a} :: RestoreDBInstanceFromS3)

-- | The name of the DB parameter group to associate with this DB instance.
--
-- If you do not specify a value for @DBParameterGroupName@, then the
-- default @DBParameterGroup@ for the specified DB engine is used.
restoreDBInstanceFromS3_dbParameterGroupName :: Lens.Lens' RestoreDBInstanceFromS3 (Prelude.Maybe Prelude.Text)
restoreDBInstanceFromS3_dbParameterGroupName :: Lens' RestoreDBInstanceFromS3 (Maybe Text)
restoreDBInstanceFromS3_dbParameterGroupName = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\RestoreDBInstanceFromS3' {Maybe Text
dbParameterGroupName :: Maybe Text
$sel:dbParameterGroupName:RestoreDBInstanceFromS3' :: RestoreDBInstanceFromS3 -> Maybe Text
dbParameterGroupName} -> Maybe Text
dbParameterGroupName) (\s :: RestoreDBInstanceFromS3
s@RestoreDBInstanceFromS3' {} Maybe Text
a -> RestoreDBInstanceFromS3
s {$sel:dbParameterGroupName:RestoreDBInstanceFromS3' :: Maybe Text
dbParameterGroupName = Maybe Text
a} :: RestoreDBInstanceFromS3)

-- | A list of DB security groups to associate with this DB instance.
--
-- Default: The default DB security group for the database engine.
restoreDBInstanceFromS3_dbSecurityGroups :: Lens.Lens' RestoreDBInstanceFromS3 (Prelude.Maybe [Prelude.Text])
restoreDBInstanceFromS3_dbSecurityGroups :: Lens' RestoreDBInstanceFromS3 (Maybe [Text])
restoreDBInstanceFromS3_dbSecurityGroups = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\RestoreDBInstanceFromS3' {Maybe [Text]
dbSecurityGroups :: Maybe [Text]
$sel:dbSecurityGroups:RestoreDBInstanceFromS3' :: RestoreDBInstanceFromS3 -> Maybe [Text]
dbSecurityGroups} -> Maybe [Text]
dbSecurityGroups) (\s :: RestoreDBInstanceFromS3
s@RestoreDBInstanceFromS3' {} Maybe [Text]
a -> RestoreDBInstanceFromS3
s {$sel:dbSecurityGroups:RestoreDBInstanceFromS3' :: Maybe [Text]
dbSecurityGroups = Maybe [Text]
a} :: RestoreDBInstanceFromS3) 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 DB subnet group to associate with this DB instance.
--
-- Constraints: If supplied, must match the name of an existing
-- DBSubnetGroup.
--
-- Example: @mydbsubnetgroup@
restoreDBInstanceFromS3_dbSubnetGroupName :: Lens.Lens' RestoreDBInstanceFromS3 (Prelude.Maybe Prelude.Text)
restoreDBInstanceFromS3_dbSubnetGroupName :: Lens' RestoreDBInstanceFromS3 (Maybe Text)
restoreDBInstanceFromS3_dbSubnetGroupName = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\RestoreDBInstanceFromS3' {Maybe Text
dbSubnetGroupName :: Maybe Text
$sel:dbSubnetGroupName:RestoreDBInstanceFromS3' :: RestoreDBInstanceFromS3 -> Maybe Text
dbSubnetGroupName} -> Maybe Text
dbSubnetGroupName) (\s :: RestoreDBInstanceFromS3
s@RestoreDBInstanceFromS3' {} Maybe Text
a -> RestoreDBInstanceFromS3
s {$sel:dbSubnetGroupName:RestoreDBInstanceFromS3' :: Maybe Text
dbSubnetGroupName = Maybe Text
a} :: RestoreDBInstanceFromS3)

-- | A value that indicates whether the DB instance has deletion protection
-- enabled. The database can\'t be deleted when deletion protection is
-- enabled. By default, deletion protection isn\'t enabled. For more
-- information, see
-- <https://docs.aws.amazon.com/AmazonRDS/latest/UserGuide/USER_DeleteInstance.html Deleting a DB Instance>.
restoreDBInstanceFromS3_deletionProtection :: Lens.Lens' RestoreDBInstanceFromS3 (Prelude.Maybe Prelude.Bool)
restoreDBInstanceFromS3_deletionProtection :: Lens' RestoreDBInstanceFromS3 (Maybe Bool)
restoreDBInstanceFromS3_deletionProtection = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\RestoreDBInstanceFromS3' {Maybe Bool
deletionProtection :: Maybe Bool
$sel:deletionProtection:RestoreDBInstanceFromS3' :: RestoreDBInstanceFromS3 -> Maybe Bool
deletionProtection} -> Maybe Bool
deletionProtection) (\s :: RestoreDBInstanceFromS3
s@RestoreDBInstanceFromS3' {} Maybe Bool
a -> RestoreDBInstanceFromS3
s {$sel:deletionProtection:RestoreDBInstanceFromS3' :: Maybe Bool
deletionProtection = Maybe Bool
a} :: RestoreDBInstanceFromS3)

-- | The list of logs that the restored DB instance is to export to
-- CloudWatch Logs. The values in the list depend on the DB engine being
-- used. For more information, see
-- <https://docs.aws.amazon.com/AmazonRDS/latest/UserGuide/USER_LogAccess.html#USER_LogAccess.Procedural.UploadtoCloudWatch Publishing Database Logs to Amazon CloudWatch Logs>
-- in the /Amazon RDS User Guide/.
restoreDBInstanceFromS3_enableCloudwatchLogsExports :: Lens.Lens' RestoreDBInstanceFromS3 (Prelude.Maybe [Prelude.Text])
restoreDBInstanceFromS3_enableCloudwatchLogsExports :: Lens' RestoreDBInstanceFromS3 (Maybe [Text])
restoreDBInstanceFromS3_enableCloudwatchLogsExports = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\RestoreDBInstanceFromS3' {Maybe [Text]
enableCloudwatchLogsExports :: Maybe [Text]
$sel:enableCloudwatchLogsExports:RestoreDBInstanceFromS3' :: RestoreDBInstanceFromS3 -> Maybe [Text]
enableCloudwatchLogsExports} -> Maybe [Text]
enableCloudwatchLogsExports) (\s :: RestoreDBInstanceFromS3
s@RestoreDBInstanceFromS3' {} Maybe [Text]
a -> RestoreDBInstanceFromS3
s {$sel:enableCloudwatchLogsExports:RestoreDBInstanceFromS3' :: Maybe [Text]
enableCloudwatchLogsExports = Maybe [Text]
a} :: RestoreDBInstanceFromS3) 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 about IAM database authentication, see
-- <https://docs.aws.amazon.com/AmazonRDS/latest/UserGuide/UsingWithRDS.IAMDBAuth.html IAM Database Authentication for MySQL and PostgreSQL>
-- in the /Amazon RDS User Guide./
restoreDBInstanceFromS3_enableIAMDatabaseAuthentication :: Lens.Lens' RestoreDBInstanceFromS3 (Prelude.Maybe Prelude.Bool)
restoreDBInstanceFromS3_enableIAMDatabaseAuthentication :: Lens' RestoreDBInstanceFromS3 (Maybe Bool)
restoreDBInstanceFromS3_enableIAMDatabaseAuthentication = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\RestoreDBInstanceFromS3' {Maybe Bool
enableIAMDatabaseAuthentication :: Maybe Bool
$sel:enableIAMDatabaseAuthentication:RestoreDBInstanceFromS3' :: RestoreDBInstanceFromS3 -> Maybe Bool
enableIAMDatabaseAuthentication} -> Maybe Bool
enableIAMDatabaseAuthentication) (\s :: RestoreDBInstanceFromS3
s@RestoreDBInstanceFromS3' {} Maybe Bool
a -> RestoreDBInstanceFromS3
s {$sel:enableIAMDatabaseAuthentication:RestoreDBInstanceFromS3' :: Maybe Bool
enableIAMDatabaseAuthentication = Maybe Bool
a} :: RestoreDBInstanceFromS3)

-- | A value that indicates whether to enable Performance Insights for the DB
-- instance.
--
-- For more information, see
-- <https://docs.aws.amazon.com/AmazonRDS/latest/UserGuide/USER_PerfInsights.html Using Amazon Performance Insights>
-- in the /Amazon RDS User Guide/.
restoreDBInstanceFromS3_enablePerformanceInsights :: Lens.Lens' RestoreDBInstanceFromS3 (Prelude.Maybe Prelude.Bool)
restoreDBInstanceFromS3_enablePerformanceInsights :: Lens' RestoreDBInstanceFromS3 (Maybe Bool)
restoreDBInstanceFromS3_enablePerformanceInsights = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\RestoreDBInstanceFromS3' {Maybe Bool
enablePerformanceInsights :: Maybe Bool
$sel:enablePerformanceInsights:RestoreDBInstanceFromS3' :: RestoreDBInstanceFromS3 -> Maybe Bool
enablePerformanceInsights} -> Maybe Bool
enablePerformanceInsights) (\s :: RestoreDBInstanceFromS3
s@RestoreDBInstanceFromS3' {} Maybe Bool
a -> RestoreDBInstanceFromS3
s {$sel:enablePerformanceInsights:RestoreDBInstanceFromS3' :: Maybe Bool
enablePerformanceInsights = Maybe Bool
a} :: RestoreDBInstanceFromS3)

-- | The version number of the database engine to use. Choose the latest
-- minor version of your database engine. For information about engine
-- versions, see @CreateDBInstance@, or call @DescribeDBEngineVersions@.
restoreDBInstanceFromS3_engineVersion :: Lens.Lens' RestoreDBInstanceFromS3 (Prelude.Maybe Prelude.Text)
restoreDBInstanceFromS3_engineVersion :: Lens' RestoreDBInstanceFromS3 (Maybe Text)
restoreDBInstanceFromS3_engineVersion = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\RestoreDBInstanceFromS3' {Maybe Text
engineVersion :: Maybe Text
$sel:engineVersion:RestoreDBInstanceFromS3' :: RestoreDBInstanceFromS3 -> Maybe Text
engineVersion} -> Maybe Text
engineVersion) (\s :: RestoreDBInstanceFromS3
s@RestoreDBInstanceFromS3' {} Maybe Text
a -> RestoreDBInstanceFromS3
s {$sel:engineVersion:RestoreDBInstanceFromS3' :: Maybe Text
engineVersion = Maybe Text
a} :: RestoreDBInstanceFromS3)

-- | The amount of Provisioned IOPS (input\/output operations per second) to
-- allocate initially for the DB instance. For information about valid IOPS
-- values, see
-- <https://docs.aws.amazon.com/AmazonRDS/latest/UserGuide/CHAP_Storage.html#USER_PIOPS Amazon RDS Provisioned IOPS storage>
-- in the /Amazon RDS User Guide./
restoreDBInstanceFromS3_iops :: Lens.Lens' RestoreDBInstanceFromS3 (Prelude.Maybe Prelude.Int)
restoreDBInstanceFromS3_iops :: Lens' RestoreDBInstanceFromS3 (Maybe Int)
restoreDBInstanceFromS3_iops = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\RestoreDBInstanceFromS3' {Maybe Int
iops :: Maybe Int
$sel:iops:RestoreDBInstanceFromS3' :: RestoreDBInstanceFromS3 -> Maybe Int
iops} -> Maybe Int
iops) (\s :: RestoreDBInstanceFromS3
s@RestoreDBInstanceFromS3' {} Maybe Int
a -> RestoreDBInstanceFromS3
s {$sel:iops:RestoreDBInstanceFromS3' :: Maybe Int
iops = Maybe Int
a} :: RestoreDBInstanceFromS3)

-- | The Amazon Web Services KMS key identifier for an encrypted DB instance.
--
-- 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.
restoreDBInstanceFromS3_kmsKeyId :: Lens.Lens' RestoreDBInstanceFromS3 (Prelude.Maybe Prelude.Text)
restoreDBInstanceFromS3_kmsKeyId :: Lens' RestoreDBInstanceFromS3 (Maybe Text)
restoreDBInstanceFromS3_kmsKeyId = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\RestoreDBInstanceFromS3' {Maybe Text
kmsKeyId :: Maybe Text
$sel:kmsKeyId:RestoreDBInstanceFromS3' :: RestoreDBInstanceFromS3 -> Maybe Text
kmsKeyId} -> Maybe Text
kmsKeyId) (\s :: RestoreDBInstanceFromS3
s@RestoreDBInstanceFromS3' {} Maybe Text
a -> RestoreDBInstanceFromS3
s {$sel:kmsKeyId:RestoreDBInstanceFromS3' :: Maybe Text
kmsKeyId = Maybe Text
a} :: RestoreDBInstanceFromS3)

-- | The license model for this DB instance. Use @general-public-license@.
restoreDBInstanceFromS3_licenseModel :: Lens.Lens' RestoreDBInstanceFromS3 (Prelude.Maybe Prelude.Text)
restoreDBInstanceFromS3_licenseModel :: Lens' RestoreDBInstanceFromS3 (Maybe Text)
restoreDBInstanceFromS3_licenseModel = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\RestoreDBInstanceFromS3' {Maybe Text
licenseModel :: Maybe Text
$sel:licenseModel:RestoreDBInstanceFromS3' :: RestoreDBInstanceFromS3 -> Maybe Text
licenseModel} -> Maybe Text
licenseModel) (\s :: RestoreDBInstanceFromS3
s@RestoreDBInstanceFromS3' {} Maybe Text
a -> RestoreDBInstanceFromS3
s {$sel:licenseModel:RestoreDBInstanceFromS3' :: Maybe Text
licenseModel = Maybe Text
a} :: RestoreDBInstanceFromS3)

-- | 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./
--
-- Constraints:
--
-- -   Can\'t manage the master user password with Amazon Web Services
--     Secrets Manager if @MasterUserPassword@ is specified.
restoreDBInstanceFromS3_manageMasterUserPassword :: Lens.Lens' RestoreDBInstanceFromS3 (Prelude.Maybe Prelude.Bool)
restoreDBInstanceFromS3_manageMasterUserPassword :: Lens' RestoreDBInstanceFromS3 (Maybe Bool)
restoreDBInstanceFromS3_manageMasterUserPassword = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\RestoreDBInstanceFromS3' {Maybe Bool
manageMasterUserPassword :: Maybe Bool
$sel:manageMasterUserPassword:RestoreDBInstanceFromS3' :: RestoreDBInstanceFromS3 -> Maybe Bool
manageMasterUserPassword} -> Maybe Bool
manageMasterUserPassword) (\s :: RestoreDBInstanceFromS3
s@RestoreDBInstanceFromS3' {} Maybe Bool
a -> RestoreDBInstanceFromS3
s {$sel:manageMasterUserPassword:RestoreDBInstanceFromS3' :: Maybe Bool
manageMasterUserPassword = Maybe Bool
a} :: RestoreDBInstanceFromS3)

-- | The password for the master user. The password can include any printable
-- ASCII character except \"\/\", \"\"\", or \"\@\".
--
-- Constraints: Can\'t be specified if @ManageMasterUserPassword@ is turned
-- on.
--
-- __MariaDB__
--
-- Constraints: Must contain from 8 to 41 characters.
--
-- __Microsoft SQL Server__
--
-- Constraints: Must contain from 8 to 128 characters.
--
-- __MySQL__
--
-- Constraints: Must contain from 8 to 41 characters.
--
-- __Oracle__
--
-- Constraints: Must contain from 8 to 30 characters.
--
-- __PostgreSQL__
--
-- Constraints: Must contain from 8 to 128 characters.
restoreDBInstanceFromS3_masterUserPassword :: Lens.Lens' RestoreDBInstanceFromS3 (Prelude.Maybe Prelude.Text)
restoreDBInstanceFromS3_masterUserPassword :: Lens' RestoreDBInstanceFromS3 (Maybe Text)
restoreDBInstanceFromS3_masterUserPassword = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\RestoreDBInstanceFromS3' {Maybe Text
masterUserPassword :: Maybe Text
$sel:masterUserPassword:RestoreDBInstanceFromS3' :: RestoreDBInstanceFromS3 -> Maybe Text
masterUserPassword} -> Maybe Text
masterUserPassword) (\s :: RestoreDBInstanceFromS3
s@RestoreDBInstanceFromS3' {} Maybe Text
a -> RestoreDBInstanceFromS3
s {$sel:masterUserPassword:RestoreDBInstanceFromS3' :: Maybe Text
masterUserPassword = Maybe Text
a} :: RestoreDBInstanceFromS3)

-- | 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 instance.
--
-- 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.
restoreDBInstanceFromS3_masterUserSecretKmsKeyId :: Lens.Lens' RestoreDBInstanceFromS3 (Prelude.Maybe Prelude.Text)
restoreDBInstanceFromS3_masterUserSecretKmsKeyId :: Lens' RestoreDBInstanceFromS3 (Maybe Text)
restoreDBInstanceFromS3_masterUserSecretKmsKeyId = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\RestoreDBInstanceFromS3' {Maybe Text
masterUserSecretKmsKeyId :: Maybe Text
$sel:masterUserSecretKmsKeyId:RestoreDBInstanceFromS3' :: RestoreDBInstanceFromS3 -> Maybe Text
masterUserSecretKmsKeyId} -> Maybe Text
masterUserSecretKmsKeyId) (\s :: RestoreDBInstanceFromS3
s@RestoreDBInstanceFromS3' {} Maybe Text
a -> RestoreDBInstanceFromS3
s {$sel:masterUserSecretKmsKeyId:RestoreDBInstanceFromS3' :: Maybe Text
masterUserSecretKmsKeyId = Maybe Text
a} :: RestoreDBInstanceFromS3)

-- | The name for the master user.
--
-- 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.
restoreDBInstanceFromS3_masterUsername :: Lens.Lens' RestoreDBInstanceFromS3 (Prelude.Maybe Prelude.Text)
restoreDBInstanceFromS3_masterUsername :: Lens' RestoreDBInstanceFromS3 (Maybe Text)
restoreDBInstanceFromS3_masterUsername = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\RestoreDBInstanceFromS3' {Maybe Text
masterUsername :: Maybe Text
$sel:masterUsername:RestoreDBInstanceFromS3' :: RestoreDBInstanceFromS3 -> Maybe Text
masterUsername} -> Maybe Text
masterUsername) (\s :: RestoreDBInstanceFromS3
s@RestoreDBInstanceFromS3' {} Maybe Text
a -> RestoreDBInstanceFromS3
s {$sel:masterUsername:RestoreDBInstanceFromS3' :: Maybe Text
masterUsername = Maybe Text
a} :: RestoreDBInstanceFromS3)

-- | The upper limit in gibibytes (GiB) to which Amazon RDS can automatically
-- scale the storage of the DB instance.
--
-- For more information about this setting, including limitations that
-- apply to it, see
-- <https://docs.aws.amazon.com/AmazonRDS/latest/UserGuide/USER_PIOPS.StorageTypes.html#USER_PIOPS.Autoscaling Managing capacity automatically with Amazon RDS storage autoscaling>
-- in the /Amazon RDS User Guide/.
restoreDBInstanceFromS3_maxAllocatedStorage :: Lens.Lens' RestoreDBInstanceFromS3 (Prelude.Maybe Prelude.Int)
restoreDBInstanceFromS3_maxAllocatedStorage :: Lens' RestoreDBInstanceFromS3 (Maybe Int)
restoreDBInstanceFromS3_maxAllocatedStorage = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\RestoreDBInstanceFromS3' {Maybe Int
maxAllocatedStorage :: Maybe Int
$sel:maxAllocatedStorage:RestoreDBInstanceFromS3' :: RestoreDBInstanceFromS3 -> Maybe Int
maxAllocatedStorage} -> Maybe Int
maxAllocatedStorage) (\s :: RestoreDBInstanceFromS3
s@RestoreDBInstanceFromS3' {} Maybe Int
a -> RestoreDBInstanceFromS3
s {$sel:maxAllocatedStorage:RestoreDBInstanceFromS3' :: Maybe Int
maxAllocatedStorage = Maybe Int
a} :: RestoreDBInstanceFromS3)

-- | The interval, in seconds, between points when Enhanced Monitoring
-- metrics are collected for the DB instance. To disable collecting
-- Enhanced Monitoring metrics, specify 0.
--
-- If @MonitoringRoleArn@ is specified, then you must also set
-- @MonitoringInterval@ to a value other than 0.
--
-- Valid Values: 0, 1, 5, 10, 15, 30, 60
--
-- Default: @0@
restoreDBInstanceFromS3_monitoringInterval :: Lens.Lens' RestoreDBInstanceFromS3 (Prelude.Maybe Prelude.Int)
restoreDBInstanceFromS3_monitoringInterval :: Lens' RestoreDBInstanceFromS3 (Maybe Int)
restoreDBInstanceFromS3_monitoringInterval = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\RestoreDBInstanceFromS3' {Maybe Int
monitoringInterval :: Maybe Int
$sel:monitoringInterval:RestoreDBInstanceFromS3' :: RestoreDBInstanceFromS3 -> Maybe Int
monitoringInterval} -> Maybe Int
monitoringInterval) (\s :: RestoreDBInstanceFromS3
s@RestoreDBInstanceFromS3' {} Maybe Int
a -> RestoreDBInstanceFromS3
s {$sel:monitoringInterval:RestoreDBInstanceFromS3' :: Maybe Int
monitoringInterval = Maybe Int
a} :: RestoreDBInstanceFromS3)

-- | The ARN for the IAM role that permits RDS to send enhanced monitoring
-- metrics to Amazon CloudWatch Logs. For example,
-- @arn:aws:iam:123456789012:role\/emaccess@. For information on creating a
-- monitoring role, see
-- <https://docs.aws.amazon.com/AmazonRDS/latest/UserGuide/USER_Monitoring.OS.html#USER_Monitoring.OS.Enabling Setting Up and Enabling Enhanced Monitoring>
-- in the /Amazon RDS User Guide./
--
-- If @MonitoringInterval@ is set to a value other than 0, then you must
-- supply a @MonitoringRoleArn@ value.
restoreDBInstanceFromS3_monitoringRoleArn :: Lens.Lens' RestoreDBInstanceFromS3 (Prelude.Maybe Prelude.Text)
restoreDBInstanceFromS3_monitoringRoleArn :: Lens' RestoreDBInstanceFromS3 (Maybe Text)
restoreDBInstanceFromS3_monitoringRoleArn = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\RestoreDBInstanceFromS3' {Maybe Text
monitoringRoleArn :: Maybe Text
$sel:monitoringRoleArn:RestoreDBInstanceFromS3' :: RestoreDBInstanceFromS3 -> Maybe Text
monitoringRoleArn} -> Maybe Text
monitoringRoleArn) (\s :: RestoreDBInstanceFromS3
s@RestoreDBInstanceFromS3' {} Maybe Text
a -> RestoreDBInstanceFromS3
s {$sel:monitoringRoleArn:RestoreDBInstanceFromS3' :: Maybe Text
monitoringRoleArn = Maybe Text
a} :: RestoreDBInstanceFromS3)

-- | A value that indicates whether the DB instance is a Multi-AZ deployment.
-- If the DB instance is a Multi-AZ deployment, you can\'t set the
-- @AvailabilityZone@ parameter.
restoreDBInstanceFromS3_multiAZ :: Lens.Lens' RestoreDBInstanceFromS3 (Prelude.Maybe Prelude.Bool)
restoreDBInstanceFromS3_multiAZ :: Lens' RestoreDBInstanceFromS3 (Maybe Bool)
restoreDBInstanceFromS3_multiAZ = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\RestoreDBInstanceFromS3' {Maybe Bool
multiAZ :: Maybe Bool
$sel:multiAZ:RestoreDBInstanceFromS3' :: RestoreDBInstanceFromS3 -> Maybe Bool
multiAZ} -> Maybe Bool
multiAZ) (\s :: RestoreDBInstanceFromS3
s@RestoreDBInstanceFromS3' {} Maybe Bool
a -> RestoreDBInstanceFromS3
s {$sel:multiAZ:RestoreDBInstanceFromS3' :: Maybe Bool
multiAZ = Maybe Bool
a} :: RestoreDBInstanceFromS3)

-- | The network type of the DB instance.
--
-- Valid values:
--
-- -   @IPV4@
--
-- -   @DUAL@
--
-- The network type is determined by the @DBSubnetGroup@ specified for the
-- DB instance. 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/UserGuide/USER_VPC.WorkingWithRDSInstanceinaVPC.html Working with a DB instance in a VPC>
-- in the /Amazon RDS User Guide./
restoreDBInstanceFromS3_networkType :: Lens.Lens' RestoreDBInstanceFromS3 (Prelude.Maybe Prelude.Text)
restoreDBInstanceFromS3_networkType :: Lens' RestoreDBInstanceFromS3 (Maybe Text)
restoreDBInstanceFromS3_networkType = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\RestoreDBInstanceFromS3' {Maybe Text
networkType :: Maybe Text
$sel:networkType:RestoreDBInstanceFromS3' :: RestoreDBInstanceFromS3 -> Maybe Text
networkType} -> Maybe Text
networkType) (\s :: RestoreDBInstanceFromS3
s@RestoreDBInstanceFromS3' {} Maybe Text
a -> RestoreDBInstanceFromS3
s {$sel:networkType:RestoreDBInstanceFromS3' :: Maybe Text
networkType = Maybe Text
a} :: RestoreDBInstanceFromS3)

-- | The name of the option group to associate with this DB instance. If this
-- argument is omitted, the default option group for the specified engine
-- is used.
restoreDBInstanceFromS3_optionGroupName :: Lens.Lens' RestoreDBInstanceFromS3 (Prelude.Maybe Prelude.Text)
restoreDBInstanceFromS3_optionGroupName :: Lens' RestoreDBInstanceFromS3 (Maybe Text)
restoreDBInstanceFromS3_optionGroupName = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\RestoreDBInstanceFromS3' {Maybe Text
optionGroupName :: Maybe Text
$sel:optionGroupName:RestoreDBInstanceFromS3' :: RestoreDBInstanceFromS3 -> Maybe Text
optionGroupName} -> Maybe Text
optionGroupName) (\s :: RestoreDBInstanceFromS3
s@RestoreDBInstanceFromS3' {} Maybe Text
a -> RestoreDBInstanceFromS3
s {$sel:optionGroupName:RestoreDBInstanceFromS3' :: Maybe Text
optionGroupName = Maybe Text
a} :: RestoreDBInstanceFromS3)

-- | The Amazon Web Services KMS key identifier for encryption of Performance
-- Insights data.
--
-- The Amazon Web Services KMS key identifier is the key ARN, key ID, alias
-- ARN, or alias name for the KMS key.
--
-- If you do not specify a value for @PerformanceInsightsKMSKeyId@, then
-- Amazon RDS uses 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.
restoreDBInstanceFromS3_performanceInsightsKMSKeyId :: Lens.Lens' RestoreDBInstanceFromS3 (Prelude.Maybe Prelude.Text)
restoreDBInstanceFromS3_performanceInsightsKMSKeyId :: Lens' RestoreDBInstanceFromS3 (Maybe Text)
restoreDBInstanceFromS3_performanceInsightsKMSKeyId = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\RestoreDBInstanceFromS3' {Maybe Text
performanceInsightsKMSKeyId :: Maybe Text
$sel:performanceInsightsKMSKeyId:RestoreDBInstanceFromS3' :: RestoreDBInstanceFromS3 -> Maybe Text
performanceInsightsKMSKeyId} -> Maybe Text
performanceInsightsKMSKeyId) (\s :: RestoreDBInstanceFromS3
s@RestoreDBInstanceFromS3' {} Maybe Text
a -> RestoreDBInstanceFromS3
s {$sel:performanceInsightsKMSKeyId:RestoreDBInstanceFromS3' :: Maybe Text
performanceInsightsKMSKeyId = Maybe Text
a} :: RestoreDBInstanceFromS3)

-- | The number of days to retain Performance Insights data. The default is 7
-- days. The following values are valid:
--
-- -   7
--
-- -   /month/ * 31, where /month/ is a number of months from 1-23
--
-- -   731
--
-- For example, the following values are valid:
--
-- -   93 (3 months * 31)
--
-- -   341 (11 months * 31)
--
-- -   589 (19 months * 31)
--
-- -   731
--
-- If you specify a retention period such as 94, which isn\'t a valid
-- value, RDS issues an error.
restoreDBInstanceFromS3_performanceInsightsRetentionPeriod :: Lens.Lens' RestoreDBInstanceFromS3 (Prelude.Maybe Prelude.Int)
restoreDBInstanceFromS3_performanceInsightsRetentionPeriod :: Lens' RestoreDBInstanceFromS3 (Maybe Int)
restoreDBInstanceFromS3_performanceInsightsRetentionPeriod = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\RestoreDBInstanceFromS3' {Maybe Int
performanceInsightsRetentionPeriod :: Maybe Int
$sel:performanceInsightsRetentionPeriod:RestoreDBInstanceFromS3' :: RestoreDBInstanceFromS3 -> Maybe Int
performanceInsightsRetentionPeriod} -> Maybe Int
performanceInsightsRetentionPeriod) (\s :: RestoreDBInstanceFromS3
s@RestoreDBInstanceFromS3' {} Maybe Int
a -> RestoreDBInstanceFromS3
s {$sel:performanceInsightsRetentionPeriod:RestoreDBInstanceFromS3' :: Maybe Int
performanceInsightsRetentionPeriod = Maybe Int
a} :: RestoreDBInstanceFromS3)

-- | The port number on which the database accepts connections.
--
-- Type: Integer
--
-- Valid Values: @1150@-@65535@
--
-- Default: @3306@
restoreDBInstanceFromS3_port :: Lens.Lens' RestoreDBInstanceFromS3 (Prelude.Maybe Prelude.Int)
restoreDBInstanceFromS3_port :: Lens' RestoreDBInstanceFromS3 (Maybe Int)
restoreDBInstanceFromS3_port = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\RestoreDBInstanceFromS3' {Maybe Int
port :: Maybe Int
$sel:port:RestoreDBInstanceFromS3' :: RestoreDBInstanceFromS3 -> Maybe Int
port} -> Maybe Int
port) (\s :: RestoreDBInstanceFromS3
s@RestoreDBInstanceFromS3' {} Maybe Int
a -> RestoreDBInstanceFromS3
s {$sel:port:RestoreDBInstanceFromS3' :: Maybe Int
port = Maybe Int
a} :: RestoreDBInstanceFromS3)

-- | The time range each day during which automated backups are created if
-- automated backups are enabled. For more information, see
-- <https://docs.aws.amazon.com/AmazonRDS/latest/UserGuide/USER_WorkingWithAutomatedBackups.html#USER_WorkingWithAutomatedBackups.BackupWindow Backup window>
-- in the /Amazon RDS 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.
restoreDBInstanceFromS3_preferredBackupWindow :: Lens.Lens' RestoreDBInstanceFromS3 (Prelude.Maybe Prelude.Text)
restoreDBInstanceFromS3_preferredBackupWindow :: Lens' RestoreDBInstanceFromS3 (Maybe Text)
restoreDBInstanceFromS3_preferredBackupWindow = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\RestoreDBInstanceFromS3' {Maybe Text
preferredBackupWindow :: Maybe Text
$sel:preferredBackupWindow:RestoreDBInstanceFromS3' :: RestoreDBInstanceFromS3 -> Maybe Text
preferredBackupWindow} -> Maybe Text
preferredBackupWindow) (\s :: RestoreDBInstanceFromS3
s@RestoreDBInstanceFromS3' {} Maybe Text
a -> RestoreDBInstanceFromS3
s {$sel:preferredBackupWindow:RestoreDBInstanceFromS3' :: Maybe Text
preferredBackupWindow = Maybe Text
a} :: RestoreDBInstanceFromS3)

-- | The time range each week during which system maintenance can occur, in
-- Universal Coordinated Time (UTC). For more information, see
-- <https://docs.aws.amazon.com/AmazonRDS/latest/UserGuide/USER_UpgradeDBInstance.Maintenance.html#Concepts.DBMaintenance Amazon RDS Maintenance Window>
-- in the /Amazon RDS User Guide./
--
-- Constraints:
--
-- -   Must be in the format @ddd:hh24:mi-ddd:hh24:mi@.
--
-- -   Valid Days: Mon, Tue, Wed, Thu, Fri, Sat, Sun.
--
-- -   Must be in Universal Coordinated Time (UTC).
--
-- -   Must not conflict with the preferred backup window.
--
-- -   Must be at least 30 minutes.
restoreDBInstanceFromS3_preferredMaintenanceWindow :: Lens.Lens' RestoreDBInstanceFromS3 (Prelude.Maybe Prelude.Text)
restoreDBInstanceFromS3_preferredMaintenanceWindow :: Lens' RestoreDBInstanceFromS3 (Maybe Text)
restoreDBInstanceFromS3_preferredMaintenanceWindow = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\RestoreDBInstanceFromS3' {Maybe Text
preferredMaintenanceWindow :: Maybe Text
$sel:preferredMaintenanceWindow:RestoreDBInstanceFromS3' :: RestoreDBInstanceFromS3 -> Maybe Text
preferredMaintenanceWindow} -> Maybe Text
preferredMaintenanceWindow) (\s :: RestoreDBInstanceFromS3
s@RestoreDBInstanceFromS3' {} Maybe Text
a -> RestoreDBInstanceFromS3
s {$sel:preferredMaintenanceWindow:RestoreDBInstanceFromS3' :: Maybe Text
preferredMaintenanceWindow = Maybe Text
a} :: RestoreDBInstanceFromS3)

-- | The number of CPU cores and the number of threads per core for the DB
-- instance class of the DB instance.
restoreDBInstanceFromS3_processorFeatures :: Lens.Lens' RestoreDBInstanceFromS3 (Prelude.Maybe [ProcessorFeature])
restoreDBInstanceFromS3_processorFeatures :: Lens' RestoreDBInstanceFromS3 (Maybe [ProcessorFeature])
restoreDBInstanceFromS3_processorFeatures = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\RestoreDBInstanceFromS3' {Maybe [ProcessorFeature]
processorFeatures :: Maybe [ProcessorFeature]
$sel:processorFeatures:RestoreDBInstanceFromS3' :: RestoreDBInstanceFromS3 -> Maybe [ProcessorFeature]
processorFeatures} -> Maybe [ProcessorFeature]
processorFeatures) (\s :: RestoreDBInstanceFromS3
s@RestoreDBInstanceFromS3' {} Maybe [ProcessorFeature]
a -> RestoreDBInstanceFromS3
s {$sel:processorFeatures:RestoreDBInstanceFromS3' :: Maybe [ProcessorFeature]
processorFeatures = Maybe [ProcessorFeature]
a} :: RestoreDBInstanceFromS3) 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 the DB instance is publicly accessible.
--
-- When the DB instance is publicly accessible, its Domain Name System
-- (DNS) endpoint resolves to the private IP address from within the DB
-- instance\'s virtual private cloud (VPC). It resolves to the public IP
-- address from outside of the DB instance\'s VPC. Access to the DB
-- instance is ultimately controlled by the security group it uses. That
-- public access is not permitted if the security group assigned to the DB
-- instance doesn\'t permit it.
--
-- When the DB instance isn\'t publicly accessible, it is an internal DB
-- instance with a DNS name that resolves to a private IP address.
--
-- For more information, see CreateDBInstance.
restoreDBInstanceFromS3_publiclyAccessible :: Lens.Lens' RestoreDBInstanceFromS3 (Prelude.Maybe Prelude.Bool)
restoreDBInstanceFromS3_publiclyAccessible :: Lens' RestoreDBInstanceFromS3 (Maybe Bool)
restoreDBInstanceFromS3_publiclyAccessible = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\RestoreDBInstanceFromS3' {Maybe Bool
publiclyAccessible :: Maybe Bool
$sel:publiclyAccessible:RestoreDBInstanceFromS3' :: RestoreDBInstanceFromS3 -> Maybe Bool
publiclyAccessible} -> Maybe Bool
publiclyAccessible) (\s :: RestoreDBInstanceFromS3
s@RestoreDBInstanceFromS3' {} Maybe Bool
a -> RestoreDBInstanceFromS3
s {$sel:publiclyAccessible:RestoreDBInstanceFromS3' :: Maybe Bool
publiclyAccessible = Maybe Bool
a} :: RestoreDBInstanceFromS3)

-- | The prefix of your Amazon S3 bucket.
restoreDBInstanceFromS3_s3Prefix :: Lens.Lens' RestoreDBInstanceFromS3 (Prelude.Maybe Prelude.Text)
restoreDBInstanceFromS3_s3Prefix :: Lens' RestoreDBInstanceFromS3 (Maybe Text)
restoreDBInstanceFromS3_s3Prefix = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\RestoreDBInstanceFromS3' {Maybe Text
s3Prefix :: Maybe Text
$sel:s3Prefix:RestoreDBInstanceFromS3' :: RestoreDBInstanceFromS3 -> Maybe Text
s3Prefix} -> Maybe Text
s3Prefix) (\s :: RestoreDBInstanceFromS3
s@RestoreDBInstanceFromS3' {} Maybe Text
a -> RestoreDBInstanceFromS3
s {$sel:s3Prefix:RestoreDBInstanceFromS3' :: Maybe Text
s3Prefix = Maybe Text
a} :: RestoreDBInstanceFromS3)

-- | A value that indicates whether the new DB instance is encrypted or not.
restoreDBInstanceFromS3_storageEncrypted :: Lens.Lens' RestoreDBInstanceFromS3 (Prelude.Maybe Prelude.Bool)
restoreDBInstanceFromS3_storageEncrypted :: Lens' RestoreDBInstanceFromS3 (Maybe Bool)
restoreDBInstanceFromS3_storageEncrypted = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\RestoreDBInstanceFromS3' {Maybe Bool
storageEncrypted :: Maybe Bool
$sel:storageEncrypted:RestoreDBInstanceFromS3' :: RestoreDBInstanceFromS3 -> Maybe Bool
storageEncrypted} -> Maybe Bool
storageEncrypted) (\s :: RestoreDBInstanceFromS3
s@RestoreDBInstanceFromS3' {} Maybe Bool
a -> RestoreDBInstanceFromS3
s {$sel:storageEncrypted:RestoreDBInstanceFromS3' :: Maybe Bool
storageEncrypted = Maybe Bool
a} :: RestoreDBInstanceFromS3)

-- | Specifies the storage throughput value for the DB instance.
--
-- This setting doesn\'t apply to RDS Custom or Amazon Aurora.
restoreDBInstanceFromS3_storageThroughput :: Lens.Lens' RestoreDBInstanceFromS3 (Prelude.Maybe Prelude.Int)
restoreDBInstanceFromS3_storageThroughput :: Lens' RestoreDBInstanceFromS3 (Maybe Int)
restoreDBInstanceFromS3_storageThroughput = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\RestoreDBInstanceFromS3' {Maybe Int
storageThroughput :: Maybe Int
$sel:storageThroughput:RestoreDBInstanceFromS3' :: RestoreDBInstanceFromS3 -> Maybe Int
storageThroughput} -> Maybe Int
storageThroughput) (\s :: RestoreDBInstanceFromS3
s@RestoreDBInstanceFromS3' {} Maybe Int
a -> RestoreDBInstanceFromS3
s {$sel:storageThroughput:RestoreDBInstanceFromS3' :: Maybe Int
storageThroughput = Maybe Int
a} :: RestoreDBInstanceFromS3)

-- | Specifies the storage type to be associated with the DB instance.
--
-- Valid values: @gp2 | gp3 | io1 | standard@
--
-- If you specify @io1@ or @gp3@, you must also include a value for the
-- @Iops@ parameter.
--
-- Default: @io1@ if the @Iops@ parameter is specified; otherwise @gp2@
restoreDBInstanceFromS3_storageType :: Lens.Lens' RestoreDBInstanceFromS3 (Prelude.Maybe Prelude.Text)
restoreDBInstanceFromS3_storageType :: Lens' RestoreDBInstanceFromS3 (Maybe Text)
restoreDBInstanceFromS3_storageType = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\RestoreDBInstanceFromS3' {Maybe Text
storageType :: Maybe Text
$sel:storageType:RestoreDBInstanceFromS3' :: RestoreDBInstanceFromS3 -> Maybe Text
storageType} -> Maybe Text
storageType) (\s :: RestoreDBInstanceFromS3
s@RestoreDBInstanceFromS3' {} Maybe Text
a -> RestoreDBInstanceFromS3
s {$sel:storageType:RestoreDBInstanceFromS3' :: Maybe Text
storageType = Maybe Text
a} :: RestoreDBInstanceFromS3)

-- | A list of tags to associate with this DB instance. For more information,
-- see
-- <https://docs.aws.amazon.com/AmazonRDS/latest/UserGuide/USER_Tagging.html Tagging Amazon RDS Resources>
-- in the /Amazon RDS User Guide./
restoreDBInstanceFromS3_tags :: Lens.Lens' RestoreDBInstanceFromS3 (Prelude.Maybe [Tag])
restoreDBInstanceFromS3_tags :: Lens' RestoreDBInstanceFromS3 (Maybe [Tag])
restoreDBInstanceFromS3_tags = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\RestoreDBInstanceFromS3' {Maybe [Tag]
tags :: Maybe [Tag]
$sel:tags:RestoreDBInstanceFromS3' :: RestoreDBInstanceFromS3 -> Maybe [Tag]
tags} -> Maybe [Tag]
tags) (\s :: RestoreDBInstanceFromS3
s@RestoreDBInstanceFromS3' {} Maybe [Tag]
a -> RestoreDBInstanceFromS3
s {$sel:tags:RestoreDBInstanceFromS3' :: Maybe [Tag]
tags = Maybe [Tag]
a} :: RestoreDBInstanceFromS3) 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 the DB instance class of the DB instance
-- uses its default processor features.
restoreDBInstanceFromS3_useDefaultProcessorFeatures :: Lens.Lens' RestoreDBInstanceFromS3 (Prelude.Maybe Prelude.Bool)
restoreDBInstanceFromS3_useDefaultProcessorFeatures :: Lens' RestoreDBInstanceFromS3 (Maybe Bool)
restoreDBInstanceFromS3_useDefaultProcessorFeatures = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\RestoreDBInstanceFromS3' {Maybe Bool
useDefaultProcessorFeatures :: Maybe Bool
$sel:useDefaultProcessorFeatures:RestoreDBInstanceFromS3' :: RestoreDBInstanceFromS3 -> Maybe Bool
useDefaultProcessorFeatures} -> Maybe Bool
useDefaultProcessorFeatures) (\s :: RestoreDBInstanceFromS3
s@RestoreDBInstanceFromS3' {} Maybe Bool
a -> RestoreDBInstanceFromS3
s {$sel:useDefaultProcessorFeatures:RestoreDBInstanceFromS3' :: Maybe Bool
useDefaultProcessorFeatures = Maybe Bool
a} :: RestoreDBInstanceFromS3)

-- | A list of VPC security groups to associate with this DB instance.
restoreDBInstanceFromS3_vpcSecurityGroupIds :: Lens.Lens' RestoreDBInstanceFromS3 (Prelude.Maybe [Prelude.Text])
restoreDBInstanceFromS3_vpcSecurityGroupIds :: Lens' RestoreDBInstanceFromS3 (Maybe [Text])
restoreDBInstanceFromS3_vpcSecurityGroupIds = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\RestoreDBInstanceFromS3' {Maybe [Text]
vpcSecurityGroupIds :: Maybe [Text]
$sel:vpcSecurityGroupIds:RestoreDBInstanceFromS3' :: RestoreDBInstanceFromS3 -> Maybe [Text]
vpcSecurityGroupIds} -> Maybe [Text]
vpcSecurityGroupIds) (\s :: RestoreDBInstanceFromS3
s@RestoreDBInstanceFromS3' {} Maybe [Text]
a -> RestoreDBInstanceFromS3
s {$sel:vpcSecurityGroupIds:RestoreDBInstanceFromS3' :: Maybe [Text]
vpcSecurityGroupIds = Maybe [Text]
a} :: RestoreDBInstanceFromS3) 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 DB instance identifier. This parameter is stored as a lowercase
-- string.
--
-- 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: @mydbinstance@
restoreDBInstanceFromS3_dbInstanceIdentifier :: Lens.Lens' RestoreDBInstanceFromS3 Prelude.Text
restoreDBInstanceFromS3_dbInstanceIdentifier :: Lens' RestoreDBInstanceFromS3 Text
restoreDBInstanceFromS3_dbInstanceIdentifier = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\RestoreDBInstanceFromS3' {Text
dbInstanceIdentifier :: Text
$sel:dbInstanceIdentifier:RestoreDBInstanceFromS3' :: RestoreDBInstanceFromS3 -> Text
dbInstanceIdentifier} -> Text
dbInstanceIdentifier) (\s :: RestoreDBInstanceFromS3
s@RestoreDBInstanceFromS3' {} Text
a -> RestoreDBInstanceFromS3
s {$sel:dbInstanceIdentifier:RestoreDBInstanceFromS3' :: Text
dbInstanceIdentifier = Text
a} :: RestoreDBInstanceFromS3)

-- | The compute and memory capacity of the DB instance, for example
-- db.m4.large. Not all DB instance classes are available in all Amazon Web
-- Services Regions, or for all database engines. For the full list of DB
-- instance classes, and availability for your engine, see
-- <https://docs.aws.amazon.com/AmazonRDS/latest/UserGuide/Concepts.DBInstanceClass.html DB Instance Class>
-- in the /Amazon RDS User Guide./
--
-- Importing from Amazon S3 isn\'t supported on the db.t2.micro DB instance
-- class.
restoreDBInstanceFromS3_dbInstanceClass :: Lens.Lens' RestoreDBInstanceFromS3 Prelude.Text
restoreDBInstanceFromS3_dbInstanceClass :: Lens' RestoreDBInstanceFromS3 Text
restoreDBInstanceFromS3_dbInstanceClass = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\RestoreDBInstanceFromS3' {Text
dbInstanceClass :: Text
$sel:dbInstanceClass:RestoreDBInstanceFromS3' :: RestoreDBInstanceFromS3 -> Text
dbInstanceClass} -> Text
dbInstanceClass) (\s :: RestoreDBInstanceFromS3
s@RestoreDBInstanceFromS3' {} Text
a -> RestoreDBInstanceFromS3
s {$sel:dbInstanceClass:RestoreDBInstanceFromS3' :: Text
dbInstanceClass = Text
a} :: RestoreDBInstanceFromS3)

-- | The name of the database engine to be used for this instance.
--
-- Valid Values: @mysql@
restoreDBInstanceFromS3_engine :: Lens.Lens' RestoreDBInstanceFromS3 Prelude.Text
restoreDBInstanceFromS3_engine :: Lens' RestoreDBInstanceFromS3 Text
restoreDBInstanceFromS3_engine = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\RestoreDBInstanceFromS3' {Text
engine :: Text
$sel:engine:RestoreDBInstanceFromS3' :: RestoreDBInstanceFromS3 -> Text
engine} -> Text
engine) (\s :: RestoreDBInstanceFromS3
s@RestoreDBInstanceFromS3' {} Text
a -> RestoreDBInstanceFromS3
s {$sel:engine:RestoreDBInstanceFromS3' :: Text
engine = Text
a} :: RestoreDBInstanceFromS3)

-- | The name of the engine of your source database.
--
-- Valid Values: @mysql@
restoreDBInstanceFromS3_sourceEngine :: Lens.Lens' RestoreDBInstanceFromS3 Prelude.Text
restoreDBInstanceFromS3_sourceEngine :: Lens' RestoreDBInstanceFromS3 Text
restoreDBInstanceFromS3_sourceEngine = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\RestoreDBInstanceFromS3' {Text
sourceEngine :: Text
$sel:sourceEngine:RestoreDBInstanceFromS3' :: RestoreDBInstanceFromS3 -> Text
sourceEngine} -> Text
sourceEngine) (\s :: RestoreDBInstanceFromS3
s@RestoreDBInstanceFromS3' {} Text
a -> RestoreDBInstanceFromS3
s {$sel:sourceEngine:RestoreDBInstanceFromS3' :: Text
sourceEngine = Text
a} :: RestoreDBInstanceFromS3)

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

-- | The name of your Amazon S3 bucket that contains your database backup
-- file.
restoreDBInstanceFromS3_s3BucketName :: Lens.Lens' RestoreDBInstanceFromS3 Prelude.Text
restoreDBInstanceFromS3_s3BucketName :: Lens' RestoreDBInstanceFromS3 Text
restoreDBInstanceFromS3_s3BucketName = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\RestoreDBInstanceFromS3' {Text
s3BucketName :: Text
$sel:s3BucketName:RestoreDBInstanceFromS3' :: RestoreDBInstanceFromS3 -> Text
s3BucketName} -> Text
s3BucketName) (\s :: RestoreDBInstanceFromS3
s@RestoreDBInstanceFromS3' {} Text
a -> RestoreDBInstanceFromS3
s {$sel:s3BucketName:RestoreDBInstanceFromS3' :: Text
s3BucketName = Text
a} :: RestoreDBInstanceFromS3)

-- | An Amazon Web Services Identity and Access Management (IAM) role to
-- allow Amazon RDS to access your Amazon S3 bucket.
restoreDBInstanceFromS3_s3IngestionRoleArn :: Lens.Lens' RestoreDBInstanceFromS3 Prelude.Text
restoreDBInstanceFromS3_s3IngestionRoleArn :: Lens' RestoreDBInstanceFromS3 Text
restoreDBInstanceFromS3_s3IngestionRoleArn = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\RestoreDBInstanceFromS3' {Text
s3IngestionRoleArn :: Text
$sel:s3IngestionRoleArn:RestoreDBInstanceFromS3' :: RestoreDBInstanceFromS3 -> Text
s3IngestionRoleArn} -> Text
s3IngestionRoleArn) (\s :: RestoreDBInstanceFromS3
s@RestoreDBInstanceFromS3' {} Text
a -> RestoreDBInstanceFromS3
s {$sel:s3IngestionRoleArn:RestoreDBInstanceFromS3' :: Text
s3IngestionRoleArn = Text
a} :: RestoreDBInstanceFromS3)

instance Core.AWSRequest RestoreDBInstanceFromS3 where
  type
    AWSResponse RestoreDBInstanceFromS3 =
      RestoreDBInstanceFromS3Response
  request :: (Service -> Service)
-> RestoreDBInstanceFromS3 -> Request RestoreDBInstanceFromS3
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 RestoreDBInstanceFromS3
-> ClientResponse ClientBody
-> m (Either
        Error (ClientResponse (AWSResponse RestoreDBInstanceFromS3)))
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
"RestoreDBInstanceFromS3Result"
      ( \Int
s ResponseHeaders
h [Node]
x ->
          Maybe DBInstance -> Int -> RestoreDBInstanceFromS3Response
RestoreDBInstanceFromS3Response'
            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
"DBInstance")
            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 RestoreDBInstanceFromS3 where
  hashWithSalt :: Int -> RestoreDBInstanceFromS3 -> Int
hashWithSalt Int
_salt RestoreDBInstanceFromS3' {Maybe Bool
Maybe Int
Maybe [Text]
Maybe [ProcessorFeature]
Maybe [Tag]
Maybe Text
Text
s3IngestionRoleArn :: Text
s3BucketName :: Text
sourceEngineVersion :: Text
sourceEngine :: Text
engine :: Text
dbInstanceClass :: Text
dbInstanceIdentifier :: Text
vpcSecurityGroupIds :: Maybe [Text]
useDefaultProcessorFeatures :: Maybe Bool
tags :: Maybe [Tag]
storageType :: Maybe Text
storageThroughput :: Maybe Int
storageEncrypted :: Maybe Bool
s3Prefix :: Maybe Text
publiclyAccessible :: Maybe Bool
processorFeatures :: Maybe [ProcessorFeature]
preferredMaintenanceWindow :: Maybe Text
preferredBackupWindow :: Maybe Text
port :: Maybe Int
performanceInsightsRetentionPeriod :: Maybe Int
performanceInsightsKMSKeyId :: Maybe Text
optionGroupName :: Maybe Text
networkType :: Maybe Text
multiAZ :: Maybe Bool
monitoringRoleArn :: Maybe Text
monitoringInterval :: Maybe Int
maxAllocatedStorage :: Maybe Int
masterUsername :: Maybe Text
masterUserSecretKmsKeyId :: Maybe Text
masterUserPassword :: Maybe Text
manageMasterUserPassword :: Maybe Bool
licenseModel :: Maybe Text
kmsKeyId :: Maybe Text
iops :: Maybe Int
engineVersion :: Maybe Text
enablePerformanceInsights :: Maybe Bool
enableIAMDatabaseAuthentication :: Maybe Bool
enableCloudwatchLogsExports :: Maybe [Text]
deletionProtection :: Maybe Bool
dbSubnetGroupName :: Maybe Text
dbSecurityGroups :: Maybe [Text]
dbParameterGroupName :: Maybe Text
dbName :: Maybe Text
copyTagsToSnapshot :: Maybe Bool
backupRetentionPeriod :: Maybe Int
availabilityZone :: Maybe Text
autoMinorVersionUpgrade :: Maybe Bool
allocatedStorage :: Maybe Int
$sel:s3IngestionRoleArn:RestoreDBInstanceFromS3' :: RestoreDBInstanceFromS3 -> Text
$sel:s3BucketName:RestoreDBInstanceFromS3' :: RestoreDBInstanceFromS3 -> Text
$sel:sourceEngineVersion:RestoreDBInstanceFromS3' :: RestoreDBInstanceFromS3 -> Text
$sel:sourceEngine:RestoreDBInstanceFromS3' :: RestoreDBInstanceFromS3 -> Text
$sel:engine:RestoreDBInstanceFromS3' :: RestoreDBInstanceFromS3 -> Text
$sel:dbInstanceClass:RestoreDBInstanceFromS3' :: RestoreDBInstanceFromS3 -> Text
$sel:dbInstanceIdentifier:RestoreDBInstanceFromS3' :: RestoreDBInstanceFromS3 -> Text
$sel:vpcSecurityGroupIds:RestoreDBInstanceFromS3' :: RestoreDBInstanceFromS3 -> Maybe [Text]
$sel:useDefaultProcessorFeatures:RestoreDBInstanceFromS3' :: RestoreDBInstanceFromS3 -> Maybe Bool
$sel:tags:RestoreDBInstanceFromS3' :: RestoreDBInstanceFromS3 -> Maybe [Tag]
$sel:storageType:RestoreDBInstanceFromS3' :: RestoreDBInstanceFromS3 -> Maybe Text
$sel:storageThroughput:RestoreDBInstanceFromS3' :: RestoreDBInstanceFromS3 -> Maybe Int
$sel:storageEncrypted:RestoreDBInstanceFromS3' :: RestoreDBInstanceFromS3 -> Maybe Bool
$sel:s3Prefix:RestoreDBInstanceFromS3' :: RestoreDBInstanceFromS3 -> Maybe Text
$sel:publiclyAccessible:RestoreDBInstanceFromS3' :: RestoreDBInstanceFromS3 -> Maybe Bool
$sel:processorFeatures:RestoreDBInstanceFromS3' :: RestoreDBInstanceFromS3 -> Maybe [ProcessorFeature]
$sel:preferredMaintenanceWindow:RestoreDBInstanceFromS3' :: RestoreDBInstanceFromS3 -> Maybe Text
$sel:preferredBackupWindow:RestoreDBInstanceFromS3' :: RestoreDBInstanceFromS3 -> Maybe Text
$sel:port:RestoreDBInstanceFromS3' :: RestoreDBInstanceFromS3 -> Maybe Int
$sel:performanceInsightsRetentionPeriod:RestoreDBInstanceFromS3' :: RestoreDBInstanceFromS3 -> Maybe Int
$sel:performanceInsightsKMSKeyId:RestoreDBInstanceFromS3' :: RestoreDBInstanceFromS3 -> Maybe Text
$sel:optionGroupName:RestoreDBInstanceFromS3' :: RestoreDBInstanceFromS3 -> Maybe Text
$sel:networkType:RestoreDBInstanceFromS3' :: RestoreDBInstanceFromS3 -> Maybe Text
$sel:multiAZ:RestoreDBInstanceFromS3' :: RestoreDBInstanceFromS3 -> Maybe Bool
$sel:monitoringRoleArn:RestoreDBInstanceFromS3' :: RestoreDBInstanceFromS3 -> Maybe Text
$sel:monitoringInterval:RestoreDBInstanceFromS3' :: RestoreDBInstanceFromS3 -> Maybe Int
$sel:maxAllocatedStorage:RestoreDBInstanceFromS3' :: RestoreDBInstanceFromS3 -> Maybe Int
$sel:masterUsername:RestoreDBInstanceFromS3' :: RestoreDBInstanceFromS3 -> Maybe Text
$sel:masterUserSecretKmsKeyId:RestoreDBInstanceFromS3' :: RestoreDBInstanceFromS3 -> Maybe Text
$sel:masterUserPassword:RestoreDBInstanceFromS3' :: RestoreDBInstanceFromS3 -> Maybe Text
$sel:manageMasterUserPassword:RestoreDBInstanceFromS3' :: RestoreDBInstanceFromS3 -> Maybe Bool
$sel:licenseModel:RestoreDBInstanceFromS3' :: RestoreDBInstanceFromS3 -> Maybe Text
$sel:kmsKeyId:RestoreDBInstanceFromS3' :: RestoreDBInstanceFromS3 -> Maybe Text
$sel:iops:RestoreDBInstanceFromS3' :: RestoreDBInstanceFromS3 -> Maybe Int
$sel:engineVersion:RestoreDBInstanceFromS3' :: RestoreDBInstanceFromS3 -> Maybe Text
$sel:enablePerformanceInsights:RestoreDBInstanceFromS3' :: RestoreDBInstanceFromS3 -> Maybe Bool
$sel:enableIAMDatabaseAuthentication:RestoreDBInstanceFromS3' :: RestoreDBInstanceFromS3 -> Maybe Bool
$sel:enableCloudwatchLogsExports:RestoreDBInstanceFromS3' :: RestoreDBInstanceFromS3 -> Maybe [Text]
$sel:deletionProtection:RestoreDBInstanceFromS3' :: RestoreDBInstanceFromS3 -> Maybe Bool
$sel:dbSubnetGroupName:RestoreDBInstanceFromS3' :: RestoreDBInstanceFromS3 -> Maybe Text
$sel:dbSecurityGroups:RestoreDBInstanceFromS3' :: RestoreDBInstanceFromS3 -> Maybe [Text]
$sel:dbParameterGroupName:RestoreDBInstanceFromS3' :: RestoreDBInstanceFromS3 -> Maybe Text
$sel:dbName:RestoreDBInstanceFromS3' :: RestoreDBInstanceFromS3 -> Maybe Text
$sel:copyTagsToSnapshot:RestoreDBInstanceFromS3' :: RestoreDBInstanceFromS3 -> Maybe Bool
$sel:backupRetentionPeriod:RestoreDBInstanceFromS3' :: RestoreDBInstanceFromS3 -> Maybe Int
$sel:availabilityZone:RestoreDBInstanceFromS3' :: RestoreDBInstanceFromS3 -> Maybe Text
$sel:autoMinorVersionUpgrade:RestoreDBInstanceFromS3' :: RestoreDBInstanceFromS3 -> Maybe Bool
$sel:allocatedStorage:RestoreDBInstanceFromS3' :: RestoreDBInstanceFromS3 -> Maybe Int
..} =
    Int
_salt
      forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Maybe Int
allocatedStorage
      forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Maybe Bool
autoMinorVersionUpgrade
      forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Maybe Text
availabilityZone
      forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Maybe Int
backupRetentionPeriod
      forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Maybe Bool
copyTagsToSnapshot
      forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Maybe Text
dbName
      forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Maybe Text
dbParameterGroupName
      forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Maybe [Text]
dbSecurityGroups
      forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Maybe Text
dbSubnetGroupName
      forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Maybe Bool
deletionProtection
      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 Bool
enablePerformanceInsights
      forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Maybe Text
engineVersion
      forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Maybe Int
iops
      forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Maybe Text
kmsKeyId
      forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Maybe Text
licenseModel
      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
masterUsername
      forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Maybe Int
maxAllocatedStorage
      forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Maybe Int
monitoringInterval
      forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Maybe Text
monitoringRoleArn
      forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Maybe Bool
multiAZ
      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 Text
performanceInsightsKMSKeyId
      forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Maybe Int
performanceInsightsRetentionPeriod
      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 [ProcessorFeature]
processorFeatures
      forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Maybe Bool
publiclyAccessible
      forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Maybe Text
s3Prefix
      forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Maybe Bool
storageEncrypted
      forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Maybe Int
storageThroughput
      forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Maybe Text
storageType
      forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Maybe [Tag]
tags
      forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Maybe Bool
useDefaultProcessorFeatures
      forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Maybe [Text]
vpcSecurityGroupIds
      forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Text
dbInstanceIdentifier
      forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Text
dbInstanceClass
      forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Text
engine
      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 RestoreDBInstanceFromS3 where
  rnf :: RestoreDBInstanceFromS3 -> ()
rnf RestoreDBInstanceFromS3' {Maybe Bool
Maybe Int
Maybe [Text]
Maybe [ProcessorFeature]
Maybe [Tag]
Maybe Text
Text
s3IngestionRoleArn :: Text
s3BucketName :: Text
sourceEngineVersion :: Text
sourceEngine :: Text
engine :: Text
dbInstanceClass :: Text
dbInstanceIdentifier :: Text
vpcSecurityGroupIds :: Maybe [Text]
useDefaultProcessorFeatures :: Maybe Bool
tags :: Maybe [Tag]
storageType :: Maybe Text
storageThroughput :: Maybe Int
storageEncrypted :: Maybe Bool
s3Prefix :: Maybe Text
publiclyAccessible :: Maybe Bool
processorFeatures :: Maybe [ProcessorFeature]
preferredMaintenanceWindow :: Maybe Text
preferredBackupWindow :: Maybe Text
port :: Maybe Int
performanceInsightsRetentionPeriod :: Maybe Int
performanceInsightsKMSKeyId :: Maybe Text
optionGroupName :: Maybe Text
networkType :: Maybe Text
multiAZ :: Maybe Bool
monitoringRoleArn :: Maybe Text
monitoringInterval :: Maybe Int
maxAllocatedStorage :: Maybe Int
masterUsername :: Maybe Text
masterUserSecretKmsKeyId :: Maybe Text
masterUserPassword :: Maybe Text
manageMasterUserPassword :: Maybe Bool
licenseModel :: Maybe Text
kmsKeyId :: Maybe Text
iops :: Maybe Int
engineVersion :: Maybe Text
enablePerformanceInsights :: Maybe Bool
enableIAMDatabaseAuthentication :: Maybe Bool
enableCloudwatchLogsExports :: Maybe [Text]
deletionProtection :: Maybe Bool
dbSubnetGroupName :: Maybe Text
dbSecurityGroups :: Maybe [Text]
dbParameterGroupName :: Maybe Text
dbName :: Maybe Text
copyTagsToSnapshot :: Maybe Bool
backupRetentionPeriod :: Maybe Int
availabilityZone :: Maybe Text
autoMinorVersionUpgrade :: Maybe Bool
allocatedStorage :: Maybe Int
$sel:s3IngestionRoleArn:RestoreDBInstanceFromS3' :: RestoreDBInstanceFromS3 -> Text
$sel:s3BucketName:RestoreDBInstanceFromS3' :: RestoreDBInstanceFromS3 -> Text
$sel:sourceEngineVersion:RestoreDBInstanceFromS3' :: RestoreDBInstanceFromS3 -> Text
$sel:sourceEngine:RestoreDBInstanceFromS3' :: RestoreDBInstanceFromS3 -> Text
$sel:engine:RestoreDBInstanceFromS3' :: RestoreDBInstanceFromS3 -> Text
$sel:dbInstanceClass:RestoreDBInstanceFromS3' :: RestoreDBInstanceFromS3 -> Text
$sel:dbInstanceIdentifier:RestoreDBInstanceFromS3' :: RestoreDBInstanceFromS3 -> Text
$sel:vpcSecurityGroupIds:RestoreDBInstanceFromS3' :: RestoreDBInstanceFromS3 -> Maybe [Text]
$sel:useDefaultProcessorFeatures:RestoreDBInstanceFromS3' :: RestoreDBInstanceFromS3 -> Maybe Bool
$sel:tags:RestoreDBInstanceFromS3' :: RestoreDBInstanceFromS3 -> Maybe [Tag]
$sel:storageType:RestoreDBInstanceFromS3' :: RestoreDBInstanceFromS3 -> Maybe Text
$sel:storageThroughput:RestoreDBInstanceFromS3' :: RestoreDBInstanceFromS3 -> Maybe Int
$sel:storageEncrypted:RestoreDBInstanceFromS3' :: RestoreDBInstanceFromS3 -> Maybe Bool
$sel:s3Prefix:RestoreDBInstanceFromS3' :: RestoreDBInstanceFromS3 -> Maybe Text
$sel:publiclyAccessible:RestoreDBInstanceFromS3' :: RestoreDBInstanceFromS3 -> Maybe Bool
$sel:processorFeatures:RestoreDBInstanceFromS3' :: RestoreDBInstanceFromS3 -> Maybe [ProcessorFeature]
$sel:preferredMaintenanceWindow:RestoreDBInstanceFromS3' :: RestoreDBInstanceFromS3 -> Maybe Text
$sel:preferredBackupWindow:RestoreDBInstanceFromS3' :: RestoreDBInstanceFromS3 -> Maybe Text
$sel:port:RestoreDBInstanceFromS3' :: RestoreDBInstanceFromS3 -> Maybe Int
$sel:performanceInsightsRetentionPeriod:RestoreDBInstanceFromS3' :: RestoreDBInstanceFromS3 -> Maybe Int
$sel:performanceInsightsKMSKeyId:RestoreDBInstanceFromS3' :: RestoreDBInstanceFromS3 -> Maybe Text
$sel:optionGroupName:RestoreDBInstanceFromS3' :: RestoreDBInstanceFromS3 -> Maybe Text
$sel:networkType:RestoreDBInstanceFromS3' :: RestoreDBInstanceFromS3 -> Maybe Text
$sel:multiAZ:RestoreDBInstanceFromS3' :: RestoreDBInstanceFromS3 -> Maybe Bool
$sel:monitoringRoleArn:RestoreDBInstanceFromS3' :: RestoreDBInstanceFromS3 -> Maybe Text
$sel:monitoringInterval:RestoreDBInstanceFromS3' :: RestoreDBInstanceFromS3 -> Maybe Int
$sel:maxAllocatedStorage:RestoreDBInstanceFromS3' :: RestoreDBInstanceFromS3 -> Maybe Int
$sel:masterUsername:RestoreDBInstanceFromS3' :: RestoreDBInstanceFromS3 -> Maybe Text
$sel:masterUserSecretKmsKeyId:RestoreDBInstanceFromS3' :: RestoreDBInstanceFromS3 -> Maybe Text
$sel:masterUserPassword:RestoreDBInstanceFromS3' :: RestoreDBInstanceFromS3 -> Maybe Text
$sel:manageMasterUserPassword:RestoreDBInstanceFromS3' :: RestoreDBInstanceFromS3 -> Maybe Bool
$sel:licenseModel:RestoreDBInstanceFromS3' :: RestoreDBInstanceFromS3 -> Maybe Text
$sel:kmsKeyId:RestoreDBInstanceFromS3' :: RestoreDBInstanceFromS3 -> Maybe Text
$sel:iops:RestoreDBInstanceFromS3' :: RestoreDBInstanceFromS3 -> Maybe Int
$sel:engineVersion:RestoreDBInstanceFromS3' :: RestoreDBInstanceFromS3 -> Maybe Text
$sel:enablePerformanceInsights:RestoreDBInstanceFromS3' :: RestoreDBInstanceFromS3 -> Maybe Bool
$sel:enableIAMDatabaseAuthentication:RestoreDBInstanceFromS3' :: RestoreDBInstanceFromS3 -> Maybe Bool
$sel:enableCloudwatchLogsExports:RestoreDBInstanceFromS3' :: RestoreDBInstanceFromS3 -> Maybe [Text]
$sel:deletionProtection:RestoreDBInstanceFromS3' :: RestoreDBInstanceFromS3 -> Maybe Bool
$sel:dbSubnetGroupName:RestoreDBInstanceFromS3' :: RestoreDBInstanceFromS3 -> Maybe Text
$sel:dbSecurityGroups:RestoreDBInstanceFromS3' :: RestoreDBInstanceFromS3 -> Maybe [Text]
$sel:dbParameterGroupName:RestoreDBInstanceFromS3' :: RestoreDBInstanceFromS3 -> Maybe Text
$sel:dbName:RestoreDBInstanceFromS3' :: RestoreDBInstanceFromS3 -> Maybe Text
$sel:copyTagsToSnapshot:RestoreDBInstanceFromS3' :: RestoreDBInstanceFromS3 -> Maybe Bool
$sel:backupRetentionPeriod:RestoreDBInstanceFromS3' :: RestoreDBInstanceFromS3 -> Maybe Int
$sel:availabilityZone:RestoreDBInstanceFromS3' :: RestoreDBInstanceFromS3 -> Maybe Text
$sel:autoMinorVersionUpgrade:RestoreDBInstanceFromS3' :: RestoreDBInstanceFromS3 -> Maybe Bool
$sel:allocatedStorage:RestoreDBInstanceFromS3' :: RestoreDBInstanceFromS3 -> Maybe Int
..} =
    forall a. NFData a => a -> ()
Prelude.rnf Maybe Int
allocatedStorage
      seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf Maybe Bool
autoMinorVersionUpgrade
      seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf Maybe Text
availabilityZone
      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 Bool
copyTagsToSnapshot
      seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf Maybe Text
dbName
      seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf Maybe Text
dbParameterGroupName
      seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf Maybe [Text]
dbSecurityGroups
      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 Bool
deletionProtection
      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 Bool
enablePerformanceInsights
      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 Int
iops
      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 Text
licenseModel
      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
masterUsername
      seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf
        Maybe Int
maxAllocatedStorage
      seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf
        Maybe Int
monitoringInterval
      seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf
        Maybe Text
monitoringRoleArn
      seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf Maybe Bool
multiAZ
      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 Text
performanceInsightsKMSKeyId
      seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf
        Maybe Int
performanceInsightsRetentionPeriod
      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 [ProcessorFeature]
processorFeatures
      seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf
        Maybe Bool
publiclyAccessible
      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 Bool
storageEncrypted
      seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf
        Maybe Int
storageThroughput
      seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf
        Maybe Text
storageType
      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 Bool
useDefaultProcessorFeatures
      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
dbInstanceIdentifier
      seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf
        Text
dbInstanceClass
      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
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 RestoreDBInstanceFromS3 where
  toHeaders :: RestoreDBInstanceFromS3 -> ResponseHeaders
toHeaders = forall a b. a -> b -> a
Prelude.const forall a. Monoid a => a
Prelude.mempty

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

instance Data.ToQuery RestoreDBInstanceFromS3 where
  toQuery :: RestoreDBInstanceFromS3 -> QueryString
toQuery RestoreDBInstanceFromS3' {Maybe Bool
Maybe Int
Maybe [Text]
Maybe [ProcessorFeature]
Maybe [Tag]
Maybe Text
Text
s3IngestionRoleArn :: Text
s3BucketName :: Text
sourceEngineVersion :: Text
sourceEngine :: Text
engine :: Text
dbInstanceClass :: Text
dbInstanceIdentifier :: Text
vpcSecurityGroupIds :: Maybe [Text]
useDefaultProcessorFeatures :: Maybe Bool
tags :: Maybe [Tag]
storageType :: Maybe Text
storageThroughput :: Maybe Int
storageEncrypted :: Maybe Bool
s3Prefix :: Maybe Text
publiclyAccessible :: Maybe Bool
processorFeatures :: Maybe [ProcessorFeature]
preferredMaintenanceWindow :: Maybe Text
preferredBackupWindow :: Maybe Text
port :: Maybe Int
performanceInsightsRetentionPeriod :: Maybe Int
performanceInsightsKMSKeyId :: Maybe Text
optionGroupName :: Maybe Text
networkType :: Maybe Text
multiAZ :: Maybe Bool
monitoringRoleArn :: Maybe Text
monitoringInterval :: Maybe Int
maxAllocatedStorage :: Maybe Int
masterUsername :: Maybe Text
masterUserSecretKmsKeyId :: Maybe Text
masterUserPassword :: Maybe Text
manageMasterUserPassword :: Maybe Bool
licenseModel :: Maybe Text
kmsKeyId :: Maybe Text
iops :: Maybe Int
engineVersion :: Maybe Text
enablePerformanceInsights :: Maybe Bool
enableIAMDatabaseAuthentication :: Maybe Bool
enableCloudwatchLogsExports :: Maybe [Text]
deletionProtection :: Maybe Bool
dbSubnetGroupName :: Maybe Text
dbSecurityGroups :: Maybe [Text]
dbParameterGroupName :: Maybe Text
dbName :: Maybe Text
copyTagsToSnapshot :: Maybe Bool
backupRetentionPeriod :: Maybe Int
availabilityZone :: Maybe Text
autoMinorVersionUpgrade :: Maybe Bool
allocatedStorage :: Maybe Int
$sel:s3IngestionRoleArn:RestoreDBInstanceFromS3' :: RestoreDBInstanceFromS3 -> Text
$sel:s3BucketName:RestoreDBInstanceFromS3' :: RestoreDBInstanceFromS3 -> Text
$sel:sourceEngineVersion:RestoreDBInstanceFromS3' :: RestoreDBInstanceFromS3 -> Text
$sel:sourceEngine:RestoreDBInstanceFromS3' :: RestoreDBInstanceFromS3 -> Text
$sel:engine:RestoreDBInstanceFromS3' :: RestoreDBInstanceFromS3 -> Text
$sel:dbInstanceClass:RestoreDBInstanceFromS3' :: RestoreDBInstanceFromS3 -> Text
$sel:dbInstanceIdentifier:RestoreDBInstanceFromS3' :: RestoreDBInstanceFromS3 -> Text
$sel:vpcSecurityGroupIds:RestoreDBInstanceFromS3' :: RestoreDBInstanceFromS3 -> Maybe [Text]
$sel:useDefaultProcessorFeatures:RestoreDBInstanceFromS3' :: RestoreDBInstanceFromS3 -> Maybe Bool
$sel:tags:RestoreDBInstanceFromS3' :: RestoreDBInstanceFromS3 -> Maybe [Tag]
$sel:storageType:RestoreDBInstanceFromS3' :: RestoreDBInstanceFromS3 -> Maybe Text
$sel:storageThroughput:RestoreDBInstanceFromS3' :: RestoreDBInstanceFromS3 -> Maybe Int
$sel:storageEncrypted:RestoreDBInstanceFromS3' :: RestoreDBInstanceFromS3 -> Maybe Bool
$sel:s3Prefix:RestoreDBInstanceFromS3' :: RestoreDBInstanceFromS3 -> Maybe Text
$sel:publiclyAccessible:RestoreDBInstanceFromS3' :: RestoreDBInstanceFromS3 -> Maybe Bool
$sel:processorFeatures:RestoreDBInstanceFromS3' :: RestoreDBInstanceFromS3 -> Maybe [ProcessorFeature]
$sel:preferredMaintenanceWindow:RestoreDBInstanceFromS3' :: RestoreDBInstanceFromS3 -> Maybe Text
$sel:preferredBackupWindow:RestoreDBInstanceFromS3' :: RestoreDBInstanceFromS3 -> Maybe Text
$sel:port:RestoreDBInstanceFromS3' :: RestoreDBInstanceFromS3 -> Maybe Int
$sel:performanceInsightsRetentionPeriod:RestoreDBInstanceFromS3' :: RestoreDBInstanceFromS3 -> Maybe Int
$sel:performanceInsightsKMSKeyId:RestoreDBInstanceFromS3' :: RestoreDBInstanceFromS3 -> Maybe Text
$sel:optionGroupName:RestoreDBInstanceFromS3' :: RestoreDBInstanceFromS3 -> Maybe Text
$sel:networkType:RestoreDBInstanceFromS3' :: RestoreDBInstanceFromS3 -> Maybe Text
$sel:multiAZ:RestoreDBInstanceFromS3' :: RestoreDBInstanceFromS3 -> Maybe Bool
$sel:monitoringRoleArn:RestoreDBInstanceFromS3' :: RestoreDBInstanceFromS3 -> Maybe Text
$sel:monitoringInterval:RestoreDBInstanceFromS3' :: RestoreDBInstanceFromS3 -> Maybe Int
$sel:maxAllocatedStorage:RestoreDBInstanceFromS3' :: RestoreDBInstanceFromS3 -> Maybe Int
$sel:masterUsername:RestoreDBInstanceFromS3' :: RestoreDBInstanceFromS3 -> Maybe Text
$sel:masterUserSecretKmsKeyId:RestoreDBInstanceFromS3' :: RestoreDBInstanceFromS3 -> Maybe Text
$sel:masterUserPassword:RestoreDBInstanceFromS3' :: RestoreDBInstanceFromS3 -> Maybe Text
$sel:manageMasterUserPassword:RestoreDBInstanceFromS3' :: RestoreDBInstanceFromS3 -> Maybe Bool
$sel:licenseModel:RestoreDBInstanceFromS3' :: RestoreDBInstanceFromS3 -> Maybe Text
$sel:kmsKeyId:RestoreDBInstanceFromS3' :: RestoreDBInstanceFromS3 -> Maybe Text
$sel:iops:RestoreDBInstanceFromS3' :: RestoreDBInstanceFromS3 -> Maybe Int
$sel:engineVersion:RestoreDBInstanceFromS3' :: RestoreDBInstanceFromS3 -> Maybe Text
$sel:enablePerformanceInsights:RestoreDBInstanceFromS3' :: RestoreDBInstanceFromS3 -> Maybe Bool
$sel:enableIAMDatabaseAuthentication:RestoreDBInstanceFromS3' :: RestoreDBInstanceFromS3 -> Maybe Bool
$sel:enableCloudwatchLogsExports:RestoreDBInstanceFromS3' :: RestoreDBInstanceFromS3 -> Maybe [Text]
$sel:deletionProtection:RestoreDBInstanceFromS3' :: RestoreDBInstanceFromS3 -> Maybe Bool
$sel:dbSubnetGroupName:RestoreDBInstanceFromS3' :: RestoreDBInstanceFromS3 -> Maybe Text
$sel:dbSecurityGroups:RestoreDBInstanceFromS3' :: RestoreDBInstanceFromS3 -> Maybe [Text]
$sel:dbParameterGroupName:RestoreDBInstanceFromS3' :: RestoreDBInstanceFromS3 -> Maybe Text
$sel:dbName:RestoreDBInstanceFromS3' :: RestoreDBInstanceFromS3 -> Maybe Text
$sel:copyTagsToSnapshot:RestoreDBInstanceFromS3' :: RestoreDBInstanceFromS3 -> Maybe Bool
$sel:backupRetentionPeriod:RestoreDBInstanceFromS3' :: RestoreDBInstanceFromS3 -> Maybe Int
$sel:availabilityZone:RestoreDBInstanceFromS3' :: RestoreDBInstanceFromS3 -> Maybe Text
$sel:autoMinorVersionUpgrade:RestoreDBInstanceFromS3' :: RestoreDBInstanceFromS3 -> Maybe Bool
$sel:allocatedStorage:RestoreDBInstanceFromS3' :: RestoreDBInstanceFromS3 -> Maybe Int
..} =
    forall a. Monoid a => [a] -> a
Prelude.mconcat
      [ ByteString
"Action"
          forall a. ToQuery a => ByteString -> a -> QueryString
Data.=: (ByteString
"RestoreDBInstanceFromS3" :: Prelude.ByteString),
        ByteString
"Version"
          forall a. ToQuery a => ByteString -> a -> QueryString
Data.=: (ByteString
"2014-10-31" :: Prelude.ByteString),
        ByteString
"AllocatedStorage" forall a. ToQuery a => ByteString -> a -> QueryString
Data.=: Maybe Int
allocatedStorage,
        ByteString
"AutoMinorVersionUpgrade"
          forall a. ToQuery a => ByteString -> a -> QueryString
Data.=: Maybe Bool
autoMinorVersionUpgrade,
        ByteString
"AvailabilityZone" forall a. ToQuery a => ByteString -> a -> QueryString
Data.=: Maybe Text
availabilityZone,
        ByteString
"BackupRetentionPeriod"
          forall a. ToQuery a => ByteString -> a -> QueryString
Data.=: Maybe Int
backupRetentionPeriod,
        ByteString
"CopyTagsToSnapshot" forall a. ToQuery a => ByteString -> a -> QueryString
Data.=: Maybe Bool
copyTagsToSnapshot,
        ByteString
"DBName" forall a. ToQuery a => ByteString -> a -> QueryString
Data.=: Maybe Text
dbName,
        ByteString
"DBParameterGroupName" forall a. ToQuery a => ByteString -> a -> QueryString
Data.=: Maybe Text
dbParameterGroupName,
        ByteString
"DBSecurityGroups"
          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
"DBSecurityGroupName"
                forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
Prelude.<$> Maybe [Text]
dbSecurityGroups
            ),
        ByteString
"DBSubnetGroupName" forall a. ToQuery a => ByteString -> a -> QueryString
Data.=: Maybe Text
dbSubnetGroupName,
        ByteString
"DeletionProtection" forall a. ToQuery a => ByteString -> a -> QueryString
Data.=: Maybe Bool
deletionProtection,
        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
"EnablePerformanceInsights"
          forall a. ToQuery a => ByteString -> a -> QueryString
Data.=: Maybe Bool
enablePerformanceInsights,
        ByteString
"EngineVersion" forall a. ToQuery a => ByteString -> a -> QueryString
Data.=: Maybe Text
engineVersion,
        ByteString
"Iops" forall a. ToQuery a => ByteString -> a -> QueryString
Data.=: Maybe Int
iops,
        ByteString
"KmsKeyId" forall a. ToQuery a => ByteString -> a -> QueryString
Data.=: Maybe Text
kmsKeyId,
        ByteString
"LicenseModel" forall a. ToQuery a => ByteString -> a -> QueryString
Data.=: Maybe Text
licenseModel,
        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
"MasterUsername" forall a. ToQuery a => ByteString -> a -> QueryString
Data.=: Maybe Text
masterUsername,
        ByteString
"MaxAllocatedStorage" forall a. ToQuery a => ByteString -> a -> QueryString
Data.=: Maybe Int
maxAllocatedStorage,
        ByteString
"MonitoringInterval" forall a. ToQuery a => ByteString -> a -> QueryString
Data.=: Maybe Int
monitoringInterval,
        ByteString
"MonitoringRoleArn" forall a. ToQuery a => ByteString -> a -> QueryString
Data.=: Maybe Text
monitoringRoleArn,
        ByteString
"MultiAZ" forall a. ToQuery a => ByteString -> a -> QueryString
Data.=: Maybe Bool
multiAZ,
        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
"PerformanceInsightsKMSKeyId"
          forall a. ToQuery a => ByteString -> a -> QueryString
Data.=: Maybe Text
performanceInsightsKMSKeyId,
        ByteString
"PerformanceInsightsRetentionPeriod"
          forall a. ToQuery a => ByteString -> a -> QueryString
Data.=: Maybe Int
performanceInsightsRetentionPeriod,
        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
"ProcessorFeatures"
          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
"ProcessorFeature"
                forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
Prelude.<$> Maybe [ProcessorFeature]
processorFeatures
            ),
        ByteString
"PubliclyAccessible" forall a. ToQuery a => ByteString -> a -> QueryString
Data.=: Maybe Bool
publiclyAccessible,
        ByteString
"S3Prefix" forall a. ToQuery a => ByteString -> a -> QueryString
Data.=: Maybe Text
s3Prefix,
        ByteString
"StorageEncrypted" forall a. ToQuery a => ByteString -> a -> QueryString
Data.=: Maybe Bool
storageEncrypted,
        ByteString
"StorageThroughput" forall a. ToQuery a => ByteString -> a -> QueryString
Data.=: Maybe Int
storageThroughput,
        ByteString
"StorageType" forall a. ToQuery a => ByteString -> a -> QueryString
Data.=: Maybe Text
storageType,
        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
"UseDefaultProcessorFeatures"
          forall a. ToQuery a => ByteString -> a -> QueryString
Data.=: Maybe Bool
useDefaultProcessorFeatures,
        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
"DBInstanceIdentifier" forall a. ToQuery a => ByteString -> a -> QueryString
Data.=: Text
dbInstanceIdentifier,
        ByteString
"DBInstanceClass" forall a. ToQuery a => ByteString -> a -> QueryString
Data.=: Text
dbInstanceClass,
        ByteString
"Engine" forall a. ToQuery a => ByteString -> a -> QueryString
Data.=: Text
engine,
        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:/ 'newRestoreDBInstanceFromS3Response' smart constructor.
data RestoreDBInstanceFromS3Response = RestoreDBInstanceFromS3Response'
  { RestoreDBInstanceFromS3Response -> Maybe DBInstance
dbInstance :: Prelude.Maybe DBInstance,
    -- | The response's http status code.
    RestoreDBInstanceFromS3Response -> Int
httpStatus :: Prelude.Int
  }
  deriving (RestoreDBInstanceFromS3Response
-> RestoreDBInstanceFromS3Response -> Bool
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: RestoreDBInstanceFromS3Response
-> RestoreDBInstanceFromS3Response -> Bool
$c/= :: RestoreDBInstanceFromS3Response
-> RestoreDBInstanceFromS3Response -> Bool
== :: RestoreDBInstanceFromS3Response
-> RestoreDBInstanceFromS3Response -> Bool
$c== :: RestoreDBInstanceFromS3Response
-> RestoreDBInstanceFromS3Response -> Bool
Prelude.Eq, ReadPrec [RestoreDBInstanceFromS3Response]
ReadPrec RestoreDBInstanceFromS3Response
Int -> ReadS RestoreDBInstanceFromS3Response
ReadS [RestoreDBInstanceFromS3Response]
forall a.
(Int -> ReadS a)
-> ReadS [a] -> ReadPrec a -> ReadPrec [a] -> Read a
readListPrec :: ReadPrec [RestoreDBInstanceFromS3Response]
$creadListPrec :: ReadPrec [RestoreDBInstanceFromS3Response]
readPrec :: ReadPrec RestoreDBInstanceFromS3Response
$creadPrec :: ReadPrec RestoreDBInstanceFromS3Response
readList :: ReadS [RestoreDBInstanceFromS3Response]
$creadList :: ReadS [RestoreDBInstanceFromS3Response]
readsPrec :: Int -> ReadS RestoreDBInstanceFromS3Response
$creadsPrec :: Int -> ReadS RestoreDBInstanceFromS3Response
Prelude.Read, Int -> RestoreDBInstanceFromS3Response -> ShowS
[RestoreDBInstanceFromS3Response] -> ShowS
RestoreDBInstanceFromS3Response -> String
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [RestoreDBInstanceFromS3Response] -> ShowS
$cshowList :: [RestoreDBInstanceFromS3Response] -> ShowS
show :: RestoreDBInstanceFromS3Response -> String
$cshow :: RestoreDBInstanceFromS3Response -> String
showsPrec :: Int -> RestoreDBInstanceFromS3Response -> ShowS
$cshowsPrec :: Int -> RestoreDBInstanceFromS3Response -> ShowS
Prelude.Show, forall x.
Rep RestoreDBInstanceFromS3Response x
-> RestoreDBInstanceFromS3Response
forall x.
RestoreDBInstanceFromS3Response
-> Rep RestoreDBInstanceFromS3Response x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cto :: forall x.
Rep RestoreDBInstanceFromS3Response x
-> RestoreDBInstanceFromS3Response
$cfrom :: forall x.
RestoreDBInstanceFromS3Response
-> Rep RestoreDBInstanceFromS3Response x
Prelude.Generic)

-- |
-- Create a value of 'RestoreDBInstanceFromS3Response' 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:
--
-- 'dbInstance', 'restoreDBInstanceFromS3Response_dbInstance' - Undocumented member.
--
-- 'httpStatus', 'restoreDBInstanceFromS3Response_httpStatus' - The response's http status code.
newRestoreDBInstanceFromS3Response ::
  -- | 'httpStatus'
  Prelude.Int ->
  RestoreDBInstanceFromS3Response
newRestoreDBInstanceFromS3Response :: Int -> RestoreDBInstanceFromS3Response
newRestoreDBInstanceFromS3Response Int
pHttpStatus_ =
  RestoreDBInstanceFromS3Response'
    { $sel:dbInstance:RestoreDBInstanceFromS3Response' :: Maybe DBInstance
dbInstance =
        forall a. Maybe a
Prelude.Nothing,
      $sel:httpStatus:RestoreDBInstanceFromS3Response' :: Int
httpStatus = Int
pHttpStatus_
    }

-- | Undocumented member.
restoreDBInstanceFromS3Response_dbInstance :: Lens.Lens' RestoreDBInstanceFromS3Response (Prelude.Maybe DBInstance)
restoreDBInstanceFromS3Response_dbInstance :: Lens' RestoreDBInstanceFromS3Response (Maybe DBInstance)
restoreDBInstanceFromS3Response_dbInstance = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\RestoreDBInstanceFromS3Response' {Maybe DBInstance
dbInstance :: Maybe DBInstance
$sel:dbInstance:RestoreDBInstanceFromS3Response' :: RestoreDBInstanceFromS3Response -> Maybe DBInstance
dbInstance} -> Maybe DBInstance
dbInstance) (\s :: RestoreDBInstanceFromS3Response
s@RestoreDBInstanceFromS3Response' {} Maybe DBInstance
a -> RestoreDBInstanceFromS3Response
s {$sel:dbInstance:RestoreDBInstanceFromS3Response' :: Maybe DBInstance
dbInstance = Maybe DBInstance
a} :: RestoreDBInstanceFromS3Response)

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

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