{-# 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.Macie.ListS3Resources
-- Copyright   : (c) 2013-2023 Brendan Hay
-- License     : Mozilla Public License, v. 2.0.
-- Maintainer  : Brendan Hay
-- Stability   : auto-generated
-- Portability : non-portable (GHC extensions)
--
-- (Discontinued) Lists all the S3 resources associated with Amazon Macie
-- Classic. If @memberAccountId@ isn\'t specified, the action lists the S3
-- resources associated with Macie Classic for the current Macie Classic
-- administrator account. If @memberAccountId@ is specified, the action
-- lists the S3 resources associated with Macie Classic for the specified
-- member account.
--
-- This operation returns paginated results.
module Amazonka.Macie.ListS3Resources
  ( -- * Creating a Request
    ListS3Resources (..),
    newListS3Resources,

    -- * Request Lenses
    listS3Resources_maxResults,
    listS3Resources_memberAccountId,
    listS3Resources_nextToken,

    -- * Destructuring the Response
    ListS3ResourcesResponse (..),
    newListS3ResourcesResponse,

    -- * Response Lenses
    listS3ResourcesResponse_nextToken,
    listS3ResourcesResponse_s3Resources,
    listS3ResourcesResponse_httpStatus,
  )
where

import qualified Amazonka.Core as Core
import qualified Amazonka.Core.Lens.Internal as Lens
import qualified Amazonka.Data as Data
import Amazonka.Macie.Types
import qualified Amazonka.Prelude as Prelude
import qualified Amazonka.Request as Request
import qualified Amazonka.Response as Response

-- | /See:/ 'newListS3Resources' smart constructor.
data ListS3Resources = ListS3Resources'
  { -- | (Discontinued) Use this parameter to indicate the maximum number of
    -- items that you want in the response. The default value is 250.
    ListS3Resources -> Maybe Int
maxResults :: Prelude.Maybe Prelude.Int,
    -- | (Discontinued) The Amazon Macie Classic member account ID whose
    -- associated S3 resources you want to list.
    ListS3Resources -> Maybe Text
memberAccountId :: Prelude.Maybe Prelude.Text,
    -- | (Discontinued) Use this parameter when paginating results. Set its value
    -- to null on your first call to the @ListS3Resources@ action. Subsequent
    -- calls to the action fill @nextToken@ in the request with the value of
    -- @nextToken@ from the previous response to continue listing data.
    ListS3Resources -> Maybe Text
nextToken :: Prelude.Maybe Prelude.Text
  }
  deriving (ListS3Resources -> ListS3Resources -> Bool
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: ListS3Resources -> ListS3Resources -> Bool
$c/= :: ListS3Resources -> ListS3Resources -> Bool
== :: ListS3Resources -> ListS3Resources -> Bool
$c== :: ListS3Resources -> ListS3Resources -> Bool
Prelude.Eq, ReadPrec [ListS3Resources]
ReadPrec ListS3Resources
Int -> ReadS ListS3Resources
ReadS [ListS3Resources]
forall a.
(Int -> ReadS a)
-> ReadS [a] -> ReadPrec a -> ReadPrec [a] -> Read a
readListPrec :: ReadPrec [ListS3Resources]
$creadListPrec :: ReadPrec [ListS3Resources]
readPrec :: ReadPrec ListS3Resources
$creadPrec :: ReadPrec ListS3Resources
readList :: ReadS [ListS3Resources]
$creadList :: ReadS [ListS3Resources]
readsPrec :: Int -> ReadS ListS3Resources
$creadsPrec :: Int -> ReadS ListS3Resources
Prelude.Read, Int -> ListS3Resources -> ShowS
[ListS3Resources] -> ShowS
ListS3Resources -> String
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [ListS3Resources] -> ShowS
$cshowList :: [ListS3Resources] -> ShowS
show :: ListS3Resources -> String
$cshow :: ListS3Resources -> String
showsPrec :: Int -> ListS3Resources -> ShowS
$cshowsPrec :: Int -> ListS3Resources -> ShowS
Prelude.Show, forall x. Rep ListS3Resources x -> ListS3Resources
forall x. ListS3Resources -> Rep ListS3Resources x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cto :: forall x. Rep ListS3Resources x -> ListS3Resources
$cfrom :: forall x. ListS3Resources -> Rep ListS3Resources x
Prelude.Generic)

-- |
-- Create a value of 'ListS3Resources' 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:
--
-- 'maxResults', 'listS3Resources_maxResults' - (Discontinued) Use this parameter to indicate the maximum number of
-- items that you want in the response. The default value is 250.
--
-- 'memberAccountId', 'listS3Resources_memberAccountId' - (Discontinued) The Amazon Macie Classic member account ID whose
-- associated S3 resources you want to list.
--
-- 'nextToken', 'listS3Resources_nextToken' - (Discontinued) Use this parameter when paginating results. Set its value
-- to null on your first call to the @ListS3Resources@ action. Subsequent
-- calls to the action fill @nextToken@ in the request with the value of
-- @nextToken@ from the previous response to continue listing data.
newListS3Resources ::
  ListS3Resources
newListS3Resources :: ListS3Resources
newListS3Resources =
  ListS3Resources'
    { $sel:maxResults:ListS3Resources' :: Maybe Int
maxResults = forall a. Maybe a
Prelude.Nothing,
      $sel:memberAccountId:ListS3Resources' :: Maybe Text
memberAccountId = forall a. Maybe a
Prelude.Nothing,
      $sel:nextToken:ListS3Resources' :: Maybe Text
nextToken = forall a. Maybe a
Prelude.Nothing
    }

-- | (Discontinued) Use this parameter to indicate the maximum number of
-- items that you want in the response. The default value is 250.
listS3Resources_maxResults :: Lens.Lens' ListS3Resources (Prelude.Maybe Prelude.Int)
listS3Resources_maxResults :: Lens' ListS3Resources (Maybe Int)
listS3Resources_maxResults = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\ListS3Resources' {Maybe Int
maxResults :: Maybe Int
$sel:maxResults:ListS3Resources' :: ListS3Resources -> Maybe Int
maxResults} -> Maybe Int
maxResults) (\s :: ListS3Resources
s@ListS3Resources' {} Maybe Int
a -> ListS3Resources
s {$sel:maxResults:ListS3Resources' :: Maybe Int
maxResults = Maybe Int
a} :: ListS3Resources)

-- | (Discontinued) The Amazon Macie Classic member account ID whose
-- associated S3 resources you want to list.
listS3Resources_memberAccountId :: Lens.Lens' ListS3Resources (Prelude.Maybe Prelude.Text)
listS3Resources_memberAccountId :: Lens' ListS3Resources (Maybe Text)
listS3Resources_memberAccountId = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\ListS3Resources' {Maybe Text
memberAccountId :: Maybe Text
$sel:memberAccountId:ListS3Resources' :: ListS3Resources -> Maybe Text
memberAccountId} -> Maybe Text
memberAccountId) (\s :: ListS3Resources
s@ListS3Resources' {} Maybe Text
a -> ListS3Resources
s {$sel:memberAccountId:ListS3Resources' :: Maybe Text
memberAccountId = Maybe Text
a} :: ListS3Resources)

-- | (Discontinued) Use this parameter when paginating results. Set its value
-- to null on your first call to the @ListS3Resources@ action. Subsequent
-- calls to the action fill @nextToken@ in the request with the value of
-- @nextToken@ from the previous response to continue listing data.
listS3Resources_nextToken :: Lens.Lens' ListS3Resources (Prelude.Maybe Prelude.Text)
listS3Resources_nextToken :: Lens' ListS3Resources (Maybe Text)
listS3Resources_nextToken = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\ListS3Resources' {Maybe Text
nextToken :: Maybe Text
$sel:nextToken:ListS3Resources' :: ListS3Resources -> Maybe Text
nextToken} -> Maybe Text
nextToken) (\s :: ListS3Resources
s@ListS3Resources' {} Maybe Text
a -> ListS3Resources
s {$sel:nextToken:ListS3Resources' :: Maybe Text
nextToken = Maybe Text
a} :: ListS3Resources)

instance Core.AWSPager ListS3Resources where
  page :: ListS3Resources
-> AWSResponse ListS3Resources -> Maybe ListS3Resources
page ListS3Resources
rq AWSResponse ListS3Resources
rs
    | forall a. AWSTruncated a => a -> Bool
Core.stop
        ( AWSResponse ListS3Resources
rs
            forall s a. s -> Getting (First a) s a -> Maybe a
Lens.^? Lens' ListS3ResourcesResponse (Maybe Text)
listS3ResourcesResponse_nextToken
            forall b c a. (b -> c) -> (a -> b) -> a -> c
Prelude.. forall a b. Prism (Maybe a) (Maybe b) a b
Lens._Just
        ) =
        forall a. Maybe a
Prelude.Nothing
    | forall a. AWSTruncated a => a -> Bool
Core.stop
        ( AWSResponse ListS3Resources
rs
            forall s a. s -> Getting (First a) s a -> Maybe a
Lens.^? Lens' ListS3ResourcesResponse (Maybe [S3ResourceClassification])
listS3ResourcesResponse_s3Resources
            forall b c a. (b -> c) -> (a -> b) -> a -> c
Prelude.. forall a b. Prism (Maybe a) (Maybe b) a b
Lens._Just
        ) =
        forall a. Maybe a
Prelude.Nothing
    | Bool
Prelude.otherwise =
        forall a. a -> Maybe a
Prelude.Just
          forall a b. (a -> b) -> a -> b
Prelude.$ ListS3Resources
rq
          forall a b. a -> (a -> b) -> b
Prelude.& Lens' ListS3Resources (Maybe Text)
listS3Resources_nextToken
          forall s t a b. ASetter s t a b -> b -> s -> t
Lens..~ AWSResponse ListS3Resources
rs
          forall s a. s -> Getting (First a) s a -> Maybe a
Lens.^? Lens' ListS3ResourcesResponse (Maybe Text)
listS3ResourcesResponse_nextToken
          forall b c a. (b -> c) -> (a -> b) -> a -> c
Prelude.. forall a b. Prism (Maybe a) (Maybe b) a b
Lens._Just

instance Core.AWSRequest ListS3Resources where
  type
    AWSResponse ListS3Resources =
      ListS3ResourcesResponse
  request :: (Service -> Service) -> ListS3Resources -> Request ListS3Resources
request Service -> Service
overrides =
    forall a. (ToRequest a, ToJSON a) => Service -> a -> Request a
Request.postJSON (Service -> Service
overrides Service
defaultService)
  response :: forall (m :: * -> *).
MonadResource m =>
(ByteStringLazy -> IO ByteStringLazy)
-> Service
-> Proxy ListS3Resources
-> ClientResponse ClientBody
-> m (Either Error (ClientResponse (AWSResponse ListS3Resources)))
response =
    forall (m :: * -> *) a.
MonadResource m =>
(Int -> ResponseHeaders -> Object -> Either String (AWSResponse a))
-> (ByteStringLazy -> IO ByteStringLazy)
-> Service
-> Proxy a
-> ClientResponse ClientBody
-> m (Either Error (ClientResponse (AWSResponse a)))
Response.receiveJSON
      ( \Int
s ResponseHeaders
h Object
x ->
          Maybe Text
-> Maybe [S3ResourceClassification]
-> Int
-> ListS3ResourcesResponse
ListS3ResourcesResponse'
            forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
Prelude.<$> (Object
x forall a. FromJSON a => Object -> Key -> Either String (Maybe a)
Data..?> Key
"nextToken")
            forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
Prelude.<*> (Object
x forall a. FromJSON a => Object -> Key -> Either String (Maybe a)
Data..?> Key
"s3Resources" forall (f :: * -> *) a. Functor f => f (Maybe a) -> a -> f a
Core..!@ forall a. Monoid a => a
Prelude.mempty)
            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 ListS3Resources where
  hashWithSalt :: Int -> ListS3Resources -> Int
hashWithSalt Int
_salt ListS3Resources' {Maybe Int
Maybe Text
nextToken :: Maybe Text
memberAccountId :: Maybe Text
maxResults :: Maybe Int
$sel:nextToken:ListS3Resources' :: ListS3Resources -> Maybe Text
$sel:memberAccountId:ListS3Resources' :: ListS3Resources -> Maybe Text
$sel:maxResults:ListS3Resources' :: ListS3Resources -> Maybe Int
..} =
    Int
_salt
      forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Maybe Int
maxResults
      forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Maybe Text
memberAccountId
      forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Maybe Text
nextToken

instance Prelude.NFData ListS3Resources where
  rnf :: ListS3Resources -> ()
rnf ListS3Resources' {Maybe Int
Maybe Text
nextToken :: Maybe Text
memberAccountId :: Maybe Text
maxResults :: Maybe Int
$sel:nextToken:ListS3Resources' :: ListS3Resources -> Maybe Text
$sel:memberAccountId:ListS3Resources' :: ListS3Resources -> Maybe Text
$sel:maxResults:ListS3Resources' :: ListS3Resources -> Maybe Int
..} =
    forall a. NFData a => a -> ()
Prelude.rnf Maybe Int
maxResults
      seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf Maybe Text
memberAccountId
      seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf Maybe Text
nextToken

instance Data.ToHeaders ListS3Resources where
  toHeaders :: ListS3Resources -> ResponseHeaders
toHeaders =
    forall a b. a -> b -> a
Prelude.const
      ( forall a. Monoid a => [a] -> a
Prelude.mconcat
          [ HeaderName
"X-Amz-Target"
              forall a. ToHeader a => HeaderName -> a -> ResponseHeaders
Data.=# ( ByteString
"MacieService.ListS3Resources" ::
                          Prelude.ByteString
                      ),
            HeaderName
"Content-Type"
              forall a. ToHeader a => HeaderName -> a -> ResponseHeaders
Data.=# ( ByteString
"application/x-amz-json-1.1" ::
                          Prelude.ByteString
                      )
          ]
      )

instance Data.ToJSON ListS3Resources where
  toJSON :: ListS3Resources -> Value
toJSON ListS3Resources' {Maybe Int
Maybe Text
nextToken :: Maybe Text
memberAccountId :: Maybe Text
maxResults :: Maybe Int
$sel:nextToken:ListS3Resources' :: ListS3Resources -> Maybe Text
$sel:memberAccountId:ListS3Resources' :: ListS3Resources -> Maybe Text
$sel:maxResults:ListS3Resources' :: ListS3Resources -> Maybe Int
..} =
    [Pair] -> Value
Data.object
      ( forall a. [Maybe a] -> [a]
Prelude.catMaybes
          [ (Key
"maxResults" forall kv v. (KeyValue kv, ToJSON v) => Key -> v -> kv
Data..=) forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
Prelude.<$> Maybe Int
maxResults,
            (Key
"memberAccountId" forall kv v. (KeyValue kv, ToJSON v) => Key -> v -> kv
Data..=)
              forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
Prelude.<$> Maybe Text
memberAccountId,
            (Key
"nextToken" forall kv v. (KeyValue kv, ToJSON v) => Key -> v -> kv
Data..=) forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
Prelude.<$> Maybe Text
nextToken
          ]
      )

instance Data.ToPath ListS3Resources where
  toPath :: ListS3Resources -> ByteString
toPath = forall a b. a -> b -> a
Prelude.const ByteString
"/"

instance Data.ToQuery ListS3Resources where
  toQuery :: ListS3Resources -> QueryString
toQuery = forall a b. a -> b -> a
Prelude.const forall a. Monoid a => a
Prelude.mempty

-- | /See:/ 'newListS3ResourcesResponse' smart constructor.
data ListS3ResourcesResponse = ListS3ResourcesResponse'
  { -- | (Discontinued) When a response is generated, if there is more data to be
    -- listed, this parameter is present in the response and contains the value
    -- to use for the @nextToken@ parameter in a subsequent pagination request.
    -- If there is no more data to be listed, this parameter is set to null.
    ListS3ResourcesResponse -> Maybe Text
nextToken :: Prelude.Maybe Prelude.Text,
    -- | (Discontinued) A list of the associated S3 resources returned by the
    -- action.
    ListS3ResourcesResponse -> Maybe [S3ResourceClassification]
s3Resources :: Prelude.Maybe [S3ResourceClassification],
    -- | The response's http status code.
    ListS3ResourcesResponse -> Int
httpStatus :: Prelude.Int
  }
  deriving (ListS3ResourcesResponse -> ListS3ResourcesResponse -> Bool
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: ListS3ResourcesResponse -> ListS3ResourcesResponse -> Bool
$c/= :: ListS3ResourcesResponse -> ListS3ResourcesResponse -> Bool
== :: ListS3ResourcesResponse -> ListS3ResourcesResponse -> Bool
$c== :: ListS3ResourcesResponse -> ListS3ResourcesResponse -> Bool
Prelude.Eq, ReadPrec [ListS3ResourcesResponse]
ReadPrec ListS3ResourcesResponse
Int -> ReadS ListS3ResourcesResponse
ReadS [ListS3ResourcesResponse]
forall a.
(Int -> ReadS a)
-> ReadS [a] -> ReadPrec a -> ReadPrec [a] -> Read a
readListPrec :: ReadPrec [ListS3ResourcesResponse]
$creadListPrec :: ReadPrec [ListS3ResourcesResponse]
readPrec :: ReadPrec ListS3ResourcesResponse
$creadPrec :: ReadPrec ListS3ResourcesResponse
readList :: ReadS [ListS3ResourcesResponse]
$creadList :: ReadS [ListS3ResourcesResponse]
readsPrec :: Int -> ReadS ListS3ResourcesResponse
$creadsPrec :: Int -> ReadS ListS3ResourcesResponse
Prelude.Read, Int -> ListS3ResourcesResponse -> ShowS
[ListS3ResourcesResponse] -> ShowS
ListS3ResourcesResponse -> String
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [ListS3ResourcesResponse] -> ShowS
$cshowList :: [ListS3ResourcesResponse] -> ShowS
show :: ListS3ResourcesResponse -> String
$cshow :: ListS3ResourcesResponse -> String
showsPrec :: Int -> ListS3ResourcesResponse -> ShowS
$cshowsPrec :: Int -> ListS3ResourcesResponse -> ShowS
Prelude.Show, forall x. Rep ListS3ResourcesResponse x -> ListS3ResourcesResponse
forall x. ListS3ResourcesResponse -> Rep ListS3ResourcesResponse x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cto :: forall x. Rep ListS3ResourcesResponse x -> ListS3ResourcesResponse
$cfrom :: forall x. ListS3ResourcesResponse -> Rep ListS3ResourcesResponse x
Prelude.Generic)

-- |
-- Create a value of 'ListS3ResourcesResponse' 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:
--
-- 'nextToken', 'listS3ResourcesResponse_nextToken' - (Discontinued) When a response is generated, if there is more data to be
-- listed, this parameter is present in the response and contains the value
-- to use for the @nextToken@ parameter in a subsequent pagination request.
-- If there is no more data to be listed, this parameter is set to null.
--
-- 's3Resources', 'listS3ResourcesResponse_s3Resources' - (Discontinued) A list of the associated S3 resources returned by the
-- action.
--
-- 'httpStatus', 'listS3ResourcesResponse_httpStatus' - The response's http status code.
newListS3ResourcesResponse ::
  -- | 'httpStatus'
  Prelude.Int ->
  ListS3ResourcesResponse
newListS3ResourcesResponse :: Int -> ListS3ResourcesResponse
newListS3ResourcesResponse Int
pHttpStatus_ =
  ListS3ResourcesResponse'
    { $sel:nextToken:ListS3ResourcesResponse' :: Maybe Text
nextToken =
        forall a. Maybe a
Prelude.Nothing,
      $sel:s3Resources:ListS3ResourcesResponse' :: Maybe [S3ResourceClassification]
s3Resources = forall a. Maybe a
Prelude.Nothing,
      $sel:httpStatus:ListS3ResourcesResponse' :: Int
httpStatus = Int
pHttpStatus_
    }

-- | (Discontinued) When a response is generated, if there is more data to be
-- listed, this parameter is present in the response and contains the value
-- to use for the @nextToken@ parameter in a subsequent pagination request.
-- If there is no more data to be listed, this parameter is set to null.
listS3ResourcesResponse_nextToken :: Lens.Lens' ListS3ResourcesResponse (Prelude.Maybe Prelude.Text)
listS3ResourcesResponse_nextToken :: Lens' ListS3ResourcesResponse (Maybe Text)
listS3ResourcesResponse_nextToken = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\ListS3ResourcesResponse' {Maybe Text
nextToken :: Maybe Text
$sel:nextToken:ListS3ResourcesResponse' :: ListS3ResourcesResponse -> Maybe Text
nextToken} -> Maybe Text
nextToken) (\s :: ListS3ResourcesResponse
s@ListS3ResourcesResponse' {} Maybe Text
a -> ListS3ResourcesResponse
s {$sel:nextToken:ListS3ResourcesResponse' :: Maybe Text
nextToken = Maybe Text
a} :: ListS3ResourcesResponse)

-- | (Discontinued) A list of the associated S3 resources returned by the
-- action.
listS3ResourcesResponse_s3Resources :: Lens.Lens' ListS3ResourcesResponse (Prelude.Maybe [S3ResourceClassification])
listS3ResourcesResponse_s3Resources :: Lens' ListS3ResourcesResponse (Maybe [S3ResourceClassification])
listS3ResourcesResponse_s3Resources = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\ListS3ResourcesResponse' {Maybe [S3ResourceClassification]
s3Resources :: Maybe [S3ResourceClassification]
$sel:s3Resources:ListS3ResourcesResponse' :: ListS3ResourcesResponse -> Maybe [S3ResourceClassification]
s3Resources} -> Maybe [S3ResourceClassification]
s3Resources) (\s :: ListS3ResourcesResponse
s@ListS3ResourcesResponse' {} Maybe [S3ResourceClassification]
a -> ListS3ResourcesResponse
s {$sel:s3Resources:ListS3ResourcesResponse' :: Maybe [S3ResourceClassification]
s3Resources = Maybe [S3ResourceClassification]
a} :: ListS3ResourcesResponse) 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.
listS3ResourcesResponse_httpStatus :: Lens.Lens' ListS3ResourcesResponse Prelude.Int
listS3ResourcesResponse_httpStatus :: Lens' ListS3ResourcesResponse Int
listS3ResourcesResponse_httpStatus = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\ListS3ResourcesResponse' {Int
httpStatus :: Int
$sel:httpStatus:ListS3ResourcesResponse' :: ListS3ResourcesResponse -> Int
httpStatus} -> Int
httpStatus) (\s :: ListS3ResourcesResponse
s@ListS3ResourcesResponse' {} Int
a -> ListS3ResourcesResponse
s {$sel:httpStatus:ListS3ResourcesResponse' :: Int
httpStatus = Int
a} :: ListS3ResourcesResponse)

instance Prelude.NFData ListS3ResourcesResponse where
  rnf :: ListS3ResourcesResponse -> ()
rnf ListS3ResourcesResponse' {Int
Maybe [S3ResourceClassification]
Maybe Text
httpStatus :: Int
s3Resources :: Maybe [S3ResourceClassification]
nextToken :: Maybe Text
$sel:httpStatus:ListS3ResourcesResponse' :: ListS3ResourcesResponse -> Int
$sel:s3Resources:ListS3ResourcesResponse' :: ListS3ResourcesResponse -> Maybe [S3ResourceClassification]
$sel:nextToken:ListS3ResourcesResponse' :: ListS3ResourcesResponse -> Maybe Text
..} =
    forall a. NFData a => a -> ()
Prelude.rnf Maybe Text
nextToken
      seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf Maybe [S3ResourceClassification]
s3Resources
      seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf Int
httpStatus