{-# 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.GetObjectLegalHold
-- Copyright   : (c) 2013-2023 Brendan Hay
-- License     : Mozilla Public License, v. 2.0.
-- Maintainer  : Brendan Hay
-- Stability   : auto-generated
-- Portability : non-portable (GHC extensions)
--
-- Gets an object\'s current legal hold status. 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 @GetObjectLegalHold@:
--
-- -   <https://docs.aws.amazon.com/AmazonS3/latest/API/API_GetObjectAttributes.html GetObjectAttributes>
module Amazonka.S3.GetObjectLegalHold
  ( -- * Creating a Request
    GetObjectLegalHold (..),
    newGetObjectLegalHold,

    -- * Request Lenses
    getObjectLegalHold_expectedBucketOwner,
    getObjectLegalHold_requestPayer,
    getObjectLegalHold_versionId,
    getObjectLegalHold_bucket,
    getObjectLegalHold_key,

    -- * Destructuring the Response
    GetObjectLegalHoldResponse (..),
    newGetObjectLegalHoldResponse,

    -- * Response Lenses
    getObjectLegalHoldResponse_legalHold,
    getObjectLegalHoldResponse_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:/ 'newGetObjectLegalHold' smart constructor.
data GetObjectLegalHold = GetObjectLegalHold'
  { -- | 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).
    GetObjectLegalHold -> Maybe Text
expectedBucketOwner :: Prelude.Maybe Prelude.Text,
    GetObjectLegalHold -> Maybe RequestPayer
requestPayer :: Prelude.Maybe RequestPayer,
    -- | The version ID of the object whose legal hold status you want to
    -- retrieve.
    GetObjectLegalHold -> Maybe ObjectVersionId
versionId :: Prelude.Maybe ObjectVersionId,
    -- | The bucket name containing the object whose legal hold status 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/.
    GetObjectLegalHold -> BucketName
bucket :: BucketName,
    -- | The key name for the object whose legal hold status you want to
    -- retrieve.
    GetObjectLegalHold -> ObjectKey
key :: ObjectKey
  }
  deriving (GetObjectLegalHold -> GetObjectLegalHold -> Bool
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: GetObjectLegalHold -> GetObjectLegalHold -> Bool
$c/= :: GetObjectLegalHold -> GetObjectLegalHold -> Bool
== :: GetObjectLegalHold -> GetObjectLegalHold -> Bool
$c== :: GetObjectLegalHold -> GetObjectLegalHold -> Bool
Prelude.Eq, ReadPrec [GetObjectLegalHold]
ReadPrec GetObjectLegalHold
Int -> ReadS GetObjectLegalHold
ReadS [GetObjectLegalHold]
forall a.
(Int -> ReadS a)
-> ReadS [a] -> ReadPrec a -> ReadPrec [a] -> Read a
readListPrec :: ReadPrec [GetObjectLegalHold]
$creadListPrec :: ReadPrec [GetObjectLegalHold]
readPrec :: ReadPrec GetObjectLegalHold
$creadPrec :: ReadPrec GetObjectLegalHold
readList :: ReadS [GetObjectLegalHold]
$creadList :: ReadS [GetObjectLegalHold]
readsPrec :: Int -> ReadS GetObjectLegalHold
$creadsPrec :: Int -> ReadS GetObjectLegalHold
Prelude.Read, Int -> GetObjectLegalHold -> ShowS
[GetObjectLegalHold] -> ShowS
GetObjectLegalHold -> String
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [GetObjectLegalHold] -> ShowS
$cshowList :: [GetObjectLegalHold] -> ShowS
show :: GetObjectLegalHold -> String
$cshow :: GetObjectLegalHold -> String
showsPrec :: Int -> GetObjectLegalHold -> ShowS
$cshowsPrec :: Int -> GetObjectLegalHold -> ShowS
Prelude.Show, forall x. Rep GetObjectLegalHold x -> GetObjectLegalHold
forall x. GetObjectLegalHold -> Rep GetObjectLegalHold x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cto :: forall x. Rep GetObjectLegalHold x -> GetObjectLegalHold
$cfrom :: forall x. GetObjectLegalHold -> Rep GetObjectLegalHold x
Prelude.Generic)

-- |
-- Create a value of 'GetObjectLegalHold' 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', 'getObjectLegalHold_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', 'getObjectLegalHold_requestPayer' - Undocumented member.
--
-- 'versionId', 'getObjectLegalHold_versionId' - The version ID of the object whose legal hold status you want to
-- retrieve.
--
-- 'bucket', 'getObjectLegalHold_bucket' - The bucket name containing the object whose legal hold status 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', 'getObjectLegalHold_key' - The key name for the object whose legal hold status you want to
-- retrieve.
newGetObjectLegalHold ::
  -- | 'bucket'
  BucketName ->
  -- | 'key'
  ObjectKey ->
  GetObjectLegalHold
newGetObjectLegalHold :: BucketName -> ObjectKey -> GetObjectLegalHold
newGetObjectLegalHold BucketName
pBucket_ ObjectKey
pKey_ =
  GetObjectLegalHold'
    { $sel:expectedBucketOwner:GetObjectLegalHold' :: Maybe Text
expectedBucketOwner =
        forall a. Maybe a
Prelude.Nothing,
      $sel:requestPayer:GetObjectLegalHold' :: Maybe RequestPayer
requestPayer = forall a. Maybe a
Prelude.Nothing,
      $sel:versionId:GetObjectLegalHold' :: Maybe ObjectVersionId
versionId = forall a. Maybe a
Prelude.Nothing,
      $sel:bucket:GetObjectLegalHold' :: BucketName
bucket = BucketName
pBucket_,
      $sel:key:GetObjectLegalHold' :: 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).
getObjectLegalHold_expectedBucketOwner :: Lens.Lens' GetObjectLegalHold (Prelude.Maybe Prelude.Text)
getObjectLegalHold_expectedBucketOwner :: Lens' GetObjectLegalHold (Maybe Text)
getObjectLegalHold_expectedBucketOwner = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\GetObjectLegalHold' {Maybe Text
expectedBucketOwner :: Maybe Text
$sel:expectedBucketOwner:GetObjectLegalHold' :: GetObjectLegalHold -> Maybe Text
expectedBucketOwner} -> Maybe Text
expectedBucketOwner) (\s :: GetObjectLegalHold
s@GetObjectLegalHold' {} Maybe Text
a -> GetObjectLegalHold
s {$sel:expectedBucketOwner:GetObjectLegalHold' :: Maybe Text
expectedBucketOwner = Maybe Text
a} :: GetObjectLegalHold)

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

-- | The version ID of the object whose legal hold status you want to
-- retrieve.
getObjectLegalHold_versionId :: Lens.Lens' GetObjectLegalHold (Prelude.Maybe ObjectVersionId)
getObjectLegalHold_versionId :: Lens' GetObjectLegalHold (Maybe ObjectVersionId)
getObjectLegalHold_versionId = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\GetObjectLegalHold' {Maybe ObjectVersionId
versionId :: Maybe ObjectVersionId
$sel:versionId:GetObjectLegalHold' :: GetObjectLegalHold -> Maybe ObjectVersionId
versionId} -> Maybe ObjectVersionId
versionId) (\s :: GetObjectLegalHold
s@GetObjectLegalHold' {} Maybe ObjectVersionId
a -> GetObjectLegalHold
s {$sel:versionId:GetObjectLegalHold' :: Maybe ObjectVersionId
versionId = Maybe ObjectVersionId
a} :: GetObjectLegalHold)

-- | The bucket name containing the object whose legal hold status 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/.
getObjectLegalHold_bucket :: Lens.Lens' GetObjectLegalHold BucketName
getObjectLegalHold_bucket :: Lens' GetObjectLegalHold BucketName
getObjectLegalHold_bucket = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\GetObjectLegalHold' {BucketName
bucket :: BucketName
$sel:bucket:GetObjectLegalHold' :: GetObjectLegalHold -> BucketName
bucket} -> BucketName
bucket) (\s :: GetObjectLegalHold
s@GetObjectLegalHold' {} BucketName
a -> GetObjectLegalHold
s {$sel:bucket:GetObjectLegalHold' :: BucketName
bucket = BucketName
a} :: GetObjectLegalHold)

-- | The key name for the object whose legal hold status you want to
-- retrieve.
getObjectLegalHold_key :: Lens.Lens' GetObjectLegalHold ObjectKey
getObjectLegalHold_key :: Lens' GetObjectLegalHold ObjectKey
getObjectLegalHold_key = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\GetObjectLegalHold' {ObjectKey
key :: ObjectKey
$sel:key:GetObjectLegalHold' :: GetObjectLegalHold -> ObjectKey
key} -> ObjectKey
key) (\s :: GetObjectLegalHold
s@GetObjectLegalHold' {} ObjectKey
a -> GetObjectLegalHold
s {$sel:key:GetObjectLegalHold' :: ObjectKey
key = ObjectKey
a} :: GetObjectLegalHold)

instance Core.AWSRequest GetObjectLegalHold where
  type
    AWSResponse GetObjectLegalHold =
      GetObjectLegalHoldResponse
  request :: (Service -> Service)
-> GetObjectLegalHold -> Request GetObjectLegalHold
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 GetObjectLegalHold
-> ClientResponse ClientBody
-> m (Either
        Error (ClientResponse (AWSResponse GetObjectLegalHold)))
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 ObjectLockLegalHold -> Int -> GetObjectLegalHoldResponse
GetObjectLegalHoldResponse'
            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 GetObjectLegalHold where
  hashWithSalt :: Int -> GetObjectLegalHold -> Int
hashWithSalt Int
_salt GetObjectLegalHold' {Maybe Text
Maybe ObjectVersionId
Maybe RequestPayer
ObjectKey
BucketName
key :: ObjectKey
bucket :: BucketName
versionId :: Maybe ObjectVersionId
requestPayer :: Maybe RequestPayer
expectedBucketOwner :: Maybe Text
$sel:key:GetObjectLegalHold' :: GetObjectLegalHold -> ObjectKey
$sel:bucket:GetObjectLegalHold' :: GetObjectLegalHold -> BucketName
$sel:versionId:GetObjectLegalHold' :: GetObjectLegalHold -> Maybe ObjectVersionId
$sel:requestPayer:GetObjectLegalHold' :: GetObjectLegalHold -> Maybe RequestPayer
$sel:expectedBucketOwner:GetObjectLegalHold' :: GetObjectLegalHold -> 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 GetObjectLegalHold where
  rnf :: GetObjectLegalHold -> ()
rnf GetObjectLegalHold' {Maybe Text
Maybe ObjectVersionId
Maybe RequestPayer
ObjectKey
BucketName
key :: ObjectKey
bucket :: BucketName
versionId :: Maybe ObjectVersionId
requestPayer :: Maybe RequestPayer
expectedBucketOwner :: Maybe Text
$sel:key:GetObjectLegalHold' :: GetObjectLegalHold -> ObjectKey
$sel:bucket:GetObjectLegalHold' :: GetObjectLegalHold -> BucketName
$sel:versionId:GetObjectLegalHold' :: GetObjectLegalHold -> Maybe ObjectVersionId
$sel:requestPayer:GetObjectLegalHold' :: GetObjectLegalHold -> Maybe RequestPayer
$sel:expectedBucketOwner:GetObjectLegalHold' :: GetObjectLegalHold -> 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 GetObjectLegalHold where
  toHeaders :: GetObjectLegalHold -> ResponseHeaders
toHeaders GetObjectLegalHold' {Maybe Text
Maybe ObjectVersionId
Maybe RequestPayer
ObjectKey
BucketName
key :: ObjectKey
bucket :: BucketName
versionId :: Maybe ObjectVersionId
requestPayer :: Maybe RequestPayer
expectedBucketOwner :: Maybe Text
$sel:key:GetObjectLegalHold' :: GetObjectLegalHold -> ObjectKey
$sel:bucket:GetObjectLegalHold' :: GetObjectLegalHold -> BucketName
$sel:versionId:GetObjectLegalHold' :: GetObjectLegalHold -> Maybe ObjectVersionId
$sel:requestPayer:GetObjectLegalHold' :: GetObjectLegalHold -> Maybe RequestPayer
$sel:expectedBucketOwner:GetObjectLegalHold' :: GetObjectLegalHold -> 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 GetObjectLegalHold where
  toPath :: GetObjectLegalHold -> ByteString
toPath GetObjectLegalHold' {Maybe Text
Maybe ObjectVersionId
Maybe RequestPayer
ObjectKey
BucketName
key :: ObjectKey
bucket :: BucketName
versionId :: Maybe ObjectVersionId
requestPayer :: Maybe RequestPayer
expectedBucketOwner :: Maybe Text
$sel:key:GetObjectLegalHold' :: GetObjectLegalHold -> ObjectKey
$sel:bucket:GetObjectLegalHold' :: GetObjectLegalHold -> BucketName
$sel:versionId:GetObjectLegalHold' :: GetObjectLegalHold -> Maybe ObjectVersionId
$sel:requestPayer:GetObjectLegalHold' :: GetObjectLegalHold -> Maybe RequestPayer
$sel:expectedBucketOwner:GetObjectLegalHold' :: GetObjectLegalHold -> 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 GetObjectLegalHold where
  toQuery :: GetObjectLegalHold -> QueryString
toQuery GetObjectLegalHold' {Maybe Text
Maybe ObjectVersionId
Maybe RequestPayer
ObjectKey
BucketName
key :: ObjectKey
bucket :: BucketName
versionId :: Maybe ObjectVersionId
requestPayer :: Maybe RequestPayer
expectedBucketOwner :: Maybe Text
$sel:key:GetObjectLegalHold' :: GetObjectLegalHold -> ObjectKey
$sel:bucket:GetObjectLegalHold' :: GetObjectLegalHold -> BucketName
$sel:versionId:GetObjectLegalHold' :: GetObjectLegalHold -> Maybe ObjectVersionId
$sel:requestPayer:GetObjectLegalHold' :: GetObjectLegalHold -> Maybe RequestPayer
$sel:expectedBucketOwner:GetObjectLegalHold' :: GetObjectLegalHold -> Maybe Text
..} =
    forall a. Monoid a => [a] -> a
Prelude.mconcat
      [ByteString
"versionId" forall a. ToQuery a => ByteString -> a -> QueryString
Data.=: Maybe ObjectVersionId
versionId, QueryString
"legal-hold"]

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

-- |
-- Create a value of 'GetObjectLegalHoldResponse' 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:
--
-- 'legalHold', 'getObjectLegalHoldResponse_legalHold' - The current legal hold status for the specified object.
--
-- 'httpStatus', 'getObjectLegalHoldResponse_httpStatus' - The response's http status code.
newGetObjectLegalHoldResponse ::
  -- | 'httpStatus'
  Prelude.Int ->
  GetObjectLegalHoldResponse
newGetObjectLegalHoldResponse :: Int -> GetObjectLegalHoldResponse
newGetObjectLegalHoldResponse Int
pHttpStatus_ =
  GetObjectLegalHoldResponse'
    { $sel:legalHold:GetObjectLegalHoldResponse' :: Maybe ObjectLockLegalHold
legalHold =
        forall a. Maybe a
Prelude.Nothing,
      $sel:httpStatus:GetObjectLegalHoldResponse' :: Int
httpStatus = Int
pHttpStatus_
    }

-- | The current legal hold status for the specified object.
getObjectLegalHoldResponse_legalHold :: Lens.Lens' GetObjectLegalHoldResponse (Prelude.Maybe ObjectLockLegalHold)
getObjectLegalHoldResponse_legalHold :: Lens' GetObjectLegalHoldResponse (Maybe ObjectLockLegalHold)
getObjectLegalHoldResponse_legalHold = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\GetObjectLegalHoldResponse' {Maybe ObjectLockLegalHold
legalHold :: Maybe ObjectLockLegalHold
$sel:legalHold:GetObjectLegalHoldResponse' :: GetObjectLegalHoldResponse -> Maybe ObjectLockLegalHold
legalHold} -> Maybe ObjectLockLegalHold
legalHold) (\s :: GetObjectLegalHoldResponse
s@GetObjectLegalHoldResponse' {} Maybe ObjectLockLegalHold
a -> GetObjectLegalHoldResponse
s {$sel:legalHold:GetObjectLegalHoldResponse' :: Maybe ObjectLockLegalHold
legalHold = Maybe ObjectLockLegalHold
a} :: GetObjectLegalHoldResponse)

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

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