{-# 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.DeleteBucketCors
-- 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 @cors@ configuration information set for the bucket.
--
-- To use this operation, you must have permission to perform the
-- @s3:PutBucketCORS@ action. The bucket owner has this permission by
-- default and can grant this permission to others.
--
-- For information about @cors@, see
-- <https://docs.aws.amazon.com/AmazonS3/latest/dev/cors.html Enabling Cross-Origin Resource Sharing>
-- in the /Amazon S3 User Guide/.
--
-- __Related Resources:__
--
-- -   <https://docs.aws.amazon.com/AmazonS3/latest/API/API_PutBucketCors.html PutBucketCors>
--
-- -   <https://docs.aws.amazon.com/AmazonS3/latest/API/RESTOPTIONSobject.html RESTOPTIONSobject>
module Amazonka.S3.DeleteBucketCors
  ( -- * Creating a Request
    DeleteBucketCors (..),
    newDeleteBucketCors,

    -- * Request Lenses
    deleteBucketCors_expectedBucketOwner,
    deleteBucketCors_bucket,

    -- * Destructuring the Response
    DeleteBucketCorsResponse (..),
    newDeleteBucketCorsResponse,
  )
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:/ 'newDeleteBucketCors' smart constructor.
data DeleteBucketCors = DeleteBucketCors'
  { -- | The account ID of the expected bucket owner. If the bucket is owned by a
    -- different account, the request fails with the HTTP status code
    -- @403 Forbidden@ (access denied).
    DeleteBucketCors -> Maybe Text
expectedBucketOwner :: Prelude.Maybe Prelude.Text,
    -- | Specifies the bucket whose @cors@ configuration is being deleted.
    DeleteBucketCors -> BucketName
bucket :: BucketName
  }
  deriving (DeleteBucketCors -> DeleteBucketCors -> Bool
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: DeleteBucketCors -> DeleteBucketCors -> Bool
$c/= :: DeleteBucketCors -> DeleteBucketCors -> Bool
== :: DeleteBucketCors -> DeleteBucketCors -> Bool
$c== :: DeleteBucketCors -> DeleteBucketCors -> Bool
Prelude.Eq, ReadPrec [DeleteBucketCors]
ReadPrec DeleteBucketCors
Int -> ReadS DeleteBucketCors
ReadS [DeleteBucketCors]
forall a.
(Int -> ReadS a)
-> ReadS [a] -> ReadPrec a -> ReadPrec [a] -> Read a
readListPrec :: ReadPrec [DeleteBucketCors]
$creadListPrec :: ReadPrec [DeleteBucketCors]
readPrec :: ReadPrec DeleteBucketCors
$creadPrec :: ReadPrec DeleteBucketCors
readList :: ReadS [DeleteBucketCors]
$creadList :: ReadS [DeleteBucketCors]
readsPrec :: Int -> ReadS DeleteBucketCors
$creadsPrec :: Int -> ReadS DeleteBucketCors
Prelude.Read, Int -> DeleteBucketCors -> ShowS
[DeleteBucketCors] -> ShowS
DeleteBucketCors -> String
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [DeleteBucketCors] -> ShowS
$cshowList :: [DeleteBucketCors] -> ShowS
show :: DeleteBucketCors -> String
$cshow :: DeleteBucketCors -> String
showsPrec :: Int -> DeleteBucketCors -> ShowS
$cshowsPrec :: Int -> DeleteBucketCors -> ShowS
Prelude.Show, forall x. Rep DeleteBucketCors x -> DeleteBucketCors
forall x. DeleteBucketCors -> Rep DeleteBucketCors x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cto :: forall x. Rep DeleteBucketCors x -> DeleteBucketCors
$cfrom :: forall x. DeleteBucketCors -> Rep DeleteBucketCors x
Prelude.Generic)

-- |
-- Create a value of 'DeleteBucketCors' 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:
--
-- 'expectedBucketOwner', 'deleteBucketCors_expectedBucketOwner' - The account ID of the expected bucket owner. If the bucket is owned by a
-- different account, the request fails with the HTTP status code
-- @403 Forbidden@ (access denied).
--
-- 'bucket', 'deleteBucketCors_bucket' - Specifies the bucket whose @cors@ configuration is being deleted.
newDeleteBucketCors ::
  -- | 'bucket'
  BucketName ->
  DeleteBucketCors
newDeleteBucketCors :: BucketName -> DeleteBucketCors
newDeleteBucketCors BucketName
pBucket_ =
  DeleteBucketCors'
    { $sel:expectedBucketOwner:DeleteBucketCors' :: Maybe Text
expectedBucketOwner =
        forall a. Maybe a
Prelude.Nothing,
      $sel:bucket:DeleteBucketCors' :: BucketName
bucket = BucketName
pBucket_
    }

-- | The account ID of the expected bucket owner. If the bucket is owned by a
-- different account, the request fails with the HTTP status code
-- @403 Forbidden@ (access denied).
deleteBucketCors_expectedBucketOwner :: Lens.Lens' DeleteBucketCors (Prelude.Maybe Prelude.Text)
deleteBucketCors_expectedBucketOwner :: Lens' DeleteBucketCors (Maybe Text)
deleteBucketCors_expectedBucketOwner = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\DeleteBucketCors' {Maybe Text
expectedBucketOwner :: Maybe Text
$sel:expectedBucketOwner:DeleteBucketCors' :: DeleteBucketCors -> Maybe Text
expectedBucketOwner} -> Maybe Text
expectedBucketOwner) (\s :: DeleteBucketCors
s@DeleteBucketCors' {} Maybe Text
a -> DeleteBucketCors
s {$sel:expectedBucketOwner:DeleteBucketCors' :: Maybe Text
expectedBucketOwner = Maybe Text
a} :: DeleteBucketCors)

-- | Specifies the bucket whose @cors@ configuration is being deleted.
deleteBucketCors_bucket :: Lens.Lens' DeleteBucketCors BucketName
deleteBucketCors_bucket :: Lens' DeleteBucketCors BucketName
deleteBucketCors_bucket = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\DeleteBucketCors' {BucketName
bucket :: BucketName
$sel:bucket:DeleteBucketCors' :: DeleteBucketCors -> BucketName
bucket} -> BucketName
bucket) (\s :: DeleteBucketCors
s@DeleteBucketCors' {} BucketName
a -> DeleteBucketCors
s {$sel:bucket:DeleteBucketCors' :: BucketName
bucket = BucketName
a} :: DeleteBucketCors)

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

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

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

instance Data.ToHeaders DeleteBucketCors where
  toHeaders :: DeleteBucketCors -> [Header]
toHeaders DeleteBucketCors' {Maybe Text
BucketName
bucket :: BucketName
expectedBucketOwner :: Maybe Text
$sel:bucket:DeleteBucketCors' :: DeleteBucketCors -> BucketName
$sel:expectedBucketOwner:DeleteBucketCors' :: DeleteBucketCors -> Maybe Text
..} =
    forall a. Monoid a => [a] -> a
Prelude.mconcat
      [ HeaderName
"x-amz-expected-bucket-owner"
          forall a. ToHeader a => HeaderName -> a -> [Header]
Data.=# Maybe Text
expectedBucketOwner
      ]

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

instance Data.ToQuery DeleteBucketCors where
  toQuery :: DeleteBucketCors -> QueryString
toQuery = forall a b. a -> b -> a
Prelude.const (forall a. Monoid a => [a] -> a
Prelude.mconcat [QueryString
"cors"])

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

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

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