{-# 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.DynamoDB.DeleteBackup
-- Copyright   : (c) 2013-2023 Brendan Hay
-- License     : Mozilla Public License, v. 2.0.
-- Maintainer  : Brendan Hay
-- Stability   : auto-generated
-- Portability : non-portable (GHC extensions)
--
-- Deletes an existing backup of a table.
--
-- You can call @DeleteBackup@ at a maximum rate of 10 times per second.
module Amazonka.DynamoDB.DeleteBackup
  ( -- * Creating a Request
    DeleteBackup (..),
    newDeleteBackup,

    -- * Request Lenses
    deleteBackup_backupArn,

    -- * Destructuring the Response
    DeleteBackupResponse (..),
    newDeleteBackupResponse,

    -- * Response Lenses
    deleteBackupResponse_backupDescription,
    deleteBackupResponse_httpStatus,
  )
where

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

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

-- |
-- Create a value of 'DeleteBackup' 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:
--
-- 'backupArn', 'deleteBackup_backupArn' - The ARN associated with the backup.
newDeleteBackup ::
  -- | 'backupArn'
  Prelude.Text ->
  DeleteBackup
newDeleteBackup :: Text -> DeleteBackup
newDeleteBackup Text
pBackupArn_ =
  DeleteBackup' {$sel:backupArn:DeleteBackup' :: Text
backupArn = Text
pBackupArn_}

-- | The ARN associated with the backup.
deleteBackup_backupArn :: Lens.Lens' DeleteBackup Prelude.Text
deleteBackup_backupArn :: Lens' DeleteBackup Text
deleteBackup_backupArn = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\DeleteBackup' {Text
backupArn :: Text
$sel:backupArn:DeleteBackup' :: DeleteBackup -> Text
backupArn} -> Text
backupArn) (\s :: DeleteBackup
s@DeleteBackup' {} Text
a -> DeleteBackup
s {$sel:backupArn:DeleteBackup' :: Text
backupArn = Text
a} :: DeleteBackup)

instance Core.AWSRequest DeleteBackup where
  type AWSResponse DeleteBackup = DeleteBackupResponse
  request :: (Service -> Service) -> DeleteBackup -> Request DeleteBackup
request Service -> Service
overrides =
    forall a. (ToRequest a, ToJSON a) => Service -> a -> Request a
Request.postJSON (Service -> Service
overrides Service
defaultService)
  response :: forall (m :: * -> *).
MonadResource m =>
(ByteStringLazy -> IO ByteStringLazy)
-> Service
-> Proxy DeleteBackup
-> ClientResponse ClientBody
-> m (Either Error (ClientResponse (AWSResponse DeleteBackup)))
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 BackupDescription -> Int -> DeleteBackupResponse
DeleteBackupResponse'
            forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
Prelude.<$> (Object
x forall a. FromJSON a => Object -> Key -> Either String (Maybe a)
Data..?> Key
"BackupDescription")
            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 DeleteBackup where
  hashWithSalt :: Int -> DeleteBackup -> Int
hashWithSalt Int
_salt DeleteBackup' {Text
backupArn :: Text
$sel:backupArn:DeleteBackup' :: DeleteBackup -> Text
..} =
    Int
_salt forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Text
backupArn

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

instance Data.ToHeaders DeleteBackup where
  toHeaders :: DeleteBackup -> ResponseHeaders
toHeaders =
    forall a b. a -> b -> a
Prelude.const
      ( forall a. Monoid a => [a] -> a
Prelude.mconcat
          [ HeaderName
"X-Amz-Target"
              forall a. ToHeader a => HeaderName -> a -> ResponseHeaders
Data.=# ( ByteString
"DynamoDB_20120810.DeleteBackup" ::
                          Prelude.ByteString
                      ),
            HeaderName
"Content-Type"
              forall a. ToHeader a => HeaderName -> a -> ResponseHeaders
Data.=# ( ByteString
"application/x-amz-json-1.0" ::
                          Prelude.ByteString
                      )
          ]
      )

instance Data.ToJSON DeleteBackup where
  toJSON :: DeleteBackup -> Value
toJSON DeleteBackup' {Text
backupArn :: Text
$sel:backupArn:DeleteBackup' :: DeleteBackup -> Text
..} =
    [Pair] -> Value
Data.object
      ( forall a. [Maybe a] -> [a]
Prelude.catMaybes
          [forall a. a -> Maybe a
Prelude.Just (Key
"BackupArn" forall kv v. (KeyValue kv, ToJSON v) => Key -> v -> kv
Data..= Text
backupArn)]
      )

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

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

-- | /See:/ 'newDeleteBackupResponse' smart constructor.
data DeleteBackupResponse = DeleteBackupResponse'
  { -- | Contains the description of the backup created for the table.
    DeleteBackupResponse -> Maybe BackupDescription
backupDescription :: Prelude.Maybe BackupDescription,
    -- | The response's http status code.
    DeleteBackupResponse -> Int
httpStatus :: Prelude.Int
  }
  deriving (DeleteBackupResponse -> DeleteBackupResponse -> Bool
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: DeleteBackupResponse -> DeleteBackupResponse -> Bool
$c/= :: DeleteBackupResponse -> DeleteBackupResponse -> Bool
== :: DeleteBackupResponse -> DeleteBackupResponse -> Bool
$c== :: DeleteBackupResponse -> DeleteBackupResponse -> Bool
Prelude.Eq, ReadPrec [DeleteBackupResponse]
ReadPrec DeleteBackupResponse
Int -> ReadS DeleteBackupResponse
ReadS [DeleteBackupResponse]
forall a.
(Int -> ReadS a)
-> ReadS [a] -> ReadPrec a -> ReadPrec [a] -> Read a
readListPrec :: ReadPrec [DeleteBackupResponse]
$creadListPrec :: ReadPrec [DeleteBackupResponse]
readPrec :: ReadPrec DeleteBackupResponse
$creadPrec :: ReadPrec DeleteBackupResponse
readList :: ReadS [DeleteBackupResponse]
$creadList :: ReadS [DeleteBackupResponse]
readsPrec :: Int -> ReadS DeleteBackupResponse
$creadsPrec :: Int -> ReadS DeleteBackupResponse
Prelude.Read, Int -> DeleteBackupResponse -> ShowS
[DeleteBackupResponse] -> ShowS
DeleteBackupResponse -> String
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [DeleteBackupResponse] -> ShowS
$cshowList :: [DeleteBackupResponse] -> ShowS
show :: DeleteBackupResponse -> String
$cshow :: DeleteBackupResponse -> String
showsPrec :: Int -> DeleteBackupResponse -> ShowS
$cshowsPrec :: Int -> DeleteBackupResponse -> ShowS
Prelude.Show, forall x. Rep DeleteBackupResponse x -> DeleteBackupResponse
forall x. DeleteBackupResponse -> Rep DeleteBackupResponse x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cto :: forall x. Rep DeleteBackupResponse x -> DeleteBackupResponse
$cfrom :: forall x. DeleteBackupResponse -> Rep DeleteBackupResponse x
Prelude.Generic)

-- |
-- Create a value of 'DeleteBackupResponse' 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:
--
-- 'backupDescription', 'deleteBackupResponse_backupDescription' - Contains the description of the backup created for the table.
--
-- 'httpStatus', 'deleteBackupResponse_httpStatus' - The response's http status code.
newDeleteBackupResponse ::
  -- | 'httpStatus'
  Prelude.Int ->
  DeleteBackupResponse
newDeleteBackupResponse :: Int -> DeleteBackupResponse
newDeleteBackupResponse Int
pHttpStatus_ =
  DeleteBackupResponse'
    { $sel:backupDescription:DeleteBackupResponse' :: Maybe BackupDescription
backupDescription =
        forall a. Maybe a
Prelude.Nothing,
      $sel:httpStatus:DeleteBackupResponse' :: Int
httpStatus = Int
pHttpStatus_
    }

-- | Contains the description of the backup created for the table.
deleteBackupResponse_backupDescription :: Lens.Lens' DeleteBackupResponse (Prelude.Maybe BackupDescription)
deleteBackupResponse_backupDescription :: Lens' DeleteBackupResponse (Maybe BackupDescription)
deleteBackupResponse_backupDescription = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\DeleteBackupResponse' {Maybe BackupDescription
backupDescription :: Maybe BackupDescription
$sel:backupDescription:DeleteBackupResponse' :: DeleteBackupResponse -> Maybe BackupDescription
backupDescription} -> Maybe BackupDescription
backupDescription) (\s :: DeleteBackupResponse
s@DeleteBackupResponse' {} Maybe BackupDescription
a -> DeleteBackupResponse
s {$sel:backupDescription:DeleteBackupResponse' :: Maybe BackupDescription
backupDescription = Maybe BackupDescription
a} :: DeleteBackupResponse)

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

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