{-# 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.RDS.ModifyDBSnapshotAttribute
-- Copyright   : (c) 2013-2023 Brendan Hay
-- License     : Mozilla Public License, v. 2.0.
-- Maintainer  : Brendan Hay
-- Stability   : auto-generated
-- Portability : non-portable (GHC extensions)
--
-- Adds an attribute and values to, or removes an attribute and values
-- from, a manual DB snapshot.
--
-- To share a manual DB snapshot with other Amazon Web Services accounts,
-- specify @restore@ as the @AttributeName@ and use the @ValuesToAdd@
-- parameter to add a list of IDs of the Amazon Web Services accounts that
-- are authorized to restore the manual DB snapshot. Uses the value @all@
-- to make the manual DB snapshot public, which means it can be copied or
-- restored by all Amazon Web Services accounts.
--
-- Don\'t add the @all@ value for any manual DB snapshots that contain
-- private information that you don\'t want available to all Amazon Web
-- Services accounts.
--
-- If the manual DB snapshot is encrypted, it can be shared, but only by
-- specifying a list of authorized Amazon Web Services account IDs for the
-- @ValuesToAdd@ parameter. You can\'t use @all@ as a value for that
-- parameter in this case.
--
-- To view which Amazon Web Services accounts have access to copy or
-- restore a manual DB snapshot, or whether a manual DB snapshot public or
-- private, use the DescribeDBSnapshotAttributes API operation. The
-- accounts are returned as values for the @restore@ attribute.
module Amazonka.RDS.ModifyDBSnapshotAttribute
  ( -- * Creating a Request
    ModifyDBSnapshotAttribute (..),
    newModifyDBSnapshotAttribute,

    -- * Request Lenses
    modifyDBSnapshotAttribute_valuesToAdd,
    modifyDBSnapshotAttribute_valuesToRemove,
    modifyDBSnapshotAttribute_dbSnapshotIdentifier,
    modifyDBSnapshotAttribute_attributeName,

    -- * Destructuring the Response
    ModifyDBSnapshotAttributeResponse (..),
    newModifyDBSnapshotAttributeResponse,

    -- * Response Lenses
    modifyDBSnapshotAttributeResponse_dbSnapshotAttributesResult,
    modifyDBSnapshotAttributeResponse_httpStatus,
  )
where

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

-- |
--
-- /See:/ 'newModifyDBSnapshotAttribute' smart constructor.
data ModifyDBSnapshotAttribute = ModifyDBSnapshotAttribute'
  { -- | A list of DB snapshot attributes to add to the attribute specified by
    -- @AttributeName@.
    --
    -- To authorize other Amazon Web Services accounts to copy or restore a
    -- manual snapshot, set this list to include one or more Amazon Web
    -- Services account IDs, or @all@ to make the manual DB snapshot restorable
    -- by any Amazon Web Services account. Do not add the @all@ value for any
    -- manual DB snapshots that contain private information that you don\'t
    -- want available to all Amazon Web Services accounts.
    ModifyDBSnapshotAttribute -> Maybe [Text]
valuesToAdd :: Prelude.Maybe [Prelude.Text],
    -- | A list of DB snapshot attributes to remove from the attribute specified
    -- by @AttributeName@.
    --
    -- To remove authorization for other Amazon Web Services accounts to copy
    -- or restore a manual snapshot, set this list to include one or more
    -- Amazon Web Services account identifiers, or @all@ to remove
    -- authorization for any Amazon Web Services account to copy or restore the
    -- DB snapshot. If you specify @all@, an Amazon Web Services account whose
    -- account ID is explicitly added to the @restore@ attribute can still copy
    -- or restore the manual DB snapshot.
    ModifyDBSnapshotAttribute -> Maybe [Text]
valuesToRemove :: Prelude.Maybe [Prelude.Text],
    -- | The identifier for the DB snapshot to modify the attributes for.
    ModifyDBSnapshotAttribute -> Text
dbSnapshotIdentifier :: Prelude.Text,
    -- | The name of the DB snapshot attribute to modify.
    --
    -- To manage authorization for other Amazon Web Services accounts to copy
    -- or restore a manual DB snapshot, set this value to @restore@.
    --
    -- To view the list of attributes available to modify, use the
    -- DescribeDBSnapshotAttributes API operation.
    ModifyDBSnapshotAttribute -> Text
attributeName :: Prelude.Text
  }
  deriving (ModifyDBSnapshotAttribute -> ModifyDBSnapshotAttribute -> Bool
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: ModifyDBSnapshotAttribute -> ModifyDBSnapshotAttribute -> Bool
$c/= :: ModifyDBSnapshotAttribute -> ModifyDBSnapshotAttribute -> Bool
== :: ModifyDBSnapshotAttribute -> ModifyDBSnapshotAttribute -> Bool
$c== :: ModifyDBSnapshotAttribute -> ModifyDBSnapshotAttribute -> Bool
Prelude.Eq, ReadPrec [ModifyDBSnapshotAttribute]
ReadPrec ModifyDBSnapshotAttribute
Int -> ReadS ModifyDBSnapshotAttribute
ReadS [ModifyDBSnapshotAttribute]
forall a.
(Int -> ReadS a)
-> ReadS [a] -> ReadPrec a -> ReadPrec [a] -> Read a
readListPrec :: ReadPrec [ModifyDBSnapshotAttribute]
$creadListPrec :: ReadPrec [ModifyDBSnapshotAttribute]
readPrec :: ReadPrec ModifyDBSnapshotAttribute
$creadPrec :: ReadPrec ModifyDBSnapshotAttribute
readList :: ReadS [ModifyDBSnapshotAttribute]
$creadList :: ReadS [ModifyDBSnapshotAttribute]
readsPrec :: Int -> ReadS ModifyDBSnapshotAttribute
$creadsPrec :: Int -> ReadS ModifyDBSnapshotAttribute
Prelude.Read, Int -> ModifyDBSnapshotAttribute -> ShowS
[ModifyDBSnapshotAttribute] -> ShowS
ModifyDBSnapshotAttribute -> String
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [ModifyDBSnapshotAttribute] -> ShowS
$cshowList :: [ModifyDBSnapshotAttribute] -> ShowS
show :: ModifyDBSnapshotAttribute -> String
$cshow :: ModifyDBSnapshotAttribute -> String
showsPrec :: Int -> ModifyDBSnapshotAttribute -> ShowS
$cshowsPrec :: Int -> ModifyDBSnapshotAttribute -> ShowS
Prelude.Show, forall x.
Rep ModifyDBSnapshotAttribute x -> ModifyDBSnapshotAttribute
forall x.
ModifyDBSnapshotAttribute -> Rep ModifyDBSnapshotAttribute x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cto :: forall x.
Rep ModifyDBSnapshotAttribute x -> ModifyDBSnapshotAttribute
$cfrom :: forall x.
ModifyDBSnapshotAttribute -> Rep ModifyDBSnapshotAttribute x
Prelude.Generic)

-- |
-- Create a value of 'ModifyDBSnapshotAttribute' 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:
--
-- 'valuesToAdd', 'modifyDBSnapshotAttribute_valuesToAdd' - A list of DB snapshot attributes to add to the attribute specified by
-- @AttributeName@.
--
-- To authorize other Amazon Web Services accounts to copy or restore a
-- manual snapshot, set this list to include one or more Amazon Web
-- Services account IDs, or @all@ to make the manual DB snapshot restorable
-- by any Amazon Web Services account. Do not add the @all@ value for any
-- manual DB snapshots that contain private information that you don\'t
-- want available to all Amazon Web Services accounts.
--
-- 'valuesToRemove', 'modifyDBSnapshotAttribute_valuesToRemove' - A list of DB snapshot attributes to remove from the attribute specified
-- by @AttributeName@.
--
-- To remove authorization for other Amazon Web Services accounts to copy
-- or restore a manual snapshot, set this list to include one or more
-- Amazon Web Services account identifiers, or @all@ to remove
-- authorization for any Amazon Web Services account to copy or restore the
-- DB snapshot. If you specify @all@, an Amazon Web Services account whose
-- account ID is explicitly added to the @restore@ attribute can still copy
-- or restore the manual DB snapshot.
--
-- 'dbSnapshotIdentifier', 'modifyDBSnapshotAttribute_dbSnapshotIdentifier' - The identifier for the DB snapshot to modify the attributes for.
--
-- 'attributeName', 'modifyDBSnapshotAttribute_attributeName' - The name of the DB snapshot attribute to modify.
--
-- To manage authorization for other Amazon Web Services accounts to copy
-- or restore a manual DB snapshot, set this value to @restore@.
--
-- To view the list of attributes available to modify, use the
-- DescribeDBSnapshotAttributes API operation.
newModifyDBSnapshotAttribute ::
  -- | 'dbSnapshotIdentifier'
  Prelude.Text ->
  -- | 'attributeName'
  Prelude.Text ->
  ModifyDBSnapshotAttribute
newModifyDBSnapshotAttribute :: Text -> Text -> ModifyDBSnapshotAttribute
newModifyDBSnapshotAttribute
  Text
pDBSnapshotIdentifier_
  Text
pAttributeName_ =
    ModifyDBSnapshotAttribute'
      { $sel:valuesToAdd:ModifyDBSnapshotAttribute' :: Maybe [Text]
valuesToAdd =
          forall a. Maybe a
Prelude.Nothing,
        $sel:valuesToRemove:ModifyDBSnapshotAttribute' :: Maybe [Text]
valuesToRemove = forall a. Maybe a
Prelude.Nothing,
        $sel:dbSnapshotIdentifier:ModifyDBSnapshotAttribute' :: Text
dbSnapshotIdentifier = Text
pDBSnapshotIdentifier_,
        $sel:attributeName:ModifyDBSnapshotAttribute' :: Text
attributeName = Text
pAttributeName_
      }

-- | A list of DB snapshot attributes to add to the attribute specified by
-- @AttributeName@.
--
-- To authorize other Amazon Web Services accounts to copy or restore a
-- manual snapshot, set this list to include one or more Amazon Web
-- Services account IDs, or @all@ to make the manual DB snapshot restorable
-- by any Amazon Web Services account. Do not add the @all@ value for any
-- manual DB snapshots that contain private information that you don\'t
-- want available to all Amazon Web Services accounts.
modifyDBSnapshotAttribute_valuesToAdd :: Lens.Lens' ModifyDBSnapshotAttribute (Prelude.Maybe [Prelude.Text])
modifyDBSnapshotAttribute_valuesToAdd :: Lens' ModifyDBSnapshotAttribute (Maybe [Text])
modifyDBSnapshotAttribute_valuesToAdd = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\ModifyDBSnapshotAttribute' {Maybe [Text]
valuesToAdd :: Maybe [Text]
$sel:valuesToAdd:ModifyDBSnapshotAttribute' :: ModifyDBSnapshotAttribute -> Maybe [Text]
valuesToAdd} -> Maybe [Text]
valuesToAdd) (\s :: ModifyDBSnapshotAttribute
s@ModifyDBSnapshotAttribute' {} Maybe [Text]
a -> ModifyDBSnapshotAttribute
s {$sel:valuesToAdd:ModifyDBSnapshotAttribute' :: Maybe [Text]
valuesToAdd = Maybe [Text]
a} :: ModifyDBSnapshotAttribute) 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 DB snapshot attributes to remove from the attribute specified
-- by @AttributeName@.
--
-- To remove authorization for other Amazon Web Services accounts to copy
-- or restore a manual snapshot, set this list to include one or more
-- Amazon Web Services account identifiers, or @all@ to remove
-- authorization for any Amazon Web Services account to copy or restore the
-- DB snapshot. If you specify @all@, an Amazon Web Services account whose
-- account ID is explicitly added to the @restore@ attribute can still copy
-- or restore the manual DB snapshot.
modifyDBSnapshotAttribute_valuesToRemove :: Lens.Lens' ModifyDBSnapshotAttribute (Prelude.Maybe [Prelude.Text])
modifyDBSnapshotAttribute_valuesToRemove :: Lens' ModifyDBSnapshotAttribute (Maybe [Text])
modifyDBSnapshotAttribute_valuesToRemove = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\ModifyDBSnapshotAttribute' {Maybe [Text]
valuesToRemove :: Maybe [Text]
$sel:valuesToRemove:ModifyDBSnapshotAttribute' :: ModifyDBSnapshotAttribute -> Maybe [Text]
valuesToRemove} -> Maybe [Text]
valuesToRemove) (\s :: ModifyDBSnapshotAttribute
s@ModifyDBSnapshotAttribute' {} Maybe [Text]
a -> ModifyDBSnapshotAttribute
s {$sel:valuesToRemove:ModifyDBSnapshotAttribute' :: Maybe [Text]
valuesToRemove = Maybe [Text]
a} :: ModifyDBSnapshotAttribute) 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 for the DB snapshot to modify the attributes for.
modifyDBSnapshotAttribute_dbSnapshotIdentifier :: Lens.Lens' ModifyDBSnapshotAttribute Prelude.Text
modifyDBSnapshotAttribute_dbSnapshotIdentifier :: Lens' ModifyDBSnapshotAttribute Text
modifyDBSnapshotAttribute_dbSnapshotIdentifier = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\ModifyDBSnapshotAttribute' {Text
dbSnapshotIdentifier :: Text
$sel:dbSnapshotIdentifier:ModifyDBSnapshotAttribute' :: ModifyDBSnapshotAttribute -> Text
dbSnapshotIdentifier} -> Text
dbSnapshotIdentifier) (\s :: ModifyDBSnapshotAttribute
s@ModifyDBSnapshotAttribute' {} Text
a -> ModifyDBSnapshotAttribute
s {$sel:dbSnapshotIdentifier:ModifyDBSnapshotAttribute' :: Text
dbSnapshotIdentifier = Text
a} :: ModifyDBSnapshotAttribute)

-- | The name of the DB snapshot attribute to modify.
--
-- To manage authorization for other Amazon Web Services accounts to copy
-- or restore a manual DB snapshot, set this value to @restore@.
--
-- To view the list of attributes available to modify, use the
-- DescribeDBSnapshotAttributes API operation.
modifyDBSnapshotAttribute_attributeName :: Lens.Lens' ModifyDBSnapshotAttribute Prelude.Text
modifyDBSnapshotAttribute_attributeName :: Lens' ModifyDBSnapshotAttribute Text
modifyDBSnapshotAttribute_attributeName = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\ModifyDBSnapshotAttribute' {Text
attributeName :: Text
$sel:attributeName:ModifyDBSnapshotAttribute' :: ModifyDBSnapshotAttribute -> Text
attributeName} -> Text
attributeName) (\s :: ModifyDBSnapshotAttribute
s@ModifyDBSnapshotAttribute' {} Text
a -> ModifyDBSnapshotAttribute
s {$sel:attributeName:ModifyDBSnapshotAttribute' :: Text
attributeName = Text
a} :: ModifyDBSnapshotAttribute)

instance Core.AWSRequest ModifyDBSnapshotAttribute where
  type
    AWSResponse ModifyDBSnapshotAttribute =
      ModifyDBSnapshotAttributeResponse
  request :: (Service -> Service)
-> ModifyDBSnapshotAttribute -> Request ModifyDBSnapshotAttribute
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 ModifyDBSnapshotAttribute
-> ClientResponse ClientBody
-> m (Either
        Error (ClientResponse (AWSResponse ModifyDBSnapshotAttribute)))
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
"ModifyDBSnapshotAttributeResult"
      ( \Int
s ResponseHeaders
h [Node]
x ->
          Maybe DBSnapshotAttributesResult
-> Int -> ModifyDBSnapshotAttributeResponse
ModifyDBSnapshotAttributeResponse'
            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
"DBSnapshotAttributesResult")
            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 ModifyDBSnapshotAttribute where
  hashWithSalt :: Int -> ModifyDBSnapshotAttribute -> Int
hashWithSalt Int
_salt ModifyDBSnapshotAttribute' {Maybe [Text]
Text
attributeName :: Text
dbSnapshotIdentifier :: Text
valuesToRemove :: Maybe [Text]
valuesToAdd :: Maybe [Text]
$sel:attributeName:ModifyDBSnapshotAttribute' :: ModifyDBSnapshotAttribute -> Text
$sel:dbSnapshotIdentifier:ModifyDBSnapshotAttribute' :: ModifyDBSnapshotAttribute -> Text
$sel:valuesToRemove:ModifyDBSnapshotAttribute' :: ModifyDBSnapshotAttribute -> Maybe [Text]
$sel:valuesToAdd:ModifyDBSnapshotAttribute' :: ModifyDBSnapshotAttribute -> Maybe [Text]
..} =
    Int
_salt
      forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Maybe [Text]
valuesToAdd
      forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Maybe [Text]
valuesToRemove
      forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Text
dbSnapshotIdentifier
      forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Text
attributeName

instance Prelude.NFData ModifyDBSnapshotAttribute where
  rnf :: ModifyDBSnapshotAttribute -> ()
rnf ModifyDBSnapshotAttribute' {Maybe [Text]
Text
attributeName :: Text
dbSnapshotIdentifier :: Text
valuesToRemove :: Maybe [Text]
valuesToAdd :: Maybe [Text]
$sel:attributeName:ModifyDBSnapshotAttribute' :: ModifyDBSnapshotAttribute -> Text
$sel:dbSnapshotIdentifier:ModifyDBSnapshotAttribute' :: ModifyDBSnapshotAttribute -> Text
$sel:valuesToRemove:ModifyDBSnapshotAttribute' :: ModifyDBSnapshotAttribute -> Maybe [Text]
$sel:valuesToAdd:ModifyDBSnapshotAttribute' :: ModifyDBSnapshotAttribute -> Maybe [Text]
..} =
    forall a. NFData a => a -> ()
Prelude.rnf Maybe [Text]
valuesToAdd
      seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf Maybe [Text]
valuesToRemove
      seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf Text
dbSnapshotIdentifier
      seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf Text
attributeName

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

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

instance Data.ToQuery ModifyDBSnapshotAttribute where
  toQuery :: ModifyDBSnapshotAttribute -> QueryString
toQuery ModifyDBSnapshotAttribute' {Maybe [Text]
Text
attributeName :: Text
dbSnapshotIdentifier :: Text
valuesToRemove :: Maybe [Text]
valuesToAdd :: Maybe [Text]
$sel:attributeName:ModifyDBSnapshotAttribute' :: ModifyDBSnapshotAttribute -> Text
$sel:dbSnapshotIdentifier:ModifyDBSnapshotAttribute' :: ModifyDBSnapshotAttribute -> Text
$sel:valuesToRemove:ModifyDBSnapshotAttribute' :: ModifyDBSnapshotAttribute -> Maybe [Text]
$sel:valuesToAdd:ModifyDBSnapshotAttribute' :: ModifyDBSnapshotAttribute -> Maybe [Text]
..} =
    forall a. Monoid a => [a] -> a
Prelude.mconcat
      [ ByteString
"Action"
          forall a. ToQuery a => ByteString -> a -> QueryString
Data.=: (ByteString
"ModifyDBSnapshotAttribute" :: Prelude.ByteString),
        ByteString
"Version"
          forall a. ToQuery a => ByteString -> a -> QueryString
Data.=: (ByteString
"2014-10-31" :: Prelude.ByteString),
        ByteString
"ValuesToAdd"
          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
"AttributeValue"
                forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
Prelude.<$> Maybe [Text]
valuesToAdd
            ),
        ByteString
"ValuesToRemove"
          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
"AttributeValue"
                forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
Prelude.<$> Maybe [Text]
valuesToRemove
            ),
        ByteString
"DBSnapshotIdentifier" forall a. ToQuery a => ByteString -> a -> QueryString
Data.=: Text
dbSnapshotIdentifier,
        ByteString
"AttributeName" forall a. ToQuery a => ByteString -> a -> QueryString
Data.=: Text
attributeName
      ]

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

-- |
-- Create a value of 'ModifyDBSnapshotAttributeResponse' 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:
--
-- 'dbSnapshotAttributesResult', 'modifyDBSnapshotAttributeResponse_dbSnapshotAttributesResult' - Undocumented member.
--
-- 'httpStatus', 'modifyDBSnapshotAttributeResponse_httpStatus' - The response's http status code.
newModifyDBSnapshotAttributeResponse ::
  -- | 'httpStatus'
  Prelude.Int ->
  ModifyDBSnapshotAttributeResponse
newModifyDBSnapshotAttributeResponse :: Int -> ModifyDBSnapshotAttributeResponse
newModifyDBSnapshotAttributeResponse Int
pHttpStatus_ =
  ModifyDBSnapshotAttributeResponse'
    { $sel:dbSnapshotAttributesResult:ModifyDBSnapshotAttributeResponse' :: Maybe DBSnapshotAttributesResult
dbSnapshotAttributesResult =
        forall a. Maybe a
Prelude.Nothing,
      $sel:httpStatus:ModifyDBSnapshotAttributeResponse' :: Int
httpStatus = Int
pHttpStatus_
    }

-- | Undocumented member.
modifyDBSnapshotAttributeResponse_dbSnapshotAttributesResult :: Lens.Lens' ModifyDBSnapshotAttributeResponse (Prelude.Maybe DBSnapshotAttributesResult)
modifyDBSnapshotAttributeResponse_dbSnapshotAttributesResult :: Lens'
  ModifyDBSnapshotAttributeResponse
  (Maybe DBSnapshotAttributesResult)
modifyDBSnapshotAttributeResponse_dbSnapshotAttributesResult = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\ModifyDBSnapshotAttributeResponse' {Maybe DBSnapshotAttributesResult
dbSnapshotAttributesResult :: Maybe DBSnapshotAttributesResult
$sel:dbSnapshotAttributesResult:ModifyDBSnapshotAttributeResponse' :: ModifyDBSnapshotAttributeResponse
-> Maybe DBSnapshotAttributesResult
dbSnapshotAttributesResult} -> Maybe DBSnapshotAttributesResult
dbSnapshotAttributesResult) (\s :: ModifyDBSnapshotAttributeResponse
s@ModifyDBSnapshotAttributeResponse' {} Maybe DBSnapshotAttributesResult
a -> ModifyDBSnapshotAttributeResponse
s {$sel:dbSnapshotAttributesResult:ModifyDBSnapshotAttributeResponse' :: Maybe DBSnapshotAttributesResult
dbSnapshotAttributesResult = Maybe DBSnapshotAttributesResult
a} :: ModifyDBSnapshotAttributeResponse)

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

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