{-# 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.BatchGetResourceConfig
-- 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 @BaseConfigurationItem@ for one or more requested resources.
-- 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 unprocessedResourceKeys list.
--
-- -   The API does not return results for deleted resources.
--
-- -   The API does not return any tags for the requested resources. This
--     information is filtered out of the supplementaryConfiguration
--     section of the API response.
module Amazonka.Config.BatchGetResourceConfig
  ( -- * Creating a Request
    BatchGetResourceConfig (..),
    newBatchGetResourceConfig,

    -- * Request Lenses
    batchGetResourceConfig_resourceKeys,

    -- * Destructuring the Response
    BatchGetResourceConfigResponse (..),
    newBatchGetResourceConfigResponse,

    -- * Response Lenses
    batchGetResourceConfigResponse_baseConfigurationItems,
    batchGetResourceConfigResponse_unprocessedResourceKeys,
    batchGetResourceConfigResponse_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:/ 'newBatchGetResourceConfig' smart constructor.
data BatchGetResourceConfig = BatchGetResourceConfig'
  { -- | A list of resource keys to be processed with the current request. Each
    -- element in the list consists of the resource type and resource ID.
    BatchGetResourceConfig -> NonEmpty ResourceKey
resourceKeys :: Prelude.NonEmpty ResourceKey
  }
  deriving (BatchGetResourceConfig -> BatchGetResourceConfig -> Bool
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: BatchGetResourceConfig -> BatchGetResourceConfig -> Bool
$c/= :: BatchGetResourceConfig -> BatchGetResourceConfig -> Bool
== :: BatchGetResourceConfig -> BatchGetResourceConfig -> Bool
$c== :: BatchGetResourceConfig -> BatchGetResourceConfig -> Bool
Prelude.Eq, ReadPrec [BatchGetResourceConfig]
ReadPrec BatchGetResourceConfig
Int -> ReadS BatchGetResourceConfig
ReadS [BatchGetResourceConfig]
forall a.
(Int -> ReadS a)
-> ReadS [a] -> ReadPrec a -> ReadPrec [a] -> Read a
readListPrec :: ReadPrec [BatchGetResourceConfig]
$creadListPrec :: ReadPrec [BatchGetResourceConfig]
readPrec :: ReadPrec BatchGetResourceConfig
$creadPrec :: ReadPrec BatchGetResourceConfig
readList :: ReadS [BatchGetResourceConfig]
$creadList :: ReadS [BatchGetResourceConfig]
readsPrec :: Int -> ReadS BatchGetResourceConfig
$creadsPrec :: Int -> ReadS BatchGetResourceConfig
Prelude.Read, Int -> BatchGetResourceConfig -> ShowS
[BatchGetResourceConfig] -> ShowS
BatchGetResourceConfig -> String
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [BatchGetResourceConfig] -> ShowS
$cshowList :: [BatchGetResourceConfig] -> ShowS
show :: BatchGetResourceConfig -> String
$cshow :: BatchGetResourceConfig -> String
showsPrec :: Int -> BatchGetResourceConfig -> ShowS
$cshowsPrec :: Int -> BatchGetResourceConfig -> ShowS
Prelude.Show, forall x. Rep BatchGetResourceConfig x -> BatchGetResourceConfig
forall x. BatchGetResourceConfig -> Rep BatchGetResourceConfig x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cto :: forall x. Rep BatchGetResourceConfig x -> BatchGetResourceConfig
$cfrom :: forall x. BatchGetResourceConfig -> Rep BatchGetResourceConfig x
Prelude.Generic)

-- |
-- Create a value of 'BatchGetResourceConfig' 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:
--
-- 'resourceKeys', 'batchGetResourceConfig_resourceKeys' - A list of resource keys to be processed with the current request. Each
-- element in the list consists of the resource type and resource ID.
newBatchGetResourceConfig ::
  -- | 'resourceKeys'
  Prelude.NonEmpty ResourceKey ->
  BatchGetResourceConfig
newBatchGetResourceConfig :: NonEmpty ResourceKey -> BatchGetResourceConfig
newBatchGetResourceConfig NonEmpty ResourceKey
pResourceKeys_ =
  BatchGetResourceConfig'
    { $sel:resourceKeys:BatchGetResourceConfig' :: NonEmpty ResourceKey
resourceKeys =
        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 ResourceKey
pResourceKeys_
    }

-- | A list of resource keys to be processed with the current request. Each
-- element in the list consists of the resource type and resource ID.
batchGetResourceConfig_resourceKeys :: Lens.Lens' BatchGetResourceConfig (Prelude.NonEmpty ResourceKey)
batchGetResourceConfig_resourceKeys :: Lens' BatchGetResourceConfig (NonEmpty ResourceKey)
batchGetResourceConfig_resourceKeys = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\BatchGetResourceConfig' {NonEmpty ResourceKey
resourceKeys :: NonEmpty ResourceKey
$sel:resourceKeys:BatchGetResourceConfig' :: BatchGetResourceConfig -> NonEmpty ResourceKey
resourceKeys} -> NonEmpty ResourceKey
resourceKeys) (\s :: BatchGetResourceConfig
s@BatchGetResourceConfig' {} NonEmpty ResourceKey
a -> BatchGetResourceConfig
s {$sel:resourceKeys:BatchGetResourceConfig' :: NonEmpty ResourceKey
resourceKeys = NonEmpty ResourceKey
a} :: BatchGetResourceConfig) 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 BatchGetResourceConfig where
  type
    AWSResponse BatchGetResourceConfig =
      BatchGetResourceConfigResponse
  request :: (Service -> Service)
-> BatchGetResourceConfig -> Request BatchGetResourceConfig
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 BatchGetResourceConfig
-> ClientResponse ClientBody
-> m (Either
        Error (ClientResponse (AWSResponse BatchGetResourceConfig)))
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 (NonEmpty ResourceKey)
-> Int
-> BatchGetResourceConfigResponse
BatchGetResourceConfigResponse'
            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
"unprocessedResourceKeys")
            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 BatchGetResourceConfig where
  hashWithSalt :: Int -> BatchGetResourceConfig -> Int
hashWithSalt Int
_salt BatchGetResourceConfig' {NonEmpty ResourceKey
resourceKeys :: NonEmpty ResourceKey
$sel:resourceKeys:BatchGetResourceConfig' :: BatchGetResourceConfig -> NonEmpty ResourceKey
..} =
    Int
_salt forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` NonEmpty ResourceKey
resourceKeys

instance Prelude.NFData BatchGetResourceConfig where
  rnf :: BatchGetResourceConfig -> ()
rnf BatchGetResourceConfig' {NonEmpty ResourceKey
resourceKeys :: NonEmpty ResourceKey
$sel:resourceKeys:BatchGetResourceConfig' :: BatchGetResourceConfig -> NonEmpty ResourceKey
..} =
    forall a. NFData a => a -> ()
Prelude.rnf NonEmpty ResourceKey
resourceKeys

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

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

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

-- | /See:/ 'newBatchGetResourceConfigResponse' smart constructor.
data BatchGetResourceConfigResponse = BatchGetResourceConfigResponse'
  { -- | A list that contains the current configuration of one or more resources.
    BatchGetResourceConfigResponse -> Maybe [BaseConfigurationItem]
baseConfigurationItems :: Prelude.Maybe [BaseConfigurationItem],
    -- | A list of resource keys that were not processed with the current
    -- response. The unprocessesResourceKeys value is in the same form as
    -- ResourceKeys, so the value can be directly provided to a subsequent
    -- BatchGetResourceConfig operation. If there are no unprocessed resource
    -- keys, the response contains an empty unprocessedResourceKeys list.
    BatchGetResourceConfigResponse -> Maybe (NonEmpty ResourceKey)
unprocessedResourceKeys :: Prelude.Maybe (Prelude.NonEmpty ResourceKey),
    -- | The response's http status code.
    BatchGetResourceConfigResponse -> Int
httpStatus :: Prelude.Int
  }
  deriving (BatchGetResourceConfigResponse
-> BatchGetResourceConfigResponse -> Bool
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: BatchGetResourceConfigResponse
-> BatchGetResourceConfigResponse -> Bool
$c/= :: BatchGetResourceConfigResponse
-> BatchGetResourceConfigResponse -> Bool
== :: BatchGetResourceConfigResponse
-> BatchGetResourceConfigResponse -> Bool
$c== :: BatchGetResourceConfigResponse
-> BatchGetResourceConfigResponse -> Bool
Prelude.Eq, ReadPrec [BatchGetResourceConfigResponse]
ReadPrec BatchGetResourceConfigResponse
Int -> ReadS BatchGetResourceConfigResponse
ReadS [BatchGetResourceConfigResponse]
forall a.
(Int -> ReadS a)
-> ReadS [a] -> ReadPrec a -> ReadPrec [a] -> Read a
readListPrec :: ReadPrec [BatchGetResourceConfigResponse]
$creadListPrec :: ReadPrec [BatchGetResourceConfigResponse]
readPrec :: ReadPrec BatchGetResourceConfigResponse
$creadPrec :: ReadPrec BatchGetResourceConfigResponse
readList :: ReadS [BatchGetResourceConfigResponse]
$creadList :: ReadS [BatchGetResourceConfigResponse]
readsPrec :: Int -> ReadS BatchGetResourceConfigResponse
$creadsPrec :: Int -> ReadS BatchGetResourceConfigResponse
Prelude.Read, Int -> BatchGetResourceConfigResponse -> ShowS
[BatchGetResourceConfigResponse] -> ShowS
BatchGetResourceConfigResponse -> String
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [BatchGetResourceConfigResponse] -> ShowS
$cshowList :: [BatchGetResourceConfigResponse] -> ShowS
show :: BatchGetResourceConfigResponse -> String
$cshow :: BatchGetResourceConfigResponse -> String
showsPrec :: Int -> BatchGetResourceConfigResponse -> ShowS
$cshowsPrec :: Int -> BatchGetResourceConfigResponse -> ShowS
Prelude.Show, forall x.
Rep BatchGetResourceConfigResponse x
-> BatchGetResourceConfigResponse
forall x.
BatchGetResourceConfigResponse
-> Rep BatchGetResourceConfigResponse x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cto :: forall x.
Rep BatchGetResourceConfigResponse x
-> BatchGetResourceConfigResponse
$cfrom :: forall x.
BatchGetResourceConfigResponse
-> Rep BatchGetResourceConfigResponse x
Prelude.Generic)

-- |
-- Create a value of 'BatchGetResourceConfigResponse' 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', 'batchGetResourceConfigResponse_baseConfigurationItems' - A list that contains the current configuration of one or more resources.
--
-- 'unprocessedResourceKeys', 'batchGetResourceConfigResponse_unprocessedResourceKeys' - A list of resource keys that were not processed with the current
-- response. The unprocessesResourceKeys value is in the same form as
-- ResourceKeys, so the value can be directly provided to a subsequent
-- BatchGetResourceConfig operation. If there are no unprocessed resource
-- keys, the response contains an empty unprocessedResourceKeys list.
--
-- 'httpStatus', 'batchGetResourceConfigResponse_httpStatus' - The response's http status code.
newBatchGetResourceConfigResponse ::
  -- | 'httpStatus'
  Prelude.Int ->
  BatchGetResourceConfigResponse
newBatchGetResourceConfigResponse :: Int -> BatchGetResourceConfigResponse
newBatchGetResourceConfigResponse Int
pHttpStatus_ =
  BatchGetResourceConfigResponse'
    { $sel:baseConfigurationItems:BatchGetResourceConfigResponse' :: Maybe [BaseConfigurationItem]
baseConfigurationItems =
        forall a. Maybe a
Prelude.Nothing,
      $sel:unprocessedResourceKeys:BatchGetResourceConfigResponse' :: Maybe (NonEmpty ResourceKey)
unprocessedResourceKeys = forall a. Maybe a
Prelude.Nothing,
      $sel:httpStatus:BatchGetResourceConfigResponse' :: Int
httpStatus = Int
pHttpStatus_
    }

-- | A list that contains the current configuration of one or more resources.
batchGetResourceConfigResponse_baseConfigurationItems :: Lens.Lens' BatchGetResourceConfigResponse (Prelude.Maybe [BaseConfigurationItem])
batchGetResourceConfigResponse_baseConfigurationItems :: Lens'
  BatchGetResourceConfigResponse (Maybe [BaseConfigurationItem])
batchGetResourceConfigResponse_baseConfigurationItems = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\BatchGetResourceConfigResponse' {Maybe [BaseConfigurationItem]
baseConfigurationItems :: Maybe [BaseConfigurationItem]
$sel:baseConfigurationItems:BatchGetResourceConfigResponse' :: BatchGetResourceConfigResponse -> Maybe [BaseConfigurationItem]
baseConfigurationItems} -> Maybe [BaseConfigurationItem]
baseConfigurationItems) (\s :: BatchGetResourceConfigResponse
s@BatchGetResourceConfigResponse' {} Maybe [BaseConfigurationItem]
a -> BatchGetResourceConfigResponse
s {$sel:baseConfigurationItems:BatchGetResourceConfigResponse' :: Maybe [BaseConfigurationItem]
baseConfigurationItems = Maybe [BaseConfigurationItem]
a} :: BatchGetResourceConfigResponse) 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 keys that were not processed with the current
-- response. The unprocessesResourceKeys value is in the same form as
-- ResourceKeys, so the value can be directly provided to a subsequent
-- BatchGetResourceConfig operation. If there are no unprocessed resource
-- keys, the response contains an empty unprocessedResourceKeys list.
batchGetResourceConfigResponse_unprocessedResourceKeys :: Lens.Lens' BatchGetResourceConfigResponse (Prelude.Maybe (Prelude.NonEmpty ResourceKey))
batchGetResourceConfigResponse_unprocessedResourceKeys :: Lens' BatchGetResourceConfigResponse (Maybe (NonEmpty ResourceKey))
batchGetResourceConfigResponse_unprocessedResourceKeys = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\BatchGetResourceConfigResponse' {Maybe (NonEmpty ResourceKey)
unprocessedResourceKeys :: Maybe (NonEmpty ResourceKey)
$sel:unprocessedResourceKeys:BatchGetResourceConfigResponse' :: BatchGetResourceConfigResponse -> Maybe (NonEmpty ResourceKey)
unprocessedResourceKeys} -> Maybe (NonEmpty ResourceKey)
unprocessedResourceKeys) (\s :: BatchGetResourceConfigResponse
s@BatchGetResourceConfigResponse' {} Maybe (NonEmpty ResourceKey)
a -> BatchGetResourceConfigResponse
s {$sel:unprocessedResourceKeys:BatchGetResourceConfigResponse' :: Maybe (NonEmpty ResourceKey)
unprocessedResourceKeys = Maybe (NonEmpty ResourceKey)
a} :: BatchGetResourceConfigResponse) 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.
batchGetResourceConfigResponse_httpStatus :: Lens.Lens' BatchGetResourceConfigResponse Prelude.Int
batchGetResourceConfigResponse_httpStatus :: Lens' BatchGetResourceConfigResponse Int
batchGetResourceConfigResponse_httpStatus = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\BatchGetResourceConfigResponse' {Int
httpStatus :: Int
$sel:httpStatus:BatchGetResourceConfigResponse' :: BatchGetResourceConfigResponse -> Int
httpStatus} -> Int
httpStatus) (\s :: BatchGetResourceConfigResponse
s@BatchGetResourceConfigResponse' {} Int
a -> BatchGetResourceConfigResponse
s {$sel:httpStatus:BatchGetResourceConfigResponse' :: Int
httpStatus = Int
a} :: BatchGetResourceConfigResponse)

instance
  Prelude.NFData
    BatchGetResourceConfigResponse
  where
  rnf :: BatchGetResourceConfigResponse -> ()
rnf BatchGetResourceConfigResponse' {Int
Maybe [BaseConfigurationItem]
Maybe (NonEmpty ResourceKey)
httpStatus :: Int
unprocessedResourceKeys :: Maybe (NonEmpty ResourceKey)
baseConfigurationItems :: Maybe [BaseConfigurationItem]
$sel:httpStatus:BatchGetResourceConfigResponse' :: BatchGetResourceConfigResponse -> Int
$sel:unprocessedResourceKeys:BatchGetResourceConfigResponse' :: BatchGetResourceConfigResponse -> Maybe (NonEmpty ResourceKey)
$sel:baseConfigurationItems:BatchGetResourceConfigResponse' :: BatchGetResourceConfigResponse -> 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 (NonEmpty ResourceKey)
unprocessedResourceKeys
      seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf Int
httpStatus