{-# 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.Discovery.ListConfigurations
-- Copyright   : (c) 2013-2023 Brendan Hay
-- License     : Mozilla Public License, v. 2.0.
-- Maintainer  : Brendan Hay
-- Stability   : auto-generated
-- Portability : non-portable (GHC extensions)
--
-- Retrieves a list of configuration items as specified by the value passed
-- to the required parameter @configurationType@. Optional filtering may be
-- applied to refine search results.
--
-- This operation returns paginated results.
module Amazonka.Discovery.ListConfigurations
  ( -- * Creating a Request
    ListConfigurations (..),
    newListConfigurations,

    -- * Request Lenses
    listConfigurations_filters,
    listConfigurations_maxResults,
    listConfigurations_nextToken,
    listConfigurations_orderBy,
    listConfigurations_configurationType,

    -- * Destructuring the Response
    ListConfigurationsResponse (..),
    newListConfigurationsResponse,

    -- * Response Lenses
    listConfigurationsResponse_configurations,
    listConfigurationsResponse_nextToken,
    listConfigurationsResponse_httpStatus,
  )
where

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

-- | /See:/ 'newListConfigurations' smart constructor.
data ListConfigurations = ListConfigurations'
  { -- | You can filter the request using various logical operators and a
    -- /key/-/value/ format. For example:
    --
    -- @{\"key\": \"serverType\", \"value\": \"webServer\"}@
    --
    -- For a complete list of filter options and guidance about using them with
    -- this action, see
    -- <https://docs.aws.amazon.com/application-discovery/latest/userguide/discovery-api-queries.html#ListConfigurations Using the ListConfigurations Action>
    -- in the /Amazon Web Services Application Discovery Service User Guide/.
    ListConfigurations -> Maybe [Filter]
filters :: Prelude.Maybe [Filter],
    -- | The total number of items to return. The maximum value is 100.
    ListConfigurations -> Maybe Int
maxResults :: Prelude.Maybe Prelude.Int,
    -- | Token to retrieve the next set of results. For example, if a previous
    -- call to ListConfigurations returned 100 items, but you set
    -- @ListConfigurationsRequest$maxResults@ to 10, you received a set of 10
    -- results along with a token. Use that token in this query to get the next
    -- set of 10.
    ListConfigurations -> Maybe Text
nextToken :: Prelude.Maybe Prelude.Text,
    -- | Certain filter criteria return output that can be sorted in ascending or
    -- descending order. For a list of output characteristics for each filter,
    -- see
    -- <https://docs.aws.amazon.com/application-discovery/latest/userguide/discovery-api-queries.html#ListConfigurations Using the ListConfigurations Action>
    -- in the /Amazon Web Services Application Discovery Service User Guide/.
    ListConfigurations -> Maybe [OrderByElement]
orderBy :: Prelude.Maybe [OrderByElement],
    -- | A valid configuration identified by Application Discovery Service.
    ListConfigurations -> ConfigurationItemType
configurationType :: ConfigurationItemType
  }
  deriving (ListConfigurations -> ListConfigurations -> Bool
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: ListConfigurations -> ListConfigurations -> Bool
$c/= :: ListConfigurations -> ListConfigurations -> Bool
== :: ListConfigurations -> ListConfigurations -> Bool
$c== :: ListConfigurations -> ListConfigurations -> Bool
Prelude.Eq, ReadPrec [ListConfigurations]
ReadPrec ListConfigurations
Int -> ReadS ListConfigurations
ReadS [ListConfigurations]
forall a.
(Int -> ReadS a)
-> ReadS [a] -> ReadPrec a -> ReadPrec [a] -> Read a
readListPrec :: ReadPrec [ListConfigurations]
$creadListPrec :: ReadPrec [ListConfigurations]
readPrec :: ReadPrec ListConfigurations
$creadPrec :: ReadPrec ListConfigurations
readList :: ReadS [ListConfigurations]
$creadList :: ReadS [ListConfigurations]
readsPrec :: Int -> ReadS ListConfigurations
$creadsPrec :: Int -> ReadS ListConfigurations
Prelude.Read, Int -> ListConfigurations -> ShowS
[ListConfigurations] -> ShowS
ListConfigurations -> String
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [ListConfigurations] -> ShowS
$cshowList :: [ListConfigurations] -> ShowS
show :: ListConfigurations -> String
$cshow :: ListConfigurations -> String
showsPrec :: Int -> ListConfigurations -> ShowS
$cshowsPrec :: Int -> ListConfigurations -> ShowS
Prelude.Show, forall x. Rep ListConfigurations x -> ListConfigurations
forall x. ListConfigurations -> Rep ListConfigurations x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cto :: forall x. Rep ListConfigurations x -> ListConfigurations
$cfrom :: forall x. ListConfigurations -> Rep ListConfigurations x
Prelude.Generic)

-- |
-- Create a value of 'ListConfigurations' 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', 'listConfigurations_filters' - You can filter the request using various logical operators and a
-- /key/-/value/ format. For example:
--
-- @{\"key\": \"serverType\", \"value\": \"webServer\"}@
--
-- For a complete list of filter options and guidance about using them with
-- this action, see
-- <https://docs.aws.amazon.com/application-discovery/latest/userguide/discovery-api-queries.html#ListConfigurations Using the ListConfigurations Action>
-- in the /Amazon Web Services Application Discovery Service User Guide/.
--
-- 'maxResults', 'listConfigurations_maxResults' - The total number of items to return. The maximum value is 100.
--
-- 'nextToken', 'listConfigurations_nextToken' - Token to retrieve the next set of results. For example, if a previous
-- call to ListConfigurations returned 100 items, but you set
-- @ListConfigurationsRequest$maxResults@ to 10, you received a set of 10
-- results along with a token. Use that token in this query to get the next
-- set of 10.
--
-- 'orderBy', 'listConfigurations_orderBy' - Certain filter criteria return output that can be sorted in ascending or
-- descending order. For a list of output characteristics for each filter,
-- see
-- <https://docs.aws.amazon.com/application-discovery/latest/userguide/discovery-api-queries.html#ListConfigurations Using the ListConfigurations Action>
-- in the /Amazon Web Services Application Discovery Service User Guide/.
--
-- 'configurationType', 'listConfigurations_configurationType' - A valid configuration identified by Application Discovery Service.
newListConfigurations ::
  -- | 'configurationType'
  ConfigurationItemType ->
  ListConfigurations
newListConfigurations :: ConfigurationItemType -> ListConfigurations
newListConfigurations ConfigurationItemType
pConfigurationType_ =
  ListConfigurations'
    { $sel:filters:ListConfigurations' :: Maybe [Filter]
filters = forall a. Maybe a
Prelude.Nothing,
      $sel:maxResults:ListConfigurations' :: Maybe Int
maxResults = forall a. Maybe a
Prelude.Nothing,
      $sel:nextToken:ListConfigurations' :: Maybe Text
nextToken = forall a. Maybe a
Prelude.Nothing,
      $sel:orderBy:ListConfigurations' :: Maybe [OrderByElement]
orderBy = forall a. Maybe a
Prelude.Nothing,
      $sel:configurationType:ListConfigurations' :: ConfigurationItemType
configurationType = ConfigurationItemType
pConfigurationType_
    }

-- | You can filter the request using various logical operators and a
-- /key/-/value/ format. For example:
--
-- @{\"key\": \"serverType\", \"value\": \"webServer\"}@
--
-- For a complete list of filter options and guidance about using them with
-- this action, see
-- <https://docs.aws.amazon.com/application-discovery/latest/userguide/discovery-api-queries.html#ListConfigurations Using the ListConfigurations Action>
-- in the /Amazon Web Services Application Discovery Service User Guide/.
listConfigurations_filters :: Lens.Lens' ListConfigurations (Prelude.Maybe [Filter])
listConfigurations_filters :: Lens' ListConfigurations (Maybe [Filter])
listConfigurations_filters = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\ListConfigurations' {Maybe [Filter]
filters :: Maybe [Filter]
$sel:filters:ListConfigurations' :: ListConfigurations -> Maybe [Filter]
filters} -> Maybe [Filter]
filters) (\s :: ListConfigurations
s@ListConfigurations' {} Maybe [Filter]
a -> ListConfigurations
s {$sel:filters:ListConfigurations' :: Maybe [Filter]
filters = Maybe [Filter]
a} :: ListConfigurations) 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 total number of items to return. The maximum value is 100.
listConfigurations_maxResults :: Lens.Lens' ListConfigurations (Prelude.Maybe Prelude.Int)
listConfigurations_maxResults :: Lens' ListConfigurations (Maybe Int)
listConfigurations_maxResults = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\ListConfigurations' {Maybe Int
maxResults :: Maybe Int
$sel:maxResults:ListConfigurations' :: ListConfigurations -> Maybe Int
maxResults} -> Maybe Int
maxResults) (\s :: ListConfigurations
s@ListConfigurations' {} Maybe Int
a -> ListConfigurations
s {$sel:maxResults:ListConfigurations' :: Maybe Int
maxResults = Maybe Int
a} :: ListConfigurations)

-- | Token to retrieve the next set of results. For example, if a previous
-- call to ListConfigurations returned 100 items, but you set
-- @ListConfigurationsRequest$maxResults@ to 10, you received a set of 10
-- results along with a token. Use that token in this query to get the next
-- set of 10.
listConfigurations_nextToken :: Lens.Lens' ListConfigurations (Prelude.Maybe Prelude.Text)
listConfigurations_nextToken :: Lens' ListConfigurations (Maybe Text)
listConfigurations_nextToken = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\ListConfigurations' {Maybe Text
nextToken :: Maybe Text
$sel:nextToken:ListConfigurations' :: ListConfigurations -> Maybe Text
nextToken} -> Maybe Text
nextToken) (\s :: ListConfigurations
s@ListConfigurations' {} Maybe Text
a -> ListConfigurations
s {$sel:nextToken:ListConfigurations' :: Maybe Text
nextToken = Maybe Text
a} :: ListConfigurations)

-- | Certain filter criteria return output that can be sorted in ascending or
-- descending order. For a list of output characteristics for each filter,
-- see
-- <https://docs.aws.amazon.com/application-discovery/latest/userguide/discovery-api-queries.html#ListConfigurations Using the ListConfigurations Action>
-- in the /Amazon Web Services Application Discovery Service User Guide/.
listConfigurations_orderBy :: Lens.Lens' ListConfigurations (Prelude.Maybe [OrderByElement])
listConfigurations_orderBy :: Lens' ListConfigurations (Maybe [OrderByElement])
listConfigurations_orderBy = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\ListConfigurations' {Maybe [OrderByElement]
orderBy :: Maybe [OrderByElement]
$sel:orderBy:ListConfigurations' :: ListConfigurations -> Maybe [OrderByElement]
orderBy} -> Maybe [OrderByElement]
orderBy) (\s :: ListConfigurations
s@ListConfigurations' {} Maybe [OrderByElement]
a -> ListConfigurations
s {$sel:orderBy:ListConfigurations' :: Maybe [OrderByElement]
orderBy = Maybe [OrderByElement]
a} :: ListConfigurations) 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 valid configuration identified by Application Discovery Service.
listConfigurations_configurationType :: Lens.Lens' ListConfigurations ConfigurationItemType
listConfigurations_configurationType :: Lens' ListConfigurations ConfigurationItemType
listConfigurations_configurationType = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\ListConfigurations' {ConfigurationItemType
configurationType :: ConfigurationItemType
$sel:configurationType:ListConfigurations' :: ListConfigurations -> ConfigurationItemType
configurationType} -> ConfigurationItemType
configurationType) (\s :: ListConfigurations
s@ListConfigurations' {} ConfigurationItemType
a -> ListConfigurations
s {$sel:configurationType:ListConfigurations' :: ConfigurationItemType
configurationType = ConfigurationItemType
a} :: ListConfigurations)

instance Core.AWSPager ListConfigurations where
  page :: ListConfigurations
-> AWSResponse ListConfigurations -> Maybe ListConfigurations
page ListConfigurations
rq AWSResponse ListConfigurations
rs
    | forall a. AWSTruncated a => a -> Bool
Core.stop
        ( AWSResponse ListConfigurations
rs
            forall s a. s -> Getting (First a) s a -> Maybe a
Lens.^? Lens' ListConfigurationsResponse (Maybe Text)
listConfigurationsResponse_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 ListConfigurations
rs
            forall s a. s -> Getting (First a) s a -> Maybe a
Lens.^? Lens' ListConfigurationsResponse (Maybe [HashMap Text Text])
listConfigurationsResponse_configurations
            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.$ ListConfigurations
rq
          forall a b. a -> (a -> b) -> b
Prelude.& Lens' ListConfigurations (Maybe Text)
listConfigurations_nextToken
          forall s t a b. ASetter s t a b -> b -> s -> t
Lens..~ AWSResponse ListConfigurations
rs
          forall s a. s -> Getting (First a) s a -> Maybe a
Lens.^? Lens' ListConfigurationsResponse (Maybe Text)
listConfigurationsResponse_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 ListConfigurations where
  type
    AWSResponse ListConfigurations =
      ListConfigurationsResponse
  request :: (Service -> Service)
-> ListConfigurations -> Request ListConfigurations
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 ListConfigurations
-> ClientResponse ClientBody
-> m (Either
        Error (ClientResponse (AWSResponse ListConfigurations)))
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 [HashMap Text Text]
-> Maybe Text -> Int -> ListConfigurationsResponse
ListConfigurationsResponse'
            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
"configurations" 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 ListConfigurations where
  hashWithSalt :: Int -> ListConfigurations -> Int
hashWithSalt Int
_salt ListConfigurations' {Maybe Int
Maybe [Filter]
Maybe [OrderByElement]
Maybe Text
ConfigurationItemType
configurationType :: ConfigurationItemType
orderBy :: Maybe [OrderByElement]
nextToken :: Maybe Text
maxResults :: Maybe Int
filters :: Maybe [Filter]
$sel:configurationType:ListConfigurations' :: ListConfigurations -> ConfigurationItemType
$sel:orderBy:ListConfigurations' :: ListConfigurations -> Maybe [OrderByElement]
$sel:nextToken:ListConfigurations' :: ListConfigurations -> Maybe Text
$sel:maxResults:ListConfigurations' :: ListConfigurations -> Maybe Int
$sel:filters:ListConfigurations' :: ListConfigurations -> Maybe [Filter]
..} =
    Int
_salt
      forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Maybe [Filter]
filters
      forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Maybe Int
maxResults
      forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Maybe Text
nextToken
      forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Maybe [OrderByElement]
orderBy
      forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` ConfigurationItemType
configurationType

instance Prelude.NFData ListConfigurations where
  rnf :: ListConfigurations -> ()
rnf ListConfigurations' {Maybe Int
Maybe [Filter]
Maybe [OrderByElement]
Maybe Text
ConfigurationItemType
configurationType :: ConfigurationItemType
orderBy :: Maybe [OrderByElement]
nextToken :: Maybe Text
maxResults :: Maybe Int
filters :: Maybe [Filter]
$sel:configurationType:ListConfigurations' :: ListConfigurations -> ConfigurationItemType
$sel:orderBy:ListConfigurations' :: ListConfigurations -> Maybe [OrderByElement]
$sel:nextToken:ListConfigurations' :: ListConfigurations -> Maybe Text
$sel:maxResults:ListConfigurations' :: ListConfigurations -> Maybe Int
$sel:filters:ListConfigurations' :: ListConfigurations -> Maybe [Filter]
..} =
    forall a. NFData a => a -> ()
Prelude.rnf Maybe [Filter]
filters
      seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf Maybe Int
maxResults
      seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf Maybe Text
nextToken
      seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf Maybe [OrderByElement]
orderBy
      seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf ConfigurationItemType
configurationType

instance Data.ToHeaders ListConfigurations where
  toHeaders :: ListConfigurations -> 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
"AWSPoseidonService_V2015_11_01.ListConfigurations" ::
                          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 ListConfigurations where
  toJSON :: ListConfigurations -> Value
toJSON ListConfigurations' {Maybe Int
Maybe [Filter]
Maybe [OrderByElement]
Maybe Text
ConfigurationItemType
configurationType :: ConfigurationItemType
orderBy :: Maybe [OrderByElement]
nextToken :: Maybe Text
maxResults :: Maybe Int
filters :: Maybe [Filter]
$sel:configurationType:ListConfigurations' :: ListConfigurations -> ConfigurationItemType
$sel:orderBy:ListConfigurations' :: ListConfigurations -> Maybe [OrderByElement]
$sel:nextToken:ListConfigurations' :: ListConfigurations -> Maybe Text
$sel:maxResults:ListConfigurations' :: ListConfigurations -> Maybe Int
$sel:filters:ListConfigurations' :: ListConfigurations -> Maybe [Filter]
..} =
    [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 [Filter]
filters,
            (Key
"maxResults" forall kv v. (KeyValue kv, ToJSON v) => Key -> v -> kv
Data..=) forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
Prelude.<$> Maybe Int
maxResults,
            (Key
"nextToken" forall kv v. (KeyValue kv, ToJSON v) => Key -> v -> kv
Data..=) forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
Prelude.<$> Maybe Text
nextToken,
            (Key
"orderBy" 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 [OrderByElement]
orderBy,
            forall a. a -> Maybe a
Prelude.Just
              (Key
"configurationType" forall kv v. (KeyValue kv, ToJSON v) => Key -> v -> kv
Data..= ConfigurationItemType
configurationType)
          ]
      )

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

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

-- | /See:/ 'newListConfigurationsResponse' smart constructor.
data ListConfigurationsResponse = ListConfigurationsResponse'
  { -- | Returns configuration details, including the configuration ID, attribute
    -- names, and attribute values.
    ListConfigurationsResponse -> Maybe [HashMap Text Text]
configurations :: Prelude.Maybe [Prelude.HashMap Prelude.Text Prelude.Text],
    -- | Token to retrieve the next set of results. For example, if your call to
    -- ListConfigurations returned 100 items, but you set
    -- @ListConfigurationsRequest$maxResults@ to 10, you received a set of 10
    -- results along with this token. Use this token in the next query to
    -- retrieve the next set of 10.
    ListConfigurationsResponse -> Maybe Text
nextToken :: Prelude.Maybe Prelude.Text,
    -- | The response's http status code.
    ListConfigurationsResponse -> Int
httpStatus :: Prelude.Int
  }
  deriving (ListConfigurationsResponse -> ListConfigurationsResponse -> Bool
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: ListConfigurationsResponse -> ListConfigurationsResponse -> Bool
$c/= :: ListConfigurationsResponse -> ListConfigurationsResponse -> Bool
== :: ListConfigurationsResponse -> ListConfigurationsResponse -> Bool
$c== :: ListConfigurationsResponse -> ListConfigurationsResponse -> Bool
Prelude.Eq, ReadPrec [ListConfigurationsResponse]
ReadPrec ListConfigurationsResponse
Int -> ReadS ListConfigurationsResponse
ReadS [ListConfigurationsResponse]
forall a.
(Int -> ReadS a)
-> ReadS [a] -> ReadPrec a -> ReadPrec [a] -> Read a
readListPrec :: ReadPrec [ListConfigurationsResponse]
$creadListPrec :: ReadPrec [ListConfigurationsResponse]
readPrec :: ReadPrec ListConfigurationsResponse
$creadPrec :: ReadPrec ListConfigurationsResponse
readList :: ReadS [ListConfigurationsResponse]
$creadList :: ReadS [ListConfigurationsResponse]
readsPrec :: Int -> ReadS ListConfigurationsResponse
$creadsPrec :: Int -> ReadS ListConfigurationsResponse
Prelude.Read, Int -> ListConfigurationsResponse -> ShowS
[ListConfigurationsResponse] -> ShowS
ListConfigurationsResponse -> String
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [ListConfigurationsResponse] -> ShowS
$cshowList :: [ListConfigurationsResponse] -> ShowS
show :: ListConfigurationsResponse -> String
$cshow :: ListConfigurationsResponse -> String
showsPrec :: Int -> ListConfigurationsResponse -> ShowS
$cshowsPrec :: Int -> ListConfigurationsResponse -> ShowS
Prelude.Show, forall x.
Rep ListConfigurationsResponse x -> ListConfigurationsResponse
forall x.
ListConfigurationsResponse -> Rep ListConfigurationsResponse x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cto :: forall x.
Rep ListConfigurationsResponse x -> ListConfigurationsResponse
$cfrom :: forall x.
ListConfigurationsResponse -> Rep ListConfigurationsResponse x
Prelude.Generic)

-- |
-- Create a value of 'ListConfigurationsResponse' 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:
--
-- 'configurations', 'listConfigurationsResponse_configurations' - Returns configuration details, including the configuration ID, attribute
-- names, and attribute values.
--
-- 'nextToken', 'listConfigurationsResponse_nextToken' - Token to retrieve the next set of results. For example, if your call to
-- ListConfigurations returned 100 items, but you set
-- @ListConfigurationsRequest$maxResults@ to 10, you received a set of 10
-- results along with this token. Use this token in the next query to
-- retrieve the next set of 10.
--
-- 'httpStatus', 'listConfigurationsResponse_httpStatus' - The response's http status code.
newListConfigurationsResponse ::
  -- | 'httpStatus'
  Prelude.Int ->
  ListConfigurationsResponse
newListConfigurationsResponse :: Int -> ListConfigurationsResponse
newListConfigurationsResponse Int
pHttpStatus_ =
  ListConfigurationsResponse'
    { $sel:configurations:ListConfigurationsResponse' :: Maybe [HashMap Text Text]
configurations =
        forall a. Maybe a
Prelude.Nothing,
      $sel:nextToken:ListConfigurationsResponse' :: Maybe Text
nextToken = forall a. Maybe a
Prelude.Nothing,
      $sel:httpStatus:ListConfigurationsResponse' :: Int
httpStatus = Int
pHttpStatus_
    }

-- | Returns configuration details, including the configuration ID, attribute
-- names, and attribute values.
listConfigurationsResponse_configurations :: Lens.Lens' ListConfigurationsResponse (Prelude.Maybe [Prelude.HashMap Prelude.Text Prelude.Text])
listConfigurationsResponse_configurations :: Lens' ListConfigurationsResponse (Maybe [HashMap Text Text])
listConfigurationsResponse_configurations = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\ListConfigurationsResponse' {Maybe [HashMap Text Text]
configurations :: Maybe [HashMap Text Text]
$sel:configurations:ListConfigurationsResponse' :: ListConfigurationsResponse -> Maybe [HashMap Text Text]
configurations} -> Maybe [HashMap Text Text]
configurations) (\s :: ListConfigurationsResponse
s@ListConfigurationsResponse' {} Maybe [HashMap Text Text]
a -> ListConfigurationsResponse
s {$sel:configurations:ListConfigurationsResponse' :: Maybe [HashMap Text Text]
configurations = Maybe [HashMap Text Text]
a} :: ListConfigurationsResponse) 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

-- | Token to retrieve the next set of results. For example, if your call to
-- ListConfigurations returned 100 items, but you set
-- @ListConfigurationsRequest$maxResults@ to 10, you received a set of 10
-- results along with this token. Use this token in the next query to
-- retrieve the next set of 10.
listConfigurationsResponse_nextToken :: Lens.Lens' ListConfigurationsResponse (Prelude.Maybe Prelude.Text)
listConfigurationsResponse_nextToken :: Lens' ListConfigurationsResponse (Maybe Text)
listConfigurationsResponse_nextToken = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\ListConfigurationsResponse' {Maybe Text
nextToken :: Maybe Text
$sel:nextToken:ListConfigurationsResponse' :: ListConfigurationsResponse -> Maybe Text
nextToken} -> Maybe Text
nextToken) (\s :: ListConfigurationsResponse
s@ListConfigurationsResponse' {} Maybe Text
a -> ListConfigurationsResponse
s {$sel:nextToken:ListConfigurationsResponse' :: Maybe Text
nextToken = Maybe Text
a} :: ListConfigurationsResponse)

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

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