{-# 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.GetObjectRetention
-- Copyright   : (c) 2013-2023 Brendan Hay
-- License     : Mozilla Public License, v. 2.0.
-- Maintainer  : Brendan Hay
-- Stability   : auto-generated
-- Portability : non-portable (GHC extensions)
--
-- Retrieves an object\'s retention settings. For more information, see
-- <https://docs.aws.amazon.com/AmazonS3/latest/dev/object-lock.html Locking Objects>.
--
-- This action is not supported by Amazon S3 on Outposts.
--
-- The following action is related to @GetObjectRetention@:
--
-- -   <https://docs.aws.amazon.com/AmazonS3/latest/API/API_GetObjectAttributes.html GetObjectAttributes>
module Amazonka.S3.GetObjectRetention
  ( -- * Creating a Request
    GetObjectRetention (..),
    newGetObjectRetention,

    -- * Request Lenses
    getObjectRetention_expectedBucketOwner,
    getObjectRetention_requestPayer,
    getObjectRetention_versionId,
    getObjectRetention_bucket,
    getObjectRetention_key,

    -- * Destructuring the Response
    GetObjectRetentionResponse (..),
    newGetObjectRetentionResponse,

    -- * Response Lenses
    getObjectRetentionResponse_retention,
    getObjectRetentionResponse_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:/ 'newGetObjectRetention' smart constructor.
data GetObjectRetention = GetObjectRetention'
  { -- | 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).
    GetObjectRetention -> Maybe Text
expectedBucketOwner :: Prelude.Maybe Prelude.Text,
    GetObjectRetention -> Maybe RequestPayer
requestPayer :: Prelude.Maybe RequestPayer,
    -- | The version ID for the object whose retention settings you want to
    -- retrieve.
    GetObjectRetention -> Maybe ObjectVersionId
versionId :: Prelude.Maybe ObjectVersionId,
    -- | The bucket name containing the object whose retention settings you want
    -- to retrieve.
    --
    -- When using this action with an access point, you must direct requests to
    -- the access point hostname. The access point hostname takes the form
    -- /AccessPointName/-/AccountId/.s3-accesspoint./Region/.amazonaws.com.
    -- When using this action with an access point through the Amazon Web
    -- Services SDKs, you provide the access point ARN in place of the bucket
    -- name. For more information about access point ARNs, see
    -- <https://docs.aws.amazon.com/AmazonS3/latest/userguide/using-access-points.html Using access points>
    -- in the /Amazon S3 User Guide/.
    GetObjectRetention -> BucketName
bucket :: BucketName,
    -- | The key name for the object whose retention settings you want to
    -- retrieve.
    GetObjectRetention -> ObjectKey
key :: ObjectKey
  }
  deriving (GetObjectRetention -> GetObjectRetention -> Bool
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: GetObjectRetention -> GetObjectRetention -> Bool
$c/= :: GetObjectRetention -> GetObjectRetention -> Bool
== :: GetObjectRetention -> GetObjectRetention -> Bool
$c== :: GetObjectRetention -> GetObjectRetention -> Bool
Prelude.Eq, ReadPrec [GetObjectRetention]
ReadPrec GetObjectRetention
Int -> ReadS GetObjectRetention
ReadS [GetObjectRetention]
forall a.
(Int -> ReadS a)
-> ReadS [a] -> ReadPrec a -> ReadPrec [a] -> Read a
readListPrec :: ReadPrec [GetObjectRetention]
$creadListPrec :: ReadPrec [GetObjectRetention]
readPrec :: ReadPrec GetObjectRetention
$creadPrec :: ReadPrec GetObjectRetention
readList :: ReadS [GetObjectRetention]
$creadList :: ReadS [GetObjectRetention]
readsPrec :: Int -> ReadS GetObjectRetention
$creadsPrec :: Int -> ReadS GetObjectRetention
Prelude.Read, Int -> GetObjectRetention -> ShowS
[GetObjectRetention] -> ShowS
GetObjectRetention -> String
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [GetObjectRetention] -> ShowS
$cshowList :: [GetObjectRetention] -> ShowS
show :: GetObjectRetention -> String
$cshow :: GetObjectRetention -> String
showsPrec :: Int -> GetObjectRetention -> ShowS
$cshowsPrec :: Int -> GetObjectRetention -> ShowS
Prelude.Show, forall x. Rep GetObjectRetention x -> GetObjectRetention
forall x. GetObjectRetention -> Rep GetObjectRetention x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cto :: forall x. Rep GetObjectRetention x -> GetObjectRetention
$cfrom :: forall x. GetObjectRetention -> Rep GetObjectRetention x
Prelude.Generic)

-- |
-- Create a value of 'GetObjectRetention' 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', 'getObjectRetention_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).
--
-- 'requestPayer', 'getObjectRetention_requestPayer' - Undocumented member.
--
-- 'versionId', 'getObjectRetention_versionId' - The version ID for the object whose retention settings you want to
-- retrieve.
--
-- 'bucket', 'getObjectRetention_bucket' - The bucket name containing the object whose retention settings you want
-- to retrieve.
--
-- When using this action with an access point, you must direct requests to
-- the access point hostname. The access point hostname takes the form
-- /AccessPointName/-/AccountId/.s3-accesspoint./Region/.amazonaws.com.
-- When using this action with an access point through the Amazon Web
-- Services SDKs, you provide the access point ARN in place of the bucket
-- name. For more information about access point ARNs, see
-- <https://docs.aws.amazon.com/AmazonS3/latest/userguide/using-access-points.html Using access points>
-- in the /Amazon S3 User Guide/.
--
-- 'key', 'getObjectRetention_key' - The key name for the object whose retention settings you want to
-- retrieve.
newGetObjectRetention ::
  -- | 'bucket'
  BucketName ->
  -- | 'key'
  ObjectKey ->
  GetObjectRetention
newGetObjectRetention :: BucketName -> ObjectKey -> GetObjectRetention
newGetObjectRetention BucketName
pBucket_ ObjectKey
pKey_ =
  GetObjectRetention'
    { $sel:expectedBucketOwner:GetObjectRetention' :: Maybe Text
expectedBucketOwner =
        forall a. Maybe a
Prelude.Nothing,
      $sel:requestPayer:GetObjectRetention' :: Maybe RequestPayer
requestPayer = forall a. Maybe a
Prelude.Nothing,
      $sel:versionId:GetObjectRetention' :: Maybe ObjectVersionId
versionId = forall a. Maybe a
Prelude.Nothing,
      $sel:bucket:GetObjectRetention' :: BucketName
bucket = BucketName
pBucket_,
      $sel:key:GetObjectRetention' :: ObjectKey
key = ObjectKey
pKey_
    }

-- | 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).
getObjectRetention_expectedBucketOwner :: Lens.Lens' GetObjectRetention (Prelude.Maybe Prelude.Text)
getObjectRetention_expectedBucketOwner :: Lens' GetObjectRetention (Maybe Text)
getObjectRetention_expectedBucketOwner = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\GetObjectRetention' {Maybe Text
expectedBucketOwner :: Maybe Text
$sel:expectedBucketOwner:GetObjectRetention' :: GetObjectRetention -> Maybe Text
expectedBucketOwner} -> Maybe Text
expectedBucketOwner) (\s :: GetObjectRetention
s@GetObjectRetention' {} Maybe Text
a -> GetObjectRetention
s {$sel:expectedBucketOwner:GetObjectRetention' :: Maybe Text
expectedBucketOwner = Maybe Text
a} :: GetObjectRetention)

-- | Undocumented member.
getObjectRetention_requestPayer :: Lens.Lens' GetObjectRetention (Prelude.Maybe RequestPayer)
getObjectRetention_requestPayer :: Lens' GetObjectRetention (Maybe RequestPayer)
getObjectRetention_requestPayer = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\GetObjectRetention' {Maybe RequestPayer
requestPayer :: Maybe RequestPayer
$sel:requestPayer:GetObjectRetention' :: GetObjectRetention -> Maybe RequestPayer
requestPayer} -> Maybe RequestPayer
requestPayer) (\s :: GetObjectRetention
s@GetObjectRetention' {} Maybe RequestPayer
a -> GetObjectRetention
s {$sel:requestPayer:GetObjectRetention' :: Maybe RequestPayer
requestPayer = Maybe RequestPayer
a} :: GetObjectRetention)

-- | The version ID for the object whose retention settings you want to
-- retrieve.
getObjectRetention_versionId :: Lens.Lens' GetObjectRetention (Prelude.Maybe ObjectVersionId)
getObjectRetention_versionId :: Lens' GetObjectRetention (Maybe ObjectVersionId)
getObjectRetention_versionId = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\GetObjectRetention' {Maybe ObjectVersionId
versionId :: Maybe ObjectVersionId
$sel:versionId:GetObjectRetention' :: GetObjectRetention -> Maybe ObjectVersionId
versionId} -> Maybe ObjectVersionId
versionId) (\s :: GetObjectRetention
s@GetObjectRetention' {} Maybe ObjectVersionId
a -> GetObjectRetention
s {$sel:versionId:GetObjectRetention' :: Maybe ObjectVersionId
versionId = Maybe ObjectVersionId
a} :: GetObjectRetention)

-- | The bucket name containing the object whose retention settings you want
-- to retrieve.
--
-- When using this action with an access point, you must direct requests to
-- the access point hostname. The access point hostname takes the form
-- /AccessPointName/-/AccountId/.s3-accesspoint./Region/.amazonaws.com.
-- When using this action with an access point through the Amazon Web
-- Services SDKs, you provide the access point ARN in place of the bucket
-- name. For more information about access point ARNs, see
-- <https://docs.aws.amazon.com/AmazonS3/latest/userguide/using-access-points.html Using access points>
-- in the /Amazon S3 User Guide/.
getObjectRetention_bucket :: Lens.Lens' GetObjectRetention BucketName
getObjectRetention_bucket :: Lens' GetObjectRetention BucketName
getObjectRetention_bucket = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\GetObjectRetention' {BucketName
bucket :: BucketName
$sel:bucket:GetObjectRetention' :: GetObjectRetention -> BucketName
bucket} -> BucketName
bucket) (\s :: GetObjectRetention
s@GetObjectRetention' {} BucketName
a -> GetObjectRetention
s {$sel:bucket:GetObjectRetention' :: BucketName
bucket = BucketName
a} :: GetObjectRetention)

-- | The key name for the object whose retention settings you want to
-- retrieve.
getObjectRetention_key :: Lens.Lens' GetObjectRetention ObjectKey
getObjectRetention_key :: Lens' GetObjectRetention ObjectKey
getObjectRetention_key = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\GetObjectRetention' {ObjectKey
key :: ObjectKey
$sel:key:GetObjectRetention' :: GetObjectRetention -> ObjectKey
key} -> ObjectKey
key) (\s :: GetObjectRetention
s@GetObjectRetention' {} ObjectKey
a -> GetObjectRetention
s {$sel:key:GetObjectRetention' :: ObjectKey
key = ObjectKey
a} :: GetObjectRetention)

instance Core.AWSRequest GetObjectRetention where
  type
    AWSResponse GetObjectRetention =
      GetObjectRetentionResponse
  request :: (Service -> Service)
-> GetObjectRetention -> Request GetObjectRetention
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 GetObjectRetention
-> ClientResponse ClientBody
-> m (Either
        Error (ClientResponse (AWSResponse GetObjectRetention)))
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 ObjectLockRetention -> Int -> GetObjectRetentionResponse
GetObjectRetentionResponse'
            forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
Prelude.<$> (forall a. FromXML a => [Node] -> Either String a
Data.parseXML [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 GetObjectRetention where
  hashWithSalt :: Int -> GetObjectRetention -> Int
hashWithSalt Int
_salt GetObjectRetention' {Maybe Text
Maybe ObjectVersionId
Maybe RequestPayer
ObjectKey
BucketName
key :: ObjectKey
bucket :: BucketName
versionId :: Maybe ObjectVersionId
requestPayer :: Maybe RequestPayer
expectedBucketOwner :: Maybe Text
$sel:key:GetObjectRetention' :: GetObjectRetention -> ObjectKey
$sel:bucket:GetObjectRetention' :: GetObjectRetention -> BucketName
$sel:versionId:GetObjectRetention' :: GetObjectRetention -> Maybe ObjectVersionId
$sel:requestPayer:GetObjectRetention' :: GetObjectRetention -> Maybe RequestPayer
$sel:expectedBucketOwner:GetObjectRetention' :: GetObjectRetention -> 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` Maybe RequestPayer
requestPayer
      forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Maybe ObjectVersionId
versionId
      forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` BucketName
bucket
      forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` ObjectKey
key

instance Prelude.NFData GetObjectRetention where
  rnf :: GetObjectRetention -> ()
rnf GetObjectRetention' {Maybe Text
Maybe ObjectVersionId
Maybe RequestPayer
ObjectKey
BucketName
key :: ObjectKey
bucket :: BucketName
versionId :: Maybe ObjectVersionId
requestPayer :: Maybe RequestPayer
expectedBucketOwner :: Maybe Text
$sel:key:GetObjectRetention' :: GetObjectRetention -> ObjectKey
$sel:bucket:GetObjectRetention' :: GetObjectRetention -> BucketName
$sel:versionId:GetObjectRetention' :: GetObjectRetention -> Maybe ObjectVersionId
$sel:requestPayer:GetObjectRetention' :: GetObjectRetention -> Maybe RequestPayer
$sel:expectedBucketOwner:GetObjectRetention' :: GetObjectRetention -> 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 Maybe RequestPayer
requestPayer
      seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf Maybe ObjectVersionId
versionId
      seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf BucketName
bucket
      seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf ObjectKey
key

instance Data.ToHeaders GetObjectRetention where
  toHeaders :: GetObjectRetention -> ResponseHeaders
toHeaders GetObjectRetention' {Maybe Text
Maybe ObjectVersionId
Maybe RequestPayer
ObjectKey
BucketName
key :: ObjectKey
bucket :: BucketName
versionId :: Maybe ObjectVersionId
requestPayer :: Maybe RequestPayer
expectedBucketOwner :: Maybe Text
$sel:key:GetObjectRetention' :: GetObjectRetention -> ObjectKey
$sel:bucket:GetObjectRetention' :: GetObjectRetention -> BucketName
$sel:versionId:GetObjectRetention' :: GetObjectRetention -> Maybe ObjectVersionId
$sel:requestPayer:GetObjectRetention' :: GetObjectRetention -> Maybe RequestPayer
$sel:expectedBucketOwner:GetObjectRetention' :: GetObjectRetention -> 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,
        HeaderName
"x-amz-request-payer" forall a. ToHeader a => HeaderName -> a -> ResponseHeaders
Data.=# Maybe RequestPayer
requestPayer
      ]

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

instance Data.ToQuery GetObjectRetention where
  toQuery :: GetObjectRetention -> QueryString
toQuery GetObjectRetention' {Maybe Text
Maybe ObjectVersionId
Maybe RequestPayer
ObjectKey
BucketName
key :: ObjectKey
bucket :: BucketName
versionId :: Maybe ObjectVersionId
requestPayer :: Maybe RequestPayer
expectedBucketOwner :: Maybe Text
$sel:key:GetObjectRetention' :: GetObjectRetention -> ObjectKey
$sel:bucket:GetObjectRetention' :: GetObjectRetention -> BucketName
$sel:versionId:GetObjectRetention' :: GetObjectRetention -> Maybe ObjectVersionId
$sel:requestPayer:GetObjectRetention' :: GetObjectRetention -> Maybe RequestPayer
$sel:expectedBucketOwner:GetObjectRetention' :: GetObjectRetention -> Maybe Text
..} =
    forall a. Monoid a => [a] -> a
Prelude.mconcat
      [ByteString
"versionId" forall a. ToQuery a => ByteString -> a -> QueryString
Data.=: Maybe ObjectVersionId
versionId, QueryString
"retention"]

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

-- |
-- Create a value of 'GetObjectRetentionResponse' 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:
--
-- 'retention', 'getObjectRetentionResponse_retention' - The container element for an object\'s retention settings.
--
-- 'httpStatus', 'getObjectRetentionResponse_httpStatus' - The response's http status code.
newGetObjectRetentionResponse ::
  -- | 'httpStatus'
  Prelude.Int ->
  GetObjectRetentionResponse
newGetObjectRetentionResponse :: Int -> GetObjectRetentionResponse
newGetObjectRetentionResponse Int
pHttpStatus_ =
  GetObjectRetentionResponse'
    { $sel:retention:GetObjectRetentionResponse' :: Maybe ObjectLockRetention
retention =
        forall a. Maybe a
Prelude.Nothing,
      $sel:httpStatus:GetObjectRetentionResponse' :: Int
httpStatus = Int
pHttpStatus_
    }

-- | The container element for an object\'s retention settings.
getObjectRetentionResponse_retention :: Lens.Lens' GetObjectRetentionResponse (Prelude.Maybe ObjectLockRetention)
getObjectRetentionResponse_retention :: Lens' GetObjectRetentionResponse (Maybe ObjectLockRetention)
getObjectRetentionResponse_retention = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\GetObjectRetentionResponse' {Maybe ObjectLockRetention
retention :: Maybe ObjectLockRetention
$sel:retention:GetObjectRetentionResponse' :: GetObjectRetentionResponse -> Maybe ObjectLockRetention
retention} -> Maybe ObjectLockRetention
retention) (\s :: GetObjectRetentionResponse
s@GetObjectRetentionResponse' {} Maybe ObjectLockRetention
a -> GetObjectRetentionResponse
s {$sel:retention:GetObjectRetentionResponse' :: Maybe ObjectLockRetention
retention = Maybe ObjectLockRetention
a} :: GetObjectRetentionResponse)

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

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