{-# 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.GetBucketPolicy
-- 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 policy of a specified bucket. If you are using an identity
-- other than the root user of the Amazon Web Services account that owns
-- the bucket, the calling identity must have the @GetBucketPolicy@
-- permissions on the specified bucket and belong to the bucket owner\'s
-- account in order to use this operation.
--
-- If you don\'t have @GetBucketPolicy@ permissions, Amazon S3 returns a
-- @403 Access Denied@ error. If you have the correct permissions, but
-- you\'re not using an identity that belongs to the bucket owner\'s
-- account, Amazon S3 returns a @405 Method Not Allowed@ error.
--
-- As a security precaution, the root user of the Amazon Web Services
-- account that owns a bucket can always use this operation, even if the
-- policy explicitly denies the root user the ability to perform this
-- action.
--
-- For more information about bucket policies, see
-- <https://docs.aws.amazon.com/AmazonS3/latest/dev/using-iam-policies.html Using Bucket Policies and User Policies>.
--
-- The following action is related to @GetBucketPolicy@:
--
-- -   <https://docs.aws.amazon.com/AmazonS3/latest/API/API_GetObject.html GetObject>
module Amazonka.S3.GetBucketPolicy
  ( -- * Creating a Request
    GetBucketPolicy (..),
    newGetBucketPolicy,

    -- * Request Lenses
    getBucketPolicy_expectedBucketOwner,
    getBucketPolicy_bucket,

    -- * Destructuring the Response
    GetBucketPolicyResponse (..),
    newGetBucketPolicyResponse,

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

-- |
-- Create a value of 'GetBucketPolicy' 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', 'getBucketPolicy_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', 'getBucketPolicy_bucket' - The bucket name for which to get the bucket policy.
newGetBucketPolicy ::
  -- | 'bucket'
  BucketName ->
  GetBucketPolicy
newGetBucketPolicy :: BucketName -> GetBucketPolicy
newGetBucketPolicy BucketName
pBucket_ =
  GetBucketPolicy'
    { $sel:expectedBucketOwner:GetBucketPolicy' :: Maybe Text
expectedBucketOwner =
        forall a. Maybe a
Prelude.Nothing,
      $sel:bucket:GetBucketPolicy' :: 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).
getBucketPolicy_expectedBucketOwner :: Lens.Lens' GetBucketPolicy (Prelude.Maybe Prelude.Text)
getBucketPolicy_expectedBucketOwner :: Lens' GetBucketPolicy (Maybe Text)
getBucketPolicy_expectedBucketOwner = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\GetBucketPolicy' {Maybe Text
expectedBucketOwner :: Maybe Text
$sel:expectedBucketOwner:GetBucketPolicy' :: GetBucketPolicy -> Maybe Text
expectedBucketOwner} -> Maybe Text
expectedBucketOwner) (\s :: GetBucketPolicy
s@GetBucketPolicy' {} Maybe Text
a -> GetBucketPolicy
s {$sel:expectedBucketOwner:GetBucketPolicy' :: Maybe Text
expectedBucketOwner = Maybe Text
a} :: GetBucketPolicy)

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

instance Core.AWSRequest GetBucketPolicy where
  type
    AWSResponse GetBucketPolicy =
      GetBucketPolicyResponse
  request :: (Service -> Service) -> GetBucketPolicy -> Request GetBucketPolicy
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 GetBucketPolicy
-> ClientResponse ClientBody
-> m (Either Error (ClientResponse (AWSResponse GetBucketPolicy)))
response =
    forall (m :: * -> *) a.
MonadResource m =>
(Int
 -> ResponseHeaders -> ByteString -> Either String (AWSResponse a))
-> (ByteStringLazy -> IO ByteStringLazy)
-> Service
-> Proxy a
-> ClientResponse ClientBody
-> m (Either Error (ClientResponse (AWSResponse a)))
Response.receiveBytes
      ( \Int
s ResponseHeaders
h ByteString
x ->
          Int -> ByteString -> GetBucketPolicyResponse
GetBucketPolicyResponse'
            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 (f :: * -> *) a. Applicative f => a -> f a
Prelude.pure ByteString
x)
      )

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

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

-- | /See:/ 'newGetBucketPolicyResponse' smart constructor.
data GetBucketPolicyResponse = GetBucketPolicyResponse'
  { -- | The response's http status code.
    GetBucketPolicyResponse -> Int
httpStatus :: Prelude.Int,
    -- | The bucket policy as a JSON document.
    GetBucketPolicyResponse -> ByteString
policy :: Prelude.ByteString
  }
  deriving (GetBucketPolicyResponse -> GetBucketPolicyResponse -> Bool
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: GetBucketPolicyResponse -> GetBucketPolicyResponse -> Bool
$c/= :: GetBucketPolicyResponse -> GetBucketPolicyResponse -> Bool
== :: GetBucketPolicyResponse -> GetBucketPolicyResponse -> Bool
$c== :: GetBucketPolicyResponse -> GetBucketPolicyResponse -> Bool
Prelude.Eq, Int -> GetBucketPolicyResponse -> ShowS
[GetBucketPolicyResponse] -> ShowS
GetBucketPolicyResponse -> String
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [GetBucketPolicyResponse] -> ShowS
$cshowList :: [GetBucketPolicyResponse] -> ShowS
show :: GetBucketPolicyResponse -> String
$cshow :: GetBucketPolicyResponse -> String
showsPrec :: Int -> GetBucketPolicyResponse -> ShowS
$cshowsPrec :: Int -> GetBucketPolicyResponse -> ShowS
Prelude.Show, forall x. Rep GetBucketPolicyResponse x -> GetBucketPolicyResponse
forall x. GetBucketPolicyResponse -> Rep GetBucketPolicyResponse x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cto :: forall x. Rep GetBucketPolicyResponse x -> GetBucketPolicyResponse
$cfrom :: forall x. GetBucketPolicyResponse -> Rep GetBucketPolicyResponse x
Prelude.Generic)

-- |
-- Create a value of 'GetBucketPolicyResponse' 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', 'getBucketPolicyResponse_httpStatus' - The response's http status code.
--
-- 'policy', 'getBucketPolicyResponse_policy' - The bucket policy as a JSON document.
newGetBucketPolicyResponse ::
  -- | 'httpStatus'
  Prelude.Int ->
  -- | 'policy'
  Prelude.ByteString ->
  GetBucketPolicyResponse
newGetBucketPolicyResponse :: Int -> ByteString -> GetBucketPolicyResponse
newGetBucketPolicyResponse Int
pHttpStatus_ ByteString
pPolicy_ =
  GetBucketPolicyResponse'
    { $sel:httpStatus:GetBucketPolicyResponse' :: Int
httpStatus = Int
pHttpStatus_,
      $sel:policy:GetBucketPolicyResponse' :: ByteString
policy = ByteString
pPolicy_
    }

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

-- | The bucket policy as a JSON document.
getBucketPolicyResponse_policy :: Lens.Lens' GetBucketPolicyResponse Prelude.ByteString
getBucketPolicyResponse_policy :: Lens' GetBucketPolicyResponse ByteString
getBucketPolicyResponse_policy = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\GetBucketPolicyResponse' {ByteString
policy :: ByteString
$sel:policy:GetBucketPolicyResponse' :: GetBucketPolicyResponse -> ByteString
policy} -> ByteString
policy) (\s :: GetBucketPolicyResponse
s@GetBucketPolicyResponse' {} ByteString
a -> GetBucketPolicyResponse
s {$sel:policy:GetBucketPolicyResponse' :: ByteString
policy = ByteString
a} :: GetBucketPolicyResponse)

instance Prelude.NFData GetBucketPolicyResponse where
  rnf :: GetBucketPolicyResponse -> ()
rnf GetBucketPolicyResponse' {Int
ByteString
policy :: ByteString
httpStatus :: Int
$sel:policy:GetBucketPolicyResponse' :: GetBucketPolicyResponse -> ByteString
$sel:httpStatus:GetBucketPolicyResponse' :: GetBucketPolicyResponse -> 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 ByteString
policy