{-# 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.DocumentDB.CreateDBClusterSnapshot
-- 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 snapshot of a cluster.
module Amazonka.DocumentDB.CreateDBClusterSnapshot
  ( -- * Creating a Request
    CreateDBClusterSnapshot (..),
    newCreateDBClusterSnapshot,

    -- * Request Lenses
    createDBClusterSnapshot_tags,
    createDBClusterSnapshot_dbClusterSnapshotIdentifier,
    createDBClusterSnapshot_dbClusterIdentifier,

    -- * Destructuring the Response
    CreateDBClusterSnapshotResponse (..),
    newCreateDBClusterSnapshotResponse,

    -- * Response Lenses
    createDBClusterSnapshotResponse_dbClusterSnapshot,
    createDBClusterSnapshotResponse_httpStatus,
  )
where

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

-- | Represents the input of CreateDBClusterSnapshot.
--
-- /See:/ 'newCreateDBClusterSnapshot' smart constructor.
data CreateDBClusterSnapshot = CreateDBClusterSnapshot'
  { -- | The tags to be assigned to the cluster snapshot.
    CreateDBClusterSnapshot -> Maybe [Tag]
tags :: Prelude.Maybe [Tag],
    -- | The identifier of the cluster snapshot. This parameter is stored as a
    -- lowercase string.
    --
    -- Constraints:
    --
    -- -   Must contain from 1 to 63 letters, numbers, or hyphens.
    --
    -- -   The first character must be a letter.
    --
    -- -   Cannot end with a hyphen or contain two consecutive hyphens.
    --
    -- Example: @my-cluster-snapshot1@
    CreateDBClusterSnapshot -> Text
dbClusterSnapshotIdentifier :: Prelude.Text,
    -- | The identifier of the cluster to create a snapshot for. This parameter
    -- is not case sensitive.
    --
    -- Constraints:
    --
    -- -   Must match the identifier of an existing @DBCluster@.
    --
    -- Example: @my-cluster@
    CreateDBClusterSnapshot -> Text
dbClusterIdentifier :: Prelude.Text
  }
  deriving (CreateDBClusterSnapshot -> CreateDBClusterSnapshot -> Bool
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: CreateDBClusterSnapshot -> CreateDBClusterSnapshot -> Bool
$c/= :: CreateDBClusterSnapshot -> CreateDBClusterSnapshot -> Bool
== :: CreateDBClusterSnapshot -> CreateDBClusterSnapshot -> Bool
$c== :: CreateDBClusterSnapshot -> CreateDBClusterSnapshot -> Bool
Prelude.Eq, ReadPrec [CreateDBClusterSnapshot]
ReadPrec CreateDBClusterSnapshot
Int -> ReadS CreateDBClusterSnapshot
ReadS [CreateDBClusterSnapshot]
forall a.
(Int -> ReadS a)
-> ReadS [a] -> ReadPrec a -> ReadPrec [a] -> Read a
readListPrec :: ReadPrec [CreateDBClusterSnapshot]
$creadListPrec :: ReadPrec [CreateDBClusterSnapshot]
readPrec :: ReadPrec CreateDBClusterSnapshot
$creadPrec :: ReadPrec CreateDBClusterSnapshot
readList :: ReadS [CreateDBClusterSnapshot]
$creadList :: ReadS [CreateDBClusterSnapshot]
readsPrec :: Int -> ReadS CreateDBClusterSnapshot
$creadsPrec :: Int -> ReadS CreateDBClusterSnapshot
Prelude.Read, Int -> CreateDBClusterSnapshot -> ShowS
[CreateDBClusterSnapshot] -> ShowS
CreateDBClusterSnapshot -> String
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [CreateDBClusterSnapshot] -> ShowS
$cshowList :: [CreateDBClusterSnapshot] -> ShowS
show :: CreateDBClusterSnapshot -> String
$cshow :: CreateDBClusterSnapshot -> String
showsPrec :: Int -> CreateDBClusterSnapshot -> ShowS
$cshowsPrec :: Int -> CreateDBClusterSnapshot -> ShowS
Prelude.Show, forall x. Rep CreateDBClusterSnapshot x -> CreateDBClusterSnapshot
forall x. CreateDBClusterSnapshot -> Rep CreateDBClusterSnapshot x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cto :: forall x. Rep CreateDBClusterSnapshot x -> CreateDBClusterSnapshot
$cfrom :: forall x. CreateDBClusterSnapshot -> Rep CreateDBClusterSnapshot x
Prelude.Generic)

-- |
-- Create a value of 'CreateDBClusterSnapshot' 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:
--
-- 'tags', 'createDBClusterSnapshot_tags' - The tags to be assigned to the cluster snapshot.
--
-- 'dbClusterSnapshotIdentifier', 'createDBClusterSnapshot_dbClusterSnapshotIdentifier' - The identifier of the cluster snapshot. This parameter is stored as a
-- lowercase string.
--
-- Constraints:
--
-- -   Must contain from 1 to 63 letters, numbers, or hyphens.
--
-- -   The first character must be a letter.
--
-- -   Cannot end with a hyphen or contain two consecutive hyphens.
--
-- Example: @my-cluster-snapshot1@
--
-- 'dbClusterIdentifier', 'createDBClusterSnapshot_dbClusterIdentifier' - The identifier of the cluster to create a snapshot for. This parameter
-- is not case sensitive.
--
-- Constraints:
--
-- -   Must match the identifier of an existing @DBCluster@.
--
-- Example: @my-cluster@
newCreateDBClusterSnapshot ::
  -- | 'dbClusterSnapshotIdentifier'
  Prelude.Text ->
  -- | 'dbClusterIdentifier'
  Prelude.Text ->
  CreateDBClusterSnapshot
newCreateDBClusterSnapshot :: Text -> Text -> CreateDBClusterSnapshot
newCreateDBClusterSnapshot
  Text
pDBClusterSnapshotIdentifier_
  Text
pDBClusterIdentifier_ =
    CreateDBClusterSnapshot'
      { $sel:tags:CreateDBClusterSnapshot' :: Maybe [Tag]
tags = forall a. Maybe a
Prelude.Nothing,
        $sel:dbClusterSnapshotIdentifier:CreateDBClusterSnapshot' :: Text
dbClusterSnapshotIdentifier =
          Text
pDBClusterSnapshotIdentifier_,
        $sel:dbClusterIdentifier:CreateDBClusterSnapshot' :: Text
dbClusterIdentifier = Text
pDBClusterIdentifier_
      }

-- | The tags to be assigned to the cluster snapshot.
createDBClusterSnapshot_tags :: Lens.Lens' CreateDBClusterSnapshot (Prelude.Maybe [Tag])
createDBClusterSnapshot_tags :: Lens' CreateDBClusterSnapshot (Maybe [Tag])
createDBClusterSnapshot_tags = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\CreateDBClusterSnapshot' {Maybe [Tag]
tags :: Maybe [Tag]
$sel:tags:CreateDBClusterSnapshot' :: CreateDBClusterSnapshot -> Maybe [Tag]
tags} -> Maybe [Tag]
tags) (\s :: CreateDBClusterSnapshot
s@CreateDBClusterSnapshot' {} Maybe [Tag]
a -> CreateDBClusterSnapshot
s {$sel:tags:CreateDBClusterSnapshot' :: Maybe [Tag]
tags = Maybe [Tag]
a} :: CreateDBClusterSnapshot) 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 identifier of the cluster snapshot. This parameter is stored as a
-- lowercase string.
--
-- Constraints:
--
-- -   Must contain from 1 to 63 letters, numbers, or hyphens.
--
-- -   The first character must be a letter.
--
-- -   Cannot end with a hyphen or contain two consecutive hyphens.
--
-- Example: @my-cluster-snapshot1@
createDBClusterSnapshot_dbClusterSnapshotIdentifier :: Lens.Lens' CreateDBClusterSnapshot Prelude.Text
createDBClusterSnapshot_dbClusterSnapshotIdentifier :: Lens' CreateDBClusterSnapshot Text
createDBClusterSnapshot_dbClusterSnapshotIdentifier = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\CreateDBClusterSnapshot' {Text
dbClusterSnapshotIdentifier :: Text
$sel:dbClusterSnapshotIdentifier:CreateDBClusterSnapshot' :: CreateDBClusterSnapshot -> Text
dbClusterSnapshotIdentifier} -> Text
dbClusterSnapshotIdentifier) (\s :: CreateDBClusterSnapshot
s@CreateDBClusterSnapshot' {} Text
a -> CreateDBClusterSnapshot
s {$sel:dbClusterSnapshotIdentifier:CreateDBClusterSnapshot' :: Text
dbClusterSnapshotIdentifier = Text
a} :: CreateDBClusterSnapshot)

-- | The identifier of the cluster to create a snapshot for. This parameter
-- is not case sensitive.
--
-- Constraints:
--
-- -   Must match the identifier of an existing @DBCluster@.
--
-- Example: @my-cluster@
createDBClusterSnapshot_dbClusterIdentifier :: Lens.Lens' CreateDBClusterSnapshot Prelude.Text
createDBClusterSnapshot_dbClusterIdentifier :: Lens' CreateDBClusterSnapshot Text
createDBClusterSnapshot_dbClusterIdentifier = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\CreateDBClusterSnapshot' {Text
dbClusterIdentifier :: Text
$sel:dbClusterIdentifier:CreateDBClusterSnapshot' :: CreateDBClusterSnapshot -> Text
dbClusterIdentifier} -> Text
dbClusterIdentifier) (\s :: CreateDBClusterSnapshot
s@CreateDBClusterSnapshot' {} Text
a -> CreateDBClusterSnapshot
s {$sel:dbClusterIdentifier:CreateDBClusterSnapshot' :: Text
dbClusterIdentifier = Text
a} :: CreateDBClusterSnapshot)

instance Core.AWSRequest CreateDBClusterSnapshot where
  type
    AWSResponse CreateDBClusterSnapshot =
      CreateDBClusterSnapshotResponse
  request :: (Service -> Service)
-> CreateDBClusterSnapshot -> Request CreateDBClusterSnapshot
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 CreateDBClusterSnapshot
-> ClientResponse ClientBody
-> m (Either
        Error (ClientResponse (AWSResponse CreateDBClusterSnapshot)))
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
"CreateDBClusterSnapshotResult"
      ( \Int
s ResponseHeaders
h [Node]
x ->
          Maybe DBClusterSnapshot -> Int -> CreateDBClusterSnapshotResponse
CreateDBClusterSnapshotResponse'
            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
"DBClusterSnapshot")
            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 CreateDBClusterSnapshot where
  hashWithSalt :: Int -> CreateDBClusterSnapshot -> Int
hashWithSalt Int
_salt CreateDBClusterSnapshot' {Maybe [Tag]
Text
dbClusterIdentifier :: Text
dbClusterSnapshotIdentifier :: Text
tags :: Maybe [Tag]
$sel:dbClusterIdentifier:CreateDBClusterSnapshot' :: CreateDBClusterSnapshot -> Text
$sel:dbClusterSnapshotIdentifier:CreateDBClusterSnapshot' :: CreateDBClusterSnapshot -> Text
$sel:tags:CreateDBClusterSnapshot' :: CreateDBClusterSnapshot -> Maybe [Tag]
..} =
    Int
_salt
      forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Maybe [Tag]
tags
      forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Text
dbClusterSnapshotIdentifier
      forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Text
dbClusterIdentifier

instance Prelude.NFData CreateDBClusterSnapshot where
  rnf :: CreateDBClusterSnapshot -> ()
rnf CreateDBClusterSnapshot' {Maybe [Tag]
Text
dbClusterIdentifier :: Text
dbClusterSnapshotIdentifier :: Text
tags :: Maybe [Tag]
$sel:dbClusterIdentifier:CreateDBClusterSnapshot' :: CreateDBClusterSnapshot -> Text
$sel:dbClusterSnapshotIdentifier:CreateDBClusterSnapshot' :: CreateDBClusterSnapshot -> Text
$sel:tags:CreateDBClusterSnapshot' :: CreateDBClusterSnapshot -> Maybe [Tag]
..} =
    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 Text
dbClusterSnapshotIdentifier
      seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf Text
dbClusterIdentifier

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

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

instance Data.ToQuery CreateDBClusterSnapshot where
  toQuery :: CreateDBClusterSnapshot -> QueryString
toQuery CreateDBClusterSnapshot' {Maybe [Tag]
Text
dbClusterIdentifier :: Text
dbClusterSnapshotIdentifier :: Text
tags :: Maybe [Tag]
$sel:dbClusterIdentifier:CreateDBClusterSnapshot' :: CreateDBClusterSnapshot -> Text
$sel:dbClusterSnapshotIdentifier:CreateDBClusterSnapshot' :: CreateDBClusterSnapshot -> Text
$sel:tags:CreateDBClusterSnapshot' :: CreateDBClusterSnapshot -> Maybe [Tag]
..} =
    forall a. Monoid a => [a] -> a
Prelude.mconcat
      [ ByteString
"Action"
          forall a. ToQuery a => ByteString -> a -> QueryString
Data.=: (ByteString
"CreateDBClusterSnapshot" :: Prelude.ByteString),
        ByteString
"Version"
          forall a. ToQuery a => ByteString -> a -> QueryString
Data.=: (ByteString
"2014-10-31" :: Prelude.ByteString),
        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
"DBClusterSnapshotIdentifier"
          forall a. ToQuery a => ByteString -> a -> QueryString
Data.=: Text
dbClusterSnapshotIdentifier,
        ByteString
"DBClusterIdentifier" forall a. ToQuery a => ByteString -> a -> QueryString
Data.=: Text
dbClusterIdentifier
      ]

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

-- |
-- Create a value of 'CreateDBClusterSnapshotResponse' 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:
--
-- 'dbClusterSnapshot', 'createDBClusterSnapshotResponse_dbClusterSnapshot' - Undocumented member.
--
-- 'httpStatus', 'createDBClusterSnapshotResponse_httpStatus' - The response's http status code.
newCreateDBClusterSnapshotResponse ::
  -- | 'httpStatus'
  Prelude.Int ->
  CreateDBClusterSnapshotResponse
newCreateDBClusterSnapshotResponse :: Int -> CreateDBClusterSnapshotResponse
newCreateDBClusterSnapshotResponse Int
pHttpStatus_ =
  CreateDBClusterSnapshotResponse'
    { $sel:dbClusterSnapshot:CreateDBClusterSnapshotResponse' :: Maybe DBClusterSnapshot
dbClusterSnapshot =
        forall a. Maybe a
Prelude.Nothing,
      $sel:httpStatus:CreateDBClusterSnapshotResponse' :: Int
httpStatus = Int
pHttpStatus_
    }

-- | Undocumented member.
createDBClusterSnapshotResponse_dbClusterSnapshot :: Lens.Lens' CreateDBClusterSnapshotResponse (Prelude.Maybe DBClusterSnapshot)
createDBClusterSnapshotResponse_dbClusterSnapshot :: Lens' CreateDBClusterSnapshotResponse (Maybe DBClusterSnapshot)
createDBClusterSnapshotResponse_dbClusterSnapshot = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\CreateDBClusterSnapshotResponse' {Maybe DBClusterSnapshot
dbClusterSnapshot :: Maybe DBClusterSnapshot
$sel:dbClusterSnapshot:CreateDBClusterSnapshotResponse' :: CreateDBClusterSnapshotResponse -> Maybe DBClusterSnapshot
dbClusterSnapshot} -> Maybe DBClusterSnapshot
dbClusterSnapshot) (\s :: CreateDBClusterSnapshotResponse
s@CreateDBClusterSnapshotResponse' {} Maybe DBClusterSnapshot
a -> CreateDBClusterSnapshotResponse
s {$sel:dbClusterSnapshot:CreateDBClusterSnapshotResponse' :: Maybe DBClusterSnapshot
dbClusterSnapshot = Maybe DBClusterSnapshot
a} :: CreateDBClusterSnapshotResponse)

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

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