{-# LANGUAGE DeriveGeneric #-}
{-# LANGUAGE DuplicateRecordFields #-}
{-# LANGUAGE NamedFieldPuns #-}
{-# LANGUAGE OverloadedStrings #-}
{-# LANGUAGE RecordWildCards #-}
{-# LANGUAGE StrictData #-}
{-# LANGUAGE NoImplicitPrelude #-}
{-# 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.Types.DBInstance
-- Copyright   : (c) 2013-2023 Brendan Hay
-- License     : Mozilla Public License, v. 2.0.
-- Maintainer  : Brendan Hay
-- Stability   : auto-generated
-- Portability : non-portable (GHC extensions)
module Amazonka.RDS.Types.DBInstance 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.ActivityStreamMode
import Amazonka.RDS.Types.ActivityStreamPolicyStatus
import Amazonka.RDS.Types.ActivityStreamStatus
import Amazonka.RDS.Types.AutomationMode
import Amazonka.RDS.Types.CertificateDetails
import Amazonka.RDS.Types.DBInstanceAutomatedBackupsReplication
import Amazonka.RDS.Types.DBInstanceRole
import Amazonka.RDS.Types.DBInstanceStatusInfo
import Amazonka.RDS.Types.DBParameterGroupStatus
import Amazonka.RDS.Types.DBSecurityGroupMembership
import Amazonka.RDS.Types.DBSubnetGroup
import Amazonka.RDS.Types.DomainMembership
import Amazonka.RDS.Types.Endpoint
import Amazonka.RDS.Types.MasterUserSecret
import Amazonka.RDS.Types.OptionGroupMembership
import Amazonka.RDS.Types.PendingModifiedValues
import Amazonka.RDS.Types.ProcessorFeature
import Amazonka.RDS.Types.ReplicaMode
import Amazonka.RDS.Types.Tag
import Amazonka.RDS.Types.VpcSecurityGroupMembership

-- | Contains the details of an Amazon RDS DB instance.
--
-- This data type is used as a response element in the operations
-- @CreateDBInstance@, @CreateDBInstanceReadReplica@, @DeleteDBInstance@,
-- @DescribeDBInstances@, @ModifyDBInstance@, @PromoteReadReplica@,
-- @RebootDBInstance@, @RestoreDBInstanceFromDBSnapshot@,
-- @RestoreDBInstanceFromS3@, @RestoreDBInstanceToPointInTime@,
-- @StartDBInstance@, and @StopDBInstance@.
--
-- /See:/ 'newDBInstance' smart constructor.
data DBInstance = DBInstance'
  { -- | Indicates whether engine-native audit fields are included in the
    -- database activity stream.
    DBInstance -> Maybe Bool
activityStreamEngineNativeAuditFieldsIncluded :: Prelude.Maybe Prelude.Bool,
    -- | The name of the Amazon Kinesis data stream used for the database
    -- activity stream.
    DBInstance -> Maybe Text
activityStreamKinesisStreamName :: Prelude.Maybe Prelude.Text,
    -- | The Amazon Web Services KMS key identifier used for encrypting messages
    -- in the database activity stream. The Amazon Web Services KMS key
    -- identifier is the key ARN, key ID, alias ARN, or alias name for the KMS
    -- key.
    DBInstance -> Maybe Text
activityStreamKmsKeyId :: Prelude.Maybe Prelude.Text,
    -- | The mode of the database activity stream. Database events such as a
    -- change or access generate an activity stream event. RDS for Oracle
    -- always handles these events asynchronously.
    DBInstance -> Maybe ActivityStreamMode
activityStreamMode :: Prelude.Maybe ActivityStreamMode,
    -- | The status of the policy state of the activity stream.
    DBInstance -> Maybe ActivityStreamPolicyStatus
activityStreamPolicyStatus :: Prelude.Maybe ActivityStreamPolicyStatus,
    -- | The status of the database activity stream.
    DBInstance -> Maybe ActivityStreamStatus
activityStreamStatus :: Prelude.Maybe ActivityStreamStatus,
    -- | Specifies the allocated storage size specified in gibibytes (GiB).
    DBInstance -> Maybe Int
allocatedStorage :: Prelude.Maybe Prelude.Int,
    -- | The Amazon Web Services Identity and Access Management (IAM) roles
    -- associated with the DB instance.
    DBInstance -> Maybe [DBInstanceRole]
associatedRoles :: Prelude.Maybe [DBInstanceRole],
    -- | A value that indicates that minor version patches are applied
    -- automatically.
    DBInstance -> Maybe Bool
autoMinorVersionUpgrade :: Prelude.Maybe Prelude.Bool,
    -- | The time when a stopped DB instance is restarted automatically.
    DBInstance -> Maybe ISO8601
automaticRestartTime :: Prelude.Maybe Data.ISO8601,
    -- | The automation mode of the RDS Custom DB instance: @full@ or
    -- @all paused@. If @full@, the DB instance automates monitoring and
    -- instance recovery. If @all paused@, the instance pauses automation for
    -- the duration set by @--resume-full-automation-mode-minutes@.
    DBInstance -> Maybe AutomationMode
automationMode :: Prelude.Maybe AutomationMode,
    -- | Specifies the name of the Availability Zone the DB instance is located
    -- in.
    DBInstance -> Maybe Text
availabilityZone :: Prelude.Maybe Prelude.Text,
    -- | The Amazon Resource Name (ARN) of the recovery point in Amazon Web
    -- Services Backup.
    DBInstance -> Maybe Text
awsBackupRecoveryPointArn :: Prelude.Maybe Prelude.Text,
    -- | Specifies the number of days for which automatic DB snapshots are
    -- retained.
    DBInstance -> Maybe Int
backupRetentionPeriod :: Prelude.Maybe Prelude.Int,
    -- | Specifies where automated backups and manual snapshots are stored:
    -- Amazon Web Services Outposts or the Amazon Web Services Region.
    DBInstance -> Maybe Text
backupTarget :: Prelude.Maybe Prelude.Text,
    -- | The identifier of the CA certificate for this DB instance.
    --
    -- For more information, see
    -- <https://docs.aws.amazon.com/AmazonRDS/latest/UserGuide/UsingWithRDS.SSL.html Using SSL\/TLS to encrypt a connection to a DB instance>
    -- in the /Amazon RDS User Guide/ and
    -- <https://docs.aws.amazon.com/AmazonRDS/latest/AuroraUserGuide/UsingWithRDS.SSL.html Using SSL\/TLS to encrypt a connection to a DB cluster>
    -- in the /Amazon Aurora User Guide/.
    DBInstance -> Maybe Text
cACertificateIdentifier :: Prelude.Maybe Prelude.Text,
    -- | The details of the DB instance\'s server certificate.
    DBInstance -> Maybe CertificateDetails
certificateDetails :: Prelude.Maybe CertificateDetails,
    -- | If present, specifies the name of the character set that this instance
    -- is associated with.
    DBInstance -> Maybe Text
characterSetName :: Prelude.Maybe Prelude.Text,
    -- | Specifies whether tags are copied from the DB instance to snapshots of
    -- the DB instance.
    --
    -- __Amazon Aurora__
    --
    -- Not applicable. Copying tags to snapshots is managed by the DB cluster.
    -- Setting this value for an Aurora DB instance has no effect on the DB
    -- cluster setting. For more information, see @DBCluster@.
    DBInstance -> Maybe Bool
copyTagsToSnapshot :: Prelude.Maybe Prelude.Bool,
    -- | The instance profile associated with the underlying Amazon EC2 instance
    -- of an RDS Custom DB instance. The instance profile must meet the
    -- following requirements:
    --
    -- -   The profile must exist in your account.
    --
    -- -   The profile must have an IAM role that Amazon EC2 has permissions to
    --     assume.
    --
    -- -   The instance profile name and the associated IAM role name must
    --     start with the prefix @AWSRDSCustom@.
    --
    -- For the list of permissions required for the IAM role, see
    -- <https://docs.aws.amazon.com/AmazonRDS/latest/UserGuide/custom-setup-orcl.html#custom-setup-orcl.iam-vpc Configure IAM and your VPC>
    -- in the /Amazon RDS User Guide/.
    DBInstance -> Maybe Text
customIamInstanceProfile :: Prelude.Maybe Prelude.Text,
    -- | Specifies whether a customer-owned IP address (CoIP) is enabled for an
    -- RDS on Outposts DB instance.
    --
    -- A /CoIP/ provides local or external connectivity to resources in your
    -- Outpost subnets through your on-premises network. For some use cases, a
    -- CoIP can provide lower latency for connections to the DB instance from
    -- outside of its virtual private cloud (VPC) on your local network.
    --
    -- For more information about RDS on Outposts, see
    -- <https://docs.aws.amazon.com/AmazonRDS/latest/UserGuide/rds-on-outposts.html Working with Amazon RDS on Amazon Web Services Outposts>
    -- in the /Amazon RDS User Guide/.
    --
    -- For more information about CoIPs, see
    -- <https://docs.aws.amazon.com/outposts/latest/userguide/routing.html#ip-addressing Customer-owned IP addresses>
    -- in the /Amazon Web Services Outposts User Guide/.
    DBInstance -> Maybe Bool
customerOwnedIpEnabled :: Prelude.Maybe Prelude.Bool,
    -- | If the DB instance is a member of a DB cluster, contains the name of the
    -- DB cluster that the DB instance is a member of.
    DBInstance -> Maybe Text
dbClusterIdentifier :: Prelude.Maybe Prelude.Text,
    -- | The Amazon Resource Name (ARN) for the DB instance.
    DBInstance -> Maybe Text
dbInstanceArn :: Prelude.Maybe Prelude.Text,
    -- | The list of replicated automated backups associated with the DB
    -- instance.
    DBInstance -> Maybe [DBInstanceAutomatedBackupsReplication]
dbInstanceAutomatedBackupsReplications :: Prelude.Maybe [DBInstanceAutomatedBackupsReplication],
    -- | Contains the name of the compute and memory capacity class of the DB
    -- instance.
    DBInstance -> Maybe Text
dbInstanceClass :: Prelude.Maybe Prelude.Text,
    -- | Contains a user-supplied database identifier. This identifier is the
    -- unique key that identifies a DB instance.
    DBInstance -> Maybe Text
dbInstanceIdentifier :: Prelude.Maybe Prelude.Text,
    -- | Specifies the current state of this database.
    --
    -- For information about DB instance statuses, see
    -- <https://docs.aws.amazon.com/AmazonRDS/latest/UserGuide/accessing-monitoring.html#Overview.DBInstance.Status Viewing DB instance status>
    -- in the /Amazon RDS User Guide./
    DBInstance -> Maybe Text
dbInstanceStatus :: Prelude.Maybe Prelude.Text,
    -- | The meaning of this parameter differs according to the database engine
    -- you use.
    --
    -- __MySQL, MariaDB, SQL Server, PostgreSQL__
    --
    -- Contains the name of the initial database of this instance that was
    -- provided at create time, if one was specified when the DB instance was
    -- created. This same name is returned for the life of the DB instance.
    --
    -- Type: String
    --
    -- __Oracle__
    --
    -- Contains the Oracle System ID (SID) of the created DB instance. Not
    -- shown when the returned parameters do not apply to an Oracle DB
    -- instance.
    DBInstance -> Maybe Text
dbName :: Prelude.Maybe Prelude.Text,
    -- | Provides the list of DB parameter groups applied to this DB instance.
    DBInstance -> Maybe [DBParameterGroupStatus]
dbParameterGroups :: Prelude.Maybe [DBParameterGroupStatus],
    -- | A list of DB security group elements containing @DBSecurityGroup.Name@
    -- and @DBSecurityGroup.Status@ subelements.
    DBInstance -> Maybe [DBSecurityGroupMembership]
dbSecurityGroups :: Prelude.Maybe [DBSecurityGroupMembership],
    -- | Specifies information on the subnet group associated with the DB
    -- instance, including the name, description, and subnets in the subnet
    -- group.
    DBInstance -> Maybe DBSubnetGroup
dbSubnetGroup :: Prelude.Maybe DBSubnetGroup,
    -- | The Oracle system ID (Oracle SID) for a container database (CDB). The
    -- Oracle SID is also the name of the CDB. This setting is valid for RDS
    -- Custom only.
    DBInstance -> Maybe Text
dbSystemId :: Prelude.Maybe Prelude.Text,
    -- | Specifies the port that the DB instance listens on. If the DB instance
    -- is part of a DB cluster, this can be a different port than the DB
    -- cluster port.
    DBInstance -> Maybe Int
dbInstancePort :: Prelude.Maybe Prelude.Int,
    -- | The Amazon Web Services Region-unique, immutable identifier for the DB
    -- instance. This identifier is found in Amazon Web Services CloudTrail log
    -- entries whenever the Amazon Web Services KMS key for the DB instance is
    -- accessed.
    DBInstance -> Maybe Text
dbiResourceId :: Prelude.Maybe Prelude.Text,
    -- | Indicates if the DB instance has deletion protection enabled. The
    -- database can\'t be deleted when deletion protection is enabled. For more
    -- information, see
    -- <https://docs.aws.amazon.com/AmazonRDS/latest/UserGuide/USER_DeleteInstance.html Deleting a DB Instance>.
    DBInstance -> Maybe Bool
deletionProtection :: Prelude.Maybe Prelude.Bool,
    -- | The Active Directory Domain membership records associated with the DB
    -- instance.
    DBInstance -> Maybe [DomainMembership]
domainMemberships :: Prelude.Maybe [DomainMembership],
    -- | A list of log types that this DB instance is configured to export to
    -- CloudWatch Logs.
    --
    -- Log types vary by DB engine. For information about the log types for
    -- each DB engine, see
    -- <https://docs.aws.amazon.com/AmazonRDS/latest/UserGuide/USER_LogAccess.html Amazon RDS Database Log Files>
    -- in the /Amazon RDS User Guide./
    DBInstance -> Maybe [Text]
enabledCloudwatchLogsExports :: Prelude.Maybe [Prelude.Text],
    -- | Specifies the connection endpoint.
    --
    -- The endpoint might not be shown for instances whose status is
    -- @creating@.
    DBInstance -> Maybe Endpoint
endpoint :: Prelude.Maybe Endpoint,
    -- | The name of the database engine to be used for this DB instance.
    DBInstance -> Maybe Text
engine :: Prelude.Maybe Prelude.Text,
    -- | Indicates the database engine version.
    DBInstance -> Maybe Text
engineVersion :: Prelude.Maybe Prelude.Text,
    -- | The Amazon Resource Name (ARN) of the Amazon CloudWatch Logs log stream
    -- that receives the Enhanced Monitoring metrics data for the DB instance.
    DBInstance -> Maybe Text
enhancedMonitoringResourceArn :: Prelude.Maybe Prelude.Text,
    -- | True if mapping of Amazon Web Services Identity and Access Management
    -- (IAM) accounts to database accounts is enabled, and otherwise false.
    --
    -- IAM database authentication can be enabled for the following database
    -- engines
    --
    -- -   For MySQL 5.6, minor version 5.6.34 or higher
    --
    -- -   For MySQL 5.7, minor version 5.7.16 or higher
    --
    -- -   Aurora 5.6 or higher. To enable IAM database authentication for
    --     Aurora, see DBCluster Type.
    DBInstance -> Maybe Bool
iAMDatabaseAuthenticationEnabled :: Prelude.Maybe Prelude.Bool,
    -- | Provides the date and time the DB instance was created.
    DBInstance -> Maybe ISO8601
instanceCreateTime :: Prelude.Maybe Data.ISO8601,
    -- | Specifies the Provisioned IOPS (I\/O operations per second) value.
    DBInstance -> Maybe Int
iops :: Prelude.Maybe Prelude.Int,
    -- | If @StorageEncrypted@ is true, the Amazon Web Services KMS key
    -- identifier for the 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.
    DBInstance -> Maybe Text
kmsKeyId :: Prelude.Maybe Prelude.Text,
    -- | Specifies the latest time to which a database can be restored with
    -- point-in-time restore.
    DBInstance -> Maybe ISO8601
latestRestorableTime :: Prelude.Maybe Data.ISO8601,
    -- | License model information for this DB instance. This setting doesn\'t
    -- apply to RDS Custom.
    DBInstance -> Maybe Text
licenseModel :: Prelude.Maybe Prelude.Text,
    -- | Specifies the listener connection endpoint for SQL Server Always On.
    DBInstance -> Maybe Endpoint
listenerEndpoint :: Prelude.Maybe Endpoint,
    -- | Contains the secret managed by RDS in Amazon Web Services Secrets
    -- Manager for the master user password.
    --
    -- 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./
    DBInstance -> Maybe MasterUserSecret
masterUserSecret :: Prelude.Maybe MasterUserSecret,
    -- | Contains the master username for the DB instance.
    DBInstance -> 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.
    DBInstance -> Maybe Int
maxAllocatedStorage :: Prelude.Maybe Prelude.Int,
    -- | The interval, in seconds, between points when Enhanced Monitoring
    -- metrics are collected for the DB instance.
    DBInstance -> 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.
    DBInstance -> Maybe Text
monitoringRoleArn :: Prelude.Maybe Prelude.Text,
    -- | Specifies if the DB instance is a Multi-AZ deployment. This setting
    -- doesn\'t apply to RDS Custom.
    DBInstance -> Maybe Bool
multiAZ :: Prelude.Maybe Prelude.Bool,
    -- | The name of the NCHAR character set for the Oracle DB instance. This
    -- character set specifies the Unicode encoding for data stored in table
    -- columns of type NCHAR, NCLOB, or NVARCHAR2.
    DBInstance -> Maybe Text
ncharCharacterSetName :: Prelude.Maybe Prelude.Text,
    -- | 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/ and
    -- <https://docs.aws.amazon.com/AmazonRDS/latest/AuroraUserGuide/USER_VPC.WorkingWithRDSInstanceinaVPC.html Working with a DB instance in a VPC>
    -- in the /Amazon Aurora User Guide./
    DBInstance -> Maybe Text
networkType :: Prelude.Maybe Prelude.Text,
    -- | Provides the list of option group memberships for this DB instance.
    DBInstance -> Maybe [OptionGroupMembership]
optionGroupMemberships :: Prelude.Maybe [OptionGroupMembership],
    -- | A value that specifies that changes to the DB instance are pending. This
    -- element is only included when changes are pending. Specific changes are
    -- identified by subelements.
    DBInstance -> Maybe PendingModifiedValues
pendingModifiedValues :: Prelude.Maybe PendingModifiedValues,
    -- | True if Performance Insights is enabled for the DB instance, and
    -- otherwise false.
    DBInstance -> Maybe Bool
performanceInsightsEnabled :: Prelude.Maybe Prelude.Bool,
    -- | 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.
    DBInstance -> 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
    DBInstance -> Maybe Int
performanceInsightsRetentionPeriod :: Prelude.Maybe Prelude.Int,
    -- | Specifies the daily time range during which automated backups are
    -- created if automated backups are enabled, as determined by the
    -- @BackupRetentionPeriod@.
    DBInstance -> Maybe Text
preferredBackupWindow :: Prelude.Maybe Prelude.Text,
    -- | Specifies the weekly time range during which system maintenance can
    -- occur, in Universal Coordinated Time (UTC).
    DBInstance -> 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.
    DBInstance -> Maybe [ProcessorFeature]
processorFeatures :: Prelude.Maybe [ProcessorFeature],
    -- | A value that specifies the order in which an Aurora Replica is promoted
    -- to the primary instance after a failure of the existing primary
    -- instance. For more information, see
    -- <https://docs.aws.amazon.com/AmazonRDS/latest/AuroraUserGuide/Aurora.Managing.Backups.html#Aurora.Managing.FaultTolerance Fault Tolerance for an Aurora DB Cluster>
    -- in the /Amazon Aurora User Guide/.
    DBInstance -> Maybe Int
promotionTier :: Prelude.Maybe Prelude.Int,
    -- | Specifies the accessibility options for the DB instance.
    --
    -- When the DB cluster is publicly accessible, its Domain Name System (DNS)
    -- endpoint resolves to the private IP address from within the DB
    -- cluster\'s virtual private cloud (VPC). It resolves to the public IP
    -- address from outside of the DB cluster\'s VPC. Access to the DB cluster
    -- is ultimately controlled by the security group it uses. That public
    -- access isn\'t permitted if the security group assigned to the DB cluster
    -- 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.
    DBInstance -> Maybe Bool
publiclyAccessible :: Prelude.Maybe Prelude.Bool,
    -- | Contains one or more identifiers of Aurora DB clusters to which the RDS
    -- DB instance is replicated as a read replica. For example, when you
    -- create an Aurora read replica of an RDS for MySQL DB instance, the
    -- Aurora MySQL DB cluster for the Aurora read replica is shown. This
    -- output doesn\'t contain information about cross-Region Aurora read
    -- replicas.
    --
    -- Currently, each RDS DB instance can have only one Aurora read replica.
    DBInstance -> Maybe [Text]
readReplicaDBClusterIdentifiers :: Prelude.Maybe [Prelude.Text],
    -- | Contains one or more identifiers of the read replicas associated with
    -- this DB instance.
    DBInstance -> Maybe [Text]
readReplicaDBInstanceIdentifiers :: Prelude.Maybe [Prelude.Text],
    -- | Contains the identifier of the source DB instance if this DB instance is
    -- a read replica.
    DBInstance -> Maybe Text
readReplicaSourceDBInstanceIdentifier :: Prelude.Maybe Prelude.Text,
    -- | The open mode of an Oracle read replica. The default is
    -- @open-read-only@. For more information, see
    -- <https://docs.aws.amazon.com/AmazonRDS/latest/UserGuide/oracle-read-replicas.html Working with Oracle Read Replicas for Amazon RDS>
    -- in the /Amazon RDS User Guide/.
    --
    -- This attribute is only supported in RDS for Oracle.
    DBInstance -> Maybe ReplicaMode
replicaMode :: Prelude.Maybe ReplicaMode,
    -- | The number of minutes to pause the automation. When the time period
    -- ends, RDS Custom resumes full automation. The minimum value is 60
    -- (default). The maximum value is 1,440.
    DBInstance -> Maybe ISO8601
resumeFullAutomationModeTime :: Prelude.Maybe Data.ISO8601,
    -- | If present, specifies the name of the secondary Availability Zone for a
    -- DB instance with multi-AZ support.
    DBInstance -> Maybe Text
secondaryAvailabilityZone :: Prelude.Maybe Prelude.Text,
    -- | The status of a read replica. If the instance isn\'t a read replica,
    -- this is blank.
    DBInstance -> Maybe [DBInstanceStatusInfo]
statusInfos :: Prelude.Maybe [DBInstanceStatusInfo],
    -- | Specifies whether the DB instance is encrypted.
    DBInstance -> Maybe Bool
storageEncrypted :: Prelude.Maybe Prelude.Bool,
    -- | Specifies the storage throughput for the DB instance.
    --
    -- This setting applies only to the @gp3@ storage type.
    DBInstance -> Maybe Int
storageThroughput :: Prelude.Maybe Prelude.Int,
    -- | Specifies the storage type associated with the DB instance.
    DBInstance -> Maybe Text
storageType :: Prelude.Maybe Prelude.Text,
    DBInstance -> Maybe [Tag]
tagList :: Prelude.Maybe [Tag],
    -- | The ARN from the key store with which the instance is associated for TDE
    -- encryption.
    DBInstance -> Maybe Text
tdeCredentialArn :: Prelude.Maybe Prelude.Text,
    -- | The time zone of the DB instance. In most cases, the @Timezone@ element
    -- is empty. @Timezone@ content appears only for Microsoft SQL Server DB
    -- instances that were created with a time zone specified.
    DBInstance -> Maybe Text
timezone :: Prelude.Maybe Prelude.Text,
    -- | Provides a list of VPC security group elements that the DB instance
    -- belongs to.
    DBInstance -> Maybe [VpcSecurityGroupMembership]
vpcSecurityGroups :: Prelude.Maybe [VpcSecurityGroupMembership]
  }
  deriving (DBInstance -> DBInstance -> Bool
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: DBInstance -> DBInstance -> Bool
$c/= :: DBInstance -> DBInstance -> Bool
== :: DBInstance -> DBInstance -> Bool
$c== :: DBInstance -> DBInstance -> Bool
Prelude.Eq, ReadPrec [DBInstance]
ReadPrec DBInstance
Int -> ReadS DBInstance
ReadS [DBInstance]
forall a.
(Int -> ReadS a)
-> ReadS [a] -> ReadPrec a -> ReadPrec [a] -> Read a
readListPrec :: ReadPrec [DBInstance]
$creadListPrec :: ReadPrec [DBInstance]
readPrec :: ReadPrec DBInstance
$creadPrec :: ReadPrec DBInstance
readList :: ReadS [DBInstance]
$creadList :: ReadS [DBInstance]
readsPrec :: Int -> ReadS DBInstance
$creadsPrec :: Int -> ReadS DBInstance
Prelude.Read, Int -> DBInstance -> ShowS
[DBInstance] -> ShowS
DBInstance -> String
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [DBInstance] -> ShowS
$cshowList :: [DBInstance] -> ShowS
show :: DBInstance -> String
$cshow :: DBInstance -> String
showsPrec :: Int -> DBInstance -> ShowS
$cshowsPrec :: Int -> DBInstance -> ShowS
Prelude.Show, forall x. Rep DBInstance x -> DBInstance
forall x. DBInstance -> Rep DBInstance x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cto :: forall x. Rep DBInstance x -> DBInstance
$cfrom :: forall x. DBInstance -> Rep DBInstance x
Prelude.Generic)

-- |
-- Create a value of 'DBInstance' 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:
--
-- 'activityStreamEngineNativeAuditFieldsIncluded', 'dbInstance_activityStreamEngineNativeAuditFieldsIncluded' - Indicates whether engine-native audit fields are included in the
-- database activity stream.
--
-- 'activityStreamKinesisStreamName', 'dbInstance_activityStreamKinesisStreamName' - The name of the Amazon Kinesis data stream used for the database
-- activity stream.
--
-- 'activityStreamKmsKeyId', 'dbInstance_activityStreamKmsKeyId' - The Amazon Web Services KMS key identifier used for encrypting messages
-- in the database activity stream. The Amazon Web Services KMS key
-- identifier is the key ARN, key ID, alias ARN, or alias name for the KMS
-- key.
--
-- 'activityStreamMode', 'dbInstance_activityStreamMode' - The mode of the database activity stream. Database events such as a
-- change or access generate an activity stream event. RDS for Oracle
-- always handles these events asynchronously.
--
-- 'activityStreamPolicyStatus', 'dbInstance_activityStreamPolicyStatus' - The status of the policy state of the activity stream.
--
-- 'activityStreamStatus', 'dbInstance_activityStreamStatus' - The status of the database activity stream.
--
-- 'allocatedStorage', 'dbInstance_allocatedStorage' - Specifies the allocated storage size specified in gibibytes (GiB).
--
-- 'associatedRoles', 'dbInstance_associatedRoles' - The Amazon Web Services Identity and Access Management (IAM) roles
-- associated with the DB instance.
--
-- 'autoMinorVersionUpgrade', 'dbInstance_autoMinorVersionUpgrade' - A value that indicates that minor version patches are applied
-- automatically.
--
-- 'automaticRestartTime', 'dbInstance_automaticRestartTime' - The time when a stopped DB instance is restarted automatically.
--
-- 'automationMode', 'dbInstance_automationMode' - The automation mode of the RDS Custom DB instance: @full@ or
-- @all paused@. If @full@, the DB instance automates monitoring and
-- instance recovery. If @all paused@, the instance pauses automation for
-- the duration set by @--resume-full-automation-mode-minutes@.
--
-- 'availabilityZone', 'dbInstance_availabilityZone' - Specifies the name of the Availability Zone the DB instance is located
-- in.
--
-- 'awsBackupRecoveryPointArn', 'dbInstance_awsBackupRecoveryPointArn' - The Amazon Resource Name (ARN) of the recovery point in Amazon Web
-- Services Backup.
--
-- 'backupRetentionPeriod', 'dbInstance_backupRetentionPeriod' - Specifies the number of days for which automatic DB snapshots are
-- retained.
--
-- 'backupTarget', 'dbInstance_backupTarget' - Specifies where automated backups and manual snapshots are stored:
-- Amazon Web Services Outposts or the Amazon Web Services Region.
--
-- 'cACertificateIdentifier', 'dbInstance_cACertificateIdentifier' - The identifier of the CA certificate for this DB instance.
--
-- For more information, see
-- <https://docs.aws.amazon.com/AmazonRDS/latest/UserGuide/UsingWithRDS.SSL.html Using SSL\/TLS to encrypt a connection to a DB instance>
-- in the /Amazon RDS User Guide/ and
-- <https://docs.aws.amazon.com/AmazonRDS/latest/AuroraUserGuide/UsingWithRDS.SSL.html Using SSL\/TLS to encrypt a connection to a DB cluster>
-- in the /Amazon Aurora User Guide/.
--
-- 'certificateDetails', 'dbInstance_certificateDetails' - The details of the DB instance\'s server certificate.
--
-- 'characterSetName', 'dbInstance_characterSetName' - If present, specifies the name of the character set that this instance
-- is associated with.
--
-- 'copyTagsToSnapshot', 'dbInstance_copyTagsToSnapshot' - Specifies whether tags are copied from the DB instance to snapshots of
-- the DB instance.
--
-- __Amazon Aurora__
--
-- Not applicable. Copying tags to snapshots is managed by the DB cluster.
-- Setting this value for an Aurora DB instance has no effect on the DB
-- cluster setting. For more information, see @DBCluster@.
--
-- 'customIamInstanceProfile', 'dbInstance_customIamInstanceProfile' - The instance profile associated with the underlying Amazon EC2 instance
-- of an RDS Custom DB instance. The instance profile must meet the
-- following requirements:
--
-- -   The profile must exist in your account.
--
-- -   The profile must have an IAM role that Amazon EC2 has permissions to
--     assume.
--
-- -   The instance profile name and the associated IAM role name must
--     start with the prefix @AWSRDSCustom@.
--
-- For the list of permissions required for the IAM role, see
-- <https://docs.aws.amazon.com/AmazonRDS/latest/UserGuide/custom-setup-orcl.html#custom-setup-orcl.iam-vpc Configure IAM and your VPC>
-- in the /Amazon RDS User Guide/.
--
-- 'customerOwnedIpEnabled', 'dbInstance_customerOwnedIpEnabled' - Specifies whether a customer-owned IP address (CoIP) is enabled for an
-- RDS on Outposts DB instance.
--
-- A /CoIP/ provides local or external connectivity to resources in your
-- Outpost subnets through your on-premises network. For some use cases, a
-- CoIP can provide lower latency for connections to the DB instance from
-- outside of its virtual private cloud (VPC) on your local network.
--
-- For more information about RDS on Outposts, see
-- <https://docs.aws.amazon.com/AmazonRDS/latest/UserGuide/rds-on-outposts.html Working with Amazon RDS on Amazon Web Services Outposts>
-- in the /Amazon RDS User Guide/.
--
-- For more information about CoIPs, see
-- <https://docs.aws.amazon.com/outposts/latest/userguide/routing.html#ip-addressing Customer-owned IP addresses>
-- in the /Amazon Web Services Outposts User Guide/.
--
-- 'dbClusterIdentifier', 'dbInstance_dbClusterIdentifier' - If the DB instance is a member of a DB cluster, contains the name of the
-- DB cluster that the DB instance is a member of.
--
-- 'dbInstanceArn', 'dbInstance_dbInstanceArn' - The Amazon Resource Name (ARN) for the DB instance.
--
-- 'dbInstanceAutomatedBackupsReplications', 'dbInstance_dbInstanceAutomatedBackupsReplications' - The list of replicated automated backups associated with the DB
-- instance.
--
-- 'dbInstanceClass', 'dbInstance_dbInstanceClass' - Contains the name of the compute and memory capacity class of the DB
-- instance.
--
-- 'dbInstanceIdentifier', 'dbInstance_dbInstanceIdentifier' - Contains a user-supplied database identifier. This identifier is the
-- unique key that identifies a DB instance.
--
-- 'dbInstanceStatus', 'dbInstance_dbInstanceStatus' - Specifies the current state of this database.
--
-- For information about DB instance statuses, see
-- <https://docs.aws.amazon.com/AmazonRDS/latest/UserGuide/accessing-monitoring.html#Overview.DBInstance.Status Viewing DB instance status>
-- in the /Amazon RDS User Guide./
--
-- 'dbName', 'dbInstance_dbName' - The meaning of this parameter differs according to the database engine
-- you use.
--
-- __MySQL, MariaDB, SQL Server, PostgreSQL__
--
-- Contains the name of the initial database of this instance that was
-- provided at create time, if one was specified when the DB instance was
-- created. This same name is returned for the life of the DB instance.
--
-- Type: String
--
-- __Oracle__
--
-- Contains the Oracle System ID (SID) of the created DB instance. Not
-- shown when the returned parameters do not apply to an Oracle DB
-- instance.
--
-- 'dbParameterGroups', 'dbInstance_dbParameterGroups' - Provides the list of DB parameter groups applied to this DB instance.
--
-- 'dbSecurityGroups', 'dbInstance_dbSecurityGroups' - A list of DB security group elements containing @DBSecurityGroup.Name@
-- and @DBSecurityGroup.Status@ subelements.
--
-- 'dbSubnetGroup', 'dbInstance_dbSubnetGroup' - Specifies information on the subnet group associated with the DB
-- instance, including the name, description, and subnets in the subnet
-- group.
--
-- 'dbSystemId', 'dbInstance_dbSystemId' - The Oracle system ID (Oracle SID) for a container database (CDB). The
-- Oracle SID is also the name of the CDB. This setting is valid for RDS
-- Custom only.
--
-- 'dbInstancePort', 'dbInstance_dbInstancePort' - Specifies the port that the DB instance listens on. If the DB instance
-- is part of a DB cluster, this can be a different port than the DB
-- cluster port.
--
-- 'dbiResourceId', 'dbInstance_dbiResourceId' - The Amazon Web Services Region-unique, immutable identifier for the DB
-- instance. This identifier is found in Amazon Web Services CloudTrail log
-- entries whenever the Amazon Web Services KMS key for the DB instance is
-- accessed.
--
-- 'deletionProtection', 'dbInstance_deletionProtection' - Indicates if the DB instance has deletion protection enabled. The
-- database can\'t be deleted when deletion protection is enabled. For more
-- information, see
-- <https://docs.aws.amazon.com/AmazonRDS/latest/UserGuide/USER_DeleteInstance.html Deleting a DB Instance>.
--
-- 'domainMemberships', 'dbInstance_domainMemberships' - The Active Directory Domain membership records associated with the DB
-- instance.
--
-- 'enabledCloudwatchLogsExports', 'dbInstance_enabledCloudwatchLogsExports' - A list of log types that this DB instance is configured to export to
-- CloudWatch Logs.
--
-- Log types vary by DB engine. For information about the log types for
-- each DB engine, see
-- <https://docs.aws.amazon.com/AmazonRDS/latest/UserGuide/USER_LogAccess.html Amazon RDS Database Log Files>
-- in the /Amazon RDS User Guide./
--
-- 'endpoint', 'dbInstance_endpoint' - Specifies the connection endpoint.
--
-- The endpoint might not be shown for instances whose status is
-- @creating@.
--
-- 'engine', 'dbInstance_engine' - The name of the database engine to be used for this DB instance.
--
-- 'engineVersion', 'dbInstance_engineVersion' - Indicates the database engine version.
--
-- 'enhancedMonitoringResourceArn', 'dbInstance_enhancedMonitoringResourceArn' - The Amazon Resource Name (ARN) of the Amazon CloudWatch Logs log stream
-- that receives the Enhanced Monitoring metrics data for the DB instance.
--
-- 'iAMDatabaseAuthenticationEnabled', 'dbInstance_iAMDatabaseAuthenticationEnabled' - True if mapping of Amazon Web Services Identity and Access Management
-- (IAM) accounts to database accounts is enabled, and otherwise false.
--
-- IAM database authentication can be enabled for the following database
-- engines
--
-- -   For MySQL 5.6, minor version 5.6.34 or higher
--
-- -   For MySQL 5.7, minor version 5.7.16 or higher
--
-- -   Aurora 5.6 or higher. To enable IAM database authentication for
--     Aurora, see DBCluster Type.
--
-- 'instanceCreateTime', 'dbInstance_instanceCreateTime' - Provides the date and time the DB instance was created.
--
-- 'iops', 'dbInstance_iops' - Specifies the Provisioned IOPS (I\/O operations per second) value.
--
-- 'kmsKeyId', 'dbInstance_kmsKeyId' - If @StorageEncrypted@ is true, the Amazon Web Services KMS key
-- identifier for the 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.
--
-- 'latestRestorableTime', 'dbInstance_latestRestorableTime' - Specifies the latest time to which a database can be restored with
-- point-in-time restore.
--
-- 'licenseModel', 'dbInstance_licenseModel' - License model information for this DB instance. This setting doesn\'t
-- apply to RDS Custom.
--
-- 'listenerEndpoint', 'dbInstance_listenerEndpoint' - Specifies the listener connection endpoint for SQL Server Always On.
--
-- 'masterUserSecret', 'dbInstance_masterUserSecret' - Contains the secret managed by RDS in Amazon Web Services Secrets
-- Manager for the master user password.
--
-- 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./
--
-- 'masterUsername', 'dbInstance_masterUsername' - Contains the master username for the DB instance.
--
-- 'maxAllocatedStorage', 'dbInstance_maxAllocatedStorage' - The upper limit in gibibytes (GiB) to which Amazon RDS can automatically
-- scale the storage of the DB instance.
--
-- 'monitoringInterval', 'dbInstance_monitoringInterval' - The interval, in seconds, between points when Enhanced Monitoring
-- metrics are collected for the DB instance.
--
-- 'monitoringRoleArn', 'dbInstance_monitoringRoleArn' - The ARN for the IAM role that permits RDS to send Enhanced Monitoring
-- metrics to Amazon CloudWatch Logs.
--
-- 'multiAZ', 'dbInstance_multiAZ' - Specifies if the DB instance is a Multi-AZ deployment. This setting
-- doesn\'t apply to RDS Custom.
--
-- 'ncharCharacterSetName', 'dbInstance_ncharCharacterSetName' - The name of the NCHAR character set for the Oracle DB instance. This
-- character set specifies the Unicode encoding for data stored in table
-- columns of type NCHAR, NCLOB, or NVARCHAR2.
--
-- 'networkType', 'dbInstance_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/ and
-- <https://docs.aws.amazon.com/AmazonRDS/latest/AuroraUserGuide/USER_VPC.WorkingWithRDSInstanceinaVPC.html Working with a DB instance in a VPC>
-- in the /Amazon Aurora User Guide./
--
-- 'optionGroupMemberships', 'dbInstance_optionGroupMemberships' - Provides the list of option group memberships for this DB instance.
--
-- 'pendingModifiedValues', 'dbInstance_pendingModifiedValues' - A value that specifies that changes to the DB instance are pending. This
-- element is only included when changes are pending. Specific changes are
-- identified by subelements.
--
-- 'performanceInsightsEnabled', 'dbInstance_performanceInsightsEnabled' - True if Performance Insights is enabled for the DB instance, and
-- otherwise false.
--
-- 'performanceInsightsKMSKeyId', 'dbInstance_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.
--
-- 'performanceInsightsRetentionPeriod', 'dbInstance_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
--
-- 'preferredBackupWindow', 'dbInstance_preferredBackupWindow' - Specifies the daily time range during which automated backups are
-- created if automated backups are enabled, as determined by the
-- @BackupRetentionPeriod@.
--
-- 'preferredMaintenanceWindow', 'dbInstance_preferredMaintenanceWindow' - Specifies the weekly time range during which system maintenance can
-- occur, in Universal Coordinated Time (UTC).
--
-- 'processorFeatures', 'dbInstance_processorFeatures' - The number of CPU cores and the number of threads per core for the DB
-- instance class of the DB instance.
--
-- 'promotionTier', 'dbInstance_promotionTier' - A value that specifies the order in which an Aurora Replica is promoted
-- to the primary instance after a failure of the existing primary
-- instance. For more information, see
-- <https://docs.aws.amazon.com/AmazonRDS/latest/AuroraUserGuide/Aurora.Managing.Backups.html#Aurora.Managing.FaultTolerance Fault Tolerance for an Aurora DB Cluster>
-- in the /Amazon Aurora User Guide/.
--
-- 'publiclyAccessible', 'dbInstance_publiclyAccessible' - Specifies the accessibility options for the DB instance.
--
-- When the DB cluster is publicly accessible, its Domain Name System (DNS)
-- endpoint resolves to the private IP address from within the DB
-- cluster\'s virtual private cloud (VPC). It resolves to the public IP
-- address from outside of the DB cluster\'s VPC. Access to the DB cluster
-- is ultimately controlled by the security group it uses. That public
-- access isn\'t permitted if the security group assigned to the DB cluster
-- 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.
--
-- 'readReplicaDBClusterIdentifiers', 'dbInstance_readReplicaDBClusterIdentifiers' - Contains one or more identifiers of Aurora DB clusters to which the RDS
-- DB instance is replicated as a read replica. For example, when you
-- create an Aurora read replica of an RDS for MySQL DB instance, the
-- Aurora MySQL DB cluster for the Aurora read replica is shown. This
-- output doesn\'t contain information about cross-Region Aurora read
-- replicas.
--
-- Currently, each RDS DB instance can have only one Aurora read replica.
--
-- 'readReplicaDBInstanceIdentifiers', 'dbInstance_readReplicaDBInstanceIdentifiers' - Contains one or more identifiers of the read replicas associated with
-- this DB instance.
--
-- 'readReplicaSourceDBInstanceIdentifier', 'dbInstance_readReplicaSourceDBInstanceIdentifier' - Contains the identifier of the source DB instance if this DB instance is
-- a read replica.
--
-- 'replicaMode', 'dbInstance_replicaMode' - The open mode of an Oracle read replica. The default is
-- @open-read-only@. For more information, see
-- <https://docs.aws.amazon.com/AmazonRDS/latest/UserGuide/oracle-read-replicas.html Working with Oracle Read Replicas for Amazon RDS>
-- in the /Amazon RDS User Guide/.
--
-- This attribute is only supported in RDS for Oracle.
--
-- 'resumeFullAutomationModeTime', 'dbInstance_resumeFullAutomationModeTime' - The number of minutes to pause the automation. When the time period
-- ends, RDS Custom resumes full automation. The minimum value is 60
-- (default). The maximum value is 1,440.
--
-- 'secondaryAvailabilityZone', 'dbInstance_secondaryAvailabilityZone' - If present, specifies the name of the secondary Availability Zone for a
-- DB instance with multi-AZ support.
--
-- 'statusInfos', 'dbInstance_statusInfos' - The status of a read replica. If the instance isn\'t a read replica,
-- this is blank.
--
-- 'storageEncrypted', 'dbInstance_storageEncrypted' - Specifies whether the DB instance is encrypted.
--
-- 'storageThroughput', 'dbInstance_storageThroughput' - Specifies the storage throughput for the DB instance.
--
-- This setting applies only to the @gp3@ storage type.
--
-- 'storageType', 'dbInstance_storageType' - Specifies the storage type associated with the DB instance.
--
-- 'tagList', 'dbInstance_tagList' - Undocumented member.
--
-- 'tdeCredentialArn', 'dbInstance_tdeCredentialArn' - The ARN from the key store with which the instance is associated for TDE
-- encryption.
--
-- 'timezone', 'dbInstance_timezone' - The time zone of the DB instance. In most cases, the @Timezone@ element
-- is empty. @Timezone@ content appears only for Microsoft SQL Server DB
-- instances that were created with a time zone specified.
--
-- 'vpcSecurityGroups', 'dbInstance_vpcSecurityGroups' - Provides a list of VPC security group elements that the DB instance
-- belongs to.
newDBInstance ::
  DBInstance
newDBInstance :: DBInstance
newDBInstance =
  DBInstance'
    { $sel:activityStreamEngineNativeAuditFieldsIncluded:DBInstance' :: Maybe Bool
activityStreamEngineNativeAuditFieldsIncluded =
        forall a. Maybe a
Prelude.Nothing,
      $sel:activityStreamKinesisStreamName:DBInstance' :: Maybe Text
activityStreamKinesisStreamName = forall a. Maybe a
Prelude.Nothing,
      $sel:activityStreamKmsKeyId:DBInstance' :: Maybe Text
activityStreamKmsKeyId = forall a. Maybe a
Prelude.Nothing,
      $sel:activityStreamMode:DBInstance' :: Maybe ActivityStreamMode
activityStreamMode = forall a. Maybe a
Prelude.Nothing,
      $sel:activityStreamPolicyStatus:DBInstance' :: Maybe ActivityStreamPolicyStatus
activityStreamPolicyStatus = forall a. Maybe a
Prelude.Nothing,
      $sel:activityStreamStatus:DBInstance' :: Maybe ActivityStreamStatus
activityStreamStatus = forall a. Maybe a
Prelude.Nothing,
      $sel:allocatedStorage:DBInstance' :: Maybe Int
allocatedStorage = forall a. Maybe a
Prelude.Nothing,
      $sel:associatedRoles:DBInstance' :: Maybe [DBInstanceRole]
associatedRoles = forall a. Maybe a
Prelude.Nothing,
      $sel:autoMinorVersionUpgrade:DBInstance' :: Maybe Bool
autoMinorVersionUpgrade = forall a. Maybe a
Prelude.Nothing,
      $sel:automaticRestartTime:DBInstance' :: Maybe ISO8601
automaticRestartTime = forall a. Maybe a
Prelude.Nothing,
      $sel:automationMode:DBInstance' :: Maybe AutomationMode
automationMode = forall a. Maybe a
Prelude.Nothing,
      $sel:availabilityZone:DBInstance' :: Maybe Text
availabilityZone = forall a. Maybe a
Prelude.Nothing,
      $sel:awsBackupRecoveryPointArn:DBInstance' :: Maybe Text
awsBackupRecoveryPointArn = forall a. Maybe a
Prelude.Nothing,
      $sel:backupRetentionPeriod:DBInstance' :: Maybe Int
backupRetentionPeriod = forall a. Maybe a
Prelude.Nothing,
      $sel:backupTarget:DBInstance' :: Maybe Text
backupTarget = forall a. Maybe a
Prelude.Nothing,
      $sel:cACertificateIdentifier:DBInstance' :: Maybe Text
cACertificateIdentifier = forall a. Maybe a
Prelude.Nothing,
      $sel:certificateDetails:DBInstance' :: Maybe CertificateDetails
certificateDetails = forall a. Maybe a
Prelude.Nothing,
      $sel:characterSetName:DBInstance' :: Maybe Text
characterSetName = forall a. Maybe a
Prelude.Nothing,
      $sel:copyTagsToSnapshot:DBInstance' :: Maybe Bool
copyTagsToSnapshot = forall a. Maybe a
Prelude.Nothing,
      $sel:customIamInstanceProfile:DBInstance' :: Maybe Text
customIamInstanceProfile = forall a. Maybe a
Prelude.Nothing,
      $sel:customerOwnedIpEnabled:DBInstance' :: Maybe Bool
customerOwnedIpEnabled = forall a. Maybe a
Prelude.Nothing,
      $sel:dbClusterIdentifier:DBInstance' :: Maybe Text
dbClusterIdentifier = forall a. Maybe a
Prelude.Nothing,
      $sel:dbInstanceArn:DBInstance' :: Maybe Text
dbInstanceArn = forall a. Maybe a
Prelude.Nothing,
      $sel:dbInstanceAutomatedBackupsReplications:DBInstance' :: Maybe [DBInstanceAutomatedBackupsReplication]
dbInstanceAutomatedBackupsReplications =
        forall a. Maybe a
Prelude.Nothing,
      $sel:dbInstanceClass:DBInstance' :: Maybe Text
dbInstanceClass = forall a. Maybe a
Prelude.Nothing,
      $sel:dbInstanceIdentifier:DBInstance' :: Maybe Text
dbInstanceIdentifier = forall a. Maybe a
Prelude.Nothing,
      $sel:dbInstanceStatus:DBInstance' :: Maybe Text
dbInstanceStatus = forall a. Maybe a
Prelude.Nothing,
      $sel:dbName:DBInstance' :: Maybe Text
dbName = forall a. Maybe a
Prelude.Nothing,
      $sel:dbParameterGroups:DBInstance' :: Maybe [DBParameterGroupStatus]
dbParameterGroups = forall a. Maybe a
Prelude.Nothing,
      $sel:dbSecurityGroups:DBInstance' :: Maybe [DBSecurityGroupMembership]
dbSecurityGroups = forall a. Maybe a
Prelude.Nothing,
      $sel:dbSubnetGroup:DBInstance' :: Maybe DBSubnetGroup
dbSubnetGroup = forall a. Maybe a
Prelude.Nothing,
      $sel:dbSystemId:DBInstance' :: Maybe Text
dbSystemId = forall a. Maybe a
Prelude.Nothing,
      $sel:dbInstancePort:DBInstance' :: Maybe Int
dbInstancePort = forall a. Maybe a
Prelude.Nothing,
      $sel:dbiResourceId:DBInstance' :: Maybe Text
dbiResourceId = forall a. Maybe a
Prelude.Nothing,
      $sel:deletionProtection:DBInstance' :: Maybe Bool
deletionProtection = forall a. Maybe a
Prelude.Nothing,
      $sel:domainMemberships:DBInstance' :: Maybe [DomainMembership]
domainMemberships = forall a. Maybe a
Prelude.Nothing,
      $sel:enabledCloudwatchLogsExports:DBInstance' :: Maybe [Text]
enabledCloudwatchLogsExports = forall a. Maybe a
Prelude.Nothing,
      $sel:endpoint:DBInstance' :: Maybe Endpoint
endpoint = forall a. Maybe a
Prelude.Nothing,
      $sel:engine:DBInstance' :: Maybe Text
engine = forall a. Maybe a
Prelude.Nothing,
      $sel:engineVersion:DBInstance' :: Maybe Text
engineVersion = forall a. Maybe a
Prelude.Nothing,
      $sel:enhancedMonitoringResourceArn:DBInstance' :: Maybe Text
enhancedMonitoringResourceArn = forall a. Maybe a
Prelude.Nothing,
      $sel:iAMDatabaseAuthenticationEnabled:DBInstance' :: Maybe Bool
iAMDatabaseAuthenticationEnabled = forall a. Maybe a
Prelude.Nothing,
      $sel:instanceCreateTime:DBInstance' :: Maybe ISO8601
instanceCreateTime = forall a. Maybe a
Prelude.Nothing,
      $sel:iops:DBInstance' :: Maybe Int
iops = forall a. Maybe a
Prelude.Nothing,
      $sel:kmsKeyId:DBInstance' :: Maybe Text
kmsKeyId = forall a. Maybe a
Prelude.Nothing,
      $sel:latestRestorableTime:DBInstance' :: Maybe ISO8601
latestRestorableTime = forall a. Maybe a
Prelude.Nothing,
      $sel:licenseModel:DBInstance' :: Maybe Text
licenseModel = forall a. Maybe a
Prelude.Nothing,
      $sel:listenerEndpoint:DBInstance' :: Maybe Endpoint
listenerEndpoint = forall a. Maybe a
Prelude.Nothing,
      $sel:masterUserSecret:DBInstance' :: Maybe MasterUserSecret
masterUserSecret = forall a. Maybe a
Prelude.Nothing,
      $sel:masterUsername:DBInstance' :: Maybe Text
masterUsername = forall a. Maybe a
Prelude.Nothing,
      $sel:maxAllocatedStorage:DBInstance' :: Maybe Int
maxAllocatedStorage = forall a. Maybe a
Prelude.Nothing,
      $sel:monitoringInterval:DBInstance' :: Maybe Int
monitoringInterval = forall a. Maybe a
Prelude.Nothing,
      $sel:monitoringRoleArn:DBInstance' :: Maybe Text
monitoringRoleArn = forall a. Maybe a
Prelude.Nothing,
      $sel:multiAZ:DBInstance' :: Maybe Bool
multiAZ = forall a. Maybe a
Prelude.Nothing,
      $sel:ncharCharacterSetName:DBInstance' :: Maybe Text
ncharCharacterSetName = forall a. Maybe a
Prelude.Nothing,
      $sel:networkType:DBInstance' :: Maybe Text
networkType = forall a. Maybe a
Prelude.Nothing,
      $sel:optionGroupMemberships:DBInstance' :: Maybe [OptionGroupMembership]
optionGroupMemberships = forall a. Maybe a
Prelude.Nothing,
      $sel:pendingModifiedValues:DBInstance' :: Maybe PendingModifiedValues
pendingModifiedValues = forall a. Maybe a
Prelude.Nothing,
      $sel:performanceInsightsEnabled:DBInstance' :: Maybe Bool
performanceInsightsEnabled = forall a. Maybe a
Prelude.Nothing,
      $sel:performanceInsightsKMSKeyId:DBInstance' :: Maybe Text
performanceInsightsKMSKeyId = forall a. Maybe a
Prelude.Nothing,
      $sel:performanceInsightsRetentionPeriod:DBInstance' :: Maybe Int
performanceInsightsRetentionPeriod = forall a. Maybe a
Prelude.Nothing,
      $sel:preferredBackupWindow:DBInstance' :: Maybe Text
preferredBackupWindow = forall a. Maybe a
Prelude.Nothing,
      $sel:preferredMaintenanceWindow:DBInstance' :: Maybe Text
preferredMaintenanceWindow = forall a. Maybe a
Prelude.Nothing,
      $sel:processorFeatures:DBInstance' :: Maybe [ProcessorFeature]
processorFeatures = forall a. Maybe a
Prelude.Nothing,
      $sel:promotionTier:DBInstance' :: Maybe Int
promotionTier = forall a. Maybe a
Prelude.Nothing,
      $sel:publiclyAccessible:DBInstance' :: Maybe Bool
publiclyAccessible = forall a. Maybe a
Prelude.Nothing,
      $sel:readReplicaDBClusterIdentifiers:DBInstance' :: Maybe [Text]
readReplicaDBClusterIdentifiers = forall a. Maybe a
Prelude.Nothing,
      $sel:readReplicaDBInstanceIdentifiers:DBInstance' :: Maybe [Text]
readReplicaDBInstanceIdentifiers = forall a. Maybe a
Prelude.Nothing,
      $sel:readReplicaSourceDBInstanceIdentifier:DBInstance' :: Maybe Text
readReplicaSourceDBInstanceIdentifier =
        forall a. Maybe a
Prelude.Nothing,
      $sel:replicaMode:DBInstance' :: Maybe ReplicaMode
replicaMode = forall a. Maybe a
Prelude.Nothing,
      $sel:resumeFullAutomationModeTime:DBInstance' :: Maybe ISO8601
resumeFullAutomationModeTime = forall a. Maybe a
Prelude.Nothing,
      $sel:secondaryAvailabilityZone:DBInstance' :: Maybe Text
secondaryAvailabilityZone = forall a. Maybe a
Prelude.Nothing,
      $sel:statusInfos:DBInstance' :: Maybe [DBInstanceStatusInfo]
statusInfos = forall a. Maybe a
Prelude.Nothing,
      $sel:storageEncrypted:DBInstance' :: Maybe Bool
storageEncrypted = forall a. Maybe a
Prelude.Nothing,
      $sel:storageThroughput:DBInstance' :: Maybe Int
storageThroughput = forall a. Maybe a
Prelude.Nothing,
      $sel:storageType:DBInstance' :: Maybe Text
storageType = forall a. Maybe a
Prelude.Nothing,
      $sel:tagList:DBInstance' :: Maybe [Tag]
tagList = forall a. Maybe a
Prelude.Nothing,
      $sel:tdeCredentialArn:DBInstance' :: Maybe Text
tdeCredentialArn = forall a. Maybe a
Prelude.Nothing,
      $sel:timezone:DBInstance' :: Maybe Text
timezone = forall a. Maybe a
Prelude.Nothing,
      $sel:vpcSecurityGroups:DBInstance' :: Maybe [VpcSecurityGroupMembership]
vpcSecurityGroups = forall a. Maybe a
Prelude.Nothing
    }

-- | Indicates whether engine-native audit fields are included in the
-- database activity stream.
dbInstance_activityStreamEngineNativeAuditFieldsIncluded :: Lens.Lens' DBInstance (Prelude.Maybe Prelude.Bool)
dbInstance_activityStreamEngineNativeAuditFieldsIncluded :: Lens' DBInstance (Maybe Bool)
dbInstance_activityStreamEngineNativeAuditFieldsIncluded = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\DBInstance' {Maybe Bool
activityStreamEngineNativeAuditFieldsIncluded :: Maybe Bool
$sel:activityStreamEngineNativeAuditFieldsIncluded:DBInstance' :: DBInstance -> Maybe Bool
activityStreamEngineNativeAuditFieldsIncluded} -> Maybe Bool
activityStreamEngineNativeAuditFieldsIncluded) (\s :: DBInstance
s@DBInstance' {} Maybe Bool
a -> DBInstance
s {$sel:activityStreamEngineNativeAuditFieldsIncluded:DBInstance' :: Maybe Bool
activityStreamEngineNativeAuditFieldsIncluded = Maybe Bool
a} :: DBInstance)

-- | The name of the Amazon Kinesis data stream used for the database
-- activity stream.
dbInstance_activityStreamKinesisStreamName :: Lens.Lens' DBInstance (Prelude.Maybe Prelude.Text)
dbInstance_activityStreamKinesisStreamName :: Lens' DBInstance (Maybe Text)
dbInstance_activityStreamKinesisStreamName = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\DBInstance' {Maybe Text
activityStreamKinesisStreamName :: Maybe Text
$sel:activityStreamKinesisStreamName:DBInstance' :: DBInstance -> Maybe Text
activityStreamKinesisStreamName} -> Maybe Text
activityStreamKinesisStreamName) (\s :: DBInstance
s@DBInstance' {} Maybe Text
a -> DBInstance
s {$sel:activityStreamKinesisStreamName:DBInstance' :: Maybe Text
activityStreamKinesisStreamName = Maybe Text
a} :: DBInstance)

-- | The Amazon Web Services KMS key identifier used for encrypting messages
-- in the database activity stream. The Amazon Web Services KMS key
-- identifier is the key ARN, key ID, alias ARN, or alias name for the KMS
-- key.
dbInstance_activityStreamKmsKeyId :: Lens.Lens' DBInstance (Prelude.Maybe Prelude.Text)
dbInstance_activityStreamKmsKeyId :: Lens' DBInstance (Maybe Text)
dbInstance_activityStreamKmsKeyId = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\DBInstance' {Maybe Text
activityStreamKmsKeyId :: Maybe Text
$sel:activityStreamKmsKeyId:DBInstance' :: DBInstance -> Maybe Text
activityStreamKmsKeyId} -> Maybe Text
activityStreamKmsKeyId) (\s :: DBInstance
s@DBInstance' {} Maybe Text
a -> DBInstance
s {$sel:activityStreamKmsKeyId:DBInstance' :: Maybe Text
activityStreamKmsKeyId = Maybe Text
a} :: DBInstance)

-- | The mode of the database activity stream. Database events such as a
-- change or access generate an activity stream event. RDS for Oracle
-- always handles these events asynchronously.
dbInstance_activityStreamMode :: Lens.Lens' DBInstance (Prelude.Maybe ActivityStreamMode)
dbInstance_activityStreamMode :: Lens' DBInstance (Maybe ActivityStreamMode)
dbInstance_activityStreamMode = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\DBInstance' {Maybe ActivityStreamMode
activityStreamMode :: Maybe ActivityStreamMode
$sel:activityStreamMode:DBInstance' :: DBInstance -> Maybe ActivityStreamMode
activityStreamMode} -> Maybe ActivityStreamMode
activityStreamMode) (\s :: DBInstance
s@DBInstance' {} Maybe ActivityStreamMode
a -> DBInstance
s {$sel:activityStreamMode:DBInstance' :: Maybe ActivityStreamMode
activityStreamMode = Maybe ActivityStreamMode
a} :: DBInstance)

-- | The status of the policy state of the activity stream.
dbInstance_activityStreamPolicyStatus :: Lens.Lens' DBInstance (Prelude.Maybe ActivityStreamPolicyStatus)
dbInstance_activityStreamPolicyStatus :: Lens' DBInstance (Maybe ActivityStreamPolicyStatus)
dbInstance_activityStreamPolicyStatus = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\DBInstance' {Maybe ActivityStreamPolicyStatus
activityStreamPolicyStatus :: Maybe ActivityStreamPolicyStatus
$sel:activityStreamPolicyStatus:DBInstance' :: DBInstance -> Maybe ActivityStreamPolicyStatus
activityStreamPolicyStatus} -> Maybe ActivityStreamPolicyStatus
activityStreamPolicyStatus) (\s :: DBInstance
s@DBInstance' {} Maybe ActivityStreamPolicyStatus
a -> DBInstance
s {$sel:activityStreamPolicyStatus:DBInstance' :: Maybe ActivityStreamPolicyStatus
activityStreamPolicyStatus = Maybe ActivityStreamPolicyStatus
a} :: DBInstance)

-- | The status of the database activity stream.
dbInstance_activityStreamStatus :: Lens.Lens' DBInstance (Prelude.Maybe ActivityStreamStatus)
dbInstance_activityStreamStatus :: Lens' DBInstance (Maybe ActivityStreamStatus)
dbInstance_activityStreamStatus = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\DBInstance' {Maybe ActivityStreamStatus
activityStreamStatus :: Maybe ActivityStreamStatus
$sel:activityStreamStatus:DBInstance' :: DBInstance -> Maybe ActivityStreamStatus
activityStreamStatus} -> Maybe ActivityStreamStatus
activityStreamStatus) (\s :: DBInstance
s@DBInstance' {} Maybe ActivityStreamStatus
a -> DBInstance
s {$sel:activityStreamStatus:DBInstance' :: Maybe ActivityStreamStatus
activityStreamStatus = Maybe ActivityStreamStatus
a} :: DBInstance)

-- | Specifies the allocated storage size specified in gibibytes (GiB).
dbInstance_allocatedStorage :: Lens.Lens' DBInstance (Prelude.Maybe Prelude.Int)
dbInstance_allocatedStorage :: Lens' DBInstance (Maybe Int)
dbInstance_allocatedStorage = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\DBInstance' {Maybe Int
allocatedStorage :: Maybe Int
$sel:allocatedStorage:DBInstance' :: DBInstance -> Maybe Int
allocatedStorage} -> Maybe Int
allocatedStorage) (\s :: DBInstance
s@DBInstance' {} Maybe Int
a -> DBInstance
s {$sel:allocatedStorage:DBInstance' :: Maybe Int
allocatedStorage = Maybe Int
a} :: DBInstance)

-- | The Amazon Web Services Identity and Access Management (IAM) roles
-- associated with the DB instance.
dbInstance_associatedRoles :: Lens.Lens' DBInstance (Prelude.Maybe [DBInstanceRole])
dbInstance_associatedRoles :: Lens' DBInstance (Maybe [DBInstanceRole])
dbInstance_associatedRoles = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\DBInstance' {Maybe [DBInstanceRole]
associatedRoles :: Maybe [DBInstanceRole]
$sel:associatedRoles:DBInstance' :: DBInstance -> Maybe [DBInstanceRole]
associatedRoles} -> Maybe [DBInstanceRole]
associatedRoles) (\s :: DBInstance
s@DBInstance' {} Maybe [DBInstanceRole]
a -> DBInstance
s {$sel:associatedRoles:DBInstance' :: Maybe [DBInstanceRole]
associatedRoles = Maybe [DBInstanceRole]
a} :: DBInstance) 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 that minor version patches are applied
-- automatically.
dbInstance_autoMinorVersionUpgrade :: Lens.Lens' DBInstance (Prelude.Maybe Prelude.Bool)
dbInstance_autoMinorVersionUpgrade :: Lens' DBInstance (Maybe Bool)
dbInstance_autoMinorVersionUpgrade = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\DBInstance' {Maybe Bool
autoMinorVersionUpgrade :: Maybe Bool
$sel:autoMinorVersionUpgrade:DBInstance' :: DBInstance -> Maybe Bool
autoMinorVersionUpgrade} -> Maybe Bool
autoMinorVersionUpgrade) (\s :: DBInstance
s@DBInstance' {} Maybe Bool
a -> DBInstance
s {$sel:autoMinorVersionUpgrade:DBInstance' :: Maybe Bool
autoMinorVersionUpgrade = Maybe Bool
a} :: DBInstance)

-- | The time when a stopped DB instance is restarted automatically.
dbInstance_automaticRestartTime :: Lens.Lens' DBInstance (Prelude.Maybe Prelude.UTCTime)
dbInstance_automaticRestartTime :: Lens' DBInstance (Maybe UTCTime)
dbInstance_automaticRestartTime = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\DBInstance' {Maybe ISO8601
automaticRestartTime :: Maybe ISO8601
$sel:automaticRestartTime:DBInstance' :: DBInstance -> Maybe ISO8601
automaticRestartTime} -> Maybe ISO8601
automaticRestartTime) (\s :: DBInstance
s@DBInstance' {} Maybe ISO8601
a -> DBInstance
s {$sel:automaticRestartTime:DBInstance' :: Maybe ISO8601
automaticRestartTime = Maybe ISO8601
a} :: DBInstance) 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 (a :: Format). Iso' (Time a) UTCTime
Data._Time

-- | The automation mode of the RDS Custom DB instance: @full@ or
-- @all paused@. If @full@, the DB instance automates monitoring and
-- instance recovery. If @all paused@, the instance pauses automation for
-- the duration set by @--resume-full-automation-mode-minutes@.
dbInstance_automationMode :: Lens.Lens' DBInstance (Prelude.Maybe AutomationMode)
dbInstance_automationMode :: Lens' DBInstance (Maybe AutomationMode)
dbInstance_automationMode = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\DBInstance' {Maybe AutomationMode
automationMode :: Maybe AutomationMode
$sel:automationMode:DBInstance' :: DBInstance -> Maybe AutomationMode
automationMode} -> Maybe AutomationMode
automationMode) (\s :: DBInstance
s@DBInstance' {} Maybe AutomationMode
a -> DBInstance
s {$sel:automationMode:DBInstance' :: Maybe AutomationMode
automationMode = Maybe AutomationMode
a} :: DBInstance)

-- | Specifies the name of the Availability Zone the DB instance is located
-- in.
dbInstance_availabilityZone :: Lens.Lens' DBInstance (Prelude.Maybe Prelude.Text)
dbInstance_availabilityZone :: Lens' DBInstance (Maybe Text)
dbInstance_availabilityZone = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\DBInstance' {Maybe Text
availabilityZone :: Maybe Text
$sel:availabilityZone:DBInstance' :: DBInstance -> Maybe Text
availabilityZone} -> Maybe Text
availabilityZone) (\s :: DBInstance
s@DBInstance' {} Maybe Text
a -> DBInstance
s {$sel:availabilityZone:DBInstance' :: Maybe Text
availabilityZone = Maybe Text
a} :: DBInstance)

-- | The Amazon Resource Name (ARN) of the recovery point in Amazon Web
-- Services Backup.
dbInstance_awsBackupRecoveryPointArn :: Lens.Lens' DBInstance (Prelude.Maybe Prelude.Text)
dbInstance_awsBackupRecoveryPointArn :: Lens' DBInstance (Maybe Text)
dbInstance_awsBackupRecoveryPointArn = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\DBInstance' {Maybe Text
awsBackupRecoveryPointArn :: Maybe Text
$sel:awsBackupRecoveryPointArn:DBInstance' :: DBInstance -> Maybe Text
awsBackupRecoveryPointArn} -> Maybe Text
awsBackupRecoveryPointArn) (\s :: DBInstance
s@DBInstance' {} Maybe Text
a -> DBInstance
s {$sel:awsBackupRecoveryPointArn:DBInstance' :: Maybe Text
awsBackupRecoveryPointArn = Maybe Text
a} :: DBInstance)

-- | Specifies the number of days for which automatic DB snapshots are
-- retained.
dbInstance_backupRetentionPeriod :: Lens.Lens' DBInstance (Prelude.Maybe Prelude.Int)
dbInstance_backupRetentionPeriod :: Lens' DBInstance (Maybe Int)
dbInstance_backupRetentionPeriod = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\DBInstance' {Maybe Int
backupRetentionPeriod :: Maybe Int
$sel:backupRetentionPeriod:DBInstance' :: DBInstance -> Maybe Int
backupRetentionPeriod} -> Maybe Int
backupRetentionPeriod) (\s :: DBInstance
s@DBInstance' {} Maybe Int
a -> DBInstance
s {$sel:backupRetentionPeriod:DBInstance' :: Maybe Int
backupRetentionPeriod = Maybe Int
a} :: DBInstance)

-- | Specifies where automated backups and manual snapshots are stored:
-- Amazon Web Services Outposts or the Amazon Web Services Region.
dbInstance_backupTarget :: Lens.Lens' DBInstance (Prelude.Maybe Prelude.Text)
dbInstance_backupTarget :: Lens' DBInstance (Maybe Text)
dbInstance_backupTarget = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\DBInstance' {Maybe Text
backupTarget :: Maybe Text
$sel:backupTarget:DBInstance' :: DBInstance -> Maybe Text
backupTarget} -> Maybe Text
backupTarget) (\s :: DBInstance
s@DBInstance' {} Maybe Text
a -> DBInstance
s {$sel:backupTarget:DBInstance' :: Maybe Text
backupTarget = Maybe Text
a} :: DBInstance)

-- | The identifier of the CA certificate for this DB instance.
--
-- For more information, see
-- <https://docs.aws.amazon.com/AmazonRDS/latest/UserGuide/UsingWithRDS.SSL.html Using SSL\/TLS to encrypt a connection to a DB instance>
-- in the /Amazon RDS User Guide/ and
-- <https://docs.aws.amazon.com/AmazonRDS/latest/AuroraUserGuide/UsingWithRDS.SSL.html Using SSL\/TLS to encrypt a connection to a DB cluster>
-- in the /Amazon Aurora User Guide/.
dbInstance_cACertificateIdentifier :: Lens.Lens' DBInstance (Prelude.Maybe Prelude.Text)
dbInstance_cACertificateIdentifier :: Lens' DBInstance (Maybe Text)
dbInstance_cACertificateIdentifier = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\DBInstance' {Maybe Text
cACertificateIdentifier :: Maybe Text
$sel:cACertificateIdentifier:DBInstance' :: DBInstance -> Maybe Text
cACertificateIdentifier} -> Maybe Text
cACertificateIdentifier) (\s :: DBInstance
s@DBInstance' {} Maybe Text
a -> DBInstance
s {$sel:cACertificateIdentifier:DBInstance' :: Maybe Text
cACertificateIdentifier = Maybe Text
a} :: DBInstance)

-- | The details of the DB instance\'s server certificate.
dbInstance_certificateDetails :: Lens.Lens' DBInstance (Prelude.Maybe CertificateDetails)
dbInstance_certificateDetails :: Lens' DBInstance (Maybe CertificateDetails)
dbInstance_certificateDetails = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\DBInstance' {Maybe CertificateDetails
certificateDetails :: Maybe CertificateDetails
$sel:certificateDetails:DBInstance' :: DBInstance -> Maybe CertificateDetails
certificateDetails} -> Maybe CertificateDetails
certificateDetails) (\s :: DBInstance
s@DBInstance' {} Maybe CertificateDetails
a -> DBInstance
s {$sel:certificateDetails:DBInstance' :: Maybe CertificateDetails
certificateDetails = Maybe CertificateDetails
a} :: DBInstance)

-- | If present, specifies the name of the character set that this instance
-- is associated with.
dbInstance_characterSetName :: Lens.Lens' DBInstance (Prelude.Maybe Prelude.Text)
dbInstance_characterSetName :: Lens' DBInstance (Maybe Text)
dbInstance_characterSetName = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\DBInstance' {Maybe Text
characterSetName :: Maybe Text
$sel:characterSetName:DBInstance' :: DBInstance -> Maybe Text
characterSetName} -> Maybe Text
characterSetName) (\s :: DBInstance
s@DBInstance' {} Maybe Text
a -> DBInstance
s {$sel:characterSetName:DBInstance' :: Maybe Text
characterSetName = Maybe Text
a} :: DBInstance)

-- | Specifies whether tags are copied from the DB instance to snapshots of
-- the DB instance.
--
-- __Amazon Aurora__
--
-- Not applicable. Copying tags to snapshots is managed by the DB cluster.
-- Setting this value for an Aurora DB instance has no effect on the DB
-- cluster setting. For more information, see @DBCluster@.
dbInstance_copyTagsToSnapshot :: Lens.Lens' DBInstance (Prelude.Maybe Prelude.Bool)
dbInstance_copyTagsToSnapshot :: Lens' DBInstance (Maybe Bool)
dbInstance_copyTagsToSnapshot = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\DBInstance' {Maybe Bool
copyTagsToSnapshot :: Maybe Bool
$sel:copyTagsToSnapshot:DBInstance' :: DBInstance -> Maybe Bool
copyTagsToSnapshot} -> Maybe Bool
copyTagsToSnapshot) (\s :: DBInstance
s@DBInstance' {} Maybe Bool
a -> DBInstance
s {$sel:copyTagsToSnapshot:DBInstance' :: Maybe Bool
copyTagsToSnapshot = Maybe Bool
a} :: DBInstance)

-- | The instance profile associated with the underlying Amazon EC2 instance
-- of an RDS Custom DB instance. The instance profile must meet the
-- following requirements:
--
-- -   The profile must exist in your account.
--
-- -   The profile must have an IAM role that Amazon EC2 has permissions to
--     assume.
--
-- -   The instance profile name and the associated IAM role name must
--     start with the prefix @AWSRDSCustom@.
--
-- For the list of permissions required for the IAM role, see
-- <https://docs.aws.amazon.com/AmazonRDS/latest/UserGuide/custom-setup-orcl.html#custom-setup-orcl.iam-vpc Configure IAM and your VPC>
-- in the /Amazon RDS User Guide/.
dbInstance_customIamInstanceProfile :: Lens.Lens' DBInstance (Prelude.Maybe Prelude.Text)
dbInstance_customIamInstanceProfile :: Lens' DBInstance (Maybe Text)
dbInstance_customIamInstanceProfile = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\DBInstance' {Maybe Text
customIamInstanceProfile :: Maybe Text
$sel:customIamInstanceProfile:DBInstance' :: DBInstance -> Maybe Text
customIamInstanceProfile} -> Maybe Text
customIamInstanceProfile) (\s :: DBInstance
s@DBInstance' {} Maybe Text
a -> DBInstance
s {$sel:customIamInstanceProfile:DBInstance' :: Maybe Text
customIamInstanceProfile = Maybe Text
a} :: DBInstance)

-- | Specifies whether a customer-owned IP address (CoIP) is enabled for an
-- RDS on Outposts DB instance.
--
-- A /CoIP/ provides local or external connectivity to resources in your
-- Outpost subnets through your on-premises network. For some use cases, a
-- CoIP can provide lower latency for connections to the DB instance from
-- outside of its virtual private cloud (VPC) on your local network.
--
-- For more information about RDS on Outposts, see
-- <https://docs.aws.amazon.com/AmazonRDS/latest/UserGuide/rds-on-outposts.html Working with Amazon RDS on Amazon Web Services Outposts>
-- in the /Amazon RDS User Guide/.
--
-- For more information about CoIPs, see
-- <https://docs.aws.amazon.com/outposts/latest/userguide/routing.html#ip-addressing Customer-owned IP addresses>
-- in the /Amazon Web Services Outposts User Guide/.
dbInstance_customerOwnedIpEnabled :: Lens.Lens' DBInstance (Prelude.Maybe Prelude.Bool)
dbInstance_customerOwnedIpEnabled :: Lens' DBInstance (Maybe Bool)
dbInstance_customerOwnedIpEnabled = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\DBInstance' {Maybe Bool
customerOwnedIpEnabled :: Maybe Bool
$sel:customerOwnedIpEnabled:DBInstance' :: DBInstance -> Maybe Bool
customerOwnedIpEnabled} -> Maybe Bool
customerOwnedIpEnabled) (\s :: DBInstance
s@DBInstance' {} Maybe Bool
a -> DBInstance
s {$sel:customerOwnedIpEnabled:DBInstance' :: Maybe Bool
customerOwnedIpEnabled = Maybe Bool
a} :: DBInstance)

-- | If the DB instance is a member of a DB cluster, contains the name of the
-- DB cluster that the DB instance is a member of.
dbInstance_dbClusterIdentifier :: Lens.Lens' DBInstance (Prelude.Maybe Prelude.Text)
dbInstance_dbClusterIdentifier :: Lens' DBInstance (Maybe Text)
dbInstance_dbClusterIdentifier = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\DBInstance' {Maybe Text
dbClusterIdentifier :: Maybe Text
$sel:dbClusterIdentifier:DBInstance' :: DBInstance -> Maybe Text
dbClusterIdentifier} -> Maybe Text
dbClusterIdentifier) (\s :: DBInstance
s@DBInstance' {} Maybe Text
a -> DBInstance
s {$sel:dbClusterIdentifier:DBInstance' :: Maybe Text
dbClusterIdentifier = Maybe Text
a} :: DBInstance)

-- | The Amazon Resource Name (ARN) for the DB instance.
dbInstance_dbInstanceArn :: Lens.Lens' DBInstance (Prelude.Maybe Prelude.Text)
dbInstance_dbInstanceArn :: Lens' DBInstance (Maybe Text)
dbInstance_dbInstanceArn = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\DBInstance' {Maybe Text
dbInstanceArn :: Maybe Text
$sel:dbInstanceArn:DBInstance' :: DBInstance -> Maybe Text
dbInstanceArn} -> Maybe Text
dbInstanceArn) (\s :: DBInstance
s@DBInstance' {} Maybe Text
a -> DBInstance
s {$sel:dbInstanceArn:DBInstance' :: Maybe Text
dbInstanceArn = Maybe Text
a} :: DBInstance)

-- | The list of replicated automated backups associated with the DB
-- instance.
dbInstance_dbInstanceAutomatedBackupsReplications :: Lens.Lens' DBInstance (Prelude.Maybe [DBInstanceAutomatedBackupsReplication])
dbInstance_dbInstanceAutomatedBackupsReplications :: Lens' DBInstance (Maybe [DBInstanceAutomatedBackupsReplication])
dbInstance_dbInstanceAutomatedBackupsReplications = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\DBInstance' {Maybe [DBInstanceAutomatedBackupsReplication]
dbInstanceAutomatedBackupsReplications :: Maybe [DBInstanceAutomatedBackupsReplication]
$sel:dbInstanceAutomatedBackupsReplications:DBInstance' :: DBInstance -> Maybe [DBInstanceAutomatedBackupsReplication]
dbInstanceAutomatedBackupsReplications} -> Maybe [DBInstanceAutomatedBackupsReplication]
dbInstanceAutomatedBackupsReplications) (\s :: DBInstance
s@DBInstance' {} Maybe [DBInstanceAutomatedBackupsReplication]
a -> DBInstance
s {$sel:dbInstanceAutomatedBackupsReplications:DBInstance' :: Maybe [DBInstanceAutomatedBackupsReplication]
dbInstanceAutomatedBackupsReplications = Maybe [DBInstanceAutomatedBackupsReplication]
a} :: DBInstance) 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

-- | Contains the name of the compute and memory capacity class of the DB
-- instance.
dbInstance_dbInstanceClass :: Lens.Lens' DBInstance (Prelude.Maybe Prelude.Text)
dbInstance_dbInstanceClass :: Lens' DBInstance (Maybe Text)
dbInstance_dbInstanceClass = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\DBInstance' {Maybe Text
dbInstanceClass :: Maybe Text
$sel:dbInstanceClass:DBInstance' :: DBInstance -> Maybe Text
dbInstanceClass} -> Maybe Text
dbInstanceClass) (\s :: DBInstance
s@DBInstance' {} Maybe Text
a -> DBInstance
s {$sel:dbInstanceClass:DBInstance' :: Maybe Text
dbInstanceClass = Maybe Text
a} :: DBInstance)

-- | Contains a user-supplied database identifier. This identifier is the
-- unique key that identifies a DB instance.
dbInstance_dbInstanceIdentifier :: Lens.Lens' DBInstance (Prelude.Maybe Prelude.Text)
dbInstance_dbInstanceIdentifier :: Lens' DBInstance (Maybe Text)
dbInstance_dbInstanceIdentifier = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\DBInstance' {Maybe Text
dbInstanceIdentifier :: Maybe Text
$sel:dbInstanceIdentifier:DBInstance' :: DBInstance -> Maybe Text
dbInstanceIdentifier} -> Maybe Text
dbInstanceIdentifier) (\s :: DBInstance
s@DBInstance' {} Maybe Text
a -> DBInstance
s {$sel:dbInstanceIdentifier:DBInstance' :: Maybe Text
dbInstanceIdentifier = Maybe Text
a} :: DBInstance)

-- | Specifies the current state of this database.
--
-- For information about DB instance statuses, see
-- <https://docs.aws.amazon.com/AmazonRDS/latest/UserGuide/accessing-monitoring.html#Overview.DBInstance.Status Viewing DB instance status>
-- in the /Amazon RDS User Guide./
dbInstance_dbInstanceStatus :: Lens.Lens' DBInstance (Prelude.Maybe Prelude.Text)
dbInstance_dbInstanceStatus :: Lens' DBInstance (Maybe Text)
dbInstance_dbInstanceStatus = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\DBInstance' {Maybe Text
dbInstanceStatus :: Maybe Text
$sel:dbInstanceStatus:DBInstance' :: DBInstance -> Maybe Text
dbInstanceStatus} -> Maybe Text
dbInstanceStatus) (\s :: DBInstance
s@DBInstance' {} Maybe Text
a -> DBInstance
s {$sel:dbInstanceStatus:DBInstance' :: Maybe Text
dbInstanceStatus = Maybe Text
a} :: DBInstance)

-- | The meaning of this parameter differs according to the database engine
-- you use.
--
-- __MySQL, MariaDB, SQL Server, PostgreSQL__
--
-- Contains the name of the initial database of this instance that was
-- provided at create time, if one was specified when the DB instance was
-- created. This same name is returned for the life of the DB instance.
--
-- Type: String
--
-- __Oracle__
--
-- Contains the Oracle System ID (SID) of the created DB instance. Not
-- shown when the returned parameters do not apply to an Oracle DB
-- instance.
dbInstance_dbName :: Lens.Lens' DBInstance (Prelude.Maybe Prelude.Text)
dbInstance_dbName :: Lens' DBInstance (Maybe Text)
dbInstance_dbName = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\DBInstance' {Maybe Text
dbName :: Maybe Text
$sel:dbName:DBInstance' :: DBInstance -> Maybe Text
dbName} -> Maybe Text
dbName) (\s :: DBInstance
s@DBInstance' {} Maybe Text
a -> DBInstance
s {$sel:dbName:DBInstance' :: Maybe Text
dbName = Maybe Text
a} :: DBInstance)

-- | Provides the list of DB parameter groups applied to this DB instance.
dbInstance_dbParameterGroups :: Lens.Lens' DBInstance (Prelude.Maybe [DBParameterGroupStatus])
dbInstance_dbParameterGroups :: Lens' DBInstance (Maybe [DBParameterGroupStatus])
dbInstance_dbParameterGroups = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\DBInstance' {Maybe [DBParameterGroupStatus]
dbParameterGroups :: Maybe [DBParameterGroupStatus]
$sel:dbParameterGroups:DBInstance' :: DBInstance -> Maybe [DBParameterGroupStatus]
dbParameterGroups} -> Maybe [DBParameterGroupStatus]
dbParameterGroups) (\s :: DBInstance
s@DBInstance' {} Maybe [DBParameterGroupStatus]
a -> DBInstance
s {$sel:dbParameterGroups:DBInstance' :: Maybe [DBParameterGroupStatus]
dbParameterGroups = Maybe [DBParameterGroupStatus]
a} :: DBInstance) forall b c a. (b -> c) -> (a -> b) -> a -> c
Prelude.. forall (f :: * -> *) (g :: * -> *) s t a b.
(Functor f, Functor g) =>
AnIso s t a b -> Iso (f s) (g t) (f a) (g b)
Lens.mapping forall s t a b. (Coercible s a, Coercible t b) => Iso s t a b
Lens.coerced

-- | A list of DB security group elements containing @DBSecurityGroup.Name@
-- and @DBSecurityGroup.Status@ subelements.
dbInstance_dbSecurityGroups :: Lens.Lens' DBInstance (Prelude.Maybe [DBSecurityGroupMembership])
dbInstance_dbSecurityGroups :: Lens' DBInstance (Maybe [DBSecurityGroupMembership])
dbInstance_dbSecurityGroups = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\DBInstance' {Maybe [DBSecurityGroupMembership]
dbSecurityGroups :: Maybe [DBSecurityGroupMembership]
$sel:dbSecurityGroups:DBInstance' :: DBInstance -> Maybe [DBSecurityGroupMembership]
dbSecurityGroups} -> Maybe [DBSecurityGroupMembership]
dbSecurityGroups) (\s :: DBInstance
s@DBInstance' {} Maybe [DBSecurityGroupMembership]
a -> DBInstance
s {$sel:dbSecurityGroups:DBInstance' :: Maybe [DBSecurityGroupMembership]
dbSecurityGroups = Maybe [DBSecurityGroupMembership]
a} :: DBInstance) 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

-- | Specifies information on the subnet group associated with the DB
-- instance, including the name, description, and subnets in the subnet
-- group.
dbInstance_dbSubnetGroup :: Lens.Lens' DBInstance (Prelude.Maybe DBSubnetGroup)
dbInstance_dbSubnetGroup :: Lens' DBInstance (Maybe DBSubnetGroup)
dbInstance_dbSubnetGroup = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\DBInstance' {Maybe DBSubnetGroup
dbSubnetGroup :: Maybe DBSubnetGroup
$sel:dbSubnetGroup:DBInstance' :: DBInstance -> Maybe DBSubnetGroup
dbSubnetGroup} -> Maybe DBSubnetGroup
dbSubnetGroup) (\s :: DBInstance
s@DBInstance' {} Maybe DBSubnetGroup
a -> DBInstance
s {$sel:dbSubnetGroup:DBInstance' :: Maybe DBSubnetGroup
dbSubnetGroup = Maybe DBSubnetGroup
a} :: DBInstance)

-- | The Oracle system ID (Oracle SID) for a container database (CDB). The
-- Oracle SID is also the name of the CDB. This setting is valid for RDS
-- Custom only.
dbInstance_dbSystemId :: Lens.Lens' DBInstance (Prelude.Maybe Prelude.Text)
dbInstance_dbSystemId :: Lens' DBInstance (Maybe Text)
dbInstance_dbSystemId = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\DBInstance' {Maybe Text
dbSystemId :: Maybe Text
$sel:dbSystemId:DBInstance' :: DBInstance -> Maybe Text
dbSystemId} -> Maybe Text
dbSystemId) (\s :: DBInstance
s@DBInstance' {} Maybe Text
a -> DBInstance
s {$sel:dbSystemId:DBInstance' :: Maybe Text
dbSystemId = Maybe Text
a} :: DBInstance)

-- | Specifies the port that the DB instance listens on. If the DB instance
-- is part of a DB cluster, this can be a different port than the DB
-- cluster port.
dbInstance_dbInstancePort :: Lens.Lens' DBInstance (Prelude.Maybe Prelude.Int)
dbInstance_dbInstancePort :: Lens' DBInstance (Maybe Int)
dbInstance_dbInstancePort = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\DBInstance' {Maybe Int
dbInstancePort :: Maybe Int
$sel:dbInstancePort:DBInstance' :: DBInstance -> Maybe Int
dbInstancePort} -> Maybe Int
dbInstancePort) (\s :: DBInstance
s@DBInstance' {} Maybe Int
a -> DBInstance
s {$sel:dbInstancePort:DBInstance' :: Maybe Int
dbInstancePort = Maybe Int
a} :: DBInstance)

-- | The Amazon Web Services Region-unique, immutable identifier for the DB
-- instance. This identifier is found in Amazon Web Services CloudTrail log
-- entries whenever the Amazon Web Services KMS key for the DB instance is
-- accessed.
dbInstance_dbiResourceId :: Lens.Lens' DBInstance (Prelude.Maybe Prelude.Text)
dbInstance_dbiResourceId :: Lens' DBInstance (Maybe Text)
dbInstance_dbiResourceId = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\DBInstance' {Maybe Text
dbiResourceId :: Maybe Text
$sel:dbiResourceId:DBInstance' :: DBInstance -> Maybe Text
dbiResourceId} -> Maybe Text
dbiResourceId) (\s :: DBInstance
s@DBInstance' {} Maybe Text
a -> DBInstance
s {$sel:dbiResourceId:DBInstance' :: Maybe Text
dbiResourceId = Maybe Text
a} :: DBInstance)

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

-- | The Active Directory Domain membership records associated with the DB
-- instance.
dbInstance_domainMemberships :: Lens.Lens' DBInstance (Prelude.Maybe [DomainMembership])
dbInstance_domainMemberships :: Lens' DBInstance (Maybe [DomainMembership])
dbInstance_domainMemberships = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\DBInstance' {Maybe [DomainMembership]
domainMemberships :: Maybe [DomainMembership]
$sel:domainMemberships:DBInstance' :: DBInstance -> Maybe [DomainMembership]
domainMemberships} -> Maybe [DomainMembership]
domainMemberships) (\s :: DBInstance
s@DBInstance' {} Maybe [DomainMembership]
a -> DBInstance
s {$sel:domainMemberships:DBInstance' :: Maybe [DomainMembership]
domainMemberships = Maybe [DomainMembership]
a} :: DBInstance) forall b c a. (b -> c) -> (a -> b) -> a -> c
Prelude.. forall (f :: * -> *) (g :: * -> *) s t a b.
(Functor f, Functor g) =>
AnIso s t a b -> Iso (f s) (g t) (f a) (g b)
Lens.mapping forall s t a b. (Coercible s a, Coercible t b) => Iso s t a b
Lens.coerced

-- | A list of log types that this DB instance is configured to export to
-- CloudWatch Logs.
--
-- Log types vary by DB engine. For information about the log types for
-- each DB engine, see
-- <https://docs.aws.amazon.com/AmazonRDS/latest/UserGuide/USER_LogAccess.html Amazon RDS Database Log Files>
-- in the /Amazon RDS User Guide./
dbInstance_enabledCloudwatchLogsExports :: Lens.Lens' DBInstance (Prelude.Maybe [Prelude.Text])
dbInstance_enabledCloudwatchLogsExports :: Lens' DBInstance (Maybe [Text])
dbInstance_enabledCloudwatchLogsExports = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\DBInstance' {Maybe [Text]
enabledCloudwatchLogsExports :: Maybe [Text]
$sel:enabledCloudwatchLogsExports:DBInstance' :: DBInstance -> Maybe [Text]
enabledCloudwatchLogsExports} -> Maybe [Text]
enabledCloudwatchLogsExports) (\s :: DBInstance
s@DBInstance' {} Maybe [Text]
a -> DBInstance
s {$sel:enabledCloudwatchLogsExports:DBInstance' :: Maybe [Text]
enabledCloudwatchLogsExports = Maybe [Text]
a} :: DBInstance) 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

-- | Specifies the connection endpoint.
--
-- The endpoint might not be shown for instances whose status is
-- @creating@.
dbInstance_endpoint :: Lens.Lens' DBInstance (Prelude.Maybe Endpoint)
dbInstance_endpoint :: Lens' DBInstance (Maybe Endpoint)
dbInstance_endpoint = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\DBInstance' {Maybe Endpoint
endpoint :: Maybe Endpoint
$sel:endpoint:DBInstance' :: DBInstance -> Maybe Endpoint
endpoint} -> Maybe Endpoint
endpoint) (\s :: DBInstance
s@DBInstance' {} Maybe Endpoint
a -> DBInstance
s {$sel:endpoint:DBInstance' :: Maybe Endpoint
endpoint = Maybe Endpoint
a} :: DBInstance)

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

-- | Indicates the database engine version.
dbInstance_engineVersion :: Lens.Lens' DBInstance (Prelude.Maybe Prelude.Text)
dbInstance_engineVersion :: Lens' DBInstance (Maybe Text)
dbInstance_engineVersion = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\DBInstance' {Maybe Text
engineVersion :: Maybe Text
$sel:engineVersion:DBInstance' :: DBInstance -> Maybe Text
engineVersion} -> Maybe Text
engineVersion) (\s :: DBInstance
s@DBInstance' {} Maybe Text
a -> DBInstance
s {$sel:engineVersion:DBInstance' :: Maybe Text
engineVersion = Maybe Text
a} :: DBInstance)

-- | The Amazon Resource Name (ARN) of the Amazon CloudWatch Logs log stream
-- that receives the Enhanced Monitoring metrics data for the DB instance.
dbInstance_enhancedMonitoringResourceArn :: Lens.Lens' DBInstance (Prelude.Maybe Prelude.Text)
dbInstance_enhancedMonitoringResourceArn :: Lens' DBInstance (Maybe Text)
dbInstance_enhancedMonitoringResourceArn = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\DBInstance' {Maybe Text
enhancedMonitoringResourceArn :: Maybe Text
$sel:enhancedMonitoringResourceArn:DBInstance' :: DBInstance -> Maybe Text
enhancedMonitoringResourceArn} -> Maybe Text
enhancedMonitoringResourceArn) (\s :: DBInstance
s@DBInstance' {} Maybe Text
a -> DBInstance
s {$sel:enhancedMonitoringResourceArn:DBInstance' :: Maybe Text
enhancedMonitoringResourceArn = Maybe Text
a} :: DBInstance)

-- | True if mapping of Amazon Web Services Identity and Access Management
-- (IAM) accounts to database accounts is enabled, and otherwise false.
--
-- IAM database authentication can be enabled for the following database
-- engines
--
-- -   For MySQL 5.6, minor version 5.6.34 or higher
--
-- -   For MySQL 5.7, minor version 5.7.16 or higher
--
-- -   Aurora 5.6 or higher. To enable IAM database authentication for
--     Aurora, see DBCluster Type.
dbInstance_iAMDatabaseAuthenticationEnabled :: Lens.Lens' DBInstance (Prelude.Maybe Prelude.Bool)
dbInstance_iAMDatabaseAuthenticationEnabled :: Lens' DBInstance (Maybe Bool)
dbInstance_iAMDatabaseAuthenticationEnabled = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\DBInstance' {Maybe Bool
iAMDatabaseAuthenticationEnabled :: Maybe Bool
$sel:iAMDatabaseAuthenticationEnabled:DBInstance' :: DBInstance -> Maybe Bool
iAMDatabaseAuthenticationEnabled} -> Maybe Bool
iAMDatabaseAuthenticationEnabled) (\s :: DBInstance
s@DBInstance' {} Maybe Bool
a -> DBInstance
s {$sel:iAMDatabaseAuthenticationEnabled:DBInstance' :: Maybe Bool
iAMDatabaseAuthenticationEnabled = Maybe Bool
a} :: DBInstance)

-- | Provides the date and time the DB instance was created.
dbInstance_instanceCreateTime :: Lens.Lens' DBInstance (Prelude.Maybe Prelude.UTCTime)
dbInstance_instanceCreateTime :: Lens' DBInstance (Maybe UTCTime)
dbInstance_instanceCreateTime = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\DBInstance' {Maybe ISO8601
instanceCreateTime :: Maybe ISO8601
$sel:instanceCreateTime:DBInstance' :: DBInstance -> Maybe ISO8601
instanceCreateTime} -> Maybe ISO8601
instanceCreateTime) (\s :: DBInstance
s@DBInstance' {} Maybe ISO8601
a -> DBInstance
s {$sel:instanceCreateTime:DBInstance' :: Maybe ISO8601
instanceCreateTime = Maybe ISO8601
a} :: DBInstance) 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 (a :: Format). Iso' (Time a) UTCTime
Data._Time

-- | Specifies the Provisioned IOPS (I\/O operations per second) value.
dbInstance_iops :: Lens.Lens' DBInstance (Prelude.Maybe Prelude.Int)
dbInstance_iops :: Lens' DBInstance (Maybe Int)
dbInstance_iops = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\DBInstance' {Maybe Int
iops :: Maybe Int
$sel:iops:DBInstance' :: DBInstance -> Maybe Int
iops} -> Maybe Int
iops) (\s :: DBInstance
s@DBInstance' {} Maybe Int
a -> DBInstance
s {$sel:iops:DBInstance' :: Maybe Int
iops = Maybe Int
a} :: DBInstance)

-- | If @StorageEncrypted@ is true, the Amazon Web Services KMS key
-- identifier for the 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.
dbInstance_kmsKeyId :: Lens.Lens' DBInstance (Prelude.Maybe Prelude.Text)
dbInstance_kmsKeyId :: Lens' DBInstance (Maybe Text)
dbInstance_kmsKeyId = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\DBInstance' {Maybe Text
kmsKeyId :: Maybe Text
$sel:kmsKeyId:DBInstance' :: DBInstance -> Maybe Text
kmsKeyId} -> Maybe Text
kmsKeyId) (\s :: DBInstance
s@DBInstance' {} Maybe Text
a -> DBInstance
s {$sel:kmsKeyId:DBInstance' :: Maybe Text
kmsKeyId = Maybe Text
a} :: DBInstance)

-- | Specifies the latest time to which a database can be restored with
-- point-in-time restore.
dbInstance_latestRestorableTime :: Lens.Lens' DBInstance (Prelude.Maybe Prelude.UTCTime)
dbInstance_latestRestorableTime :: Lens' DBInstance (Maybe UTCTime)
dbInstance_latestRestorableTime = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\DBInstance' {Maybe ISO8601
latestRestorableTime :: Maybe ISO8601
$sel:latestRestorableTime:DBInstance' :: DBInstance -> Maybe ISO8601
latestRestorableTime} -> Maybe ISO8601
latestRestorableTime) (\s :: DBInstance
s@DBInstance' {} Maybe ISO8601
a -> DBInstance
s {$sel:latestRestorableTime:DBInstance' :: Maybe ISO8601
latestRestorableTime = Maybe ISO8601
a} :: DBInstance) 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 (a :: Format). Iso' (Time a) UTCTime
Data._Time

-- | License model information for this DB instance. This setting doesn\'t
-- apply to RDS Custom.
dbInstance_licenseModel :: Lens.Lens' DBInstance (Prelude.Maybe Prelude.Text)
dbInstance_licenseModel :: Lens' DBInstance (Maybe Text)
dbInstance_licenseModel = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\DBInstance' {Maybe Text
licenseModel :: Maybe Text
$sel:licenseModel:DBInstance' :: DBInstance -> Maybe Text
licenseModel} -> Maybe Text
licenseModel) (\s :: DBInstance
s@DBInstance' {} Maybe Text
a -> DBInstance
s {$sel:licenseModel:DBInstance' :: Maybe Text
licenseModel = Maybe Text
a} :: DBInstance)

-- | Specifies the listener connection endpoint for SQL Server Always On.
dbInstance_listenerEndpoint :: Lens.Lens' DBInstance (Prelude.Maybe Endpoint)
dbInstance_listenerEndpoint :: Lens' DBInstance (Maybe Endpoint)
dbInstance_listenerEndpoint = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\DBInstance' {Maybe Endpoint
listenerEndpoint :: Maybe Endpoint
$sel:listenerEndpoint:DBInstance' :: DBInstance -> Maybe Endpoint
listenerEndpoint} -> Maybe Endpoint
listenerEndpoint) (\s :: DBInstance
s@DBInstance' {} Maybe Endpoint
a -> DBInstance
s {$sel:listenerEndpoint:DBInstance' :: Maybe Endpoint
listenerEndpoint = Maybe Endpoint
a} :: DBInstance)

-- | Contains the secret managed by RDS in Amazon Web Services Secrets
-- Manager for the master user password.
--
-- 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./
dbInstance_masterUserSecret :: Lens.Lens' DBInstance (Prelude.Maybe MasterUserSecret)
dbInstance_masterUserSecret :: Lens' DBInstance (Maybe MasterUserSecret)
dbInstance_masterUserSecret = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\DBInstance' {Maybe MasterUserSecret
masterUserSecret :: Maybe MasterUserSecret
$sel:masterUserSecret:DBInstance' :: DBInstance -> Maybe MasterUserSecret
masterUserSecret} -> Maybe MasterUserSecret
masterUserSecret) (\s :: DBInstance
s@DBInstance' {} Maybe MasterUserSecret
a -> DBInstance
s {$sel:masterUserSecret:DBInstance' :: Maybe MasterUserSecret
masterUserSecret = Maybe MasterUserSecret
a} :: DBInstance)

-- | Contains the master username for the DB instance.
dbInstance_masterUsername :: Lens.Lens' DBInstance (Prelude.Maybe Prelude.Text)
dbInstance_masterUsername :: Lens' DBInstance (Maybe Text)
dbInstance_masterUsername = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\DBInstance' {Maybe Text
masterUsername :: Maybe Text
$sel:masterUsername:DBInstance' :: DBInstance -> Maybe Text
masterUsername} -> Maybe Text
masterUsername) (\s :: DBInstance
s@DBInstance' {} Maybe Text
a -> DBInstance
s {$sel:masterUsername:DBInstance' :: Maybe Text
masterUsername = Maybe Text
a} :: DBInstance)

-- | The upper limit in gibibytes (GiB) to which Amazon RDS can automatically
-- scale the storage of the DB instance.
dbInstance_maxAllocatedStorage :: Lens.Lens' DBInstance (Prelude.Maybe Prelude.Int)
dbInstance_maxAllocatedStorage :: Lens' DBInstance (Maybe Int)
dbInstance_maxAllocatedStorage = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\DBInstance' {Maybe Int
maxAllocatedStorage :: Maybe Int
$sel:maxAllocatedStorage:DBInstance' :: DBInstance -> Maybe Int
maxAllocatedStorage} -> Maybe Int
maxAllocatedStorage) (\s :: DBInstance
s@DBInstance' {} Maybe Int
a -> DBInstance
s {$sel:maxAllocatedStorage:DBInstance' :: Maybe Int
maxAllocatedStorage = Maybe Int
a} :: DBInstance)

-- | The interval, in seconds, between points when Enhanced Monitoring
-- metrics are collected for the DB instance.
dbInstance_monitoringInterval :: Lens.Lens' DBInstance (Prelude.Maybe Prelude.Int)
dbInstance_monitoringInterval :: Lens' DBInstance (Maybe Int)
dbInstance_monitoringInterval = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\DBInstance' {Maybe Int
monitoringInterval :: Maybe Int
$sel:monitoringInterval:DBInstance' :: DBInstance -> Maybe Int
monitoringInterval} -> Maybe Int
monitoringInterval) (\s :: DBInstance
s@DBInstance' {} Maybe Int
a -> DBInstance
s {$sel:monitoringInterval:DBInstance' :: Maybe Int
monitoringInterval = Maybe Int
a} :: DBInstance)

-- | The ARN for the IAM role that permits RDS to send Enhanced Monitoring
-- metrics to Amazon CloudWatch Logs.
dbInstance_monitoringRoleArn :: Lens.Lens' DBInstance (Prelude.Maybe Prelude.Text)
dbInstance_monitoringRoleArn :: Lens' DBInstance (Maybe Text)
dbInstance_monitoringRoleArn = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\DBInstance' {Maybe Text
monitoringRoleArn :: Maybe Text
$sel:monitoringRoleArn:DBInstance' :: DBInstance -> Maybe Text
monitoringRoleArn} -> Maybe Text
monitoringRoleArn) (\s :: DBInstance
s@DBInstance' {} Maybe Text
a -> DBInstance
s {$sel:monitoringRoleArn:DBInstance' :: Maybe Text
monitoringRoleArn = Maybe Text
a} :: DBInstance)

-- | Specifies if the DB instance is a Multi-AZ deployment. This setting
-- doesn\'t apply to RDS Custom.
dbInstance_multiAZ :: Lens.Lens' DBInstance (Prelude.Maybe Prelude.Bool)
dbInstance_multiAZ :: Lens' DBInstance (Maybe Bool)
dbInstance_multiAZ = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\DBInstance' {Maybe Bool
multiAZ :: Maybe Bool
$sel:multiAZ:DBInstance' :: DBInstance -> Maybe Bool
multiAZ} -> Maybe Bool
multiAZ) (\s :: DBInstance
s@DBInstance' {} Maybe Bool
a -> DBInstance
s {$sel:multiAZ:DBInstance' :: Maybe Bool
multiAZ = Maybe Bool
a} :: DBInstance)

-- | The name of the NCHAR character set for the Oracle DB instance. This
-- character set specifies the Unicode encoding for data stored in table
-- columns of type NCHAR, NCLOB, or NVARCHAR2.
dbInstance_ncharCharacterSetName :: Lens.Lens' DBInstance (Prelude.Maybe Prelude.Text)
dbInstance_ncharCharacterSetName :: Lens' DBInstance (Maybe Text)
dbInstance_ncharCharacterSetName = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\DBInstance' {Maybe Text
ncharCharacterSetName :: Maybe Text
$sel:ncharCharacterSetName:DBInstance' :: DBInstance -> Maybe Text
ncharCharacterSetName} -> Maybe Text
ncharCharacterSetName) (\s :: DBInstance
s@DBInstance' {} Maybe Text
a -> DBInstance
s {$sel:ncharCharacterSetName:DBInstance' :: Maybe Text
ncharCharacterSetName = Maybe Text
a} :: DBInstance)

-- | 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/ and
-- <https://docs.aws.amazon.com/AmazonRDS/latest/AuroraUserGuide/USER_VPC.WorkingWithRDSInstanceinaVPC.html Working with a DB instance in a VPC>
-- in the /Amazon Aurora User Guide./
dbInstance_networkType :: Lens.Lens' DBInstance (Prelude.Maybe Prelude.Text)
dbInstance_networkType :: Lens' DBInstance (Maybe Text)
dbInstance_networkType = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\DBInstance' {Maybe Text
networkType :: Maybe Text
$sel:networkType:DBInstance' :: DBInstance -> Maybe Text
networkType} -> Maybe Text
networkType) (\s :: DBInstance
s@DBInstance' {} Maybe Text
a -> DBInstance
s {$sel:networkType:DBInstance' :: Maybe Text
networkType = Maybe Text
a} :: DBInstance)

-- | Provides the list of option group memberships for this DB instance.
dbInstance_optionGroupMemberships :: Lens.Lens' DBInstance (Prelude.Maybe [OptionGroupMembership])
dbInstance_optionGroupMemberships :: Lens' DBInstance (Maybe [OptionGroupMembership])
dbInstance_optionGroupMemberships = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\DBInstance' {Maybe [OptionGroupMembership]
optionGroupMemberships :: Maybe [OptionGroupMembership]
$sel:optionGroupMemberships:DBInstance' :: DBInstance -> Maybe [OptionGroupMembership]
optionGroupMemberships} -> Maybe [OptionGroupMembership]
optionGroupMemberships) (\s :: DBInstance
s@DBInstance' {} Maybe [OptionGroupMembership]
a -> DBInstance
s {$sel:optionGroupMemberships:DBInstance' :: Maybe [OptionGroupMembership]
optionGroupMemberships = Maybe [OptionGroupMembership]
a} :: DBInstance) 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 specifies that changes to the DB instance are pending. This
-- element is only included when changes are pending. Specific changes are
-- identified by subelements.
dbInstance_pendingModifiedValues :: Lens.Lens' DBInstance (Prelude.Maybe PendingModifiedValues)
dbInstance_pendingModifiedValues :: Lens' DBInstance (Maybe PendingModifiedValues)
dbInstance_pendingModifiedValues = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\DBInstance' {Maybe PendingModifiedValues
pendingModifiedValues :: Maybe PendingModifiedValues
$sel:pendingModifiedValues:DBInstance' :: DBInstance -> Maybe PendingModifiedValues
pendingModifiedValues} -> Maybe PendingModifiedValues
pendingModifiedValues) (\s :: DBInstance
s@DBInstance' {} Maybe PendingModifiedValues
a -> DBInstance
s {$sel:pendingModifiedValues:DBInstance' :: Maybe PendingModifiedValues
pendingModifiedValues = Maybe PendingModifiedValues
a} :: DBInstance)

-- | True if Performance Insights is enabled for the DB instance, and
-- otherwise false.
dbInstance_performanceInsightsEnabled :: Lens.Lens' DBInstance (Prelude.Maybe Prelude.Bool)
dbInstance_performanceInsightsEnabled :: Lens' DBInstance (Maybe Bool)
dbInstance_performanceInsightsEnabled = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\DBInstance' {Maybe Bool
performanceInsightsEnabled :: Maybe Bool
$sel:performanceInsightsEnabled:DBInstance' :: DBInstance -> Maybe Bool
performanceInsightsEnabled} -> Maybe Bool
performanceInsightsEnabled) (\s :: DBInstance
s@DBInstance' {} Maybe Bool
a -> DBInstance
s {$sel:performanceInsightsEnabled:DBInstance' :: Maybe Bool
performanceInsightsEnabled = Maybe Bool
a} :: DBInstance)

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

-- | 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
dbInstance_performanceInsightsRetentionPeriod :: Lens.Lens' DBInstance (Prelude.Maybe Prelude.Int)
dbInstance_performanceInsightsRetentionPeriod :: Lens' DBInstance (Maybe Int)
dbInstance_performanceInsightsRetentionPeriod = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\DBInstance' {Maybe Int
performanceInsightsRetentionPeriod :: Maybe Int
$sel:performanceInsightsRetentionPeriod:DBInstance' :: DBInstance -> Maybe Int
performanceInsightsRetentionPeriod} -> Maybe Int
performanceInsightsRetentionPeriod) (\s :: DBInstance
s@DBInstance' {} Maybe Int
a -> DBInstance
s {$sel:performanceInsightsRetentionPeriod:DBInstance' :: Maybe Int
performanceInsightsRetentionPeriod = Maybe Int
a} :: DBInstance)

-- | Specifies the daily time range during which automated backups are
-- created if automated backups are enabled, as determined by the
-- @BackupRetentionPeriod@.
dbInstance_preferredBackupWindow :: Lens.Lens' DBInstance (Prelude.Maybe Prelude.Text)
dbInstance_preferredBackupWindow :: Lens' DBInstance (Maybe Text)
dbInstance_preferredBackupWindow = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\DBInstance' {Maybe Text
preferredBackupWindow :: Maybe Text
$sel:preferredBackupWindow:DBInstance' :: DBInstance -> Maybe Text
preferredBackupWindow} -> Maybe Text
preferredBackupWindow) (\s :: DBInstance
s@DBInstance' {} Maybe Text
a -> DBInstance
s {$sel:preferredBackupWindow:DBInstance' :: Maybe Text
preferredBackupWindow = Maybe Text
a} :: DBInstance)

-- | Specifies the weekly time range during which system maintenance can
-- occur, in Universal Coordinated Time (UTC).
dbInstance_preferredMaintenanceWindow :: Lens.Lens' DBInstance (Prelude.Maybe Prelude.Text)
dbInstance_preferredMaintenanceWindow :: Lens' DBInstance (Maybe Text)
dbInstance_preferredMaintenanceWindow = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\DBInstance' {Maybe Text
preferredMaintenanceWindow :: Maybe Text
$sel:preferredMaintenanceWindow:DBInstance' :: DBInstance -> Maybe Text
preferredMaintenanceWindow} -> Maybe Text
preferredMaintenanceWindow) (\s :: DBInstance
s@DBInstance' {} Maybe Text
a -> DBInstance
s {$sel:preferredMaintenanceWindow:DBInstance' :: Maybe Text
preferredMaintenanceWindow = Maybe Text
a} :: DBInstance)

-- | The number of CPU cores and the number of threads per core for the DB
-- instance class of the DB instance.
dbInstance_processorFeatures :: Lens.Lens' DBInstance (Prelude.Maybe [ProcessorFeature])
dbInstance_processorFeatures :: Lens' DBInstance (Maybe [ProcessorFeature])
dbInstance_processorFeatures = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\DBInstance' {Maybe [ProcessorFeature]
processorFeatures :: Maybe [ProcessorFeature]
$sel:processorFeatures:DBInstance' :: DBInstance -> Maybe [ProcessorFeature]
processorFeatures} -> Maybe [ProcessorFeature]
processorFeatures) (\s :: DBInstance
s@DBInstance' {} Maybe [ProcessorFeature]
a -> DBInstance
s {$sel:processorFeatures:DBInstance' :: Maybe [ProcessorFeature]
processorFeatures = Maybe [ProcessorFeature]
a} :: DBInstance) 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 specifies the order in which an Aurora Replica is promoted
-- to the primary instance after a failure of the existing primary
-- instance. For more information, see
-- <https://docs.aws.amazon.com/AmazonRDS/latest/AuroraUserGuide/Aurora.Managing.Backups.html#Aurora.Managing.FaultTolerance Fault Tolerance for an Aurora DB Cluster>
-- in the /Amazon Aurora User Guide/.
dbInstance_promotionTier :: Lens.Lens' DBInstance (Prelude.Maybe Prelude.Int)
dbInstance_promotionTier :: Lens' DBInstance (Maybe Int)
dbInstance_promotionTier = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\DBInstance' {Maybe Int
promotionTier :: Maybe Int
$sel:promotionTier:DBInstance' :: DBInstance -> Maybe Int
promotionTier} -> Maybe Int
promotionTier) (\s :: DBInstance
s@DBInstance' {} Maybe Int
a -> DBInstance
s {$sel:promotionTier:DBInstance' :: Maybe Int
promotionTier = Maybe Int
a} :: DBInstance)

-- | Specifies the accessibility options for the DB instance.
--
-- When the DB cluster is publicly accessible, its Domain Name System (DNS)
-- endpoint resolves to the private IP address from within the DB
-- cluster\'s virtual private cloud (VPC). It resolves to the public IP
-- address from outside of the DB cluster\'s VPC. Access to the DB cluster
-- is ultimately controlled by the security group it uses. That public
-- access isn\'t permitted if the security group assigned to the DB cluster
-- 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.
dbInstance_publiclyAccessible :: Lens.Lens' DBInstance (Prelude.Maybe Prelude.Bool)
dbInstance_publiclyAccessible :: Lens' DBInstance (Maybe Bool)
dbInstance_publiclyAccessible = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\DBInstance' {Maybe Bool
publiclyAccessible :: Maybe Bool
$sel:publiclyAccessible:DBInstance' :: DBInstance -> Maybe Bool
publiclyAccessible} -> Maybe Bool
publiclyAccessible) (\s :: DBInstance
s@DBInstance' {} Maybe Bool
a -> DBInstance
s {$sel:publiclyAccessible:DBInstance' :: Maybe Bool
publiclyAccessible = Maybe Bool
a} :: DBInstance)

-- | Contains one or more identifiers of Aurora DB clusters to which the RDS
-- DB instance is replicated as a read replica. For example, when you
-- create an Aurora read replica of an RDS for MySQL DB instance, the
-- Aurora MySQL DB cluster for the Aurora read replica is shown. This
-- output doesn\'t contain information about cross-Region Aurora read
-- replicas.
--
-- Currently, each RDS DB instance can have only one Aurora read replica.
dbInstance_readReplicaDBClusterIdentifiers :: Lens.Lens' DBInstance (Prelude.Maybe [Prelude.Text])
dbInstance_readReplicaDBClusterIdentifiers :: Lens' DBInstance (Maybe [Text])
dbInstance_readReplicaDBClusterIdentifiers = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\DBInstance' {Maybe [Text]
readReplicaDBClusterIdentifiers :: Maybe [Text]
$sel:readReplicaDBClusterIdentifiers:DBInstance' :: DBInstance -> Maybe [Text]
readReplicaDBClusterIdentifiers} -> Maybe [Text]
readReplicaDBClusterIdentifiers) (\s :: DBInstance
s@DBInstance' {} Maybe [Text]
a -> DBInstance
s {$sel:readReplicaDBClusterIdentifiers:DBInstance' :: Maybe [Text]
readReplicaDBClusterIdentifiers = Maybe [Text]
a} :: DBInstance) 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

-- | Contains one or more identifiers of the read replicas associated with
-- this DB instance.
dbInstance_readReplicaDBInstanceIdentifiers :: Lens.Lens' DBInstance (Prelude.Maybe [Prelude.Text])
dbInstance_readReplicaDBInstanceIdentifiers :: Lens' DBInstance (Maybe [Text])
dbInstance_readReplicaDBInstanceIdentifiers = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\DBInstance' {Maybe [Text]
readReplicaDBInstanceIdentifiers :: Maybe [Text]
$sel:readReplicaDBInstanceIdentifiers:DBInstance' :: DBInstance -> Maybe [Text]
readReplicaDBInstanceIdentifiers} -> Maybe [Text]
readReplicaDBInstanceIdentifiers) (\s :: DBInstance
s@DBInstance' {} Maybe [Text]
a -> DBInstance
s {$sel:readReplicaDBInstanceIdentifiers:DBInstance' :: Maybe [Text]
readReplicaDBInstanceIdentifiers = Maybe [Text]
a} :: DBInstance) 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

-- | Contains the identifier of the source DB instance if this DB instance is
-- a read replica.
dbInstance_readReplicaSourceDBInstanceIdentifier :: Lens.Lens' DBInstance (Prelude.Maybe Prelude.Text)
dbInstance_readReplicaSourceDBInstanceIdentifier :: Lens' DBInstance (Maybe Text)
dbInstance_readReplicaSourceDBInstanceIdentifier = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\DBInstance' {Maybe Text
readReplicaSourceDBInstanceIdentifier :: Maybe Text
$sel:readReplicaSourceDBInstanceIdentifier:DBInstance' :: DBInstance -> Maybe Text
readReplicaSourceDBInstanceIdentifier} -> Maybe Text
readReplicaSourceDBInstanceIdentifier) (\s :: DBInstance
s@DBInstance' {} Maybe Text
a -> DBInstance
s {$sel:readReplicaSourceDBInstanceIdentifier:DBInstance' :: Maybe Text
readReplicaSourceDBInstanceIdentifier = Maybe Text
a} :: DBInstance)

-- | The open mode of an Oracle read replica. The default is
-- @open-read-only@. For more information, see
-- <https://docs.aws.amazon.com/AmazonRDS/latest/UserGuide/oracle-read-replicas.html Working with Oracle Read Replicas for Amazon RDS>
-- in the /Amazon RDS User Guide/.
--
-- This attribute is only supported in RDS for Oracle.
dbInstance_replicaMode :: Lens.Lens' DBInstance (Prelude.Maybe ReplicaMode)
dbInstance_replicaMode :: Lens' DBInstance (Maybe ReplicaMode)
dbInstance_replicaMode = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\DBInstance' {Maybe ReplicaMode
replicaMode :: Maybe ReplicaMode
$sel:replicaMode:DBInstance' :: DBInstance -> Maybe ReplicaMode
replicaMode} -> Maybe ReplicaMode
replicaMode) (\s :: DBInstance
s@DBInstance' {} Maybe ReplicaMode
a -> DBInstance
s {$sel:replicaMode:DBInstance' :: Maybe ReplicaMode
replicaMode = Maybe ReplicaMode
a} :: DBInstance)

-- | The number of minutes to pause the automation. When the time period
-- ends, RDS Custom resumes full automation. The minimum value is 60
-- (default). The maximum value is 1,440.
dbInstance_resumeFullAutomationModeTime :: Lens.Lens' DBInstance (Prelude.Maybe Prelude.UTCTime)
dbInstance_resumeFullAutomationModeTime :: Lens' DBInstance (Maybe UTCTime)
dbInstance_resumeFullAutomationModeTime = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\DBInstance' {Maybe ISO8601
resumeFullAutomationModeTime :: Maybe ISO8601
$sel:resumeFullAutomationModeTime:DBInstance' :: DBInstance -> Maybe ISO8601
resumeFullAutomationModeTime} -> Maybe ISO8601
resumeFullAutomationModeTime) (\s :: DBInstance
s@DBInstance' {} Maybe ISO8601
a -> DBInstance
s {$sel:resumeFullAutomationModeTime:DBInstance' :: Maybe ISO8601
resumeFullAutomationModeTime = Maybe ISO8601
a} :: DBInstance) 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 (a :: Format). Iso' (Time a) UTCTime
Data._Time

-- | If present, specifies the name of the secondary Availability Zone for a
-- DB instance with multi-AZ support.
dbInstance_secondaryAvailabilityZone :: Lens.Lens' DBInstance (Prelude.Maybe Prelude.Text)
dbInstance_secondaryAvailabilityZone :: Lens' DBInstance (Maybe Text)
dbInstance_secondaryAvailabilityZone = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\DBInstance' {Maybe Text
secondaryAvailabilityZone :: Maybe Text
$sel:secondaryAvailabilityZone:DBInstance' :: DBInstance -> Maybe Text
secondaryAvailabilityZone} -> Maybe Text
secondaryAvailabilityZone) (\s :: DBInstance
s@DBInstance' {} Maybe Text
a -> DBInstance
s {$sel:secondaryAvailabilityZone:DBInstance' :: Maybe Text
secondaryAvailabilityZone = Maybe Text
a} :: DBInstance)

-- | The status of a read replica. If the instance isn\'t a read replica,
-- this is blank.
dbInstance_statusInfos :: Lens.Lens' DBInstance (Prelude.Maybe [DBInstanceStatusInfo])
dbInstance_statusInfos :: Lens' DBInstance (Maybe [DBInstanceStatusInfo])
dbInstance_statusInfos = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\DBInstance' {Maybe [DBInstanceStatusInfo]
statusInfos :: Maybe [DBInstanceStatusInfo]
$sel:statusInfos:DBInstance' :: DBInstance -> Maybe [DBInstanceStatusInfo]
statusInfos} -> Maybe [DBInstanceStatusInfo]
statusInfos) (\s :: DBInstance
s@DBInstance' {} Maybe [DBInstanceStatusInfo]
a -> DBInstance
s {$sel:statusInfos:DBInstance' :: Maybe [DBInstanceStatusInfo]
statusInfos = Maybe [DBInstanceStatusInfo]
a} :: DBInstance) 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

-- | Specifies whether the DB instance is encrypted.
dbInstance_storageEncrypted :: Lens.Lens' DBInstance (Prelude.Maybe Prelude.Bool)
dbInstance_storageEncrypted :: Lens' DBInstance (Maybe Bool)
dbInstance_storageEncrypted = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\DBInstance' {Maybe Bool
storageEncrypted :: Maybe Bool
$sel:storageEncrypted:DBInstance' :: DBInstance -> Maybe Bool
storageEncrypted} -> Maybe Bool
storageEncrypted) (\s :: DBInstance
s@DBInstance' {} Maybe Bool
a -> DBInstance
s {$sel:storageEncrypted:DBInstance' :: Maybe Bool
storageEncrypted = Maybe Bool
a} :: DBInstance)

-- | Specifies the storage throughput for the DB instance.
--
-- This setting applies only to the @gp3@ storage type.
dbInstance_storageThroughput :: Lens.Lens' DBInstance (Prelude.Maybe Prelude.Int)
dbInstance_storageThroughput :: Lens' DBInstance (Maybe Int)
dbInstance_storageThroughput = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\DBInstance' {Maybe Int
storageThroughput :: Maybe Int
$sel:storageThroughput:DBInstance' :: DBInstance -> Maybe Int
storageThroughput} -> Maybe Int
storageThroughput) (\s :: DBInstance
s@DBInstance' {} Maybe Int
a -> DBInstance
s {$sel:storageThroughput:DBInstance' :: Maybe Int
storageThroughput = Maybe Int
a} :: DBInstance)

-- | Specifies the storage type associated with the DB instance.
dbInstance_storageType :: Lens.Lens' DBInstance (Prelude.Maybe Prelude.Text)
dbInstance_storageType :: Lens' DBInstance (Maybe Text)
dbInstance_storageType = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\DBInstance' {Maybe Text
storageType :: Maybe Text
$sel:storageType:DBInstance' :: DBInstance -> Maybe Text
storageType} -> Maybe Text
storageType) (\s :: DBInstance
s@DBInstance' {} Maybe Text
a -> DBInstance
s {$sel:storageType:DBInstance' :: Maybe Text
storageType = Maybe Text
a} :: DBInstance)

-- | Undocumented member.
dbInstance_tagList :: Lens.Lens' DBInstance (Prelude.Maybe [Tag])
dbInstance_tagList :: Lens' DBInstance (Maybe [Tag])
dbInstance_tagList = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\DBInstance' {Maybe [Tag]
tagList :: Maybe [Tag]
$sel:tagList:DBInstance' :: DBInstance -> Maybe [Tag]
tagList} -> Maybe [Tag]
tagList) (\s :: DBInstance
s@DBInstance' {} Maybe [Tag]
a -> DBInstance
s {$sel:tagList:DBInstance' :: Maybe [Tag]
tagList = Maybe [Tag]
a} :: DBInstance) 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 ARN from the key store with which the instance is associated for TDE
-- encryption.
dbInstance_tdeCredentialArn :: Lens.Lens' DBInstance (Prelude.Maybe Prelude.Text)
dbInstance_tdeCredentialArn :: Lens' DBInstance (Maybe Text)
dbInstance_tdeCredentialArn = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\DBInstance' {Maybe Text
tdeCredentialArn :: Maybe Text
$sel:tdeCredentialArn:DBInstance' :: DBInstance -> Maybe Text
tdeCredentialArn} -> Maybe Text
tdeCredentialArn) (\s :: DBInstance
s@DBInstance' {} Maybe Text
a -> DBInstance
s {$sel:tdeCredentialArn:DBInstance' :: Maybe Text
tdeCredentialArn = Maybe Text
a} :: DBInstance)

-- | The time zone of the DB instance. In most cases, the @Timezone@ element
-- is empty. @Timezone@ content appears only for Microsoft SQL Server DB
-- instances that were created with a time zone specified.
dbInstance_timezone :: Lens.Lens' DBInstance (Prelude.Maybe Prelude.Text)
dbInstance_timezone :: Lens' DBInstance (Maybe Text)
dbInstance_timezone = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\DBInstance' {Maybe Text
timezone :: Maybe Text
$sel:timezone:DBInstance' :: DBInstance -> Maybe Text
timezone} -> Maybe Text
timezone) (\s :: DBInstance
s@DBInstance' {} Maybe Text
a -> DBInstance
s {$sel:timezone:DBInstance' :: Maybe Text
timezone = Maybe Text
a} :: DBInstance)

-- | Provides a list of VPC security group elements that the DB instance
-- belongs to.
dbInstance_vpcSecurityGroups :: Lens.Lens' DBInstance (Prelude.Maybe [VpcSecurityGroupMembership])
dbInstance_vpcSecurityGroups :: Lens' DBInstance (Maybe [VpcSecurityGroupMembership])
dbInstance_vpcSecurityGroups = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\DBInstance' {Maybe [VpcSecurityGroupMembership]
vpcSecurityGroups :: Maybe [VpcSecurityGroupMembership]
$sel:vpcSecurityGroups:DBInstance' :: DBInstance -> Maybe [VpcSecurityGroupMembership]
vpcSecurityGroups} -> Maybe [VpcSecurityGroupMembership]
vpcSecurityGroups) (\s :: DBInstance
s@DBInstance' {} Maybe [VpcSecurityGroupMembership]
a -> DBInstance
s {$sel:vpcSecurityGroups:DBInstance' :: Maybe [VpcSecurityGroupMembership]
vpcSecurityGroups = Maybe [VpcSecurityGroupMembership]
a} :: DBInstance) 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

instance Data.FromXML DBInstance where
  parseXML :: [Node] -> Either String DBInstance
parseXML [Node]
x =
    Maybe Bool
-> Maybe Text
-> Maybe Text
-> Maybe ActivityStreamMode
-> Maybe ActivityStreamPolicyStatus
-> Maybe ActivityStreamStatus
-> Maybe Int
-> Maybe [DBInstanceRole]
-> Maybe Bool
-> Maybe ISO8601
-> Maybe AutomationMode
-> Maybe Text
-> Maybe Text
-> Maybe Int
-> Maybe Text
-> Maybe Text
-> Maybe CertificateDetails
-> Maybe Text
-> Maybe Bool
-> Maybe Text
-> Maybe Bool
-> Maybe Text
-> Maybe Text
-> Maybe [DBInstanceAutomatedBackupsReplication]
-> Maybe Text
-> Maybe Text
-> Maybe Text
-> Maybe Text
-> Maybe [DBParameterGroupStatus]
-> Maybe [DBSecurityGroupMembership]
-> Maybe DBSubnetGroup
-> Maybe Text
-> Maybe Int
-> Maybe Text
-> Maybe Bool
-> Maybe [DomainMembership]
-> Maybe [Text]
-> Maybe Endpoint
-> Maybe Text
-> Maybe Text
-> Maybe Text
-> Maybe Bool
-> Maybe ISO8601
-> Maybe Int
-> Maybe Text
-> Maybe ISO8601
-> Maybe Text
-> Maybe Endpoint
-> Maybe MasterUserSecret
-> Maybe Text
-> Maybe Int
-> Maybe Int
-> Maybe Text
-> Maybe Bool
-> Maybe Text
-> Maybe Text
-> Maybe [OptionGroupMembership]
-> Maybe PendingModifiedValues
-> Maybe Bool
-> Maybe Text
-> Maybe Int
-> Maybe Text
-> Maybe Text
-> Maybe [ProcessorFeature]
-> Maybe Int
-> Maybe Bool
-> Maybe [Text]
-> Maybe [Text]
-> Maybe Text
-> Maybe ReplicaMode
-> Maybe ISO8601
-> Maybe Text
-> Maybe [DBInstanceStatusInfo]
-> Maybe Bool
-> Maybe Int
-> Maybe Text
-> Maybe [Tag]
-> Maybe Text
-> Maybe Text
-> Maybe [VpcSecurityGroupMembership]
-> DBInstance
DBInstance'
      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
"ActivityStreamEngineNativeAuditFieldsIncluded"
                  )
      forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
Prelude.<*> ([Node]
x forall a. FromXML a => [Node] -> Text -> Either String (Maybe a)
Data..@? Text
"ActivityStreamKinesisStreamName")
      forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
Prelude.<*> ([Node]
x forall a. FromXML a => [Node] -> Text -> Either String (Maybe a)
Data..@? Text
"ActivityStreamKmsKeyId")
      forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
Prelude.<*> ([Node]
x forall a. FromXML a => [Node] -> Text -> Either String (Maybe a)
Data..@? Text
"ActivityStreamMode")
      forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
Prelude.<*> ([Node]
x forall a. FromXML a => [Node] -> Text -> Either String (Maybe a)
Data..@? Text
"ActivityStreamPolicyStatus")
      forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
Prelude.<*> ([Node]
x forall a. FromXML a => [Node] -> Text -> Either String (Maybe a)
Data..@? Text
"ActivityStreamStatus")
      forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
Prelude.<*> ([Node]
x forall a. FromXML a => [Node] -> Text -> Either String (Maybe a)
Data..@? Text
"AllocatedStorage")
      forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
Prelude.<*> ( [Node]
x
                      forall a. FromXML a => [Node] -> Text -> Either String (Maybe a)
Data..@? Text
"AssociatedRoles"
                      forall (f :: * -> *) a. Functor f => f (Maybe a) -> a -> f a
Core..!@ forall a. Monoid a => a
Prelude.mempty
                      forall (m :: * -> *) a b. Monad m => m a -> (a -> m b) -> m b
Prelude.>>= forall (f :: * -> *) a b.
Applicative f =>
([a] -> f b) -> [a] -> f (Maybe b)
Core.may (forall a. FromXML a => Text -> [Node] -> Either String [a]
Data.parseXMLList Text
"DBInstanceRole")
                  )
      forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
Prelude.<*> ([Node]
x forall a. FromXML a => [Node] -> Text -> Either String (Maybe a)
Data..@? Text
"AutoMinorVersionUpgrade")
      forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
Prelude.<*> ([Node]
x forall a. FromXML a => [Node] -> Text -> Either String (Maybe a)
Data..@? Text
"AutomaticRestartTime")
      forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
Prelude.<*> ([Node]
x forall a. FromXML a => [Node] -> Text -> Either String (Maybe a)
Data..@? Text
"AutomationMode")
      forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
Prelude.<*> ([Node]
x forall a. FromXML a => [Node] -> Text -> Either String (Maybe a)
Data..@? Text
"AvailabilityZone")
      forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
Prelude.<*> ([Node]
x forall a. FromXML a => [Node] -> Text -> Either String (Maybe a)
Data..@? Text
"AwsBackupRecoveryPointArn")
      forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
Prelude.<*> ([Node]
x forall a. FromXML a => [Node] -> Text -> Either String (Maybe a)
Data..@? Text
"BackupRetentionPeriod")
      forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
Prelude.<*> ([Node]
x forall a. FromXML a => [Node] -> Text -> Either String (Maybe a)
Data..@? Text
"BackupTarget")
      forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
Prelude.<*> ([Node]
x forall a. FromXML a => [Node] -> Text -> Either String (Maybe a)
Data..@? Text
"CACertificateIdentifier")
      forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
Prelude.<*> ([Node]
x forall a. FromXML a => [Node] -> Text -> Either String (Maybe a)
Data..@? Text
"CertificateDetails")
      forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
Prelude.<*> ([Node]
x forall a. FromXML a => [Node] -> Text -> Either String (Maybe a)
Data..@? Text
"CharacterSetName")
      forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
Prelude.<*> ([Node]
x forall a. FromXML a => [Node] -> Text -> Either String (Maybe a)
Data..@? Text
"CopyTagsToSnapshot")
      forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
Prelude.<*> ([Node]
x forall a. FromXML a => [Node] -> Text -> Either String (Maybe a)
Data..@? Text
"CustomIamInstanceProfile")
      forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
Prelude.<*> ([Node]
x forall a. FromXML a => [Node] -> Text -> Either String (Maybe a)
Data..@? Text
"CustomerOwnedIpEnabled")
      forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
Prelude.<*> ([Node]
x forall a. FromXML a => [Node] -> Text -> Either String (Maybe a)
Data..@? Text
"DBClusterIdentifier")
      forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
Prelude.<*> ([Node]
x forall a. FromXML a => [Node] -> Text -> Either String (Maybe a)
Data..@? Text
"DBInstanceArn")
      forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
Prelude.<*> ( [Node]
x
                      forall a. FromXML a => [Node] -> Text -> Either String (Maybe a)
Data..@? Text
"DBInstanceAutomatedBackupsReplications"
                      forall (f :: * -> *) a. Functor f => f (Maybe a) -> a -> f a
Core..!@ forall a. Monoid a => a
Prelude.mempty
                      forall (m :: * -> *) a b. Monad m => m a -> (a -> m b) -> m b
Prelude.>>= forall (f :: * -> *) a b.
Applicative f =>
([a] -> f b) -> [a] -> f (Maybe b)
Core.may
                        ( forall a. FromXML a => Text -> [Node] -> Either String [a]
Data.parseXMLList
                            Text
"DBInstanceAutomatedBackupsReplication"
                        )
                  )
      forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
Prelude.<*> ([Node]
x forall a. FromXML a => [Node] -> Text -> Either String (Maybe a)
Data..@? Text
"DBInstanceClass")
      forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
Prelude.<*> ([Node]
x forall a. FromXML a => [Node] -> Text -> Either String (Maybe a)
Data..@? Text
"DBInstanceIdentifier")
      forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
Prelude.<*> ([Node]
x forall a. FromXML a => [Node] -> Text -> Either String (Maybe a)
Data..@? Text
"DBInstanceStatus")
      forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
Prelude.<*> ([Node]
x forall a. FromXML a => [Node] -> Text -> Either String (Maybe a)
Data..@? Text
"DBName")
      forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
Prelude.<*> ( [Node]
x
                      forall a. FromXML a => [Node] -> Text -> Either String (Maybe a)
Data..@? Text
"DBParameterGroups"
                      forall (f :: * -> *) a. Functor f => f (Maybe a) -> a -> f a
Core..!@ forall a. Monoid a => a
Prelude.mempty
                      forall (m :: * -> *) a b. Monad m => m a -> (a -> m b) -> m b
Prelude.>>= forall (f :: * -> *) a b.
Applicative f =>
([a] -> f b) -> [a] -> f (Maybe b)
Core.may (forall a. FromXML a => Text -> [Node] -> Either String [a]
Data.parseXMLList Text
"DBParameterGroup")
                  )
      forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
Prelude.<*> ( [Node]
x
                      forall a. FromXML a => [Node] -> Text -> Either String (Maybe a)
Data..@? Text
"DBSecurityGroups"
                      forall (f :: * -> *) a. Functor f => f (Maybe a) -> a -> f a
Core..!@ forall a. Monoid a => a
Prelude.mempty
                      forall (m :: * -> *) a b. Monad m => m a -> (a -> m b) -> m b
Prelude.>>= forall (f :: * -> *) a b.
Applicative f =>
([a] -> f b) -> [a] -> f (Maybe b)
Core.may (forall a. FromXML a => Text -> [Node] -> Either String [a]
Data.parseXMLList Text
"DBSecurityGroup")
                  )
      forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
Prelude.<*> ([Node]
x forall a. FromXML a => [Node] -> Text -> Either String (Maybe a)
Data..@? Text
"DBSubnetGroup")
      forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
Prelude.<*> ([Node]
x forall a. FromXML a => [Node] -> Text -> Either String (Maybe a)
Data..@? Text
"DBSystemId")
      forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
Prelude.<*> ([Node]
x forall a. FromXML a => [Node] -> Text -> Either String (Maybe a)
Data..@? Text
"DbInstancePort")
      forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
Prelude.<*> ([Node]
x forall a. FromXML a => [Node] -> Text -> Either String (Maybe a)
Data..@? Text
"DbiResourceId")
      forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
Prelude.<*> ([Node]
x forall a. FromXML a => [Node] -> Text -> Either String (Maybe a)
Data..@? Text
"DeletionProtection")
      forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
Prelude.<*> ( [Node]
x
                      forall a. FromXML a => [Node] -> Text -> Either String (Maybe a)
Data..@? Text
"DomainMemberships"
                      forall (f :: * -> *) a. Functor f => f (Maybe a) -> a -> f a
Core..!@ forall a. Monoid a => a
Prelude.mempty
                      forall (m :: * -> *) a b. Monad m => m a -> (a -> m b) -> m b
Prelude.>>= forall (f :: * -> *) a b.
Applicative f =>
([a] -> f b) -> [a] -> f (Maybe b)
Core.may (forall a. FromXML a => Text -> [Node] -> Either String [a]
Data.parseXMLList Text
"DomainMembership")
                  )
      forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
Prelude.<*> ( [Node]
x
                      forall a. FromXML a => [Node] -> Text -> Either String (Maybe a)
Data..@? Text
"EnabledCloudwatchLogsExports"
                      forall (f :: * -> *) a. Functor f => f (Maybe a) -> a -> f a
Core..!@ forall a. Monoid a => a
Prelude.mempty
                      forall (m :: * -> *) a b. Monad m => m a -> (a -> m b) -> m b
Prelude.>>= forall (f :: * -> *) a b.
Applicative f =>
([a] -> f b) -> [a] -> f (Maybe b)
Core.may (forall a. FromXML a => Text -> [Node] -> Either String [a]
Data.parseXMLList Text
"member")
                  )
      forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
Prelude.<*> ([Node]
x forall a. FromXML a => [Node] -> Text -> Either String (Maybe a)
Data..@? Text
"Endpoint")
      forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
Prelude.<*> ([Node]
x forall a. FromXML a => [Node] -> Text -> Either String (Maybe a)
Data..@? Text
"Engine")
      forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
Prelude.<*> ([Node]
x forall a. FromXML a => [Node] -> Text -> Either String (Maybe a)
Data..@? Text
"EngineVersion")
      forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
Prelude.<*> ([Node]
x forall a. FromXML a => [Node] -> Text -> Either String (Maybe a)
Data..@? Text
"EnhancedMonitoringResourceArn")
      forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
Prelude.<*> ([Node]
x forall a. FromXML a => [Node] -> Text -> Either String (Maybe a)
Data..@? Text
"IAMDatabaseAuthenticationEnabled")
      forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
Prelude.<*> ([Node]
x forall a. FromXML a => [Node] -> Text -> Either String (Maybe a)
Data..@? Text
"InstanceCreateTime")
      forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
Prelude.<*> ([Node]
x forall a. FromXML a => [Node] -> Text -> Either String (Maybe a)
Data..@? Text
"Iops")
      forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
Prelude.<*> ([Node]
x forall a. FromXML a => [Node] -> Text -> Either String (Maybe a)
Data..@? Text
"KmsKeyId")
      forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
Prelude.<*> ([Node]
x forall a. FromXML a => [Node] -> Text -> Either String (Maybe a)
Data..@? Text
"LatestRestorableTime")
      forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
Prelude.<*> ([Node]
x forall a. FromXML a => [Node] -> Text -> Either String (Maybe a)
Data..@? Text
"LicenseModel")
      forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
Prelude.<*> ([Node]
x forall a. FromXML a => [Node] -> Text -> Either String (Maybe a)
Data..@? Text
"ListenerEndpoint")
      forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
Prelude.<*> ([Node]
x forall a. FromXML a => [Node] -> Text -> Either String (Maybe a)
Data..@? Text
"MasterUserSecret")
      forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
Prelude.<*> ([Node]
x forall a. FromXML a => [Node] -> Text -> Either String (Maybe a)
Data..@? Text
"MasterUsername")
      forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
Prelude.<*> ([Node]
x forall a. FromXML a => [Node] -> Text -> Either String (Maybe a)
Data..@? Text
"MaxAllocatedStorage")
      forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
Prelude.<*> ([Node]
x forall a. FromXML a => [Node] -> Text -> Either String (Maybe a)
Data..@? Text
"MonitoringInterval")
      forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
Prelude.<*> ([Node]
x forall a. FromXML a => [Node] -> Text -> Either String (Maybe a)
Data..@? Text
"MonitoringRoleArn")
      forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
Prelude.<*> ([Node]
x forall a. FromXML a => [Node] -> Text -> Either String (Maybe a)
Data..@? Text
"MultiAZ")
      forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
Prelude.<*> ([Node]
x forall a. FromXML a => [Node] -> Text -> Either String (Maybe a)
Data..@? Text
"NcharCharacterSetName")
      forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
Prelude.<*> ([Node]
x forall a. FromXML a => [Node] -> Text -> Either String (Maybe a)
Data..@? Text
"NetworkType")
      forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
Prelude.<*> ( [Node]
x
                      forall a. FromXML a => [Node] -> Text -> Either String (Maybe a)
Data..@? Text
"OptionGroupMemberships"
                      forall (f :: * -> *) a. Functor f => f (Maybe a) -> a -> f a
Core..!@ forall a. Monoid a => a
Prelude.mempty
                      forall (m :: * -> *) a b. Monad m => m a -> (a -> m b) -> m b
Prelude.>>= forall (f :: * -> *) a b.
Applicative f =>
([a] -> f b) -> [a] -> f (Maybe b)
Core.may (forall a. FromXML a => Text -> [Node] -> Either String [a]
Data.parseXMLList Text
"OptionGroupMembership")
                  )
      forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
Prelude.<*> ([Node]
x forall a. FromXML a => [Node] -> Text -> Either String (Maybe a)
Data..@? Text
"PendingModifiedValues")
      forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
Prelude.<*> ([Node]
x forall a. FromXML a => [Node] -> Text -> Either String (Maybe a)
Data..@? Text
"PerformanceInsightsEnabled")
      forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
Prelude.<*> ([Node]
x forall a. FromXML a => [Node] -> Text -> Either String (Maybe a)
Data..@? Text
"PerformanceInsightsKMSKeyId")
      forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
Prelude.<*> ([Node]
x forall a. FromXML a => [Node] -> Text -> Either String (Maybe a)
Data..@? Text
"PerformanceInsightsRetentionPeriod")
      forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
Prelude.<*> ([Node]
x forall a. FromXML a => [Node] -> Text -> Either String (Maybe a)
Data..@? Text
"PreferredBackupWindow")
      forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
Prelude.<*> ([Node]
x forall a. FromXML a => [Node] -> Text -> Either String (Maybe a)
Data..@? Text
"PreferredMaintenanceWindow")
      forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
Prelude.<*> ( [Node]
x
                      forall a. FromXML a => [Node] -> Text -> Either String (Maybe a)
Data..@? Text
"ProcessorFeatures"
                      forall (f :: * -> *) a. Functor f => f (Maybe a) -> a -> f a
Core..!@ forall a. Monoid a => a
Prelude.mempty
                      forall (m :: * -> *) a b. Monad m => m a -> (a -> m b) -> m b
Prelude.>>= forall (f :: * -> *) a b.
Applicative f =>
([a] -> f b) -> [a] -> f (Maybe b)
Core.may (forall a. FromXML a => Text -> [Node] -> Either String [a]
Data.parseXMLList Text
"ProcessorFeature")
                  )
      forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
Prelude.<*> ([Node]
x forall a. FromXML a => [Node] -> Text -> Either String (Maybe a)
Data..@? Text
"PromotionTier")
      forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
Prelude.<*> ([Node]
x forall a. FromXML a => [Node] -> Text -> Either String (Maybe a)
Data..@? Text
"PubliclyAccessible")
      forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
Prelude.<*> ( [Node]
x
                      forall a. FromXML a => [Node] -> Text -> Either String (Maybe a)
Data..@? Text
"ReadReplicaDBClusterIdentifiers"
                      forall (f :: * -> *) a. Functor f => f (Maybe a) -> a -> f a
Core..!@ forall a. Monoid a => a
Prelude.mempty
                      forall (m :: * -> *) a b. Monad m => m a -> (a -> m b) -> m b
Prelude.>>= forall (f :: * -> *) a b.
Applicative f =>
([a] -> f b) -> [a] -> f (Maybe b)
Core.may
                        (forall a. FromXML a => Text -> [Node] -> Either String [a]
Data.parseXMLList Text
"ReadReplicaDBClusterIdentifier")
                  )
      forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
Prelude.<*> ( [Node]
x
                      forall a. FromXML a => [Node] -> Text -> Either String (Maybe a)
Data..@? Text
"ReadReplicaDBInstanceIdentifiers"
                      forall (f :: * -> *) a. Functor f => f (Maybe a) -> a -> f a
Core..!@ forall a. Monoid a => a
Prelude.mempty
                      forall (m :: * -> *) a b. Monad m => m a -> (a -> m b) -> m b
Prelude.>>= forall (f :: * -> *) a b.
Applicative f =>
([a] -> f b) -> [a] -> f (Maybe b)
Core.may
                        ( forall a. FromXML a => Text -> [Node] -> Either String [a]
Data.parseXMLList
                            Text
"ReadReplicaDBInstanceIdentifier"
                        )
                  )
      forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
Prelude.<*> ([Node]
x forall a. FromXML a => [Node] -> Text -> Either String (Maybe a)
Data..@? Text
"ReadReplicaSourceDBInstanceIdentifier")
      forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
Prelude.<*> ([Node]
x forall a. FromXML a => [Node] -> Text -> Either String (Maybe a)
Data..@? Text
"ReplicaMode")
      forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
Prelude.<*> ([Node]
x forall a. FromXML a => [Node] -> Text -> Either String (Maybe a)
Data..@? Text
"ResumeFullAutomationModeTime")
      forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
Prelude.<*> ([Node]
x forall a. FromXML a => [Node] -> Text -> Either String (Maybe a)
Data..@? Text
"SecondaryAvailabilityZone")
      forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
Prelude.<*> ( [Node]
x
                      forall a. FromXML a => [Node] -> Text -> Either String (Maybe a)
Data..@? Text
"StatusInfos"
                      forall (f :: * -> *) a. Functor f => f (Maybe a) -> a -> f a
Core..!@ forall a. Monoid a => a
Prelude.mempty
                      forall (m :: * -> *) a b. Monad m => m a -> (a -> m b) -> m b
Prelude.>>= forall (f :: * -> *) a b.
Applicative f =>
([a] -> f b) -> [a] -> f (Maybe b)
Core.may (forall a. FromXML a => Text -> [Node] -> Either String [a]
Data.parseXMLList Text
"DBInstanceStatusInfo")
                  )
      forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
Prelude.<*> ([Node]
x forall a. FromXML a => [Node] -> Text -> Either String (Maybe a)
Data..@? Text
"StorageEncrypted")
      forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
Prelude.<*> ([Node]
x forall a. FromXML a => [Node] -> Text -> Either String (Maybe a)
Data..@? Text
"StorageThroughput")
      forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
Prelude.<*> ([Node]
x forall a. FromXML a => [Node] -> Text -> Either String (Maybe a)
Data..@? Text
"StorageType")
      forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
Prelude.<*> ( [Node]
x
                      forall a. FromXML a => [Node] -> Text -> Either String (Maybe a)
Data..@? Text
"TagList"
                      forall (f :: * -> *) a. Functor f => f (Maybe a) -> a -> f a
Core..!@ forall a. Monoid a => a
Prelude.mempty
                      forall (m :: * -> *) a b. Monad m => m a -> (a -> m b) -> m b
Prelude.>>= forall (f :: * -> *) a b.
Applicative f =>
([a] -> f b) -> [a] -> f (Maybe b)
Core.may (forall a. FromXML a => Text -> [Node] -> Either String [a]
Data.parseXMLList Text
"Tag")
                  )
      forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
Prelude.<*> ([Node]
x forall a. FromXML a => [Node] -> Text -> Either String (Maybe a)
Data..@? Text
"TdeCredentialArn")
      forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
Prelude.<*> ([Node]
x forall a. FromXML a => [Node] -> Text -> Either String (Maybe a)
Data..@? Text
"Timezone")
      forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
Prelude.<*> ( [Node]
x
                      forall a. FromXML a => [Node] -> Text -> Either String (Maybe a)
Data..@? Text
"VpcSecurityGroups"
                      forall (f :: * -> *) a. Functor f => f (Maybe a) -> a -> f a
Core..!@ forall a. Monoid a => a
Prelude.mempty
                      forall (m :: * -> *) a b. Monad m => m a -> (a -> m b) -> m b
Prelude.>>= forall (f :: * -> *) a b.
Applicative f =>
([a] -> f b) -> [a] -> f (Maybe b)
Core.may
                        (forall a. FromXML a => Text -> [Node] -> Either String [a]
Data.parseXMLList Text
"VpcSecurityGroupMembership")
                  )

instance Prelude.Hashable DBInstance where
  hashWithSalt :: Int -> DBInstance -> Int
hashWithSalt Int
_salt DBInstance' {Maybe Bool
Maybe Int
Maybe [Text]
Maybe [DBInstanceAutomatedBackupsReplication]
Maybe [DBInstanceRole]
Maybe [DBInstanceStatusInfo]
Maybe [DBParameterGroupStatus]
Maybe [DBSecurityGroupMembership]
Maybe [DomainMembership]
Maybe [OptionGroupMembership]
Maybe [ProcessorFeature]
Maybe [Tag]
Maybe [VpcSecurityGroupMembership]
Maybe Text
Maybe ISO8601
Maybe ActivityStreamMode
Maybe ActivityStreamPolicyStatus
Maybe ActivityStreamStatus
Maybe AutomationMode
Maybe CertificateDetails
Maybe Endpoint
Maybe MasterUserSecret
Maybe PendingModifiedValues
Maybe ReplicaMode
Maybe DBSubnetGroup
vpcSecurityGroups :: Maybe [VpcSecurityGroupMembership]
timezone :: Maybe Text
tdeCredentialArn :: Maybe Text
tagList :: Maybe [Tag]
storageType :: Maybe Text
storageThroughput :: Maybe Int
storageEncrypted :: Maybe Bool
statusInfos :: Maybe [DBInstanceStatusInfo]
secondaryAvailabilityZone :: Maybe Text
resumeFullAutomationModeTime :: Maybe ISO8601
replicaMode :: Maybe ReplicaMode
readReplicaSourceDBInstanceIdentifier :: Maybe Text
readReplicaDBInstanceIdentifiers :: Maybe [Text]
readReplicaDBClusterIdentifiers :: Maybe [Text]
publiclyAccessible :: Maybe Bool
promotionTier :: Maybe Int
processorFeatures :: Maybe [ProcessorFeature]
preferredMaintenanceWindow :: Maybe Text
preferredBackupWindow :: Maybe Text
performanceInsightsRetentionPeriod :: Maybe Int
performanceInsightsKMSKeyId :: Maybe Text
performanceInsightsEnabled :: Maybe Bool
pendingModifiedValues :: Maybe PendingModifiedValues
optionGroupMemberships :: Maybe [OptionGroupMembership]
networkType :: Maybe Text
ncharCharacterSetName :: Maybe Text
multiAZ :: Maybe Bool
monitoringRoleArn :: Maybe Text
monitoringInterval :: Maybe Int
maxAllocatedStorage :: Maybe Int
masterUsername :: Maybe Text
masterUserSecret :: Maybe MasterUserSecret
listenerEndpoint :: Maybe Endpoint
licenseModel :: Maybe Text
latestRestorableTime :: Maybe ISO8601
kmsKeyId :: Maybe Text
iops :: Maybe Int
instanceCreateTime :: Maybe ISO8601
iAMDatabaseAuthenticationEnabled :: Maybe Bool
enhancedMonitoringResourceArn :: Maybe Text
engineVersion :: Maybe Text
engine :: Maybe Text
endpoint :: Maybe Endpoint
enabledCloudwatchLogsExports :: Maybe [Text]
domainMemberships :: Maybe [DomainMembership]
deletionProtection :: Maybe Bool
dbiResourceId :: Maybe Text
dbInstancePort :: Maybe Int
dbSystemId :: Maybe Text
dbSubnetGroup :: Maybe DBSubnetGroup
dbSecurityGroups :: Maybe [DBSecurityGroupMembership]
dbParameterGroups :: Maybe [DBParameterGroupStatus]
dbName :: Maybe Text
dbInstanceStatus :: Maybe Text
dbInstanceIdentifier :: Maybe Text
dbInstanceClass :: Maybe Text
dbInstanceAutomatedBackupsReplications :: Maybe [DBInstanceAutomatedBackupsReplication]
dbInstanceArn :: Maybe Text
dbClusterIdentifier :: Maybe Text
customerOwnedIpEnabled :: Maybe Bool
customIamInstanceProfile :: Maybe Text
copyTagsToSnapshot :: Maybe Bool
characterSetName :: Maybe Text
certificateDetails :: Maybe CertificateDetails
cACertificateIdentifier :: Maybe Text
backupTarget :: Maybe Text
backupRetentionPeriod :: Maybe Int
awsBackupRecoveryPointArn :: Maybe Text
availabilityZone :: Maybe Text
automationMode :: Maybe AutomationMode
automaticRestartTime :: Maybe ISO8601
autoMinorVersionUpgrade :: Maybe Bool
associatedRoles :: Maybe [DBInstanceRole]
allocatedStorage :: Maybe Int
activityStreamStatus :: Maybe ActivityStreamStatus
activityStreamPolicyStatus :: Maybe ActivityStreamPolicyStatus
activityStreamMode :: Maybe ActivityStreamMode
activityStreamKmsKeyId :: Maybe Text
activityStreamKinesisStreamName :: Maybe Text
activityStreamEngineNativeAuditFieldsIncluded :: Maybe Bool
$sel:vpcSecurityGroups:DBInstance' :: DBInstance -> Maybe [VpcSecurityGroupMembership]
$sel:timezone:DBInstance' :: DBInstance -> Maybe Text
$sel:tdeCredentialArn:DBInstance' :: DBInstance -> Maybe Text
$sel:tagList:DBInstance' :: DBInstance -> Maybe [Tag]
$sel:storageType:DBInstance' :: DBInstance -> Maybe Text
$sel:storageThroughput:DBInstance' :: DBInstance -> Maybe Int
$sel:storageEncrypted:DBInstance' :: DBInstance -> Maybe Bool
$sel:statusInfos:DBInstance' :: DBInstance -> Maybe [DBInstanceStatusInfo]
$sel:secondaryAvailabilityZone:DBInstance' :: DBInstance -> Maybe Text
$sel:resumeFullAutomationModeTime:DBInstance' :: DBInstance -> Maybe ISO8601
$sel:replicaMode:DBInstance' :: DBInstance -> Maybe ReplicaMode
$sel:readReplicaSourceDBInstanceIdentifier:DBInstance' :: DBInstance -> Maybe Text
$sel:readReplicaDBInstanceIdentifiers:DBInstance' :: DBInstance -> Maybe [Text]
$sel:readReplicaDBClusterIdentifiers:DBInstance' :: DBInstance -> Maybe [Text]
$sel:publiclyAccessible:DBInstance' :: DBInstance -> Maybe Bool
$sel:promotionTier:DBInstance' :: DBInstance -> Maybe Int
$sel:processorFeatures:DBInstance' :: DBInstance -> Maybe [ProcessorFeature]
$sel:preferredMaintenanceWindow:DBInstance' :: DBInstance -> Maybe Text
$sel:preferredBackupWindow:DBInstance' :: DBInstance -> Maybe Text
$sel:performanceInsightsRetentionPeriod:DBInstance' :: DBInstance -> Maybe Int
$sel:performanceInsightsKMSKeyId:DBInstance' :: DBInstance -> Maybe Text
$sel:performanceInsightsEnabled:DBInstance' :: DBInstance -> Maybe Bool
$sel:pendingModifiedValues:DBInstance' :: DBInstance -> Maybe PendingModifiedValues
$sel:optionGroupMemberships:DBInstance' :: DBInstance -> Maybe [OptionGroupMembership]
$sel:networkType:DBInstance' :: DBInstance -> Maybe Text
$sel:ncharCharacterSetName:DBInstance' :: DBInstance -> Maybe Text
$sel:multiAZ:DBInstance' :: DBInstance -> Maybe Bool
$sel:monitoringRoleArn:DBInstance' :: DBInstance -> Maybe Text
$sel:monitoringInterval:DBInstance' :: DBInstance -> Maybe Int
$sel:maxAllocatedStorage:DBInstance' :: DBInstance -> Maybe Int
$sel:masterUsername:DBInstance' :: DBInstance -> Maybe Text
$sel:masterUserSecret:DBInstance' :: DBInstance -> Maybe MasterUserSecret
$sel:listenerEndpoint:DBInstance' :: DBInstance -> Maybe Endpoint
$sel:licenseModel:DBInstance' :: DBInstance -> Maybe Text
$sel:latestRestorableTime:DBInstance' :: DBInstance -> Maybe ISO8601
$sel:kmsKeyId:DBInstance' :: DBInstance -> Maybe Text
$sel:iops:DBInstance' :: DBInstance -> Maybe Int
$sel:instanceCreateTime:DBInstance' :: DBInstance -> Maybe ISO8601
$sel:iAMDatabaseAuthenticationEnabled:DBInstance' :: DBInstance -> Maybe Bool
$sel:enhancedMonitoringResourceArn:DBInstance' :: DBInstance -> Maybe Text
$sel:engineVersion:DBInstance' :: DBInstance -> Maybe Text
$sel:engine:DBInstance' :: DBInstance -> Maybe Text
$sel:endpoint:DBInstance' :: DBInstance -> Maybe Endpoint
$sel:enabledCloudwatchLogsExports:DBInstance' :: DBInstance -> Maybe [Text]
$sel:domainMemberships:DBInstance' :: DBInstance -> Maybe [DomainMembership]
$sel:deletionProtection:DBInstance' :: DBInstance -> Maybe Bool
$sel:dbiResourceId:DBInstance' :: DBInstance -> Maybe Text
$sel:dbInstancePort:DBInstance' :: DBInstance -> Maybe Int
$sel:dbSystemId:DBInstance' :: DBInstance -> Maybe Text
$sel:dbSubnetGroup:DBInstance' :: DBInstance -> Maybe DBSubnetGroup
$sel:dbSecurityGroups:DBInstance' :: DBInstance -> Maybe [DBSecurityGroupMembership]
$sel:dbParameterGroups:DBInstance' :: DBInstance -> Maybe [DBParameterGroupStatus]
$sel:dbName:DBInstance' :: DBInstance -> Maybe Text
$sel:dbInstanceStatus:DBInstance' :: DBInstance -> Maybe Text
$sel:dbInstanceIdentifier:DBInstance' :: DBInstance -> Maybe Text
$sel:dbInstanceClass:DBInstance' :: DBInstance -> Maybe Text
$sel:dbInstanceAutomatedBackupsReplications:DBInstance' :: DBInstance -> Maybe [DBInstanceAutomatedBackupsReplication]
$sel:dbInstanceArn:DBInstance' :: DBInstance -> Maybe Text
$sel:dbClusterIdentifier:DBInstance' :: DBInstance -> Maybe Text
$sel:customerOwnedIpEnabled:DBInstance' :: DBInstance -> Maybe Bool
$sel:customIamInstanceProfile:DBInstance' :: DBInstance -> Maybe Text
$sel:copyTagsToSnapshot:DBInstance' :: DBInstance -> Maybe Bool
$sel:characterSetName:DBInstance' :: DBInstance -> Maybe Text
$sel:certificateDetails:DBInstance' :: DBInstance -> Maybe CertificateDetails
$sel:cACertificateIdentifier:DBInstance' :: DBInstance -> Maybe Text
$sel:backupTarget:DBInstance' :: DBInstance -> Maybe Text
$sel:backupRetentionPeriod:DBInstance' :: DBInstance -> Maybe Int
$sel:awsBackupRecoveryPointArn:DBInstance' :: DBInstance -> Maybe Text
$sel:availabilityZone:DBInstance' :: DBInstance -> Maybe Text
$sel:automationMode:DBInstance' :: DBInstance -> Maybe AutomationMode
$sel:automaticRestartTime:DBInstance' :: DBInstance -> Maybe ISO8601
$sel:autoMinorVersionUpgrade:DBInstance' :: DBInstance -> Maybe Bool
$sel:associatedRoles:DBInstance' :: DBInstance -> Maybe [DBInstanceRole]
$sel:allocatedStorage:DBInstance' :: DBInstance -> Maybe Int
$sel:activityStreamStatus:DBInstance' :: DBInstance -> Maybe ActivityStreamStatus
$sel:activityStreamPolicyStatus:DBInstance' :: DBInstance -> Maybe ActivityStreamPolicyStatus
$sel:activityStreamMode:DBInstance' :: DBInstance -> Maybe ActivityStreamMode
$sel:activityStreamKmsKeyId:DBInstance' :: DBInstance -> Maybe Text
$sel:activityStreamKinesisStreamName:DBInstance' :: DBInstance -> Maybe Text
$sel:activityStreamEngineNativeAuditFieldsIncluded:DBInstance' :: DBInstance -> Maybe Bool
..} =
    Int
_salt
      forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Maybe Bool
activityStreamEngineNativeAuditFieldsIncluded
      forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Maybe Text
activityStreamKinesisStreamName
      forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Maybe Text
activityStreamKmsKeyId
      forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Maybe ActivityStreamMode
activityStreamMode
      forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Maybe ActivityStreamPolicyStatus
activityStreamPolicyStatus
      forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Maybe ActivityStreamStatus
activityStreamStatus
      forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Maybe Int
allocatedStorage
      forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Maybe [DBInstanceRole]
associatedRoles
      forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Maybe Bool
autoMinorVersionUpgrade
      forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Maybe ISO8601
automaticRestartTime
      forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Maybe AutomationMode
automationMode
      forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Maybe Text
availabilityZone
      forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Maybe Text
awsBackupRecoveryPointArn
      forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Maybe Int
backupRetentionPeriod
      forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Maybe Text
backupTarget
      forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Maybe Text
cACertificateIdentifier
      forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Maybe CertificateDetails
certificateDetails
      forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Maybe Text
characterSetName
      forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Maybe Bool
copyTagsToSnapshot
      forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Maybe Text
customIamInstanceProfile
      forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Maybe Bool
customerOwnedIpEnabled
      forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Maybe Text
dbClusterIdentifier
      forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Maybe Text
dbInstanceArn
      forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Maybe [DBInstanceAutomatedBackupsReplication]
dbInstanceAutomatedBackupsReplications
      forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Maybe Text
dbInstanceClass
      forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Maybe Text
dbInstanceIdentifier
      forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Maybe Text
dbInstanceStatus
      forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Maybe Text
dbName
      forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Maybe [DBParameterGroupStatus]
dbParameterGroups
      forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Maybe [DBSecurityGroupMembership]
dbSecurityGroups
      forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Maybe DBSubnetGroup
dbSubnetGroup
      forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Maybe Text
dbSystemId
      forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Maybe Int
dbInstancePort
      forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Maybe Text
dbiResourceId
      forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Maybe Bool
deletionProtection
      forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Maybe [DomainMembership]
domainMemberships
      forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Maybe [Text]
enabledCloudwatchLogsExports
      forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Maybe Endpoint
endpoint
      forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Maybe Text
engine
      forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Maybe Text
engineVersion
      forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Maybe Text
enhancedMonitoringResourceArn
      forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Maybe Bool
iAMDatabaseAuthenticationEnabled
      forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Maybe ISO8601
instanceCreateTime
      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 ISO8601
latestRestorableTime
      forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Maybe Text
licenseModel
      forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Maybe Endpoint
listenerEndpoint
      forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Maybe MasterUserSecret
masterUserSecret
      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
ncharCharacterSetName
      forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Maybe Text
networkType
      forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Maybe [OptionGroupMembership]
optionGroupMemberships
      forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Maybe PendingModifiedValues
pendingModifiedValues
      forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Maybe Bool
performanceInsightsEnabled
      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 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 Int
promotionTier
      forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Maybe Bool
publiclyAccessible
      forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Maybe [Text]
readReplicaDBClusterIdentifiers
      forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Maybe [Text]
readReplicaDBInstanceIdentifiers
      forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Maybe Text
readReplicaSourceDBInstanceIdentifier
      forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Maybe ReplicaMode
replicaMode
      forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Maybe ISO8601
resumeFullAutomationModeTime
      forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Maybe Text
secondaryAvailabilityZone
      forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Maybe [DBInstanceStatusInfo]
statusInfos
      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]
tagList
      forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Maybe Text
tdeCredentialArn
      forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Maybe Text
timezone
      forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Maybe [VpcSecurityGroupMembership]
vpcSecurityGroups

instance Prelude.NFData DBInstance where
  rnf :: DBInstance -> ()
rnf DBInstance' {Maybe Bool
Maybe Int
Maybe [Text]
Maybe [DBInstanceAutomatedBackupsReplication]
Maybe [DBInstanceRole]
Maybe [DBInstanceStatusInfo]
Maybe [DBParameterGroupStatus]
Maybe [DBSecurityGroupMembership]
Maybe [DomainMembership]
Maybe [OptionGroupMembership]
Maybe [ProcessorFeature]
Maybe [Tag]
Maybe [VpcSecurityGroupMembership]
Maybe Text
Maybe ISO8601
Maybe ActivityStreamMode
Maybe ActivityStreamPolicyStatus
Maybe ActivityStreamStatus
Maybe AutomationMode
Maybe CertificateDetails
Maybe Endpoint
Maybe MasterUserSecret
Maybe PendingModifiedValues
Maybe ReplicaMode
Maybe DBSubnetGroup
vpcSecurityGroups :: Maybe [VpcSecurityGroupMembership]
timezone :: Maybe Text
tdeCredentialArn :: Maybe Text
tagList :: Maybe [Tag]
storageType :: Maybe Text
storageThroughput :: Maybe Int
storageEncrypted :: Maybe Bool
statusInfos :: Maybe [DBInstanceStatusInfo]
secondaryAvailabilityZone :: Maybe Text
resumeFullAutomationModeTime :: Maybe ISO8601
replicaMode :: Maybe ReplicaMode
readReplicaSourceDBInstanceIdentifier :: Maybe Text
readReplicaDBInstanceIdentifiers :: Maybe [Text]
readReplicaDBClusterIdentifiers :: Maybe [Text]
publiclyAccessible :: Maybe Bool
promotionTier :: Maybe Int
processorFeatures :: Maybe [ProcessorFeature]
preferredMaintenanceWindow :: Maybe Text
preferredBackupWindow :: Maybe Text
performanceInsightsRetentionPeriod :: Maybe Int
performanceInsightsKMSKeyId :: Maybe Text
performanceInsightsEnabled :: Maybe Bool
pendingModifiedValues :: Maybe PendingModifiedValues
optionGroupMemberships :: Maybe [OptionGroupMembership]
networkType :: Maybe Text
ncharCharacterSetName :: Maybe Text
multiAZ :: Maybe Bool
monitoringRoleArn :: Maybe Text
monitoringInterval :: Maybe Int
maxAllocatedStorage :: Maybe Int
masterUsername :: Maybe Text
masterUserSecret :: Maybe MasterUserSecret
listenerEndpoint :: Maybe Endpoint
licenseModel :: Maybe Text
latestRestorableTime :: Maybe ISO8601
kmsKeyId :: Maybe Text
iops :: Maybe Int
instanceCreateTime :: Maybe ISO8601
iAMDatabaseAuthenticationEnabled :: Maybe Bool
enhancedMonitoringResourceArn :: Maybe Text
engineVersion :: Maybe Text
engine :: Maybe Text
endpoint :: Maybe Endpoint
enabledCloudwatchLogsExports :: Maybe [Text]
domainMemberships :: Maybe [DomainMembership]
deletionProtection :: Maybe Bool
dbiResourceId :: Maybe Text
dbInstancePort :: Maybe Int
dbSystemId :: Maybe Text
dbSubnetGroup :: Maybe DBSubnetGroup
dbSecurityGroups :: Maybe [DBSecurityGroupMembership]
dbParameterGroups :: Maybe [DBParameterGroupStatus]
dbName :: Maybe Text
dbInstanceStatus :: Maybe Text
dbInstanceIdentifier :: Maybe Text
dbInstanceClass :: Maybe Text
dbInstanceAutomatedBackupsReplications :: Maybe [DBInstanceAutomatedBackupsReplication]
dbInstanceArn :: Maybe Text
dbClusterIdentifier :: Maybe Text
customerOwnedIpEnabled :: Maybe Bool
customIamInstanceProfile :: Maybe Text
copyTagsToSnapshot :: Maybe Bool
characterSetName :: Maybe Text
certificateDetails :: Maybe CertificateDetails
cACertificateIdentifier :: Maybe Text
backupTarget :: Maybe Text
backupRetentionPeriod :: Maybe Int
awsBackupRecoveryPointArn :: Maybe Text
availabilityZone :: Maybe Text
automationMode :: Maybe AutomationMode
automaticRestartTime :: Maybe ISO8601
autoMinorVersionUpgrade :: Maybe Bool
associatedRoles :: Maybe [DBInstanceRole]
allocatedStorage :: Maybe Int
activityStreamStatus :: Maybe ActivityStreamStatus
activityStreamPolicyStatus :: Maybe ActivityStreamPolicyStatus
activityStreamMode :: Maybe ActivityStreamMode
activityStreamKmsKeyId :: Maybe Text
activityStreamKinesisStreamName :: Maybe Text
activityStreamEngineNativeAuditFieldsIncluded :: Maybe Bool
$sel:vpcSecurityGroups:DBInstance' :: DBInstance -> Maybe [VpcSecurityGroupMembership]
$sel:timezone:DBInstance' :: DBInstance -> Maybe Text
$sel:tdeCredentialArn:DBInstance' :: DBInstance -> Maybe Text
$sel:tagList:DBInstance' :: DBInstance -> Maybe [Tag]
$sel:storageType:DBInstance' :: DBInstance -> Maybe Text
$sel:storageThroughput:DBInstance' :: DBInstance -> Maybe Int
$sel:storageEncrypted:DBInstance' :: DBInstance -> Maybe Bool
$sel:statusInfos:DBInstance' :: DBInstance -> Maybe [DBInstanceStatusInfo]
$sel:secondaryAvailabilityZone:DBInstance' :: DBInstance -> Maybe Text
$sel:resumeFullAutomationModeTime:DBInstance' :: DBInstance -> Maybe ISO8601
$sel:replicaMode:DBInstance' :: DBInstance -> Maybe ReplicaMode
$sel:readReplicaSourceDBInstanceIdentifier:DBInstance' :: DBInstance -> Maybe Text
$sel:readReplicaDBInstanceIdentifiers:DBInstance' :: DBInstance -> Maybe [Text]
$sel:readReplicaDBClusterIdentifiers:DBInstance' :: DBInstance -> Maybe [Text]
$sel:publiclyAccessible:DBInstance' :: DBInstance -> Maybe Bool
$sel:promotionTier:DBInstance' :: DBInstance -> Maybe Int
$sel:processorFeatures:DBInstance' :: DBInstance -> Maybe [ProcessorFeature]
$sel:preferredMaintenanceWindow:DBInstance' :: DBInstance -> Maybe Text
$sel:preferredBackupWindow:DBInstance' :: DBInstance -> Maybe Text
$sel:performanceInsightsRetentionPeriod:DBInstance' :: DBInstance -> Maybe Int
$sel:performanceInsightsKMSKeyId:DBInstance' :: DBInstance -> Maybe Text
$sel:performanceInsightsEnabled:DBInstance' :: DBInstance -> Maybe Bool
$sel:pendingModifiedValues:DBInstance' :: DBInstance -> Maybe PendingModifiedValues
$sel:optionGroupMemberships:DBInstance' :: DBInstance -> Maybe [OptionGroupMembership]
$sel:networkType:DBInstance' :: DBInstance -> Maybe Text
$sel:ncharCharacterSetName:DBInstance' :: DBInstance -> Maybe Text
$sel:multiAZ:DBInstance' :: DBInstance -> Maybe Bool
$sel:monitoringRoleArn:DBInstance' :: DBInstance -> Maybe Text
$sel:monitoringInterval:DBInstance' :: DBInstance -> Maybe Int
$sel:maxAllocatedStorage:DBInstance' :: DBInstance -> Maybe Int
$sel:masterUsername:DBInstance' :: DBInstance -> Maybe Text
$sel:masterUserSecret:DBInstance' :: DBInstance -> Maybe MasterUserSecret
$sel:listenerEndpoint:DBInstance' :: DBInstance -> Maybe Endpoint
$sel:licenseModel:DBInstance' :: DBInstance -> Maybe Text
$sel:latestRestorableTime:DBInstance' :: DBInstance -> Maybe ISO8601
$sel:kmsKeyId:DBInstance' :: DBInstance -> Maybe Text
$sel:iops:DBInstance' :: DBInstance -> Maybe Int
$sel:instanceCreateTime:DBInstance' :: DBInstance -> Maybe ISO8601
$sel:iAMDatabaseAuthenticationEnabled:DBInstance' :: DBInstance -> Maybe Bool
$sel:enhancedMonitoringResourceArn:DBInstance' :: DBInstance -> Maybe Text
$sel:engineVersion:DBInstance' :: DBInstance -> Maybe Text
$sel:engine:DBInstance' :: DBInstance -> Maybe Text
$sel:endpoint:DBInstance' :: DBInstance -> Maybe Endpoint
$sel:enabledCloudwatchLogsExports:DBInstance' :: DBInstance -> Maybe [Text]
$sel:domainMemberships:DBInstance' :: DBInstance -> Maybe [DomainMembership]
$sel:deletionProtection:DBInstance' :: DBInstance -> Maybe Bool
$sel:dbiResourceId:DBInstance' :: DBInstance -> Maybe Text
$sel:dbInstancePort:DBInstance' :: DBInstance -> Maybe Int
$sel:dbSystemId:DBInstance' :: DBInstance -> Maybe Text
$sel:dbSubnetGroup:DBInstance' :: DBInstance -> Maybe DBSubnetGroup
$sel:dbSecurityGroups:DBInstance' :: DBInstance -> Maybe [DBSecurityGroupMembership]
$sel:dbParameterGroups:DBInstance' :: DBInstance -> Maybe [DBParameterGroupStatus]
$sel:dbName:DBInstance' :: DBInstance -> Maybe Text
$sel:dbInstanceStatus:DBInstance' :: DBInstance -> Maybe Text
$sel:dbInstanceIdentifier:DBInstance' :: DBInstance -> Maybe Text
$sel:dbInstanceClass:DBInstance' :: DBInstance -> Maybe Text
$sel:dbInstanceAutomatedBackupsReplications:DBInstance' :: DBInstance -> Maybe [DBInstanceAutomatedBackupsReplication]
$sel:dbInstanceArn:DBInstance' :: DBInstance -> Maybe Text
$sel:dbClusterIdentifier:DBInstance' :: DBInstance -> Maybe Text
$sel:customerOwnedIpEnabled:DBInstance' :: DBInstance -> Maybe Bool
$sel:customIamInstanceProfile:DBInstance' :: DBInstance -> Maybe Text
$sel:copyTagsToSnapshot:DBInstance' :: DBInstance -> Maybe Bool
$sel:characterSetName:DBInstance' :: DBInstance -> Maybe Text
$sel:certificateDetails:DBInstance' :: DBInstance -> Maybe CertificateDetails
$sel:cACertificateIdentifier:DBInstance' :: DBInstance -> Maybe Text
$sel:backupTarget:DBInstance' :: DBInstance -> Maybe Text
$sel:backupRetentionPeriod:DBInstance' :: DBInstance -> Maybe Int
$sel:awsBackupRecoveryPointArn:DBInstance' :: DBInstance -> Maybe Text
$sel:availabilityZone:DBInstance' :: DBInstance -> Maybe Text
$sel:automationMode:DBInstance' :: DBInstance -> Maybe AutomationMode
$sel:automaticRestartTime:DBInstance' :: DBInstance -> Maybe ISO8601
$sel:autoMinorVersionUpgrade:DBInstance' :: DBInstance -> Maybe Bool
$sel:associatedRoles:DBInstance' :: DBInstance -> Maybe [DBInstanceRole]
$sel:allocatedStorage:DBInstance' :: DBInstance -> Maybe Int
$sel:activityStreamStatus:DBInstance' :: DBInstance -> Maybe ActivityStreamStatus
$sel:activityStreamPolicyStatus:DBInstance' :: DBInstance -> Maybe ActivityStreamPolicyStatus
$sel:activityStreamMode:DBInstance' :: DBInstance -> Maybe ActivityStreamMode
$sel:activityStreamKmsKeyId:DBInstance' :: DBInstance -> Maybe Text
$sel:activityStreamKinesisStreamName:DBInstance' :: DBInstance -> Maybe Text
$sel:activityStreamEngineNativeAuditFieldsIncluded:DBInstance' :: DBInstance -> Maybe Bool
..} =
    forall a. NFData a => a -> ()
Prelude.rnf
      Maybe Bool
activityStreamEngineNativeAuditFieldsIncluded
      seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf Maybe Text
activityStreamKinesisStreamName
      seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf Maybe Text
activityStreamKmsKeyId
      seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf Maybe ActivityStreamMode
activityStreamMode
      seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf Maybe ActivityStreamPolicyStatus
activityStreamPolicyStatus
      seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf Maybe ActivityStreamStatus
activityStreamStatus
      seq :: forall a b. a -> b -> b
`Prelude.seq` 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 [DBInstanceRole]
associatedRoles
      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 ISO8601
automaticRestartTime
      seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf Maybe AutomationMode
automationMode
      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 Text
awsBackupRecoveryPointArn
      seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf Maybe Int
backupRetentionPeriod
      seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf Maybe Text
backupTarget
      seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf Maybe Text
cACertificateIdentifier
      seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf Maybe CertificateDetails
certificateDetails
      seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf Maybe Text
characterSetName
      seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf Maybe Bool
copyTagsToSnapshot
      seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf
        Maybe Text
customIamInstanceProfile
      seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf
        Maybe Bool
customerOwnedIpEnabled
      seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf
        Maybe Text
dbClusterIdentifier
      seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf
        Maybe Text
dbInstanceArn
      seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf
        Maybe [DBInstanceAutomatedBackupsReplication]
dbInstanceAutomatedBackupsReplications
      seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf
        Maybe Text
dbInstanceClass
      seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf
        Maybe Text
dbInstanceIdentifier
      seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf
        Maybe Text
dbInstanceStatus
      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 [DBParameterGroupStatus]
dbParameterGroups
      seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf
        Maybe [DBSecurityGroupMembership]
dbSecurityGroups
      seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf
        Maybe DBSubnetGroup
dbSubnetGroup
      seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf
        Maybe Text
dbSystemId
      seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf
        Maybe Int
dbInstancePort
      seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf
        Maybe Text
dbiResourceId
      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 [DomainMembership]
domainMemberships
      seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf
        Maybe [Text]
enabledCloudwatchLogsExports
      seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf
        Maybe Endpoint
endpoint
      seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf
        Maybe Text
engine
      seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf
        Maybe Text
engineVersion
      seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf
        Maybe Text
enhancedMonitoringResourceArn
      seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf
        Maybe Bool
iAMDatabaseAuthenticationEnabled
      seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf
        Maybe ISO8601
instanceCreateTime
      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 ISO8601
latestRestorableTime
      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 Endpoint
listenerEndpoint
      seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf
        Maybe MasterUserSecret
masterUserSecret
      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
ncharCharacterSetName
      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 [OptionGroupMembership]
optionGroupMemberships
      seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf
        Maybe PendingModifiedValues
pendingModifiedValues
      seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf
        Maybe Bool
performanceInsightsEnabled
      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 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 Int
promotionTier
      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]
readReplicaDBClusterIdentifiers
      seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf
        Maybe [Text]
readReplicaDBInstanceIdentifiers
      seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf
        Maybe Text
readReplicaSourceDBInstanceIdentifier
      seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf
        Maybe ReplicaMode
replicaMode
      seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf
        Maybe ISO8601
resumeFullAutomationModeTime
      seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf
        Maybe Text
secondaryAvailabilityZone
      seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf
        Maybe [DBInstanceStatusInfo]
statusInfos
      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]
tagList
      seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf
        Maybe Text
tdeCredentialArn
      seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf
        Maybe Text
timezone
      seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf
        Maybe [VpcSecurityGroupMembership]
vpcSecurityGroups