{-# 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.GetResourceProfile
-- 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) sensitive data discovery statistics and the
-- sensitivity score for an S3 bucket.
module Amazonka.MacieV2.GetResourceProfile
  ( -- * Creating a Request
    GetResourceProfile (..),
    newGetResourceProfile,

    -- * Request Lenses
    getResourceProfile_resourceArn,

    -- * Destructuring the Response
    GetResourceProfileResponse (..),
    newGetResourceProfileResponse,

    -- * Response Lenses
    getResourceProfileResponse_profileUpdatedAt,
    getResourceProfileResponse_sensitivityScore,
    getResourceProfileResponse_sensitivityScoreOverridden,
    getResourceProfileResponse_statistics,
    getResourceProfileResponse_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:/ 'newGetResourceProfile' smart constructor.
data GetResourceProfile = GetResourceProfile'
  { -- | The Amazon Resource Name (ARN) of the S3 bucket that the request applies
    -- to.
    GetResourceProfile -> Text
resourceArn :: Prelude.Text
  }
  deriving (GetResourceProfile -> GetResourceProfile -> Bool
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: GetResourceProfile -> GetResourceProfile -> Bool
$c/= :: GetResourceProfile -> GetResourceProfile -> Bool
== :: GetResourceProfile -> GetResourceProfile -> Bool
$c== :: GetResourceProfile -> GetResourceProfile -> Bool
Prelude.Eq, ReadPrec [GetResourceProfile]
ReadPrec GetResourceProfile
Int -> ReadS GetResourceProfile
ReadS [GetResourceProfile]
forall a.
(Int -> ReadS a)
-> ReadS [a] -> ReadPrec a -> ReadPrec [a] -> Read a
readListPrec :: ReadPrec [GetResourceProfile]
$creadListPrec :: ReadPrec [GetResourceProfile]
readPrec :: ReadPrec GetResourceProfile
$creadPrec :: ReadPrec GetResourceProfile
readList :: ReadS [GetResourceProfile]
$creadList :: ReadS [GetResourceProfile]
readsPrec :: Int -> ReadS GetResourceProfile
$creadsPrec :: Int -> ReadS GetResourceProfile
Prelude.Read, Int -> GetResourceProfile -> ShowS
[GetResourceProfile] -> ShowS
GetResourceProfile -> String
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [GetResourceProfile] -> ShowS
$cshowList :: [GetResourceProfile] -> ShowS
show :: GetResourceProfile -> String
$cshow :: GetResourceProfile -> String
showsPrec :: Int -> GetResourceProfile -> ShowS
$cshowsPrec :: Int -> GetResourceProfile -> ShowS
Prelude.Show, forall x. Rep GetResourceProfile x -> GetResourceProfile
forall x. GetResourceProfile -> Rep GetResourceProfile x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cto :: forall x. Rep GetResourceProfile x -> GetResourceProfile
$cfrom :: forall x. GetResourceProfile -> Rep GetResourceProfile x
Prelude.Generic)

-- |
-- Create a value of 'GetResourceProfile' 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:
--
-- 'resourceArn', 'getResourceProfile_resourceArn' - The Amazon Resource Name (ARN) of the S3 bucket that the request applies
-- to.
newGetResourceProfile ::
  -- | 'resourceArn'
  Prelude.Text ->
  GetResourceProfile
newGetResourceProfile :: Text -> GetResourceProfile
newGetResourceProfile Text
pResourceArn_ =
  GetResourceProfile' {$sel:resourceArn:GetResourceProfile' :: Text
resourceArn = Text
pResourceArn_}

-- | The Amazon Resource Name (ARN) of the S3 bucket that the request applies
-- to.
getResourceProfile_resourceArn :: Lens.Lens' GetResourceProfile Prelude.Text
getResourceProfile_resourceArn :: Lens' GetResourceProfile Text
getResourceProfile_resourceArn = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\GetResourceProfile' {Text
resourceArn :: Text
$sel:resourceArn:GetResourceProfile' :: GetResourceProfile -> Text
resourceArn} -> Text
resourceArn) (\s :: GetResourceProfile
s@GetResourceProfile' {} Text
a -> GetResourceProfile
s {$sel:resourceArn:GetResourceProfile' :: Text
resourceArn = Text
a} :: GetResourceProfile)

instance Core.AWSRequest GetResourceProfile where
  type
    AWSResponse GetResourceProfile =
      GetResourceProfileResponse
  request :: (Service -> Service)
-> GetResourceProfile -> Request GetResourceProfile
request Service -> Service
overrides =
    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 GetResourceProfile
-> ClientResponse ClientBody
-> m (Either
        Error (ClientResponse (AWSResponse GetResourceProfile)))
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 ISO8601
-> Maybe Int
-> Maybe Bool
-> Maybe ResourceStatistics
-> Int
-> GetResourceProfileResponse
GetResourceProfileResponse'
            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
"profileUpdatedAt")
            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
"sensitivityScore")
            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
"sensitivityScoreOverridden")
            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
"statistics")
            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 GetResourceProfile where
  hashWithSalt :: Int -> GetResourceProfile -> Int
hashWithSalt Int
_salt GetResourceProfile' {Text
resourceArn :: Text
$sel:resourceArn:GetResourceProfile' :: GetResourceProfile -> Text
..} =
    Int
_salt forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Text
resourceArn

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

instance Data.ToHeaders GetResourceProfile where
  toHeaders :: GetResourceProfile -> 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.ToPath GetResourceProfile where
  toPath :: GetResourceProfile -> ByteString
toPath = forall a b. a -> b -> a
Prelude.const ByteString
"/resource-profiles"

instance Data.ToQuery GetResourceProfile where
  toQuery :: GetResourceProfile -> QueryString
toQuery GetResourceProfile' {Text
resourceArn :: Text
$sel:resourceArn:GetResourceProfile' :: GetResourceProfile -> Text
..} =
    forall a. Monoid a => [a] -> a
Prelude.mconcat [ByteString
"resourceArn" forall a. ToQuery a => ByteString -> a -> QueryString
Data.=: Text
resourceArn]

-- | /See:/ 'newGetResourceProfileResponse' smart constructor.
data GetResourceProfileResponse = GetResourceProfileResponse'
  { -- | The date and time, in UTC and extended ISO 8601 format, when Amazon
    -- Macie most recently recalculated sensitive data discovery statistics and
    -- details for the bucket. If the bucket\'s sensitivity score is calculated
    -- automatically, this includes the score.
    GetResourceProfileResponse -> Maybe ISO8601
profileUpdatedAt :: Prelude.Maybe Data.ISO8601,
    -- | The current sensitivity score for the bucket, ranging from -1 (no
    -- analysis due to an error) to 100 (sensitive). By default, this score is
    -- calculated automatically based on the amount of data that Amazon Macie
    -- has analyzed in the bucket and the amount of sensitive data that Macie
    -- has found in the bucket.
    GetResourceProfileResponse -> Maybe Int
sensitivityScore :: Prelude.Maybe Prelude.Int,
    -- | Specifies whether the bucket\'s current sensitivity score was set
    -- manually. If this value is true, the score was manually changed to 100.
    -- If this value is false, the score was calculated automatically by Amazon
    -- Macie.
    GetResourceProfileResponse -> Maybe Bool
sensitivityScoreOverridden :: Prelude.Maybe Prelude.Bool,
    -- | The sensitive data discovery statistics for the bucket. The statistics
    -- capture the results of automated sensitive data discovery activities
    -- that Amazon Macie has performed for the bucket.
    GetResourceProfileResponse -> Maybe ResourceStatistics
statistics :: Prelude.Maybe ResourceStatistics,
    -- | The response's http status code.
    GetResourceProfileResponse -> Int
httpStatus :: Prelude.Int
  }
  deriving (GetResourceProfileResponse -> GetResourceProfileResponse -> Bool
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: GetResourceProfileResponse -> GetResourceProfileResponse -> Bool
$c/= :: GetResourceProfileResponse -> GetResourceProfileResponse -> Bool
== :: GetResourceProfileResponse -> GetResourceProfileResponse -> Bool
$c== :: GetResourceProfileResponse -> GetResourceProfileResponse -> Bool
Prelude.Eq, ReadPrec [GetResourceProfileResponse]
ReadPrec GetResourceProfileResponse
Int -> ReadS GetResourceProfileResponse
ReadS [GetResourceProfileResponse]
forall a.
(Int -> ReadS a)
-> ReadS [a] -> ReadPrec a -> ReadPrec [a] -> Read a
readListPrec :: ReadPrec [GetResourceProfileResponse]
$creadListPrec :: ReadPrec [GetResourceProfileResponse]
readPrec :: ReadPrec GetResourceProfileResponse
$creadPrec :: ReadPrec GetResourceProfileResponse
readList :: ReadS [GetResourceProfileResponse]
$creadList :: ReadS [GetResourceProfileResponse]
readsPrec :: Int -> ReadS GetResourceProfileResponse
$creadsPrec :: Int -> ReadS GetResourceProfileResponse
Prelude.Read, Int -> GetResourceProfileResponse -> ShowS
[GetResourceProfileResponse] -> ShowS
GetResourceProfileResponse -> String
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [GetResourceProfileResponse] -> ShowS
$cshowList :: [GetResourceProfileResponse] -> ShowS
show :: GetResourceProfileResponse -> String
$cshow :: GetResourceProfileResponse -> String
showsPrec :: Int -> GetResourceProfileResponse -> ShowS
$cshowsPrec :: Int -> GetResourceProfileResponse -> ShowS
Prelude.Show, forall x.
Rep GetResourceProfileResponse x -> GetResourceProfileResponse
forall x.
GetResourceProfileResponse -> Rep GetResourceProfileResponse x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cto :: forall x.
Rep GetResourceProfileResponse x -> GetResourceProfileResponse
$cfrom :: forall x.
GetResourceProfileResponse -> Rep GetResourceProfileResponse x
Prelude.Generic)

-- |
-- Create a value of 'GetResourceProfileResponse' 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:
--
-- 'profileUpdatedAt', 'getResourceProfileResponse_profileUpdatedAt' - The date and time, in UTC and extended ISO 8601 format, when Amazon
-- Macie most recently recalculated sensitive data discovery statistics and
-- details for the bucket. If the bucket\'s sensitivity score is calculated
-- automatically, this includes the score.
--
-- 'sensitivityScore', 'getResourceProfileResponse_sensitivityScore' - The current sensitivity score for the bucket, ranging from -1 (no
-- analysis due to an error) to 100 (sensitive). By default, this score is
-- calculated automatically based on the amount of data that Amazon Macie
-- has analyzed in the bucket and the amount of sensitive data that Macie
-- has found in the bucket.
--
-- 'sensitivityScoreOverridden', 'getResourceProfileResponse_sensitivityScoreOverridden' - Specifies whether the bucket\'s current sensitivity score was set
-- manually. If this value is true, the score was manually changed to 100.
-- If this value is false, the score was calculated automatically by Amazon
-- Macie.
--
-- 'statistics', 'getResourceProfileResponse_statistics' - The sensitive data discovery statistics for the bucket. The statistics
-- capture the results of automated sensitive data discovery activities
-- that Amazon Macie has performed for the bucket.
--
-- 'httpStatus', 'getResourceProfileResponse_httpStatus' - The response's http status code.
newGetResourceProfileResponse ::
  -- | 'httpStatus'
  Prelude.Int ->
  GetResourceProfileResponse
newGetResourceProfileResponse :: Int -> GetResourceProfileResponse
newGetResourceProfileResponse Int
pHttpStatus_ =
  GetResourceProfileResponse'
    { $sel:profileUpdatedAt:GetResourceProfileResponse' :: Maybe ISO8601
profileUpdatedAt =
        forall a. Maybe a
Prelude.Nothing,
      $sel:sensitivityScore:GetResourceProfileResponse' :: Maybe Int
sensitivityScore = forall a. Maybe a
Prelude.Nothing,
      $sel:sensitivityScoreOverridden:GetResourceProfileResponse' :: Maybe Bool
sensitivityScoreOverridden = forall a. Maybe a
Prelude.Nothing,
      $sel:statistics:GetResourceProfileResponse' :: Maybe ResourceStatistics
statistics = forall a. Maybe a
Prelude.Nothing,
      $sel:httpStatus:GetResourceProfileResponse' :: Int
httpStatus = Int
pHttpStatus_
    }

-- | The date and time, in UTC and extended ISO 8601 format, when Amazon
-- Macie most recently recalculated sensitive data discovery statistics and
-- details for the bucket. If the bucket\'s sensitivity score is calculated
-- automatically, this includes the score.
getResourceProfileResponse_profileUpdatedAt :: Lens.Lens' GetResourceProfileResponse (Prelude.Maybe Prelude.UTCTime)
getResourceProfileResponse_profileUpdatedAt :: Lens' GetResourceProfileResponse (Maybe UTCTime)
getResourceProfileResponse_profileUpdatedAt = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\GetResourceProfileResponse' {Maybe ISO8601
profileUpdatedAt :: Maybe ISO8601
$sel:profileUpdatedAt:GetResourceProfileResponse' :: GetResourceProfileResponse -> Maybe ISO8601
profileUpdatedAt} -> Maybe ISO8601
profileUpdatedAt) (\s :: GetResourceProfileResponse
s@GetResourceProfileResponse' {} Maybe ISO8601
a -> GetResourceProfileResponse
s {$sel:profileUpdatedAt:GetResourceProfileResponse' :: Maybe ISO8601
profileUpdatedAt = Maybe ISO8601
a} :: GetResourceProfileResponse) 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 current sensitivity score for the bucket, ranging from -1 (no
-- analysis due to an error) to 100 (sensitive). By default, this score is
-- calculated automatically based on the amount of data that Amazon Macie
-- has analyzed in the bucket and the amount of sensitive data that Macie
-- has found in the bucket.
getResourceProfileResponse_sensitivityScore :: Lens.Lens' GetResourceProfileResponse (Prelude.Maybe Prelude.Int)
getResourceProfileResponse_sensitivityScore :: Lens' GetResourceProfileResponse (Maybe Int)
getResourceProfileResponse_sensitivityScore = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\GetResourceProfileResponse' {Maybe Int
sensitivityScore :: Maybe Int
$sel:sensitivityScore:GetResourceProfileResponse' :: GetResourceProfileResponse -> Maybe Int
sensitivityScore} -> Maybe Int
sensitivityScore) (\s :: GetResourceProfileResponse
s@GetResourceProfileResponse' {} Maybe Int
a -> GetResourceProfileResponse
s {$sel:sensitivityScore:GetResourceProfileResponse' :: Maybe Int
sensitivityScore = Maybe Int
a} :: GetResourceProfileResponse)

-- | Specifies whether the bucket\'s current sensitivity score was set
-- manually. If this value is true, the score was manually changed to 100.
-- If this value is false, the score was calculated automatically by Amazon
-- Macie.
getResourceProfileResponse_sensitivityScoreOverridden :: Lens.Lens' GetResourceProfileResponse (Prelude.Maybe Prelude.Bool)
getResourceProfileResponse_sensitivityScoreOverridden :: Lens' GetResourceProfileResponse (Maybe Bool)
getResourceProfileResponse_sensitivityScoreOverridden = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\GetResourceProfileResponse' {Maybe Bool
sensitivityScoreOverridden :: Maybe Bool
$sel:sensitivityScoreOverridden:GetResourceProfileResponse' :: GetResourceProfileResponse -> Maybe Bool
sensitivityScoreOverridden} -> Maybe Bool
sensitivityScoreOverridden) (\s :: GetResourceProfileResponse
s@GetResourceProfileResponse' {} Maybe Bool
a -> GetResourceProfileResponse
s {$sel:sensitivityScoreOverridden:GetResourceProfileResponse' :: Maybe Bool
sensitivityScoreOverridden = Maybe Bool
a} :: GetResourceProfileResponse)

-- | The sensitive data discovery statistics for the bucket. The statistics
-- capture the results of automated sensitive data discovery activities
-- that Amazon Macie has performed for the bucket.
getResourceProfileResponse_statistics :: Lens.Lens' GetResourceProfileResponse (Prelude.Maybe ResourceStatistics)
getResourceProfileResponse_statistics :: Lens' GetResourceProfileResponse (Maybe ResourceStatistics)
getResourceProfileResponse_statistics = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\GetResourceProfileResponse' {Maybe ResourceStatistics
statistics :: Maybe ResourceStatistics
$sel:statistics:GetResourceProfileResponse' :: GetResourceProfileResponse -> Maybe ResourceStatistics
statistics} -> Maybe ResourceStatistics
statistics) (\s :: GetResourceProfileResponse
s@GetResourceProfileResponse' {} Maybe ResourceStatistics
a -> GetResourceProfileResponse
s {$sel:statistics:GetResourceProfileResponse' :: Maybe ResourceStatistics
statistics = Maybe ResourceStatistics
a} :: GetResourceProfileResponse)

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

instance Prelude.NFData GetResourceProfileResponse where
  rnf :: GetResourceProfileResponse -> ()
rnf GetResourceProfileResponse' {Int
Maybe Bool
Maybe Int
Maybe ISO8601
Maybe ResourceStatistics
httpStatus :: Int
statistics :: Maybe ResourceStatistics
sensitivityScoreOverridden :: Maybe Bool
sensitivityScore :: Maybe Int
profileUpdatedAt :: Maybe ISO8601
$sel:httpStatus:GetResourceProfileResponse' :: GetResourceProfileResponse -> Int
$sel:statistics:GetResourceProfileResponse' :: GetResourceProfileResponse -> Maybe ResourceStatistics
$sel:sensitivityScoreOverridden:GetResourceProfileResponse' :: GetResourceProfileResponse -> Maybe Bool
$sel:sensitivityScore:GetResourceProfileResponse' :: GetResourceProfileResponse -> Maybe Int
$sel:profileUpdatedAt:GetResourceProfileResponse' :: GetResourceProfileResponse -> Maybe ISO8601
..} =
    forall a. NFData a => a -> ()
Prelude.rnf Maybe ISO8601
profileUpdatedAt
      seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf Maybe Int
sensitivityScore
      seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf Maybe Bool
sensitivityScoreOverridden
      seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf Maybe ResourceStatistics
statistics
      seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf Int
httpStatus