{-# 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.GetBucketLogging
-- 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 logging status of a bucket and the permissions users have to
-- view and modify that status. To use GET, you must be the bucket owner.
--
-- The following operations are related to @GetBucketLogging@:
--
-- -   <https://docs.aws.amazon.com/AmazonS3/latest/API/API_CreateBucket.html CreateBucket>
--
-- -   <https://docs.aws.amazon.com/AmazonS3/latest/API/API_PutBucketLogging.html PutBucketLogging>
module Amazonka.S3.GetBucketLogging
  ( -- * Creating a Request
    GetBucketLogging (..),
    newGetBucketLogging,

    -- * Request Lenses
    getBucketLogging_expectedBucketOwner,
    getBucketLogging_bucket,

    -- * Destructuring the Response
    GetBucketLoggingResponse (..),
    newGetBucketLoggingResponse,

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

-- |
-- Create a value of 'GetBucketLogging' 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', 'getBucketLogging_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', 'getBucketLogging_bucket' - The bucket name for which to get the logging information.
newGetBucketLogging ::
  -- | 'bucket'
  BucketName ->
  GetBucketLogging
newGetBucketLogging :: BucketName -> GetBucketLogging
newGetBucketLogging BucketName
pBucket_ =
  GetBucketLogging'
    { $sel:expectedBucketOwner:GetBucketLogging' :: Maybe Text
expectedBucketOwner =
        forall a. Maybe a
Prelude.Nothing,
      $sel:bucket:GetBucketLogging' :: 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).
getBucketLogging_expectedBucketOwner :: Lens.Lens' GetBucketLogging (Prelude.Maybe Prelude.Text)
getBucketLogging_expectedBucketOwner :: Lens' GetBucketLogging (Maybe Text)
getBucketLogging_expectedBucketOwner = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\GetBucketLogging' {Maybe Text
expectedBucketOwner :: Maybe Text
$sel:expectedBucketOwner:GetBucketLogging' :: GetBucketLogging -> Maybe Text
expectedBucketOwner} -> Maybe Text
expectedBucketOwner) (\s :: GetBucketLogging
s@GetBucketLogging' {} Maybe Text
a -> GetBucketLogging
s {$sel:expectedBucketOwner:GetBucketLogging' :: Maybe Text
expectedBucketOwner = Maybe Text
a} :: GetBucketLogging)

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

instance Core.AWSRequest GetBucketLogging where
  type
    AWSResponse GetBucketLogging =
      GetBucketLoggingResponse
  request :: (Service -> Service)
-> GetBucketLogging -> Request GetBucketLogging
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 GetBucketLogging
-> ClientResponse ClientBody
-> m (Either Error (ClientResponse (AWSResponse GetBucketLogging)))
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 LoggingEnabled -> Int -> GetBucketLoggingResponse
GetBucketLoggingResponse'
            forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
Prelude.<$> ([Node]
x forall a. FromXML a => [Node] -> Text -> Either String (Maybe a)
Data..@? Text
"LoggingEnabled")
            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 GetBucketLogging where
  hashWithSalt :: Int -> GetBucketLogging -> Int
hashWithSalt Int
_salt GetBucketLogging' {Maybe Text
BucketName
bucket :: BucketName
expectedBucketOwner :: Maybe Text
$sel:bucket:GetBucketLogging' :: GetBucketLogging -> BucketName
$sel:expectedBucketOwner:GetBucketLogging' :: GetBucketLogging -> 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 GetBucketLogging where
  rnf :: GetBucketLogging -> ()
rnf GetBucketLogging' {Maybe Text
BucketName
bucket :: BucketName
expectedBucketOwner :: Maybe Text
$sel:bucket:GetBucketLogging' :: GetBucketLogging -> BucketName
$sel:expectedBucketOwner:GetBucketLogging' :: GetBucketLogging -> 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 GetBucketLogging where
  toHeaders :: GetBucketLogging -> ResponseHeaders
toHeaders GetBucketLogging' {Maybe Text
BucketName
bucket :: BucketName
expectedBucketOwner :: Maybe Text
$sel:bucket:GetBucketLogging' :: GetBucketLogging -> BucketName
$sel:expectedBucketOwner:GetBucketLogging' :: GetBucketLogging -> 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 GetBucketLogging where
  toPath :: GetBucketLogging -> ByteString
toPath GetBucketLogging' {Maybe Text
BucketName
bucket :: BucketName
expectedBucketOwner :: Maybe Text
$sel:bucket:GetBucketLogging' :: GetBucketLogging -> BucketName
$sel:expectedBucketOwner:GetBucketLogging' :: GetBucketLogging -> Maybe Text
..} =
    forall a. Monoid a => [a] -> a
Prelude.mconcat [ByteString
"/", forall a. ToByteString a => a -> ByteString
Data.toBS BucketName
bucket]

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

-- | /See:/ 'newGetBucketLoggingResponse' smart constructor.
data GetBucketLoggingResponse = GetBucketLoggingResponse'
  { GetBucketLoggingResponse -> Maybe LoggingEnabled
loggingEnabled :: Prelude.Maybe LoggingEnabled,
    -- | The response's http status code.
    GetBucketLoggingResponse -> Int
httpStatus :: Prelude.Int
  }
  deriving (GetBucketLoggingResponse -> GetBucketLoggingResponse -> Bool
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: GetBucketLoggingResponse -> GetBucketLoggingResponse -> Bool
$c/= :: GetBucketLoggingResponse -> GetBucketLoggingResponse -> Bool
== :: GetBucketLoggingResponse -> GetBucketLoggingResponse -> Bool
$c== :: GetBucketLoggingResponse -> GetBucketLoggingResponse -> Bool
Prelude.Eq, ReadPrec [GetBucketLoggingResponse]
ReadPrec GetBucketLoggingResponse
Int -> ReadS GetBucketLoggingResponse
ReadS [GetBucketLoggingResponse]
forall a.
(Int -> ReadS a)
-> ReadS [a] -> ReadPrec a -> ReadPrec [a] -> Read a
readListPrec :: ReadPrec [GetBucketLoggingResponse]
$creadListPrec :: ReadPrec [GetBucketLoggingResponse]
readPrec :: ReadPrec GetBucketLoggingResponse
$creadPrec :: ReadPrec GetBucketLoggingResponse
readList :: ReadS [GetBucketLoggingResponse]
$creadList :: ReadS [GetBucketLoggingResponse]
readsPrec :: Int -> ReadS GetBucketLoggingResponse
$creadsPrec :: Int -> ReadS GetBucketLoggingResponse
Prelude.Read, Int -> GetBucketLoggingResponse -> ShowS
[GetBucketLoggingResponse] -> ShowS
GetBucketLoggingResponse -> String
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [GetBucketLoggingResponse] -> ShowS
$cshowList :: [GetBucketLoggingResponse] -> ShowS
show :: GetBucketLoggingResponse -> String
$cshow :: GetBucketLoggingResponse -> String
showsPrec :: Int -> GetBucketLoggingResponse -> ShowS
$cshowsPrec :: Int -> GetBucketLoggingResponse -> ShowS
Prelude.Show, forall x.
Rep GetBucketLoggingResponse x -> GetBucketLoggingResponse
forall x.
GetBucketLoggingResponse -> Rep GetBucketLoggingResponse x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cto :: forall x.
Rep GetBucketLoggingResponse x -> GetBucketLoggingResponse
$cfrom :: forall x.
GetBucketLoggingResponse -> Rep GetBucketLoggingResponse x
Prelude.Generic)

-- |
-- Create a value of 'GetBucketLoggingResponse' 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:
--
-- 'loggingEnabled', 'getBucketLoggingResponse_loggingEnabled' - Undocumented member.
--
-- 'httpStatus', 'getBucketLoggingResponse_httpStatus' - The response's http status code.
newGetBucketLoggingResponse ::
  -- | 'httpStatus'
  Prelude.Int ->
  GetBucketLoggingResponse
newGetBucketLoggingResponse :: Int -> GetBucketLoggingResponse
newGetBucketLoggingResponse Int
pHttpStatus_ =
  GetBucketLoggingResponse'
    { $sel:loggingEnabled:GetBucketLoggingResponse' :: Maybe LoggingEnabled
loggingEnabled =
        forall a. Maybe a
Prelude.Nothing,
      $sel:httpStatus:GetBucketLoggingResponse' :: Int
httpStatus = Int
pHttpStatus_
    }

-- | Undocumented member.
getBucketLoggingResponse_loggingEnabled :: Lens.Lens' GetBucketLoggingResponse (Prelude.Maybe LoggingEnabled)
getBucketLoggingResponse_loggingEnabled :: Lens' GetBucketLoggingResponse (Maybe LoggingEnabled)
getBucketLoggingResponse_loggingEnabled = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\GetBucketLoggingResponse' {Maybe LoggingEnabled
loggingEnabled :: Maybe LoggingEnabled
$sel:loggingEnabled:GetBucketLoggingResponse' :: GetBucketLoggingResponse -> Maybe LoggingEnabled
loggingEnabled} -> Maybe LoggingEnabled
loggingEnabled) (\s :: GetBucketLoggingResponse
s@GetBucketLoggingResponse' {} Maybe LoggingEnabled
a -> GetBucketLoggingResponse
s {$sel:loggingEnabled:GetBucketLoggingResponse' :: Maybe LoggingEnabled
loggingEnabled = Maybe LoggingEnabled
a} :: GetBucketLoggingResponse)

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

instance Prelude.NFData GetBucketLoggingResponse where
  rnf :: GetBucketLoggingResponse -> ()
rnf GetBucketLoggingResponse' {Int
Maybe LoggingEnabled
httpStatus :: Int
loggingEnabled :: Maybe LoggingEnabled
$sel:httpStatus:GetBucketLoggingResponse' :: GetBucketLoggingResponse -> Int
$sel:loggingEnabled:GetBucketLoggingResponse' :: GetBucketLoggingResponse -> Maybe LoggingEnabled
..} =
    forall a. NFData a => a -> ()
Prelude.rnf Maybe LoggingEnabled
loggingEnabled
      seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf Int
httpStatus