{-# 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.Inspector2.ListFindingAggregations
-- Copyright   : (c) 2013-2023 Brendan Hay
-- License     : Mozilla Public License, v. 2.0.
-- Maintainer  : Brendan Hay
-- Stability   : auto-generated
-- Portability : non-portable (GHC extensions)
--
-- Lists aggregated finding data for your environment based on specific
-- criteria.
--
-- This operation returns paginated results.
module Amazonka.Inspector2.ListFindingAggregations
  ( -- * Creating a Request
    ListFindingAggregations (..),
    newListFindingAggregations,

    -- * Request Lenses
    listFindingAggregations_accountIds,
    listFindingAggregations_aggregationRequest,
    listFindingAggregations_maxResults,
    listFindingAggregations_nextToken,
    listFindingAggregations_aggregationType,

    -- * Destructuring the Response
    ListFindingAggregationsResponse (..),
    newListFindingAggregationsResponse,

    -- * Response Lenses
    listFindingAggregationsResponse_nextToken,
    listFindingAggregationsResponse_responses,
    listFindingAggregationsResponse_httpStatus,
    listFindingAggregationsResponse_aggregationType,
  )
where

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

-- | /See:/ 'newListFindingAggregations' smart constructor.
data ListFindingAggregations = ListFindingAggregations'
  { -- | The Amazon Web Services account IDs to retrieve finding aggregation data
    -- for.
    ListFindingAggregations -> Maybe (NonEmpty StringFilter)
accountIds :: Prelude.Maybe (Prelude.NonEmpty StringFilter),
    -- | Details of the aggregation request that is used to filter your
    -- aggregation results.
    ListFindingAggregations -> Maybe AggregationRequest
aggregationRequest :: Prelude.Maybe AggregationRequest,
    -- | The maximum number of results to return in the response.
    ListFindingAggregations -> Maybe Natural
maxResults :: Prelude.Maybe Prelude.Natural,
    -- | A token to use for paginating results that are returned in the response.
    -- Set the value of this parameter to null for the first request to a list
    -- action. For subsequent calls, use the @NextToken@ value returned from
    -- the previous request to continue listing results after the first page.
    ListFindingAggregations -> Maybe Text
nextToken :: Prelude.Maybe Prelude.Text,
    -- | The type of the aggregation request.
    ListFindingAggregations -> AggregationType
aggregationType :: AggregationType
  }
  deriving (ListFindingAggregations -> ListFindingAggregations -> Bool
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: ListFindingAggregations -> ListFindingAggregations -> Bool
$c/= :: ListFindingAggregations -> ListFindingAggregations -> Bool
== :: ListFindingAggregations -> ListFindingAggregations -> Bool
$c== :: ListFindingAggregations -> ListFindingAggregations -> Bool
Prelude.Eq, ReadPrec [ListFindingAggregations]
ReadPrec ListFindingAggregations
Int -> ReadS ListFindingAggregations
ReadS [ListFindingAggregations]
forall a.
(Int -> ReadS a)
-> ReadS [a] -> ReadPrec a -> ReadPrec [a] -> Read a
readListPrec :: ReadPrec [ListFindingAggregations]
$creadListPrec :: ReadPrec [ListFindingAggregations]
readPrec :: ReadPrec ListFindingAggregations
$creadPrec :: ReadPrec ListFindingAggregations
readList :: ReadS [ListFindingAggregations]
$creadList :: ReadS [ListFindingAggregations]
readsPrec :: Int -> ReadS ListFindingAggregations
$creadsPrec :: Int -> ReadS ListFindingAggregations
Prelude.Read, Int -> ListFindingAggregations -> ShowS
[ListFindingAggregations] -> ShowS
ListFindingAggregations -> String
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [ListFindingAggregations] -> ShowS
$cshowList :: [ListFindingAggregations] -> ShowS
show :: ListFindingAggregations -> String
$cshow :: ListFindingAggregations -> String
showsPrec :: Int -> ListFindingAggregations -> ShowS
$cshowsPrec :: Int -> ListFindingAggregations -> ShowS
Prelude.Show, forall x. Rep ListFindingAggregations x -> ListFindingAggregations
forall x. ListFindingAggregations -> Rep ListFindingAggregations x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cto :: forall x. Rep ListFindingAggregations x -> ListFindingAggregations
$cfrom :: forall x. ListFindingAggregations -> Rep ListFindingAggregations x
Prelude.Generic)

-- |
-- Create a value of 'ListFindingAggregations' 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:
--
-- 'accountIds', 'listFindingAggregations_accountIds' - The Amazon Web Services account IDs to retrieve finding aggregation data
-- for.
--
-- 'aggregationRequest', 'listFindingAggregations_aggregationRequest' - Details of the aggregation request that is used to filter your
-- aggregation results.
--
-- 'maxResults', 'listFindingAggregations_maxResults' - The maximum number of results to return in the response.
--
-- 'nextToken', 'listFindingAggregations_nextToken' - A token to use for paginating results that are returned in the response.
-- Set the value of this parameter to null for the first request to a list
-- action. For subsequent calls, use the @NextToken@ value returned from
-- the previous request to continue listing results after the first page.
--
-- 'aggregationType', 'listFindingAggregations_aggregationType' - The type of the aggregation request.
newListFindingAggregations ::
  -- | 'aggregationType'
  AggregationType ->
  ListFindingAggregations
newListFindingAggregations :: AggregationType -> ListFindingAggregations
newListFindingAggregations AggregationType
pAggregationType_ =
  ListFindingAggregations'
    { $sel:accountIds:ListFindingAggregations' :: Maybe (NonEmpty StringFilter)
accountIds =
        forall a. Maybe a
Prelude.Nothing,
      $sel:aggregationRequest:ListFindingAggregations' :: Maybe AggregationRequest
aggregationRequest = forall a. Maybe a
Prelude.Nothing,
      $sel:maxResults:ListFindingAggregations' :: Maybe Natural
maxResults = forall a. Maybe a
Prelude.Nothing,
      $sel:nextToken:ListFindingAggregations' :: Maybe Text
nextToken = forall a. Maybe a
Prelude.Nothing,
      $sel:aggregationType:ListFindingAggregations' :: AggregationType
aggregationType = AggregationType
pAggregationType_
    }

-- | The Amazon Web Services account IDs to retrieve finding aggregation data
-- for.
listFindingAggregations_accountIds :: Lens.Lens' ListFindingAggregations (Prelude.Maybe (Prelude.NonEmpty StringFilter))
listFindingAggregations_accountIds :: Lens' ListFindingAggregations (Maybe (NonEmpty StringFilter))
listFindingAggregations_accountIds = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\ListFindingAggregations' {Maybe (NonEmpty StringFilter)
accountIds :: Maybe (NonEmpty StringFilter)
$sel:accountIds:ListFindingAggregations' :: ListFindingAggregations -> Maybe (NonEmpty StringFilter)
accountIds} -> Maybe (NonEmpty StringFilter)
accountIds) (\s :: ListFindingAggregations
s@ListFindingAggregations' {} Maybe (NonEmpty StringFilter)
a -> ListFindingAggregations
s {$sel:accountIds:ListFindingAggregations' :: Maybe (NonEmpty StringFilter)
accountIds = Maybe (NonEmpty StringFilter)
a} :: ListFindingAggregations) 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

-- | Details of the aggregation request that is used to filter your
-- aggregation results.
listFindingAggregations_aggregationRequest :: Lens.Lens' ListFindingAggregations (Prelude.Maybe AggregationRequest)
listFindingAggregations_aggregationRequest :: Lens' ListFindingAggregations (Maybe AggregationRequest)
listFindingAggregations_aggregationRequest = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\ListFindingAggregations' {Maybe AggregationRequest
aggregationRequest :: Maybe AggregationRequest
$sel:aggregationRequest:ListFindingAggregations' :: ListFindingAggregations -> Maybe AggregationRequest
aggregationRequest} -> Maybe AggregationRequest
aggregationRequest) (\s :: ListFindingAggregations
s@ListFindingAggregations' {} Maybe AggregationRequest
a -> ListFindingAggregations
s {$sel:aggregationRequest:ListFindingAggregations' :: Maybe AggregationRequest
aggregationRequest = Maybe AggregationRequest
a} :: ListFindingAggregations)

-- | The maximum number of results to return in the response.
listFindingAggregations_maxResults :: Lens.Lens' ListFindingAggregations (Prelude.Maybe Prelude.Natural)
listFindingAggregations_maxResults :: Lens' ListFindingAggregations (Maybe Natural)
listFindingAggregations_maxResults = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\ListFindingAggregations' {Maybe Natural
maxResults :: Maybe Natural
$sel:maxResults:ListFindingAggregations' :: ListFindingAggregations -> Maybe Natural
maxResults} -> Maybe Natural
maxResults) (\s :: ListFindingAggregations
s@ListFindingAggregations' {} Maybe Natural
a -> ListFindingAggregations
s {$sel:maxResults:ListFindingAggregations' :: Maybe Natural
maxResults = Maybe Natural
a} :: ListFindingAggregations)

-- | A token to use for paginating results that are returned in the response.
-- Set the value of this parameter to null for the first request to a list
-- action. For subsequent calls, use the @NextToken@ value returned from
-- the previous request to continue listing results after the first page.
listFindingAggregations_nextToken :: Lens.Lens' ListFindingAggregations (Prelude.Maybe Prelude.Text)
listFindingAggregations_nextToken :: Lens' ListFindingAggregations (Maybe Text)
listFindingAggregations_nextToken = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\ListFindingAggregations' {Maybe Text
nextToken :: Maybe Text
$sel:nextToken:ListFindingAggregations' :: ListFindingAggregations -> Maybe Text
nextToken} -> Maybe Text
nextToken) (\s :: ListFindingAggregations
s@ListFindingAggregations' {} Maybe Text
a -> ListFindingAggregations
s {$sel:nextToken:ListFindingAggregations' :: Maybe Text
nextToken = Maybe Text
a} :: ListFindingAggregations)

-- | The type of the aggregation request.
listFindingAggregations_aggregationType :: Lens.Lens' ListFindingAggregations AggregationType
listFindingAggregations_aggregationType :: Lens' ListFindingAggregations AggregationType
listFindingAggregations_aggregationType = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\ListFindingAggregations' {AggregationType
aggregationType :: AggregationType
$sel:aggregationType:ListFindingAggregations' :: ListFindingAggregations -> AggregationType
aggregationType} -> AggregationType
aggregationType) (\s :: ListFindingAggregations
s@ListFindingAggregations' {} AggregationType
a -> ListFindingAggregations
s {$sel:aggregationType:ListFindingAggregations' :: AggregationType
aggregationType = AggregationType
a} :: ListFindingAggregations)

instance Core.AWSPager ListFindingAggregations where
  page :: ListFindingAggregations
-> AWSResponse ListFindingAggregations
-> Maybe ListFindingAggregations
page ListFindingAggregations
rq AWSResponse ListFindingAggregations
rs
    | forall a. AWSTruncated a => a -> Bool
Core.stop
        ( AWSResponse ListFindingAggregations
rs
            forall s a. s -> Getting (First a) s a -> Maybe a
Lens.^? Lens' ListFindingAggregationsResponse (Maybe Text)
listFindingAggregationsResponse_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 ListFindingAggregations
rs
            forall s a. s -> Getting (First a) s a -> Maybe a
Lens.^? Lens' ListFindingAggregationsResponse (Maybe [AggregationResponse])
listFindingAggregationsResponse_responses
            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.$ ListFindingAggregations
rq
          forall a b. a -> (a -> b) -> b
Prelude.& Lens' ListFindingAggregations (Maybe Text)
listFindingAggregations_nextToken
          forall s t a b. ASetter s t a b -> b -> s -> t
Lens..~ AWSResponse ListFindingAggregations
rs
          forall s a. s -> Getting (First a) s a -> Maybe a
Lens.^? Lens' ListFindingAggregationsResponse (Maybe Text)
listFindingAggregationsResponse_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 ListFindingAggregations where
  type
    AWSResponse ListFindingAggregations =
      ListFindingAggregationsResponse
  request :: (Service -> Service)
-> ListFindingAggregations -> Request ListFindingAggregations
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 ListFindingAggregations
-> ClientResponse ClientBody
-> m (Either
        Error (ClientResponse (AWSResponse ListFindingAggregations)))
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 [AggregationResponse]
-> Int
-> AggregationType
-> ListFindingAggregationsResponse
ListFindingAggregationsResponse'
            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
"responses" 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))
            forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
Prelude.<*> (Object
x forall a. FromJSON a => Object -> Key -> Either String a
Data..:> Key
"aggregationType")
      )

instance Prelude.Hashable ListFindingAggregations where
  hashWithSalt :: Int -> ListFindingAggregations -> Int
hashWithSalt Int
_salt ListFindingAggregations' {Maybe Natural
Maybe (NonEmpty StringFilter)
Maybe Text
Maybe AggregationRequest
AggregationType
aggregationType :: AggregationType
nextToken :: Maybe Text
maxResults :: Maybe Natural
aggregationRequest :: Maybe AggregationRequest
accountIds :: Maybe (NonEmpty StringFilter)
$sel:aggregationType:ListFindingAggregations' :: ListFindingAggregations -> AggregationType
$sel:nextToken:ListFindingAggregations' :: ListFindingAggregations -> Maybe Text
$sel:maxResults:ListFindingAggregations' :: ListFindingAggregations -> Maybe Natural
$sel:aggregationRequest:ListFindingAggregations' :: ListFindingAggregations -> Maybe AggregationRequest
$sel:accountIds:ListFindingAggregations' :: ListFindingAggregations -> Maybe (NonEmpty StringFilter)
..} =
    Int
_salt
      forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Maybe (NonEmpty StringFilter)
accountIds
      forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Maybe AggregationRequest
aggregationRequest
      forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Maybe Natural
maxResults
      forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Maybe Text
nextToken
      forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` AggregationType
aggregationType

instance Prelude.NFData ListFindingAggregations where
  rnf :: ListFindingAggregations -> ()
rnf ListFindingAggregations' {Maybe Natural
Maybe (NonEmpty StringFilter)
Maybe Text
Maybe AggregationRequest
AggregationType
aggregationType :: AggregationType
nextToken :: Maybe Text
maxResults :: Maybe Natural
aggregationRequest :: Maybe AggregationRequest
accountIds :: Maybe (NonEmpty StringFilter)
$sel:aggregationType:ListFindingAggregations' :: ListFindingAggregations -> AggregationType
$sel:nextToken:ListFindingAggregations' :: ListFindingAggregations -> Maybe Text
$sel:maxResults:ListFindingAggregations' :: ListFindingAggregations -> Maybe Natural
$sel:aggregationRequest:ListFindingAggregations' :: ListFindingAggregations -> Maybe AggregationRequest
$sel:accountIds:ListFindingAggregations' :: ListFindingAggregations -> Maybe (NonEmpty StringFilter)
..} =
    forall a. NFData a => a -> ()
Prelude.rnf Maybe (NonEmpty StringFilter)
accountIds
      seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf Maybe AggregationRequest
aggregationRequest
      seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf Maybe Natural
maxResults
      seq :: forall a b. a -> b -> b
`Prelude.seq` 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 AggregationType
aggregationType

instance Data.ToHeaders ListFindingAggregations where
  toHeaders :: ListFindingAggregations -> 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 ListFindingAggregations where
  toJSON :: ListFindingAggregations -> Value
toJSON ListFindingAggregations' {Maybe Natural
Maybe (NonEmpty StringFilter)
Maybe Text
Maybe AggregationRequest
AggregationType
aggregationType :: AggregationType
nextToken :: Maybe Text
maxResults :: Maybe Natural
aggregationRequest :: Maybe AggregationRequest
accountIds :: Maybe (NonEmpty StringFilter)
$sel:aggregationType:ListFindingAggregations' :: ListFindingAggregations -> AggregationType
$sel:nextToken:ListFindingAggregations' :: ListFindingAggregations -> Maybe Text
$sel:maxResults:ListFindingAggregations' :: ListFindingAggregations -> Maybe Natural
$sel:aggregationRequest:ListFindingAggregations' :: ListFindingAggregations -> Maybe AggregationRequest
$sel:accountIds:ListFindingAggregations' :: ListFindingAggregations -> Maybe (NonEmpty StringFilter)
..} =
    [Pair] -> Value
Data.object
      ( forall a. [Maybe a] -> [a]
Prelude.catMaybes
          [ (Key
"accountIds" 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 (NonEmpty StringFilter)
accountIds,
            (Key
"aggregationRequest" 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 AggregationRequest
aggregationRequest,
            (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 Natural
maxResults,
            (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,
            forall a. a -> Maybe a
Prelude.Just
              (Key
"aggregationType" forall kv v. (KeyValue kv, ToJSON v) => Key -> v -> kv
Data..= AggregationType
aggregationType)
          ]
      )

instance Data.ToPath ListFindingAggregations where
  toPath :: ListFindingAggregations -> ByteString
toPath = forall a b. a -> b -> a
Prelude.const ByteString
"/findings/aggregation/list"

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

-- | /See:/ 'newListFindingAggregationsResponse' smart constructor.
data ListFindingAggregationsResponse = ListFindingAggregationsResponse'
  { -- | A token to use for paginating results that are returned in the response.
    -- Set the value of this parameter to null for the first request to a list
    -- action. For subsequent calls, use the @NextToken@ value returned from
    -- the previous request to continue listing results after the first page.
    ListFindingAggregationsResponse -> Maybe Text
nextToken :: Prelude.Maybe Prelude.Text,
    -- | Objects that contain the results of an aggregation operation.
    ListFindingAggregationsResponse -> Maybe [AggregationResponse]
responses :: Prelude.Maybe [AggregationResponse],
    -- | The response's http status code.
    ListFindingAggregationsResponse -> Int
httpStatus :: Prelude.Int,
    -- | The type of aggregation to perform.
    ListFindingAggregationsResponse -> AggregationType
aggregationType :: AggregationType
  }
  deriving (ListFindingAggregationsResponse
-> ListFindingAggregationsResponse -> Bool
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: ListFindingAggregationsResponse
-> ListFindingAggregationsResponse -> Bool
$c/= :: ListFindingAggregationsResponse
-> ListFindingAggregationsResponse -> Bool
== :: ListFindingAggregationsResponse
-> ListFindingAggregationsResponse -> Bool
$c== :: ListFindingAggregationsResponse
-> ListFindingAggregationsResponse -> Bool
Prelude.Eq, ReadPrec [ListFindingAggregationsResponse]
ReadPrec ListFindingAggregationsResponse
Int -> ReadS ListFindingAggregationsResponse
ReadS [ListFindingAggregationsResponse]
forall a.
(Int -> ReadS a)
-> ReadS [a] -> ReadPrec a -> ReadPrec [a] -> Read a
readListPrec :: ReadPrec [ListFindingAggregationsResponse]
$creadListPrec :: ReadPrec [ListFindingAggregationsResponse]
readPrec :: ReadPrec ListFindingAggregationsResponse
$creadPrec :: ReadPrec ListFindingAggregationsResponse
readList :: ReadS [ListFindingAggregationsResponse]
$creadList :: ReadS [ListFindingAggregationsResponse]
readsPrec :: Int -> ReadS ListFindingAggregationsResponse
$creadsPrec :: Int -> ReadS ListFindingAggregationsResponse
Prelude.Read, Int -> ListFindingAggregationsResponse -> ShowS
[ListFindingAggregationsResponse] -> ShowS
ListFindingAggregationsResponse -> String
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [ListFindingAggregationsResponse] -> ShowS
$cshowList :: [ListFindingAggregationsResponse] -> ShowS
show :: ListFindingAggregationsResponse -> String
$cshow :: ListFindingAggregationsResponse -> String
showsPrec :: Int -> ListFindingAggregationsResponse -> ShowS
$cshowsPrec :: Int -> ListFindingAggregationsResponse -> ShowS
Prelude.Show, forall x.
Rep ListFindingAggregationsResponse x
-> ListFindingAggregationsResponse
forall x.
ListFindingAggregationsResponse
-> Rep ListFindingAggregationsResponse x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cto :: forall x.
Rep ListFindingAggregationsResponse x
-> ListFindingAggregationsResponse
$cfrom :: forall x.
ListFindingAggregationsResponse
-> Rep ListFindingAggregationsResponse x
Prelude.Generic)

-- |
-- Create a value of 'ListFindingAggregationsResponse' 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', 'listFindingAggregationsResponse_nextToken' - A token to use for paginating results that are returned in the response.
-- Set the value of this parameter to null for the first request to a list
-- action. For subsequent calls, use the @NextToken@ value returned from
-- the previous request to continue listing results after the first page.
--
-- 'responses', 'listFindingAggregationsResponse_responses' - Objects that contain the results of an aggregation operation.
--
-- 'httpStatus', 'listFindingAggregationsResponse_httpStatus' - The response's http status code.
--
-- 'aggregationType', 'listFindingAggregationsResponse_aggregationType' - The type of aggregation to perform.
newListFindingAggregationsResponse ::
  -- | 'httpStatus'
  Prelude.Int ->
  -- | 'aggregationType'
  AggregationType ->
  ListFindingAggregationsResponse
newListFindingAggregationsResponse :: Int -> AggregationType -> ListFindingAggregationsResponse
newListFindingAggregationsResponse
  Int
pHttpStatus_
  AggregationType
pAggregationType_ =
    ListFindingAggregationsResponse'
      { $sel:nextToken:ListFindingAggregationsResponse' :: Maybe Text
nextToken =
          forall a. Maybe a
Prelude.Nothing,
        $sel:responses:ListFindingAggregationsResponse' :: Maybe [AggregationResponse]
responses = forall a. Maybe a
Prelude.Nothing,
        $sel:httpStatus:ListFindingAggregationsResponse' :: Int
httpStatus = Int
pHttpStatus_,
        $sel:aggregationType:ListFindingAggregationsResponse' :: AggregationType
aggregationType = AggregationType
pAggregationType_
      }

-- | A token to use for paginating results that are returned in the response.
-- Set the value of this parameter to null for the first request to a list
-- action. For subsequent calls, use the @NextToken@ value returned from
-- the previous request to continue listing results after the first page.
listFindingAggregationsResponse_nextToken :: Lens.Lens' ListFindingAggregationsResponse (Prelude.Maybe Prelude.Text)
listFindingAggregationsResponse_nextToken :: Lens' ListFindingAggregationsResponse (Maybe Text)
listFindingAggregationsResponse_nextToken = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\ListFindingAggregationsResponse' {Maybe Text
nextToken :: Maybe Text
$sel:nextToken:ListFindingAggregationsResponse' :: ListFindingAggregationsResponse -> Maybe Text
nextToken} -> Maybe Text
nextToken) (\s :: ListFindingAggregationsResponse
s@ListFindingAggregationsResponse' {} Maybe Text
a -> ListFindingAggregationsResponse
s {$sel:nextToken:ListFindingAggregationsResponse' :: Maybe Text
nextToken = Maybe Text
a} :: ListFindingAggregationsResponse)

-- | Objects that contain the results of an aggregation operation.
listFindingAggregationsResponse_responses :: Lens.Lens' ListFindingAggregationsResponse (Prelude.Maybe [AggregationResponse])
listFindingAggregationsResponse_responses :: Lens' ListFindingAggregationsResponse (Maybe [AggregationResponse])
listFindingAggregationsResponse_responses = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\ListFindingAggregationsResponse' {Maybe [AggregationResponse]
responses :: Maybe [AggregationResponse]
$sel:responses:ListFindingAggregationsResponse' :: ListFindingAggregationsResponse -> Maybe [AggregationResponse]
responses} -> Maybe [AggregationResponse]
responses) (\s :: ListFindingAggregationsResponse
s@ListFindingAggregationsResponse' {} Maybe [AggregationResponse]
a -> ListFindingAggregationsResponse
s {$sel:responses:ListFindingAggregationsResponse' :: Maybe [AggregationResponse]
responses = Maybe [AggregationResponse]
a} :: ListFindingAggregationsResponse) 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.
listFindingAggregationsResponse_httpStatus :: Lens.Lens' ListFindingAggregationsResponse Prelude.Int
listFindingAggregationsResponse_httpStatus :: Lens' ListFindingAggregationsResponse Int
listFindingAggregationsResponse_httpStatus = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\ListFindingAggregationsResponse' {Int
httpStatus :: Int
$sel:httpStatus:ListFindingAggregationsResponse' :: ListFindingAggregationsResponse -> Int
httpStatus} -> Int
httpStatus) (\s :: ListFindingAggregationsResponse
s@ListFindingAggregationsResponse' {} Int
a -> ListFindingAggregationsResponse
s {$sel:httpStatus:ListFindingAggregationsResponse' :: Int
httpStatus = Int
a} :: ListFindingAggregationsResponse)

-- | The type of aggregation to perform.
listFindingAggregationsResponse_aggregationType :: Lens.Lens' ListFindingAggregationsResponse AggregationType
listFindingAggregationsResponse_aggregationType :: Lens' ListFindingAggregationsResponse AggregationType
listFindingAggregationsResponse_aggregationType = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\ListFindingAggregationsResponse' {AggregationType
aggregationType :: AggregationType
$sel:aggregationType:ListFindingAggregationsResponse' :: ListFindingAggregationsResponse -> AggregationType
aggregationType} -> AggregationType
aggregationType) (\s :: ListFindingAggregationsResponse
s@ListFindingAggregationsResponse' {} AggregationType
a -> ListFindingAggregationsResponse
s {$sel:aggregationType:ListFindingAggregationsResponse' :: AggregationType
aggregationType = AggregationType
a} :: ListFindingAggregationsResponse)

instance
  Prelude.NFData
    ListFindingAggregationsResponse
  where
  rnf :: ListFindingAggregationsResponse -> ()
rnf ListFindingAggregationsResponse' {Int
Maybe [AggregationResponse]
Maybe Text
AggregationType
aggregationType :: AggregationType
httpStatus :: Int
responses :: Maybe [AggregationResponse]
nextToken :: Maybe Text
$sel:aggregationType:ListFindingAggregationsResponse' :: ListFindingAggregationsResponse -> AggregationType
$sel:httpStatus:ListFindingAggregationsResponse' :: ListFindingAggregationsResponse -> Int
$sel:responses:ListFindingAggregationsResponse' :: ListFindingAggregationsResponse -> Maybe [AggregationResponse]
$sel:nextToken:ListFindingAggregationsResponse' :: ListFindingAggregationsResponse -> 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 [AggregationResponse]
responses
      seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf Int
httpStatus
      seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf AggregationType
aggregationType