{-# 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.SetVaultNotifications
-- 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 configures notifications that will be sent when specific
-- events happen to a vault. By default, you don\'t get any notifications.
--
-- To configure vault notifications, send a PUT request to the
-- @notification-configuration@ subresource of the vault. The request
-- should include a JSON document that provides an Amazon SNS topic and
-- specific events for which you want Amazon S3 Glacier to send
-- notifications to the topic.
--
-- Amazon SNS topics must grant permission to the vault to be allowed to
-- publish notifications to the topic. You can configure a vault to publish
-- a notification for the following vault events:
--
-- -   __ArchiveRetrievalCompleted__ This event occurs when a job that was
--     initiated for an archive retrieval is completed (InitiateJob). The
--     status of the completed job can be \"Succeeded\" or \"Failed\". The
--     notification sent to the SNS topic is the same output as returned
--     from DescribeJob.
--
-- -   __InventoryRetrievalCompleted__ This event occurs when a job that
--     was initiated for an inventory retrieval is completed (InitiateJob).
--     The status of the completed job can be \"Succeeded\" or \"Failed\".
--     The notification sent to the SNS topic is the same output as
--     returned from DescribeJob.
--
-- 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-put.html Set Vault Notification Configuration>
-- in the /Amazon Glacier Developer Guide/.
module Amazonka.Glacier.SetVaultNotifications
  ( -- * Creating a Request
    SetVaultNotifications (..),
    newSetVaultNotifications,

    -- * Request Lenses
    setVaultNotifications_vaultNotificationConfig,
    setVaultNotifications_accountId,
    setVaultNotifications_vaultName,

    -- * Destructuring the Response
    SetVaultNotificationsResponse (..),
    newSetVaultNotificationsResponse,
  )
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 to configure notifications that will be sent when
-- specific events happen to a vault.
--
-- /See:/ 'newSetVaultNotifications' smart constructor.
data SetVaultNotifications = SetVaultNotifications'
  { -- | Provides options for specifying notification configuration.
    SetVaultNotifications -> Maybe VaultNotificationConfig
vaultNotificationConfig :: Prelude.Maybe VaultNotificationConfig,
    -- | 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.
    SetVaultNotifications -> Text
accountId :: Prelude.Text,
    -- | The name of the vault.
    SetVaultNotifications -> Text
vaultName :: Prelude.Text
  }
  deriving (SetVaultNotifications -> SetVaultNotifications -> Bool
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: SetVaultNotifications -> SetVaultNotifications -> Bool
$c/= :: SetVaultNotifications -> SetVaultNotifications -> Bool
== :: SetVaultNotifications -> SetVaultNotifications -> Bool
$c== :: SetVaultNotifications -> SetVaultNotifications -> Bool
Prelude.Eq, ReadPrec [SetVaultNotifications]
ReadPrec SetVaultNotifications
Int -> ReadS SetVaultNotifications
ReadS [SetVaultNotifications]
forall a.
(Int -> ReadS a)
-> ReadS [a] -> ReadPrec a -> ReadPrec [a] -> Read a
readListPrec :: ReadPrec [SetVaultNotifications]
$creadListPrec :: ReadPrec [SetVaultNotifications]
readPrec :: ReadPrec SetVaultNotifications
$creadPrec :: ReadPrec SetVaultNotifications
readList :: ReadS [SetVaultNotifications]
$creadList :: ReadS [SetVaultNotifications]
readsPrec :: Int -> ReadS SetVaultNotifications
$creadsPrec :: Int -> ReadS SetVaultNotifications
Prelude.Read, Int -> SetVaultNotifications -> ShowS
[SetVaultNotifications] -> ShowS
SetVaultNotifications -> String
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [SetVaultNotifications] -> ShowS
$cshowList :: [SetVaultNotifications] -> ShowS
show :: SetVaultNotifications -> String
$cshow :: SetVaultNotifications -> String
showsPrec :: Int -> SetVaultNotifications -> ShowS
$cshowsPrec :: Int -> SetVaultNotifications -> ShowS
Prelude.Show, forall x. Rep SetVaultNotifications x -> SetVaultNotifications
forall x. SetVaultNotifications -> Rep SetVaultNotifications x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cto :: forall x. Rep SetVaultNotifications x -> SetVaultNotifications
$cfrom :: forall x. SetVaultNotifications -> Rep SetVaultNotifications x
Prelude.Generic)

-- |
-- Create a value of 'SetVaultNotifications' 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', 'setVaultNotifications_vaultNotificationConfig' - Provides options for specifying notification configuration.
--
-- 'accountId', 'setVaultNotifications_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', 'setVaultNotifications_vaultName' - The name of the vault.
newSetVaultNotifications ::
  -- | 'accountId'
  Prelude.Text ->
  -- | 'vaultName'
  Prelude.Text ->
  SetVaultNotifications
newSetVaultNotifications :: Text -> Text -> SetVaultNotifications
newSetVaultNotifications Text
pAccountId_ Text
pVaultName_ =
  SetVaultNotifications'
    { $sel:vaultNotificationConfig:SetVaultNotifications' :: Maybe VaultNotificationConfig
vaultNotificationConfig =
        forall a. Maybe a
Prelude.Nothing,
      $sel:accountId:SetVaultNotifications' :: Text
accountId = Text
pAccountId_,
      $sel:vaultName:SetVaultNotifications' :: Text
vaultName = Text
pVaultName_
    }

-- | Provides options for specifying notification configuration.
setVaultNotifications_vaultNotificationConfig :: Lens.Lens' SetVaultNotifications (Prelude.Maybe VaultNotificationConfig)
setVaultNotifications_vaultNotificationConfig :: Lens' SetVaultNotifications (Maybe VaultNotificationConfig)
setVaultNotifications_vaultNotificationConfig = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\SetVaultNotifications' {Maybe VaultNotificationConfig
vaultNotificationConfig :: Maybe VaultNotificationConfig
$sel:vaultNotificationConfig:SetVaultNotifications' :: SetVaultNotifications -> Maybe VaultNotificationConfig
vaultNotificationConfig} -> Maybe VaultNotificationConfig
vaultNotificationConfig) (\s :: SetVaultNotifications
s@SetVaultNotifications' {} Maybe VaultNotificationConfig
a -> SetVaultNotifications
s {$sel:vaultNotificationConfig:SetVaultNotifications' :: Maybe VaultNotificationConfig
vaultNotificationConfig = Maybe VaultNotificationConfig
a} :: SetVaultNotifications)

-- | 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.
setVaultNotifications_accountId :: Lens.Lens' SetVaultNotifications Prelude.Text
setVaultNotifications_accountId :: Lens' SetVaultNotifications Text
setVaultNotifications_accountId = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\SetVaultNotifications' {Text
accountId :: Text
$sel:accountId:SetVaultNotifications' :: SetVaultNotifications -> Text
accountId} -> Text
accountId) (\s :: SetVaultNotifications
s@SetVaultNotifications' {} Text
a -> SetVaultNotifications
s {$sel:accountId:SetVaultNotifications' :: Text
accountId = Text
a} :: SetVaultNotifications)

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

instance Core.AWSRequest SetVaultNotifications where
  type
    AWSResponse SetVaultNotifications =
      SetVaultNotificationsResponse
  request :: (Service -> Service)
-> SetVaultNotifications -> Request SetVaultNotifications
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, ToJSON a) => Service -> a -> Request a
Request.putJSON (Service -> Service
overrides Service
defaultService)
  response :: forall (m :: * -> *).
MonadResource m =>
(ByteStringLazy -> IO ByteStringLazy)
-> Service
-> Proxy SetVaultNotifications
-> ClientResponse ClientBody
-> m (Either
        Error (ClientResponse (AWSResponse SetVaultNotifications)))
response =
    forall (m :: * -> *) a.
MonadResource m =>
AWSResponse a
-> (ByteStringLazy -> IO ByteStringLazy)
-> Service
-> Proxy a
-> ClientResponse ClientBody
-> m (Either Error (ClientResponse (AWSResponse a)))
Response.receiveNull SetVaultNotificationsResponse
SetVaultNotificationsResponse'

instance Prelude.Hashable SetVaultNotifications where
  hashWithSalt :: Int -> SetVaultNotifications -> Int
hashWithSalt Int
_salt SetVaultNotifications' {Maybe VaultNotificationConfig
Text
vaultName :: Text
accountId :: Text
vaultNotificationConfig :: Maybe VaultNotificationConfig
$sel:vaultName:SetVaultNotifications' :: SetVaultNotifications -> Text
$sel:accountId:SetVaultNotifications' :: SetVaultNotifications -> Text
$sel:vaultNotificationConfig:SetVaultNotifications' :: SetVaultNotifications -> Maybe VaultNotificationConfig
..} =
    Int
_salt
      forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Maybe VaultNotificationConfig
vaultNotificationConfig
      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 SetVaultNotifications where
  rnf :: SetVaultNotifications -> ()
rnf SetVaultNotifications' {Maybe VaultNotificationConfig
Text
vaultName :: Text
accountId :: Text
vaultNotificationConfig :: Maybe VaultNotificationConfig
$sel:vaultName:SetVaultNotifications' :: SetVaultNotifications -> Text
$sel:accountId:SetVaultNotifications' :: SetVaultNotifications -> Text
$sel:vaultNotificationConfig:SetVaultNotifications' :: SetVaultNotifications -> 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 Text
accountId
      seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf Text
vaultName

instance Data.ToHeaders SetVaultNotifications where
  toHeaders :: SetVaultNotifications -> [Header]
toHeaders = forall a b. a -> b -> a
Prelude.const forall a. Monoid a => a
Prelude.mempty

instance Data.ToJSON SetVaultNotifications where
  toJSON :: SetVaultNotifications -> Value
toJSON SetVaultNotifications' {Maybe VaultNotificationConfig
Text
vaultName :: Text
accountId :: Text
vaultNotificationConfig :: Maybe VaultNotificationConfig
$sel:vaultName:SetVaultNotifications' :: SetVaultNotifications -> Text
$sel:accountId:SetVaultNotifications' :: SetVaultNotifications -> Text
$sel:vaultNotificationConfig:SetVaultNotifications' :: SetVaultNotifications -> Maybe VaultNotificationConfig
..} =
    forall a. ToJSON a => a -> Value
Data.toJSON Maybe VaultNotificationConfig
vaultNotificationConfig

instance Data.ToPath SetVaultNotifications where
  toPath :: SetVaultNotifications -> ByteString
toPath SetVaultNotifications' {Maybe VaultNotificationConfig
Text
vaultName :: Text
accountId :: Text
vaultNotificationConfig :: Maybe VaultNotificationConfig
$sel:vaultName:SetVaultNotifications' :: SetVaultNotifications -> Text
$sel:accountId:SetVaultNotifications' :: SetVaultNotifications -> Text
$sel:vaultNotificationConfig:SetVaultNotifications' :: SetVaultNotifications -> Maybe VaultNotificationConfig
..} =
    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 SetVaultNotifications where
  toQuery :: SetVaultNotifications -> QueryString
toQuery = forall a b. a -> b -> a
Prelude.const forall a. Monoid a => a
Prelude.mempty

-- | /See:/ 'newSetVaultNotificationsResponse' smart constructor.
data SetVaultNotificationsResponse = SetVaultNotificationsResponse'
  {
  }
  deriving (SetVaultNotificationsResponse
-> SetVaultNotificationsResponse -> Bool
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: SetVaultNotificationsResponse
-> SetVaultNotificationsResponse -> Bool
$c/= :: SetVaultNotificationsResponse
-> SetVaultNotificationsResponse -> Bool
== :: SetVaultNotificationsResponse
-> SetVaultNotificationsResponse -> Bool
$c== :: SetVaultNotificationsResponse
-> SetVaultNotificationsResponse -> Bool
Prelude.Eq, ReadPrec [SetVaultNotificationsResponse]
ReadPrec SetVaultNotificationsResponse
Int -> ReadS SetVaultNotificationsResponse
ReadS [SetVaultNotificationsResponse]
forall a.
(Int -> ReadS a)
-> ReadS [a] -> ReadPrec a -> ReadPrec [a] -> Read a
readListPrec :: ReadPrec [SetVaultNotificationsResponse]
$creadListPrec :: ReadPrec [SetVaultNotificationsResponse]
readPrec :: ReadPrec SetVaultNotificationsResponse
$creadPrec :: ReadPrec SetVaultNotificationsResponse
readList :: ReadS [SetVaultNotificationsResponse]
$creadList :: ReadS [SetVaultNotificationsResponse]
readsPrec :: Int -> ReadS SetVaultNotificationsResponse
$creadsPrec :: Int -> ReadS SetVaultNotificationsResponse
Prelude.Read, Int -> SetVaultNotificationsResponse -> ShowS
[SetVaultNotificationsResponse] -> ShowS
SetVaultNotificationsResponse -> String
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [SetVaultNotificationsResponse] -> ShowS
$cshowList :: [SetVaultNotificationsResponse] -> ShowS
show :: SetVaultNotificationsResponse -> String
$cshow :: SetVaultNotificationsResponse -> String
showsPrec :: Int -> SetVaultNotificationsResponse -> ShowS
$cshowsPrec :: Int -> SetVaultNotificationsResponse -> ShowS
Prelude.Show, forall x.
Rep SetVaultNotificationsResponse x
-> SetVaultNotificationsResponse
forall x.
SetVaultNotificationsResponse
-> Rep SetVaultNotificationsResponse x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cto :: forall x.
Rep SetVaultNotificationsResponse x
-> SetVaultNotificationsResponse
$cfrom :: forall x.
SetVaultNotificationsResponse
-> Rep SetVaultNotificationsResponse x
Prelude.Generic)

-- |
-- Create a value of 'SetVaultNotificationsResponse' 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.
newSetVaultNotificationsResponse ::
  SetVaultNotificationsResponse
newSetVaultNotificationsResponse :: SetVaultNotificationsResponse
newSetVaultNotificationsResponse =
  SetVaultNotificationsResponse
SetVaultNotificationsResponse'

instance Prelude.NFData SetVaultNotificationsResponse where
  rnf :: SetVaultNotificationsResponse -> ()
rnf SetVaultNotificationsResponse
_ = ()