{-# 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.DocDbElastic.RestoreClusterFromSnapshot
-- Copyright   : (c) 2013-2023 Brendan Hay
-- License     : Mozilla Public License, v. 2.0.
-- Maintainer  : Brendan Hay
-- Stability   : auto-generated
-- Portability : non-portable (GHC extensions)
--
-- Restores a Elastic DocumentDB cluster from a snapshot.
module Amazonka.DocDbElastic.RestoreClusterFromSnapshot
  ( -- * Creating a Request
    RestoreClusterFromSnapshot (..),
    newRestoreClusterFromSnapshot,

    -- * Request Lenses
    restoreClusterFromSnapshot_kmsKeyId,
    restoreClusterFromSnapshot_subnetIds,
    restoreClusterFromSnapshot_tags,
    restoreClusterFromSnapshot_vpcSecurityGroupIds,
    restoreClusterFromSnapshot_clusterName,
    restoreClusterFromSnapshot_snapshotArn,

    -- * Destructuring the Response
    RestoreClusterFromSnapshotResponse (..),
    newRestoreClusterFromSnapshotResponse,

    -- * Response Lenses
    restoreClusterFromSnapshotResponse_httpStatus,
    restoreClusterFromSnapshotResponse_cluster,
  )
where

import qualified Amazonka.Core as Core
import qualified Amazonka.Core.Lens.Internal as Lens
import qualified Amazonka.Data as Data
import Amazonka.DocDbElastic.Types
import qualified Amazonka.Prelude as Prelude
import qualified Amazonka.Request as Request
import qualified Amazonka.Response as Response

-- | /See:/ 'newRestoreClusterFromSnapshot' smart constructor.
data RestoreClusterFromSnapshot = RestoreClusterFromSnapshot'
  { -- | The KMS key identifier to use to encrypt the new Elastic DocumentDB
    -- cluster.
    --
    -- The KMS key identifier is the Amazon Resource Name (ARN) for the KMS
    -- encryption key. If you are creating a cluster using the same Amazon
    -- account that owns this KMS encryption key, you can use the KMS key alias
    -- instead of the ARN as the KMS encryption key.
    --
    -- If an encryption key is not specified here, Elastic DocumentDB uses the
    -- default encryption key that KMS creates for your account. Your account
    -- has a different default encryption key for each Amazon Region.
    RestoreClusterFromSnapshot -> Maybe Text
kmsKeyId :: Prelude.Maybe Prelude.Text,
    -- | The Amazon EC2 subnet IDs for the Elastic DocumentDB cluster.
    RestoreClusterFromSnapshot -> Maybe [Text]
subnetIds :: Prelude.Maybe [Prelude.Text],
    -- | A list of the tag names to be assigned to the restored DB cluster, in
    -- the form of an array of key-value pairs in which the key is the tag name
    -- and the value is the key value.
    RestoreClusterFromSnapshot -> Maybe (HashMap Text Text)
tags :: Prelude.Maybe (Prelude.HashMap Prelude.Text Prelude.Text),
    -- | A list of EC2 VPC security groups to associate with the Elastic
    -- DocumentDB cluster.
    RestoreClusterFromSnapshot -> Maybe [Text]
vpcSecurityGroupIds :: Prelude.Maybe [Prelude.Text],
    -- | The name of the Elastic DocumentDB cluster.
    RestoreClusterFromSnapshot -> Text
clusterName :: Prelude.Text,
    -- | The arn of the Elastic DocumentDB snapshot.
    RestoreClusterFromSnapshot -> Text
snapshotArn :: Prelude.Text
  }
  deriving (RestoreClusterFromSnapshot -> RestoreClusterFromSnapshot -> Bool
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: RestoreClusterFromSnapshot -> RestoreClusterFromSnapshot -> Bool
$c/= :: RestoreClusterFromSnapshot -> RestoreClusterFromSnapshot -> Bool
== :: RestoreClusterFromSnapshot -> RestoreClusterFromSnapshot -> Bool
$c== :: RestoreClusterFromSnapshot -> RestoreClusterFromSnapshot -> Bool
Prelude.Eq, ReadPrec [RestoreClusterFromSnapshot]
ReadPrec RestoreClusterFromSnapshot
Int -> ReadS RestoreClusterFromSnapshot
ReadS [RestoreClusterFromSnapshot]
forall a.
(Int -> ReadS a)
-> ReadS [a] -> ReadPrec a -> ReadPrec [a] -> Read a
readListPrec :: ReadPrec [RestoreClusterFromSnapshot]
$creadListPrec :: ReadPrec [RestoreClusterFromSnapshot]
readPrec :: ReadPrec RestoreClusterFromSnapshot
$creadPrec :: ReadPrec RestoreClusterFromSnapshot
readList :: ReadS [RestoreClusterFromSnapshot]
$creadList :: ReadS [RestoreClusterFromSnapshot]
readsPrec :: Int -> ReadS RestoreClusterFromSnapshot
$creadsPrec :: Int -> ReadS RestoreClusterFromSnapshot
Prelude.Read, Int -> RestoreClusterFromSnapshot -> ShowS
[RestoreClusterFromSnapshot] -> ShowS
RestoreClusterFromSnapshot -> String
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [RestoreClusterFromSnapshot] -> ShowS
$cshowList :: [RestoreClusterFromSnapshot] -> ShowS
show :: RestoreClusterFromSnapshot -> String
$cshow :: RestoreClusterFromSnapshot -> String
showsPrec :: Int -> RestoreClusterFromSnapshot -> ShowS
$cshowsPrec :: Int -> RestoreClusterFromSnapshot -> ShowS
Prelude.Show, forall x.
Rep RestoreClusterFromSnapshot x -> RestoreClusterFromSnapshot
forall x.
RestoreClusterFromSnapshot -> Rep RestoreClusterFromSnapshot x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cto :: forall x.
Rep RestoreClusterFromSnapshot x -> RestoreClusterFromSnapshot
$cfrom :: forall x.
RestoreClusterFromSnapshot -> Rep RestoreClusterFromSnapshot x
Prelude.Generic)

-- |
-- Create a value of 'RestoreClusterFromSnapshot' 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:
--
-- 'kmsKeyId', 'restoreClusterFromSnapshot_kmsKeyId' - The KMS key identifier to use to encrypt the new Elastic DocumentDB
-- cluster.
--
-- The KMS key identifier is the Amazon Resource Name (ARN) for the KMS
-- encryption key. If you are creating a cluster using the same Amazon
-- account that owns this KMS encryption key, you can use the KMS key alias
-- instead of the ARN as the KMS encryption key.
--
-- If an encryption key is not specified here, Elastic DocumentDB uses the
-- default encryption key that KMS creates for your account. Your account
-- has a different default encryption key for each Amazon Region.
--
-- 'subnetIds', 'restoreClusterFromSnapshot_subnetIds' - The Amazon EC2 subnet IDs for the Elastic DocumentDB cluster.
--
-- 'tags', 'restoreClusterFromSnapshot_tags' - A list of the tag names to be assigned to the restored DB cluster, in
-- the form of an array of key-value pairs in which the key is the tag name
-- and the value is the key value.
--
-- 'vpcSecurityGroupIds', 'restoreClusterFromSnapshot_vpcSecurityGroupIds' - A list of EC2 VPC security groups to associate with the Elastic
-- DocumentDB cluster.
--
-- 'clusterName', 'restoreClusterFromSnapshot_clusterName' - The name of the Elastic DocumentDB cluster.
--
-- 'snapshotArn', 'restoreClusterFromSnapshot_snapshotArn' - The arn of the Elastic DocumentDB snapshot.
newRestoreClusterFromSnapshot ::
  -- | 'clusterName'
  Prelude.Text ->
  -- | 'snapshotArn'
  Prelude.Text ->
  RestoreClusterFromSnapshot
newRestoreClusterFromSnapshot :: Text -> Text -> RestoreClusterFromSnapshot
newRestoreClusterFromSnapshot
  Text
pClusterName_
  Text
pSnapshotArn_ =
    RestoreClusterFromSnapshot'
      { $sel:kmsKeyId:RestoreClusterFromSnapshot' :: Maybe Text
kmsKeyId =
          forall a. Maybe a
Prelude.Nothing,
        $sel:subnetIds:RestoreClusterFromSnapshot' :: Maybe [Text]
subnetIds = forall a. Maybe a
Prelude.Nothing,
        $sel:tags:RestoreClusterFromSnapshot' :: Maybe (HashMap Text Text)
tags = forall a. Maybe a
Prelude.Nothing,
        $sel:vpcSecurityGroupIds:RestoreClusterFromSnapshot' :: Maybe [Text]
vpcSecurityGroupIds = forall a. Maybe a
Prelude.Nothing,
        $sel:clusterName:RestoreClusterFromSnapshot' :: Text
clusterName = Text
pClusterName_,
        $sel:snapshotArn:RestoreClusterFromSnapshot' :: Text
snapshotArn = Text
pSnapshotArn_
      }

-- | The KMS key identifier to use to encrypt the new Elastic DocumentDB
-- cluster.
--
-- The KMS key identifier is the Amazon Resource Name (ARN) for the KMS
-- encryption key. If you are creating a cluster using the same Amazon
-- account that owns this KMS encryption key, you can use the KMS key alias
-- instead of the ARN as the KMS encryption key.
--
-- If an encryption key is not specified here, Elastic DocumentDB uses the
-- default encryption key that KMS creates for your account. Your account
-- has a different default encryption key for each Amazon Region.
restoreClusterFromSnapshot_kmsKeyId :: Lens.Lens' RestoreClusterFromSnapshot (Prelude.Maybe Prelude.Text)
restoreClusterFromSnapshot_kmsKeyId :: Lens' RestoreClusterFromSnapshot (Maybe Text)
restoreClusterFromSnapshot_kmsKeyId = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\RestoreClusterFromSnapshot' {Maybe Text
kmsKeyId :: Maybe Text
$sel:kmsKeyId:RestoreClusterFromSnapshot' :: RestoreClusterFromSnapshot -> Maybe Text
kmsKeyId} -> Maybe Text
kmsKeyId) (\s :: RestoreClusterFromSnapshot
s@RestoreClusterFromSnapshot' {} Maybe Text
a -> RestoreClusterFromSnapshot
s {$sel:kmsKeyId:RestoreClusterFromSnapshot' :: Maybe Text
kmsKeyId = Maybe Text
a} :: RestoreClusterFromSnapshot)

-- | The Amazon EC2 subnet IDs for the Elastic DocumentDB cluster.
restoreClusterFromSnapshot_subnetIds :: Lens.Lens' RestoreClusterFromSnapshot (Prelude.Maybe [Prelude.Text])
restoreClusterFromSnapshot_subnetIds :: Lens' RestoreClusterFromSnapshot (Maybe [Text])
restoreClusterFromSnapshot_subnetIds = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\RestoreClusterFromSnapshot' {Maybe [Text]
subnetIds :: Maybe [Text]
$sel:subnetIds:RestoreClusterFromSnapshot' :: RestoreClusterFromSnapshot -> Maybe [Text]
subnetIds} -> Maybe [Text]
subnetIds) (\s :: RestoreClusterFromSnapshot
s@RestoreClusterFromSnapshot' {} Maybe [Text]
a -> RestoreClusterFromSnapshot
s {$sel:subnetIds:RestoreClusterFromSnapshot' :: Maybe [Text]
subnetIds = Maybe [Text]
a} :: RestoreClusterFromSnapshot) 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 the tag names to be assigned to the restored DB cluster, in
-- the form of an array of key-value pairs in which the key is the tag name
-- and the value is the key value.
restoreClusterFromSnapshot_tags :: Lens.Lens' RestoreClusterFromSnapshot (Prelude.Maybe (Prelude.HashMap Prelude.Text Prelude.Text))
restoreClusterFromSnapshot_tags :: Lens' RestoreClusterFromSnapshot (Maybe (HashMap Text Text))
restoreClusterFromSnapshot_tags = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\RestoreClusterFromSnapshot' {Maybe (HashMap Text Text)
tags :: Maybe (HashMap Text Text)
$sel:tags:RestoreClusterFromSnapshot' :: RestoreClusterFromSnapshot -> Maybe (HashMap Text Text)
tags} -> Maybe (HashMap Text Text)
tags) (\s :: RestoreClusterFromSnapshot
s@RestoreClusterFromSnapshot' {} Maybe (HashMap Text Text)
a -> RestoreClusterFromSnapshot
s {$sel:tags:RestoreClusterFromSnapshot' :: Maybe (HashMap Text Text)
tags = Maybe (HashMap Text Text)
a} :: RestoreClusterFromSnapshot) 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 EC2 VPC security groups to associate with the Elastic
-- DocumentDB cluster.
restoreClusterFromSnapshot_vpcSecurityGroupIds :: Lens.Lens' RestoreClusterFromSnapshot (Prelude.Maybe [Prelude.Text])
restoreClusterFromSnapshot_vpcSecurityGroupIds :: Lens' RestoreClusterFromSnapshot (Maybe [Text])
restoreClusterFromSnapshot_vpcSecurityGroupIds = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\RestoreClusterFromSnapshot' {Maybe [Text]
vpcSecurityGroupIds :: Maybe [Text]
$sel:vpcSecurityGroupIds:RestoreClusterFromSnapshot' :: RestoreClusterFromSnapshot -> Maybe [Text]
vpcSecurityGroupIds} -> Maybe [Text]
vpcSecurityGroupIds) (\s :: RestoreClusterFromSnapshot
s@RestoreClusterFromSnapshot' {} Maybe [Text]
a -> RestoreClusterFromSnapshot
s {$sel:vpcSecurityGroupIds:RestoreClusterFromSnapshot' :: Maybe [Text]
vpcSecurityGroupIds = Maybe [Text]
a} :: RestoreClusterFromSnapshot) 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 Elastic DocumentDB cluster.
restoreClusterFromSnapshot_clusterName :: Lens.Lens' RestoreClusterFromSnapshot Prelude.Text
restoreClusterFromSnapshot_clusterName :: Lens' RestoreClusterFromSnapshot Text
restoreClusterFromSnapshot_clusterName = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\RestoreClusterFromSnapshot' {Text
clusterName :: Text
$sel:clusterName:RestoreClusterFromSnapshot' :: RestoreClusterFromSnapshot -> Text
clusterName} -> Text
clusterName) (\s :: RestoreClusterFromSnapshot
s@RestoreClusterFromSnapshot' {} Text
a -> RestoreClusterFromSnapshot
s {$sel:clusterName:RestoreClusterFromSnapshot' :: Text
clusterName = Text
a} :: RestoreClusterFromSnapshot)

-- | The arn of the Elastic DocumentDB snapshot.
restoreClusterFromSnapshot_snapshotArn :: Lens.Lens' RestoreClusterFromSnapshot Prelude.Text
restoreClusterFromSnapshot_snapshotArn :: Lens' RestoreClusterFromSnapshot Text
restoreClusterFromSnapshot_snapshotArn = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\RestoreClusterFromSnapshot' {Text
snapshotArn :: Text
$sel:snapshotArn:RestoreClusterFromSnapshot' :: RestoreClusterFromSnapshot -> Text
snapshotArn} -> Text
snapshotArn) (\s :: RestoreClusterFromSnapshot
s@RestoreClusterFromSnapshot' {} Text
a -> RestoreClusterFromSnapshot
s {$sel:snapshotArn:RestoreClusterFromSnapshot' :: Text
snapshotArn = Text
a} :: RestoreClusterFromSnapshot)

instance Core.AWSRequest RestoreClusterFromSnapshot where
  type
    AWSResponse RestoreClusterFromSnapshot =
      RestoreClusterFromSnapshotResponse
  request :: (Service -> Service)
-> RestoreClusterFromSnapshot -> Request RestoreClusterFromSnapshot
request Service -> Service
overrides =
    forall a. (ToRequest a, ToJSON a) => Service -> a -> Request a
Request.postJSON (Service -> Service
overrides Service
defaultService)
  response :: forall (m :: * -> *).
MonadResource m =>
(ByteStringLazy -> IO ByteStringLazy)
-> Service
-> Proxy RestoreClusterFromSnapshot
-> ClientResponse ClientBody
-> m (Either
        Error (ClientResponse (AWSResponse RestoreClusterFromSnapshot)))
response =
    forall (m :: * -> *) a.
MonadResource m =>
(Int -> ResponseHeaders -> Object -> Either String (AWSResponse a))
-> (ByteStringLazy -> IO ByteStringLazy)
-> Service
-> Proxy a
-> ClientResponse ClientBody
-> m (Either Error (ClientResponse (AWSResponse a)))
Response.receiveJSON
      ( \Int
s ResponseHeaders
h Object
x ->
          Int -> Cluster -> RestoreClusterFromSnapshotResponse
RestoreClusterFromSnapshotResponse'
            forall (f :: * -> *) a b. Functor 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))
            forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
Prelude.<*> (Object
x forall a. FromJSON a => Object -> Key -> Either String a
Data..:> Key
"cluster")
      )

instance Prelude.Hashable RestoreClusterFromSnapshot where
  hashWithSalt :: Int -> RestoreClusterFromSnapshot -> Int
hashWithSalt Int
_salt RestoreClusterFromSnapshot' {Maybe [Text]
Maybe Text
Maybe (HashMap Text Text)
Text
snapshotArn :: Text
clusterName :: Text
vpcSecurityGroupIds :: Maybe [Text]
tags :: Maybe (HashMap Text Text)
subnetIds :: Maybe [Text]
kmsKeyId :: Maybe Text
$sel:snapshotArn:RestoreClusterFromSnapshot' :: RestoreClusterFromSnapshot -> Text
$sel:clusterName:RestoreClusterFromSnapshot' :: RestoreClusterFromSnapshot -> Text
$sel:vpcSecurityGroupIds:RestoreClusterFromSnapshot' :: RestoreClusterFromSnapshot -> Maybe [Text]
$sel:tags:RestoreClusterFromSnapshot' :: RestoreClusterFromSnapshot -> Maybe (HashMap Text Text)
$sel:subnetIds:RestoreClusterFromSnapshot' :: RestoreClusterFromSnapshot -> Maybe [Text]
$sel:kmsKeyId:RestoreClusterFromSnapshot' :: RestoreClusterFromSnapshot -> Maybe Text
..} =
    Int
_salt
      forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Maybe Text
kmsKeyId
      forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Maybe [Text]
subnetIds
      forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Maybe (HashMap Text Text)
tags
      forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Maybe [Text]
vpcSecurityGroupIds
      forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Text
clusterName
      forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Text
snapshotArn

instance Prelude.NFData RestoreClusterFromSnapshot where
  rnf :: RestoreClusterFromSnapshot -> ()
rnf RestoreClusterFromSnapshot' {Maybe [Text]
Maybe Text
Maybe (HashMap Text Text)
Text
snapshotArn :: Text
clusterName :: Text
vpcSecurityGroupIds :: Maybe [Text]
tags :: Maybe (HashMap Text Text)
subnetIds :: Maybe [Text]
kmsKeyId :: Maybe Text
$sel:snapshotArn:RestoreClusterFromSnapshot' :: RestoreClusterFromSnapshot -> Text
$sel:clusterName:RestoreClusterFromSnapshot' :: RestoreClusterFromSnapshot -> Text
$sel:vpcSecurityGroupIds:RestoreClusterFromSnapshot' :: RestoreClusterFromSnapshot -> Maybe [Text]
$sel:tags:RestoreClusterFromSnapshot' :: RestoreClusterFromSnapshot -> Maybe (HashMap Text Text)
$sel:subnetIds:RestoreClusterFromSnapshot' :: RestoreClusterFromSnapshot -> Maybe [Text]
$sel:kmsKeyId:RestoreClusterFromSnapshot' :: RestoreClusterFromSnapshot -> Maybe Text
..} =
    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]
subnetIds
      seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf Maybe (HashMap Text Text)
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
clusterName
      seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf Text
snapshotArn

instance Data.ToHeaders RestoreClusterFromSnapshot where
  toHeaders :: RestoreClusterFromSnapshot -> ResponseHeaders
toHeaders =
    forall a b. a -> b -> a
Prelude.const
      ( forall a. Monoid a => [a] -> a
Prelude.mconcat
          [ HeaderName
"Content-Type"
              forall a. ToHeader a => HeaderName -> a -> ResponseHeaders
Data.=# ( ByteString
"application/x-amz-json-1.1" ::
                          Prelude.ByteString
                      )
          ]
      )

instance Data.ToJSON RestoreClusterFromSnapshot where
  toJSON :: RestoreClusterFromSnapshot -> Value
toJSON RestoreClusterFromSnapshot' {Maybe [Text]
Maybe Text
Maybe (HashMap Text Text)
Text
snapshotArn :: Text
clusterName :: Text
vpcSecurityGroupIds :: Maybe [Text]
tags :: Maybe (HashMap Text Text)
subnetIds :: Maybe [Text]
kmsKeyId :: Maybe Text
$sel:snapshotArn:RestoreClusterFromSnapshot' :: RestoreClusterFromSnapshot -> Text
$sel:clusterName:RestoreClusterFromSnapshot' :: RestoreClusterFromSnapshot -> Text
$sel:vpcSecurityGroupIds:RestoreClusterFromSnapshot' :: RestoreClusterFromSnapshot -> Maybe [Text]
$sel:tags:RestoreClusterFromSnapshot' :: RestoreClusterFromSnapshot -> Maybe (HashMap Text Text)
$sel:subnetIds:RestoreClusterFromSnapshot' :: RestoreClusterFromSnapshot -> Maybe [Text]
$sel:kmsKeyId:RestoreClusterFromSnapshot' :: RestoreClusterFromSnapshot -> Maybe Text
..} =
    [Pair] -> Value
Data.object
      ( forall a. [Maybe a] -> [a]
Prelude.catMaybes
          [ (Key
"kmsKeyId" forall kv v. (KeyValue kv, ToJSON v) => Key -> v -> kv
Data..=) forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
Prelude.<$> Maybe Text
kmsKeyId,
            (Key
"subnetIds" forall kv v. (KeyValue kv, ToJSON v) => Key -> v -> kv
Data..=) forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
Prelude.<$> Maybe [Text]
subnetIds,
            (Key
"tags" forall kv v. (KeyValue kv, ToJSON v) => Key -> v -> kv
Data..=) forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
Prelude.<$> Maybe (HashMap Text Text)
tags,
            (Key
"vpcSecurityGroupIds" forall kv v. (KeyValue kv, ToJSON v) => Key -> v -> kv
Data..=)
              forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
Prelude.<$> Maybe [Text]
vpcSecurityGroupIds,
            forall a. a -> Maybe a
Prelude.Just (Key
"clusterName" forall kv v. (KeyValue kv, ToJSON v) => Key -> v -> kv
Data..= Text
clusterName)
          ]
      )

instance Data.ToPath RestoreClusterFromSnapshot where
  toPath :: RestoreClusterFromSnapshot -> ByteString
toPath RestoreClusterFromSnapshot' {Maybe [Text]
Maybe Text
Maybe (HashMap Text Text)
Text
snapshotArn :: Text
clusterName :: Text
vpcSecurityGroupIds :: Maybe [Text]
tags :: Maybe (HashMap Text Text)
subnetIds :: Maybe [Text]
kmsKeyId :: Maybe Text
$sel:snapshotArn:RestoreClusterFromSnapshot' :: RestoreClusterFromSnapshot -> Text
$sel:clusterName:RestoreClusterFromSnapshot' :: RestoreClusterFromSnapshot -> Text
$sel:vpcSecurityGroupIds:RestoreClusterFromSnapshot' :: RestoreClusterFromSnapshot -> Maybe [Text]
$sel:tags:RestoreClusterFromSnapshot' :: RestoreClusterFromSnapshot -> Maybe (HashMap Text Text)
$sel:subnetIds:RestoreClusterFromSnapshot' :: RestoreClusterFromSnapshot -> Maybe [Text]
$sel:kmsKeyId:RestoreClusterFromSnapshot' :: RestoreClusterFromSnapshot -> Maybe Text
..} =
    forall a. Monoid a => [a] -> a
Prelude.mconcat
      [ ByteString
"/cluster-snapshot/",
        forall a. ToByteString a => a -> ByteString
Data.toBS Text
snapshotArn,
        ByteString
"/restore"
      ]

instance Data.ToQuery RestoreClusterFromSnapshot where
  toQuery :: RestoreClusterFromSnapshot -> QueryString
toQuery = forall a b. a -> b -> a
Prelude.const forall a. Monoid a => a
Prelude.mempty

-- | /See:/ 'newRestoreClusterFromSnapshotResponse' smart constructor.
data RestoreClusterFromSnapshotResponse = RestoreClusterFromSnapshotResponse'
  { -- | The response's http status code.
    RestoreClusterFromSnapshotResponse -> Int
httpStatus :: Prelude.Int,
    -- | Returns information about a the restored Elastic DocumentDB cluster.
    RestoreClusterFromSnapshotResponse -> Cluster
cluster :: Cluster
  }
  deriving (RestoreClusterFromSnapshotResponse
-> RestoreClusterFromSnapshotResponse -> Bool
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: RestoreClusterFromSnapshotResponse
-> RestoreClusterFromSnapshotResponse -> Bool
$c/= :: RestoreClusterFromSnapshotResponse
-> RestoreClusterFromSnapshotResponse -> Bool
== :: RestoreClusterFromSnapshotResponse
-> RestoreClusterFromSnapshotResponse -> Bool
$c== :: RestoreClusterFromSnapshotResponse
-> RestoreClusterFromSnapshotResponse -> Bool
Prelude.Eq, ReadPrec [RestoreClusterFromSnapshotResponse]
ReadPrec RestoreClusterFromSnapshotResponse
Int -> ReadS RestoreClusterFromSnapshotResponse
ReadS [RestoreClusterFromSnapshotResponse]
forall a.
(Int -> ReadS a)
-> ReadS [a] -> ReadPrec a -> ReadPrec [a] -> Read a
readListPrec :: ReadPrec [RestoreClusterFromSnapshotResponse]
$creadListPrec :: ReadPrec [RestoreClusterFromSnapshotResponse]
readPrec :: ReadPrec RestoreClusterFromSnapshotResponse
$creadPrec :: ReadPrec RestoreClusterFromSnapshotResponse
readList :: ReadS [RestoreClusterFromSnapshotResponse]
$creadList :: ReadS [RestoreClusterFromSnapshotResponse]
readsPrec :: Int -> ReadS RestoreClusterFromSnapshotResponse
$creadsPrec :: Int -> ReadS RestoreClusterFromSnapshotResponse
Prelude.Read, Int -> RestoreClusterFromSnapshotResponse -> ShowS
[RestoreClusterFromSnapshotResponse] -> ShowS
RestoreClusterFromSnapshotResponse -> String
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [RestoreClusterFromSnapshotResponse] -> ShowS
$cshowList :: [RestoreClusterFromSnapshotResponse] -> ShowS
show :: RestoreClusterFromSnapshotResponse -> String
$cshow :: RestoreClusterFromSnapshotResponse -> String
showsPrec :: Int -> RestoreClusterFromSnapshotResponse -> ShowS
$cshowsPrec :: Int -> RestoreClusterFromSnapshotResponse -> ShowS
Prelude.Show, forall x.
Rep RestoreClusterFromSnapshotResponse x
-> RestoreClusterFromSnapshotResponse
forall x.
RestoreClusterFromSnapshotResponse
-> Rep RestoreClusterFromSnapshotResponse x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cto :: forall x.
Rep RestoreClusterFromSnapshotResponse x
-> RestoreClusterFromSnapshotResponse
$cfrom :: forall x.
RestoreClusterFromSnapshotResponse
-> Rep RestoreClusterFromSnapshotResponse x
Prelude.Generic)

-- |
-- Create a value of 'RestoreClusterFromSnapshotResponse' 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:
--
-- 'httpStatus', 'restoreClusterFromSnapshotResponse_httpStatus' - The response's http status code.
--
-- 'cluster', 'restoreClusterFromSnapshotResponse_cluster' - Returns information about a the restored Elastic DocumentDB cluster.
newRestoreClusterFromSnapshotResponse ::
  -- | 'httpStatus'
  Prelude.Int ->
  -- | 'cluster'
  Cluster ->
  RestoreClusterFromSnapshotResponse
newRestoreClusterFromSnapshotResponse :: Int -> Cluster -> RestoreClusterFromSnapshotResponse
newRestoreClusterFromSnapshotResponse
  Int
pHttpStatus_
  Cluster
pCluster_ =
    RestoreClusterFromSnapshotResponse'
      { $sel:httpStatus:RestoreClusterFromSnapshotResponse' :: Int
httpStatus =
          Int
pHttpStatus_,
        $sel:cluster:RestoreClusterFromSnapshotResponse' :: Cluster
cluster = Cluster
pCluster_
      }

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

-- | Returns information about a the restored Elastic DocumentDB cluster.
restoreClusterFromSnapshotResponse_cluster :: Lens.Lens' RestoreClusterFromSnapshotResponse Cluster
restoreClusterFromSnapshotResponse_cluster :: Lens' RestoreClusterFromSnapshotResponse Cluster
restoreClusterFromSnapshotResponse_cluster = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\RestoreClusterFromSnapshotResponse' {Cluster
cluster :: Cluster
$sel:cluster:RestoreClusterFromSnapshotResponse' :: RestoreClusterFromSnapshotResponse -> Cluster
cluster} -> Cluster
cluster) (\s :: RestoreClusterFromSnapshotResponse
s@RestoreClusterFromSnapshotResponse' {} Cluster
a -> RestoreClusterFromSnapshotResponse
s {$sel:cluster:RestoreClusterFromSnapshotResponse' :: Cluster
cluster = Cluster
a} :: RestoreClusterFromSnapshotResponse)

instance
  Prelude.NFData
    RestoreClusterFromSnapshotResponse
  where
  rnf :: RestoreClusterFromSnapshotResponse -> ()
rnf RestoreClusterFromSnapshotResponse' {Int
Cluster
cluster :: Cluster
httpStatus :: Int
$sel:cluster:RestoreClusterFromSnapshotResponse' :: RestoreClusterFromSnapshotResponse -> Cluster
$sel:httpStatus:RestoreClusterFromSnapshotResponse' :: RestoreClusterFromSnapshotResponse -> Int
..} =
    forall a. NFData a => a -> ()
Prelude.rnf Int
httpStatus
      seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf Cluster
cluster