{-# 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.Config.GetAggregateConformancePackComplianceSummary
-- Copyright   : (c) 2013-2023 Brendan Hay
-- License     : Mozilla Public License, v. 2.0.
-- Maintainer  : Brendan Hay
-- Stability   : auto-generated
-- Portability : non-portable (GHC extensions)
--
-- Returns the count of compliant and noncompliant conformance packs across
-- all Amazon Web Services accounts and Amazon Web Services Regions in an
-- aggregator. You can filter based on Amazon Web Services account ID or
-- Amazon Web Services Region.
--
-- The results can return an empty result page, but if you have a
-- nextToken, the results are displayed on the next page.
module Amazonka.Config.GetAggregateConformancePackComplianceSummary
  ( -- * Creating a Request
    GetAggregateConformancePackComplianceSummary (..),
    newGetAggregateConformancePackComplianceSummary,

    -- * Request Lenses
    getAggregateConformancePackComplianceSummary_filters,
    getAggregateConformancePackComplianceSummary_groupByKey,
    getAggregateConformancePackComplianceSummary_limit,
    getAggregateConformancePackComplianceSummary_nextToken,
    getAggregateConformancePackComplianceSummary_configurationAggregatorName,

    -- * Destructuring the Response
    GetAggregateConformancePackComplianceSummaryResponse (..),
    newGetAggregateConformancePackComplianceSummaryResponse,

    -- * Response Lenses
    getAggregateConformancePackComplianceSummaryResponse_aggregateConformancePackComplianceSummaries,
    getAggregateConformancePackComplianceSummaryResponse_groupByKey,
    getAggregateConformancePackComplianceSummaryResponse_nextToken,
    getAggregateConformancePackComplianceSummaryResponse_httpStatus,
  )
where

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

-- | /See:/ 'newGetAggregateConformancePackComplianceSummary' smart constructor.
data GetAggregateConformancePackComplianceSummary = GetAggregateConformancePackComplianceSummary'
  { -- | Filters the results based on the
    -- @AggregateConformancePackComplianceSummaryFilters@ object.
    GetAggregateConformancePackComplianceSummary
-> Maybe AggregateConformancePackComplianceSummaryFilters
filters :: Prelude.Maybe AggregateConformancePackComplianceSummaryFilters,
    -- | Groups the result based on Amazon Web Services account ID or Amazon Web
    -- Services Region.
    GetAggregateConformancePackComplianceSummary
-> Maybe AggregateConformancePackComplianceSummaryGroupKey
groupByKey :: Prelude.Maybe AggregateConformancePackComplianceSummaryGroupKey,
    -- | The maximum number of results returned on each page. The default is
    -- maximum. If you specify 0, Config uses the default.
    GetAggregateConformancePackComplianceSummary -> Maybe Natural
limit :: Prelude.Maybe Prelude.Natural,
    -- | The @nextToken@ string returned on a previous page that you use to get
    -- the next page of results in a paginated response.
    GetAggregateConformancePackComplianceSummary -> Maybe Text
nextToken :: Prelude.Maybe Prelude.Text,
    -- | The name of the configuration aggregator.
    GetAggregateConformancePackComplianceSummary -> Text
configurationAggregatorName :: Prelude.Text
  }
  deriving (GetAggregateConformancePackComplianceSummary
-> GetAggregateConformancePackComplianceSummary -> Bool
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: GetAggregateConformancePackComplianceSummary
-> GetAggregateConformancePackComplianceSummary -> Bool
$c/= :: GetAggregateConformancePackComplianceSummary
-> GetAggregateConformancePackComplianceSummary -> Bool
== :: GetAggregateConformancePackComplianceSummary
-> GetAggregateConformancePackComplianceSummary -> Bool
$c== :: GetAggregateConformancePackComplianceSummary
-> GetAggregateConformancePackComplianceSummary -> Bool
Prelude.Eq, ReadPrec [GetAggregateConformancePackComplianceSummary]
ReadPrec GetAggregateConformancePackComplianceSummary
Int -> ReadS GetAggregateConformancePackComplianceSummary
ReadS [GetAggregateConformancePackComplianceSummary]
forall a.
(Int -> ReadS a)
-> ReadS [a] -> ReadPrec a -> ReadPrec [a] -> Read a
readListPrec :: ReadPrec [GetAggregateConformancePackComplianceSummary]
$creadListPrec :: ReadPrec [GetAggregateConformancePackComplianceSummary]
readPrec :: ReadPrec GetAggregateConformancePackComplianceSummary
$creadPrec :: ReadPrec GetAggregateConformancePackComplianceSummary
readList :: ReadS [GetAggregateConformancePackComplianceSummary]
$creadList :: ReadS [GetAggregateConformancePackComplianceSummary]
readsPrec :: Int -> ReadS GetAggregateConformancePackComplianceSummary
$creadsPrec :: Int -> ReadS GetAggregateConformancePackComplianceSummary
Prelude.Read, Int -> GetAggregateConformancePackComplianceSummary -> ShowS
[GetAggregateConformancePackComplianceSummary] -> ShowS
GetAggregateConformancePackComplianceSummary -> String
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [GetAggregateConformancePackComplianceSummary] -> ShowS
$cshowList :: [GetAggregateConformancePackComplianceSummary] -> ShowS
show :: GetAggregateConformancePackComplianceSummary -> String
$cshow :: GetAggregateConformancePackComplianceSummary -> String
showsPrec :: Int -> GetAggregateConformancePackComplianceSummary -> ShowS
$cshowsPrec :: Int -> GetAggregateConformancePackComplianceSummary -> ShowS
Prelude.Show, forall x.
Rep GetAggregateConformancePackComplianceSummary x
-> GetAggregateConformancePackComplianceSummary
forall x.
GetAggregateConformancePackComplianceSummary
-> Rep GetAggregateConformancePackComplianceSummary x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cto :: forall x.
Rep GetAggregateConformancePackComplianceSummary x
-> GetAggregateConformancePackComplianceSummary
$cfrom :: forall x.
GetAggregateConformancePackComplianceSummary
-> Rep GetAggregateConformancePackComplianceSummary x
Prelude.Generic)

-- |
-- Create a value of 'GetAggregateConformancePackComplianceSummary' 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:
--
-- 'filters', 'getAggregateConformancePackComplianceSummary_filters' - Filters the results based on the
-- @AggregateConformancePackComplianceSummaryFilters@ object.
--
-- 'groupByKey', 'getAggregateConformancePackComplianceSummary_groupByKey' - Groups the result based on Amazon Web Services account ID or Amazon Web
-- Services Region.
--
-- 'limit', 'getAggregateConformancePackComplianceSummary_limit' - The maximum number of results returned on each page. The default is
-- maximum. If you specify 0, Config uses the default.
--
-- 'nextToken', 'getAggregateConformancePackComplianceSummary_nextToken' - The @nextToken@ string returned on a previous page that you use to get
-- the next page of results in a paginated response.
--
-- 'configurationAggregatorName', 'getAggregateConformancePackComplianceSummary_configurationAggregatorName' - The name of the configuration aggregator.
newGetAggregateConformancePackComplianceSummary ::
  -- | 'configurationAggregatorName'
  Prelude.Text ->
  GetAggregateConformancePackComplianceSummary
newGetAggregateConformancePackComplianceSummary :: Text -> GetAggregateConformancePackComplianceSummary
newGetAggregateConformancePackComplianceSummary
  Text
pConfigurationAggregatorName_ =
    GetAggregateConformancePackComplianceSummary'
      { $sel:filters:GetAggregateConformancePackComplianceSummary' :: Maybe AggregateConformancePackComplianceSummaryFilters
filters =
          forall a. Maybe a
Prelude.Nothing,
        $sel:groupByKey:GetAggregateConformancePackComplianceSummary' :: Maybe AggregateConformancePackComplianceSummaryGroupKey
groupByKey = forall a. Maybe a
Prelude.Nothing,
        $sel:limit:GetAggregateConformancePackComplianceSummary' :: Maybe Natural
limit = forall a. Maybe a
Prelude.Nothing,
        $sel:nextToken:GetAggregateConformancePackComplianceSummary' :: Maybe Text
nextToken = forall a. Maybe a
Prelude.Nothing,
        $sel:configurationAggregatorName:GetAggregateConformancePackComplianceSummary' :: Text
configurationAggregatorName =
          Text
pConfigurationAggregatorName_
      }

-- | Filters the results based on the
-- @AggregateConformancePackComplianceSummaryFilters@ object.
getAggregateConformancePackComplianceSummary_filters :: Lens.Lens' GetAggregateConformancePackComplianceSummary (Prelude.Maybe AggregateConformancePackComplianceSummaryFilters)
getAggregateConformancePackComplianceSummary_filters :: Lens'
  GetAggregateConformancePackComplianceSummary
  (Maybe AggregateConformancePackComplianceSummaryFilters)
getAggregateConformancePackComplianceSummary_filters = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\GetAggregateConformancePackComplianceSummary' {Maybe AggregateConformancePackComplianceSummaryFilters
filters :: Maybe AggregateConformancePackComplianceSummaryFilters
$sel:filters:GetAggregateConformancePackComplianceSummary' :: GetAggregateConformancePackComplianceSummary
-> Maybe AggregateConformancePackComplianceSummaryFilters
filters} -> Maybe AggregateConformancePackComplianceSummaryFilters
filters) (\s :: GetAggregateConformancePackComplianceSummary
s@GetAggregateConformancePackComplianceSummary' {} Maybe AggregateConformancePackComplianceSummaryFilters
a -> GetAggregateConformancePackComplianceSummary
s {$sel:filters:GetAggregateConformancePackComplianceSummary' :: Maybe AggregateConformancePackComplianceSummaryFilters
filters = Maybe AggregateConformancePackComplianceSummaryFilters
a} :: GetAggregateConformancePackComplianceSummary)

-- | Groups the result based on Amazon Web Services account ID or Amazon Web
-- Services Region.
getAggregateConformancePackComplianceSummary_groupByKey :: Lens.Lens' GetAggregateConformancePackComplianceSummary (Prelude.Maybe AggregateConformancePackComplianceSummaryGroupKey)
getAggregateConformancePackComplianceSummary_groupByKey :: Lens'
  GetAggregateConformancePackComplianceSummary
  (Maybe AggregateConformancePackComplianceSummaryGroupKey)
getAggregateConformancePackComplianceSummary_groupByKey = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\GetAggregateConformancePackComplianceSummary' {Maybe AggregateConformancePackComplianceSummaryGroupKey
groupByKey :: Maybe AggregateConformancePackComplianceSummaryGroupKey
$sel:groupByKey:GetAggregateConformancePackComplianceSummary' :: GetAggregateConformancePackComplianceSummary
-> Maybe AggregateConformancePackComplianceSummaryGroupKey
groupByKey} -> Maybe AggregateConformancePackComplianceSummaryGroupKey
groupByKey) (\s :: GetAggregateConformancePackComplianceSummary
s@GetAggregateConformancePackComplianceSummary' {} Maybe AggregateConformancePackComplianceSummaryGroupKey
a -> GetAggregateConformancePackComplianceSummary
s {$sel:groupByKey:GetAggregateConformancePackComplianceSummary' :: Maybe AggregateConformancePackComplianceSummaryGroupKey
groupByKey = Maybe AggregateConformancePackComplianceSummaryGroupKey
a} :: GetAggregateConformancePackComplianceSummary)

-- | The maximum number of results returned on each page. The default is
-- maximum. If you specify 0, Config uses the default.
getAggregateConformancePackComplianceSummary_limit :: Lens.Lens' GetAggregateConformancePackComplianceSummary (Prelude.Maybe Prelude.Natural)
getAggregateConformancePackComplianceSummary_limit :: Lens' GetAggregateConformancePackComplianceSummary (Maybe Natural)
getAggregateConformancePackComplianceSummary_limit = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\GetAggregateConformancePackComplianceSummary' {Maybe Natural
limit :: Maybe Natural
$sel:limit:GetAggregateConformancePackComplianceSummary' :: GetAggregateConformancePackComplianceSummary -> Maybe Natural
limit} -> Maybe Natural
limit) (\s :: GetAggregateConformancePackComplianceSummary
s@GetAggregateConformancePackComplianceSummary' {} Maybe Natural
a -> GetAggregateConformancePackComplianceSummary
s {$sel:limit:GetAggregateConformancePackComplianceSummary' :: Maybe Natural
limit = Maybe Natural
a} :: GetAggregateConformancePackComplianceSummary)

-- | The @nextToken@ string returned on a previous page that you use to get
-- the next page of results in a paginated response.
getAggregateConformancePackComplianceSummary_nextToken :: Lens.Lens' GetAggregateConformancePackComplianceSummary (Prelude.Maybe Prelude.Text)
getAggregateConformancePackComplianceSummary_nextToken :: Lens' GetAggregateConformancePackComplianceSummary (Maybe Text)
getAggregateConformancePackComplianceSummary_nextToken = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\GetAggregateConformancePackComplianceSummary' {Maybe Text
nextToken :: Maybe Text
$sel:nextToken:GetAggregateConformancePackComplianceSummary' :: GetAggregateConformancePackComplianceSummary -> Maybe Text
nextToken} -> Maybe Text
nextToken) (\s :: GetAggregateConformancePackComplianceSummary
s@GetAggregateConformancePackComplianceSummary' {} Maybe Text
a -> GetAggregateConformancePackComplianceSummary
s {$sel:nextToken:GetAggregateConformancePackComplianceSummary' :: Maybe Text
nextToken = Maybe Text
a} :: GetAggregateConformancePackComplianceSummary)

-- | The name of the configuration aggregator.
getAggregateConformancePackComplianceSummary_configurationAggregatorName :: Lens.Lens' GetAggregateConformancePackComplianceSummary Prelude.Text
getAggregateConformancePackComplianceSummary_configurationAggregatorName :: Lens' GetAggregateConformancePackComplianceSummary Text
getAggregateConformancePackComplianceSummary_configurationAggregatorName = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\GetAggregateConformancePackComplianceSummary' {Text
configurationAggregatorName :: Text
$sel:configurationAggregatorName:GetAggregateConformancePackComplianceSummary' :: GetAggregateConformancePackComplianceSummary -> Text
configurationAggregatorName} -> Text
configurationAggregatorName) (\s :: GetAggregateConformancePackComplianceSummary
s@GetAggregateConformancePackComplianceSummary' {} Text
a -> GetAggregateConformancePackComplianceSummary
s {$sel:configurationAggregatorName:GetAggregateConformancePackComplianceSummary' :: Text
configurationAggregatorName = Text
a} :: GetAggregateConformancePackComplianceSummary)

instance
  Core.AWSRequest
    GetAggregateConformancePackComplianceSummary
  where
  type
    AWSResponse
      GetAggregateConformancePackComplianceSummary =
      GetAggregateConformancePackComplianceSummaryResponse
  request :: (Service -> Service)
-> GetAggregateConformancePackComplianceSummary
-> Request GetAggregateConformancePackComplianceSummary
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 GetAggregateConformancePackComplianceSummary
-> ClientResponse ClientBody
-> m (Either
        Error
        (ClientResponse
           (AWSResponse GetAggregateConformancePackComplianceSummary)))
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 [AggregateConformancePackComplianceSummary]
-> Maybe Text
-> Maybe Text
-> Int
-> GetAggregateConformancePackComplianceSummaryResponse
GetAggregateConformancePackComplianceSummaryResponse'
            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
"AggregateConformancePackComplianceSummaries"
                            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.<*> (Object
x forall a. FromJSON a => Object -> Key -> Either String (Maybe a)
Data..?> Key
"GroupByKey")
            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
"NextToken")
            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
    GetAggregateConformancePackComplianceSummary
  where
  hashWithSalt :: Int -> GetAggregateConformancePackComplianceSummary -> Int
hashWithSalt
    Int
_salt
    GetAggregateConformancePackComplianceSummary' {Maybe Natural
Maybe Text
Maybe AggregateConformancePackComplianceSummaryFilters
Maybe AggregateConformancePackComplianceSummaryGroupKey
Text
configurationAggregatorName :: Text
nextToken :: Maybe Text
limit :: Maybe Natural
groupByKey :: Maybe AggregateConformancePackComplianceSummaryGroupKey
filters :: Maybe AggregateConformancePackComplianceSummaryFilters
$sel:configurationAggregatorName:GetAggregateConformancePackComplianceSummary' :: GetAggregateConformancePackComplianceSummary -> Text
$sel:nextToken:GetAggregateConformancePackComplianceSummary' :: GetAggregateConformancePackComplianceSummary -> Maybe Text
$sel:limit:GetAggregateConformancePackComplianceSummary' :: GetAggregateConformancePackComplianceSummary -> Maybe Natural
$sel:groupByKey:GetAggregateConformancePackComplianceSummary' :: GetAggregateConformancePackComplianceSummary
-> Maybe AggregateConformancePackComplianceSummaryGroupKey
$sel:filters:GetAggregateConformancePackComplianceSummary' :: GetAggregateConformancePackComplianceSummary
-> Maybe AggregateConformancePackComplianceSummaryFilters
..} =
      Int
_salt
        forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Maybe AggregateConformancePackComplianceSummaryFilters
filters
        forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Maybe AggregateConformancePackComplianceSummaryGroupKey
groupByKey
        forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Maybe Natural
limit
        forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Maybe Text
nextToken
        forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Text
configurationAggregatorName

instance
  Prelude.NFData
    GetAggregateConformancePackComplianceSummary
  where
  rnf :: GetAggregateConformancePackComplianceSummary -> ()
rnf GetAggregateConformancePackComplianceSummary' {Maybe Natural
Maybe Text
Maybe AggregateConformancePackComplianceSummaryFilters
Maybe AggregateConformancePackComplianceSummaryGroupKey
Text
configurationAggregatorName :: Text
nextToken :: Maybe Text
limit :: Maybe Natural
groupByKey :: Maybe AggregateConformancePackComplianceSummaryGroupKey
filters :: Maybe AggregateConformancePackComplianceSummaryFilters
$sel:configurationAggregatorName:GetAggregateConformancePackComplianceSummary' :: GetAggregateConformancePackComplianceSummary -> Text
$sel:nextToken:GetAggregateConformancePackComplianceSummary' :: GetAggregateConformancePackComplianceSummary -> Maybe Text
$sel:limit:GetAggregateConformancePackComplianceSummary' :: GetAggregateConformancePackComplianceSummary -> Maybe Natural
$sel:groupByKey:GetAggregateConformancePackComplianceSummary' :: GetAggregateConformancePackComplianceSummary
-> Maybe AggregateConformancePackComplianceSummaryGroupKey
$sel:filters:GetAggregateConformancePackComplianceSummary' :: GetAggregateConformancePackComplianceSummary
-> Maybe AggregateConformancePackComplianceSummaryFilters
..} =
    forall a. NFData a => a -> ()
Prelude.rnf Maybe AggregateConformancePackComplianceSummaryFilters
filters
      seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf Maybe AggregateConformancePackComplianceSummaryGroupKey
groupByKey
      seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf Maybe Natural
limit
      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 Text
configurationAggregatorName

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

instance
  Data.ToJSON
    GetAggregateConformancePackComplianceSummary
  where
  toJSON :: GetAggregateConformancePackComplianceSummary -> Value
toJSON
    GetAggregateConformancePackComplianceSummary' {Maybe Natural
Maybe Text
Maybe AggregateConformancePackComplianceSummaryFilters
Maybe AggregateConformancePackComplianceSummaryGroupKey
Text
configurationAggregatorName :: Text
nextToken :: Maybe Text
limit :: Maybe Natural
groupByKey :: Maybe AggregateConformancePackComplianceSummaryGroupKey
filters :: Maybe AggregateConformancePackComplianceSummaryFilters
$sel:configurationAggregatorName:GetAggregateConformancePackComplianceSummary' :: GetAggregateConformancePackComplianceSummary -> Text
$sel:nextToken:GetAggregateConformancePackComplianceSummary' :: GetAggregateConformancePackComplianceSummary -> Maybe Text
$sel:limit:GetAggregateConformancePackComplianceSummary' :: GetAggregateConformancePackComplianceSummary -> Maybe Natural
$sel:groupByKey:GetAggregateConformancePackComplianceSummary' :: GetAggregateConformancePackComplianceSummary
-> Maybe AggregateConformancePackComplianceSummaryGroupKey
$sel:filters:GetAggregateConformancePackComplianceSummary' :: GetAggregateConformancePackComplianceSummary
-> Maybe AggregateConformancePackComplianceSummaryFilters
..} =
      [Pair] -> Value
Data.object
        ( forall a. [Maybe a] -> [a]
Prelude.catMaybes
            [ (Key
"Filters" 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 AggregateConformancePackComplianceSummaryFilters
filters,
              (Key
"GroupByKey" 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 AggregateConformancePackComplianceSummaryGroupKey
groupByKey,
              (Key
"Limit" 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
limit,
              (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
"ConfigurationAggregatorName"
                    forall kv v. (KeyValue kv, ToJSON v) => Key -> v -> kv
Data..= Text
configurationAggregatorName
                )
            ]
        )

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

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

-- | /See:/ 'newGetAggregateConformancePackComplianceSummaryResponse' smart constructor.
data GetAggregateConformancePackComplianceSummaryResponse = GetAggregateConformancePackComplianceSummaryResponse'
  { -- | Returns a list of @AggregateConformancePackComplianceSummary@ object.
    GetAggregateConformancePackComplianceSummaryResponse
-> Maybe [AggregateConformancePackComplianceSummary]
aggregateConformancePackComplianceSummaries :: Prelude.Maybe [AggregateConformancePackComplianceSummary],
    -- | Groups the result based on Amazon Web Services account ID or Amazon Web
    -- Services Region.
    GetAggregateConformancePackComplianceSummaryResponse -> Maybe Text
groupByKey :: Prelude.Maybe Prelude.Text,
    -- | The @nextToken@ string returned on a previous page that you use to get
    -- the next page of results in a paginated response.
    GetAggregateConformancePackComplianceSummaryResponse -> Maybe Text
nextToken :: Prelude.Maybe Prelude.Text,
    -- | The response's http status code.
    GetAggregateConformancePackComplianceSummaryResponse -> Int
httpStatus :: Prelude.Int
  }
  deriving (GetAggregateConformancePackComplianceSummaryResponse
-> GetAggregateConformancePackComplianceSummaryResponse -> Bool
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: GetAggregateConformancePackComplianceSummaryResponse
-> GetAggregateConformancePackComplianceSummaryResponse -> Bool
$c/= :: GetAggregateConformancePackComplianceSummaryResponse
-> GetAggregateConformancePackComplianceSummaryResponse -> Bool
== :: GetAggregateConformancePackComplianceSummaryResponse
-> GetAggregateConformancePackComplianceSummaryResponse -> Bool
$c== :: GetAggregateConformancePackComplianceSummaryResponse
-> GetAggregateConformancePackComplianceSummaryResponse -> Bool
Prelude.Eq, ReadPrec [GetAggregateConformancePackComplianceSummaryResponse]
ReadPrec GetAggregateConformancePackComplianceSummaryResponse
Int -> ReadS GetAggregateConformancePackComplianceSummaryResponse
ReadS [GetAggregateConformancePackComplianceSummaryResponse]
forall a.
(Int -> ReadS a)
-> ReadS [a] -> ReadPrec a -> ReadPrec [a] -> Read a
readListPrec :: ReadPrec [GetAggregateConformancePackComplianceSummaryResponse]
$creadListPrec :: ReadPrec [GetAggregateConformancePackComplianceSummaryResponse]
readPrec :: ReadPrec GetAggregateConformancePackComplianceSummaryResponse
$creadPrec :: ReadPrec GetAggregateConformancePackComplianceSummaryResponse
readList :: ReadS [GetAggregateConformancePackComplianceSummaryResponse]
$creadList :: ReadS [GetAggregateConformancePackComplianceSummaryResponse]
readsPrec :: Int -> ReadS GetAggregateConformancePackComplianceSummaryResponse
$creadsPrec :: Int -> ReadS GetAggregateConformancePackComplianceSummaryResponse
Prelude.Read, Int
-> GetAggregateConformancePackComplianceSummaryResponse -> ShowS
[GetAggregateConformancePackComplianceSummaryResponse] -> ShowS
GetAggregateConformancePackComplianceSummaryResponse -> String
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [GetAggregateConformancePackComplianceSummaryResponse] -> ShowS
$cshowList :: [GetAggregateConformancePackComplianceSummaryResponse] -> ShowS
show :: GetAggregateConformancePackComplianceSummaryResponse -> String
$cshow :: GetAggregateConformancePackComplianceSummaryResponse -> String
showsPrec :: Int
-> GetAggregateConformancePackComplianceSummaryResponse -> ShowS
$cshowsPrec :: Int
-> GetAggregateConformancePackComplianceSummaryResponse -> ShowS
Prelude.Show, forall x.
Rep GetAggregateConformancePackComplianceSummaryResponse x
-> GetAggregateConformancePackComplianceSummaryResponse
forall x.
GetAggregateConformancePackComplianceSummaryResponse
-> Rep GetAggregateConformancePackComplianceSummaryResponse x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cto :: forall x.
Rep GetAggregateConformancePackComplianceSummaryResponse x
-> GetAggregateConformancePackComplianceSummaryResponse
$cfrom :: forall x.
GetAggregateConformancePackComplianceSummaryResponse
-> Rep GetAggregateConformancePackComplianceSummaryResponse x
Prelude.Generic)

-- |
-- Create a value of 'GetAggregateConformancePackComplianceSummaryResponse' 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:
--
-- 'aggregateConformancePackComplianceSummaries', 'getAggregateConformancePackComplianceSummaryResponse_aggregateConformancePackComplianceSummaries' - Returns a list of @AggregateConformancePackComplianceSummary@ object.
--
-- 'groupByKey', 'getAggregateConformancePackComplianceSummaryResponse_groupByKey' - Groups the result based on Amazon Web Services account ID or Amazon Web
-- Services Region.
--
-- 'nextToken', 'getAggregateConformancePackComplianceSummaryResponse_nextToken' - The @nextToken@ string returned on a previous page that you use to get
-- the next page of results in a paginated response.
--
-- 'httpStatus', 'getAggregateConformancePackComplianceSummaryResponse_httpStatus' - The response's http status code.
newGetAggregateConformancePackComplianceSummaryResponse ::
  -- | 'httpStatus'
  Prelude.Int ->
  GetAggregateConformancePackComplianceSummaryResponse
newGetAggregateConformancePackComplianceSummaryResponse :: Int -> GetAggregateConformancePackComplianceSummaryResponse
newGetAggregateConformancePackComplianceSummaryResponse
  Int
pHttpStatus_ =
    GetAggregateConformancePackComplianceSummaryResponse'
      { $sel:aggregateConformancePackComplianceSummaries:GetAggregateConformancePackComplianceSummaryResponse' :: Maybe [AggregateConformancePackComplianceSummary]
aggregateConformancePackComplianceSummaries =
          forall a. Maybe a
Prelude.Nothing,
        $sel:groupByKey:GetAggregateConformancePackComplianceSummaryResponse' :: Maybe Text
groupByKey =
          forall a. Maybe a
Prelude.Nothing,
        $sel:nextToken:GetAggregateConformancePackComplianceSummaryResponse' :: Maybe Text
nextToken =
          forall a. Maybe a
Prelude.Nothing,
        $sel:httpStatus:GetAggregateConformancePackComplianceSummaryResponse' :: Int
httpStatus =
          Int
pHttpStatus_
      }

-- | Returns a list of @AggregateConformancePackComplianceSummary@ object.
getAggregateConformancePackComplianceSummaryResponse_aggregateConformancePackComplianceSummaries :: Lens.Lens' GetAggregateConformancePackComplianceSummaryResponse (Prelude.Maybe [AggregateConformancePackComplianceSummary])
getAggregateConformancePackComplianceSummaryResponse_aggregateConformancePackComplianceSummaries :: Lens'
  GetAggregateConformancePackComplianceSummaryResponse
  (Maybe [AggregateConformancePackComplianceSummary])
getAggregateConformancePackComplianceSummaryResponse_aggregateConformancePackComplianceSummaries = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\GetAggregateConformancePackComplianceSummaryResponse' {Maybe [AggregateConformancePackComplianceSummary]
aggregateConformancePackComplianceSummaries :: Maybe [AggregateConformancePackComplianceSummary]
$sel:aggregateConformancePackComplianceSummaries:GetAggregateConformancePackComplianceSummaryResponse' :: GetAggregateConformancePackComplianceSummaryResponse
-> Maybe [AggregateConformancePackComplianceSummary]
aggregateConformancePackComplianceSummaries} -> Maybe [AggregateConformancePackComplianceSummary]
aggregateConformancePackComplianceSummaries) (\s :: GetAggregateConformancePackComplianceSummaryResponse
s@GetAggregateConformancePackComplianceSummaryResponse' {} Maybe [AggregateConformancePackComplianceSummary]
a -> GetAggregateConformancePackComplianceSummaryResponse
s {$sel:aggregateConformancePackComplianceSummaries:GetAggregateConformancePackComplianceSummaryResponse' :: Maybe [AggregateConformancePackComplianceSummary]
aggregateConformancePackComplianceSummaries = Maybe [AggregateConformancePackComplianceSummary]
a} :: GetAggregateConformancePackComplianceSummaryResponse) 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

-- | Groups the result based on Amazon Web Services account ID or Amazon Web
-- Services Region.
getAggregateConformancePackComplianceSummaryResponse_groupByKey :: Lens.Lens' GetAggregateConformancePackComplianceSummaryResponse (Prelude.Maybe Prelude.Text)
getAggregateConformancePackComplianceSummaryResponse_groupByKey :: Lens'
  GetAggregateConformancePackComplianceSummaryResponse (Maybe Text)
getAggregateConformancePackComplianceSummaryResponse_groupByKey = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\GetAggregateConformancePackComplianceSummaryResponse' {Maybe Text
groupByKey :: Maybe Text
$sel:groupByKey:GetAggregateConformancePackComplianceSummaryResponse' :: GetAggregateConformancePackComplianceSummaryResponse -> Maybe Text
groupByKey} -> Maybe Text
groupByKey) (\s :: GetAggregateConformancePackComplianceSummaryResponse
s@GetAggregateConformancePackComplianceSummaryResponse' {} Maybe Text
a -> GetAggregateConformancePackComplianceSummaryResponse
s {$sel:groupByKey:GetAggregateConformancePackComplianceSummaryResponse' :: Maybe Text
groupByKey = Maybe Text
a} :: GetAggregateConformancePackComplianceSummaryResponse)

-- | The @nextToken@ string returned on a previous page that you use to get
-- the next page of results in a paginated response.
getAggregateConformancePackComplianceSummaryResponse_nextToken :: Lens.Lens' GetAggregateConformancePackComplianceSummaryResponse (Prelude.Maybe Prelude.Text)
getAggregateConformancePackComplianceSummaryResponse_nextToken :: Lens'
  GetAggregateConformancePackComplianceSummaryResponse (Maybe Text)
getAggregateConformancePackComplianceSummaryResponse_nextToken = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\GetAggregateConformancePackComplianceSummaryResponse' {Maybe Text
nextToken :: Maybe Text
$sel:nextToken:GetAggregateConformancePackComplianceSummaryResponse' :: GetAggregateConformancePackComplianceSummaryResponse -> Maybe Text
nextToken} -> Maybe Text
nextToken) (\s :: GetAggregateConformancePackComplianceSummaryResponse
s@GetAggregateConformancePackComplianceSummaryResponse' {} Maybe Text
a -> GetAggregateConformancePackComplianceSummaryResponse
s {$sel:nextToken:GetAggregateConformancePackComplianceSummaryResponse' :: Maybe Text
nextToken = Maybe Text
a} :: GetAggregateConformancePackComplianceSummaryResponse)

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

instance
  Prelude.NFData
    GetAggregateConformancePackComplianceSummaryResponse
  where
  rnf :: GetAggregateConformancePackComplianceSummaryResponse -> ()
rnf
    GetAggregateConformancePackComplianceSummaryResponse' {Int
Maybe [AggregateConformancePackComplianceSummary]
Maybe Text
httpStatus :: Int
nextToken :: Maybe Text
groupByKey :: Maybe Text
aggregateConformancePackComplianceSummaries :: Maybe [AggregateConformancePackComplianceSummary]
$sel:httpStatus:GetAggregateConformancePackComplianceSummaryResponse' :: GetAggregateConformancePackComplianceSummaryResponse -> Int
$sel:nextToken:GetAggregateConformancePackComplianceSummaryResponse' :: GetAggregateConformancePackComplianceSummaryResponse -> Maybe Text
$sel:groupByKey:GetAggregateConformancePackComplianceSummaryResponse' :: GetAggregateConformancePackComplianceSummaryResponse -> Maybe Text
$sel:aggregateConformancePackComplianceSummaries:GetAggregateConformancePackComplianceSummaryResponse' :: GetAggregateConformancePackComplianceSummaryResponse
-> Maybe [AggregateConformancePackComplianceSummary]
..} =
      forall a. NFData a => a -> ()
Prelude.rnf
        Maybe [AggregateConformancePackComplianceSummary]
aggregateConformancePackComplianceSummaries
        seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf Maybe Text
groupByKey
        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 Int
httpStatus