{-# 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.GetBucketLocation
-- 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 Region the bucket resides in. You set the bucket\'s Region
-- using the @LocationConstraint@ request parameter in a @CreateBucket@
-- request. For more information, see
-- <https://docs.aws.amazon.com/AmazonS3/latest/API/API_CreateBucket.html CreateBucket>.
--
-- To use this implementation of the operation, you must be the bucket
-- owner.
--
-- To use this API against an access point, provide the alias of the access
-- point in place of the bucket name.
--
-- The following operations are related to @GetBucketLocation@:
--
-- -   <https://docs.aws.amazon.com/AmazonS3/latest/API/API_GetObject.html GetObject>
--
-- -   <https://docs.aws.amazon.com/AmazonS3/latest/API/API_CreateBucket.html CreateBucket>
module Amazonka.S3.GetBucketLocation
  ( -- * Creating a Request
    GetBucketLocation (..),
    newGetBucketLocation,

    -- * Request Lenses
    getBucketLocation_expectedBucketOwner,
    getBucketLocation_bucket,

    -- * Destructuring the Response
    GetBucketLocationResponse (..),
    newGetBucketLocationResponse,

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

-- |
-- Create a value of 'GetBucketLocation' 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', 'getBucketLocation_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', 'getBucketLocation_bucket' - The name of the bucket for which to get the location.
newGetBucketLocation ::
  -- | 'bucket'
  BucketName ->
  GetBucketLocation
newGetBucketLocation :: BucketName -> GetBucketLocation
newGetBucketLocation BucketName
pBucket_ =
  GetBucketLocation'
    { $sel:expectedBucketOwner:GetBucketLocation' :: Maybe Text
expectedBucketOwner =
        forall a. Maybe a
Prelude.Nothing,
      $sel:bucket:GetBucketLocation' :: 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).
getBucketLocation_expectedBucketOwner :: Lens.Lens' GetBucketLocation (Prelude.Maybe Prelude.Text)
getBucketLocation_expectedBucketOwner :: Lens' GetBucketLocation (Maybe Text)
getBucketLocation_expectedBucketOwner = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\GetBucketLocation' {Maybe Text
expectedBucketOwner :: Maybe Text
$sel:expectedBucketOwner:GetBucketLocation' :: GetBucketLocation -> Maybe Text
expectedBucketOwner} -> Maybe Text
expectedBucketOwner) (\s :: GetBucketLocation
s@GetBucketLocation' {} Maybe Text
a -> GetBucketLocation
s {$sel:expectedBucketOwner:GetBucketLocation' :: Maybe Text
expectedBucketOwner = Maybe Text
a} :: GetBucketLocation)

-- | The name of the bucket for which to get the location.
getBucketLocation_bucket :: Lens.Lens' GetBucketLocation BucketName
getBucketLocation_bucket :: Lens' GetBucketLocation BucketName
getBucketLocation_bucket = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\GetBucketLocation' {BucketName
bucket :: BucketName
$sel:bucket:GetBucketLocation' :: GetBucketLocation -> BucketName
bucket} -> BucketName
bucket) (\s :: GetBucketLocation
s@GetBucketLocation' {} BucketName
a -> GetBucketLocation
s {$sel:bucket:GetBucketLocation' :: BucketName
bucket = BucketName
a} :: GetBucketLocation)

instance Core.AWSRequest GetBucketLocation where
  type
    AWSResponse GetBucketLocation =
      GetBucketLocationResponse
  request :: (Service -> Service)
-> GetBucketLocation -> Request GetBucketLocation
request Service -> Service
overrides =
    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 GetBucketLocation
-> ClientResponse ClientBody
-> m (Either
        Error (ClientResponse (AWSResponse GetBucketLocation)))
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 ->
          Int -> LocationConstraint -> GetBucketLocationResponse
GetBucketLocationResponse'
            forall (f :: * -> *) a b. Functor 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))
            forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
Prelude.<*> (forall a. FromXML a => [Node] -> Either String a
Data.parseXML [Node]
x)
      )

instance Prelude.Hashable GetBucketLocation where
  hashWithSalt :: Int -> GetBucketLocation -> Int
hashWithSalt Int
_salt GetBucketLocation' {Maybe Text
BucketName
bucket :: BucketName
expectedBucketOwner :: Maybe Text
$sel:bucket:GetBucketLocation' :: GetBucketLocation -> BucketName
$sel:expectedBucketOwner:GetBucketLocation' :: GetBucketLocation -> 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 GetBucketLocation where
  rnf :: GetBucketLocation -> ()
rnf GetBucketLocation' {Maybe Text
BucketName
bucket :: BucketName
expectedBucketOwner :: Maybe Text
$sel:bucket:GetBucketLocation' :: GetBucketLocation -> BucketName
$sel:expectedBucketOwner:GetBucketLocation' :: GetBucketLocation -> 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 GetBucketLocation where
  toHeaders :: GetBucketLocation -> ResponseHeaders
toHeaders GetBucketLocation' {Maybe Text
BucketName
bucket :: BucketName
expectedBucketOwner :: Maybe Text
$sel:bucket:GetBucketLocation' :: GetBucketLocation -> BucketName
$sel:expectedBucketOwner:GetBucketLocation' :: GetBucketLocation -> 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 GetBucketLocation where
  toPath :: GetBucketLocation -> ByteString
toPath GetBucketLocation' {Maybe Text
BucketName
bucket :: BucketName
expectedBucketOwner :: Maybe Text
$sel:bucket:GetBucketLocation' :: GetBucketLocation -> BucketName
$sel:expectedBucketOwner:GetBucketLocation' :: GetBucketLocation -> Maybe Text
..} =
    forall a. Monoid a => [a] -> a
Prelude.mconcat [ByteString
"/", forall a. ToByteString a => a -> ByteString
Data.toBS BucketName
bucket]

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

-- | /See:/ 'newGetBucketLocationResponse' smart constructor.
data GetBucketLocationResponse = GetBucketLocationResponse'
  { -- | The response's http status code.
    GetBucketLocationResponse -> Int
httpStatus :: Prelude.Int,
    -- | Specifies the Region where the bucket resides. For a list of all the
    -- Amazon S3 supported location constraints by Region, see
    -- <https://docs.aws.amazon.com/general/latest/gr/rande.html#s3_region Regions and Endpoints>.
    -- Buckets in Region @us-east-1@ have a LocationConstraint of @null@.
    GetBucketLocationResponse -> LocationConstraint
locationConstraint :: LocationConstraint
  }
  deriving (GetBucketLocationResponse -> GetBucketLocationResponse -> Bool
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: GetBucketLocationResponse -> GetBucketLocationResponse -> Bool
$c/= :: GetBucketLocationResponse -> GetBucketLocationResponse -> Bool
== :: GetBucketLocationResponse -> GetBucketLocationResponse -> Bool
$c== :: GetBucketLocationResponse -> GetBucketLocationResponse -> Bool
Prelude.Eq, ReadPrec [GetBucketLocationResponse]
ReadPrec GetBucketLocationResponse
Int -> ReadS GetBucketLocationResponse
ReadS [GetBucketLocationResponse]
forall a.
(Int -> ReadS a)
-> ReadS [a] -> ReadPrec a -> ReadPrec [a] -> Read a
readListPrec :: ReadPrec [GetBucketLocationResponse]
$creadListPrec :: ReadPrec [GetBucketLocationResponse]
readPrec :: ReadPrec GetBucketLocationResponse
$creadPrec :: ReadPrec GetBucketLocationResponse
readList :: ReadS [GetBucketLocationResponse]
$creadList :: ReadS [GetBucketLocationResponse]
readsPrec :: Int -> ReadS GetBucketLocationResponse
$creadsPrec :: Int -> ReadS GetBucketLocationResponse
Prelude.Read, Int -> GetBucketLocationResponse -> ShowS
[GetBucketLocationResponse] -> ShowS
GetBucketLocationResponse -> String
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [GetBucketLocationResponse] -> ShowS
$cshowList :: [GetBucketLocationResponse] -> ShowS
show :: GetBucketLocationResponse -> String
$cshow :: GetBucketLocationResponse -> String
showsPrec :: Int -> GetBucketLocationResponse -> ShowS
$cshowsPrec :: Int -> GetBucketLocationResponse -> ShowS
Prelude.Show, forall x.
Rep GetBucketLocationResponse x -> GetBucketLocationResponse
forall x.
GetBucketLocationResponse -> Rep GetBucketLocationResponse x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cto :: forall x.
Rep GetBucketLocationResponse x -> GetBucketLocationResponse
$cfrom :: forall x.
GetBucketLocationResponse -> Rep GetBucketLocationResponse x
Prelude.Generic)

-- |
-- Create a value of 'GetBucketLocationResponse' 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:
--
-- 'httpStatus', 'getBucketLocationResponse_httpStatus' - The response's http status code.
--
-- 'locationConstraint', 'getBucketLocationResponse_locationConstraint' - Specifies the Region where the bucket resides. For a list of all the
-- Amazon S3 supported location constraints by Region, see
-- <https://docs.aws.amazon.com/general/latest/gr/rande.html#s3_region Regions and Endpoints>.
-- Buckets in Region @us-east-1@ have a LocationConstraint of @null@.
newGetBucketLocationResponse ::
  -- | 'httpStatus'
  Prelude.Int ->
  -- | 'locationConstraint'
  LocationConstraint ->
  GetBucketLocationResponse
newGetBucketLocationResponse :: Int -> LocationConstraint -> GetBucketLocationResponse
newGetBucketLocationResponse
  Int
pHttpStatus_
  LocationConstraint
pLocationConstraint_ =
    GetBucketLocationResponse'
      { $sel:httpStatus:GetBucketLocationResponse' :: Int
httpStatus =
          Int
pHttpStatus_,
        $sel:locationConstraint:GetBucketLocationResponse' :: LocationConstraint
locationConstraint = LocationConstraint
pLocationConstraint_
      }

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

-- | Specifies the Region where the bucket resides. For a list of all the
-- Amazon S3 supported location constraints by Region, see
-- <https://docs.aws.amazon.com/general/latest/gr/rande.html#s3_region Regions and Endpoints>.
-- Buckets in Region @us-east-1@ have a LocationConstraint of @null@.
getBucketLocationResponse_locationConstraint :: Lens.Lens' GetBucketLocationResponse LocationConstraint
getBucketLocationResponse_locationConstraint :: Lens' GetBucketLocationResponse LocationConstraint
getBucketLocationResponse_locationConstraint = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\GetBucketLocationResponse' {LocationConstraint
locationConstraint :: LocationConstraint
$sel:locationConstraint:GetBucketLocationResponse' :: GetBucketLocationResponse -> LocationConstraint
locationConstraint} -> LocationConstraint
locationConstraint) (\s :: GetBucketLocationResponse
s@GetBucketLocationResponse' {} LocationConstraint
a -> GetBucketLocationResponse
s {$sel:locationConstraint:GetBucketLocationResponse' :: LocationConstraint
locationConstraint = LocationConstraint
a} :: GetBucketLocationResponse)

instance Prelude.NFData GetBucketLocationResponse where
  rnf :: GetBucketLocationResponse -> ()
rnf GetBucketLocationResponse' {Int
LocationConstraint
locationConstraint :: LocationConstraint
httpStatus :: Int
$sel:locationConstraint:GetBucketLocationResponse' :: GetBucketLocationResponse -> LocationConstraint
$sel:httpStatus:GetBucketLocationResponse' :: GetBucketLocationResponse -> Int
..} =
    forall a. NFData a => a -> ()
Prelude.rnf Int
httpStatus
      seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf LocationConstraint
locationConstraint