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

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

-- |
-- Module      : Amazonka.RDS.Types.DBSnapshot
-- Copyright   : (c) 2013-2023 Brendan Hay
-- License     : Mozilla Public License, v. 2.0.
-- Maintainer  : Brendan Hay
-- Stability   : auto-generated
-- Portability : non-portable (GHC extensions)
module Amazonka.RDS.Types.DBSnapshot where

import qualified Amazonka.Core as Core
import qualified Amazonka.Core.Lens.Internal as Lens
import qualified Amazonka.Data as Data
import qualified Amazonka.Prelude as Prelude
import Amazonka.RDS.Types.ProcessorFeature
import Amazonka.RDS.Types.Tag

-- | Contains the details of an Amazon RDS DB snapshot.
--
-- This data type is used as a response element in the
-- @DescribeDBSnapshots@ action.
--
-- /See:/ 'newDBSnapshot' smart constructor.
data DBSnapshot = DBSnapshot'
  { -- | Specifies the allocated storage size in gibibytes (GiB).
    DBSnapshot -> Maybe Int
allocatedStorage :: Prelude.Maybe Prelude.Int,
    -- | Specifies the name of the Availability Zone the DB instance was located
    -- in at the time of the DB snapshot.
    DBSnapshot -> Maybe Text
availabilityZone :: Prelude.Maybe Prelude.Text,
    -- | Specifies the DB instance identifier of the DB instance this DB snapshot
    -- was created from.
    DBSnapshot -> Maybe Text
dbInstanceIdentifier :: Prelude.Maybe Prelude.Text,
    -- | The Amazon Resource Name (ARN) for the DB snapshot.
    DBSnapshot -> Maybe Text
dbSnapshotArn :: Prelude.Maybe Prelude.Text,
    -- | Specifies the identifier for the DB snapshot.
    DBSnapshot -> Maybe Text
dbSnapshotIdentifier :: Prelude.Maybe Prelude.Text,
    -- | The identifier for the source DB instance, which can\'t be changed and
    -- which is unique to an Amazon Web Services Region.
    DBSnapshot -> Maybe Text
dbiResourceId :: Prelude.Maybe Prelude.Text,
    -- | Specifies whether the DB snapshot is encrypted.
    DBSnapshot -> Maybe Bool
encrypted :: Prelude.Maybe Prelude.Bool,
    -- | Specifies the name of the database engine.
    DBSnapshot -> Maybe Text
engine :: Prelude.Maybe Prelude.Text,
    -- | Specifies the version of the database engine.
    DBSnapshot -> Maybe Text
engineVersion :: Prelude.Maybe Prelude.Text,
    -- | True if mapping of Amazon Web Services Identity and Access Management
    -- (IAM) accounts to database accounts is enabled, and otherwise false.
    DBSnapshot -> Maybe Bool
iAMDatabaseAuthenticationEnabled :: Prelude.Maybe Prelude.Bool,
    -- | Specifies the time in Coordinated Universal Time (UTC) when the DB
    -- instance, from which the snapshot was taken, was created.
    DBSnapshot -> Maybe ISO8601
instanceCreateTime :: Prelude.Maybe Data.ISO8601,
    -- | Specifies the Provisioned IOPS (I\/O operations per second) value of the
    -- DB instance at the time of the snapshot.
    DBSnapshot -> Maybe Int
iops :: Prelude.Maybe Prelude.Int,
    -- | If @Encrypted@ is true, the Amazon Web Services KMS key identifier for
    -- the encrypted DB snapshot.
    --
    -- The Amazon Web Services KMS key identifier is the key ARN, key ID, alias
    -- ARN, or alias name for the KMS key.
    DBSnapshot -> Maybe Text
kmsKeyId :: Prelude.Maybe Prelude.Text,
    -- | License model information for the restored DB instance.
    DBSnapshot -> Maybe Text
licenseModel :: Prelude.Maybe Prelude.Text,
    -- | Provides the master username for the DB snapshot.
    DBSnapshot -> Maybe Text
masterUsername :: Prelude.Maybe Prelude.Text,
    -- | Provides the option group name for the DB snapshot.
    DBSnapshot -> Maybe Text
optionGroupName :: Prelude.Maybe Prelude.Text,
    -- | Specifies the time of the CreateDBSnapshot operation in Coordinated
    -- Universal Time (UTC). Doesn\'t change when the snapshot is copied.
    DBSnapshot -> Maybe ISO8601
originalSnapshotCreateTime :: Prelude.Maybe Data.ISO8601,
    -- | The percentage of the estimated data that has been transferred.
    DBSnapshot -> Maybe Int
percentProgress :: Prelude.Maybe Prelude.Int,
    -- | Specifies the port that the database engine was listening on at the time
    -- of the snapshot.
    DBSnapshot -> Maybe Int
port :: Prelude.Maybe Prelude.Int,
    -- | The number of CPU cores and the number of threads per core for the DB
    -- instance class of the DB instance when the DB snapshot was created.
    DBSnapshot -> Maybe [ProcessorFeature]
processorFeatures :: Prelude.Maybe [ProcessorFeature],
    -- | Specifies when the snapshot was taken in Coordinated Universal Time
    -- (UTC). Changes for the copy when the snapshot is copied.
    DBSnapshot -> Maybe ISO8601
snapshotCreateTime :: Prelude.Maybe Data.ISO8601,
    -- | The timestamp of the most recent transaction applied to the database
    -- that you\'re backing up. Thus, if you restore a snapshot,
    -- SnapshotDatabaseTime is the most recent transaction in the restored DB
    -- instance. In contrast, originalSnapshotCreateTime specifies the system
    -- time that the snapshot completed.
    --
    -- If you back up a read replica, you can determine the replica lag by
    -- comparing SnapshotDatabaseTime with originalSnapshotCreateTime. For
    -- example, if originalSnapshotCreateTime is two hours later than
    -- SnapshotDatabaseTime, then the replica lag is two hours.
    DBSnapshot -> Maybe ISO8601
snapshotDatabaseTime :: Prelude.Maybe Data.ISO8601,
    -- | Specifies where manual snapshots are stored: Amazon Web Services
    -- Outposts or the Amazon Web Services Region.
    DBSnapshot -> Maybe Text
snapshotTarget :: Prelude.Maybe Prelude.Text,
    -- | Provides the type of the DB snapshot.
    DBSnapshot -> Maybe Text
snapshotType :: Prelude.Maybe Prelude.Text,
    -- | The DB snapshot Amazon Resource Name (ARN) that the DB snapshot was
    -- copied from. It only has a value in the case of a cross-account or
    -- cross-Region copy.
    DBSnapshot -> Maybe Text
sourceDBSnapshotIdentifier :: Prelude.Maybe Prelude.Text,
    -- | The Amazon Web Services Region that the DB snapshot was created in or
    -- copied from.
    DBSnapshot -> Maybe Text
sourceRegion :: Prelude.Maybe Prelude.Text,
    -- | Specifies the status of this DB snapshot.
    DBSnapshot -> Maybe Text
status :: Prelude.Maybe Prelude.Text,
    -- | Specifies the storage throughput for the DB snapshot.
    DBSnapshot -> Maybe Int
storageThroughput :: Prelude.Maybe Prelude.Int,
    -- | Specifies the storage type associated with DB snapshot.
    DBSnapshot -> Maybe Text
storageType :: Prelude.Maybe Prelude.Text,
    DBSnapshot -> Maybe [Tag]
tagList :: Prelude.Maybe [Tag],
    -- | The ARN from the key store with which to associate the instance for TDE
    -- encryption.
    DBSnapshot -> Maybe Text
tdeCredentialArn :: Prelude.Maybe Prelude.Text,
    -- | The time zone of the DB snapshot. In most cases, the @Timezone@ element
    -- is empty. @Timezone@ content appears only for snapshots taken from
    -- Microsoft SQL Server DB instances that were created with a time zone
    -- specified.
    DBSnapshot -> Maybe Text
timezone :: Prelude.Maybe Prelude.Text,
    -- | Provides the VPC ID associated with the DB snapshot.
    DBSnapshot -> Maybe Text
vpcId :: Prelude.Maybe Prelude.Text
  }
  deriving (DBSnapshot -> DBSnapshot -> Bool
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: DBSnapshot -> DBSnapshot -> Bool
$c/= :: DBSnapshot -> DBSnapshot -> Bool
== :: DBSnapshot -> DBSnapshot -> Bool
$c== :: DBSnapshot -> DBSnapshot -> Bool
Prelude.Eq, ReadPrec [DBSnapshot]
ReadPrec DBSnapshot
Int -> ReadS DBSnapshot
ReadS [DBSnapshot]
forall a.
(Int -> ReadS a)
-> ReadS [a] -> ReadPrec a -> ReadPrec [a] -> Read a
readListPrec :: ReadPrec [DBSnapshot]
$creadListPrec :: ReadPrec [DBSnapshot]
readPrec :: ReadPrec DBSnapshot
$creadPrec :: ReadPrec DBSnapshot
readList :: ReadS [DBSnapshot]
$creadList :: ReadS [DBSnapshot]
readsPrec :: Int -> ReadS DBSnapshot
$creadsPrec :: Int -> ReadS DBSnapshot
Prelude.Read, Int -> DBSnapshot -> ShowS
[DBSnapshot] -> ShowS
DBSnapshot -> String
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [DBSnapshot] -> ShowS
$cshowList :: [DBSnapshot] -> ShowS
show :: DBSnapshot -> String
$cshow :: DBSnapshot -> String
showsPrec :: Int -> DBSnapshot -> ShowS
$cshowsPrec :: Int -> DBSnapshot -> ShowS
Prelude.Show, forall x. Rep DBSnapshot x -> DBSnapshot
forall x. DBSnapshot -> Rep DBSnapshot x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cto :: forall x. Rep DBSnapshot x -> DBSnapshot
$cfrom :: forall x. DBSnapshot -> Rep DBSnapshot x
Prelude.Generic)

-- |
-- Create a value of 'DBSnapshot' 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', 'dbSnapshot_allocatedStorage' - Specifies the allocated storage size in gibibytes (GiB).
--
-- 'availabilityZone', 'dbSnapshot_availabilityZone' - Specifies the name of the Availability Zone the DB instance was located
-- in at the time of the DB snapshot.
--
-- 'dbInstanceIdentifier', 'dbSnapshot_dbInstanceIdentifier' - Specifies the DB instance identifier of the DB instance this DB snapshot
-- was created from.
--
-- 'dbSnapshotArn', 'dbSnapshot_dbSnapshotArn' - The Amazon Resource Name (ARN) for the DB snapshot.
--
-- 'dbSnapshotIdentifier', 'dbSnapshot_dbSnapshotIdentifier' - Specifies the identifier for the DB snapshot.
--
-- 'dbiResourceId', 'dbSnapshot_dbiResourceId' - The identifier for the source DB instance, which can\'t be changed and
-- which is unique to an Amazon Web Services Region.
--
-- 'encrypted', 'dbSnapshot_encrypted' - Specifies whether the DB snapshot is encrypted.
--
-- 'engine', 'dbSnapshot_engine' - Specifies the name of the database engine.
--
-- 'engineVersion', 'dbSnapshot_engineVersion' - Specifies the version of the database engine.
--
-- 'iAMDatabaseAuthenticationEnabled', 'dbSnapshot_iAMDatabaseAuthenticationEnabled' - True if mapping of Amazon Web Services Identity and Access Management
-- (IAM) accounts to database accounts is enabled, and otherwise false.
--
-- 'instanceCreateTime', 'dbSnapshot_instanceCreateTime' - Specifies the time in Coordinated Universal Time (UTC) when the DB
-- instance, from which the snapshot was taken, was created.
--
-- 'iops', 'dbSnapshot_iops' - Specifies the Provisioned IOPS (I\/O operations per second) value of the
-- DB instance at the time of the snapshot.
--
-- 'kmsKeyId', 'dbSnapshot_kmsKeyId' - If @Encrypted@ is true, the Amazon Web Services KMS key identifier for
-- the encrypted DB snapshot.
--
-- The Amazon Web Services KMS key identifier is the key ARN, key ID, alias
-- ARN, or alias name for the KMS key.
--
-- 'licenseModel', 'dbSnapshot_licenseModel' - License model information for the restored DB instance.
--
-- 'masterUsername', 'dbSnapshot_masterUsername' - Provides the master username for the DB snapshot.
--
-- 'optionGroupName', 'dbSnapshot_optionGroupName' - Provides the option group name for the DB snapshot.
--
-- 'originalSnapshotCreateTime', 'dbSnapshot_originalSnapshotCreateTime' - Specifies the time of the CreateDBSnapshot operation in Coordinated
-- Universal Time (UTC). Doesn\'t change when the snapshot is copied.
--
-- 'percentProgress', 'dbSnapshot_percentProgress' - The percentage of the estimated data that has been transferred.
--
-- 'port', 'dbSnapshot_port' - Specifies the port that the database engine was listening on at the time
-- of the snapshot.
--
-- 'processorFeatures', 'dbSnapshot_processorFeatures' - The number of CPU cores and the number of threads per core for the DB
-- instance class of the DB instance when the DB snapshot was created.
--
-- 'snapshotCreateTime', 'dbSnapshot_snapshotCreateTime' - Specifies when the snapshot was taken in Coordinated Universal Time
-- (UTC). Changes for the copy when the snapshot is copied.
--
-- 'snapshotDatabaseTime', 'dbSnapshot_snapshotDatabaseTime' - The timestamp of the most recent transaction applied to the database
-- that you\'re backing up. Thus, if you restore a snapshot,
-- SnapshotDatabaseTime is the most recent transaction in the restored DB
-- instance. In contrast, originalSnapshotCreateTime specifies the system
-- time that the snapshot completed.
--
-- If you back up a read replica, you can determine the replica lag by
-- comparing SnapshotDatabaseTime with originalSnapshotCreateTime. For
-- example, if originalSnapshotCreateTime is two hours later than
-- SnapshotDatabaseTime, then the replica lag is two hours.
--
-- 'snapshotTarget', 'dbSnapshot_snapshotTarget' - Specifies where manual snapshots are stored: Amazon Web Services
-- Outposts or the Amazon Web Services Region.
--
-- 'snapshotType', 'dbSnapshot_snapshotType' - Provides the type of the DB snapshot.
--
-- 'sourceDBSnapshotIdentifier', 'dbSnapshot_sourceDBSnapshotIdentifier' - The DB snapshot Amazon Resource Name (ARN) that the DB snapshot was
-- copied from. It only has a value in the case of a cross-account or
-- cross-Region copy.
--
-- 'sourceRegion', 'dbSnapshot_sourceRegion' - The Amazon Web Services Region that the DB snapshot was created in or
-- copied from.
--
-- 'status', 'dbSnapshot_status' - Specifies the status of this DB snapshot.
--
-- 'storageThroughput', 'dbSnapshot_storageThroughput' - Specifies the storage throughput for the DB snapshot.
--
-- 'storageType', 'dbSnapshot_storageType' - Specifies the storage type associated with DB snapshot.
--
-- 'tagList', 'dbSnapshot_tagList' - Undocumented member.
--
-- 'tdeCredentialArn', 'dbSnapshot_tdeCredentialArn' - The ARN from the key store with which to associate the instance for TDE
-- encryption.
--
-- 'timezone', 'dbSnapshot_timezone' - The time zone of the DB snapshot. In most cases, the @Timezone@ element
-- is empty. @Timezone@ content appears only for snapshots taken from
-- Microsoft SQL Server DB instances that were created with a time zone
-- specified.
--
-- 'vpcId', 'dbSnapshot_vpcId' - Provides the VPC ID associated with the DB snapshot.
newDBSnapshot ::
  DBSnapshot
newDBSnapshot :: DBSnapshot
newDBSnapshot =
  DBSnapshot'
    { $sel:allocatedStorage:DBSnapshot' :: Maybe Int
allocatedStorage = forall a. Maybe a
Prelude.Nothing,
      $sel:availabilityZone:DBSnapshot' :: Maybe Text
availabilityZone = forall a. Maybe a
Prelude.Nothing,
      $sel:dbInstanceIdentifier:DBSnapshot' :: Maybe Text
dbInstanceIdentifier = forall a. Maybe a
Prelude.Nothing,
      $sel:dbSnapshotArn:DBSnapshot' :: Maybe Text
dbSnapshotArn = forall a. Maybe a
Prelude.Nothing,
      $sel:dbSnapshotIdentifier:DBSnapshot' :: Maybe Text
dbSnapshotIdentifier = forall a. Maybe a
Prelude.Nothing,
      $sel:dbiResourceId:DBSnapshot' :: Maybe Text
dbiResourceId = forall a. Maybe a
Prelude.Nothing,
      $sel:encrypted:DBSnapshot' :: Maybe Bool
encrypted = forall a. Maybe a
Prelude.Nothing,
      $sel:engine:DBSnapshot' :: Maybe Text
engine = forall a. Maybe a
Prelude.Nothing,
      $sel:engineVersion:DBSnapshot' :: Maybe Text
engineVersion = forall a. Maybe a
Prelude.Nothing,
      $sel:iAMDatabaseAuthenticationEnabled:DBSnapshot' :: Maybe Bool
iAMDatabaseAuthenticationEnabled = forall a. Maybe a
Prelude.Nothing,
      $sel:instanceCreateTime:DBSnapshot' :: Maybe ISO8601
instanceCreateTime = forall a. Maybe a
Prelude.Nothing,
      $sel:iops:DBSnapshot' :: Maybe Int
iops = forall a. Maybe a
Prelude.Nothing,
      $sel:kmsKeyId:DBSnapshot' :: Maybe Text
kmsKeyId = forall a. Maybe a
Prelude.Nothing,
      $sel:licenseModel:DBSnapshot' :: Maybe Text
licenseModel = forall a. Maybe a
Prelude.Nothing,
      $sel:masterUsername:DBSnapshot' :: Maybe Text
masterUsername = forall a. Maybe a
Prelude.Nothing,
      $sel:optionGroupName:DBSnapshot' :: Maybe Text
optionGroupName = forall a. Maybe a
Prelude.Nothing,
      $sel:originalSnapshotCreateTime:DBSnapshot' :: Maybe ISO8601
originalSnapshotCreateTime = forall a. Maybe a
Prelude.Nothing,
      $sel:percentProgress:DBSnapshot' :: Maybe Int
percentProgress = forall a. Maybe a
Prelude.Nothing,
      $sel:port:DBSnapshot' :: Maybe Int
port = forall a. Maybe a
Prelude.Nothing,
      $sel:processorFeatures:DBSnapshot' :: Maybe [ProcessorFeature]
processorFeatures = forall a. Maybe a
Prelude.Nothing,
      $sel:snapshotCreateTime:DBSnapshot' :: Maybe ISO8601
snapshotCreateTime = forall a. Maybe a
Prelude.Nothing,
      $sel:snapshotDatabaseTime:DBSnapshot' :: Maybe ISO8601
snapshotDatabaseTime = forall a. Maybe a
Prelude.Nothing,
      $sel:snapshotTarget:DBSnapshot' :: Maybe Text
snapshotTarget = forall a. Maybe a
Prelude.Nothing,
      $sel:snapshotType:DBSnapshot' :: Maybe Text
snapshotType = forall a. Maybe a
Prelude.Nothing,
      $sel:sourceDBSnapshotIdentifier:DBSnapshot' :: Maybe Text
sourceDBSnapshotIdentifier = forall a. Maybe a
Prelude.Nothing,
      $sel:sourceRegion:DBSnapshot' :: Maybe Text
sourceRegion = forall a. Maybe a
Prelude.Nothing,
      $sel:status:DBSnapshot' :: Maybe Text
status = forall a. Maybe a
Prelude.Nothing,
      $sel:storageThroughput:DBSnapshot' :: Maybe Int
storageThroughput = forall a. Maybe a
Prelude.Nothing,
      $sel:storageType:DBSnapshot' :: Maybe Text
storageType = forall a. Maybe a
Prelude.Nothing,
      $sel:tagList:DBSnapshot' :: Maybe [Tag]
tagList = forall a. Maybe a
Prelude.Nothing,
      $sel:tdeCredentialArn:DBSnapshot' :: Maybe Text
tdeCredentialArn = forall a. Maybe a
Prelude.Nothing,
      $sel:timezone:DBSnapshot' :: Maybe Text
timezone = forall a. Maybe a
Prelude.Nothing,
      $sel:vpcId:DBSnapshot' :: Maybe Text
vpcId = forall a. Maybe a
Prelude.Nothing
    }

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

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

-- | Specifies the DB instance identifier of the DB instance this DB snapshot
-- was created from.
dbSnapshot_dbInstanceIdentifier :: Lens.Lens' DBSnapshot (Prelude.Maybe Prelude.Text)
dbSnapshot_dbInstanceIdentifier :: Lens' DBSnapshot (Maybe Text)
dbSnapshot_dbInstanceIdentifier = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\DBSnapshot' {Maybe Text
dbInstanceIdentifier :: Maybe Text
$sel:dbInstanceIdentifier:DBSnapshot' :: DBSnapshot -> Maybe Text
dbInstanceIdentifier} -> Maybe Text
dbInstanceIdentifier) (\s :: DBSnapshot
s@DBSnapshot' {} Maybe Text
a -> DBSnapshot
s {$sel:dbInstanceIdentifier:DBSnapshot' :: Maybe Text
dbInstanceIdentifier = Maybe Text
a} :: DBSnapshot)

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

-- | Specifies the identifier for the DB snapshot.
dbSnapshot_dbSnapshotIdentifier :: Lens.Lens' DBSnapshot (Prelude.Maybe Prelude.Text)
dbSnapshot_dbSnapshotIdentifier :: Lens' DBSnapshot (Maybe Text)
dbSnapshot_dbSnapshotIdentifier = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\DBSnapshot' {Maybe Text
dbSnapshotIdentifier :: Maybe Text
$sel:dbSnapshotIdentifier:DBSnapshot' :: DBSnapshot -> Maybe Text
dbSnapshotIdentifier} -> Maybe Text
dbSnapshotIdentifier) (\s :: DBSnapshot
s@DBSnapshot' {} Maybe Text
a -> DBSnapshot
s {$sel:dbSnapshotIdentifier:DBSnapshot' :: Maybe Text
dbSnapshotIdentifier = Maybe Text
a} :: DBSnapshot)

-- | The identifier for the source DB instance, which can\'t be changed and
-- which is unique to an Amazon Web Services Region.
dbSnapshot_dbiResourceId :: Lens.Lens' DBSnapshot (Prelude.Maybe Prelude.Text)
dbSnapshot_dbiResourceId :: Lens' DBSnapshot (Maybe Text)
dbSnapshot_dbiResourceId = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\DBSnapshot' {Maybe Text
dbiResourceId :: Maybe Text
$sel:dbiResourceId:DBSnapshot' :: DBSnapshot -> Maybe Text
dbiResourceId} -> Maybe Text
dbiResourceId) (\s :: DBSnapshot
s@DBSnapshot' {} Maybe Text
a -> DBSnapshot
s {$sel:dbiResourceId:DBSnapshot' :: Maybe Text
dbiResourceId = Maybe Text
a} :: DBSnapshot)

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

-- | Specifies the name of the database engine.
dbSnapshot_engine :: Lens.Lens' DBSnapshot (Prelude.Maybe Prelude.Text)
dbSnapshot_engine :: Lens' DBSnapshot (Maybe Text)
dbSnapshot_engine = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\DBSnapshot' {Maybe Text
engine :: Maybe Text
$sel:engine:DBSnapshot' :: DBSnapshot -> Maybe Text
engine} -> Maybe Text
engine) (\s :: DBSnapshot
s@DBSnapshot' {} Maybe Text
a -> DBSnapshot
s {$sel:engine:DBSnapshot' :: Maybe Text
engine = Maybe Text
a} :: DBSnapshot)

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

-- | True if mapping of Amazon Web Services Identity and Access Management
-- (IAM) accounts to database accounts is enabled, and otherwise false.
dbSnapshot_iAMDatabaseAuthenticationEnabled :: Lens.Lens' DBSnapshot (Prelude.Maybe Prelude.Bool)
dbSnapshot_iAMDatabaseAuthenticationEnabled :: Lens' DBSnapshot (Maybe Bool)
dbSnapshot_iAMDatabaseAuthenticationEnabled = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\DBSnapshot' {Maybe Bool
iAMDatabaseAuthenticationEnabled :: Maybe Bool
$sel:iAMDatabaseAuthenticationEnabled:DBSnapshot' :: DBSnapshot -> Maybe Bool
iAMDatabaseAuthenticationEnabled} -> Maybe Bool
iAMDatabaseAuthenticationEnabled) (\s :: DBSnapshot
s@DBSnapshot' {} Maybe Bool
a -> DBSnapshot
s {$sel:iAMDatabaseAuthenticationEnabled:DBSnapshot' :: Maybe Bool
iAMDatabaseAuthenticationEnabled = Maybe Bool
a} :: DBSnapshot)

-- | Specifies the time in Coordinated Universal Time (UTC) when the DB
-- instance, from which the snapshot was taken, was created.
dbSnapshot_instanceCreateTime :: Lens.Lens' DBSnapshot (Prelude.Maybe Prelude.UTCTime)
dbSnapshot_instanceCreateTime :: Lens' DBSnapshot (Maybe UTCTime)
dbSnapshot_instanceCreateTime = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\DBSnapshot' {Maybe ISO8601
instanceCreateTime :: Maybe ISO8601
$sel:instanceCreateTime:DBSnapshot' :: DBSnapshot -> Maybe ISO8601
instanceCreateTime} -> Maybe ISO8601
instanceCreateTime) (\s :: DBSnapshot
s@DBSnapshot' {} Maybe ISO8601
a -> DBSnapshot
s {$sel:instanceCreateTime:DBSnapshot' :: Maybe ISO8601
instanceCreateTime = Maybe ISO8601
a} :: DBSnapshot) 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 of the
-- DB instance at the time of the snapshot.
dbSnapshot_iops :: Lens.Lens' DBSnapshot (Prelude.Maybe Prelude.Int)
dbSnapshot_iops :: Lens' DBSnapshot (Maybe Int)
dbSnapshot_iops = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\DBSnapshot' {Maybe Int
iops :: Maybe Int
$sel:iops:DBSnapshot' :: DBSnapshot -> Maybe Int
iops} -> Maybe Int
iops) (\s :: DBSnapshot
s@DBSnapshot' {} Maybe Int
a -> DBSnapshot
s {$sel:iops:DBSnapshot' :: Maybe Int
iops = Maybe Int
a} :: DBSnapshot)

-- | If @Encrypted@ is true, the Amazon Web Services KMS key identifier for
-- the encrypted DB snapshot.
--
-- The Amazon Web Services KMS key identifier is the key ARN, key ID, alias
-- ARN, or alias name for the KMS key.
dbSnapshot_kmsKeyId :: Lens.Lens' DBSnapshot (Prelude.Maybe Prelude.Text)
dbSnapshot_kmsKeyId :: Lens' DBSnapshot (Maybe Text)
dbSnapshot_kmsKeyId = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\DBSnapshot' {Maybe Text
kmsKeyId :: Maybe Text
$sel:kmsKeyId:DBSnapshot' :: DBSnapshot -> Maybe Text
kmsKeyId} -> Maybe Text
kmsKeyId) (\s :: DBSnapshot
s@DBSnapshot' {} Maybe Text
a -> DBSnapshot
s {$sel:kmsKeyId:DBSnapshot' :: Maybe Text
kmsKeyId = Maybe Text
a} :: DBSnapshot)

-- | License model information for the restored DB instance.
dbSnapshot_licenseModel :: Lens.Lens' DBSnapshot (Prelude.Maybe Prelude.Text)
dbSnapshot_licenseModel :: Lens' DBSnapshot (Maybe Text)
dbSnapshot_licenseModel = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\DBSnapshot' {Maybe Text
licenseModel :: Maybe Text
$sel:licenseModel:DBSnapshot' :: DBSnapshot -> Maybe Text
licenseModel} -> Maybe Text
licenseModel) (\s :: DBSnapshot
s@DBSnapshot' {} Maybe Text
a -> DBSnapshot
s {$sel:licenseModel:DBSnapshot' :: Maybe Text
licenseModel = Maybe Text
a} :: DBSnapshot)

-- | Provides the master username for the DB snapshot.
dbSnapshot_masterUsername :: Lens.Lens' DBSnapshot (Prelude.Maybe Prelude.Text)
dbSnapshot_masterUsername :: Lens' DBSnapshot (Maybe Text)
dbSnapshot_masterUsername = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\DBSnapshot' {Maybe Text
masterUsername :: Maybe Text
$sel:masterUsername:DBSnapshot' :: DBSnapshot -> Maybe Text
masterUsername} -> Maybe Text
masterUsername) (\s :: DBSnapshot
s@DBSnapshot' {} Maybe Text
a -> DBSnapshot
s {$sel:masterUsername:DBSnapshot' :: Maybe Text
masterUsername = Maybe Text
a} :: DBSnapshot)

-- | Provides the option group name for the DB snapshot.
dbSnapshot_optionGroupName :: Lens.Lens' DBSnapshot (Prelude.Maybe Prelude.Text)
dbSnapshot_optionGroupName :: Lens' DBSnapshot (Maybe Text)
dbSnapshot_optionGroupName = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\DBSnapshot' {Maybe Text
optionGroupName :: Maybe Text
$sel:optionGroupName:DBSnapshot' :: DBSnapshot -> Maybe Text
optionGroupName} -> Maybe Text
optionGroupName) (\s :: DBSnapshot
s@DBSnapshot' {} Maybe Text
a -> DBSnapshot
s {$sel:optionGroupName:DBSnapshot' :: Maybe Text
optionGroupName = Maybe Text
a} :: DBSnapshot)

-- | Specifies the time of the CreateDBSnapshot operation in Coordinated
-- Universal Time (UTC). Doesn\'t change when the snapshot is copied.
dbSnapshot_originalSnapshotCreateTime :: Lens.Lens' DBSnapshot (Prelude.Maybe Prelude.UTCTime)
dbSnapshot_originalSnapshotCreateTime :: Lens' DBSnapshot (Maybe UTCTime)
dbSnapshot_originalSnapshotCreateTime = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\DBSnapshot' {Maybe ISO8601
originalSnapshotCreateTime :: Maybe ISO8601
$sel:originalSnapshotCreateTime:DBSnapshot' :: DBSnapshot -> Maybe ISO8601
originalSnapshotCreateTime} -> Maybe ISO8601
originalSnapshotCreateTime) (\s :: DBSnapshot
s@DBSnapshot' {} Maybe ISO8601
a -> DBSnapshot
s {$sel:originalSnapshotCreateTime:DBSnapshot' :: Maybe ISO8601
originalSnapshotCreateTime = Maybe ISO8601
a} :: DBSnapshot) forall b c a. (b -> c) -> (a -> b) -> a -> c
Prelude.. forall (f :: * -> *) (g :: * -> *) s t a b.
(Functor f, Functor g) =>
AnIso s t a b -> Iso (f s) (g t) (f a) (g b)
Lens.mapping forall (a :: Format). Iso' (Time a) UTCTime
Data._Time

-- | The percentage of the estimated data that has been transferred.
dbSnapshot_percentProgress :: Lens.Lens' DBSnapshot (Prelude.Maybe Prelude.Int)
dbSnapshot_percentProgress :: Lens' DBSnapshot (Maybe Int)
dbSnapshot_percentProgress = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\DBSnapshot' {Maybe Int
percentProgress :: Maybe Int
$sel:percentProgress:DBSnapshot' :: DBSnapshot -> Maybe Int
percentProgress} -> Maybe Int
percentProgress) (\s :: DBSnapshot
s@DBSnapshot' {} Maybe Int
a -> DBSnapshot
s {$sel:percentProgress:DBSnapshot' :: Maybe Int
percentProgress = Maybe Int
a} :: DBSnapshot)

-- | Specifies the port that the database engine was listening on at the time
-- of the snapshot.
dbSnapshot_port :: Lens.Lens' DBSnapshot (Prelude.Maybe Prelude.Int)
dbSnapshot_port :: Lens' DBSnapshot (Maybe Int)
dbSnapshot_port = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\DBSnapshot' {Maybe Int
port :: Maybe Int
$sel:port:DBSnapshot' :: DBSnapshot -> Maybe Int
port} -> Maybe Int
port) (\s :: DBSnapshot
s@DBSnapshot' {} Maybe Int
a -> DBSnapshot
s {$sel:port:DBSnapshot' :: Maybe Int
port = Maybe Int
a} :: DBSnapshot)

-- | The number of CPU cores and the number of threads per core for the DB
-- instance class of the DB instance when the DB snapshot was created.
dbSnapshot_processorFeatures :: Lens.Lens' DBSnapshot (Prelude.Maybe [ProcessorFeature])
dbSnapshot_processorFeatures :: Lens' DBSnapshot (Maybe [ProcessorFeature])
dbSnapshot_processorFeatures = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\DBSnapshot' {Maybe [ProcessorFeature]
processorFeatures :: Maybe [ProcessorFeature]
$sel:processorFeatures:DBSnapshot' :: DBSnapshot -> Maybe [ProcessorFeature]
processorFeatures} -> Maybe [ProcessorFeature]
processorFeatures) (\s :: DBSnapshot
s@DBSnapshot' {} Maybe [ProcessorFeature]
a -> DBSnapshot
s {$sel:processorFeatures:DBSnapshot' :: Maybe [ProcessorFeature]
processorFeatures = Maybe [ProcessorFeature]
a} :: DBSnapshot) 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 when the snapshot was taken in Coordinated Universal Time
-- (UTC). Changes for the copy when the snapshot is copied.
dbSnapshot_snapshotCreateTime :: Lens.Lens' DBSnapshot (Prelude.Maybe Prelude.UTCTime)
dbSnapshot_snapshotCreateTime :: Lens' DBSnapshot (Maybe UTCTime)
dbSnapshot_snapshotCreateTime = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\DBSnapshot' {Maybe ISO8601
snapshotCreateTime :: Maybe ISO8601
$sel:snapshotCreateTime:DBSnapshot' :: DBSnapshot -> Maybe ISO8601
snapshotCreateTime} -> Maybe ISO8601
snapshotCreateTime) (\s :: DBSnapshot
s@DBSnapshot' {} Maybe ISO8601
a -> DBSnapshot
s {$sel:snapshotCreateTime:DBSnapshot' :: Maybe ISO8601
snapshotCreateTime = Maybe ISO8601
a} :: DBSnapshot) forall b c a. (b -> c) -> (a -> b) -> a -> c
Prelude.. forall (f :: * -> *) (g :: * -> *) s t a b.
(Functor f, Functor g) =>
AnIso s t a b -> Iso (f s) (g t) (f a) (g b)
Lens.mapping forall (a :: Format). Iso' (Time a) UTCTime
Data._Time

-- | The timestamp of the most recent transaction applied to the database
-- that you\'re backing up. Thus, if you restore a snapshot,
-- SnapshotDatabaseTime is the most recent transaction in the restored DB
-- instance. In contrast, originalSnapshotCreateTime specifies the system
-- time that the snapshot completed.
--
-- If you back up a read replica, you can determine the replica lag by
-- comparing SnapshotDatabaseTime with originalSnapshotCreateTime. For
-- example, if originalSnapshotCreateTime is two hours later than
-- SnapshotDatabaseTime, then the replica lag is two hours.
dbSnapshot_snapshotDatabaseTime :: Lens.Lens' DBSnapshot (Prelude.Maybe Prelude.UTCTime)
dbSnapshot_snapshotDatabaseTime :: Lens' DBSnapshot (Maybe UTCTime)
dbSnapshot_snapshotDatabaseTime = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\DBSnapshot' {Maybe ISO8601
snapshotDatabaseTime :: Maybe ISO8601
$sel:snapshotDatabaseTime:DBSnapshot' :: DBSnapshot -> Maybe ISO8601
snapshotDatabaseTime} -> Maybe ISO8601
snapshotDatabaseTime) (\s :: DBSnapshot
s@DBSnapshot' {} Maybe ISO8601
a -> DBSnapshot
s {$sel:snapshotDatabaseTime:DBSnapshot' :: Maybe ISO8601
snapshotDatabaseTime = Maybe ISO8601
a} :: DBSnapshot) 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 where manual snapshots are stored: Amazon Web Services
-- Outposts or the Amazon Web Services Region.
dbSnapshot_snapshotTarget :: Lens.Lens' DBSnapshot (Prelude.Maybe Prelude.Text)
dbSnapshot_snapshotTarget :: Lens' DBSnapshot (Maybe Text)
dbSnapshot_snapshotTarget = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\DBSnapshot' {Maybe Text
snapshotTarget :: Maybe Text
$sel:snapshotTarget:DBSnapshot' :: DBSnapshot -> Maybe Text
snapshotTarget} -> Maybe Text
snapshotTarget) (\s :: DBSnapshot
s@DBSnapshot' {} Maybe Text
a -> DBSnapshot
s {$sel:snapshotTarget:DBSnapshot' :: Maybe Text
snapshotTarget = Maybe Text
a} :: DBSnapshot)

-- | Provides the type of the DB snapshot.
dbSnapshot_snapshotType :: Lens.Lens' DBSnapshot (Prelude.Maybe Prelude.Text)
dbSnapshot_snapshotType :: Lens' DBSnapshot (Maybe Text)
dbSnapshot_snapshotType = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\DBSnapshot' {Maybe Text
snapshotType :: Maybe Text
$sel:snapshotType:DBSnapshot' :: DBSnapshot -> Maybe Text
snapshotType} -> Maybe Text
snapshotType) (\s :: DBSnapshot
s@DBSnapshot' {} Maybe Text
a -> DBSnapshot
s {$sel:snapshotType:DBSnapshot' :: Maybe Text
snapshotType = Maybe Text
a} :: DBSnapshot)

-- | The DB snapshot Amazon Resource Name (ARN) that the DB snapshot was
-- copied from. It only has a value in the case of a cross-account or
-- cross-Region copy.
dbSnapshot_sourceDBSnapshotIdentifier :: Lens.Lens' DBSnapshot (Prelude.Maybe Prelude.Text)
dbSnapshot_sourceDBSnapshotIdentifier :: Lens' DBSnapshot (Maybe Text)
dbSnapshot_sourceDBSnapshotIdentifier = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\DBSnapshot' {Maybe Text
sourceDBSnapshotIdentifier :: Maybe Text
$sel:sourceDBSnapshotIdentifier:DBSnapshot' :: DBSnapshot -> Maybe Text
sourceDBSnapshotIdentifier} -> Maybe Text
sourceDBSnapshotIdentifier) (\s :: DBSnapshot
s@DBSnapshot' {} Maybe Text
a -> DBSnapshot
s {$sel:sourceDBSnapshotIdentifier:DBSnapshot' :: Maybe Text
sourceDBSnapshotIdentifier = Maybe Text
a} :: DBSnapshot)

-- | The Amazon Web Services Region that the DB snapshot was created in or
-- copied from.
dbSnapshot_sourceRegion :: Lens.Lens' DBSnapshot (Prelude.Maybe Prelude.Text)
dbSnapshot_sourceRegion :: Lens' DBSnapshot (Maybe Text)
dbSnapshot_sourceRegion = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\DBSnapshot' {Maybe Text
sourceRegion :: Maybe Text
$sel:sourceRegion:DBSnapshot' :: DBSnapshot -> Maybe Text
sourceRegion} -> Maybe Text
sourceRegion) (\s :: DBSnapshot
s@DBSnapshot' {} Maybe Text
a -> DBSnapshot
s {$sel:sourceRegion:DBSnapshot' :: Maybe Text
sourceRegion = Maybe Text
a} :: DBSnapshot)

-- | Specifies the status of this DB snapshot.
dbSnapshot_status :: Lens.Lens' DBSnapshot (Prelude.Maybe Prelude.Text)
dbSnapshot_status :: Lens' DBSnapshot (Maybe Text)
dbSnapshot_status = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\DBSnapshot' {Maybe Text
status :: Maybe Text
$sel:status:DBSnapshot' :: DBSnapshot -> Maybe Text
status} -> Maybe Text
status) (\s :: DBSnapshot
s@DBSnapshot' {} Maybe Text
a -> DBSnapshot
s {$sel:status:DBSnapshot' :: Maybe Text
status = Maybe Text
a} :: DBSnapshot)

-- | Specifies the storage throughput for the DB snapshot.
dbSnapshot_storageThroughput :: Lens.Lens' DBSnapshot (Prelude.Maybe Prelude.Int)
dbSnapshot_storageThroughput :: Lens' DBSnapshot (Maybe Int)
dbSnapshot_storageThroughput = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\DBSnapshot' {Maybe Int
storageThroughput :: Maybe Int
$sel:storageThroughput:DBSnapshot' :: DBSnapshot -> Maybe Int
storageThroughput} -> Maybe Int
storageThroughput) (\s :: DBSnapshot
s@DBSnapshot' {} Maybe Int
a -> DBSnapshot
s {$sel:storageThroughput:DBSnapshot' :: Maybe Int
storageThroughput = Maybe Int
a} :: DBSnapshot)

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

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

-- | The ARN from the key store with which to associate the instance for TDE
-- encryption.
dbSnapshot_tdeCredentialArn :: Lens.Lens' DBSnapshot (Prelude.Maybe Prelude.Text)
dbSnapshot_tdeCredentialArn :: Lens' DBSnapshot (Maybe Text)
dbSnapshot_tdeCredentialArn = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\DBSnapshot' {Maybe Text
tdeCredentialArn :: Maybe Text
$sel:tdeCredentialArn:DBSnapshot' :: DBSnapshot -> Maybe Text
tdeCredentialArn} -> Maybe Text
tdeCredentialArn) (\s :: DBSnapshot
s@DBSnapshot' {} Maybe Text
a -> DBSnapshot
s {$sel:tdeCredentialArn:DBSnapshot' :: Maybe Text
tdeCredentialArn = Maybe Text
a} :: DBSnapshot)

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

-- | Provides the VPC ID associated with the DB snapshot.
dbSnapshot_vpcId :: Lens.Lens' DBSnapshot (Prelude.Maybe Prelude.Text)
dbSnapshot_vpcId :: Lens' DBSnapshot (Maybe Text)
dbSnapshot_vpcId = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\DBSnapshot' {Maybe Text
vpcId :: Maybe Text
$sel:vpcId:DBSnapshot' :: DBSnapshot -> Maybe Text
vpcId} -> Maybe Text
vpcId) (\s :: DBSnapshot
s@DBSnapshot' {} Maybe Text
a -> DBSnapshot
s {$sel:vpcId:DBSnapshot' :: Maybe Text
vpcId = Maybe Text
a} :: DBSnapshot)

instance Data.FromXML DBSnapshot where
  parseXML :: [Node] -> Either String DBSnapshot
parseXML [Node]
x =
    Maybe Int
-> Maybe Text
-> Maybe Text
-> Maybe Text
-> Maybe Text
-> Maybe Text
-> Maybe Bool
-> Maybe Text
-> Maybe Text
-> Maybe Bool
-> Maybe ISO8601
-> Maybe Int
-> Maybe Text
-> Maybe Text
-> Maybe Text
-> Maybe Text
-> Maybe ISO8601
-> Maybe Int
-> Maybe Int
-> Maybe [ProcessorFeature]
-> Maybe ISO8601
-> Maybe ISO8601
-> Maybe Text
-> Maybe Text
-> Maybe Text
-> Maybe Text
-> Maybe Text
-> Maybe Int
-> Maybe Text
-> Maybe [Tag]
-> Maybe Text
-> Maybe Text
-> Maybe Text
-> DBSnapshot
DBSnapshot'
      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
"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
"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
"DBSnapshotArn")
      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
"DBSnapshotIdentifier")
      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
"Encrypted")
      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
"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
"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
"OptionGroupName")
      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
"OriginalSnapshotCreateTime")
      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
"PercentProgress")
      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
"Port")
      forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
Prelude.<*> ( [Node]
x
                      forall a. FromXML a => [Node] -> Text -> Either String (Maybe a)
Data..@? Text
"ProcessorFeatures"
                      forall (f :: * -> *) a. Functor f => f (Maybe a) -> a -> f a
Core..!@ forall a. Monoid a => a
Prelude.mempty
                      forall (m :: * -> *) a b. Monad m => m a -> (a -> m b) -> m b
Prelude.>>= forall (f :: * -> *) a b.
Applicative f =>
([a] -> f b) -> [a] -> f (Maybe b)
Core.may (forall a. FromXML a => Text -> [Node] -> Either String [a]
Data.parseXMLList Text
"ProcessorFeature")
                  )
      forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
Prelude.<*> ([Node]
x forall a. FromXML a => [Node] -> Text -> Either String (Maybe a)
Data..@? Text
"SnapshotCreateTime")
      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
"SnapshotDatabaseTime")
      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
"SnapshotTarget")
      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
"SnapshotType")
      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
"SourceDBSnapshotIdentifier")
      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
"SourceRegion")
      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
"Status")
      forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
Prelude.<*> ([Node]
x forall a. FromXML a => [Node] -> Text -> Either String (Maybe a)
Data..@? Text
"StorageThroughput")
      forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
Prelude.<*> ([Node]
x forall a. FromXML a => [Node] -> Text -> Either String (Maybe a)
Data..@? Text
"StorageType")
      forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
Prelude.<*> ( [Node]
x
                      forall a. FromXML a => [Node] -> Text -> Either String (Maybe a)
Data..@? Text
"TagList"
                      forall (f :: * -> *) a. Functor f => f (Maybe a) -> a -> f a
Core..!@ forall a. Monoid a => a
Prelude.mempty
                      forall (m :: * -> *) a b. Monad m => m a -> (a -> m b) -> m b
Prelude.>>= forall (f :: * -> *) a b.
Applicative f =>
([a] -> f b) -> [a] -> f (Maybe b)
Core.may (forall a. FromXML a => Text -> [Node] -> Either String [a]
Data.parseXMLList Text
"Tag")
                  )
      forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
Prelude.<*> ([Node]
x forall a. FromXML a => [Node] -> Text -> Either String (Maybe a)
Data..@? Text
"TdeCredentialArn")
      forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
Prelude.<*> ([Node]
x forall a. FromXML a => [Node] -> Text -> Either String (Maybe a)
Data..@? Text
"Timezone")
      forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
Prelude.<*> ([Node]
x forall a. FromXML a => [Node] -> Text -> Either String (Maybe a)
Data..@? Text
"VpcId")

instance Prelude.Hashable DBSnapshot where
  hashWithSalt :: Int -> DBSnapshot -> Int
hashWithSalt Int
_salt DBSnapshot' {Maybe Bool
Maybe Int
Maybe [ProcessorFeature]
Maybe [Tag]
Maybe Text
Maybe ISO8601
vpcId :: Maybe Text
timezone :: Maybe Text
tdeCredentialArn :: Maybe Text
tagList :: Maybe [Tag]
storageType :: Maybe Text
storageThroughput :: Maybe Int
status :: Maybe Text
sourceRegion :: Maybe Text
sourceDBSnapshotIdentifier :: Maybe Text
snapshotType :: Maybe Text
snapshotTarget :: Maybe Text
snapshotDatabaseTime :: Maybe ISO8601
snapshotCreateTime :: Maybe ISO8601
processorFeatures :: Maybe [ProcessorFeature]
port :: Maybe Int
percentProgress :: Maybe Int
originalSnapshotCreateTime :: Maybe ISO8601
optionGroupName :: Maybe Text
masterUsername :: Maybe Text
licenseModel :: Maybe Text
kmsKeyId :: Maybe Text
iops :: Maybe Int
instanceCreateTime :: Maybe ISO8601
iAMDatabaseAuthenticationEnabled :: Maybe Bool
engineVersion :: Maybe Text
engine :: Maybe Text
encrypted :: Maybe Bool
dbiResourceId :: Maybe Text
dbSnapshotIdentifier :: Maybe Text
dbSnapshotArn :: Maybe Text
dbInstanceIdentifier :: Maybe Text
availabilityZone :: Maybe Text
allocatedStorage :: Maybe Int
$sel:vpcId:DBSnapshot' :: DBSnapshot -> Maybe Text
$sel:timezone:DBSnapshot' :: DBSnapshot -> Maybe Text
$sel:tdeCredentialArn:DBSnapshot' :: DBSnapshot -> Maybe Text
$sel:tagList:DBSnapshot' :: DBSnapshot -> Maybe [Tag]
$sel:storageType:DBSnapshot' :: DBSnapshot -> Maybe Text
$sel:storageThroughput:DBSnapshot' :: DBSnapshot -> Maybe Int
$sel:status:DBSnapshot' :: DBSnapshot -> Maybe Text
$sel:sourceRegion:DBSnapshot' :: DBSnapshot -> Maybe Text
$sel:sourceDBSnapshotIdentifier:DBSnapshot' :: DBSnapshot -> Maybe Text
$sel:snapshotType:DBSnapshot' :: DBSnapshot -> Maybe Text
$sel:snapshotTarget:DBSnapshot' :: DBSnapshot -> Maybe Text
$sel:snapshotDatabaseTime:DBSnapshot' :: DBSnapshot -> Maybe ISO8601
$sel:snapshotCreateTime:DBSnapshot' :: DBSnapshot -> Maybe ISO8601
$sel:processorFeatures:DBSnapshot' :: DBSnapshot -> Maybe [ProcessorFeature]
$sel:port:DBSnapshot' :: DBSnapshot -> Maybe Int
$sel:percentProgress:DBSnapshot' :: DBSnapshot -> Maybe Int
$sel:originalSnapshotCreateTime:DBSnapshot' :: DBSnapshot -> Maybe ISO8601
$sel:optionGroupName:DBSnapshot' :: DBSnapshot -> Maybe Text
$sel:masterUsername:DBSnapshot' :: DBSnapshot -> Maybe Text
$sel:licenseModel:DBSnapshot' :: DBSnapshot -> Maybe Text
$sel:kmsKeyId:DBSnapshot' :: DBSnapshot -> Maybe Text
$sel:iops:DBSnapshot' :: DBSnapshot -> Maybe Int
$sel:instanceCreateTime:DBSnapshot' :: DBSnapshot -> Maybe ISO8601
$sel:iAMDatabaseAuthenticationEnabled:DBSnapshot' :: DBSnapshot -> Maybe Bool
$sel:engineVersion:DBSnapshot' :: DBSnapshot -> Maybe Text
$sel:engine:DBSnapshot' :: DBSnapshot -> Maybe Text
$sel:encrypted:DBSnapshot' :: DBSnapshot -> Maybe Bool
$sel:dbiResourceId:DBSnapshot' :: DBSnapshot -> Maybe Text
$sel:dbSnapshotIdentifier:DBSnapshot' :: DBSnapshot -> Maybe Text
$sel:dbSnapshotArn:DBSnapshot' :: DBSnapshot -> Maybe Text
$sel:dbInstanceIdentifier:DBSnapshot' :: DBSnapshot -> Maybe Text
$sel:availabilityZone:DBSnapshot' :: DBSnapshot -> Maybe Text
$sel:allocatedStorage:DBSnapshot' :: DBSnapshot -> 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 Text
availabilityZone
      forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Maybe Text
dbInstanceIdentifier
      forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Maybe Text
dbSnapshotArn
      forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Maybe Text
dbSnapshotIdentifier
      forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Maybe Text
dbiResourceId
      forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Maybe Bool
encrypted
      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 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 Text
licenseModel
      forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Maybe Text
masterUsername
      forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Maybe Text
optionGroupName
      forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Maybe ISO8601
originalSnapshotCreateTime
      forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Maybe Int
percentProgress
      forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Maybe Int
port
      forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Maybe [ProcessorFeature]
processorFeatures
      forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Maybe ISO8601
snapshotCreateTime
      forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Maybe ISO8601
snapshotDatabaseTime
      forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Maybe Text
snapshotTarget
      forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Maybe Text
snapshotType
      forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Maybe Text
sourceDBSnapshotIdentifier
      forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Maybe Text
sourceRegion
      forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Maybe Text
status
      forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Maybe Int
storageThroughput
      forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Maybe Text
storageType
      forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Maybe [Tag]
tagList
      forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Maybe Text
tdeCredentialArn
      forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Maybe Text
timezone
      forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Maybe Text
vpcId

instance Prelude.NFData DBSnapshot where
  rnf :: DBSnapshot -> ()
rnf DBSnapshot' {Maybe Bool
Maybe Int
Maybe [ProcessorFeature]
Maybe [Tag]
Maybe Text
Maybe ISO8601
vpcId :: Maybe Text
timezone :: Maybe Text
tdeCredentialArn :: Maybe Text
tagList :: Maybe [Tag]
storageType :: Maybe Text
storageThroughput :: Maybe Int
status :: Maybe Text
sourceRegion :: Maybe Text
sourceDBSnapshotIdentifier :: Maybe Text
snapshotType :: Maybe Text
snapshotTarget :: Maybe Text
snapshotDatabaseTime :: Maybe ISO8601
snapshotCreateTime :: Maybe ISO8601
processorFeatures :: Maybe [ProcessorFeature]
port :: Maybe Int
percentProgress :: Maybe Int
originalSnapshotCreateTime :: Maybe ISO8601
optionGroupName :: Maybe Text
masterUsername :: Maybe Text
licenseModel :: Maybe Text
kmsKeyId :: Maybe Text
iops :: Maybe Int
instanceCreateTime :: Maybe ISO8601
iAMDatabaseAuthenticationEnabled :: Maybe Bool
engineVersion :: Maybe Text
engine :: Maybe Text
encrypted :: Maybe Bool
dbiResourceId :: Maybe Text
dbSnapshotIdentifier :: Maybe Text
dbSnapshotArn :: Maybe Text
dbInstanceIdentifier :: Maybe Text
availabilityZone :: Maybe Text
allocatedStorage :: Maybe Int
$sel:vpcId:DBSnapshot' :: DBSnapshot -> Maybe Text
$sel:timezone:DBSnapshot' :: DBSnapshot -> Maybe Text
$sel:tdeCredentialArn:DBSnapshot' :: DBSnapshot -> Maybe Text
$sel:tagList:DBSnapshot' :: DBSnapshot -> Maybe [Tag]
$sel:storageType:DBSnapshot' :: DBSnapshot -> Maybe Text
$sel:storageThroughput:DBSnapshot' :: DBSnapshot -> Maybe Int
$sel:status:DBSnapshot' :: DBSnapshot -> Maybe Text
$sel:sourceRegion:DBSnapshot' :: DBSnapshot -> Maybe Text
$sel:sourceDBSnapshotIdentifier:DBSnapshot' :: DBSnapshot -> Maybe Text
$sel:snapshotType:DBSnapshot' :: DBSnapshot -> Maybe Text
$sel:snapshotTarget:DBSnapshot' :: DBSnapshot -> Maybe Text
$sel:snapshotDatabaseTime:DBSnapshot' :: DBSnapshot -> Maybe ISO8601
$sel:snapshotCreateTime:DBSnapshot' :: DBSnapshot -> Maybe ISO8601
$sel:processorFeatures:DBSnapshot' :: DBSnapshot -> Maybe [ProcessorFeature]
$sel:port:DBSnapshot' :: DBSnapshot -> Maybe Int
$sel:percentProgress:DBSnapshot' :: DBSnapshot -> Maybe Int
$sel:originalSnapshotCreateTime:DBSnapshot' :: DBSnapshot -> Maybe ISO8601
$sel:optionGroupName:DBSnapshot' :: DBSnapshot -> Maybe Text
$sel:masterUsername:DBSnapshot' :: DBSnapshot -> Maybe Text
$sel:licenseModel:DBSnapshot' :: DBSnapshot -> Maybe Text
$sel:kmsKeyId:DBSnapshot' :: DBSnapshot -> Maybe Text
$sel:iops:DBSnapshot' :: DBSnapshot -> Maybe Int
$sel:instanceCreateTime:DBSnapshot' :: DBSnapshot -> Maybe ISO8601
$sel:iAMDatabaseAuthenticationEnabled:DBSnapshot' :: DBSnapshot -> Maybe Bool
$sel:engineVersion:DBSnapshot' :: DBSnapshot -> Maybe Text
$sel:engine:DBSnapshot' :: DBSnapshot -> Maybe Text
$sel:encrypted:DBSnapshot' :: DBSnapshot -> Maybe Bool
$sel:dbiResourceId:DBSnapshot' :: DBSnapshot -> Maybe Text
$sel:dbSnapshotIdentifier:DBSnapshot' :: DBSnapshot -> Maybe Text
$sel:dbSnapshotArn:DBSnapshot' :: DBSnapshot -> Maybe Text
$sel:dbInstanceIdentifier:DBSnapshot' :: DBSnapshot -> Maybe Text
$sel:availabilityZone:DBSnapshot' :: DBSnapshot -> Maybe Text
$sel:allocatedStorage:DBSnapshot' :: DBSnapshot -> 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 Text
availabilityZone
      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
dbSnapshotArn
      seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf Maybe Text
dbSnapshotIdentifier
      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
encrypted
      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 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 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 Text
optionGroupName
      seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf
        Maybe ISO8601
originalSnapshotCreateTime
      seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf Maybe Int
percentProgress
      seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf Maybe Int
port
      seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf Maybe [ProcessorFeature]
processorFeatures
      seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf
        Maybe ISO8601
snapshotCreateTime
      seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf
        Maybe ISO8601
snapshotDatabaseTime
      seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf
        Maybe Text
snapshotTarget
      seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf
        Maybe Text
snapshotType
      seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf
        Maybe Text
sourceDBSnapshotIdentifier
      seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf
        Maybe Text
sourceRegion
      seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf
        Maybe Text
status
      seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf
        Maybe Int
storageThroughput
      seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf
        Maybe Text
storageType
      seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf
        Maybe [Tag]
tagList
      seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf
        Maybe Text
tdeCredentialArn
      seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf
        Maybe Text
timezone
      seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf
        Maybe Text
vpcId