{-# 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.Glacier.GetVaultNotifications
-- Copyright   : (c) 2013-2023 Brendan Hay
-- License     : Mozilla Public License, v. 2.0.
-- Maintainer  : Brendan Hay
-- Stability   : auto-generated
-- Portability : non-portable (GHC extensions)
--
-- This operation retrieves the @notification-configuration@ subresource of
-- the specified vault.
--
-- For information about setting a notification configuration on a vault,
-- see SetVaultNotifications. If a notification configuration for a vault
-- is not set, the operation returns a @404 Not Found@ error. For more
-- information about vault notifications, see
-- <https://docs.aws.amazon.com/amazonglacier/latest/dev/configuring-notifications.html Configuring Vault Notifications in Amazon S3 Glacier>.
--
-- An AWS account has full permission to perform all operations (actions).
-- However, AWS Identity and Access Management (IAM) users don\'t have any
-- permissions by default. You must grant them explicit permission to
-- perform specific actions. For more information, see
-- <https://docs.aws.amazon.com/amazonglacier/latest/dev/using-iam-with-amazon-glacier.html Access Control Using AWS Identity and Access Management (IAM)>.
--
-- For conceptual information and underlying REST API, see
-- <https://docs.aws.amazon.com/amazonglacier/latest/dev/configuring-notifications.html Configuring Vault Notifications in Amazon S3 Glacier>
-- and
-- <https://docs.aws.amazon.com/amazonglacier/latest/dev/api-vault-notifications-get.html Get Vault Notification Configuration>
-- in the /Amazon Glacier Developer Guide/.
module Amazonka.Glacier.GetVaultNotifications
  ( -- * Creating a Request
    GetVaultNotifications (..),
    newGetVaultNotifications,

    -- * Request Lenses
    getVaultNotifications_accountId,
    getVaultNotifications_vaultName,

    -- * Destructuring the Response
    GetVaultNotificationsResponse (..),
    newGetVaultNotificationsResponse,

    -- * Response Lenses
    getVaultNotificationsResponse_vaultNotificationConfig,
    getVaultNotificationsResponse_httpStatus,
  )
where

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

-- | Provides options for retrieving the notification configuration set on an
-- Amazon Glacier vault.
--
-- /See:/ 'newGetVaultNotifications' smart constructor.
data GetVaultNotifications = GetVaultNotifications'
  { -- | The @AccountId@ value is the AWS account ID of the account that owns the
    -- vault. You can either specify an AWS account ID or optionally a single
    -- \'@-@\' (hyphen), in which case Amazon S3 Glacier uses the AWS account
    -- ID associated with the credentials used to sign the request. If you use
    -- an account ID, do not include any hyphens (\'-\') in the ID.
    GetVaultNotifications -> Text
accountId :: Prelude.Text,
    -- | The name of the vault.
    GetVaultNotifications -> Text
vaultName :: Prelude.Text
  }
  deriving (GetVaultNotifications -> GetVaultNotifications -> Bool
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: GetVaultNotifications -> GetVaultNotifications -> Bool
$c/= :: GetVaultNotifications -> GetVaultNotifications -> Bool
== :: GetVaultNotifications -> GetVaultNotifications -> Bool
$c== :: GetVaultNotifications -> GetVaultNotifications -> Bool
Prelude.Eq, ReadPrec [GetVaultNotifications]
ReadPrec GetVaultNotifications
Int -> ReadS GetVaultNotifications
ReadS [GetVaultNotifications]
forall a.
(Int -> ReadS a)
-> ReadS [a] -> ReadPrec a -> ReadPrec [a] -> Read a
readListPrec :: ReadPrec [GetVaultNotifications]
$creadListPrec :: ReadPrec [GetVaultNotifications]
readPrec :: ReadPrec GetVaultNotifications
$creadPrec :: ReadPrec GetVaultNotifications
readList :: ReadS [GetVaultNotifications]
$creadList :: ReadS [GetVaultNotifications]
readsPrec :: Int -> ReadS GetVaultNotifications
$creadsPrec :: Int -> ReadS GetVaultNotifications
Prelude.Read, Int -> GetVaultNotifications -> ShowS
[GetVaultNotifications] -> ShowS
GetVaultNotifications -> String
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [GetVaultNotifications] -> ShowS
$cshowList :: [GetVaultNotifications] -> ShowS
show :: GetVaultNotifications -> String
$cshow :: GetVaultNotifications -> String
showsPrec :: Int -> GetVaultNotifications -> ShowS
$cshowsPrec :: Int -> GetVaultNotifications -> ShowS
Prelude.Show, forall x. Rep GetVaultNotifications x -> GetVaultNotifications
forall x. GetVaultNotifications -> Rep GetVaultNotifications x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cto :: forall x. Rep GetVaultNotifications x -> GetVaultNotifications
$cfrom :: forall x. GetVaultNotifications -> Rep GetVaultNotifications x
Prelude.Generic)

-- |
-- Create a value of 'GetVaultNotifications' 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:
--
-- 'accountId', 'getVaultNotifications_accountId' - The @AccountId@ value is the AWS account ID of the account that owns the
-- vault. You can either specify an AWS account ID or optionally a single
-- \'@-@\' (hyphen), in which case Amazon S3 Glacier uses the AWS account
-- ID associated with the credentials used to sign the request. If you use
-- an account ID, do not include any hyphens (\'-\') in the ID.
--
-- 'vaultName', 'getVaultNotifications_vaultName' - The name of the vault.
newGetVaultNotifications ::
  -- | 'accountId'
  Prelude.Text ->
  -- | 'vaultName'
  Prelude.Text ->
  GetVaultNotifications
newGetVaultNotifications :: Text -> Text -> GetVaultNotifications
newGetVaultNotifications Text
pAccountId_ Text
pVaultName_ =
  GetVaultNotifications'
    { $sel:accountId:GetVaultNotifications' :: Text
accountId = Text
pAccountId_,
      $sel:vaultName:GetVaultNotifications' :: Text
vaultName = Text
pVaultName_
    }

-- | The @AccountId@ value is the AWS account ID of the account that owns the
-- vault. You can either specify an AWS account ID or optionally a single
-- \'@-@\' (hyphen), in which case Amazon S3 Glacier uses the AWS account
-- ID associated with the credentials used to sign the request. If you use
-- an account ID, do not include any hyphens (\'-\') in the ID.
getVaultNotifications_accountId :: Lens.Lens' GetVaultNotifications Prelude.Text
getVaultNotifications_accountId :: Lens' GetVaultNotifications Text
getVaultNotifications_accountId = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\GetVaultNotifications' {Text
accountId :: Text
$sel:accountId:GetVaultNotifications' :: GetVaultNotifications -> Text
accountId} -> Text
accountId) (\s :: GetVaultNotifications
s@GetVaultNotifications' {} Text
a -> GetVaultNotifications
s {$sel:accountId:GetVaultNotifications' :: Text
accountId = Text
a} :: GetVaultNotifications)

-- | The name of the vault.
getVaultNotifications_vaultName :: Lens.Lens' GetVaultNotifications Prelude.Text
getVaultNotifications_vaultName :: Lens' GetVaultNotifications Text
getVaultNotifications_vaultName = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\GetVaultNotifications' {Text
vaultName :: Text
$sel:vaultName:GetVaultNotifications' :: GetVaultNotifications -> Text
vaultName} -> Text
vaultName) (\s :: GetVaultNotifications
s@GetVaultNotifications' {} Text
a -> GetVaultNotifications
s {$sel:vaultName:GetVaultNotifications' :: Text
vaultName = Text
a} :: GetVaultNotifications)

instance Core.AWSRequest GetVaultNotifications where
  type
    AWSResponse GetVaultNotifications =
      GetVaultNotificationsResponse
  request :: (Service -> Service)
-> GetVaultNotifications -> Request GetVaultNotifications
request Service -> Service
overrides =
    forall a. ByteString -> Request a -> Request a
Request.glacierVersionHeader (Service -> ByteString
Core.version Service
defaultService)
      forall b c a. (b -> c) -> (a -> b) -> a -> c
Prelude.. forall a. ToRequest a => Service -> a -> Request a
Request.get (Service -> Service
overrides Service
defaultService)
  response :: forall (m :: * -> *).
MonadResource m =>
(ByteStringLazy -> IO ByteStringLazy)
-> Service
-> Proxy GetVaultNotifications
-> ClientResponse ClientBody
-> m (Either
        Error (ClientResponse (AWSResponse GetVaultNotifications)))
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 ->
          Maybe VaultNotificationConfig
-> Int -> GetVaultNotificationsResponse
GetVaultNotificationsResponse'
            forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
Prelude.<$> (forall a. FromJSON a => Object -> Either String a
Data.eitherParseJSON Object
x)
            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 GetVaultNotifications where
  hashWithSalt :: Int -> GetVaultNotifications -> Int
hashWithSalt Int
_salt GetVaultNotifications' {Text
vaultName :: Text
accountId :: Text
$sel:vaultName:GetVaultNotifications' :: GetVaultNotifications -> Text
$sel:accountId:GetVaultNotifications' :: GetVaultNotifications -> Text
..} =
    Int
_salt
      forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Text
accountId
      forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Text
vaultName

instance Prelude.NFData GetVaultNotifications where
  rnf :: GetVaultNotifications -> ()
rnf GetVaultNotifications' {Text
vaultName :: Text
accountId :: Text
$sel:vaultName:GetVaultNotifications' :: GetVaultNotifications -> Text
$sel:accountId:GetVaultNotifications' :: GetVaultNotifications -> Text
..} =
    forall a. NFData a => a -> ()
Prelude.rnf Text
accountId
      seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf Text
vaultName

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

instance Data.ToPath GetVaultNotifications where
  toPath :: GetVaultNotifications -> ByteString
toPath GetVaultNotifications' {Text
vaultName :: Text
accountId :: Text
$sel:vaultName:GetVaultNotifications' :: GetVaultNotifications -> Text
$sel:accountId:GetVaultNotifications' :: GetVaultNotifications -> Text
..} =
    forall a. Monoid a => [a] -> a
Prelude.mconcat
      [ ByteString
"/",
        forall a. ToByteString a => a -> ByteString
Data.toBS Text
accountId,
        ByteString
"/vaults/",
        forall a. ToByteString a => a -> ByteString
Data.toBS Text
vaultName,
        ByteString
"/notification-configuration"
      ]

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

-- | Contains the Amazon S3 Glacier response to your request.
--
-- /See:/ 'newGetVaultNotificationsResponse' smart constructor.
data GetVaultNotificationsResponse = GetVaultNotificationsResponse'
  { -- | Returns the notification configuration set on the vault.
    GetVaultNotificationsResponse -> Maybe VaultNotificationConfig
vaultNotificationConfig :: Prelude.Maybe VaultNotificationConfig,
    -- | The response's http status code.
    GetVaultNotificationsResponse -> Int
httpStatus :: Prelude.Int
  }
  deriving (GetVaultNotificationsResponse
-> GetVaultNotificationsResponse -> Bool
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: GetVaultNotificationsResponse
-> GetVaultNotificationsResponse -> Bool
$c/= :: GetVaultNotificationsResponse
-> GetVaultNotificationsResponse -> Bool
== :: GetVaultNotificationsResponse
-> GetVaultNotificationsResponse -> Bool
$c== :: GetVaultNotificationsResponse
-> GetVaultNotificationsResponse -> Bool
Prelude.Eq, ReadPrec [GetVaultNotificationsResponse]
ReadPrec GetVaultNotificationsResponse
Int -> ReadS GetVaultNotificationsResponse
ReadS [GetVaultNotificationsResponse]
forall a.
(Int -> ReadS a)
-> ReadS [a] -> ReadPrec a -> ReadPrec [a] -> Read a
readListPrec :: ReadPrec [GetVaultNotificationsResponse]
$creadListPrec :: ReadPrec [GetVaultNotificationsResponse]
readPrec :: ReadPrec GetVaultNotificationsResponse
$creadPrec :: ReadPrec GetVaultNotificationsResponse
readList :: ReadS [GetVaultNotificationsResponse]
$creadList :: ReadS [GetVaultNotificationsResponse]
readsPrec :: Int -> ReadS GetVaultNotificationsResponse
$creadsPrec :: Int -> ReadS GetVaultNotificationsResponse
Prelude.Read, Int -> GetVaultNotificationsResponse -> ShowS
[GetVaultNotificationsResponse] -> ShowS
GetVaultNotificationsResponse -> String
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [GetVaultNotificationsResponse] -> ShowS
$cshowList :: [GetVaultNotificationsResponse] -> ShowS
show :: GetVaultNotificationsResponse -> String
$cshow :: GetVaultNotificationsResponse -> String
showsPrec :: Int -> GetVaultNotificationsResponse -> ShowS
$cshowsPrec :: Int -> GetVaultNotificationsResponse -> ShowS
Prelude.Show, forall x.
Rep GetVaultNotificationsResponse x
-> GetVaultNotificationsResponse
forall x.
GetVaultNotificationsResponse
-> Rep GetVaultNotificationsResponse x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cto :: forall x.
Rep GetVaultNotificationsResponse x
-> GetVaultNotificationsResponse
$cfrom :: forall x.
GetVaultNotificationsResponse
-> Rep GetVaultNotificationsResponse x
Prelude.Generic)

-- |
-- Create a value of 'GetVaultNotificationsResponse' 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:
--
-- 'vaultNotificationConfig', 'getVaultNotificationsResponse_vaultNotificationConfig' - Returns the notification configuration set on the vault.
--
-- 'httpStatus', 'getVaultNotificationsResponse_httpStatus' - The response's http status code.
newGetVaultNotificationsResponse ::
  -- | 'httpStatus'
  Prelude.Int ->
  GetVaultNotificationsResponse
newGetVaultNotificationsResponse :: Int -> GetVaultNotificationsResponse
newGetVaultNotificationsResponse Int
pHttpStatus_ =
  GetVaultNotificationsResponse'
    { $sel:vaultNotificationConfig:GetVaultNotificationsResponse' :: Maybe VaultNotificationConfig
vaultNotificationConfig =
        forall a. Maybe a
Prelude.Nothing,
      $sel:httpStatus:GetVaultNotificationsResponse' :: Int
httpStatus = Int
pHttpStatus_
    }

-- | Returns the notification configuration set on the vault.
getVaultNotificationsResponse_vaultNotificationConfig :: Lens.Lens' GetVaultNotificationsResponse (Prelude.Maybe VaultNotificationConfig)
getVaultNotificationsResponse_vaultNotificationConfig :: Lens' GetVaultNotificationsResponse (Maybe VaultNotificationConfig)
getVaultNotificationsResponse_vaultNotificationConfig = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\GetVaultNotificationsResponse' {Maybe VaultNotificationConfig
vaultNotificationConfig :: Maybe VaultNotificationConfig
$sel:vaultNotificationConfig:GetVaultNotificationsResponse' :: GetVaultNotificationsResponse -> Maybe VaultNotificationConfig
vaultNotificationConfig} -> Maybe VaultNotificationConfig
vaultNotificationConfig) (\s :: GetVaultNotificationsResponse
s@GetVaultNotificationsResponse' {} Maybe VaultNotificationConfig
a -> GetVaultNotificationsResponse
s {$sel:vaultNotificationConfig:GetVaultNotificationsResponse' :: Maybe VaultNotificationConfig
vaultNotificationConfig = Maybe VaultNotificationConfig
a} :: GetVaultNotificationsResponse)

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

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