{-# 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.Backup.PutBackupVaultNotifications
-- Copyright   : (c) 2013-2023 Brendan Hay
-- License     : Mozilla Public License, v. 2.0.
-- Maintainer  : Brendan Hay
-- Stability   : auto-generated
-- Portability : non-portable (GHC extensions)
--
-- Turns on notifications on a backup vault for the specified topic and
-- events.
module Amazonka.Backup.PutBackupVaultNotifications
  ( -- * Creating a Request
    PutBackupVaultNotifications (..),
    newPutBackupVaultNotifications,

    -- * Request Lenses
    putBackupVaultNotifications_backupVaultName,
    putBackupVaultNotifications_sNSTopicArn,
    putBackupVaultNotifications_backupVaultEvents,

    -- * Destructuring the Response
    PutBackupVaultNotificationsResponse (..),
    newPutBackupVaultNotificationsResponse,
  )
where

import Amazonka.Backup.Types
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 qualified Amazonka.Request as Request
import qualified Amazonka.Response as Response

-- | /See:/ 'newPutBackupVaultNotifications' smart constructor.
data PutBackupVaultNotifications = PutBackupVaultNotifications'
  { -- | The name of a logical container where backups are stored. Backup vaults
    -- are identified by names that are unique to the account used to create
    -- them and the Amazon Web Services Region where they are created. They
    -- consist of lowercase letters, numbers, and hyphens.
    PutBackupVaultNotifications -> Text
backupVaultName :: Prelude.Text,
    -- | The Amazon Resource Name (ARN) that specifies the topic for a backup
    -- vault’s events; for example,
    -- @arn:aws:sns:us-west-2:111122223333:MyVaultTopic@.
    PutBackupVaultNotifications -> Text
sNSTopicArn :: Prelude.Text,
    -- | An array of events that indicate the status of jobs to back up resources
    -- to the backup vault.
    --
    -- For common use cases and code samples, see
    -- <https://docs.aws.amazon.com/aws-backup/latest/devguide/sns-notifications.html Using Amazon SNS to track Backup events>.
    --
    -- The following events are supported:
    --
    -- -   @BACKUP_JOB_STARTED@ | @BACKUP_JOB_COMPLETED@
    --
    -- -   @COPY_JOB_STARTED@ | @COPY_JOB_SUCCESSFUL@ | @COPY_JOB_FAILED@
    --
    -- -   @RESTORE_JOB_STARTED@ | @RESTORE_JOB_COMPLETED@ |
    --     @RECOVERY_POINT_MODIFIED@
    --
    -- -   @S3_BACKUP_OBJECT_FAILED@ | @S3_RESTORE_OBJECT_FAILED@
    --
    -- The list below shows items that are deprecated events (for reference)
    -- and are no longer in use. They are no longer supported and will not
    -- return statuses or notifications. Refer to the list above for current
    -- supported events.
    PutBackupVaultNotifications -> [BackupVaultEvent]
backupVaultEvents :: [BackupVaultEvent]
  }
  deriving (PutBackupVaultNotifications -> PutBackupVaultNotifications -> Bool
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: PutBackupVaultNotifications -> PutBackupVaultNotifications -> Bool
$c/= :: PutBackupVaultNotifications -> PutBackupVaultNotifications -> Bool
== :: PutBackupVaultNotifications -> PutBackupVaultNotifications -> Bool
$c== :: PutBackupVaultNotifications -> PutBackupVaultNotifications -> Bool
Prelude.Eq, ReadPrec [PutBackupVaultNotifications]
ReadPrec PutBackupVaultNotifications
Int -> ReadS PutBackupVaultNotifications
ReadS [PutBackupVaultNotifications]
forall a.
(Int -> ReadS a)
-> ReadS [a] -> ReadPrec a -> ReadPrec [a] -> Read a
readListPrec :: ReadPrec [PutBackupVaultNotifications]
$creadListPrec :: ReadPrec [PutBackupVaultNotifications]
readPrec :: ReadPrec PutBackupVaultNotifications
$creadPrec :: ReadPrec PutBackupVaultNotifications
readList :: ReadS [PutBackupVaultNotifications]
$creadList :: ReadS [PutBackupVaultNotifications]
readsPrec :: Int -> ReadS PutBackupVaultNotifications
$creadsPrec :: Int -> ReadS PutBackupVaultNotifications
Prelude.Read, Int -> PutBackupVaultNotifications -> ShowS
[PutBackupVaultNotifications] -> ShowS
PutBackupVaultNotifications -> String
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [PutBackupVaultNotifications] -> ShowS
$cshowList :: [PutBackupVaultNotifications] -> ShowS
show :: PutBackupVaultNotifications -> String
$cshow :: PutBackupVaultNotifications -> String
showsPrec :: Int -> PutBackupVaultNotifications -> ShowS
$cshowsPrec :: Int -> PutBackupVaultNotifications -> ShowS
Prelude.Show, forall x.
Rep PutBackupVaultNotifications x -> PutBackupVaultNotifications
forall x.
PutBackupVaultNotifications -> Rep PutBackupVaultNotifications x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cto :: forall x.
Rep PutBackupVaultNotifications x -> PutBackupVaultNotifications
$cfrom :: forall x.
PutBackupVaultNotifications -> Rep PutBackupVaultNotifications x
Prelude.Generic)

-- |
-- Create a value of 'PutBackupVaultNotifications' 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:
--
-- 'backupVaultName', 'putBackupVaultNotifications_backupVaultName' - The name of a logical container where backups are stored. Backup vaults
-- are identified by names that are unique to the account used to create
-- them and the Amazon Web Services Region where they are created. They
-- consist of lowercase letters, numbers, and hyphens.
--
-- 'sNSTopicArn', 'putBackupVaultNotifications_sNSTopicArn' - The Amazon Resource Name (ARN) that specifies the topic for a backup
-- vault’s events; for example,
-- @arn:aws:sns:us-west-2:111122223333:MyVaultTopic@.
--
-- 'backupVaultEvents', 'putBackupVaultNotifications_backupVaultEvents' - An array of events that indicate the status of jobs to back up resources
-- to the backup vault.
--
-- For common use cases and code samples, see
-- <https://docs.aws.amazon.com/aws-backup/latest/devguide/sns-notifications.html Using Amazon SNS to track Backup events>.
--
-- The following events are supported:
--
-- -   @BACKUP_JOB_STARTED@ | @BACKUP_JOB_COMPLETED@
--
-- -   @COPY_JOB_STARTED@ | @COPY_JOB_SUCCESSFUL@ | @COPY_JOB_FAILED@
--
-- -   @RESTORE_JOB_STARTED@ | @RESTORE_JOB_COMPLETED@ |
--     @RECOVERY_POINT_MODIFIED@
--
-- -   @S3_BACKUP_OBJECT_FAILED@ | @S3_RESTORE_OBJECT_FAILED@
--
-- The list below shows items that are deprecated events (for reference)
-- and are no longer in use. They are no longer supported and will not
-- return statuses or notifications. Refer to the list above for current
-- supported events.
newPutBackupVaultNotifications ::
  -- | 'backupVaultName'
  Prelude.Text ->
  -- | 'sNSTopicArn'
  Prelude.Text ->
  PutBackupVaultNotifications
newPutBackupVaultNotifications :: Text -> Text -> PutBackupVaultNotifications
newPutBackupVaultNotifications
  Text
pBackupVaultName_
  Text
pSNSTopicArn_ =
    PutBackupVaultNotifications'
      { $sel:backupVaultName:PutBackupVaultNotifications' :: Text
backupVaultName =
          Text
pBackupVaultName_,
        $sel:sNSTopicArn:PutBackupVaultNotifications' :: Text
sNSTopicArn = Text
pSNSTopicArn_,
        $sel:backupVaultEvents:PutBackupVaultNotifications' :: [BackupVaultEvent]
backupVaultEvents = forall a. Monoid a => a
Prelude.mempty
      }

-- | The name of a logical container where backups are stored. Backup vaults
-- are identified by names that are unique to the account used to create
-- them and the Amazon Web Services Region where they are created. They
-- consist of lowercase letters, numbers, and hyphens.
putBackupVaultNotifications_backupVaultName :: Lens.Lens' PutBackupVaultNotifications Prelude.Text
putBackupVaultNotifications_backupVaultName :: Lens' PutBackupVaultNotifications Text
putBackupVaultNotifications_backupVaultName = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\PutBackupVaultNotifications' {Text
backupVaultName :: Text
$sel:backupVaultName:PutBackupVaultNotifications' :: PutBackupVaultNotifications -> Text
backupVaultName} -> Text
backupVaultName) (\s :: PutBackupVaultNotifications
s@PutBackupVaultNotifications' {} Text
a -> PutBackupVaultNotifications
s {$sel:backupVaultName:PutBackupVaultNotifications' :: Text
backupVaultName = Text
a} :: PutBackupVaultNotifications)

-- | The Amazon Resource Name (ARN) that specifies the topic for a backup
-- vault’s events; for example,
-- @arn:aws:sns:us-west-2:111122223333:MyVaultTopic@.
putBackupVaultNotifications_sNSTopicArn :: Lens.Lens' PutBackupVaultNotifications Prelude.Text
putBackupVaultNotifications_sNSTopicArn :: Lens' PutBackupVaultNotifications Text
putBackupVaultNotifications_sNSTopicArn = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\PutBackupVaultNotifications' {Text
sNSTopicArn :: Text
$sel:sNSTopicArn:PutBackupVaultNotifications' :: PutBackupVaultNotifications -> Text
sNSTopicArn} -> Text
sNSTopicArn) (\s :: PutBackupVaultNotifications
s@PutBackupVaultNotifications' {} Text
a -> PutBackupVaultNotifications
s {$sel:sNSTopicArn:PutBackupVaultNotifications' :: Text
sNSTopicArn = Text
a} :: PutBackupVaultNotifications)

-- | An array of events that indicate the status of jobs to back up resources
-- to the backup vault.
--
-- For common use cases and code samples, see
-- <https://docs.aws.amazon.com/aws-backup/latest/devguide/sns-notifications.html Using Amazon SNS to track Backup events>.
--
-- The following events are supported:
--
-- -   @BACKUP_JOB_STARTED@ | @BACKUP_JOB_COMPLETED@
--
-- -   @COPY_JOB_STARTED@ | @COPY_JOB_SUCCESSFUL@ | @COPY_JOB_FAILED@
--
-- -   @RESTORE_JOB_STARTED@ | @RESTORE_JOB_COMPLETED@ |
--     @RECOVERY_POINT_MODIFIED@
--
-- -   @S3_BACKUP_OBJECT_FAILED@ | @S3_RESTORE_OBJECT_FAILED@
--
-- The list below shows items that are deprecated events (for reference)
-- and are no longer in use. They are no longer supported and will not
-- return statuses or notifications. Refer to the list above for current
-- supported events.
putBackupVaultNotifications_backupVaultEvents :: Lens.Lens' PutBackupVaultNotifications [BackupVaultEvent]
putBackupVaultNotifications_backupVaultEvents :: Lens' PutBackupVaultNotifications [BackupVaultEvent]
putBackupVaultNotifications_backupVaultEvents = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\PutBackupVaultNotifications' {[BackupVaultEvent]
backupVaultEvents :: [BackupVaultEvent]
$sel:backupVaultEvents:PutBackupVaultNotifications' :: PutBackupVaultNotifications -> [BackupVaultEvent]
backupVaultEvents} -> [BackupVaultEvent]
backupVaultEvents) (\s :: PutBackupVaultNotifications
s@PutBackupVaultNotifications' {} [BackupVaultEvent]
a -> PutBackupVaultNotifications
s {$sel:backupVaultEvents:PutBackupVaultNotifications' :: [BackupVaultEvent]
backupVaultEvents = [BackupVaultEvent]
a} :: PutBackupVaultNotifications) forall b c a. (b -> c) -> (a -> b) -> a -> c
Prelude.. forall s t a b. (Coercible s a, Coercible t b) => Iso s t a b
Lens.coerced

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

instance Prelude.Hashable PutBackupVaultNotifications where
  hashWithSalt :: Int -> PutBackupVaultNotifications -> Int
hashWithSalt Int
_salt PutBackupVaultNotifications' {[BackupVaultEvent]
Text
backupVaultEvents :: [BackupVaultEvent]
sNSTopicArn :: Text
backupVaultName :: Text
$sel:backupVaultEvents:PutBackupVaultNotifications' :: PutBackupVaultNotifications -> [BackupVaultEvent]
$sel:sNSTopicArn:PutBackupVaultNotifications' :: PutBackupVaultNotifications -> Text
$sel:backupVaultName:PutBackupVaultNotifications' :: PutBackupVaultNotifications -> Text
..} =
    Int
_salt
      forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Text
backupVaultName
      forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Text
sNSTopicArn
      forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` [BackupVaultEvent]
backupVaultEvents

instance Prelude.NFData PutBackupVaultNotifications where
  rnf :: PutBackupVaultNotifications -> ()
rnf PutBackupVaultNotifications' {[BackupVaultEvent]
Text
backupVaultEvents :: [BackupVaultEvent]
sNSTopicArn :: Text
backupVaultName :: Text
$sel:backupVaultEvents:PutBackupVaultNotifications' :: PutBackupVaultNotifications -> [BackupVaultEvent]
$sel:sNSTopicArn:PutBackupVaultNotifications' :: PutBackupVaultNotifications -> Text
$sel:backupVaultName:PutBackupVaultNotifications' :: PutBackupVaultNotifications -> Text
..} =
    forall a. NFData a => a -> ()
Prelude.rnf Text
backupVaultName
      seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf Text
sNSTopicArn
      seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf [BackupVaultEvent]
backupVaultEvents

instance Data.ToHeaders PutBackupVaultNotifications where
  toHeaders :: PutBackupVaultNotifications -> [Header]
toHeaders =
    forall a b. a -> b -> a
Prelude.const
      ( forall a. Monoid a => [a] -> a
Prelude.mconcat
          [ HeaderName
"Content-Type"
              forall a. ToHeader a => HeaderName -> a -> [Header]
Data.=# ( ByteString
"application/x-amz-json-1.1" ::
                          Prelude.ByteString
                      )
          ]
      )

instance Data.ToJSON PutBackupVaultNotifications where
  toJSON :: PutBackupVaultNotifications -> Value
toJSON PutBackupVaultNotifications' {[BackupVaultEvent]
Text
backupVaultEvents :: [BackupVaultEvent]
sNSTopicArn :: Text
backupVaultName :: Text
$sel:backupVaultEvents:PutBackupVaultNotifications' :: PutBackupVaultNotifications -> [BackupVaultEvent]
$sel:sNSTopicArn:PutBackupVaultNotifications' :: PutBackupVaultNotifications -> Text
$sel:backupVaultName:PutBackupVaultNotifications' :: PutBackupVaultNotifications -> Text
..} =
    [Pair] -> Value
Data.object
      ( forall a. [Maybe a] -> [a]
Prelude.catMaybes
          [ forall a. a -> Maybe a
Prelude.Just (Key
"SNSTopicArn" forall kv v. (KeyValue kv, ToJSON v) => Key -> v -> kv
Data..= Text
sNSTopicArn),
            forall a. a -> Maybe a
Prelude.Just
              (Key
"BackupVaultEvents" forall kv v. (KeyValue kv, ToJSON v) => Key -> v -> kv
Data..= [BackupVaultEvent]
backupVaultEvents)
          ]
      )

instance Data.ToPath PutBackupVaultNotifications where
  toPath :: PutBackupVaultNotifications -> ByteString
toPath PutBackupVaultNotifications' {[BackupVaultEvent]
Text
backupVaultEvents :: [BackupVaultEvent]
sNSTopicArn :: Text
backupVaultName :: Text
$sel:backupVaultEvents:PutBackupVaultNotifications' :: PutBackupVaultNotifications -> [BackupVaultEvent]
$sel:sNSTopicArn:PutBackupVaultNotifications' :: PutBackupVaultNotifications -> Text
$sel:backupVaultName:PutBackupVaultNotifications' :: PutBackupVaultNotifications -> Text
..} =
    forall a. Monoid a => [a] -> a
Prelude.mconcat
      [ ByteString
"/backup-vaults/",
        forall a. ToByteString a => a -> ByteString
Data.toBS Text
backupVaultName,
        ByteString
"/notification-configuration"
      ]

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

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

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

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