{-# 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.Neptune.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.Neptune.Types.DBInstance where

import qualified Amazonka.Core as Core
import qualified Amazonka.Core.Lens.Internal as Lens
import qualified Amazonka.Data as Data
import Amazonka.Neptune.Types.DBInstanceStatusInfo
import Amazonka.Neptune.Types.DBParameterGroupStatus
import Amazonka.Neptune.Types.DBSecurityGroupMembership
import Amazonka.Neptune.Types.DBSubnetGroup
import Amazonka.Neptune.Types.DomainMembership
import Amazonka.Neptune.Types.Endpoint
import Amazonka.Neptune.Types.OptionGroupMembership
import Amazonka.Neptune.Types.PendingModifiedValues
import Amazonka.Neptune.Types.VpcSecurityGroupMembership
import qualified Amazonka.Prelude as Prelude

-- | Contains the details of an Amazon Neptune DB instance.
--
-- This data type is used as a response element in the DescribeDBInstances
-- action.
--
-- /See:/ 'newDBInstance' smart constructor.
data DBInstance = DBInstance'
  { -- | Not supported by Neptune.
    DBInstance -> Maybe Int
allocatedStorage :: Prelude.Maybe Prelude.Int,
    -- | Indicates that minor version patches are applied automatically.
    DBInstance -> Maybe Bool
autoMinorVersionUpgrade :: Prelude.Maybe Prelude.Bool,
    -- | Specifies the name of the Availability Zone the DB instance is located
    -- in.
    DBInstance -> Maybe Text
availabilityZone :: Prelude.Maybe Prelude.Text,
    -- | Specifies the number of days for which automatic DB snapshots are
    -- retained.
    DBInstance -> Maybe Int
backupRetentionPeriod :: Prelude.Maybe Prelude.Int,
    -- | The identifier of the CA certificate for this DB instance.
    DBInstance -> Maybe Text
cACertificateIdentifier :: Prelude.Maybe Prelude.Text,
    -- | /(Not supported by Neptune)/
    DBInstance -> Maybe Text
characterSetName :: Prelude.Maybe Prelude.Text,
    -- | Specifies whether tags are copied from the DB instance to snapshots of
    -- the DB instance.
    DBInstance -> Maybe Bool
copyTagsToSnapshot :: 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,
    -- | 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.
    DBInstance -> Maybe Text
dbInstanceStatus :: Prelude.Maybe Prelude.Text,
    -- | The database name.
    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],
    -- | Provides List of DB security group elements containing only
    -- @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,
    -- | 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 Region-unique, immutable identifier for the DB instance. This
    -- identifier is found in Amazon CloudTrail log entries whenever the Amazon
    -- KMS key for the DB instance is accessed.
    DBInstance -> Maybe Text
dbiResourceId :: Prelude.Maybe Prelude.Text,
    -- | Indicates whether or not the DB instance has deletion protection
    -- enabled. The instance can\'t be deleted when deletion protection is
    -- enabled. See
    -- <https://docs.aws.amazon.com/neptune/latest/userguide/manage-console-instances-delete.html Deleting a DB Instance>.
    DBInstance -> Maybe Bool
deletionProtection :: Prelude.Maybe Prelude.Bool,
    -- | Not supported
    DBInstance -> Maybe [DomainMembership]
domainMemberships :: Prelude.Maybe [DomainMembership],
    -- | A list of log types that this DB instance is configured to export to
    -- CloudWatch Logs.
    DBInstance -> Maybe [Text]
enabledCloudwatchLogsExports :: Prelude.Maybe [Prelude.Text],
    -- | Specifies the connection endpoint.
    DBInstance -> Maybe Endpoint
endpoint :: Prelude.Maybe Endpoint,
    -- | Provides 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 Amazon Identity and Access Management (IAM) authentication is
    -- enabled, and otherwise false.
    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,
    -- | Not supported: The encryption for DB instances is managed by the DB
    -- cluster.
    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.
    DBInstance -> Maybe Text
licenseModel :: Prelude.Maybe Prelude.Text,
    -- | Not supported by Neptune.
    DBInstance -> Maybe Text
masterUsername :: Prelude.Maybe Prelude.Text,
    -- | 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 Neptune 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.
    DBInstance -> Maybe Bool
multiAZ :: Prelude.Maybe Prelude.Bool,
    -- | /(Not supported by Neptune)/
    DBInstance -> Maybe [OptionGroupMembership]
optionGroupMemberships :: Prelude.Maybe [OptionGroupMembership],
    -- | 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,
    -- | /(Not supported by Neptune)/
    DBInstance -> Maybe Bool
performanceInsightsEnabled :: Prelude.Maybe Prelude.Bool,
    -- | /(Not supported by Neptune)/
    DBInstance -> Maybe Text
performanceInsightsKMSKeyId :: Prelude.Maybe Prelude.Text,
    -- | 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,
    -- | A value that specifies the order in which a Read Replica is promoted to
    -- the primary instance after a failure of the existing primary instance.
    DBInstance -> Maybe Int
promotionTier :: Prelude.Maybe Prelude.Int,
    -- | This flag should no longer be used.
    DBInstance -> Maybe Bool
publiclyAccessible :: Prelude.Maybe Prelude.Bool,
    -- | Contains one or more identifiers of DB clusters that are Read Replicas
    -- of this DB instance.
    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,
    -- | 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 is not a Read Replica,
    -- this is blank.
    DBInstance -> Maybe [DBInstanceStatusInfo]
statusInfos :: Prelude.Maybe [DBInstanceStatusInfo],
    -- | Not supported: The encryption for DB instances is managed by the DB
    -- cluster.
    DBInstance -> Maybe Bool
storageEncrypted :: Prelude.Maybe Prelude.Bool,
    -- | Specifies the storage type associated with DB instance.
    DBInstance -> Maybe Text
storageType :: Prelude.Maybe Prelude.Text,
    -- | The ARN from the key store with which the instance is associated for TDE
    -- encryption.
    DBInstance -> Maybe Text
tdeCredentialArn :: Prelude.Maybe Prelude.Text,
    -- | Not supported.
    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:
--
-- 'allocatedStorage', 'dbInstance_allocatedStorage' - Not supported by Neptune.
--
-- 'autoMinorVersionUpgrade', 'dbInstance_autoMinorVersionUpgrade' - Indicates that minor version patches are applied automatically.
--
-- 'availabilityZone', 'dbInstance_availabilityZone' - Specifies the name of the Availability Zone the DB instance is located
-- in.
--
-- 'backupRetentionPeriod', 'dbInstance_backupRetentionPeriod' - Specifies the number of days for which automatic DB snapshots are
-- retained.
--
-- 'cACertificateIdentifier', 'dbInstance_cACertificateIdentifier' - The identifier of the CA certificate for this DB instance.
--
-- 'characterSetName', 'dbInstance_characterSetName' - /(Not supported by Neptune)/
--
-- 'copyTagsToSnapshot', 'dbInstance_copyTagsToSnapshot' - Specifies whether tags are copied from the DB instance to snapshots of
-- the DB instance.
--
-- '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.
--
-- '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.
--
-- 'dbName', 'dbInstance_dbName' - The database name.
--
-- 'dbParameterGroups', 'dbInstance_dbParameterGroups' - Provides the list of DB parameter groups applied to this DB instance.
--
-- 'dbSecurityGroups', 'dbInstance_dbSecurityGroups' - Provides List of DB security group elements containing only
-- @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.
--
-- '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 Region-unique, immutable identifier for the DB instance. This
-- identifier is found in Amazon CloudTrail log entries whenever the Amazon
-- KMS key for the DB instance is accessed.
--
-- 'deletionProtection', 'dbInstance_deletionProtection' - Indicates whether or not the DB instance has deletion protection
-- enabled. The instance can\'t be deleted when deletion protection is
-- enabled. See
-- <https://docs.aws.amazon.com/neptune/latest/userguide/manage-console-instances-delete.html Deleting a DB Instance>.
--
-- 'domainMemberships', 'dbInstance_domainMemberships' - Not supported
--
-- 'enabledCloudwatchLogsExports', 'dbInstance_enabledCloudwatchLogsExports' - A list of log types that this DB instance is configured to export to
-- CloudWatch Logs.
--
-- 'endpoint', 'dbInstance_endpoint' - Specifies the connection endpoint.
--
-- 'engine', 'dbInstance_engine' - Provides 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 Amazon Identity and Access Management (IAM) authentication is
-- enabled, and otherwise false.
--
-- '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' - Not supported: The encryption for DB instances is managed by the DB
-- cluster.
--
-- '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.
--
-- 'masterUsername', 'dbInstance_masterUsername' - Not supported by Neptune.
--
-- '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 Neptune to send Enhanced
-- Monitoring metrics to Amazon CloudWatch Logs.
--
-- 'multiAZ', 'dbInstance_multiAZ' - Specifies if the DB instance is a Multi-AZ deployment.
--
-- 'optionGroupMemberships', 'dbInstance_optionGroupMemberships' - /(Not supported by Neptune)/
--
-- 'pendingModifiedValues', 'dbInstance_pendingModifiedValues' - 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' - /(Not supported by Neptune)/
--
-- 'performanceInsightsKMSKeyId', 'dbInstance_performanceInsightsKMSKeyId' - /(Not supported by Neptune)/
--
-- '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).
--
-- 'promotionTier', 'dbInstance_promotionTier' - A value that specifies the order in which a Read Replica is promoted to
-- the primary instance after a failure of the existing primary instance.
--
-- 'publiclyAccessible', 'dbInstance_publiclyAccessible' - This flag should no longer be used.
--
-- 'readReplicaDBClusterIdentifiers', 'dbInstance_readReplicaDBClusterIdentifiers' - Contains one or more identifiers of DB clusters that are Read Replicas
-- of this DB instance.
--
-- '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.
--
-- '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 is not a Read Replica,
-- this is blank.
--
-- 'storageEncrypted', 'dbInstance_storageEncrypted' - Not supported: The encryption for DB instances is managed by the DB
-- cluster.
--
-- 'storageType', 'dbInstance_storageType' - Specifies the storage type associated with DB instance.
--
-- 'tdeCredentialArn', 'dbInstance_tdeCredentialArn' - The ARN from the key store with which the instance is associated for TDE
-- encryption.
--
-- 'timezone', 'dbInstance_timezone' - Not supported.
--
-- 'vpcSecurityGroups', 'dbInstance_vpcSecurityGroups' - Provides a list of VPC security group elements that the DB instance
-- belongs to.
newDBInstance ::
  DBInstance
newDBInstance :: DBInstance
newDBInstance =
  DBInstance'
    { $sel:allocatedStorage:DBInstance' :: Maybe Int
allocatedStorage = forall a. Maybe a
Prelude.Nothing,
      $sel:autoMinorVersionUpgrade:DBInstance' :: Maybe Bool
autoMinorVersionUpgrade = forall a. Maybe a
Prelude.Nothing,
      $sel:availabilityZone:DBInstance' :: Maybe Text
availabilityZone = forall a. Maybe a
Prelude.Nothing,
      $sel:backupRetentionPeriod:DBInstance' :: Maybe Int
backupRetentionPeriod = forall a. Maybe a
Prelude.Nothing,
      $sel:cACertificateIdentifier:DBInstance' :: Maybe Text
cACertificateIdentifier = 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:dbClusterIdentifier:DBInstance' :: Maybe Text
dbClusterIdentifier = forall a. Maybe a
Prelude.Nothing,
      $sel:dbInstanceArn:DBInstance' :: Maybe Text
dbInstanceArn = 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: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:masterUsername:DBInstance' :: Maybe Text
masterUsername = 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: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:preferredBackupWindow:DBInstance' :: Maybe Text
preferredBackupWindow = forall a. Maybe a
Prelude.Nothing,
      $sel:preferredMaintenanceWindow:DBInstance' :: Maybe Text
preferredMaintenanceWindow = 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: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:storageType:DBInstance' :: Maybe Text
storageType = 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
    }

-- | Not supported by Neptune.
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)

-- | 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)

-- | 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)

-- | 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)

-- | The identifier of the CA certificate for this DB instance.
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)

-- | /(Not supported by Neptune)/
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.
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)

-- | 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)

-- | 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.
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 database name.
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

-- | Provides List of DB security group elements containing only
-- @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)

-- | 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 Region-unique, immutable identifier for the DB instance. This
-- identifier is found in Amazon CloudTrail log entries whenever the Amazon
-- 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 whether or not the DB instance has deletion protection
-- enabled. The instance can\'t be deleted when deletion protection is
-- enabled. See
-- <https://docs.aws.amazon.com/neptune/latest/userguide/manage-console-instances-delete.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)

-- | Not supported
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.
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.
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)

-- | Provides 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 Amazon Identity and Access Management (IAM) authentication is
-- enabled, and otherwise false.
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)

-- | Not supported: The encryption for DB instances is managed by the DB
-- cluster.
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.
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)

-- | Not supported by Neptune.
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 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 Neptune 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.
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)

-- | /(Not supported by Neptune)/
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

-- | 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)

-- | /(Not supported by Neptune)/
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)

-- | /(Not supported by Neptune)/
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)

-- | 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)

-- | A value that specifies the order in which a Read Replica is promoted to
-- the primary instance after a failure of the existing primary instance.
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)

-- | This flag should no longer be used.
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 DB clusters that are Read Replicas
-- of this DB instance.
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)

-- | 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 is not 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

-- | Not supported: The encryption for DB instances is managed by the DB
-- cluster.
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 type associated with 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)

-- | 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)

-- | Not supported.
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 Int
-> Maybe Bool
-> Maybe Text
-> Maybe Int
-> Maybe Text
-> Maybe Text
-> Maybe Bool
-> Maybe Text
-> Maybe Text
-> Maybe Text
-> Maybe Text
-> Maybe Text
-> Maybe Text
-> Maybe [DBParameterGroupStatus]
-> Maybe [DBSecurityGroupMembership]
-> Maybe DBSubnetGroup
-> 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 Text
-> Maybe Int
-> Maybe Text
-> Maybe Bool
-> Maybe [OptionGroupMembership]
-> Maybe PendingModifiedValues
-> Maybe Bool
-> Maybe Text
-> Maybe Text
-> Maybe Text
-> Maybe Int
-> Maybe Bool
-> Maybe [Text]
-> Maybe [Text]
-> Maybe Text
-> Maybe Text
-> Maybe [DBInstanceStatusInfo]
-> Maybe Bool
-> Maybe Text
-> 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
"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
"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
"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
"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
"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
"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
"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
"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
"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
"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
"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
"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
"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
"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
"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
"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
"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 [DBInstanceStatusInfo]
Maybe [DBParameterGroupStatus]
Maybe [DBSecurityGroupMembership]
Maybe [DomainMembership]
Maybe [OptionGroupMembership]
Maybe [VpcSecurityGroupMembership]
Maybe Text
Maybe ISO8601
Maybe Endpoint
Maybe PendingModifiedValues
Maybe DBSubnetGroup
vpcSecurityGroups :: Maybe [VpcSecurityGroupMembership]
timezone :: Maybe Text
tdeCredentialArn :: Maybe Text
storageType :: Maybe Text
storageEncrypted :: Maybe Bool
statusInfos :: Maybe [DBInstanceStatusInfo]
secondaryAvailabilityZone :: Maybe Text
readReplicaSourceDBInstanceIdentifier :: Maybe Text
readReplicaDBInstanceIdentifiers :: Maybe [Text]
readReplicaDBClusterIdentifiers :: Maybe [Text]
publiclyAccessible :: Maybe Bool
promotionTier :: Maybe Int
preferredMaintenanceWindow :: Maybe Text
preferredBackupWindow :: Maybe Text
performanceInsightsKMSKeyId :: Maybe Text
performanceInsightsEnabled :: Maybe Bool
pendingModifiedValues :: Maybe PendingModifiedValues
optionGroupMemberships :: Maybe [OptionGroupMembership]
multiAZ :: Maybe Bool
monitoringRoleArn :: Maybe Text
monitoringInterval :: Maybe Int
masterUsername :: Maybe Text
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
dbSubnetGroup :: Maybe DBSubnetGroup
dbSecurityGroups :: Maybe [DBSecurityGroupMembership]
dbParameterGroups :: Maybe [DBParameterGroupStatus]
dbName :: Maybe Text
dbInstanceStatus :: Maybe Text
dbInstanceIdentifier :: Maybe Text
dbInstanceClass :: Maybe Text
dbInstanceArn :: Maybe Text
dbClusterIdentifier :: Maybe Text
copyTagsToSnapshot :: Maybe Bool
characterSetName :: Maybe Text
cACertificateIdentifier :: Maybe Text
backupRetentionPeriod :: Maybe Int
availabilityZone :: Maybe Text
autoMinorVersionUpgrade :: Maybe Bool
allocatedStorage :: Maybe Int
$sel:vpcSecurityGroups:DBInstance' :: DBInstance -> Maybe [VpcSecurityGroupMembership]
$sel:timezone:DBInstance' :: DBInstance -> Maybe Text
$sel:tdeCredentialArn:DBInstance' :: DBInstance -> Maybe Text
$sel:storageType:DBInstance' :: DBInstance -> Maybe Text
$sel:storageEncrypted:DBInstance' :: DBInstance -> Maybe Bool
$sel:statusInfos:DBInstance' :: DBInstance -> Maybe [DBInstanceStatusInfo]
$sel:secondaryAvailabilityZone:DBInstance' :: DBInstance -> Maybe Text
$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:preferredMaintenanceWindow:DBInstance' :: DBInstance -> Maybe Text
$sel:preferredBackupWindow:DBInstance' :: DBInstance -> Maybe Text
$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:multiAZ:DBInstance' :: DBInstance -> Maybe Bool
$sel:monitoringRoleArn:DBInstance' :: DBInstance -> Maybe Text
$sel:monitoringInterval:DBInstance' :: DBInstance -> Maybe Int
$sel:masterUsername:DBInstance' :: DBInstance -> Maybe Text
$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: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:dbInstanceArn:DBInstance' :: DBInstance -> Maybe Text
$sel:dbClusterIdentifier:DBInstance' :: DBInstance -> Maybe Text
$sel:copyTagsToSnapshot:DBInstance' :: DBInstance -> Maybe Bool
$sel:characterSetName:DBInstance' :: DBInstance -> Maybe Text
$sel:cACertificateIdentifier:DBInstance' :: DBInstance -> Maybe Text
$sel:backupRetentionPeriod:DBInstance' :: DBInstance -> Maybe Int
$sel:availabilityZone:DBInstance' :: DBInstance -> Maybe Text
$sel:autoMinorVersionUpgrade:DBInstance' :: DBInstance -> Maybe Bool
$sel:allocatedStorage:DBInstance' :: DBInstance -> Maybe Int
..} =
    Int
_salt
      forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Maybe Int
allocatedStorage
      forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Maybe Bool
autoMinorVersionUpgrade
      forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Maybe Text
availabilityZone
      forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Maybe Int
backupRetentionPeriod
      forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Maybe Text
cACertificateIdentifier
      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
dbClusterIdentifier
      forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Maybe Text
dbInstanceArn
      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 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 Text
masterUsername
      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 [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 Text
preferredBackupWindow
      forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Maybe Text
preferredMaintenanceWindow
      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 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 Text
storageType
      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 [DBInstanceStatusInfo]
Maybe [DBParameterGroupStatus]
Maybe [DBSecurityGroupMembership]
Maybe [DomainMembership]
Maybe [OptionGroupMembership]
Maybe [VpcSecurityGroupMembership]
Maybe Text
Maybe ISO8601
Maybe Endpoint
Maybe PendingModifiedValues
Maybe DBSubnetGroup
vpcSecurityGroups :: Maybe [VpcSecurityGroupMembership]
timezone :: Maybe Text
tdeCredentialArn :: Maybe Text
storageType :: Maybe Text
storageEncrypted :: Maybe Bool
statusInfos :: Maybe [DBInstanceStatusInfo]
secondaryAvailabilityZone :: Maybe Text
readReplicaSourceDBInstanceIdentifier :: Maybe Text
readReplicaDBInstanceIdentifiers :: Maybe [Text]
readReplicaDBClusterIdentifiers :: Maybe [Text]
publiclyAccessible :: Maybe Bool
promotionTier :: Maybe Int
preferredMaintenanceWindow :: Maybe Text
preferredBackupWindow :: Maybe Text
performanceInsightsKMSKeyId :: Maybe Text
performanceInsightsEnabled :: Maybe Bool
pendingModifiedValues :: Maybe PendingModifiedValues
optionGroupMemberships :: Maybe [OptionGroupMembership]
multiAZ :: Maybe Bool
monitoringRoleArn :: Maybe Text
monitoringInterval :: Maybe Int
masterUsername :: Maybe Text
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
dbSubnetGroup :: Maybe DBSubnetGroup
dbSecurityGroups :: Maybe [DBSecurityGroupMembership]
dbParameterGroups :: Maybe [DBParameterGroupStatus]
dbName :: Maybe Text
dbInstanceStatus :: Maybe Text
dbInstanceIdentifier :: Maybe Text
dbInstanceClass :: Maybe Text
dbInstanceArn :: Maybe Text
dbClusterIdentifier :: Maybe Text
copyTagsToSnapshot :: Maybe Bool
characterSetName :: Maybe Text
cACertificateIdentifier :: Maybe Text
backupRetentionPeriod :: Maybe Int
availabilityZone :: Maybe Text
autoMinorVersionUpgrade :: Maybe Bool
allocatedStorage :: Maybe Int
$sel:vpcSecurityGroups:DBInstance' :: DBInstance -> Maybe [VpcSecurityGroupMembership]
$sel:timezone:DBInstance' :: DBInstance -> Maybe Text
$sel:tdeCredentialArn:DBInstance' :: DBInstance -> Maybe Text
$sel:storageType:DBInstance' :: DBInstance -> Maybe Text
$sel:storageEncrypted:DBInstance' :: DBInstance -> Maybe Bool
$sel:statusInfos:DBInstance' :: DBInstance -> Maybe [DBInstanceStatusInfo]
$sel:secondaryAvailabilityZone:DBInstance' :: DBInstance -> Maybe Text
$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:preferredMaintenanceWindow:DBInstance' :: DBInstance -> Maybe Text
$sel:preferredBackupWindow:DBInstance' :: DBInstance -> Maybe Text
$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:multiAZ:DBInstance' :: DBInstance -> Maybe Bool
$sel:monitoringRoleArn:DBInstance' :: DBInstance -> Maybe Text
$sel:monitoringInterval:DBInstance' :: DBInstance -> Maybe Int
$sel:masterUsername:DBInstance' :: DBInstance -> Maybe Text
$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: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:dbInstanceArn:DBInstance' :: DBInstance -> Maybe Text
$sel:dbClusterIdentifier:DBInstance' :: DBInstance -> Maybe Text
$sel:copyTagsToSnapshot:DBInstance' :: DBInstance -> Maybe Bool
$sel:characterSetName:DBInstance' :: DBInstance -> Maybe Text
$sel:cACertificateIdentifier:DBInstance' :: DBInstance -> Maybe Text
$sel:backupRetentionPeriod:DBInstance' :: DBInstance -> Maybe Int
$sel:availabilityZone:DBInstance' :: DBInstance -> Maybe Text
$sel:autoMinorVersionUpgrade:DBInstance' :: DBInstance -> Maybe Bool
$sel:allocatedStorage:DBInstance' :: DBInstance -> Maybe Int
..} =
    forall a. NFData a => a -> ()
Prelude.rnf Maybe Int
allocatedStorage
      seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf Maybe Bool
autoMinorVersionUpgrade
      seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf Maybe Text
availabilityZone
      seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf Maybe Int
backupRetentionPeriod
      seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf Maybe Text
cACertificateIdentifier
      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
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 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 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 Text
masterUsername
      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 [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 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 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 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 Text
storageType
      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