{-# 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.DescribeConfigurationAggregators
-- 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 details of one or more configuration aggregators. If the
-- configuration aggregator is not specified, this action returns the
-- details for all the configuration aggregators associated with the
-- account.
--
-- This operation returns paginated results.
module Amazonka.Config.DescribeConfigurationAggregators
  ( -- * Creating a Request
    DescribeConfigurationAggregators (..),
    newDescribeConfigurationAggregators,

    -- * Request Lenses
    describeConfigurationAggregators_configurationAggregatorNames,
    describeConfigurationAggregators_limit,
    describeConfigurationAggregators_nextToken,

    -- * Destructuring the Response
    DescribeConfigurationAggregatorsResponse (..),
    newDescribeConfigurationAggregatorsResponse,

    -- * Response Lenses
    describeConfigurationAggregatorsResponse_configurationAggregators,
    describeConfigurationAggregatorsResponse_nextToken,
    describeConfigurationAggregatorsResponse_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:/ 'newDescribeConfigurationAggregators' smart constructor.
data DescribeConfigurationAggregators = DescribeConfigurationAggregators'
  { -- | The name of the configuration aggregators.
    DescribeConfigurationAggregators -> Maybe [Text]
configurationAggregatorNames :: Prelude.Maybe [Prelude.Text],
    -- | The maximum number of configuration aggregators returned on each page.
    -- The default is maximum. If you specify 0, Config uses the default.
    DescribeConfigurationAggregators -> 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.
    DescribeConfigurationAggregators -> Maybe Text
nextToken :: Prelude.Maybe Prelude.Text
  }
  deriving (DescribeConfigurationAggregators
-> DescribeConfigurationAggregators -> Bool
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: DescribeConfigurationAggregators
-> DescribeConfigurationAggregators -> Bool
$c/= :: DescribeConfigurationAggregators
-> DescribeConfigurationAggregators -> Bool
== :: DescribeConfigurationAggregators
-> DescribeConfigurationAggregators -> Bool
$c== :: DescribeConfigurationAggregators
-> DescribeConfigurationAggregators -> Bool
Prelude.Eq, ReadPrec [DescribeConfigurationAggregators]
ReadPrec DescribeConfigurationAggregators
Int -> ReadS DescribeConfigurationAggregators
ReadS [DescribeConfigurationAggregators]
forall a.
(Int -> ReadS a)
-> ReadS [a] -> ReadPrec a -> ReadPrec [a] -> Read a
readListPrec :: ReadPrec [DescribeConfigurationAggregators]
$creadListPrec :: ReadPrec [DescribeConfigurationAggregators]
readPrec :: ReadPrec DescribeConfigurationAggregators
$creadPrec :: ReadPrec DescribeConfigurationAggregators
readList :: ReadS [DescribeConfigurationAggregators]
$creadList :: ReadS [DescribeConfigurationAggregators]
readsPrec :: Int -> ReadS DescribeConfigurationAggregators
$creadsPrec :: Int -> ReadS DescribeConfigurationAggregators
Prelude.Read, Int -> DescribeConfigurationAggregators -> ShowS
[DescribeConfigurationAggregators] -> ShowS
DescribeConfigurationAggregators -> String
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [DescribeConfigurationAggregators] -> ShowS
$cshowList :: [DescribeConfigurationAggregators] -> ShowS
show :: DescribeConfigurationAggregators -> String
$cshow :: DescribeConfigurationAggregators -> String
showsPrec :: Int -> DescribeConfigurationAggregators -> ShowS
$cshowsPrec :: Int -> DescribeConfigurationAggregators -> ShowS
Prelude.Show, forall x.
Rep DescribeConfigurationAggregators x
-> DescribeConfigurationAggregators
forall x.
DescribeConfigurationAggregators
-> Rep DescribeConfigurationAggregators x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cto :: forall x.
Rep DescribeConfigurationAggregators x
-> DescribeConfigurationAggregators
$cfrom :: forall x.
DescribeConfigurationAggregators
-> Rep DescribeConfigurationAggregators x
Prelude.Generic)

-- |
-- Create a value of 'DescribeConfigurationAggregators' 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:
--
-- 'configurationAggregatorNames', 'describeConfigurationAggregators_configurationAggregatorNames' - The name of the configuration aggregators.
--
-- 'limit', 'describeConfigurationAggregators_limit' - The maximum number of configuration aggregators returned on each page.
-- The default is maximum. If you specify 0, Config uses the default.
--
-- 'nextToken', 'describeConfigurationAggregators_nextToken' - The @nextToken@ string returned on a previous page that you use to get
-- the next page of results in a paginated response.
newDescribeConfigurationAggregators ::
  DescribeConfigurationAggregators
newDescribeConfigurationAggregators :: DescribeConfigurationAggregators
newDescribeConfigurationAggregators =
  DescribeConfigurationAggregators'
    { $sel:configurationAggregatorNames:DescribeConfigurationAggregators' :: Maybe [Text]
configurationAggregatorNames =
        forall a. Maybe a
Prelude.Nothing,
      $sel:limit:DescribeConfigurationAggregators' :: Maybe Natural
limit = forall a. Maybe a
Prelude.Nothing,
      $sel:nextToken:DescribeConfigurationAggregators' :: Maybe Text
nextToken = forall a. Maybe a
Prelude.Nothing
    }

-- | The name of the configuration aggregators.
describeConfigurationAggregators_configurationAggregatorNames :: Lens.Lens' DescribeConfigurationAggregators (Prelude.Maybe [Prelude.Text])
describeConfigurationAggregators_configurationAggregatorNames :: Lens' DescribeConfigurationAggregators (Maybe [Text])
describeConfigurationAggregators_configurationAggregatorNames = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\DescribeConfigurationAggregators' {Maybe [Text]
configurationAggregatorNames :: Maybe [Text]
$sel:configurationAggregatorNames:DescribeConfigurationAggregators' :: DescribeConfigurationAggregators -> Maybe [Text]
configurationAggregatorNames} -> Maybe [Text]
configurationAggregatorNames) (\s :: DescribeConfigurationAggregators
s@DescribeConfigurationAggregators' {} Maybe [Text]
a -> DescribeConfigurationAggregators
s {$sel:configurationAggregatorNames:DescribeConfigurationAggregators' :: Maybe [Text]
configurationAggregatorNames = Maybe [Text]
a} :: DescribeConfigurationAggregators) 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 maximum number of configuration aggregators returned on each page.
-- The default is maximum. If you specify 0, Config uses the default.
describeConfigurationAggregators_limit :: Lens.Lens' DescribeConfigurationAggregators (Prelude.Maybe Prelude.Natural)
describeConfigurationAggregators_limit :: Lens' DescribeConfigurationAggregators (Maybe Natural)
describeConfigurationAggregators_limit = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\DescribeConfigurationAggregators' {Maybe Natural
limit :: Maybe Natural
$sel:limit:DescribeConfigurationAggregators' :: DescribeConfigurationAggregators -> Maybe Natural
limit} -> Maybe Natural
limit) (\s :: DescribeConfigurationAggregators
s@DescribeConfigurationAggregators' {} Maybe Natural
a -> DescribeConfigurationAggregators
s {$sel:limit:DescribeConfigurationAggregators' :: Maybe Natural
limit = Maybe Natural
a} :: DescribeConfigurationAggregators)

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

instance
  Core.AWSPager
    DescribeConfigurationAggregators
  where
  page :: DescribeConfigurationAggregators
-> AWSResponse DescribeConfigurationAggregators
-> Maybe DescribeConfigurationAggregators
page DescribeConfigurationAggregators
rq AWSResponse DescribeConfigurationAggregators
rs
    | forall a. AWSTruncated a => a -> Bool
Core.stop
        ( AWSResponse DescribeConfigurationAggregators
rs
            forall s a. s -> Getting (First a) s a -> Maybe a
Lens.^? Lens' DescribeConfigurationAggregatorsResponse (Maybe Text)
describeConfigurationAggregatorsResponse_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 DescribeConfigurationAggregators
rs
            forall s a. s -> Getting (First a) s a -> Maybe a
Lens.^? Lens'
  DescribeConfigurationAggregatorsResponse
  (Maybe [ConfigurationAggregator])
describeConfigurationAggregatorsResponse_configurationAggregators
            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.$ DescribeConfigurationAggregators
rq
          forall a b. a -> (a -> b) -> b
Prelude.& Lens' DescribeConfigurationAggregators (Maybe Text)
describeConfigurationAggregators_nextToken
          forall s t a b. ASetter s t a b -> b -> s -> t
Lens..~ AWSResponse DescribeConfigurationAggregators
rs
          forall s a. s -> Getting (First a) s a -> Maybe a
Lens.^? Lens' DescribeConfigurationAggregatorsResponse (Maybe Text)
describeConfigurationAggregatorsResponse_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
    DescribeConfigurationAggregators
  where
  type
    AWSResponse DescribeConfigurationAggregators =
      DescribeConfigurationAggregatorsResponse
  request :: (Service -> Service)
-> DescribeConfigurationAggregators
-> Request DescribeConfigurationAggregators
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 DescribeConfigurationAggregators
-> ClientResponse ClientBody
-> m (Either
        Error
        (ClientResponse (AWSResponse DescribeConfigurationAggregators)))
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 [ConfigurationAggregator]
-> Maybe Text -> Int -> DescribeConfigurationAggregatorsResponse
DescribeConfigurationAggregatorsResponse'
            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
"ConfigurationAggregators"
                            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
"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
    DescribeConfigurationAggregators
  where
  hashWithSalt :: Int -> DescribeConfigurationAggregators -> Int
hashWithSalt
    Int
_salt
    DescribeConfigurationAggregators' {Maybe Natural
Maybe [Text]
Maybe Text
nextToken :: Maybe Text
limit :: Maybe Natural
configurationAggregatorNames :: Maybe [Text]
$sel:nextToken:DescribeConfigurationAggregators' :: DescribeConfigurationAggregators -> Maybe Text
$sel:limit:DescribeConfigurationAggregators' :: DescribeConfigurationAggregators -> Maybe Natural
$sel:configurationAggregatorNames:DescribeConfigurationAggregators' :: DescribeConfigurationAggregators -> Maybe [Text]
..} =
      Int
_salt
        forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Maybe [Text]
configurationAggregatorNames
        forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Maybe Natural
limit
        forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Maybe Text
nextToken

instance
  Prelude.NFData
    DescribeConfigurationAggregators
  where
  rnf :: DescribeConfigurationAggregators -> ()
rnf DescribeConfigurationAggregators' {Maybe Natural
Maybe [Text]
Maybe Text
nextToken :: Maybe Text
limit :: Maybe Natural
configurationAggregatorNames :: Maybe [Text]
$sel:nextToken:DescribeConfigurationAggregators' :: DescribeConfigurationAggregators -> Maybe Text
$sel:limit:DescribeConfigurationAggregators' :: DescribeConfigurationAggregators -> Maybe Natural
$sel:configurationAggregatorNames:DescribeConfigurationAggregators' :: DescribeConfigurationAggregators -> Maybe [Text]
..} =
    forall a. NFData a => a -> ()
Prelude.rnf Maybe [Text]
configurationAggregatorNames
      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

instance
  Data.ToHeaders
    DescribeConfigurationAggregators
  where
  toHeaders :: DescribeConfigurationAggregators -> 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.DescribeConfigurationAggregators" ::
                          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 DescribeConfigurationAggregators where
  toJSON :: DescribeConfigurationAggregators -> Value
toJSON DescribeConfigurationAggregators' {Maybe Natural
Maybe [Text]
Maybe Text
nextToken :: Maybe Text
limit :: Maybe Natural
configurationAggregatorNames :: Maybe [Text]
$sel:nextToken:DescribeConfigurationAggregators' :: DescribeConfigurationAggregators -> Maybe Text
$sel:limit:DescribeConfigurationAggregators' :: DescribeConfigurationAggregators -> Maybe Natural
$sel:configurationAggregatorNames:DescribeConfigurationAggregators' :: DescribeConfigurationAggregators -> Maybe [Text]
..} =
    [Pair] -> Value
Data.object
      ( forall a. [Maybe a] -> [a]
Prelude.catMaybes
          [ (Key
"ConfigurationAggregatorNames" 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]
configurationAggregatorNames,
            (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
          ]
      )

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

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

-- | /See:/ 'newDescribeConfigurationAggregatorsResponse' smart constructor.
data DescribeConfigurationAggregatorsResponse = DescribeConfigurationAggregatorsResponse'
  { -- | Returns a ConfigurationAggregators object.
    DescribeConfigurationAggregatorsResponse
-> Maybe [ConfigurationAggregator]
configurationAggregators :: Prelude.Maybe [ConfigurationAggregator],
    -- | The @nextToken@ string returned on a previous page that you use to get
    -- the next page of results in a paginated response.
    DescribeConfigurationAggregatorsResponse -> Maybe Text
nextToken :: Prelude.Maybe Prelude.Text,
    -- | The response's http status code.
    DescribeConfigurationAggregatorsResponse -> Int
httpStatus :: Prelude.Int
  }
  deriving (DescribeConfigurationAggregatorsResponse
-> DescribeConfigurationAggregatorsResponse -> Bool
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: DescribeConfigurationAggregatorsResponse
-> DescribeConfigurationAggregatorsResponse -> Bool
$c/= :: DescribeConfigurationAggregatorsResponse
-> DescribeConfigurationAggregatorsResponse -> Bool
== :: DescribeConfigurationAggregatorsResponse
-> DescribeConfigurationAggregatorsResponse -> Bool
$c== :: DescribeConfigurationAggregatorsResponse
-> DescribeConfigurationAggregatorsResponse -> Bool
Prelude.Eq, ReadPrec [DescribeConfigurationAggregatorsResponse]
ReadPrec DescribeConfigurationAggregatorsResponse
Int -> ReadS DescribeConfigurationAggregatorsResponse
ReadS [DescribeConfigurationAggregatorsResponse]
forall a.
(Int -> ReadS a)
-> ReadS [a] -> ReadPrec a -> ReadPrec [a] -> Read a
readListPrec :: ReadPrec [DescribeConfigurationAggregatorsResponse]
$creadListPrec :: ReadPrec [DescribeConfigurationAggregatorsResponse]
readPrec :: ReadPrec DescribeConfigurationAggregatorsResponse
$creadPrec :: ReadPrec DescribeConfigurationAggregatorsResponse
readList :: ReadS [DescribeConfigurationAggregatorsResponse]
$creadList :: ReadS [DescribeConfigurationAggregatorsResponse]
readsPrec :: Int -> ReadS DescribeConfigurationAggregatorsResponse
$creadsPrec :: Int -> ReadS DescribeConfigurationAggregatorsResponse
Prelude.Read, Int -> DescribeConfigurationAggregatorsResponse -> ShowS
[DescribeConfigurationAggregatorsResponse] -> ShowS
DescribeConfigurationAggregatorsResponse -> String
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [DescribeConfigurationAggregatorsResponse] -> ShowS
$cshowList :: [DescribeConfigurationAggregatorsResponse] -> ShowS
show :: DescribeConfigurationAggregatorsResponse -> String
$cshow :: DescribeConfigurationAggregatorsResponse -> String
showsPrec :: Int -> DescribeConfigurationAggregatorsResponse -> ShowS
$cshowsPrec :: Int -> DescribeConfigurationAggregatorsResponse -> ShowS
Prelude.Show, forall x.
Rep DescribeConfigurationAggregatorsResponse x
-> DescribeConfigurationAggregatorsResponse
forall x.
DescribeConfigurationAggregatorsResponse
-> Rep DescribeConfigurationAggregatorsResponse x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cto :: forall x.
Rep DescribeConfigurationAggregatorsResponse x
-> DescribeConfigurationAggregatorsResponse
$cfrom :: forall x.
DescribeConfigurationAggregatorsResponse
-> Rep DescribeConfigurationAggregatorsResponse x
Prelude.Generic)

-- |
-- Create a value of 'DescribeConfigurationAggregatorsResponse' 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:
--
-- 'configurationAggregators', 'describeConfigurationAggregatorsResponse_configurationAggregators' - Returns a ConfigurationAggregators object.
--
-- 'nextToken', 'describeConfigurationAggregatorsResponse_nextToken' - The @nextToken@ string returned on a previous page that you use to get
-- the next page of results in a paginated response.
--
-- 'httpStatus', 'describeConfigurationAggregatorsResponse_httpStatus' - The response's http status code.
newDescribeConfigurationAggregatorsResponse ::
  -- | 'httpStatus'
  Prelude.Int ->
  DescribeConfigurationAggregatorsResponse
newDescribeConfigurationAggregatorsResponse :: Int -> DescribeConfigurationAggregatorsResponse
newDescribeConfigurationAggregatorsResponse
  Int
pHttpStatus_ =
    DescribeConfigurationAggregatorsResponse'
      { $sel:configurationAggregators:DescribeConfigurationAggregatorsResponse' :: Maybe [ConfigurationAggregator]
configurationAggregators =
          forall a. Maybe a
Prelude.Nothing,
        $sel:nextToken:DescribeConfigurationAggregatorsResponse' :: Maybe Text
nextToken = forall a. Maybe a
Prelude.Nothing,
        $sel:httpStatus:DescribeConfigurationAggregatorsResponse' :: Int
httpStatus = Int
pHttpStatus_
      }

-- | Returns a ConfigurationAggregators object.
describeConfigurationAggregatorsResponse_configurationAggregators :: Lens.Lens' DescribeConfigurationAggregatorsResponse (Prelude.Maybe [ConfigurationAggregator])
describeConfigurationAggregatorsResponse_configurationAggregators :: Lens'
  DescribeConfigurationAggregatorsResponse
  (Maybe [ConfigurationAggregator])
describeConfigurationAggregatorsResponse_configurationAggregators = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\DescribeConfigurationAggregatorsResponse' {Maybe [ConfigurationAggregator]
configurationAggregators :: Maybe [ConfigurationAggregator]
$sel:configurationAggregators:DescribeConfigurationAggregatorsResponse' :: DescribeConfigurationAggregatorsResponse
-> Maybe [ConfigurationAggregator]
configurationAggregators} -> Maybe [ConfigurationAggregator]
configurationAggregators) (\s :: DescribeConfigurationAggregatorsResponse
s@DescribeConfigurationAggregatorsResponse' {} Maybe [ConfigurationAggregator]
a -> DescribeConfigurationAggregatorsResponse
s {$sel:configurationAggregators:DescribeConfigurationAggregatorsResponse' :: Maybe [ConfigurationAggregator]
configurationAggregators = Maybe [ConfigurationAggregator]
a} :: DescribeConfigurationAggregatorsResponse) 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 @nextToken@ string returned on a previous page that you use to get
-- the next page of results in a paginated response.
describeConfigurationAggregatorsResponse_nextToken :: Lens.Lens' DescribeConfigurationAggregatorsResponse (Prelude.Maybe Prelude.Text)
describeConfigurationAggregatorsResponse_nextToken :: Lens' DescribeConfigurationAggregatorsResponse (Maybe Text)
describeConfigurationAggregatorsResponse_nextToken = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\DescribeConfigurationAggregatorsResponse' {Maybe Text
nextToken :: Maybe Text
$sel:nextToken:DescribeConfigurationAggregatorsResponse' :: DescribeConfigurationAggregatorsResponse -> Maybe Text
nextToken} -> Maybe Text
nextToken) (\s :: DescribeConfigurationAggregatorsResponse
s@DescribeConfigurationAggregatorsResponse' {} Maybe Text
a -> DescribeConfigurationAggregatorsResponse
s {$sel:nextToken:DescribeConfigurationAggregatorsResponse' :: Maybe Text
nextToken = Maybe Text
a} :: DescribeConfigurationAggregatorsResponse)

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

instance
  Prelude.NFData
    DescribeConfigurationAggregatorsResponse
  where
  rnf :: DescribeConfigurationAggregatorsResponse -> ()
rnf DescribeConfigurationAggregatorsResponse' {Int
Maybe [ConfigurationAggregator]
Maybe Text
httpStatus :: Int
nextToken :: Maybe Text
configurationAggregators :: Maybe [ConfigurationAggregator]
$sel:httpStatus:DescribeConfigurationAggregatorsResponse' :: DescribeConfigurationAggregatorsResponse -> Int
$sel:nextToken:DescribeConfigurationAggregatorsResponse' :: DescribeConfigurationAggregatorsResponse -> Maybe Text
$sel:configurationAggregators:DescribeConfigurationAggregatorsResponse' :: DescribeConfigurationAggregatorsResponse
-> Maybe [ConfigurationAggregator]
..} =
    forall a. NFData a => a -> ()
Prelude.rnf Maybe [ConfigurationAggregator]
configurationAggregators
      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