{-# 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.GetBucketLifecycleConfiguration
-- Copyright   : (c) 2013-2023 Brendan Hay
-- License     : Mozilla Public License, v. 2.0.
-- Maintainer  : Brendan Hay
-- Stability   : auto-generated
-- Portability : non-portable (GHC extensions)
--
-- Bucket lifecycle configuration now supports specifying a lifecycle rule
-- using an object key name prefix, one or more object tags, or a
-- combination of both. Accordingly, this section describes the latest API.
-- The response describes the new filter element that you can use to
-- specify a filter to select a subset of objects to which the rule
-- applies. If you are using a previous version of the lifecycle
-- configuration, it still works. For the earlier action, see
-- <https://docs.aws.amazon.com/AmazonS3/latest/API/API_GetBucketLifecycle.html GetBucketLifecycle>.
--
-- Returns the lifecycle configuration information set on the bucket. For
-- information about lifecycle configuration, see
-- <https://docs.aws.amazon.com/AmazonS3/latest/dev/object-lifecycle-mgmt.html Object Lifecycle Management>.
--
-- To use this operation, you must have permission to perform the
-- @s3:GetLifecycleConfiguration@ action. The bucket owner has this
-- permission, by default. The bucket owner can grant this permission to
-- others. For more information about permissions, see
-- <https://docs.aws.amazon.com/AmazonS3/latest/userguide/using-with-s3-actions.html#using-with-s3-actions-related-to-bucket-subresources Permissions Related to Bucket Subresource Operations>
-- and
-- <https://docs.aws.amazon.com/AmazonS3/latest/userguide/s3-access-control.html Managing Access Permissions to Your Amazon S3 Resources>.
--
-- @GetBucketLifecycleConfiguration@ has the following special error:
--
-- -   Error code: @NoSuchLifecycleConfiguration@
--
--     -   Description: The lifecycle configuration does not exist.
--
--     -   HTTP Status Code: 404 Not Found
--
--     -   SOAP Fault Code Prefix: Client
--
-- The following operations are related to
-- @GetBucketLifecycleConfiguration@:
--
-- -   <https://docs.aws.amazon.com/AmazonS3/latest/API/API_GetBucketLifecycle.html GetBucketLifecycle>
--
-- -   <https://docs.aws.amazon.com/AmazonS3/latest/API/API_PutBucketLifecycle.html PutBucketLifecycle>
--
-- -   <https://docs.aws.amazon.com/AmazonS3/latest/API/API_DeleteBucketLifecycle.html DeleteBucketLifecycle>
module Amazonka.S3.GetBucketLifecycleConfiguration
  ( -- * Creating a Request
    GetBucketLifecycleConfiguration (..),
    newGetBucketLifecycleConfiguration,

    -- * Request Lenses
    getBucketLifecycleConfiguration_expectedBucketOwner,
    getBucketLifecycleConfiguration_bucket,

    -- * Destructuring the Response
    GetBucketLifecycleConfigurationResponse (..),
    newGetBucketLifecycleConfigurationResponse,

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

-- |
-- Create a value of 'GetBucketLifecycleConfiguration' 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', 'getBucketLifecycleConfiguration_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', 'getBucketLifecycleConfiguration_bucket' - The name of the bucket for which to get the lifecycle information.
newGetBucketLifecycleConfiguration ::
  -- | 'bucket'
  BucketName ->
  GetBucketLifecycleConfiguration
newGetBucketLifecycleConfiguration :: BucketName -> GetBucketLifecycleConfiguration
newGetBucketLifecycleConfiguration BucketName
pBucket_ =
  GetBucketLifecycleConfiguration'
    { $sel:expectedBucketOwner:GetBucketLifecycleConfiguration' :: Maybe Text
expectedBucketOwner =
        forall a. Maybe a
Prelude.Nothing,
      $sel:bucket:GetBucketLifecycleConfiguration' :: 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).
getBucketLifecycleConfiguration_expectedBucketOwner :: Lens.Lens' GetBucketLifecycleConfiguration (Prelude.Maybe Prelude.Text)
getBucketLifecycleConfiguration_expectedBucketOwner :: Lens' GetBucketLifecycleConfiguration (Maybe Text)
getBucketLifecycleConfiguration_expectedBucketOwner = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\GetBucketLifecycleConfiguration' {Maybe Text
expectedBucketOwner :: Maybe Text
$sel:expectedBucketOwner:GetBucketLifecycleConfiguration' :: GetBucketLifecycleConfiguration -> Maybe Text
expectedBucketOwner} -> Maybe Text
expectedBucketOwner) (\s :: GetBucketLifecycleConfiguration
s@GetBucketLifecycleConfiguration' {} Maybe Text
a -> GetBucketLifecycleConfiguration
s {$sel:expectedBucketOwner:GetBucketLifecycleConfiguration' :: Maybe Text
expectedBucketOwner = Maybe Text
a} :: GetBucketLifecycleConfiguration)

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

instance
  Core.AWSRequest
    GetBucketLifecycleConfiguration
  where
  type
    AWSResponse GetBucketLifecycleConfiguration =
      GetBucketLifecycleConfigurationResponse
  request :: (Service -> Service)
-> GetBucketLifecycleConfiguration
-> Request GetBucketLifecycleConfiguration
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 GetBucketLifecycleConfiguration
-> ClientResponse ClientBody
-> m (Either
        Error
        (ClientResponse (AWSResponse GetBucketLifecycleConfiguration)))
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 [LifecycleRule]
-> Int -> GetBucketLifecycleConfigurationResponse
GetBucketLifecycleConfigurationResponse'
            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
"Rule") [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
    GetBucketLifecycleConfiguration
  where
  hashWithSalt :: Int -> GetBucketLifecycleConfiguration -> Int
hashWithSalt
    Int
_salt
    GetBucketLifecycleConfiguration' {Maybe Text
BucketName
bucket :: BucketName
expectedBucketOwner :: Maybe Text
$sel:bucket:GetBucketLifecycleConfiguration' :: GetBucketLifecycleConfiguration -> BucketName
$sel:expectedBucketOwner:GetBucketLifecycleConfiguration' :: GetBucketLifecycleConfiguration -> 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
    GetBucketLifecycleConfiguration
  where
  rnf :: GetBucketLifecycleConfiguration -> ()
rnf GetBucketLifecycleConfiguration' {Maybe Text
BucketName
bucket :: BucketName
expectedBucketOwner :: Maybe Text
$sel:bucket:GetBucketLifecycleConfiguration' :: GetBucketLifecycleConfiguration -> BucketName
$sel:expectedBucketOwner:GetBucketLifecycleConfiguration' :: GetBucketLifecycleConfiguration -> 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
    GetBucketLifecycleConfiguration
  where
  toHeaders :: GetBucketLifecycleConfiguration -> ResponseHeaders
toHeaders GetBucketLifecycleConfiguration' {Maybe Text
BucketName
bucket :: BucketName
expectedBucketOwner :: Maybe Text
$sel:bucket:GetBucketLifecycleConfiguration' :: GetBucketLifecycleConfiguration -> BucketName
$sel:expectedBucketOwner:GetBucketLifecycleConfiguration' :: GetBucketLifecycleConfiguration -> 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 GetBucketLifecycleConfiguration where
  toPath :: GetBucketLifecycleConfiguration -> ByteString
toPath GetBucketLifecycleConfiguration' {Maybe Text
BucketName
bucket :: BucketName
expectedBucketOwner :: Maybe Text
$sel:bucket:GetBucketLifecycleConfiguration' :: GetBucketLifecycleConfiguration -> BucketName
$sel:expectedBucketOwner:GetBucketLifecycleConfiguration' :: GetBucketLifecycleConfiguration -> Maybe Text
..} =
    forall a. Monoid a => [a] -> a
Prelude.mconcat [ByteString
"/", forall a. ToByteString a => a -> ByteString
Data.toBS BucketName
bucket]

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

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

-- |
-- Create a value of 'GetBucketLifecycleConfigurationResponse' 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:
--
-- 'rules', 'getBucketLifecycleConfigurationResponse_rules' - Container for a lifecycle rule.
--
-- 'httpStatus', 'getBucketLifecycleConfigurationResponse_httpStatus' - The response's http status code.
newGetBucketLifecycleConfigurationResponse ::
  -- | 'httpStatus'
  Prelude.Int ->
  GetBucketLifecycleConfigurationResponse
newGetBucketLifecycleConfigurationResponse :: Int -> GetBucketLifecycleConfigurationResponse
newGetBucketLifecycleConfigurationResponse
  Int
pHttpStatus_ =
    GetBucketLifecycleConfigurationResponse'
      { $sel:rules:GetBucketLifecycleConfigurationResponse' :: Maybe [LifecycleRule]
rules =
          forall a. Maybe a
Prelude.Nothing,
        $sel:httpStatus:GetBucketLifecycleConfigurationResponse' :: Int
httpStatus = Int
pHttpStatus_
      }

-- | Container for a lifecycle rule.
getBucketLifecycleConfigurationResponse_rules :: Lens.Lens' GetBucketLifecycleConfigurationResponse (Prelude.Maybe [LifecycleRule])
getBucketLifecycleConfigurationResponse_rules :: Lens'
  GetBucketLifecycleConfigurationResponse (Maybe [LifecycleRule])
getBucketLifecycleConfigurationResponse_rules = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\GetBucketLifecycleConfigurationResponse' {Maybe [LifecycleRule]
rules :: Maybe [LifecycleRule]
$sel:rules:GetBucketLifecycleConfigurationResponse' :: GetBucketLifecycleConfigurationResponse -> Maybe [LifecycleRule]
rules} -> Maybe [LifecycleRule]
rules) (\s :: GetBucketLifecycleConfigurationResponse
s@GetBucketLifecycleConfigurationResponse' {} Maybe [LifecycleRule]
a -> GetBucketLifecycleConfigurationResponse
s {$sel:rules:GetBucketLifecycleConfigurationResponse' :: Maybe [LifecycleRule]
rules = Maybe [LifecycleRule]
a} :: GetBucketLifecycleConfigurationResponse) 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.
getBucketLifecycleConfigurationResponse_httpStatus :: Lens.Lens' GetBucketLifecycleConfigurationResponse Prelude.Int
getBucketLifecycleConfigurationResponse_httpStatus :: Lens' GetBucketLifecycleConfigurationResponse Int
getBucketLifecycleConfigurationResponse_httpStatus = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\GetBucketLifecycleConfigurationResponse' {Int
httpStatus :: Int
$sel:httpStatus:GetBucketLifecycleConfigurationResponse' :: GetBucketLifecycleConfigurationResponse -> Int
httpStatus} -> Int
httpStatus) (\s :: GetBucketLifecycleConfigurationResponse
s@GetBucketLifecycleConfigurationResponse' {} Int
a -> GetBucketLifecycleConfigurationResponse
s {$sel:httpStatus:GetBucketLifecycleConfigurationResponse' :: Int
httpStatus = Int
a} :: GetBucketLifecycleConfigurationResponse)

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