{-# 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.MacieV2.GetBucketStatistics
-- 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 (queries) aggregated statistical data about all the S3 buckets
-- that Amazon Macie monitors and analyzes for an account.
module Amazonka.MacieV2.GetBucketStatistics
  ( -- * Creating a Request
    GetBucketStatistics (..),
    newGetBucketStatistics,

    -- * Request Lenses
    getBucketStatistics_accountId,

    -- * Destructuring the Response
    GetBucketStatisticsResponse (..),
    newGetBucketStatisticsResponse,

    -- * Response Lenses
    getBucketStatisticsResponse_bucketCount,
    getBucketStatisticsResponse_bucketCountByEffectivePermission,
    getBucketStatisticsResponse_bucketCountByEncryptionType,
    getBucketStatisticsResponse_bucketCountByObjectEncryptionRequirement,
    getBucketStatisticsResponse_bucketCountBySharedAccessType,
    getBucketStatisticsResponse_bucketStatisticsBySensitivity,
    getBucketStatisticsResponse_classifiableObjectCount,
    getBucketStatisticsResponse_classifiableSizeInBytes,
    getBucketStatisticsResponse_lastUpdated,
    getBucketStatisticsResponse_objectCount,
    getBucketStatisticsResponse_sizeInBytes,
    getBucketStatisticsResponse_sizeInBytesCompressed,
    getBucketStatisticsResponse_unclassifiableObjectCount,
    getBucketStatisticsResponse_unclassifiableObjectSizeInBytes,
    getBucketStatisticsResponse_httpStatus,
  )
where

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

-- | /See:/ 'newGetBucketStatistics' smart constructor.
data GetBucketStatistics = GetBucketStatistics'
  { -- | The unique identifier for the Amazon Web Services account.
    GetBucketStatistics -> Maybe Text
accountId :: Prelude.Maybe Prelude.Text
  }
  deriving (GetBucketStatistics -> GetBucketStatistics -> Bool
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: GetBucketStatistics -> GetBucketStatistics -> Bool
$c/= :: GetBucketStatistics -> GetBucketStatistics -> Bool
== :: GetBucketStatistics -> GetBucketStatistics -> Bool
$c== :: GetBucketStatistics -> GetBucketStatistics -> Bool
Prelude.Eq, ReadPrec [GetBucketStatistics]
ReadPrec GetBucketStatistics
Int -> ReadS GetBucketStatistics
ReadS [GetBucketStatistics]
forall a.
(Int -> ReadS a)
-> ReadS [a] -> ReadPrec a -> ReadPrec [a] -> Read a
readListPrec :: ReadPrec [GetBucketStatistics]
$creadListPrec :: ReadPrec [GetBucketStatistics]
readPrec :: ReadPrec GetBucketStatistics
$creadPrec :: ReadPrec GetBucketStatistics
readList :: ReadS [GetBucketStatistics]
$creadList :: ReadS [GetBucketStatistics]
readsPrec :: Int -> ReadS GetBucketStatistics
$creadsPrec :: Int -> ReadS GetBucketStatistics
Prelude.Read, Int -> GetBucketStatistics -> ShowS
[GetBucketStatistics] -> ShowS
GetBucketStatistics -> String
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [GetBucketStatistics] -> ShowS
$cshowList :: [GetBucketStatistics] -> ShowS
show :: GetBucketStatistics -> String
$cshow :: GetBucketStatistics -> String
showsPrec :: Int -> GetBucketStatistics -> ShowS
$cshowsPrec :: Int -> GetBucketStatistics -> ShowS
Prelude.Show, forall x. Rep GetBucketStatistics x -> GetBucketStatistics
forall x. GetBucketStatistics -> Rep GetBucketStatistics x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cto :: forall x. Rep GetBucketStatistics x -> GetBucketStatistics
$cfrom :: forall x. GetBucketStatistics -> Rep GetBucketStatistics x
Prelude.Generic)

-- |
-- Create a value of 'GetBucketStatistics' 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:
--
-- 'accountId', 'getBucketStatistics_accountId' - The unique identifier for the Amazon Web Services account.
newGetBucketStatistics ::
  GetBucketStatistics
newGetBucketStatistics :: GetBucketStatistics
newGetBucketStatistics =
  GetBucketStatistics' {$sel:accountId:GetBucketStatistics' :: Maybe Text
accountId = forall a. Maybe a
Prelude.Nothing}

-- | The unique identifier for the Amazon Web Services account.
getBucketStatistics_accountId :: Lens.Lens' GetBucketStatistics (Prelude.Maybe Prelude.Text)
getBucketStatistics_accountId :: Lens' GetBucketStatistics (Maybe Text)
getBucketStatistics_accountId = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\GetBucketStatistics' {Maybe Text
accountId :: Maybe Text
$sel:accountId:GetBucketStatistics' :: GetBucketStatistics -> Maybe Text
accountId} -> Maybe Text
accountId) (\s :: GetBucketStatistics
s@GetBucketStatistics' {} Maybe Text
a -> GetBucketStatistics
s {$sel:accountId:GetBucketStatistics' :: Maybe Text
accountId = Maybe Text
a} :: GetBucketStatistics)

instance Core.AWSRequest GetBucketStatistics where
  type
    AWSResponse GetBucketStatistics =
      GetBucketStatisticsResponse
  request :: (Service -> Service)
-> GetBucketStatistics -> Request GetBucketStatistics
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 GetBucketStatistics
-> ClientResponse ClientBody
-> m (Either
        Error (ClientResponse (AWSResponse GetBucketStatistics)))
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 Integer
-> Maybe BucketCountByEffectivePermission
-> Maybe BucketCountByEncryptionType
-> Maybe BucketCountPolicyAllowsUnencryptedObjectUploads
-> Maybe BucketCountBySharedAccessType
-> Maybe BucketStatisticsBySensitivity
-> Maybe Integer
-> Maybe Integer
-> Maybe ISO8601
-> Maybe Integer
-> Maybe Integer
-> Maybe Integer
-> Maybe ObjectLevelStatistics
-> Maybe ObjectLevelStatistics
-> Int
-> GetBucketStatisticsResponse
GetBucketStatisticsResponse'
            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
"bucketCount")
            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
"bucketCountByEffectivePermission")
            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
"bucketCountByEncryptionType")
            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
"bucketCountByObjectEncryptionRequirement"
                        )
            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
"bucketCountBySharedAccessType")
            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
"bucketStatisticsBySensitivity")
            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
"classifiableObjectCount")
            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
"classifiableSizeInBytes")
            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
"lastUpdated")
            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
"objectCount")
            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
"sizeInBytes")
            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
"sizeInBytesCompressed")
            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
"unclassifiableObjectCount")
            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
"unclassifiableObjectSizeInBytes")
            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 GetBucketStatistics where
  hashWithSalt :: Int -> GetBucketStatistics -> Int
hashWithSalt Int
_salt GetBucketStatistics' {Maybe Text
accountId :: Maybe Text
$sel:accountId:GetBucketStatistics' :: GetBucketStatistics -> Maybe Text
..} =
    Int
_salt forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Maybe Text
accountId

instance Prelude.NFData GetBucketStatistics where
  rnf :: GetBucketStatistics -> ()
rnf GetBucketStatistics' {Maybe Text
accountId :: Maybe Text
$sel:accountId:GetBucketStatistics' :: GetBucketStatistics -> Maybe Text
..} = forall a. NFData a => a -> ()
Prelude.rnf Maybe Text
accountId

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

instance Data.ToJSON GetBucketStatistics where
  toJSON :: GetBucketStatistics -> Value
toJSON GetBucketStatistics' {Maybe Text
accountId :: Maybe Text
$sel:accountId:GetBucketStatistics' :: GetBucketStatistics -> Maybe Text
..} =
    [Pair] -> Value
Data.object
      ( forall a. [Maybe a] -> [a]
Prelude.catMaybes
          [(Key
"accountId" 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
accountId]
      )

instance Data.ToPath GetBucketStatistics where
  toPath :: GetBucketStatistics -> ByteString
toPath = forall a b. a -> b -> a
Prelude.const ByteString
"/datasources/s3/statistics"

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

-- | /See:/ 'newGetBucketStatisticsResponse' smart constructor.
data GetBucketStatisticsResponse = GetBucketStatisticsResponse'
  { -- | The total number of buckets.
    GetBucketStatisticsResponse -> Maybe Integer
bucketCount :: Prelude.Maybe Prelude.Integer,
    -- | The total number of buckets that are publicly accessible based on a
    -- combination of permissions settings for each bucket.
    GetBucketStatisticsResponse
-> Maybe BucketCountByEffectivePermission
bucketCountByEffectivePermission :: Prelude.Maybe BucketCountByEffectivePermission,
    -- | The total number of buckets that use certain types of server-side
    -- encryption to encrypt new objects by default. This object also reports
    -- the total number of buckets that don\'t encrypt new objects by default.
    GetBucketStatisticsResponse -> Maybe BucketCountByEncryptionType
bucketCountByEncryptionType :: Prelude.Maybe BucketCountByEncryptionType,
    -- | The total number of buckets whose bucket policies do or don\'t require
    -- server-side encryption of objects when objects are uploaded to the
    -- buckets.
    GetBucketStatisticsResponse
-> Maybe BucketCountPolicyAllowsUnencryptedObjectUploads
bucketCountByObjectEncryptionRequirement :: Prelude.Maybe BucketCountPolicyAllowsUnencryptedObjectUploads,
    -- | The total number of buckets that are or aren\'t shared with another
    -- Amazon Web Services account.
    GetBucketStatisticsResponse -> Maybe BucketCountBySharedAccessType
bucketCountBySharedAccessType :: Prelude.Maybe BucketCountBySharedAccessType,
    -- | The aggregated sensitive data discovery statistics for the buckets. If
    -- automated sensitive data discovery is currently disabled for your
    -- account, the value for each statistic is 0.
    GetBucketStatisticsResponse -> Maybe BucketStatisticsBySensitivity
bucketStatisticsBySensitivity :: Prelude.Maybe BucketStatisticsBySensitivity,
    -- | The total number of objects that Amazon Macie can analyze in the
    -- buckets. These objects use a supported storage class and have a file
    -- name extension for a supported file or storage format.
    GetBucketStatisticsResponse -> Maybe Integer
classifiableObjectCount :: Prelude.Maybe Prelude.Integer,
    -- | The total storage size, in bytes, of all the objects that Amazon Macie
    -- can analyze in the buckets. These objects use a supported storage class
    -- and have a file name extension for a supported file or storage format.
    --
    -- If versioning is enabled for any of the buckets, this value is based on
    -- the size of the latest version of each applicable object in the buckets.
    -- This value doesn\'t reflect the storage size of all versions of all
    -- applicable objects in the buckets.
    GetBucketStatisticsResponse -> Maybe Integer
classifiableSizeInBytes :: Prelude.Maybe Prelude.Integer,
    -- | The date and time, in UTC and extended ISO 8601 format, when Amazon
    -- Macie most recently retrieved both bucket and object metadata from
    -- Amazon S3 for the buckets.
    GetBucketStatisticsResponse -> Maybe ISO8601
lastUpdated :: Prelude.Maybe Data.ISO8601,
    -- | The total number of objects in the buckets.
    GetBucketStatisticsResponse -> Maybe Integer
objectCount :: Prelude.Maybe Prelude.Integer,
    -- | The total storage size, in bytes, of the buckets.
    --
    -- If versioning is enabled for any of the buckets, this value is based on
    -- the size of the latest version of each object in the buckets. This value
    -- doesn\'t reflect the storage size of all versions of the objects in the
    -- buckets.
    GetBucketStatisticsResponse -> Maybe Integer
sizeInBytes :: Prelude.Maybe Prelude.Integer,
    -- | The total storage size, in bytes, of the objects that are compressed
    -- (.gz, .gzip, .zip) files in the buckets.
    --
    -- If versioning is enabled for any of the buckets, this value is based on
    -- the size of the latest version of each applicable object in the buckets.
    -- This value doesn\'t reflect the storage size of all versions of the
    -- applicable objects in the buckets.
    GetBucketStatisticsResponse -> Maybe Integer
sizeInBytesCompressed :: Prelude.Maybe Prelude.Integer,
    -- | The total number of objects that Amazon Macie can\'t analyze in the
    -- buckets. These objects don\'t use a supported storage class or don\'t
    -- have a file name extension for a supported file or storage format.
    GetBucketStatisticsResponse -> Maybe ObjectLevelStatistics
unclassifiableObjectCount :: Prelude.Maybe ObjectLevelStatistics,
    -- | The total storage size, in bytes, of the objects that Amazon Macie
    -- can\'t analyze in the buckets. These objects don\'t use a supported
    -- storage class or don\'t have a file name extension for a supported file
    -- or storage format.
    GetBucketStatisticsResponse -> Maybe ObjectLevelStatistics
unclassifiableObjectSizeInBytes :: Prelude.Maybe ObjectLevelStatistics,
    -- | The response's http status code.
    GetBucketStatisticsResponse -> Int
httpStatus :: Prelude.Int
  }
  deriving (GetBucketStatisticsResponse -> GetBucketStatisticsResponse -> Bool
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: GetBucketStatisticsResponse -> GetBucketStatisticsResponse -> Bool
$c/= :: GetBucketStatisticsResponse -> GetBucketStatisticsResponse -> Bool
== :: GetBucketStatisticsResponse -> GetBucketStatisticsResponse -> Bool
$c== :: GetBucketStatisticsResponse -> GetBucketStatisticsResponse -> Bool
Prelude.Eq, ReadPrec [GetBucketStatisticsResponse]
ReadPrec GetBucketStatisticsResponse
Int -> ReadS GetBucketStatisticsResponse
ReadS [GetBucketStatisticsResponse]
forall a.
(Int -> ReadS a)
-> ReadS [a] -> ReadPrec a -> ReadPrec [a] -> Read a
readListPrec :: ReadPrec [GetBucketStatisticsResponse]
$creadListPrec :: ReadPrec [GetBucketStatisticsResponse]
readPrec :: ReadPrec GetBucketStatisticsResponse
$creadPrec :: ReadPrec GetBucketStatisticsResponse
readList :: ReadS [GetBucketStatisticsResponse]
$creadList :: ReadS [GetBucketStatisticsResponse]
readsPrec :: Int -> ReadS GetBucketStatisticsResponse
$creadsPrec :: Int -> ReadS GetBucketStatisticsResponse
Prelude.Read, Int -> GetBucketStatisticsResponse -> ShowS
[GetBucketStatisticsResponse] -> ShowS
GetBucketStatisticsResponse -> String
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [GetBucketStatisticsResponse] -> ShowS
$cshowList :: [GetBucketStatisticsResponse] -> ShowS
show :: GetBucketStatisticsResponse -> String
$cshow :: GetBucketStatisticsResponse -> String
showsPrec :: Int -> GetBucketStatisticsResponse -> ShowS
$cshowsPrec :: Int -> GetBucketStatisticsResponse -> ShowS
Prelude.Show, forall x.
Rep GetBucketStatisticsResponse x -> GetBucketStatisticsResponse
forall x.
GetBucketStatisticsResponse -> Rep GetBucketStatisticsResponse x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cto :: forall x.
Rep GetBucketStatisticsResponse x -> GetBucketStatisticsResponse
$cfrom :: forall x.
GetBucketStatisticsResponse -> Rep GetBucketStatisticsResponse x
Prelude.Generic)

-- |
-- Create a value of 'GetBucketStatisticsResponse' 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:
--
-- 'bucketCount', 'getBucketStatisticsResponse_bucketCount' - The total number of buckets.
--
-- 'bucketCountByEffectivePermission', 'getBucketStatisticsResponse_bucketCountByEffectivePermission' - The total number of buckets that are publicly accessible based on a
-- combination of permissions settings for each bucket.
--
-- 'bucketCountByEncryptionType', 'getBucketStatisticsResponse_bucketCountByEncryptionType' - The total number of buckets that use certain types of server-side
-- encryption to encrypt new objects by default. This object also reports
-- the total number of buckets that don\'t encrypt new objects by default.
--
-- 'bucketCountByObjectEncryptionRequirement', 'getBucketStatisticsResponse_bucketCountByObjectEncryptionRequirement' - The total number of buckets whose bucket policies do or don\'t require
-- server-side encryption of objects when objects are uploaded to the
-- buckets.
--
-- 'bucketCountBySharedAccessType', 'getBucketStatisticsResponse_bucketCountBySharedAccessType' - The total number of buckets that are or aren\'t shared with another
-- Amazon Web Services account.
--
-- 'bucketStatisticsBySensitivity', 'getBucketStatisticsResponse_bucketStatisticsBySensitivity' - The aggregated sensitive data discovery statistics for the buckets. If
-- automated sensitive data discovery is currently disabled for your
-- account, the value for each statistic is 0.
--
-- 'classifiableObjectCount', 'getBucketStatisticsResponse_classifiableObjectCount' - The total number of objects that Amazon Macie can analyze in the
-- buckets. These objects use a supported storage class and have a file
-- name extension for a supported file or storage format.
--
-- 'classifiableSizeInBytes', 'getBucketStatisticsResponse_classifiableSizeInBytes' - The total storage size, in bytes, of all the objects that Amazon Macie
-- can analyze in the buckets. These objects use a supported storage class
-- and have a file name extension for a supported file or storage format.
--
-- If versioning is enabled for any of the buckets, this value is based on
-- the size of the latest version of each applicable object in the buckets.
-- This value doesn\'t reflect the storage size of all versions of all
-- applicable objects in the buckets.
--
-- 'lastUpdated', 'getBucketStatisticsResponse_lastUpdated' - The date and time, in UTC and extended ISO 8601 format, when Amazon
-- Macie most recently retrieved both bucket and object metadata from
-- Amazon S3 for the buckets.
--
-- 'objectCount', 'getBucketStatisticsResponse_objectCount' - The total number of objects in the buckets.
--
-- 'sizeInBytes', 'getBucketStatisticsResponse_sizeInBytes' - The total storage size, in bytes, of the buckets.
--
-- If versioning is enabled for any of the buckets, this value is based on
-- the size of the latest version of each object in the buckets. This value
-- doesn\'t reflect the storage size of all versions of the objects in the
-- buckets.
--
-- 'sizeInBytesCompressed', 'getBucketStatisticsResponse_sizeInBytesCompressed' - The total storage size, in bytes, of the objects that are compressed
-- (.gz, .gzip, .zip) files in the buckets.
--
-- If versioning is enabled for any of the buckets, this value is based on
-- the size of the latest version of each applicable object in the buckets.
-- This value doesn\'t reflect the storage size of all versions of the
-- applicable objects in the buckets.
--
-- 'unclassifiableObjectCount', 'getBucketStatisticsResponse_unclassifiableObjectCount' - The total number of objects that Amazon Macie can\'t analyze in the
-- buckets. These objects don\'t use a supported storage class or don\'t
-- have a file name extension for a supported file or storage format.
--
-- 'unclassifiableObjectSizeInBytes', 'getBucketStatisticsResponse_unclassifiableObjectSizeInBytes' - The total storage size, in bytes, of the objects that Amazon Macie
-- can\'t analyze in the buckets. These objects don\'t use a supported
-- storage class or don\'t have a file name extension for a supported file
-- or storage format.
--
-- 'httpStatus', 'getBucketStatisticsResponse_httpStatus' - The response's http status code.
newGetBucketStatisticsResponse ::
  -- | 'httpStatus'
  Prelude.Int ->
  GetBucketStatisticsResponse
newGetBucketStatisticsResponse :: Int -> GetBucketStatisticsResponse
newGetBucketStatisticsResponse Int
pHttpStatus_ =
  GetBucketStatisticsResponse'
    { $sel:bucketCount:GetBucketStatisticsResponse' :: Maybe Integer
bucketCount =
        forall a. Maybe a
Prelude.Nothing,
      $sel:bucketCountByEffectivePermission:GetBucketStatisticsResponse' :: Maybe BucketCountByEffectivePermission
bucketCountByEffectivePermission =
        forall a. Maybe a
Prelude.Nothing,
      $sel:bucketCountByEncryptionType:GetBucketStatisticsResponse' :: Maybe BucketCountByEncryptionType
bucketCountByEncryptionType = forall a. Maybe a
Prelude.Nothing,
      $sel:bucketCountByObjectEncryptionRequirement:GetBucketStatisticsResponse' :: Maybe BucketCountPolicyAllowsUnencryptedObjectUploads
bucketCountByObjectEncryptionRequirement =
        forall a. Maybe a
Prelude.Nothing,
      $sel:bucketCountBySharedAccessType:GetBucketStatisticsResponse' :: Maybe BucketCountBySharedAccessType
bucketCountBySharedAccessType =
        forall a. Maybe a
Prelude.Nothing,
      $sel:bucketStatisticsBySensitivity:GetBucketStatisticsResponse' :: Maybe BucketStatisticsBySensitivity
bucketStatisticsBySensitivity =
        forall a. Maybe a
Prelude.Nothing,
      $sel:classifiableObjectCount:GetBucketStatisticsResponse' :: Maybe Integer
classifiableObjectCount = forall a. Maybe a
Prelude.Nothing,
      $sel:classifiableSizeInBytes:GetBucketStatisticsResponse' :: Maybe Integer
classifiableSizeInBytes = forall a. Maybe a
Prelude.Nothing,
      $sel:lastUpdated:GetBucketStatisticsResponse' :: Maybe ISO8601
lastUpdated = forall a. Maybe a
Prelude.Nothing,
      $sel:objectCount:GetBucketStatisticsResponse' :: Maybe Integer
objectCount = forall a. Maybe a
Prelude.Nothing,
      $sel:sizeInBytes:GetBucketStatisticsResponse' :: Maybe Integer
sizeInBytes = forall a. Maybe a
Prelude.Nothing,
      $sel:sizeInBytesCompressed:GetBucketStatisticsResponse' :: Maybe Integer
sizeInBytesCompressed = forall a. Maybe a
Prelude.Nothing,
      $sel:unclassifiableObjectCount:GetBucketStatisticsResponse' :: Maybe ObjectLevelStatistics
unclassifiableObjectCount = forall a. Maybe a
Prelude.Nothing,
      $sel:unclassifiableObjectSizeInBytes:GetBucketStatisticsResponse' :: Maybe ObjectLevelStatistics
unclassifiableObjectSizeInBytes =
        forall a. Maybe a
Prelude.Nothing,
      $sel:httpStatus:GetBucketStatisticsResponse' :: Int
httpStatus = Int
pHttpStatus_
    }

-- | The total number of buckets.
getBucketStatisticsResponse_bucketCount :: Lens.Lens' GetBucketStatisticsResponse (Prelude.Maybe Prelude.Integer)
getBucketStatisticsResponse_bucketCount :: Lens' GetBucketStatisticsResponse (Maybe Integer)
getBucketStatisticsResponse_bucketCount = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\GetBucketStatisticsResponse' {Maybe Integer
bucketCount :: Maybe Integer
$sel:bucketCount:GetBucketStatisticsResponse' :: GetBucketStatisticsResponse -> Maybe Integer
bucketCount} -> Maybe Integer
bucketCount) (\s :: GetBucketStatisticsResponse
s@GetBucketStatisticsResponse' {} Maybe Integer
a -> GetBucketStatisticsResponse
s {$sel:bucketCount:GetBucketStatisticsResponse' :: Maybe Integer
bucketCount = Maybe Integer
a} :: GetBucketStatisticsResponse)

-- | The total number of buckets that are publicly accessible based on a
-- combination of permissions settings for each bucket.
getBucketStatisticsResponse_bucketCountByEffectivePermission :: Lens.Lens' GetBucketStatisticsResponse (Prelude.Maybe BucketCountByEffectivePermission)
getBucketStatisticsResponse_bucketCountByEffectivePermission :: Lens'
  GetBucketStatisticsResponse
  (Maybe BucketCountByEffectivePermission)
getBucketStatisticsResponse_bucketCountByEffectivePermission = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\GetBucketStatisticsResponse' {Maybe BucketCountByEffectivePermission
bucketCountByEffectivePermission :: Maybe BucketCountByEffectivePermission
$sel:bucketCountByEffectivePermission:GetBucketStatisticsResponse' :: GetBucketStatisticsResponse
-> Maybe BucketCountByEffectivePermission
bucketCountByEffectivePermission} -> Maybe BucketCountByEffectivePermission
bucketCountByEffectivePermission) (\s :: GetBucketStatisticsResponse
s@GetBucketStatisticsResponse' {} Maybe BucketCountByEffectivePermission
a -> GetBucketStatisticsResponse
s {$sel:bucketCountByEffectivePermission:GetBucketStatisticsResponse' :: Maybe BucketCountByEffectivePermission
bucketCountByEffectivePermission = Maybe BucketCountByEffectivePermission
a} :: GetBucketStatisticsResponse)

-- | The total number of buckets that use certain types of server-side
-- encryption to encrypt new objects by default. This object also reports
-- the total number of buckets that don\'t encrypt new objects by default.
getBucketStatisticsResponse_bucketCountByEncryptionType :: Lens.Lens' GetBucketStatisticsResponse (Prelude.Maybe BucketCountByEncryptionType)
getBucketStatisticsResponse_bucketCountByEncryptionType :: Lens'
  GetBucketStatisticsResponse (Maybe BucketCountByEncryptionType)
getBucketStatisticsResponse_bucketCountByEncryptionType = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\GetBucketStatisticsResponse' {Maybe BucketCountByEncryptionType
bucketCountByEncryptionType :: Maybe BucketCountByEncryptionType
$sel:bucketCountByEncryptionType:GetBucketStatisticsResponse' :: GetBucketStatisticsResponse -> Maybe BucketCountByEncryptionType
bucketCountByEncryptionType} -> Maybe BucketCountByEncryptionType
bucketCountByEncryptionType) (\s :: GetBucketStatisticsResponse
s@GetBucketStatisticsResponse' {} Maybe BucketCountByEncryptionType
a -> GetBucketStatisticsResponse
s {$sel:bucketCountByEncryptionType:GetBucketStatisticsResponse' :: Maybe BucketCountByEncryptionType
bucketCountByEncryptionType = Maybe BucketCountByEncryptionType
a} :: GetBucketStatisticsResponse)

-- | The total number of buckets whose bucket policies do or don\'t require
-- server-side encryption of objects when objects are uploaded to the
-- buckets.
getBucketStatisticsResponse_bucketCountByObjectEncryptionRequirement :: Lens.Lens' GetBucketStatisticsResponse (Prelude.Maybe BucketCountPolicyAllowsUnencryptedObjectUploads)
getBucketStatisticsResponse_bucketCountByObjectEncryptionRequirement :: Lens'
  GetBucketStatisticsResponse
  (Maybe BucketCountPolicyAllowsUnencryptedObjectUploads)
getBucketStatisticsResponse_bucketCountByObjectEncryptionRequirement = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\GetBucketStatisticsResponse' {Maybe BucketCountPolicyAllowsUnencryptedObjectUploads
bucketCountByObjectEncryptionRequirement :: Maybe BucketCountPolicyAllowsUnencryptedObjectUploads
$sel:bucketCountByObjectEncryptionRequirement:GetBucketStatisticsResponse' :: GetBucketStatisticsResponse
-> Maybe BucketCountPolicyAllowsUnencryptedObjectUploads
bucketCountByObjectEncryptionRequirement} -> Maybe BucketCountPolicyAllowsUnencryptedObjectUploads
bucketCountByObjectEncryptionRequirement) (\s :: GetBucketStatisticsResponse
s@GetBucketStatisticsResponse' {} Maybe BucketCountPolicyAllowsUnencryptedObjectUploads
a -> GetBucketStatisticsResponse
s {$sel:bucketCountByObjectEncryptionRequirement:GetBucketStatisticsResponse' :: Maybe BucketCountPolicyAllowsUnencryptedObjectUploads
bucketCountByObjectEncryptionRequirement = Maybe BucketCountPolicyAllowsUnencryptedObjectUploads
a} :: GetBucketStatisticsResponse)

-- | The total number of buckets that are or aren\'t shared with another
-- Amazon Web Services account.
getBucketStatisticsResponse_bucketCountBySharedAccessType :: Lens.Lens' GetBucketStatisticsResponse (Prelude.Maybe BucketCountBySharedAccessType)
getBucketStatisticsResponse_bucketCountBySharedAccessType :: Lens'
  GetBucketStatisticsResponse (Maybe BucketCountBySharedAccessType)
getBucketStatisticsResponse_bucketCountBySharedAccessType = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\GetBucketStatisticsResponse' {Maybe BucketCountBySharedAccessType
bucketCountBySharedAccessType :: Maybe BucketCountBySharedAccessType
$sel:bucketCountBySharedAccessType:GetBucketStatisticsResponse' :: GetBucketStatisticsResponse -> Maybe BucketCountBySharedAccessType
bucketCountBySharedAccessType} -> Maybe BucketCountBySharedAccessType
bucketCountBySharedAccessType) (\s :: GetBucketStatisticsResponse
s@GetBucketStatisticsResponse' {} Maybe BucketCountBySharedAccessType
a -> GetBucketStatisticsResponse
s {$sel:bucketCountBySharedAccessType:GetBucketStatisticsResponse' :: Maybe BucketCountBySharedAccessType
bucketCountBySharedAccessType = Maybe BucketCountBySharedAccessType
a} :: GetBucketStatisticsResponse)

-- | The aggregated sensitive data discovery statistics for the buckets. If
-- automated sensitive data discovery is currently disabled for your
-- account, the value for each statistic is 0.
getBucketStatisticsResponse_bucketStatisticsBySensitivity :: Lens.Lens' GetBucketStatisticsResponse (Prelude.Maybe BucketStatisticsBySensitivity)
getBucketStatisticsResponse_bucketStatisticsBySensitivity :: Lens'
  GetBucketStatisticsResponse (Maybe BucketStatisticsBySensitivity)
getBucketStatisticsResponse_bucketStatisticsBySensitivity = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\GetBucketStatisticsResponse' {Maybe BucketStatisticsBySensitivity
bucketStatisticsBySensitivity :: Maybe BucketStatisticsBySensitivity
$sel:bucketStatisticsBySensitivity:GetBucketStatisticsResponse' :: GetBucketStatisticsResponse -> Maybe BucketStatisticsBySensitivity
bucketStatisticsBySensitivity} -> Maybe BucketStatisticsBySensitivity
bucketStatisticsBySensitivity) (\s :: GetBucketStatisticsResponse
s@GetBucketStatisticsResponse' {} Maybe BucketStatisticsBySensitivity
a -> GetBucketStatisticsResponse
s {$sel:bucketStatisticsBySensitivity:GetBucketStatisticsResponse' :: Maybe BucketStatisticsBySensitivity
bucketStatisticsBySensitivity = Maybe BucketStatisticsBySensitivity
a} :: GetBucketStatisticsResponse)

-- | The total number of objects that Amazon Macie can analyze in the
-- buckets. These objects use a supported storage class and have a file
-- name extension for a supported file or storage format.
getBucketStatisticsResponse_classifiableObjectCount :: Lens.Lens' GetBucketStatisticsResponse (Prelude.Maybe Prelude.Integer)
getBucketStatisticsResponse_classifiableObjectCount :: Lens' GetBucketStatisticsResponse (Maybe Integer)
getBucketStatisticsResponse_classifiableObjectCount = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\GetBucketStatisticsResponse' {Maybe Integer
classifiableObjectCount :: Maybe Integer
$sel:classifiableObjectCount:GetBucketStatisticsResponse' :: GetBucketStatisticsResponse -> Maybe Integer
classifiableObjectCount} -> Maybe Integer
classifiableObjectCount) (\s :: GetBucketStatisticsResponse
s@GetBucketStatisticsResponse' {} Maybe Integer
a -> GetBucketStatisticsResponse
s {$sel:classifiableObjectCount:GetBucketStatisticsResponse' :: Maybe Integer
classifiableObjectCount = Maybe Integer
a} :: GetBucketStatisticsResponse)

-- | The total storage size, in bytes, of all the objects that Amazon Macie
-- can analyze in the buckets. These objects use a supported storage class
-- and have a file name extension for a supported file or storage format.
--
-- If versioning is enabled for any of the buckets, this value is based on
-- the size of the latest version of each applicable object in the buckets.
-- This value doesn\'t reflect the storage size of all versions of all
-- applicable objects in the buckets.
getBucketStatisticsResponse_classifiableSizeInBytes :: Lens.Lens' GetBucketStatisticsResponse (Prelude.Maybe Prelude.Integer)
getBucketStatisticsResponse_classifiableSizeInBytes :: Lens' GetBucketStatisticsResponse (Maybe Integer)
getBucketStatisticsResponse_classifiableSizeInBytes = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\GetBucketStatisticsResponse' {Maybe Integer
classifiableSizeInBytes :: Maybe Integer
$sel:classifiableSizeInBytes:GetBucketStatisticsResponse' :: GetBucketStatisticsResponse -> Maybe Integer
classifiableSizeInBytes} -> Maybe Integer
classifiableSizeInBytes) (\s :: GetBucketStatisticsResponse
s@GetBucketStatisticsResponse' {} Maybe Integer
a -> GetBucketStatisticsResponse
s {$sel:classifiableSizeInBytes:GetBucketStatisticsResponse' :: Maybe Integer
classifiableSizeInBytes = Maybe Integer
a} :: GetBucketStatisticsResponse)

-- | The date and time, in UTC and extended ISO 8601 format, when Amazon
-- Macie most recently retrieved both bucket and object metadata from
-- Amazon S3 for the buckets.
getBucketStatisticsResponse_lastUpdated :: Lens.Lens' GetBucketStatisticsResponse (Prelude.Maybe Prelude.UTCTime)
getBucketStatisticsResponse_lastUpdated :: Lens' GetBucketStatisticsResponse (Maybe UTCTime)
getBucketStatisticsResponse_lastUpdated = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\GetBucketStatisticsResponse' {Maybe ISO8601
lastUpdated :: Maybe ISO8601
$sel:lastUpdated:GetBucketStatisticsResponse' :: GetBucketStatisticsResponse -> Maybe ISO8601
lastUpdated} -> Maybe ISO8601
lastUpdated) (\s :: GetBucketStatisticsResponse
s@GetBucketStatisticsResponse' {} Maybe ISO8601
a -> GetBucketStatisticsResponse
s {$sel:lastUpdated:GetBucketStatisticsResponse' :: Maybe ISO8601
lastUpdated = Maybe ISO8601
a} :: GetBucketStatisticsResponse) 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 (a :: Format). Iso' (Time a) UTCTime
Data._Time

-- | The total number of objects in the buckets.
getBucketStatisticsResponse_objectCount :: Lens.Lens' GetBucketStatisticsResponse (Prelude.Maybe Prelude.Integer)
getBucketStatisticsResponse_objectCount :: Lens' GetBucketStatisticsResponse (Maybe Integer)
getBucketStatisticsResponse_objectCount = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\GetBucketStatisticsResponse' {Maybe Integer
objectCount :: Maybe Integer
$sel:objectCount:GetBucketStatisticsResponse' :: GetBucketStatisticsResponse -> Maybe Integer
objectCount} -> Maybe Integer
objectCount) (\s :: GetBucketStatisticsResponse
s@GetBucketStatisticsResponse' {} Maybe Integer
a -> GetBucketStatisticsResponse
s {$sel:objectCount:GetBucketStatisticsResponse' :: Maybe Integer
objectCount = Maybe Integer
a} :: GetBucketStatisticsResponse)

-- | The total storage size, in bytes, of the buckets.
--
-- If versioning is enabled for any of the buckets, this value is based on
-- the size of the latest version of each object in the buckets. This value
-- doesn\'t reflect the storage size of all versions of the objects in the
-- buckets.
getBucketStatisticsResponse_sizeInBytes :: Lens.Lens' GetBucketStatisticsResponse (Prelude.Maybe Prelude.Integer)
getBucketStatisticsResponse_sizeInBytes :: Lens' GetBucketStatisticsResponse (Maybe Integer)
getBucketStatisticsResponse_sizeInBytes = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\GetBucketStatisticsResponse' {Maybe Integer
sizeInBytes :: Maybe Integer
$sel:sizeInBytes:GetBucketStatisticsResponse' :: GetBucketStatisticsResponse -> Maybe Integer
sizeInBytes} -> Maybe Integer
sizeInBytes) (\s :: GetBucketStatisticsResponse
s@GetBucketStatisticsResponse' {} Maybe Integer
a -> GetBucketStatisticsResponse
s {$sel:sizeInBytes:GetBucketStatisticsResponse' :: Maybe Integer
sizeInBytes = Maybe Integer
a} :: GetBucketStatisticsResponse)

-- | The total storage size, in bytes, of the objects that are compressed
-- (.gz, .gzip, .zip) files in the buckets.
--
-- If versioning is enabled for any of the buckets, this value is based on
-- the size of the latest version of each applicable object in the buckets.
-- This value doesn\'t reflect the storage size of all versions of the
-- applicable objects in the buckets.
getBucketStatisticsResponse_sizeInBytesCompressed :: Lens.Lens' GetBucketStatisticsResponse (Prelude.Maybe Prelude.Integer)
getBucketStatisticsResponse_sizeInBytesCompressed :: Lens' GetBucketStatisticsResponse (Maybe Integer)
getBucketStatisticsResponse_sizeInBytesCompressed = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\GetBucketStatisticsResponse' {Maybe Integer
sizeInBytesCompressed :: Maybe Integer
$sel:sizeInBytesCompressed:GetBucketStatisticsResponse' :: GetBucketStatisticsResponse -> Maybe Integer
sizeInBytesCompressed} -> Maybe Integer
sizeInBytesCompressed) (\s :: GetBucketStatisticsResponse
s@GetBucketStatisticsResponse' {} Maybe Integer
a -> GetBucketStatisticsResponse
s {$sel:sizeInBytesCompressed:GetBucketStatisticsResponse' :: Maybe Integer
sizeInBytesCompressed = Maybe Integer
a} :: GetBucketStatisticsResponse)

-- | The total number of objects that Amazon Macie can\'t analyze in the
-- buckets. These objects don\'t use a supported storage class or don\'t
-- have a file name extension for a supported file or storage format.
getBucketStatisticsResponse_unclassifiableObjectCount :: Lens.Lens' GetBucketStatisticsResponse (Prelude.Maybe ObjectLevelStatistics)
getBucketStatisticsResponse_unclassifiableObjectCount :: Lens' GetBucketStatisticsResponse (Maybe ObjectLevelStatistics)
getBucketStatisticsResponse_unclassifiableObjectCount = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\GetBucketStatisticsResponse' {Maybe ObjectLevelStatistics
unclassifiableObjectCount :: Maybe ObjectLevelStatistics
$sel:unclassifiableObjectCount:GetBucketStatisticsResponse' :: GetBucketStatisticsResponse -> Maybe ObjectLevelStatistics
unclassifiableObjectCount} -> Maybe ObjectLevelStatistics
unclassifiableObjectCount) (\s :: GetBucketStatisticsResponse
s@GetBucketStatisticsResponse' {} Maybe ObjectLevelStatistics
a -> GetBucketStatisticsResponse
s {$sel:unclassifiableObjectCount:GetBucketStatisticsResponse' :: Maybe ObjectLevelStatistics
unclassifiableObjectCount = Maybe ObjectLevelStatistics
a} :: GetBucketStatisticsResponse)

-- | The total storage size, in bytes, of the objects that Amazon Macie
-- can\'t analyze in the buckets. These objects don\'t use a supported
-- storage class or don\'t have a file name extension for a supported file
-- or storage format.
getBucketStatisticsResponse_unclassifiableObjectSizeInBytes :: Lens.Lens' GetBucketStatisticsResponse (Prelude.Maybe ObjectLevelStatistics)
getBucketStatisticsResponse_unclassifiableObjectSizeInBytes :: Lens' GetBucketStatisticsResponse (Maybe ObjectLevelStatistics)
getBucketStatisticsResponse_unclassifiableObjectSizeInBytes = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\GetBucketStatisticsResponse' {Maybe ObjectLevelStatistics
unclassifiableObjectSizeInBytes :: Maybe ObjectLevelStatistics
$sel:unclassifiableObjectSizeInBytes:GetBucketStatisticsResponse' :: GetBucketStatisticsResponse -> Maybe ObjectLevelStatistics
unclassifiableObjectSizeInBytes} -> Maybe ObjectLevelStatistics
unclassifiableObjectSizeInBytes) (\s :: GetBucketStatisticsResponse
s@GetBucketStatisticsResponse' {} Maybe ObjectLevelStatistics
a -> GetBucketStatisticsResponse
s {$sel:unclassifiableObjectSizeInBytes:GetBucketStatisticsResponse' :: Maybe ObjectLevelStatistics
unclassifiableObjectSizeInBytes = Maybe ObjectLevelStatistics
a} :: GetBucketStatisticsResponse)

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

instance Prelude.NFData GetBucketStatisticsResponse where
  rnf :: GetBucketStatisticsResponse -> ()
rnf GetBucketStatisticsResponse' {Int
Maybe Integer
Maybe ISO8601
Maybe BucketCountByEffectivePermission
Maybe BucketCountByEncryptionType
Maybe BucketCountBySharedAccessType
Maybe BucketCountPolicyAllowsUnencryptedObjectUploads
Maybe ObjectLevelStatistics
Maybe BucketStatisticsBySensitivity
httpStatus :: Int
unclassifiableObjectSizeInBytes :: Maybe ObjectLevelStatistics
unclassifiableObjectCount :: Maybe ObjectLevelStatistics
sizeInBytesCompressed :: Maybe Integer
sizeInBytes :: Maybe Integer
objectCount :: Maybe Integer
lastUpdated :: Maybe ISO8601
classifiableSizeInBytes :: Maybe Integer
classifiableObjectCount :: Maybe Integer
bucketStatisticsBySensitivity :: Maybe BucketStatisticsBySensitivity
bucketCountBySharedAccessType :: Maybe BucketCountBySharedAccessType
bucketCountByObjectEncryptionRequirement :: Maybe BucketCountPolicyAllowsUnencryptedObjectUploads
bucketCountByEncryptionType :: Maybe BucketCountByEncryptionType
bucketCountByEffectivePermission :: Maybe BucketCountByEffectivePermission
bucketCount :: Maybe Integer
$sel:httpStatus:GetBucketStatisticsResponse' :: GetBucketStatisticsResponse -> Int
$sel:unclassifiableObjectSizeInBytes:GetBucketStatisticsResponse' :: GetBucketStatisticsResponse -> Maybe ObjectLevelStatistics
$sel:unclassifiableObjectCount:GetBucketStatisticsResponse' :: GetBucketStatisticsResponse -> Maybe ObjectLevelStatistics
$sel:sizeInBytesCompressed:GetBucketStatisticsResponse' :: GetBucketStatisticsResponse -> Maybe Integer
$sel:sizeInBytes:GetBucketStatisticsResponse' :: GetBucketStatisticsResponse -> Maybe Integer
$sel:objectCount:GetBucketStatisticsResponse' :: GetBucketStatisticsResponse -> Maybe Integer
$sel:lastUpdated:GetBucketStatisticsResponse' :: GetBucketStatisticsResponse -> Maybe ISO8601
$sel:classifiableSizeInBytes:GetBucketStatisticsResponse' :: GetBucketStatisticsResponse -> Maybe Integer
$sel:classifiableObjectCount:GetBucketStatisticsResponse' :: GetBucketStatisticsResponse -> Maybe Integer
$sel:bucketStatisticsBySensitivity:GetBucketStatisticsResponse' :: GetBucketStatisticsResponse -> Maybe BucketStatisticsBySensitivity
$sel:bucketCountBySharedAccessType:GetBucketStatisticsResponse' :: GetBucketStatisticsResponse -> Maybe BucketCountBySharedAccessType
$sel:bucketCountByObjectEncryptionRequirement:GetBucketStatisticsResponse' :: GetBucketStatisticsResponse
-> Maybe BucketCountPolicyAllowsUnencryptedObjectUploads
$sel:bucketCountByEncryptionType:GetBucketStatisticsResponse' :: GetBucketStatisticsResponse -> Maybe BucketCountByEncryptionType
$sel:bucketCountByEffectivePermission:GetBucketStatisticsResponse' :: GetBucketStatisticsResponse
-> Maybe BucketCountByEffectivePermission
$sel:bucketCount:GetBucketStatisticsResponse' :: GetBucketStatisticsResponse -> Maybe Integer
..} =
    forall a. NFData a => a -> ()
Prelude.rnf Maybe Integer
bucketCount
      seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf Maybe BucketCountByEffectivePermission
bucketCountByEffectivePermission
      seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf Maybe BucketCountByEncryptionType
bucketCountByEncryptionType
      seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf Maybe BucketCountPolicyAllowsUnencryptedObjectUploads
bucketCountByObjectEncryptionRequirement
      seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf Maybe BucketCountBySharedAccessType
bucketCountBySharedAccessType
      seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf Maybe BucketStatisticsBySensitivity
bucketStatisticsBySensitivity
      seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf Maybe Integer
classifiableObjectCount
      seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf Maybe Integer
classifiableSizeInBytes
      seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf Maybe ISO8601
lastUpdated
      seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf Maybe Integer
objectCount
      seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf Maybe Integer
sizeInBytes
      seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf Maybe Integer
sizeInBytesCompressed
      seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf Maybe ObjectLevelStatistics
unclassifiableObjectCount
      seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf
        Maybe ObjectLevelStatistics
unclassifiableObjectSizeInBytes
      seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf Int
httpStatus