{-# 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.BatchGetAggregateResourceConfig
-- 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 current configuration items for resources that are present
-- in your Config aggregator. The operation also returns a list of
-- resources that are not processed in the current request. If there are no
-- unprocessed resources, the operation returns an empty
-- @unprocessedResourceIdentifiers@ list.
--
-- -   The API does not return results for deleted resources.
--
-- -   The API does not return tags and relationships.
module Amazonka.Config.BatchGetAggregateResourceConfig
  ( -- * Creating a Request
    BatchGetAggregateResourceConfig (..),
    newBatchGetAggregateResourceConfig,

    -- * Request Lenses
    batchGetAggregateResourceConfig_configurationAggregatorName,
    batchGetAggregateResourceConfig_resourceIdentifiers,

    -- * Destructuring the Response
    BatchGetAggregateResourceConfigResponse (..),
    newBatchGetAggregateResourceConfigResponse,

    -- * Response Lenses
    batchGetAggregateResourceConfigResponse_baseConfigurationItems,
    batchGetAggregateResourceConfigResponse_unprocessedResourceIdentifiers,
    batchGetAggregateResourceConfigResponse_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:/ 'newBatchGetAggregateResourceConfig' smart constructor.
data BatchGetAggregateResourceConfig = BatchGetAggregateResourceConfig'
  { -- | The name of the configuration aggregator.
    BatchGetAggregateResourceConfig -> Text
configurationAggregatorName :: Prelude.Text,
    -- | A list of aggregate ResourceIdentifiers objects.
    BatchGetAggregateResourceConfig
-> NonEmpty AggregateResourceIdentifier
resourceIdentifiers :: Prelude.NonEmpty AggregateResourceIdentifier
  }
  deriving (BatchGetAggregateResourceConfig
-> BatchGetAggregateResourceConfig -> Bool
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: BatchGetAggregateResourceConfig
-> BatchGetAggregateResourceConfig -> Bool
$c/= :: BatchGetAggregateResourceConfig
-> BatchGetAggregateResourceConfig -> Bool
== :: BatchGetAggregateResourceConfig
-> BatchGetAggregateResourceConfig -> Bool
$c== :: BatchGetAggregateResourceConfig
-> BatchGetAggregateResourceConfig -> Bool
Prelude.Eq, ReadPrec [BatchGetAggregateResourceConfig]
ReadPrec BatchGetAggregateResourceConfig
Int -> ReadS BatchGetAggregateResourceConfig
ReadS [BatchGetAggregateResourceConfig]
forall a.
(Int -> ReadS a)
-> ReadS [a] -> ReadPrec a -> ReadPrec [a] -> Read a
readListPrec :: ReadPrec [BatchGetAggregateResourceConfig]
$creadListPrec :: ReadPrec [BatchGetAggregateResourceConfig]
readPrec :: ReadPrec BatchGetAggregateResourceConfig
$creadPrec :: ReadPrec BatchGetAggregateResourceConfig
readList :: ReadS [BatchGetAggregateResourceConfig]
$creadList :: ReadS [BatchGetAggregateResourceConfig]
readsPrec :: Int -> ReadS BatchGetAggregateResourceConfig
$creadsPrec :: Int -> ReadS BatchGetAggregateResourceConfig
Prelude.Read, Int -> BatchGetAggregateResourceConfig -> ShowS
[BatchGetAggregateResourceConfig] -> ShowS
BatchGetAggregateResourceConfig -> String
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [BatchGetAggregateResourceConfig] -> ShowS
$cshowList :: [BatchGetAggregateResourceConfig] -> ShowS
show :: BatchGetAggregateResourceConfig -> String
$cshow :: BatchGetAggregateResourceConfig -> String
showsPrec :: Int -> BatchGetAggregateResourceConfig -> ShowS
$cshowsPrec :: Int -> BatchGetAggregateResourceConfig -> ShowS
Prelude.Show, forall x.
Rep BatchGetAggregateResourceConfig x
-> BatchGetAggregateResourceConfig
forall x.
BatchGetAggregateResourceConfig
-> Rep BatchGetAggregateResourceConfig x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cto :: forall x.
Rep BatchGetAggregateResourceConfig x
-> BatchGetAggregateResourceConfig
$cfrom :: forall x.
BatchGetAggregateResourceConfig
-> Rep BatchGetAggregateResourceConfig x
Prelude.Generic)

-- |
-- Create a value of 'BatchGetAggregateResourceConfig' 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:
--
-- 'configurationAggregatorName', 'batchGetAggregateResourceConfig_configurationAggregatorName' - The name of the configuration aggregator.
--
-- 'resourceIdentifiers', 'batchGetAggregateResourceConfig_resourceIdentifiers' - A list of aggregate ResourceIdentifiers objects.
newBatchGetAggregateResourceConfig ::
  -- | 'configurationAggregatorName'
  Prelude.Text ->
  -- | 'resourceIdentifiers'
  Prelude.NonEmpty AggregateResourceIdentifier ->
  BatchGetAggregateResourceConfig
newBatchGetAggregateResourceConfig :: Text
-> NonEmpty AggregateResourceIdentifier
-> BatchGetAggregateResourceConfig
newBatchGetAggregateResourceConfig
  Text
pConfigurationAggregatorName_
  NonEmpty AggregateResourceIdentifier
pResourceIdentifiers_ =
    BatchGetAggregateResourceConfig'
      { $sel:configurationAggregatorName:BatchGetAggregateResourceConfig' :: Text
configurationAggregatorName =
          Text
pConfigurationAggregatorName_,
        $sel:resourceIdentifiers:BatchGetAggregateResourceConfig' :: NonEmpty AggregateResourceIdentifier
resourceIdentifiers =
          forall s t a b. (Coercible s a, Coercible t b) => Iso s t a b
Lens.coerced
            forall t b. AReview t b -> b -> t
Lens.# NonEmpty AggregateResourceIdentifier
pResourceIdentifiers_
      }

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

-- | A list of aggregate ResourceIdentifiers objects.
batchGetAggregateResourceConfig_resourceIdentifiers :: Lens.Lens' BatchGetAggregateResourceConfig (Prelude.NonEmpty AggregateResourceIdentifier)
batchGetAggregateResourceConfig_resourceIdentifiers :: Lens'
  BatchGetAggregateResourceConfig
  (NonEmpty AggregateResourceIdentifier)
batchGetAggregateResourceConfig_resourceIdentifiers = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\BatchGetAggregateResourceConfig' {NonEmpty AggregateResourceIdentifier
resourceIdentifiers :: NonEmpty AggregateResourceIdentifier
$sel:resourceIdentifiers:BatchGetAggregateResourceConfig' :: BatchGetAggregateResourceConfig
-> NonEmpty AggregateResourceIdentifier
resourceIdentifiers} -> NonEmpty AggregateResourceIdentifier
resourceIdentifiers) (\s :: BatchGetAggregateResourceConfig
s@BatchGetAggregateResourceConfig' {} NonEmpty AggregateResourceIdentifier
a -> BatchGetAggregateResourceConfig
s {$sel:resourceIdentifiers:BatchGetAggregateResourceConfig' :: NonEmpty AggregateResourceIdentifier
resourceIdentifiers = NonEmpty AggregateResourceIdentifier
a} :: BatchGetAggregateResourceConfig) forall b c a. (b -> c) -> (a -> b) -> a -> c
Prelude.. forall s t a b. (Coercible s a, Coercible t b) => Iso s t a b
Lens.coerced

instance
  Core.AWSRequest
    BatchGetAggregateResourceConfig
  where
  type
    AWSResponse BatchGetAggregateResourceConfig =
      BatchGetAggregateResourceConfigResponse
  request :: (Service -> Service)
-> BatchGetAggregateResourceConfig
-> Request BatchGetAggregateResourceConfig
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 BatchGetAggregateResourceConfig
-> ClientResponse ClientBody
-> m (Either
        Error
        (ClientResponse (AWSResponse BatchGetAggregateResourceConfig)))
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 [BaseConfigurationItem]
-> Maybe [AggregateResourceIdentifier]
-> Int
-> BatchGetAggregateResourceConfigResponse
BatchGetAggregateResourceConfigResponse'
            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
"BaseConfigurationItems"
                            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
"UnprocessedResourceIdentifiers"
                            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))
      )

instance
  Prelude.Hashable
    BatchGetAggregateResourceConfig
  where
  hashWithSalt :: Int -> BatchGetAggregateResourceConfig -> Int
hashWithSalt
    Int
_salt
    BatchGetAggregateResourceConfig' {NonEmpty AggregateResourceIdentifier
Text
resourceIdentifiers :: NonEmpty AggregateResourceIdentifier
configurationAggregatorName :: Text
$sel:resourceIdentifiers:BatchGetAggregateResourceConfig' :: BatchGetAggregateResourceConfig
-> NonEmpty AggregateResourceIdentifier
$sel:configurationAggregatorName:BatchGetAggregateResourceConfig' :: BatchGetAggregateResourceConfig -> Text
..} =
      Int
_salt
        forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Text
configurationAggregatorName
        forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` NonEmpty AggregateResourceIdentifier
resourceIdentifiers

instance
  Prelude.NFData
    BatchGetAggregateResourceConfig
  where
  rnf :: BatchGetAggregateResourceConfig -> ()
rnf BatchGetAggregateResourceConfig' {NonEmpty AggregateResourceIdentifier
Text
resourceIdentifiers :: NonEmpty AggregateResourceIdentifier
configurationAggregatorName :: Text
$sel:resourceIdentifiers:BatchGetAggregateResourceConfig' :: BatchGetAggregateResourceConfig
-> NonEmpty AggregateResourceIdentifier
$sel:configurationAggregatorName:BatchGetAggregateResourceConfig' :: BatchGetAggregateResourceConfig -> Text
..} =
    forall a. NFData a => a -> ()
Prelude.rnf Text
configurationAggregatorName
      seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf NonEmpty AggregateResourceIdentifier
resourceIdentifiers

instance
  Data.ToHeaders
    BatchGetAggregateResourceConfig
  where
  toHeaders :: BatchGetAggregateResourceConfig -> 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.BatchGetAggregateResourceConfig" ::
                          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 BatchGetAggregateResourceConfig where
  toJSON :: BatchGetAggregateResourceConfig -> Value
toJSON BatchGetAggregateResourceConfig' {NonEmpty AggregateResourceIdentifier
Text
resourceIdentifiers :: NonEmpty AggregateResourceIdentifier
configurationAggregatorName :: Text
$sel:resourceIdentifiers:BatchGetAggregateResourceConfig' :: BatchGetAggregateResourceConfig
-> NonEmpty AggregateResourceIdentifier
$sel:configurationAggregatorName:BatchGetAggregateResourceConfig' :: BatchGetAggregateResourceConfig -> Text
..} =
    [Pair] -> Value
Data.object
      ( forall a. [Maybe a] -> [a]
Prelude.catMaybes
          [ forall a. a -> Maybe a
Prelude.Just
              ( Key
"ConfigurationAggregatorName"
                  forall kv v. (KeyValue kv, ToJSON v) => Key -> v -> kv
Data..= Text
configurationAggregatorName
              ),
            forall a. a -> Maybe a
Prelude.Just
              (Key
"ResourceIdentifiers" forall kv v. (KeyValue kv, ToJSON v) => Key -> v -> kv
Data..= NonEmpty AggregateResourceIdentifier
resourceIdentifiers)
          ]
      )

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

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

-- | /See:/ 'newBatchGetAggregateResourceConfigResponse' smart constructor.
data BatchGetAggregateResourceConfigResponse = BatchGetAggregateResourceConfigResponse'
  { -- | A list that contains the current configuration of one or more resources.
    BatchGetAggregateResourceConfigResponse
-> Maybe [BaseConfigurationItem]
baseConfigurationItems :: Prelude.Maybe [BaseConfigurationItem],
    -- | A list of resource identifiers that were not processed with current
    -- scope. The list is empty if all the resources are processed.
    BatchGetAggregateResourceConfigResponse
-> Maybe [AggregateResourceIdentifier]
unprocessedResourceIdentifiers :: Prelude.Maybe [AggregateResourceIdentifier],
    -- | The response's http status code.
    BatchGetAggregateResourceConfigResponse -> Int
httpStatus :: Prelude.Int
  }
  deriving (BatchGetAggregateResourceConfigResponse
-> BatchGetAggregateResourceConfigResponse -> Bool
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: BatchGetAggregateResourceConfigResponse
-> BatchGetAggregateResourceConfigResponse -> Bool
$c/= :: BatchGetAggregateResourceConfigResponse
-> BatchGetAggregateResourceConfigResponse -> Bool
== :: BatchGetAggregateResourceConfigResponse
-> BatchGetAggregateResourceConfigResponse -> Bool
$c== :: BatchGetAggregateResourceConfigResponse
-> BatchGetAggregateResourceConfigResponse -> Bool
Prelude.Eq, ReadPrec [BatchGetAggregateResourceConfigResponse]
ReadPrec BatchGetAggregateResourceConfigResponse
Int -> ReadS BatchGetAggregateResourceConfigResponse
ReadS [BatchGetAggregateResourceConfigResponse]
forall a.
(Int -> ReadS a)
-> ReadS [a] -> ReadPrec a -> ReadPrec [a] -> Read a
readListPrec :: ReadPrec [BatchGetAggregateResourceConfigResponse]
$creadListPrec :: ReadPrec [BatchGetAggregateResourceConfigResponse]
readPrec :: ReadPrec BatchGetAggregateResourceConfigResponse
$creadPrec :: ReadPrec BatchGetAggregateResourceConfigResponse
readList :: ReadS [BatchGetAggregateResourceConfigResponse]
$creadList :: ReadS [BatchGetAggregateResourceConfigResponse]
readsPrec :: Int -> ReadS BatchGetAggregateResourceConfigResponse
$creadsPrec :: Int -> ReadS BatchGetAggregateResourceConfigResponse
Prelude.Read, Int -> BatchGetAggregateResourceConfigResponse -> ShowS
[BatchGetAggregateResourceConfigResponse] -> ShowS
BatchGetAggregateResourceConfigResponse -> String
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [BatchGetAggregateResourceConfigResponse] -> ShowS
$cshowList :: [BatchGetAggregateResourceConfigResponse] -> ShowS
show :: BatchGetAggregateResourceConfigResponse -> String
$cshow :: BatchGetAggregateResourceConfigResponse -> String
showsPrec :: Int -> BatchGetAggregateResourceConfigResponse -> ShowS
$cshowsPrec :: Int -> BatchGetAggregateResourceConfigResponse -> ShowS
Prelude.Show, forall x.
Rep BatchGetAggregateResourceConfigResponse x
-> BatchGetAggregateResourceConfigResponse
forall x.
BatchGetAggregateResourceConfigResponse
-> Rep BatchGetAggregateResourceConfigResponse x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cto :: forall x.
Rep BatchGetAggregateResourceConfigResponse x
-> BatchGetAggregateResourceConfigResponse
$cfrom :: forall x.
BatchGetAggregateResourceConfigResponse
-> Rep BatchGetAggregateResourceConfigResponse x
Prelude.Generic)

-- |
-- Create a value of 'BatchGetAggregateResourceConfigResponse' 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:
--
-- 'baseConfigurationItems', 'batchGetAggregateResourceConfigResponse_baseConfigurationItems' - A list that contains the current configuration of one or more resources.
--
-- 'unprocessedResourceIdentifiers', 'batchGetAggregateResourceConfigResponse_unprocessedResourceIdentifiers' - A list of resource identifiers that were not processed with current
-- scope. The list is empty if all the resources are processed.
--
-- 'httpStatus', 'batchGetAggregateResourceConfigResponse_httpStatus' - The response's http status code.
newBatchGetAggregateResourceConfigResponse ::
  -- | 'httpStatus'
  Prelude.Int ->
  BatchGetAggregateResourceConfigResponse
newBatchGetAggregateResourceConfigResponse :: Int -> BatchGetAggregateResourceConfigResponse
newBatchGetAggregateResourceConfigResponse
  Int
pHttpStatus_ =
    BatchGetAggregateResourceConfigResponse'
      { $sel:baseConfigurationItems:BatchGetAggregateResourceConfigResponse' :: Maybe [BaseConfigurationItem]
baseConfigurationItems =
          forall a. Maybe a
Prelude.Nothing,
        $sel:unprocessedResourceIdentifiers:BatchGetAggregateResourceConfigResponse' :: Maybe [AggregateResourceIdentifier]
unprocessedResourceIdentifiers =
          forall a. Maybe a
Prelude.Nothing,
        $sel:httpStatus:BatchGetAggregateResourceConfigResponse' :: Int
httpStatus = Int
pHttpStatus_
      }

-- | A list that contains the current configuration of one or more resources.
batchGetAggregateResourceConfigResponse_baseConfigurationItems :: Lens.Lens' BatchGetAggregateResourceConfigResponse (Prelude.Maybe [BaseConfigurationItem])
batchGetAggregateResourceConfigResponse_baseConfigurationItems :: Lens'
  BatchGetAggregateResourceConfigResponse
  (Maybe [BaseConfigurationItem])
batchGetAggregateResourceConfigResponse_baseConfigurationItems = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\BatchGetAggregateResourceConfigResponse' {Maybe [BaseConfigurationItem]
baseConfigurationItems :: Maybe [BaseConfigurationItem]
$sel:baseConfigurationItems:BatchGetAggregateResourceConfigResponse' :: BatchGetAggregateResourceConfigResponse
-> Maybe [BaseConfigurationItem]
baseConfigurationItems} -> Maybe [BaseConfigurationItem]
baseConfigurationItems) (\s :: BatchGetAggregateResourceConfigResponse
s@BatchGetAggregateResourceConfigResponse' {} Maybe [BaseConfigurationItem]
a -> BatchGetAggregateResourceConfigResponse
s {$sel:baseConfigurationItems:BatchGetAggregateResourceConfigResponse' :: Maybe [BaseConfigurationItem]
baseConfigurationItems = Maybe [BaseConfigurationItem]
a} :: BatchGetAggregateResourceConfigResponse) 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

-- | A list of resource identifiers that were not processed with current
-- scope. The list is empty if all the resources are processed.
batchGetAggregateResourceConfigResponse_unprocessedResourceIdentifiers :: Lens.Lens' BatchGetAggregateResourceConfigResponse (Prelude.Maybe [AggregateResourceIdentifier])
batchGetAggregateResourceConfigResponse_unprocessedResourceIdentifiers :: Lens'
  BatchGetAggregateResourceConfigResponse
  (Maybe [AggregateResourceIdentifier])
batchGetAggregateResourceConfigResponse_unprocessedResourceIdentifiers = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\BatchGetAggregateResourceConfigResponse' {Maybe [AggregateResourceIdentifier]
unprocessedResourceIdentifiers :: Maybe [AggregateResourceIdentifier]
$sel:unprocessedResourceIdentifiers:BatchGetAggregateResourceConfigResponse' :: BatchGetAggregateResourceConfigResponse
-> Maybe [AggregateResourceIdentifier]
unprocessedResourceIdentifiers} -> Maybe [AggregateResourceIdentifier]
unprocessedResourceIdentifiers) (\s :: BatchGetAggregateResourceConfigResponse
s@BatchGetAggregateResourceConfigResponse' {} Maybe [AggregateResourceIdentifier]
a -> BatchGetAggregateResourceConfigResponse
s {$sel:unprocessedResourceIdentifiers:BatchGetAggregateResourceConfigResponse' :: Maybe [AggregateResourceIdentifier]
unprocessedResourceIdentifiers = Maybe [AggregateResourceIdentifier]
a} :: BatchGetAggregateResourceConfigResponse) 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.
batchGetAggregateResourceConfigResponse_httpStatus :: Lens.Lens' BatchGetAggregateResourceConfigResponse Prelude.Int
batchGetAggregateResourceConfigResponse_httpStatus :: Lens' BatchGetAggregateResourceConfigResponse Int
batchGetAggregateResourceConfigResponse_httpStatus = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\BatchGetAggregateResourceConfigResponse' {Int
httpStatus :: Int
$sel:httpStatus:BatchGetAggregateResourceConfigResponse' :: BatchGetAggregateResourceConfigResponse -> Int
httpStatus} -> Int
httpStatus) (\s :: BatchGetAggregateResourceConfigResponse
s@BatchGetAggregateResourceConfigResponse' {} Int
a -> BatchGetAggregateResourceConfigResponse
s {$sel:httpStatus:BatchGetAggregateResourceConfigResponse' :: Int
httpStatus = Int
a} :: BatchGetAggregateResourceConfigResponse)

instance
  Prelude.NFData
    BatchGetAggregateResourceConfigResponse
  where
  rnf :: BatchGetAggregateResourceConfigResponse -> ()
rnf BatchGetAggregateResourceConfigResponse' {Int
Maybe [BaseConfigurationItem]
Maybe [AggregateResourceIdentifier]
httpStatus :: Int
unprocessedResourceIdentifiers :: Maybe [AggregateResourceIdentifier]
baseConfigurationItems :: Maybe [BaseConfigurationItem]
$sel:httpStatus:BatchGetAggregateResourceConfigResponse' :: BatchGetAggregateResourceConfigResponse -> Int
$sel:unprocessedResourceIdentifiers:BatchGetAggregateResourceConfigResponse' :: BatchGetAggregateResourceConfigResponse
-> Maybe [AggregateResourceIdentifier]
$sel:baseConfigurationItems:BatchGetAggregateResourceConfigResponse' :: BatchGetAggregateResourceConfigResponse
-> Maybe [BaseConfigurationItem]
..} =
    forall a. NFData a => a -> ()
Prelude.rnf Maybe [BaseConfigurationItem]
baseConfigurationItems
      seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf Maybe [AggregateResourceIdentifier]
unprocessedResourceIdentifiers
      seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf Int
httpStatus