{-# 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.DescribeDBClusterSnapshotAttributes
-- Copyright   : (c) 2013-2023 Brendan Hay
-- License     : Mozilla Public License, v. 2.0.
-- Maintainer  : Brendan Hay
-- Stability   : auto-generated
-- Portability : non-portable (GHC extensions)
--
-- Returns a list of DB cluster snapshot attribute names and values for a
-- manual DB cluster snapshot.
--
-- When sharing snapshots with other Amazon accounts,
-- @DescribeDBClusterSnapshotAttributes@ returns the @restore@ attribute
-- and a list of IDs for the Amazon accounts that are authorized to copy or
-- restore the manual DB cluster snapshot. If @all@ is included in the list
-- of values for the @restore@ attribute, then the manual DB cluster
-- snapshot is public and can be copied or restored by all Amazon accounts.
--
-- To add or remove access for an Amazon account to copy or restore a
-- manual DB cluster snapshot, or to make the manual DB cluster snapshot
-- public or private, use the ModifyDBClusterSnapshotAttribute API action.
module Amazonka.Neptune.DescribeDBClusterSnapshotAttributes
  ( -- * Creating a Request
    DescribeDBClusterSnapshotAttributes (..),
    newDescribeDBClusterSnapshotAttributes,

    -- * Request Lenses
    describeDBClusterSnapshotAttributes_dbClusterSnapshotIdentifier,

    -- * Destructuring the Response
    DescribeDBClusterSnapshotAttributesResponse (..),
    newDescribeDBClusterSnapshotAttributesResponse,

    -- * Response Lenses
    describeDBClusterSnapshotAttributesResponse_dbClusterSnapshotAttributesResult,
    describeDBClusterSnapshotAttributesResponse_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:/ 'newDescribeDBClusterSnapshotAttributes' smart constructor.
data DescribeDBClusterSnapshotAttributes = DescribeDBClusterSnapshotAttributes'
  { -- | The identifier for the DB cluster snapshot to describe the attributes
    -- for.
    DescribeDBClusterSnapshotAttributes -> Text
dbClusterSnapshotIdentifier :: Prelude.Text
  }
  deriving (DescribeDBClusterSnapshotAttributes
-> DescribeDBClusterSnapshotAttributes -> Bool
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: DescribeDBClusterSnapshotAttributes
-> DescribeDBClusterSnapshotAttributes -> Bool
$c/= :: DescribeDBClusterSnapshotAttributes
-> DescribeDBClusterSnapshotAttributes -> Bool
== :: DescribeDBClusterSnapshotAttributes
-> DescribeDBClusterSnapshotAttributes -> Bool
$c== :: DescribeDBClusterSnapshotAttributes
-> DescribeDBClusterSnapshotAttributes -> Bool
Prelude.Eq, ReadPrec [DescribeDBClusterSnapshotAttributes]
ReadPrec DescribeDBClusterSnapshotAttributes
Int -> ReadS DescribeDBClusterSnapshotAttributes
ReadS [DescribeDBClusterSnapshotAttributes]
forall a.
(Int -> ReadS a)
-> ReadS [a] -> ReadPrec a -> ReadPrec [a] -> Read a
readListPrec :: ReadPrec [DescribeDBClusterSnapshotAttributes]
$creadListPrec :: ReadPrec [DescribeDBClusterSnapshotAttributes]
readPrec :: ReadPrec DescribeDBClusterSnapshotAttributes
$creadPrec :: ReadPrec DescribeDBClusterSnapshotAttributes
readList :: ReadS [DescribeDBClusterSnapshotAttributes]
$creadList :: ReadS [DescribeDBClusterSnapshotAttributes]
readsPrec :: Int -> ReadS DescribeDBClusterSnapshotAttributes
$creadsPrec :: Int -> ReadS DescribeDBClusterSnapshotAttributes
Prelude.Read, Int -> DescribeDBClusterSnapshotAttributes -> ShowS
[DescribeDBClusterSnapshotAttributes] -> ShowS
DescribeDBClusterSnapshotAttributes -> String
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [DescribeDBClusterSnapshotAttributes] -> ShowS
$cshowList :: [DescribeDBClusterSnapshotAttributes] -> ShowS
show :: DescribeDBClusterSnapshotAttributes -> String
$cshow :: DescribeDBClusterSnapshotAttributes -> String
showsPrec :: Int -> DescribeDBClusterSnapshotAttributes -> ShowS
$cshowsPrec :: Int -> DescribeDBClusterSnapshotAttributes -> ShowS
Prelude.Show, forall x.
Rep DescribeDBClusterSnapshotAttributes x
-> DescribeDBClusterSnapshotAttributes
forall x.
DescribeDBClusterSnapshotAttributes
-> Rep DescribeDBClusterSnapshotAttributes x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cto :: forall x.
Rep DescribeDBClusterSnapshotAttributes x
-> DescribeDBClusterSnapshotAttributes
$cfrom :: forall x.
DescribeDBClusterSnapshotAttributes
-> Rep DescribeDBClusterSnapshotAttributes x
Prelude.Generic)

-- |
-- Create a value of 'DescribeDBClusterSnapshotAttributes' 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:
--
-- 'dbClusterSnapshotIdentifier', 'describeDBClusterSnapshotAttributes_dbClusterSnapshotIdentifier' - The identifier for the DB cluster snapshot to describe the attributes
-- for.
newDescribeDBClusterSnapshotAttributes ::
  -- | 'dbClusterSnapshotIdentifier'
  Prelude.Text ->
  DescribeDBClusterSnapshotAttributes
newDescribeDBClusterSnapshotAttributes :: Text -> DescribeDBClusterSnapshotAttributes
newDescribeDBClusterSnapshotAttributes
  Text
pDBClusterSnapshotIdentifier_ =
    DescribeDBClusterSnapshotAttributes'
      { $sel:dbClusterSnapshotIdentifier:DescribeDBClusterSnapshotAttributes' :: Text
dbClusterSnapshotIdentifier =
          Text
pDBClusterSnapshotIdentifier_
      }

-- | The identifier for the DB cluster snapshot to describe the attributes
-- for.
describeDBClusterSnapshotAttributes_dbClusterSnapshotIdentifier :: Lens.Lens' DescribeDBClusterSnapshotAttributes Prelude.Text
describeDBClusterSnapshotAttributes_dbClusterSnapshotIdentifier :: Lens' DescribeDBClusterSnapshotAttributes Text
describeDBClusterSnapshotAttributes_dbClusterSnapshotIdentifier = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\DescribeDBClusterSnapshotAttributes' {Text
dbClusterSnapshotIdentifier :: Text
$sel:dbClusterSnapshotIdentifier:DescribeDBClusterSnapshotAttributes' :: DescribeDBClusterSnapshotAttributes -> Text
dbClusterSnapshotIdentifier} -> Text
dbClusterSnapshotIdentifier) (\s :: DescribeDBClusterSnapshotAttributes
s@DescribeDBClusterSnapshotAttributes' {} Text
a -> DescribeDBClusterSnapshotAttributes
s {$sel:dbClusterSnapshotIdentifier:DescribeDBClusterSnapshotAttributes' :: Text
dbClusterSnapshotIdentifier = Text
a} :: DescribeDBClusterSnapshotAttributes)

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

instance
  Prelude.NFData
    DescribeDBClusterSnapshotAttributes
  where
  rnf :: DescribeDBClusterSnapshotAttributes -> ()
rnf DescribeDBClusterSnapshotAttributes' {Text
dbClusterSnapshotIdentifier :: Text
$sel:dbClusterSnapshotIdentifier:DescribeDBClusterSnapshotAttributes' :: DescribeDBClusterSnapshotAttributes -> Text
..} =
    forall a. NFData a => a -> ()
Prelude.rnf Text
dbClusterSnapshotIdentifier

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

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

instance
  Data.ToQuery
    DescribeDBClusterSnapshotAttributes
  where
  toQuery :: DescribeDBClusterSnapshotAttributes -> QueryString
toQuery DescribeDBClusterSnapshotAttributes' {Text
dbClusterSnapshotIdentifier :: Text
$sel:dbClusterSnapshotIdentifier:DescribeDBClusterSnapshotAttributes' :: DescribeDBClusterSnapshotAttributes -> Text
..} =
    forall a. Monoid a => [a] -> a
Prelude.mconcat
      [ ByteString
"Action"
          forall a. ToQuery a => ByteString -> a -> QueryString
Data.=: ( ByteString
"DescribeDBClusterSnapshotAttributes" ::
                      Prelude.ByteString
                  ),
        ByteString
"Version"
          forall a. ToQuery a => ByteString -> a -> QueryString
Data.=: (ByteString
"2014-10-31" :: Prelude.ByteString),
        ByteString
"DBClusterSnapshotIdentifier"
          forall a. ToQuery a => ByteString -> a -> QueryString
Data.=: Text
dbClusterSnapshotIdentifier
      ]

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

-- |
-- Create a value of 'DescribeDBClusterSnapshotAttributesResponse' 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:
--
-- 'dbClusterSnapshotAttributesResult', 'describeDBClusterSnapshotAttributesResponse_dbClusterSnapshotAttributesResult' - Undocumented member.
--
-- 'httpStatus', 'describeDBClusterSnapshotAttributesResponse_httpStatus' - The response's http status code.
newDescribeDBClusterSnapshotAttributesResponse ::
  -- | 'httpStatus'
  Prelude.Int ->
  DescribeDBClusterSnapshotAttributesResponse
newDescribeDBClusterSnapshotAttributesResponse :: Int -> DescribeDBClusterSnapshotAttributesResponse
newDescribeDBClusterSnapshotAttributesResponse
  Int
pHttpStatus_ =
    DescribeDBClusterSnapshotAttributesResponse'
      { $sel:dbClusterSnapshotAttributesResult:DescribeDBClusterSnapshotAttributesResponse' :: Maybe DBClusterSnapshotAttributesResult
dbClusterSnapshotAttributesResult =
          forall a. Maybe a
Prelude.Nothing,
        $sel:httpStatus:DescribeDBClusterSnapshotAttributesResponse' :: Int
httpStatus = Int
pHttpStatus_
      }

-- | Undocumented member.
describeDBClusterSnapshotAttributesResponse_dbClusterSnapshotAttributesResult :: Lens.Lens' DescribeDBClusterSnapshotAttributesResponse (Prelude.Maybe DBClusterSnapshotAttributesResult)
describeDBClusterSnapshotAttributesResponse_dbClusterSnapshotAttributesResult :: Lens'
  DescribeDBClusterSnapshotAttributesResponse
  (Maybe DBClusterSnapshotAttributesResult)
describeDBClusterSnapshotAttributesResponse_dbClusterSnapshotAttributesResult = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\DescribeDBClusterSnapshotAttributesResponse' {Maybe DBClusterSnapshotAttributesResult
dbClusterSnapshotAttributesResult :: Maybe DBClusterSnapshotAttributesResult
$sel:dbClusterSnapshotAttributesResult:DescribeDBClusterSnapshotAttributesResponse' :: DescribeDBClusterSnapshotAttributesResponse
-> Maybe DBClusterSnapshotAttributesResult
dbClusterSnapshotAttributesResult} -> Maybe DBClusterSnapshotAttributesResult
dbClusterSnapshotAttributesResult) (\s :: DescribeDBClusterSnapshotAttributesResponse
s@DescribeDBClusterSnapshotAttributesResponse' {} Maybe DBClusterSnapshotAttributesResult
a -> DescribeDBClusterSnapshotAttributesResponse
s {$sel:dbClusterSnapshotAttributesResult:DescribeDBClusterSnapshotAttributesResponse' :: Maybe DBClusterSnapshotAttributesResult
dbClusterSnapshotAttributesResult = Maybe DBClusterSnapshotAttributesResult
a} :: DescribeDBClusterSnapshotAttributesResponse)

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

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