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

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

-- |
-- Module      : Amazonka.Neptune.RestoreDBClusterFromSnapshot
-- Copyright   : (c) 2013-2023 Brendan Hay
-- License     : Mozilla Public License, v. 2.0.
-- Maintainer  : Brendan Hay
-- Stability   : auto-generated
-- Portability : non-portable (GHC extensions)
--
-- Creates a new DB cluster from a DB snapshot or DB cluster snapshot.
--
-- If a DB snapshot is specified, the target DB cluster is created from the
-- source DB snapshot with a default configuration and default security
-- group.
--
-- If a DB cluster snapshot is specified, the target DB cluster is created
-- from the source DB cluster restore point with the same configuration as
-- the original source DB cluster, except that the new DB cluster is
-- created with the default security group.
module Amazonka.Neptune.RestoreDBClusterFromSnapshot
  ( -- * Creating a Request
    RestoreDBClusterFromSnapshot (..),
    newRestoreDBClusterFromSnapshot,

    -- * Request Lenses
    restoreDBClusterFromSnapshot_availabilityZones,
    restoreDBClusterFromSnapshot_copyTagsToSnapshot,
    restoreDBClusterFromSnapshot_dbClusterParameterGroupName,
    restoreDBClusterFromSnapshot_dbSubnetGroupName,
    restoreDBClusterFromSnapshot_databaseName,
    restoreDBClusterFromSnapshot_deletionProtection,
    restoreDBClusterFromSnapshot_enableCloudwatchLogsExports,
    restoreDBClusterFromSnapshot_enableIAMDatabaseAuthentication,
    restoreDBClusterFromSnapshot_engineVersion,
    restoreDBClusterFromSnapshot_kmsKeyId,
    restoreDBClusterFromSnapshot_optionGroupName,
    restoreDBClusterFromSnapshot_port,
    restoreDBClusterFromSnapshot_serverlessV2ScalingConfiguration,
    restoreDBClusterFromSnapshot_tags,
    restoreDBClusterFromSnapshot_vpcSecurityGroupIds,
    restoreDBClusterFromSnapshot_dbClusterIdentifier,
    restoreDBClusterFromSnapshot_snapshotIdentifier,
    restoreDBClusterFromSnapshot_engine,

    -- * Destructuring the Response
    RestoreDBClusterFromSnapshotResponse (..),
    newRestoreDBClusterFromSnapshotResponse,

    -- * Response Lenses
    restoreDBClusterFromSnapshotResponse_dbCluster,
    restoreDBClusterFromSnapshotResponse_httpStatus,
  )
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
import qualified Amazonka.Prelude as Prelude
import qualified Amazonka.Request as Request
import qualified Amazonka.Response as Response

-- | /See:/ 'newRestoreDBClusterFromSnapshot' smart constructor.
data RestoreDBClusterFromSnapshot = RestoreDBClusterFromSnapshot'
  { -- | Provides the list of EC2 Availability Zones that instances in the
    -- restored DB cluster can be created in.
    RestoreDBClusterFromSnapshot -> Maybe [Text]
availabilityZones :: Prelude.Maybe [Prelude.Text],
    -- | /If set to @true@, tags are copied to any snapshot of the restored DB
    -- cluster that is created./
    RestoreDBClusterFromSnapshot -> Maybe Bool
copyTagsToSnapshot :: Prelude.Maybe Prelude.Bool,
    -- | The name of the DB cluster parameter group to associate with the new DB
    -- cluster.
    --
    -- Constraints:
    --
    -- -   If supplied, must match the name of an existing
    --     DBClusterParameterGroup.
    RestoreDBClusterFromSnapshot -> Maybe Text
dbClusterParameterGroupName :: Prelude.Maybe Prelude.Text,
    -- | The name of the DB subnet group to use for the new DB cluster.
    --
    -- Constraints: If supplied, must match the name of an existing
    -- DBSubnetGroup.
    --
    -- Example: @mySubnetgroup@
    RestoreDBClusterFromSnapshot -> Maybe Text
dbSubnetGroupName :: Prelude.Maybe Prelude.Text,
    -- | Not supported.
    RestoreDBClusterFromSnapshot -> Maybe Text
databaseName :: Prelude.Maybe Prelude.Text,
    -- | A value that indicates whether the DB cluster has deletion protection
    -- enabled. The database can\'t be deleted when deletion protection is
    -- enabled. By default, deletion protection is disabled.
    RestoreDBClusterFromSnapshot -> Maybe Bool
deletionProtection :: Prelude.Maybe Prelude.Bool,
    -- | The list of logs that the restored DB cluster is to export to Amazon
    -- CloudWatch Logs.
    RestoreDBClusterFromSnapshot -> Maybe [Text]
enableCloudwatchLogsExports :: Prelude.Maybe [Prelude.Text],
    -- | True to enable mapping of Amazon Identity and Access Management (IAM)
    -- accounts to database accounts, and otherwise false.
    --
    -- Default: @false@
    RestoreDBClusterFromSnapshot -> Maybe Bool
enableIAMDatabaseAuthentication :: Prelude.Maybe Prelude.Bool,
    -- | The version of the database engine to use for the new DB cluster.
    RestoreDBClusterFromSnapshot -> Maybe Text
engineVersion :: Prelude.Maybe Prelude.Text,
    -- | The Amazon KMS key identifier to use when restoring an encrypted DB
    -- cluster from a DB snapshot or DB cluster snapshot.
    --
    -- The KMS key identifier is the Amazon Resource Name (ARN) for the KMS
    -- encryption key. If you are restoring a DB cluster with the same Amazon
    -- account that owns the KMS encryption key used to encrypt the new DB
    -- cluster, then you can use the KMS key alias instead of the ARN for the
    -- KMS encryption key.
    --
    -- If you do not specify a value for the @KmsKeyId@ parameter, then the
    -- following will occur:
    --
    -- -   If the DB snapshot or DB cluster snapshot in @SnapshotIdentifier@ is
    --     encrypted, then the restored DB cluster is encrypted using the KMS
    --     key that was used to encrypt the DB snapshot or DB cluster snapshot.
    --
    -- -   If the DB snapshot or DB cluster snapshot in @SnapshotIdentifier@ is
    --     not encrypted, then the restored DB cluster is not encrypted.
    RestoreDBClusterFromSnapshot -> Maybe Text
kmsKeyId :: Prelude.Maybe Prelude.Text,
    -- | /(Not supported by Neptune)/
    RestoreDBClusterFromSnapshot -> Maybe Text
optionGroupName :: Prelude.Maybe Prelude.Text,
    -- | The port number on which the new DB cluster accepts connections.
    --
    -- Constraints: Value must be @1150-65535@
    --
    -- Default: The same port as the original DB cluster.
    RestoreDBClusterFromSnapshot -> Maybe Int
port :: Prelude.Maybe Prelude.Int,
    RestoreDBClusterFromSnapshot
-> Maybe ServerlessV2ScalingConfiguration
serverlessV2ScalingConfiguration :: Prelude.Maybe ServerlessV2ScalingConfiguration,
    -- | The tags to be assigned to the restored DB cluster.
    RestoreDBClusterFromSnapshot -> Maybe [Tag]
tags :: Prelude.Maybe [Tag],
    -- | A list of VPC security groups that the new DB cluster will belong to.
    RestoreDBClusterFromSnapshot -> Maybe [Text]
vpcSecurityGroupIds :: Prelude.Maybe [Prelude.Text],
    -- | The name of the DB cluster to create from the DB snapshot or DB cluster
    -- snapshot. This parameter isn\'t case-sensitive.
    --
    -- Constraints:
    --
    -- -   Must contain from 1 to 63 letters, numbers, or hyphens
    --
    -- -   First character must be a letter
    --
    -- -   Cannot end with a hyphen or contain two consecutive hyphens
    --
    -- Example: @my-snapshot-id@
    RestoreDBClusterFromSnapshot -> Text
dbClusterIdentifier :: Prelude.Text,
    -- | The identifier for the DB snapshot or DB cluster snapshot to restore
    -- from.
    --
    -- You can use either the name or the Amazon Resource Name (ARN) to specify
    -- a DB cluster snapshot. However, you can use only the ARN to specify a DB
    -- snapshot.
    --
    -- Constraints:
    --
    -- -   Must match the identifier of an existing Snapshot.
    RestoreDBClusterFromSnapshot -> Text
snapshotIdentifier :: Prelude.Text,
    -- | The database engine to use for the new DB cluster.
    --
    -- Default: The same as source
    --
    -- Constraint: Must be compatible with the engine of the source
    RestoreDBClusterFromSnapshot -> Text
engine :: Prelude.Text
  }
  deriving (RestoreDBClusterFromSnapshot
-> RestoreDBClusterFromSnapshot -> Bool
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: RestoreDBClusterFromSnapshot
-> RestoreDBClusterFromSnapshot -> Bool
$c/= :: RestoreDBClusterFromSnapshot
-> RestoreDBClusterFromSnapshot -> Bool
== :: RestoreDBClusterFromSnapshot
-> RestoreDBClusterFromSnapshot -> Bool
$c== :: RestoreDBClusterFromSnapshot
-> RestoreDBClusterFromSnapshot -> Bool
Prelude.Eq, ReadPrec [RestoreDBClusterFromSnapshot]
ReadPrec RestoreDBClusterFromSnapshot
Int -> ReadS RestoreDBClusterFromSnapshot
ReadS [RestoreDBClusterFromSnapshot]
forall a.
(Int -> ReadS a)
-> ReadS [a] -> ReadPrec a -> ReadPrec [a] -> Read a
readListPrec :: ReadPrec [RestoreDBClusterFromSnapshot]
$creadListPrec :: ReadPrec [RestoreDBClusterFromSnapshot]
readPrec :: ReadPrec RestoreDBClusterFromSnapshot
$creadPrec :: ReadPrec RestoreDBClusterFromSnapshot
readList :: ReadS [RestoreDBClusterFromSnapshot]
$creadList :: ReadS [RestoreDBClusterFromSnapshot]
readsPrec :: Int -> ReadS RestoreDBClusterFromSnapshot
$creadsPrec :: Int -> ReadS RestoreDBClusterFromSnapshot
Prelude.Read, Int -> RestoreDBClusterFromSnapshot -> ShowS
[RestoreDBClusterFromSnapshot] -> ShowS
RestoreDBClusterFromSnapshot -> String
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [RestoreDBClusterFromSnapshot] -> ShowS
$cshowList :: [RestoreDBClusterFromSnapshot] -> ShowS
show :: RestoreDBClusterFromSnapshot -> String
$cshow :: RestoreDBClusterFromSnapshot -> String
showsPrec :: Int -> RestoreDBClusterFromSnapshot -> ShowS
$cshowsPrec :: Int -> RestoreDBClusterFromSnapshot -> ShowS
Prelude.Show, forall x.
Rep RestoreDBClusterFromSnapshot x -> RestoreDBClusterFromSnapshot
forall x.
RestoreDBClusterFromSnapshot -> Rep RestoreDBClusterFromSnapshot x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cto :: forall x.
Rep RestoreDBClusterFromSnapshot x -> RestoreDBClusterFromSnapshot
$cfrom :: forall x.
RestoreDBClusterFromSnapshot -> Rep RestoreDBClusterFromSnapshot x
Prelude.Generic)

-- |
-- Create a value of 'RestoreDBClusterFromSnapshot' with all optional fields omitted.
--
-- Use <https://hackage.haskell.org/package/generic-lens generic-lens> or <https://hackage.haskell.org/package/optics optics> to modify other optional fields.
--
-- The following record fields are available, with the corresponding lenses provided
-- for backwards compatibility:
--
-- 'availabilityZones', 'restoreDBClusterFromSnapshot_availabilityZones' - Provides the list of EC2 Availability Zones that instances in the
-- restored DB cluster can be created in.
--
-- 'copyTagsToSnapshot', 'restoreDBClusterFromSnapshot_copyTagsToSnapshot' - /If set to @true@, tags are copied to any snapshot of the restored DB
-- cluster that is created./
--
-- 'dbClusterParameterGroupName', 'restoreDBClusterFromSnapshot_dbClusterParameterGroupName' - The name of the DB cluster parameter group to associate with the new DB
-- cluster.
--
-- Constraints:
--
-- -   If supplied, must match the name of an existing
--     DBClusterParameterGroup.
--
-- 'dbSubnetGroupName', 'restoreDBClusterFromSnapshot_dbSubnetGroupName' - The name of the DB subnet group to use for the new DB cluster.
--
-- Constraints: If supplied, must match the name of an existing
-- DBSubnetGroup.
--
-- Example: @mySubnetgroup@
--
-- 'databaseName', 'restoreDBClusterFromSnapshot_databaseName' - Not supported.
--
-- 'deletionProtection', 'restoreDBClusterFromSnapshot_deletionProtection' - A value that indicates whether the DB cluster has deletion protection
-- enabled. The database can\'t be deleted when deletion protection is
-- enabled. By default, deletion protection is disabled.
--
-- 'enableCloudwatchLogsExports', 'restoreDBClusterFromSnapshot_enableCloudwatchLogsExports' - The list of logs that the restored DB cluster is to export to Amazon
-- CloudWatch Logs.
--
-- 'enableIAMDatabaseAuthentication', 'restoreDBClusterFromSnapshot_enableIAMDatabaseAuthentication' - True to enable mapping of Amazon Identity and Access Management (IAM)
-- accounts to database accounts, and otherwise false.
--
-- Default: @false@
--
-- 'engineVersion', 'restoreDBClusterFromSnapshot_engineVersion' - The version of the database engine to use for the new DB cluster.
--
-- 'kmsKeyId', 'restoreDBClusterFromSnapshot_kmsKeyId' - The Amazon KMS key identifier to use when restoring an encrypted DB
-- cluster from a DB snapshot or DB cluster snapshot.
--
-- The KMS key identifier is the Amazon Resource Name (ARN) for the KMS
-- encryption key. If you are restoring a DB cluster with the same Amazon
-- account that owns the KMS encryption key used to encrypt the new DB
-- cluster, then you can use the KMS key alias instead of the ARN for the
-- KMS encryption key.
--
-- If you do not specify a value for the @KmsKeyId@ parameter, then the
-- following will occur:
--
-- -   If the DB snapshot or DB cluster snapshot in @SnapshotIdentifier@ is
--     encrypted, then the restored DB cluster is encrypted using the KMS
--     key that was used to encrypt the DB snapshot or DB cluster snapshot.
--
-- -   If the DB snapshot or DB cluster snapshot in @SnapshotIdentifier@ is
--     not encrypted, then the restored DB cluster is not encrypted.
--
-- 'optionGroupName', 'restoreDBClusterFromSnapshot_optionGroupName' - /(Not supported by Neptune)/
--
-- 'port', 'restoreDBClusterFromSnapshot_port' - The port number on which the new DB cluster accepts connections.
--
-- Constraints: Value must be @1150-65535@
--
-- Default: The same port as the original DB cluster.
--
-- 'serverlessV2ScalingConfiguration', 'restoreDBClusterFromSnapshot_serverlessV2ScalingConfiguration' - Undocumented member.
--
-- 'tags', 'restoreDBClusterFromSnapshot_tags' - The tags to be assigned to the restored DB cluster.
--
-- 'vpcSecurityGroupIds', 'restoreDBClusterFromSnapshot_vpcSecurityGroupIds' - A list of VPC security groups that the new DB cluster will belong to.
--
-- 'dbClusterIdentifier', 'restoreDBClusterFromSnapshot_dbClusterIdentifier' - The name of the DB cluster to create from the DB snapshot or DB cluster
-- snapshot. This parameter isn\'t case-sensitive.
--
-- Constraints:
--
-- -   Must contain from 1 to 63 letters, numbers, or hyphens
--
-- -   First character must be a letter
--
-- -   Cannot end with a hyphen or contain two consecutive hyphens
--
-- Example: @my-snapshot-id@
--
-- 'snapshotIdentifier', 'restoreDBClusterFromSnapshot_snapshotIdentifier' - The identifier for the DB snapshot or DB cluster snapshot to restore
-- from.
--
-- You can use either the name or the Amazon Resource Name (ARN) to specify
-- a DB cluster snapshot. However, you can use only the ARN to specify a DB
-- snapshot.
--
-- Constraints:
--
-- -   Must match the identifier of an existing Snapshot.
--
-- 'engine', 'restoreDBClusterFromSnapshot_engine' - The database engine to use for the new DB cluster.
--
-- Default: The same as source
--
-- Constraint: Must be compatible with the engine of the source
newRestoreDBClusterFromSnapshot ::
  -- | 'dbClusterIdentifier'
  Prelude.Text ->
  -- | 'snapshotIdentifier'
  Prelude.Text ->
  -- | 'engine'
  Prelude.Text ->
  RestoreDBClusterFromSnapshot
newRestoreDBClusterFromSnapshot :: Text -> Text -> Text -> RestoreDBClusterFromSnapshot
newRestoreDBClusterFromSnapshot
  Text
pDBClusterIdentifier_
  Text
pSnapshotIdentifier_
  Text
pEngine_ =
    RestoreDBClusterFromSnapshot'
      { $sel:availabilityZones:RestoreDBClusterFromSnapshot' :: Maybe [Text]
availabilityZones =
          forall a. Maybe a
Prelude.Nothing,
        $sel:copyTagsToSnapshot:RestoreDBClusterFromSnapshot' :: Maybe Bool
copyTagsToSnapshot = forall a. Maybe a
Prelude.Nothing,
        $sel:dbClusterParameterGroupName:RestoreDBClusterFromSnapshot' :: Maybe Text
dbClusterParameterGroupName = forall a. Maybe a
Prelude.Nothing,
        $sel:dbSubnetGroupName:RestoreDBClusterFromSnapshot' :: Maybe Text
dbSubnetGroupName = forall a. Maybe a
Prelude.Nothing,
        $sel:databaseName:RestoreDBClusterFromSnapshot' :: Maybe Text
databaseName = forall a. Maybe a
Prelude.Nothing,
        $sel:deletionProtection:RestoreDBClusterFromSnapshot' :: Maybe Bool
deletionProtection = forall a. Maybe a
Prelude.Nothing,
        $sel:enableCloudwatchLogsExports:RestoreDBClusterFromSnapshot' :: Maybe [Text]
enableCloudwatchLogsExports = forall a. Maybe a
Prelude.Nothing,
        $sel:enableIAMDatabaseAuthentication:RestoreDBClusterFromSnapshot' :: Maybe Bool
enableIAMDatabaseAuthentication =
          forall a. Maybe a
Prelude.Nothing,
        $sel:engineVersion:RestoreDBClusterFromSnapshot' :: Maybe Text
engineVersion = forall a. Maybe a
Prelude.Nothing,
        $sel:kmsKeyId:RestoreDBClusterFromSnapshot' :: Maybe Text
kmsKeyId = forall a. Maybe a
Prelude.Nothing,
        $sel:optionGroupName:RestoreDBClusterFromSnapshot' :: Maybe Text
optionGroupName = forall a. Maybe a
Prelude.Nothing,
        $sel:port:RestoreDBClusterFromSnapshot' :: Maybe Int
port = forall a. Maybe a
Prelude.Nothing,
        $sel:serverlessV2ScalingConfiguration:RestoreDBClusterFromSnapshot' :: Maybe ServerlessV2ScalingConfiguration
serverlessV2ScalingConfiguration =
          forall a. Maybe a
Prelude.Nothing,
        $sel:tags:RestoreDBClusterFromSnapshot' :: Maybe [Tag]
tags = forall a. Maybe a
Prelude.Nothing,
        $sel:vpcSecurityGroupIds:RestoreDBClusterFromSnapshot' :: Maybe [Text]
vpcSecurityGroupIds = forall a. Maybe a
Prelude.Nothing,
        $sel:dbClusterIdentifier:RestoreDBClusterFromSnapshot' :: Text
dbClusterIdentifier = Text
pDBClusterIdentifier_,
        $sel:snapshotIdentifier:RestoreDBClusterFromSnapshot' :: Text
snapshotIdentifier = Text
pSnapshotIdentifier_,
        $sel:engine:RestoreDBClusterFromSnapshot' :: Text
engine = Text
pEngine_
      }

-- | Provides the list of EC2 Availability Zones that instances in the
-- restored DB cluster can be created in.
restoreDBClusterFromSnapshot_availabilityZones :: Lens.Lens' RestoreDBClusterFromSnapshot (Prelude.Maybe [Prelude.Text])
restoreDBClusterFromSnapshot_availabilityZones :: Lens' RestoreDBClusterFromSnapshot (Maybe [Text])
restoreDBClusterFromSnapshot_availabilityZones = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\RestoreDBClusterFromSnapshot' {Maybe [Text]
availabilityZones :: Maybe [Text]
$sel:availabilityZones:RestoreDBClusterFromSnapshot' :: RestoreDBClusterFromSnapshot -> Maybe [Text]
availabilityZones} -> Maybe [Text]
availabilityZones) (\s :: RestoreDBClusterFromSnapshot
s@RestoreDBClusterFromSnapshot' {} Maybe [Text]
a -> RestoreDBClusterFromSnapshot
s {$sel:availabilityZones:RestoreDBClusterFromSnapshot' :: Maybe [Text]
availabilityZones = Maybe [Text]
a} :: RestoreDBClusterFromSnapshot) 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

-- | /If set to @true@, tags are copied to any snapshot of the restored DB
-- cluster that is created./
restoreDBClusterFromSnapshot_copyTagsToSnapshot :: Lens.Lens' RestoreDBClusterFromSnapshot (Prelude.Maybe Prelude.Bool)
restoreDBClusterFromSnapshot_copyTagsToSnapshot :: Lens' RestoreDBClusterFromSnapshot (Maybe Bool)
restoreDBClusterFromSnapshot_copyTagsToSnapshot = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\RestoreDBClusterFromSnapshot' {Maybe Bool
copyTagsToSnapshot :: Maybe Bool
$sel:copyTagsToSnapshot:RestoreDBClusterFromSnapshot' :: RestoreDBClusterFromSnapshot -> Maybe Bool
copyTagsToSnapshot} -> Maybe Bool
copyTagsToSnapshot) (\s :: RestoreDBClusterFromSnapshot
s@RestoreDBClusterFromSnapshot' {} Maybe Bool
a -> RestoreDBClusterFromSnapshot
s {$sel:copyTagsToSnapshot:RestoreDBClusterFromSnapshot' :: Maybe Bool
copyTagsToSnapshot = Maybe Bool
a} :: RestoreDBClusterFromSnapshot)

-- | The name of the DB cluster parameter group to associate with the new DB
-- cluster.
--
-- Constraints:
--
-- -   If supplied, must match the name of an existing
--     DBClusterParameterGroup.
restoreDBClusterFromSnapshot_dbClusterParameterGroupName :: Lens.Lens' RestoreDBClusterFromSnapshot (Prelude.Maybe Prelude.Text)
restoreDBClusterFromSnapshot_dbClusterParameterGroupName :: Lens' RestoreDBClusterFromSnapshot (Maybe Text)
restoreDBClusterFromSnapshot_dbClusterParameterGroupName = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\RestoreDBClusterFromSnapshot' {Maybe Text
dbClusterParameterGroupName :: Maybe Text
$sel:dbClusterParameterGroupName:RestoreDBClusterFromSnapshot' :: RestoreDBClusterFromSnapshot -> Maybe Text
dbClusterParameterGroupName} -> Maybe Text
dbClusterParameterGroupName) (\s :: RestoreDBClusterFromSnapshot
s@RestoreDBClusterFromSnapshot' {} Maybe Text
a -> RestoreDBClusterFromSnapshot
s {$sel:dbClusterParameterGroupName:RestoreDBClusterFromSnapshot' :: Maybe Text
dbClusterParameterGroupName = Maybe Text
a} :: RestoreDBClusterFromSnapshot)

-- | The name of the DB subnet group to use for the new DB cluster.
--
-- Constraints: If supplied, must match the name of an existing
-- DBSubnetGroup.
--
-- Example: @mySubnetgroup@
restoreDBClusterFromSnapshot_dbSubnetGroupName :: Lens.Lens' RestoreDBClusterFromSnapshot (Prelude.Maybe Prelude.Text)
restoreDBClusterFromSnapshot_dbSubnetGroupName :: Lens' RestoreDBClusterFromSnapshot (Maybe Text)
restoreDBClusterFromSnapshot_dbSubnetGroupName = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\RestoreDBClusterFromSnapshot' {Maybe Text
dbSubnetGroupName :: Maybe Text
$sel:dbSubnetGroupName:RestoreDBClusterFromSnapshot' :: RestoreDBClusterFromSnapshot -> Maybe Text
dbSubnetGroupName} -> Maybe Text
dbSubnetGroupName) (\s :: RestoreDBClusterFromSnapshot
s@RestoreDBClusterFromSnapshot' {} Maybe Text
a -> RestoreDBClusterFromSnapshot
s {$sel:dbSubnetGroupName:RestoreDBClusterFromSnapshot' :: Maybe Text
dbSubnetGroupName = Maybe Text
a} :: RestoreDBClusterFromSnapshot)

-- | Not supported.
restoreDBClusterFromSnapshot_databaseName :: Lens.Lens' RestoreDBClusterFromSnapshot (Prelude.Maybe Prelude.Text)
restoreDBClusterFromSnapshot_databaseName :: Lens' RestoreDBClusterFromSnapshot (Maybe Text)
restoreDBClusterFromSnapshot_databaseName = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\RestoreDBClusterFromSnapshot' {Maybe Text
databaseName :: Maybe Text
$sel:databaseName:RestoreDBClusterFromSnapshot' :: RestoreDBClusterFromSnapshot -> Maybe Text
databaseName} -> Maybe Text
databaseName) (\s :: RestoreDBClusterFromSnapshot
s@RestoreDBClusterFromSnapshot' {} Maybe Text
a -> RestoreDBClusterFromSnapshot
s {$sel:databaseName:RestoreDBClusterFromSnapshot' :: Maybe Text
databaseName = Maybe Text
a} :: RestoreDBClusterFromSnapshot)

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

-- | The list of logs that the restored DB cluster is to export to Amazon
-- CloudWatch Logs.
restoreDBClusterFromSnapshot_enableCloudwatchLogsExports :: Lens.Lens' RestoreDBClusterFromSnapshot (Prelude.Maybe [Prelude.Text])
restoreDBClusterFromSnapshot_enableCloudwatchLogsExports :: Lens' RestoreDBClusterFromSnapshot (Maybe [Text])
restoreDBClusterFromSnapshot_enableCloudwatchLogsExports = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\RestoreDBClusterFromSnapshot' {Maybe [Text]
enableCloudwatchLogsExports :: Maybe [Text]
$sel:enableCloudwatchLogsExports:RestoreDBClusterFromSnapshot' :: RestoreDBClusterFromSnapshot -> Maybe [Text]
enableCloudwatchLogsExports} -> Maybe [Text]
enableCloudwatchLogsExports) (\s :: RestoreDBClusterFromSnapshot
s@RestoreDBClusterFromSnapshot' {} Maybe [Text]
a -> RestoreDBClusterFromSnapshot
s {$sel:enableCloudwatchLogsExports:RestoreDBClusterFromSnapshot' :: Maybe [Text]
enableCloudwatchLogsExports = Maybe [Text]
a} :: RestoreDBClusterFromSnapshot) 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

-- | True to enable mapping of Amazon Identity and Access Management (IAM)
-- accounts to database accounts, and otherwise false.
--
-- Default: @false@
restoreDBClusterFromSnapshot_enableIAMDatabaseAuthentication :: Lens.Lens' RestoreDBClusterFromSnapshot (Prelude.Maybe Prelude.Bool)
restoreDBClusterFromSnapshot_enableIAMDatabaseAuthentication :: Lens' RestoreDBClusterFromSnapshot (Maybe Bool)
restoreDBClusterFromSnapshot_enableIAMDatabaseAuthentication = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\RestoreDBClusterFromSnapshot' {Maybe Bool
enableIAMDatabaseAuthentication :: Maybe Bool
$sel:enableIAMDatabaseAuthentication:RestoreDBClusterFromSnapshot' :: RestoreDBClusterFromSnapshot -> Maybe Bool
enableIAMDatabaseAuthentication} -> Maybe Bool
enableIAMDatabaseAuthentication) (\s :: RestoreDBClusterFromSnapshot
s@RestoreDBClusterFromSnapshot' {} Maybe Bool
a -> RestoreDBClusterFromSnapshot
s {$sel:enableIAMDatabaseAuthentication:RestoreDBClusterFromSnapshot' :: Maybe Bool
enableIAMDatabaseAuthentication = Maybe Bool
a} :: RestoreDBClusterFromSnapshot)

-- | The version of the database engine to use for the new DB cluster.
restoreDBClusterFromSnapshot_engineVersion :: Lens.Lens' RestoreDBClusterFromSnapshot (Prelude.Maybe Prelude.Text)
restoreDBClusterFromSnapshot_engineVersion :: Lens' RestoreDBClusterFromSnapshot (Maybe Text)
restoreDBClusterFromSnapshot_engineVersion = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\RestoreDBClusterFromSnapshot' {Maybe Text
engineVersion :: Maybe Text
$sel:engineVersion:RestoreDBClusterFromSnapshot' :: RestoreDBClusterFromSnapshot -> Maybe Text
engineVersion} -> Maybe Text
engineVersion) (\s :: RestoreDBClusterFromSnapshot
s@RestoreDBClusterFromSnapshot' {} Maybe Text
a -> RestoreDBClusterFromSnapshot
s {$sel:engineVersion:RestoreDBClusterFromSnapshot' :: Maybe Text
engineVersion = Maybe Text
a} :: RestoreDBClusterFromSnapshot)

-- | The Amazon KMS key identifier to use when restoring an encrypted DB
-- cluster from a DB snapshot or DB cluster snapshot.
--
-- The KMS key identifier is the Amazon Resource Name (ARN) for the KMS
-- encryption key. If you are restoring a DB cluster with the same Amazon
-- account that owns the KMS encryption key used to encrypt the new DB
-- cluster, then you can use the KMS key alias instead of the ARN for the
-- KMS encryption key.
--
-- If you do not specify a value for the @KmsKeyId@ parameter, then the
-- following will occur:
--
-- -   If the DB snapshot or DB cluster snapshot in @SnapshotIdentifier@ is
--     encrypted, then the restored DB cluster is encrypted using the KMS
--     key that was used to encrypt the DB snapshot or DB cluster snapshot.
--
-- -   If the DB snapshot or DB cluster snapshot in @SnapshotIdentifier@ is
--     not encrypted, then the restored DB cluster is not encrypted.
restoreDBClusterFromSnapshot_kmsKeyId :: Lens.Lens' RestoreDBClusterFromSnapshot (Prelude.Maybe Prelude.Text)
restoreDBClusterFromSnapshot_kmsKeyId :: Lens' RestoreDBClusterFromSnapshot (Maybe Text)
restoreDBClusterFromSnapshot_kmsKeyId = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\RestoreDBClusterFromSnapshot' {Maybe Text
kmsKeyId :: Maybe Text
$sel:kmsKeyId:RestoreDBClusterFromSnapshot' :: RestoreDBClusterFromSnapshot -> Maybe Text
kmsKeyId} -> Maybe Text
kmsKeyId) (\s :: RestoreDBClusterFromSnapshot
s@RestoreDBClusterFromSnapshot' {} Maybe Text
a -> RestoreDBClusterFromSnapshot
s {$sel:kmsKeyId:RestoreDBClusterFromSnapshot' :: Maybe Text
kmsKeyId = Maybe Text
a} :: RestoreDBClusterFromSnapshot)

-- | /(Not supported by Neptune)/
restoreDBClusterFromSnapshot_optionGroupName :: Lens.Lens' RestoreDBClusterFromSnapshot (Prelude.Maybe Prelude.Text)
restoreDBClusterFromSnapshot_optionGroupName :: Lens' RestoreDBClusterFromSnapshot (Maybe Text)
restoreDBClusterFromSnapshot_optionGroupName = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\RestoreDBClusterFromSnapshot' {Maybe Text
optionGroupName :: Maybe Text
$sel:optionGroupName:RestoreDBClusterFromSnapshot' :: RestoreDBClusterFromSnapshot -> Maybe Text
optionGroupName} -> Maybe Text
optionGroupName) (\s :: RestoreDBClusterFromSnapshot
s@RestoreDBClusterFromSnapshot' {} Maybe Text
a -> RestoreDBClusterFromSnapshot
s {$sel:optionGroupName:RestoreDBClusterFromSnapshot' :: Maybe Text
optionGroupName = Maybe Text
a} :: RestoreDBClusterFromSnapshot)

-- | The port number on which the new DB cluster accepts connections.
--
-- Constraints: Value must be @1150-65535@
--
-- Default: The same port as the original DB cluster.
restoreDBClusterFromSnapshot_port :: Lens.Lens' RestoreDBClusterFromSnapshot (Prelude.Maybe Prelude.Int)
restoreDBClusterFromSnapshot_port :: Lens' RestoreDBClusterFromSnapshot (Maybe Int)
restoreDBClusterFromSnapshot_port = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\RestoreDBClusterFromSnapshot' {Maybe Int
port :: Maybe Int
$sel:port:RestoreDBClusterFromSnapshot' :: RestoreDBClusterFromSnapshot -> Maybe Int
port} -> Maybe Int
port) (\s :: RestoreDBClusterFromSnapshot
s@RestoreDBClusterFromSnapshot' {} Maybe Int
a -> RestoreDBClusterFromSnapshot
s {$sel:port:RestoreDBClusterFromSnapshot' :: Maybe Int
port = Maybe Int
a} :: RestoreDBClusterFromSnapshot)

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

-- | The tags to be assigned to the restored DB cluster.
restoreDBClusterFromSnapshot_tags :: Lens.Lens' RestoreDBClusterFromSnapshot (Prelude.Maybe [Tag])
restoreDBClusterFromSnapshot_tags :: Lens' RestoreDBClusterFromSnapshot (Maybe [Tag])
restoreDBClusterFromSnapshot_tags = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\RestoreDBClusterFromSnapshot' {Maybe [Tag]
tags :: Maybe [Tag]
$sel:tags:RestoreDBClusterFromSnapshot' :: RestoreDBClusterFromSnapshot -> Maybe [Tag]
tags} -> Maybe [Tag]
tags) (\s :: RestoreDBClusterFromSnapshot
s@RestoreDBClusterFromSnapshot' {} Maybe [Tag]
a -> RestoreDBClusterFromSnapshot
s {$sel:tags:RestoreDBClusterFromSnapshot' :: Maybe [Tag]
tags = Maybe [Tag]
a} :: RestoreDBClusterFromSnapshot) 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 VPC security groups that the new DB cluster will belong to.
restoreDBClusterFromSnapshot_vpcSecurityGroupIds :: Lens.Lens' RestoreDBClusterFromSnapshot (Prelude.Maybe [Prelude.Text])
restoreDBClusterFromSnapshot_vpcSecurityGroupIds :: Lens' RestoreDBClusterFromSnapshot (Maybe [Text])
restoreDBClusterFromSnapshot_vpcSecurityGroupIds = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\RestoreDBClusterFromSnapshot' {Maybe [Text]
vpcSecurityGroupIds :: Maybe [Text]
$sel:vpcSecurityGroupIds:RestoreDBClusterFromSnapshot' :: RestoreDBClusterFromSnapshot -> Maybe [Text]
vpcSecurityGroupIds} -> Maybe [Text]
vpcSecurityGroupIds) (\s :: RestoreDBClusterFromSnapshot
s@RestoreDBClusterFromSnapshot' {} Maybe [Text]
a -> RestoreDBClusterFromSnapshot
s {$sel:vpcSecurityGroupIds:RestoreDBClusterFromSnapshot' :: Maybe [Text]
vpcSecurityGroupIds = Maybe [Text]
a} :: RestoreDBClusterFromSnapshot) forall b c a. (b -> c) -> (a -> b) -> a -> c
Prelude.. forall (f :: * -> *) (g :: * -> *) s t a b.
(Functor f, Functor g) =>
AnIso s t a b -> Iso (f s) (g t) (f a) (g b)
Lens.mapping forall s t a b. (Coercible s a, Coercible t b) => Iso s t a b
Lens.coerced

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

-- | The identifier for the DB snapshot or DB cluster snapshot to restore
-- from.
--
-- You can use either the name or the Amazon Resource Name (ARN) to specify
-- a DB cluster snapshot. However, you can use only the ARN to specify a DB
-- snapshot.
--
-- Constraints:
--
-- -   Must match the identifier of an existing Snapshot.
restoreDBClusterFromSnapshot_snapshotIdentifier :: Lens.Lens' RestoreDBClusterFromSnapshot Prelude.Text
restoreDBClusterFromSnapshot_snapshotIdentifier :: Lens' RestoreDBClusterFromSnapshot Text
restoreDBClusterFromSnapshot_snapshotIdentifier = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\RestoreDBClusterFromSnapshot' {Text
snapshotIdentifier :: Text
$sel:snapshotIdentifier:RestoreDBClusterFromSnapshot' :: RestoreDBClusterFromSnapshot -> Text
snapshotIdentifier} -> Text
snapshotIdentifier) (\s :: RestoreDBClusterFromSnapshot
s@RestoreDBClusterFromSnapshot' {} Text
a -> RestoreDBClusterFromSnapshot
s {$sel:snapshotIdentifier:RestoreDBClusterFromSnapshot' :: Text
snapshotIdentifier = Text
a} :: RestoreDBClusterFromSnapshot)

-- | The database engine to use for the new DB cluster.
--
-- Default: The same as source
--
-- Constraint: Must be compatible with the engine of the source
restoreDBClusterFromSnapshot_engine :: Lens.Lens' RestoreDBClusterFromSnapshot Prelude.Text
restoreDBClusterFromSnapshot_engine :: Lens' RestoreDBClusterFromSnapshot Text
restoreDBClusterFromSnapshot_engine = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\RestoreDBClusterFromSnapshot' {Text
engine :: Text
$sel:engine:RestoreDBClusterFromSnapshot' :: RestoreDBClusterFromSnapshot -> Text
engine} -> Text
engine) (\s :: RestoreDBClusterFromSnapshot
s@RestoreDBClusterFromSnapshot' {} Text
a -> RestoreDBClusterFromSnapshot
s {$sel:engine:RestoreDBClusterFromSnapshot' :: Text
engine = Text
a} :: RestoreDBClusterFromSnapshot)

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

instance
  Prelude.Hashable
    RestoreDBClusterFromSnapshot
  where
  hashWithSalt :: Int -> RestoreDBClusterFromSnapshot -> Int
hashWithSalt Int
_salt RestoreDBClusterFromSnapshot' {Maybe Bool
Maybe Int
Maybe [Text]
Maybe [Tag]
Maybe Text
Maybe ServerlessV2ScalingConfiguration
Text
engine :: Text
snapshotIdentifier :: Text
dbClusterIdentifier :: Text
vpcSecurityGroupIds :: Maybe [Text]
tags :: Maybe [Tag]
serverlessV2ScalingConfiguration :: Maybe ServerlessV2ScalingConfiguration
port :: Maybe Int
optionGroupName :: Maybe Text
kmsKeyId :: Maybe Text
engineVersion :: Maybe Text
enableIAMDatabaseAuthentication :: Maybe Bool
enableCloudwatchLogsExports :: Maybe [Text]
deletionProtection :: Maybe Bool
databaseName :: Maybe Text
dbSubnetGroupName :: Maybe Text
dbClusterParameterGroupName :: Maybe Text
copyTagsToSnapshot :: Maybe Bool
availabilityZones :: Maybe [Text]
$sel:engine:RestoreDBClusterFromSnapshot' :: RestoreDBClusterFromSnapshot -> Text
$sel:snapshotIdentifier:RestoreDBClusterFromSnapshot' :: RestoreDBClusterFromSnapshot -> Text
$sel:dbClusterIdentifier:RestoreDBClusterFromSnapshot' :: RestoreDBClusterFromSnapshot -> Text
$sel:vpcSecurityGroupIds:RestoreDBClusterFromSnapshot' :: RestoreDBClusterFromSnapshot -> Maybe [Text]
$sel:tags:RestoreDBClusterFromSnapshot' :: RestoreDBClusterFromSnapshot -> Maybe [Tag]
$sel:serverlessV2ScalingConfiguration:RestoreDBClusterFromSnapshot' :: RestoreDBClusterFromSnapshot
-> Maybe ServerlessV2ScalingConfiguration
$sel:port:RestoreDBClusterFromSnapshot' :: RestoreDBClusterFromSnapshot -> Maybe Int
$sel:optionGroupName:RestoreDBClusterFromSnapshot' :: RestoreDBClusterFromSnapshot -> Maybe Text
$sel:kmsKeyId:RestoreDBClusterFromSnapshot' :: RestoreDBClusterFromSnapshot -> Maybe Text
$sel:engineVersion:RestoreDBClusterFromSnapshot' :: RestoreDBClusterFromSnapshot -> Maybe Text
$sel:enableIAMDatabaseAuthentication:RestoreDBClusterFromSnapshot' :: RestoreDBClusterFromSnapshot -> Maybe Bool
$sel:enableCloudwatchLogsExports:RestoreDBClusterFromSnapshot' :: RestoreDBClusterFromSnapshot -> Maybe [Text]
$sel:deletionProtection:RestoreDBClusterFromSnapshot' :: RestoreDBClusterFromSnapshot -> Maybe Bool
$sel:databaseName:RestoreDBClusterFromSnapshot' :: RestoreDBClusterFromSnapshot -> Maybe Text
$sel:dbSubnetGroupName:RestoreDBClusterFromSnapshot' :: RestoreDBClusterFromSnapshot -> Maybe Text
$sel:dbClusterParameterGroupName:RestoreDBClusterFromSnapshot' :: RestoreDBClusterFromSnapshot -> Maybe Text
$sel:copyTagsToSnapshot:RestoreDBClusterFromSnapshot' :: RestoreDBClusterFromSnapshot -> Maybe Bool
$sel:availabilityZones:RestoreDBClusterFromSnapshot' :: RestoreDBClusterFromSnapshot -> Maybe [Text]
..} =
    Int
_salt
      forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Maybe [Text]
availabilityZones
      forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Maybe Bool
copyTagsToSnapshot
      forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Maybe Text
dbClusterParameterGroupName
      forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Maybe Text
dbSubnetGroupName
      forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Maybe Text
databaseName
      forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Maybe Bool
deletionProtection
      forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Maybe [Text]
enableCloudwatchLogsExports
      forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Maybe Bool
enableIAMDatabaseAuthentication
      forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Maybe Text
engineVersion
      forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Maybe Text
kmsKeyId
      forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Maybe Text
optionGroupName
      forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Maybe Int
port
      forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Maybe ServerlessV2ScalingConfiguration
serverlessV2ScalingConfiguration
      forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Maybe [Tag]
tags
      forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Maybe [Text]
vpcSecurityGroupIds
      forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Text
dbClusterIdentifier
      forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Text
snapshotIdentifier
      forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Text
engine

instance Prelude.NFData RestoreDBClusterFromSnapshot where
  rnf :: RestoreDBClusterFromSnapshot -> ()
rnf RestoreDBClusterFromSnapshot' {Maybe Bool
Maybe Int
Maybe [Text]
Maybe [Tag]
Maybe Text
Maybe ServerlessV2ScalingConfiguration
Text
engine :: Text
snapshotIdentifier :: Text
dbClusterIdentifier :: Text
vpcSecurityGroupIds :: Maybe [Text]
tags :: Maybe [Tag]
serverlessV2ScalingConfiguration :: Maybe ServerlessV2ScalingConfiguration
port :: Maybe Int
optionGroupName :: Maybe Text
kmsKeyId :: Maybe Text
engineVersion :: Maybe Text
enableIAMDatabaseAuthentication :: Maybe Bool
enableCloudwatchLogsExports :: Maybe [Text]
deletionProtection :: Maybe Bool
databaseName :: Maybe Text
dbSubnetGroupName :: Maybe Text
dbClusterParameterGroupName :: Maybe Text
copyTagsToSnapshot :: Maybe Bool
availabilityZones :: Maybe [Text]
$sel:engine:RestoreDBClusterFromSnapshot' :: RestoreDBClusterFromSnapshot -> Text
$sel:snapshotIdentifier:RestoreDBClusterFromSnapshot' :: RestoreDBClusterFromSnapshot -> Text
$sel:dbClusterIdentifier:RestoreDBClusterFromSnapshot' :: RestoreDBClusterFromSnapshot -> Text
$sel:vpcSecurityGroupIds:RestoreDBClusterFromSnapshot' :: RestoreDBClusterFromSnapshot -> Maybe [Text]
$sel:tags:RestoreDBClusterFromSnapshot' :: RestoreDBClusterFromSnapshot -> Maybe [Tag]
$sel:serverlessV2ScalingConfiguration:RestoreDBClusterFromSnapshot' :: RestoreDBClusterFromSnapshot
-> Maybe ServerlessV2ScalingConfiguration
$sel:port:RestoreDBClusterFromSnapshot' :: RestoreDBClusterFromSnapshot -> Maybe Int
$sel:optionGroupName:RestoreDBClusterFromSnapshot' :: RestoreDBClusterFromSnapshot -> Maybe Text
$sel:kmsKeyId:RestoreDBClusterFromSnapshot' :: RestoreDBClusterFromSnapshot -> Maybe Text
$sel:engineVersion:RestoreDBClusterFromSnapshot' :: RestoreDBClusterFromSnapshot -> Maybe Text
$sel:enableIAMDatabaseAuthentication:RestoreDBClusterFromSnapshot' :: RestoreDBClusterFromSnapshot -> Maybe Bool
$sel:enableCloudwatchLogsExports:RestoreDBClusterFromSnapshot' :: RestoreDBClusterFromSnapshot -> Maybe [Text]
$sel:deletionProtection:RestoreDBClusterFromSnapshot' :: RestoreDBClusterFromSnapshot -> Maybe Bool
$sel:databaseName:RestoreDBClusterFromSnapshot' :: RestoreDBClusterFromSnapshot -> Maybe Text
$sel:dbSubnetGroupName:RestoreDBClusterFromSnapshot' :: RestoreDBClusterFromSnapshot -> Maybe Text
$sel:dbClusterParameterGroupName:RestoreDBClusterFromSnapshot' :: RestoreDBClusterFromSnapshot -> Maybe Text
$sel:copyTagsToSnapshot:RestoreDBClusterFromSnapshot' :: RestoreDBClusterFromSnapshot -> Maybe Bool
$sel:availabilityZones:RestoreDBClusterFromSnapshot' :: RestoreDBClusterFromSnapshot -> Maybe [Text]
..} =
    forall a. NFData a => a -> ()
Prelude.rnf Maybe [Text]
availabilityZones
      seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf Maybe Bool
copyTagsToSnapshot
      seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf Maybe Text
dbClusterParameterGroupName
      seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf Maybe Text
dbSubnetGroupName
      seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf Maybe Text
databaseName
      seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf Maybe Bool
deletionProtection
      seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf Maybe [Text]
enableCloudwatchLogsExports
      seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf Maybe Bool
enableIAMDatabaseAuthentication
      seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf Maybe Text
engineVersion
      seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf Maybe Text
kmsKeyId
      seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf Maybe Text
optionGroupName
      seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf Maybe Int
port
      seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf Maybe ServerlessV2ScalingConfiguration
serverlessV2ScalingConfiguration
      seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf Maybe [Tag]
tags
      seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf Maybe [Text]
vpcSecurityGroupIds
      seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf Text
dbClusterIdentifier
      seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf Text
snapshotIdentifier
      seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf Text
engine

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

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

instance Data.ToQuery RestoreDBClusterFromSnapshot where
  toQuery :: RestoreDBClusterFromSnapshot -> QueryString
toQuery RestoreDBClusterFromSnapshot' {Maybe Bool
Maybe Int
Maybe [Text]
Maybe [Tag]
Maybe Text
Maybe ServerlessV2ScalingConfiguration
Text
engine :: Text
snapshotIdentifier :: Text
dbClusterIdentifier :: Text
vpcSecurityGroupIds :: Maybe [Text]
tags :: Maybe [Tag]
serverlessV2ScalingConfiguration :: Maybe ServerlessV2ScalingConfiguration
port :: Maybe Int
optionGroupName :: Maybe Text
kmsKeyId :: Maybe Text
engineVersion :: Maybe Text
enableIAMDatabaseAuthentication :: Maybe Bool
enableCloudwatchLogsExports :: Maybe [Text]
deletionProtection :: Maybe Bool
databaseName :: Maybe Text
dbSubnetGroupName :: Maybe Text
dbClusterParameterGroupName :: Maybe Text
copyTagsToSnapshot :: Maybe Bool
availabilityZones :: Maybe [Text]
$sel:engine:RestoreDBClusterFromSnapshot' :: RestoreDBClusterFromSnapshot -> Text
$sel:snapshotIdentifier:RestoreDBClusterFromSnapshot' :: RestoreDBClusterFromSnapshot -> Text
$sel:dbClusterIdentifier:RestoreDBClusterFromSnapshot' :: RestoreDBClusterFromSnapshot -> Text
$sel:vpcSecurityGroupIds:RestoreDBClusterFromSnapshot' :: RestoreDBClusterFromSnapshot -> Maybe [Text]
$sel:tags:RestoreDBClusterFromSnapshot' :: RestoreDBClusterFromSnapshot -> Maybe [Tag]
$sel:serverlessV2ScalingConfiguration:RestoreDBClusterFromSnapshot' :: RestoreDBClusterFromSnapshot
-> Maybe ServerlessV2ScalingConfiguration
$sel:port:RestoreDBClusterFromSnapshot' :: RestoreDBClusterFromSnapshot -> Maybe Int
$sel:optionGroupName:RestoreDBClusterFromSnapshot' :: RestoreDBClusterFromSnapshot -> Maybe Text
$sel:kmsKeyId:RestoreDBClusterFromSnapshot' :: RestoreDBClusterFromSnapshot -> Maybe Text
$sel:engineVersion:RestoreDBClusterFromSnapshot' :: RestoreDBClusterFromSnapshot -> Maybe Text
$sel:enableIAMDatabaseAuthentication:RestoreDBClusterFromSnapshot' :: RestoreDBClusterFromSnapshot -> Maybe Bool
$sel:enableCloudwatchLogsExports:RestoreDBClusterFromSnapshot' :: RestoreDBClusterFromSnapshot -> Maybe [Text]
$sel:deletionProtection:RestoreDBClusterFromSnapshot' :: RestoreDBClusterFromSnapshot -> Maybe Bool
$sel:databaseName:RestoreDBClusterFromSnapshot' :: RestoreDBClusterFromSnapshot -> Maybe Text
$sel:dbSubnetGroupName:RestoreDBClusterFromSnapshot' :: RestoreDBClusterFromSnapshot -> Maybe Text
$sel:dbClusterParameterGroupName:RestoreDBClusterFromSnapshot' :: RestoreDBClusterFromSnapshot -> Maybe Text
$sel:copyTagsToSnapshot:RestoreDBClusterFromSnapshot' :: RestoreDBClusterFromSnapshot -> Maybe Bool
$sel:availabilityZones:RestoreDBClusterFromSnapshot' :: RestoreDBClusterFromSnapshot -> Maybe [Text]
..} =
    forall a. Monoid a => [a] -> a
Prelude.mconcat
      [ ByteString
"Action"
          forall a. ToQuery a => ByteString -> a -> QueryString
Data.=: ( ByteString
"RestoreDBClusterFromSnapshot" ::
                      Prelude.ByteString
                  ),
        ByteString
"Version"
          forall a. ToQuery a => ByteString -> a -> QueryString
Data.=: (ByteString
"2014-10-31" :: Prelude.ByteString),
        ByteString
"AvailabilityZones"
          forall a. ToQuery a => ByteString -> a -> QueryString
Data.=: forall a. ToQuery a => a -> QueryString
Data.toQuery
            ( forall a.
(IsList a, ToQuery (Item a)) =>
ByteString -> a -> QueryString
Data.toQueryList ByteString
"AvailabilityZone"
                forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
Prelude.<$> Maybe [Text]
availabilityZones
            ),
        ByteString
"CopyTagsToSnapshot" forall a. ToQuery a => ByteString -> a -> QueryString
Data.=: Maybe Bool
copyTagsToSnapshot,
        ByteString
"DBClusterParameterGroupName"
          forall a. ToQuery a => ByteString -> a -> QueryString
Data.=: Maybe Text
dbClusterParameterGroupName,
        ByteString
"DBSubnetGroupName" forall a. ToQuery a => ByteString -> a -> QueryString
Data.=: Maybe Text
dbSubnetGroupName,
        ByteString
"DatabaseName" forall a. ToQuery a => ByteString -> a -> QueryString
Data.=: Maybe Text
databaseName,
        ByteString
"DeletionProtection" forall a. ToQuery a => ByteString -> a -> QueryString
Data.=: Maybe Bool
deletionProtection,
        ByteString
"EnableCloudwatchLogsExports"
          forall a. ToQuery a => ByteString -> a -> QueryString
Data.=: forall a. ToQuery a => a -> QueryString
Data.toQuery
            ( forall a.
(IsList a, ToQuery (Item a)) =>
ByteString -> a -> QueryString
Data.toQueryList ByteString
"member"
                forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
Prelude.<$> Maybe [Text]
enableCloudwatchLogsExports
            ),
        ByteString
"EnableIAMDatabaseAuthentication"
          forall a. ToQuery a => ByteString -> a -> QueryString
Data.=: Maybe Bool
enableIAMDatabaseAuthentication,
        ByteString
"EngineVersion" forall a. ToQuery a => ByteString -> a -> QueryString
Data.=: Maybe Text
engineVersion,
        ByteString
"KmsKeyId" forall a. ToQuery a => ByteString -> a -> QueryString
Data.=: Maybe Text
kmsKeyId,
        ByteString
"OptionGroupName" forall a. ToQuery a => ByteString -> a -> QueryString
Data.=: Maybe Text
optionGroupName,
        ByteString
"Port" forall a. ToQuery a => ByteString -> a -> QueryString
Data.=: Maybe Int
port,
        ByteString
"ServerlessV2ScalingConfiguration"
          forall a. ToQuery a => ByteString -> a -> QueryString
Data.=: Maybe ServerlessV2ScalingConfiguration
serverlessV2ScalingConfiguration,
        ByteString
"Tags"
          forall a. ToQuery a => ByteString -> a -> QueryString
Data.=: forall a. ToQuery a => a -> QueryString
Data.toQuery
            (forall a.
(IsList a, ToQuery (Item a)) =>
ByteString -> a -> QueryString
Data.toQueryList ByteString
"Tag" forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
Prelude.<$> Maybe [Tag]
tags),
        ByteString
"VpcSecurityGroupIds"
          forall a. ToQuery a => ByteString -> a -> QueryString
Data.=: forall a. ToQuery a => a -> QueryString
Data.toQuery
            ( forall a.
(IsList a, ToQuery (Item a)) =>
ByteString -> a -> QueryString
Data.toQueryList ByteString
"VpcSecurityGroupId"
                forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
Prelude.<$> Maybe [Text]
vpcSecurityGroupIds
            ),
        ByteString
"DBClusterIdentifier" forall a. ToQuery a => ByteString -> a -> QueryString
Data.=: Text
dbClusterIdentifier,
        ByteString
"SnapshotIdentifier" forall a. ToQuery a => ByteString -> a -> QueryString
Data.=: Text
snapshotIdentifier,
        ByteString
"Engine" forall a. ToQuery a => ByteString -> a -> QueryString
Data.=: Text
engine
      ]

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

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

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

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

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