{-# 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.GetBucketCors
-- Copyright   : (c) 2013-2023 Brendan Hay
-- License     : Mozilla Public License, v. 2.0.
-- Maintainer  : Brendan Hay
-- Stability   : auto-generated
-- Portability : non-portable (GHC extensions)
--
-- Returns the Cross-Origin Resource Sharing (CORS) configuration
-- information set for the bucket.
--
-- To use this operation, you must have permission to perform the
-- @s3:GetBucketCORS@ action. By default, the bucket owner has this
-- permission and can grant it to others.
--
-- For more information about CORS, see
-- <https://docs.aws.amazon.com/AmazonS3/latest/dev/cors.html Enabling Cross-Origin Resource Sharing>.
--
-- The following operations are related to @GetBucketCors@:
--
-- -   <https://docs.aws.amazon.com/AmazonS3/latest/API/API_PutBucketCors.html PutBucketCors>
--
-- -   <https://docs.aws.amazon.com/AmazonS3/latest/API/API_DeleteBucketCors.html DeleteBucketCors>
module Amazonka.S3.GetBucketCors
  ( -- * Creating a Request
    GetBucketCors (..),
    newGetBucketCors,

    -- * Request Lenses
    getBucketCors_expectedBucketOwner,
    getBucketCors_bucket,

    -- * Destructuring the Response
    GetBucketCorsResponse (..),
    newGetBucketCorsResponse,

    -- * Response Lenses
    getBucketCorsResponse_cORSRules,
    getBucketCorsResponse_httpStatus,
  )
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:/ 'newGetBucketCors' smart constructor.
data GetBucketCors = GetBucketCors'
  { -- | 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).
    GetBucketCors -> Maybe Text
expectedBucketOwner :: Prelude.Maybe Prelude.Text,
    -- | The bucket name for which to get the cors configuration.
    GetBucketCors -> BucketName
bucket :: BucketName
  }
  deriving (GetBucketCors -> GetBucketCors -> Bool
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: GetBucketCors -> GetBucketCors -> Bool
$c/= :: GetBucketCors -> GetBucketCors -> Bool
== :: GetBucketCors -> GetBucketCors -> Bool
$c== :: GetBucketCors -> GetBucketCors -> Bool
Prelude.Eq, ReadPrec [GetBucketCors]
ReadPrec GetBucketCors
Int -> ReadS GetBucketCors
ReadS [GetBucketCors]
forall a.
(Int -> ReadS a)
-> ReadS [a] -> ReadPrec a -> ReadPrec [a] -> Read a
readListPrec :: ReadPrec [GetBucketCors]
$creadListPrec :: ReadPrec [GetBucketCors]
readPrec :: ReadPrec GetBucketCors
$creadPrec :: ReadPrec GetBucketCors
readList :: ReadS [GetBucketCors]
$creadList :: ReadS [GetBucketCors]
readsPrec :: Int -> ReadS GetBucketCors
$creadsPrec :: Int -> ReadS GetBucketCors
Prelude.Read, Int -> GetBucketCors -> ShowS
[GetBucketCors] -> ShowS
GetBucketCors -> String
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [GetBucketCors] -> ShowS
$cshowList :: [GetBucketCors] -> ShowS
show :: GetBucketCors -> String
$cshow :: GetBucketCors -> String
showsPrec :: Int -> GetBucketCors -> ShowS
$cshowsPrec :: Int -> GetBucketCors -> ShowS
Prelude.Show, forall x. Rep GetBucketCors x -> GetBucketCors
forall x. GetBucketCors -> Rep GetBucketCors x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cto :: forall x. Rep GetBucketCors x -> GetBucketCors
$cfrom :: forall x. GetBucketCors -> Rep GetBucketCors x
Prelude.Generic)

-- |
-- Create a value of 'GetBucketCors' 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', 'getBucketCors_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', 'getBucketCors_bucket' - The bucket name for which to get the cors configuration.
newGetBucketCors ::
  -- | 'bucket'
  BucketName ->
  GetBucketCors
newGetBucketCors :: BucketName -> GetBucketCors
newGetBucketCors BucketName
pBucket_ =
  GetBucketCors'
    { $sel:expectedBucketOwner:GetBucketCors' :: Maybe Text
expectedBucketOwner =
        forall a. Maybe a
Prelude.Nothing,
      $sel:bucket:GetBucketCors' :: 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).
getBucketCors_expectedBucketOwner :: Lens.Lens' GetBucketCors (Prelude.Maybe Prelude.Text)
getBucketCors_expectedBucketOwner :: Lens' GetBucketCors (Maybe Text)
getBucketCors_expectedBucketOwner = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\GetBucketCors' {Maybe Text
expectedBucketOwner :: Maybe Text
$sel:expectedBucketOwner:GetBucketCors' :: GetBucketCors -> Maybe Text
expectedBucketOwner} -> Maybe Text
expectedBucketOwner) (\s :: GetBucketCors
s@GetBucketCors' {} Maybe Text
a -> GetBucketCors
s {$sel:expectedBucketOwner:GetBucketCors' :: Maybe Text
expectedBucketOwner = Maybe Text
a} :: GetBucketCors)

-- | The bucket name for which to get the cors configuration.
getBucketCors_bucket :: Lens.Lens' GetBucketCors BucketName
getBucketCors_bucket :: Lens' GetBucketCors BucketName
getBucketCors_bucket = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\GetBucketCors' {BucketName
bucket :: BucketName
$sel:bucket:GetBucketCors' :: GetBucketCors -> BucketName
bucket} -> BucketName
bucket) (\s :: GetBucketCors
s@GetBucketCors' {} BucketName
a -> GetBucketCors
s {$sel:bucket:GetBucketCors' :: BucketName
bucket = BucketName
a} :: GetBucketCors)

instance Core.AWSRequest GetBucketCors where
  type
    AWSResponse GetBucketCors =
      GetBucketCorsResponse
  request :: (Service -> Service) -> GetBucketCors -> Request GetBucketCors
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.get (Service -> Service
overrides Service
defaultService)
  response :: forall (m :: * -> *).
MonadResource m =>
(ByteStringLazy -> IO ByteStringLazy)
-> Service
-> Proxy GetBucketCors
-> ClientResponse ClientBody
-> m (Either Error (ClientResponse (AWSResponse GetBucketCors)))
response =
    forall (m :: * -> *) a.
MonadResource m =>
(Int -> ResponseHeaders -> [Node] -> Either String (AWSResponse a))
-> (ByteStringLazy -> IO ByteStringLazy)
-> Service
-> Proxy a
-> ClientResponse ClientBody
-> m (Either Error (ClientResponse (AWSResponse a)))
Response.receiveXML
      ( \Int
s ResponseHeaders
h [Node]
x ->
          Maybe [CORSRule] -> Int -> GetBucketCorsResponse
GetBucketCorsResponse'
            forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
Prelude.<$> (forall (f :: * -> *) a b.
Applicative f =>
([a] -> f b) -> [a] -> f (Maybe b)
Core.may (forall a. FromXML a => Text -> [Node] -> Either String [a]
Data.parseXMLList Text
"CORSRule") [Node]
x)
            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 GetBucketCors where
  hashWithSalt :: Int -> GetBucketCors -> Int
hashWithSalt Int
_salt GetBucketCors' {Maybe Text
BucketName
bucket :: BucketName
expectedBucketOwner :: Maybe Text
$sel:bucket:GetBucketCors' :: GetBucketCors -> BucketName
$sel:expectedBucketOwner:GetBucketCors' :: GetBucketCors -> 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 GetBucketCors where
  rnf :: GetBucketCors -> ()
rnf GetBucketCors' {Maybe Text
BucketName
bucket :: BucketName
expectedBucketOwner :: Maybe Text
$sel:bucket:GetBucketCors' :: GetBucketCors -> BucketName
$sel:expectedBucketOwner:GetBucketCors' :: GetBucketCors -> 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 GetBucketCors where
  toHeaders :: GetBucketCors -> ResponseHeaders
toHeaders GetBucketCors' {Maybe Text
BucketName
bucket :: BucketName
expectedBucketOwner :: Maybe Text
$sel:bucket:GetBucketCors' :: GetBucketCors -> BucketName
$sel:expectedBucketOwner:GetBucketCors' :: GetBucketCors -> Maybe Text
..} =
    forall a. Monoid a => [a] -> a
Prelude.mconcat
      [ HeaderName
"x-amz-expected-bucket-owner"
          forall a. ToHeader a => HeaderName -> a -> ResponseHeaders
Data.=# Maybe Text
expectedBucketOwner
      ]

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

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

-- | /See:/ 'newGetBucketCorsResponse' smart constructor.
data GetBucketCorsResponse = GetBucketCorsResponse'
  { -- | A set of origins and methods (cross-origin access that you want to
    -- allow). You can add up to 100 rules to the configuration.
    GetBucketCorsResponse -> Maybe [CORSRule]
cORSRules :: Prelude.Maybe [CORSRule],
    -- | The response's http status code.
    GetBucketCorsResponse -> Int
httpStatus :: Prelude.Int
  }
  deriving (GetBucketCorsResponse -> GetBucketCorsResponse -> Bool
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: GetBucketCorsResponse -> GetBucketCorsResponse -> Bool
$c/= :: GetBucketCorsResponse -> GetBucketCorsResponse -> Bool
== :: GetBucketCorsResponse -> GetBucketCorsResponse -> Bool
$c== :: GetBucketCorsResponse -> GetBucketCorsResponse -> Bool
Prelude.Eq, ReadPrec [GetBucketCorsResponse]
ReadPrec GetBucketCorsResponse
Int -> ReadS GetBucketCorsResponse
ReadS [GetBucketCorsResponse]
forall a.
(Int -> ReadS a)
-> ReadS [a] -> ReadPrec a -> ReadPrec [a] -> Read a
readListPrec :: ReadPrec [GetBucketCorsResponse]
$creadListPrec :: ReadPrec [GetBucketCorsResponse]
readPrec :: ReadPrec GetBucketCorsResponse
$creadPrec :: ReadPrec GetBucketCorsResponse
readList :: ReadS [GetBucketCorsResponse]
$creadList :: ReadS [GetBucketCorsResponse]
readsPrec :: Int -> ReadS GetBucketCorsResponse
$creadsPrec :: Int -> ReadS GetBucketCorsResponse
Prelude.Read, Int -> GetBucketCorsResponse -> ShowS
[GetBucketCorsResponse] -> ShowS
GetBucketCorsResponse -> String
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [GetBucketCorsResponse] -> ShowS
$cshowList :: [GetBucketCorsResponse] -> ShowS
show :: GetBucketCorsResponse -> String
$cshow :: GetBucketCorsResponse -> String
showsPrec :: Int -> GetBucketCorsResponse -> ShowS
$cshowsPrec :: Int -> GetBucketCorsResponse -> ShowS
Prelude.Show, forall x. Rep GetBucketCorsResponse x -> GetBucketCorsResponse
forall x. GetBucketCorsResponse -> Rep GetBucketCorsResponse x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cto :: forall x. Rep GetBucketCorsResponse x -> GetBucketCorsResponse
$cfrom :: forall x. GetBucketCorsResponse -> Rep GetBucketCorsResponse x
Prelude.Generic)

-- |
-- Create a value of 'GetBucketCorsResponse' 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:
--
-- 'cORSRules', 'getBucketCorsResponse_cORSRules' - A set of origins and methods (cross-origin access that you want to
-- allow). You can add up to 100 rules to the configuration.
--
-- 'httpStatus', 'getBucketCorsResponse_httpStatus' - The response's http status code.
newGetBucketCorsResponse ::
  -- | 'httpStatus'
  Prelude.Int ->
  GetBucketCorsResponse
newGetBucketCorsResponse :: Int -> GetBucketCorsResponse
newGetBucketCorsResponse Int
pHttpStatus_ =
  GetBucketCorsResponse'
    { $sel:cORSRules:GetBucketCorsResponse' :: Maybe [CORSRule]
cORSRules = forall a. Maybe a
Prelude.Nothing,
      $sel:httpStatus:GetBucketCorsResponse' :: Int
httpStatus = Int
pHttpStatus_
    }

-- | A set of origins and methods (cross-origin access that you want to
-- allow). You can add up to 100 rules to the configuration.
getBucketCorsResponse_cORSRules :: Lens.Lens' GetBucketCorsResponse (Prelude.Maybe [CORSRule])
getBucketCorsResponse_cORSRules :: Lens' GetBucketCorsResponse (Maybe [CORSRule])
getBucketCorsResponse_cORSRules = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\GetBucketCorsResponse' {Maybe [CORSRule]
cORSRules :: Maybe [CORSRule]
$sel:cORSRules:GetBucketCorsResponse' :: GetBucketCorsResponse -> Maybe [CORSRule]
cORSRules} -> Maybe [CORSRule]
cORSRules) (\s :: GetBucketCorsResponse
s@GetBucketCorsResponse' {} Maybe [CORSRule]
a -> GetBucketCorsResponse
s {$sel:cORSRules:GetBucketCorsResponse' :: Maybe [CORSRule]
cORSRules = Maybe [CORSRule]
a} :: GetBucketCorsResponse) forall b c a. (b -> c) -> (a -> b) -> a -> c
Prelude.. forall (f :: * -> *) (g :: * -> *) s t a b.
(Functor f, Functor g) =>
AnIso s t a b -> Iso (f s) (g t) (f a) (g b)
Lens.mapping forall s t a b. (Coercible s a, Coercible t b) => Iso s t a b
Lens.coerced

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

instance Prelude.NFData GetBucketCorsResponse where
  rnf :: GetBucketCorsResponse -> ()
rnf GetBucketCorsResponse' {Int
Maybe [CORSRule]
httpStatus :: Int
cORSRules :: Maybe [CORSRule]
$sel:httpStatus:GetBucketCorsResponse' :: GetBucketCorsResponse -> Int
$sel:cORSRules:GetBucketCorsResponse' :: GetBucketCorsResponse -> Maybe [CORSRule]
..} =
    forall a. NFData a => a -> ()
Prelude.rnf Maybe [CORSRule]
cORSRules
      seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf Int
httpStatus