{-# 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.S3.DeleteBucketIntelligentTieringConfiguration
-- 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 the S3 Intelligent-Tiering configuration from the specified
-- bucket.
--
-- The S3 Intelligent-Tiering storage class is designed to optimize storage
-- costs by automatically moving data to the most cost-effective storage
-- access tier, without performance impact or operational overhead. S3
-- Intelligent-Tiering delivers automatic cost savings in three low latency
-- and high throughput access tiers. To get the lowest storage cost on data
-- that can be accessed in minutes to hours, you can choose to activate
-- additional archiving capabilities.
--
-- The S3 Intelligent-Tiering storage class is the ideal storage class for
-- data with unknown, changing, or unpredictable access patterns,
-- independent of object size or retention period. If the size of an object
-- is less than 128 KB, it is not monitored and not eligible for
-- auto-tiering. Smaller objects can be stored, but they are always charged
-- at the Frequent Access tier rates in the S3 Intelligent-Tiering storage
-- class.
--
-- For more information, see
-- <https://docs.aws.amazon.com/AmazonS3/latest/dev/storage-class-intro.html#sc-dynamic-data-access Storage class for automatically optimizing frequently and infrequently accessed objects>.
--
-- Operations related to @DeleteBucketIntelligentTieringConfiguration@
-- include:
--
-- -   <https://docs.aws.amazon.com/AmazonS3/latest/API/API_GetBucketIntelligentTieringConfiguration.html GetBucketIntelligentTieringConfiguration>
--
-- -   <https://docs.aws.amazon.com/AmazonS3/latest/API/API_PutBucketIntelligentTieringConfiguration.html PutBucketIntelligentTieringConfiguration>
--
-- -   <https://docs.aws.amazon.com/AmazonS3/latest/API/API_ListBucketIntelligentTieringConfigurations.html ListBucketIntelligentTieringConfigurations>
module Amazonka.S3.DeleteBucketIntelligentTieringConfiguration
  ( -- * Creating a Request
    DeleteBucketIntelligentTieringConfiguration (..),
    newDeleteBucketIntelligentTieringConfiguration,

    -- * Request Lenses
    deleteBucketIntelligentTieringConfiguration_bucket,
    deleteBucketIntelligentTieringConfiguration_id,

    -- * Destructuring the Response
    DeleteBucketIntelligentTieringConfigurationResponse (..),
    newDeleteBucketIntelligentTieringConfigurationResponse,
  )
where

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
import Amazonka.S3.Types

-- | /See:/ 'newDeleteBucketIntelligentTieringConfiguration' smart constructor.
data DeleteBucketIntelligentTieringConfiguration = DeleteBucketIntelligentTieringConfiguration'
  { -- | The name of the Amazon S3 bucket whose configuration you want to modify
    -- or retrieve.
    DeleteBucketIntelligentTieringConfiguration -> BucketName
bucket :: BucketName,
    -- | The ID used to identify the S3 Intelligent-Tiering configuration.
    DeleteBucketIntelligentTieringConfiguration -> Text
id :: Prelude.Text
  }
  deriving (DeleteBucketIntelligentTieringConfiguration
-> DeleteBucketIntelligentTieringConfiguration -> Bool
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: DeleteBucketIntelligentTieringConfiguration
-> DeleteBucketIntelligentTieringConfiguration -> Bool
$c/= :: DeleteBucketIntelligentTieringConfiguration
-> DeleteBucketIntelligentTieringConfiguration -> Bool
== :: DeleteBucketIntelligentTieringConfiguration
-> DeleteBucketIntelligentTieringConfiguration -> Bool
$c== :: DeleteBucketIntelligentTieringConfiguration
-> DeleteBucketIntelligentTieringConfiguration -> Bool
Prelude.Eq, ReadPrec [DeleteBucketIntelligentTieringConfiguration]
ReadPrec DeleteBucketIntelligentTieringConfiguration
Int -> ReadS DeleteBucketIntelligentTieringConfiguration
ReadS [DeleteBucketIntelligentTieringConfiguration]
forall a.
(Int -> ReadS a)
-> ReadS [a] -> ReadPrec a -> ReadPrec [a] -> Read a
readListPrec :: ReadPrec [DeleteBucketIntelligentTieringConfiguration]
$creadListPrec :: ReadPrec [DeleteBucketIntelligentTieringConfiguration]
readPrec :: ReadPrec DeleteBucketIntelligentTieringConfiguration
$creadPrec :: ReadPrec DeleteBucketIntelligentTieringConfiguration
readList :: ReadS [DeleteBucketIntelligentTieringConfiguration]
$creadList :: ReadS [DeleteBucketIntelligentTieringConfiguration]
readsPrec :: Int -> ReadS DeleteBucketIntelligentTieringConfiguration
$creadsPrec :: Int -> ReadS DeleteBucketIntelligentTieringConfiguration
Prelude.Read, Int -> DeleteBucketIntelligentTieringConfiguration -> ShowS
[DeleteBucketIntelligentTieringConfiguration] -> ShowS
DeleteBucketIntelligentTieringConfiguration -> String
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [DeleteBucketIntelligentTieringConfiguration] -> ShowS
$cshowList :: [DeleteBucketIntelligentTieringConfiguration] -> ShowS
show :: DeleteBucketIntelligentTieringConfiguration -> String
$cshow :: DeleteBucketIntelligentTieringConfiguration -> String
showsPrec :: Int -> DeleteBucketIntelligentTieringConfiguration -> ShowS
$cshowsPrec :: Int -> DeleteBucketIntelligentTieringConfiguration -> ShowS
Prelude.Show, forall x.
Rep DeleteBucketIntelligentTieringConfiguration x
-> DeleteBucketIntelligentTieringConfiguration
forall x.
DeleteBucketIntelligentTieringConfiguration
-> Rep DeleteBucketIntelligentTieringConfiguration x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cto :: forall x.
Rep DeleteBucketIntelligentTieringConfiguration x
-> DeleteBucketIntelligentTieringConfiguration
$cfrom :: forall x.
DeleteBucketIntelligentTieringConfiguration
-> Rep DeleteBucketIntelligentTieringConfiguration x
Prelude.Generic)

-- |
-- Create a value of 'DeleteBucketIntelligentTieringConfiguration' 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:
--
-- 'bucket', 'deleteBucketIntelligentTieringConfiguration_bucket' - The name of the Amazon S3 bucket whose configuration you want to modify
-- or retrieve.
--
-- 'id', 'deleteBucketIntelligentTieringConfiguration_id' - The ID used to identify the S3 Intelligent-Tiering configuration.
newDeleteBucketIntelligentTieringConfiguration ::
  -- | 'bucket'
  BucketName ->
  -- | 'id'
  Prelude.Text ->
  DeleteBucketIntelligentTieringConfiguration
newDeleteBucketIntelligentTieringConfiguration :: BucketName -> Text -> DeleteBucketIntelligentTieringConfiguration
newDeleteBucketIntelligentTieringConfiguration
  BucketName
pBucket_
  Text
pId_ =
    DeleteBucketIntelligentTieringConfiguration'
      { $sel:bucket:DeleteBucketIntelligentTieringConfiguration' :: BucketName
bucket =
          BucketName
pBucket_,
        $sel:id:DeleteBucketIntelligentTieringConfiguration' :: Text
id = Text
pId_
      }

-- | The name of the Amazon S3 bucket whose configuration you want to modify
-- or retrieve.
deleteBucketIntelligentTieringConfiguration_bucket :: Lens.Lens' DeleteBucketIntelligentTieringConfiguration BucketName
deleteBucketIntelligentTieringConfiguration_bucket :: Lens' DeleteBucketIntelligentTieringConfiguration BucketName
deleteBucketIntelligentTieringConfiguration_bucket = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\DeleteBucketIntelligentTieringConfiguration' {BucketName
bucket :: BucketName
$sel:bucket:DeleteBucketIntelligentTieringConfiguration' :: DeleteBucketIntelligentTieringConfiguration -> BucketName
bucket} -> BucketName
bucket) (\s :: DeleteBucketIntelligentTieringConfiguration
s@DeleteBucketIntelligentTieringConfiguration' {} BucketName
a -> DeleteBucketIntelligentTieringConfiguration
s {$sel:bucket:DeleteBucketIntelligentTieringConfiguration' :: BucketName
bucket = BucketName
a} :: DeleteBucketIntelligentTieringConfiguration)

-- | The ID used to identify the S3 Intelligent-Tiering configuration.
deleteBucketIntelligentTieringConfiguration_id :: Lens.Lens' DeleteBucketIntelligentTieringConfiguration Prelude.Text
deleteBucketIntelligentTieringConfiguration_id :: Lens' DeleteBucketIntelligentTieringConfiguration Text
deleteBucketIntelligentTieringConfiguration_id = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\DeleteBucketIntelligentTieringConfiguration' {Text
id :: Text
$sel:id:DeleteBucketIntelligentTieringConfiguration' :: DeleteBucketIntelligentTieringConfiguration -> Text
id} -> Text
id) (\s :: DeleteBucketIntelligentTieringConfiguration
s@DeleteBucketIntelligentTieringConfiguration' {} Text
a -> DeleteBucketIntelligentTieringConfiguration
s {$sel:id:DeleteBucketIntelligentTieringConfiguration' :: Text
id = Text
a} :: DeleteBucketIntelligentTieringConfiguration)

instance
  Core.AWSRequest
    DeleteBucketIntelligentTieringConfiguration
  where
  type
    AWSResponse
      DeleteBucketIntelligentTieringConfiguration =
      DeleteBucketIntelligentTieringConfigurationResponse
  request :: (Service -> Service)
-> DeleteBucketIntelligentTieringConfiguration
-> Request DeleteBucketIntelligentTieringConfiguration
request Service -> Service
overrides =
    forall a. Request a -> Request a
Request.s3vhost
      forall b c a. (b -> c) -> (a -> b) -> a -> c
Prelude.. forall a. ToRequest a => Service -> a -> Request a
Request.delete (Service -> Service
overrides Service
defaultService)
  response :: forall (m :: * -> *).
MonadResource m =>
(ByteStringLazy -> IO ByteStringLazy)
-> Service
-> Proxy DeleteBucketIntelligentTieringConfiguration
-> ClientResponse ClientBody
-> m (Either
        Error
        (ClientResponse
           (AWSResponse DeleteBucketIntelligentTieringConfiguration)))
response =
    forall (m :: * -> *) a.
MonadResource m =>
AWSResponse a
-> (ByteStringLazy -> IO ByteStringLazy)
-> Service
-> Proxy a
-> ClientResponse ClientBody
-> m (Either Error (ClientResponse (AWSResponse a)))
Response.receiveNull
      DeleteBucketIntelligentTieringConfigurationResponse
DeleteBucketIntelligentTieringConfigurationResponse'

instance
  Prelude.Hashable
    DeleteBucketIntelligentTieringConfiguration
  where
  hashWithSalt :: Int -> DeleteBucketIntelligentTieringConfiguration -> Int
hashWithSalt
    Int
_salt
    DeleteBucketIntelligentTieringConfiguration' {Text
BucketName
id :: Text
bucket :: BucketName
$sel:id:DeleteBucketIntelligentTieringConfiguration' :: DeleteBucketIntelligentTieringConfiguration -> Text
$sel:bucket:DeleteBucketIntelligentTieringConfiguration' :: DeleteBucketIntelligentTieringConfiguration -> BucketName
..} =
      Int
_salt
        forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` BucketName
bucket
        forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Text
id

instance
  Prelude.NFData
    DeleteBucketIntelligentTieringConfiguration
  where
  rnf :: DeleteBucketIntelligentTieringConfiguration -> ()
rnf DeleteBucketIntelligentTieringConfiguration' {Text
BucketName
id :: Text
bucket :: BucketName
$sel:id:DeleteBucketIntelligentTieringConfiguration' :: DeleteBucketIntelligentTieringConfiguration -> Text
$sel:bucket:DeleteBucketIntelligentTieringConfiguration' :: DeleteBucketIntelligentTieringConfiguration -> BucketName
..} =
    forall a. NFData a => a -> ()
Prelude.rnf BucketName
bucket seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf Text
id

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

instance
  Data.ToPath
    DeleteBucketIntelligentTieringConfiguration
  where
  toPath :: DeleteBucketIntelligentTieringConfiguration -> ByteString
toPath
    DeleteBucketIntelligentTieringConfiguration' {Text
BucketName
id :: Text
bucket :: BucketName
$sel:id:DeleteBucketIntelligentTieringConfiguration' :: DeleteBucketIntelligentTieringConfiguration -> Text
$sel:bucket:DeleteBucketIntelligentTieringConfiguration' :: DeleteBucketIntelligentTieringConfiguration -> BucketName
..} =
      forall a. Monoid a => [a] -> a
Prelude.mconcat [ByteString
"/", forall a. ToByteString a => a -> ByteString
Data.toBS BucketName
bucket]

instance
  Data.ToQuery
    DeleteBucketIntelligentTieringConfiguration
  where
  toQuery :: DeleteBucketIntelligentTieringConfiguration -> QueryString
toQuery
    DeleteBucketIntelligentTieringConfiguration' {Text
BucketName
id :: Text
bucket :: BucketName
$sel:id:DeleteBucketIntelligentTieringConfiguration' :: DeleteBucketIntelligentTieringConfiguration -> Text
$sel:bucket:DeleteBucketIntelligentTieringConfiguration' :: DeleteBucketIntelligentTieringConfiguration -> BucketName
..} =
      forall a. Monoid a => [a] -> a
Prelude.mconcat
        [ByteString
"id" forall a. ToQuery a => ByteString -> a -> QueryString
Data.=: Text
id, QueryString
"intelligent-tiering"]

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

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

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