{-# 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.SES.ListConfigurationSets
-- Copyright   : (c) 2013-2023 Brendan Hay
-- License     : Mozilla Public License, v. 2.0.
-- Maintainer  : Brendan Hay
-- Stability   : auto-generated
-- Portability : non-portable (GHC extensions)
--
-- Provides a list of the configuration sets associated with your Amazon
-- SES account in the current AWS Region. For information about using
-- configuration sets, see
-- <https://docs.aws.amazon.com/ses/latest/DeveloperGuide/monitor-sending-activity.html Monitoring Your Amazon SES Sending Activity>
-- in the /Amazon SES Developer Guide./
--
-- You can execute this operation no more than once per second. This
-- operation will return up to 1,000 configuration sets each time it is
-- run. If your Amazon SES account has more than 1,000 configuration sets,
-- this operation will also return a NextToken element. You can then
-- execute the @ListConfigurationSets@ operation again, passing the
-- @NextToken@ parameter and the value of the NextToken element to retrieve
-- additional results.
--
-- This operation returns paginated results.
module Amazonka.SES.ListConfigurationSets
  ( -- * Creating a Request
    ListConfigurationSets (..),
    newListConfigurationSets,

    -- * Request Lenses
    listConfigurationSets_maxItems,
    listConfigurationSets_nextToken,

    -- * Destructuring the Response
    ListConfigurationSetsResponse (..),
    newListConfigurationSetsResponse,

    -- * Response Lenses
    listConfigurationSetsResponse_configurationSets,
    listConfigurationSetsResponse_nextToken,
    listConfigurationSetsResponse_httpStatus,
  )
where

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
import Amazonka.SES.Types

-- | Represents a request to list the configuration sets associated with your
-- AWS account. Configuration sets enable you to publish email sending
-- events. For information about using configuration sets, see the
-- <https://docs.aws.amazon.com/ses/latest/DeveloperGuide/monitor-sending-activity.html Amazon SES Developer Guide>.
--
-- /See:/ 'newListConfigurationSets' smart constructor.
data ListConfigurationSets = ListConfigurationSets'
  { -- | The number of configuration sets to return.
    ListConfigurationSets -> Maybe Int
maxItems :: Prelude.Maybe Prelude.Int,
    -- | A token returned from a previous call to @ListConfigurationSets@ to
    -- indicate the position of the configuration set in the configuration set
    -- list.
    ListConfigurationSets -> Maybe Text
nextToken :: Prelude.Maybe Prelude.Text
  }
  deriving (ListConfigurationSets -> ListConfigurationSets -> Bool
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: ListConfigurationSets -> ListConfigurationSets -> Bool
$c/= :: ListConfigurationSets -> ListConfigurationSets -> Bool
== :: ListConfigurationSets -> ListConfigurationSets -> Bool
$c== :: ListConfigurationSets -> ListConfigurationSets -> Bool
Prelude.Eq, ReadPrec [ListConfigurationSets]
ReadPrec ListConfigurationSets
Int -> ReadS ListConfigurationSets
ReadS [ListConfigurationSets]
forall a.
(Int -> ReadS a)
-> ReadS [a] -> ReadPrec a -> ReadPrec [a] -> Read a
readListPrec :: ReadPrec [ListConfigurationSets]
$creadListPrec :: ReadPrec [ListConfigurationSets]
readPrec :: ReadPrec ListConfigurationSets
$creadPrec :: ReadPrec ListConfigurationSets
readList :: ReadS [ListConfigurationSets]
$creadList :: ReadS [ListConfigurationSets]
readsPrec :: Int -> ReadS ListConfigurationSets
$creadsPrec :: Int -> ReadS ListConfigurationSets
Prelude.Read, Int -> ListConfigurationSets -> ShowS
[ListConfigurationSets] -> ShowS
ListConfigurationSets -> String
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [ListConfigurationSets] -> ShowS
$cshowList :: [ListConfigurationSets] -> ShowS
show :: ListConfigurationSets -> String
$cshow :: ListConfigurationSets -> String
showsPrec :: Int -> ListConfigurationSets -> ShowS
$cshowsPrec :: Int -> ListConfigurationSets -> ShowS
Prelude.Show, forall x. Rep ListConfigurationSets x -> ListConfigurationSets
forall x. ListConfigurationSets -> Rep ListConfigurationSets x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cto :: forall x. Rep ListConfigurationSets x -> ListConfigurationSets
$cfrom :: forall x. ListConfigurationSets -> Rep ListConfigurationSets x
Prelude.Generic)

-- |
-- Create a value of 'ListConfigurationSets' 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:
--
-- 'maxItems', 'listConfigurationSets_maxItems' - The number of configuration sets to return.
--
-- 'nextToken', 'listConfigurationSets_nextToken' - A token returned from a previous call to @ListConfigurationSets@ to
-- indicate the position of the configuration set in the configuration set
-- list.
newListConfigurationSets ::
  ListConfigurationSets
newListConfigurationSets :: ListConfigurationSets
newListConfigurationSets =
  ListConfigurationSets'
    { $sel:maxItems:ListConfigurationSets' :: Maybe Int
maxItems = forall a. Maybe a
Prelude.Nothing,
      $sel:nextToken:ListConfigurationSets' :: Maybe Text
nextToken = forall a. Maybe a
Prelude.Nothing
    }

-- | The number of configuration sets to return.
listConfigurationSets_maxItems :: Lens.Lens' ListConfigurationSets (Prelude.Maybe Prelude.Int)
listConfigurationSets_maxItems :: Lens' ListConfigurationSets (Maybe Int)
listConfigurationSets_maxItems = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\ListConfigurationSets' {Maybe Int
maxItems :: Maybe Int
$sel:maxItems:ListConfigurationSets' :: ListConfigurationSets -> Maybe Int
maxItems} -> Maybe Int
maxItems) (\s :: ListConfigurationSets
s@ListConfigurationSets' {} Maybe Int
a -> ListConfigurationSets
s {$sel:maxItems:ListConfigurationSets' :: Maybe Int
maxItems = Maybe Int
a} :: ListConfigurationSets)

-- | A token returned from a previous call to @ListConfigurationSets@ to
-- indicate the position of the configuration set in the configuration set
-- list.
listConfigurationSets_nextToken :: Lens.Lens' ListConfigurationSets (Prelude.Maybe Prelude.Text)
listConfigurationSets_nextToken :: Lens' ListConfigurationSets (Maybe Text)
listConfigurationSets_nextToken = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\ListConfigurationSets' {Maybe Text
nextToken :: Maybe Text
$sel:nextToken:ListConfigurationSets' :: ListConfigurationSets -> Maybe Text
nextToken} -> Maybe Text
nextToken) (\s :: ListConfigurationSets
s@ListConfigurationSets' {} Maybe Text
a -> ListConfigurationSets
s {$sel:nextToken:ListConfigurationSets' :: Maybe Text
nextToken = Maybe Text
a} :: ListConfigurationSets)

instance Core.AWSPager ListConfigurationSets where
  page :: ListConfigurationSets
-> AWSResponse ListConfigurationSets -> Maybe ListConfigurationSets
page ListConfigurationSets
rq AWSResponse ListConfigurationSets
rs
    | forall a. AWSTruncated a => a -> Bool
Core.stop
        ( AWSResponse ListConfigurationSets
rs
            forall s a. s -> Getting (First a) s a -> Maybe a
Lens.^? Lens' ListConfigurationSetsResponse (Maybe Text)
listConfigurationSetsResponse_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 ListConfigurationSets
rs
            forall s a. s -> Getting (First a) s a -> Maybe a
Lens.^? Lens' ListConfigurationSetsResponse (Maybe [ConfigurationSet])
listConfigurationSetsResponse_configurationSets
            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.$ ListConfigurationSets
rq
          forall a b. a -> (a -> b) -> b
Prelude.& Lens' ListConfigurationSets (Maybe Text)
listConfigurationSets_nextToken
          forall s t a b. ASetter s t a b -> b -> s -> t
Lens..~ AWSResponse ListConfigurationSets
rs
          forall s a. s -> Getting (First a) s a -> Maybe a
Lens.^? Lens' ListConfigurationSetsResponse (Maybe Text)
listConfigurationSetsResponse_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 ListConfigurationSets where
  type
    AWSResponse ListConfigurationSets =
      ListConfigurationSetsResponse
  request :: (Service -> Service)
-> ListConfigurationSets -> Request ListConfigurationSets
request Service -> Service
overrides =
    forall a. ToRequest a => Service -> a -> Request a
Request.postQuery (Service -> Service
overrides Service
defaultService)
  response :: forall (m :: * -> *).
MonadResource m =>
(ByteStringLazy -> IO ByteStringLazy)
-> Service
-> Proxy ListConfigurationSets
-> ClientResponse ClientBody
-> m (Either
        Error (ClientResponse (AWSResponse ListConfigurationSets)))
response =
    forall (m :: * -> *) a.
MonadResource m =>
Text
-> (Int
    -> ResponseHeaders -> [Node] -> Either String (AWSResponse a))
-> (ByteStringLazy -> IO ByteStringLazy)
-> Service
-> Proxy a
-> ClientResponse ClientBody
-> m (Either Error (ClientResponse (AWSResponse a)))
Response.receiveXMLWrapper
      Text
"ListConfigurationSetsResult"
      ( \Int
s ResponseHeaders
h [Node]
x ->
          Maybe [ConfigurationSet]
-> Maybe Text -> Int -> ListConfigurationSetsResponse
ListConfigurationSetsResponse'
            forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
Prelude.<$> ( [Node]
x
                            forall a. FromXML a => [Node] -> Text -> Either String (Maybe a)
Data..@? Text
"ConfigurationSets"
                            forall (f :: * -> *) a. Functor f => f (Maybe a) -> a -> f a
Core..!@ forall a. Monoid a => a
Prelude.mempty
                            forall (m :: * -> *) a b. Monad m => m a -> (a -> m b) -> m b
Prelude.>>= forall (f :: * -> *) a b.
Applicative f =>
([a] -> f b) -> [a] -> f (Maybe b)
Core.may (forall a. FromXML a => Text -> [Node] -> Either String [a]
Data.parseXMLList Text
"member")
                        )
            forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
Prelude.<*> ([Node]
x forall a. FromXML a => [Node] -> Text -> Either String (Maybe a)
Data..@? Text
"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 ListConfigurationSets where
  hashWithSalt :: Int -> ListConfigurationSets -> Int
hashWithSalt Int
_salt ListConfigurationSets' {Maybe Int
Maybe Text
nextToken :: Maybe Text
maxItems :: Maybe Int
$sel:nextToken:ListConfigurationSets' :: ListConfigurationSets -> Maybe Text
$sel:maxItems:ListConfigurationSets' :: ListConfigurationSets -> Maybe Int
..} =
    Int
_salt
      forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Maybe Int
maxItems
      forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Maybe Text
nextToken

instance Prelude.NFData ListConfigurationSets where
  rnf :: ListConfigurationSets -> ()
rnf ListConfigurationSets' {Maybe Int
Maybe Text
nextToken :: Maybe Text
maxItems :: Maybe Int
$sel:nextToken:ListConfigurationSets' :: ListConfigurationSets -> Maybe Text
$sel:maxItems:ListConfigurationSets' :: ListConfigurationSets -> Maybe Int
..} =
    forall a. NFData a => a -> ()
Prelude.rnf Maybe Int
maxItems
      seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf Maybe Text
nextToken

instance Data.ToHeaders ListConfigurationSets where
  toHeaders :: ListConfigurationSets -> ResponseHeaders
toHeaders = forall a b. a -> b -> a
Prelude.const forall a. Monoid a => a
Prelude.mempty

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

instance Data.ToQuery ListConfigurationSets where
  toQuery :: ListConfigurationSets -> QueryString
toQuery ListConfigurationSets' {Maybe Int
Maybe Text
nextToken :: Maybe Text
maxItems :: Maybe Int
$sel:nextToken:ListConfigurationSets' :: ListConfigurationSets -> Maybe Text
$sel:maxItems:ListConfigurationSets' :: ListConfigurationSets -> Maybe Int
..} =
    forall a. Monoid a => [a] -> a
Prelude.mconcat
      [ ByteString
"Action"
          forall a. ToQuery a => ByteString -> a -> QueryString
Data.=: (ByteString
"ListConfigurationSets" :: Prelude.ByteString),
        ByteString
"Version"
          forall a. ToQuery a => ByteString -> a -> QueryString
Data.=: (ByteString
"2010-12-01" :: Prelude.ByteString),
        ByteString
"MaxItems" forall a. ToQuery a => ByteString -> a -> QueryString
Data.=: Maybe Int
maxItems,
        ByteString
"NextToken" forall a. ToQuery a => ByteString -> a -> QueryString
Data.=: Maybe Text
nextToken
      ]

-- | A list of configuration sets associated with your AWS account.
-- Configuration sets enable you to publish email sending events. For
-- information about using configuration sets, see the
-- <https://docs.aws.amazon.com/ses/latest/DeveloperGuide/monitor-sending-activity.html Amazon SES Developer Guide>.
--
-- /See:/ 'newListConfigurationSetsResponse' smart constructor.
data ListConfigurationSetsResponse = ListConfigurationSetsResponse'
  { -- | A list of configuration sets.
    ListConfigurationSetsResponse -> Maybe [ConfigurationSet]
configurationSets :: Prelude.Maybe [ConfigurationSet],
    -- | A token indicating that there are additional configuration sets
    -- available to be listed. Pass this token to successive calls of
    -- @ListConfigurationSets@.
    ListConfigurationSetsResponse -> Maybe Text
nextToken :: Prelude.Maybe Prelude.Text,
    -- | The response's http status code.
    ListConfigurationSetsResponse -> Int
httpStatus :: Prelude.Int
  }
  deriving (ListConfigurationSetsResponse
-> ListConfigurationSetsResponse -> Bool
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: ListConfigurationSetsResponse
-> ListConfigurationSetsResponse -> Bool
$c/= :: ListConfigurationSetsResponse
-> ListConfigurationSetsResponse -> Bool
== :: ListConfigurationSetsResponse
-> ListConfigurationSetsResponse -> Bool
$c== :: ListConfigurationSetsResponse
-> ListConfigurationSetsResponse -> Bool
Prelude.Eq, ReadPrec [ListConfigurationSetsResponse]
ReadPrec ListConfigurationSetsResponse
Int -> ReadS ListConfigurationSetsResponse
ReadS [ListConfigurationSetsResponse]
forall a.
(Int -> ReadS a)
-> ReadS [a] -> ReadPrec a -> ReadPrec [a] -> Read a
readListPrec :: ReadPrec [ListConfigurationSetsResponse]
$creadListPrec :: ReadPrec [ListConfigurationSetsResponse]
readPrec :: ReadPrec ListConfigurationSetsResponse
$creadPrec :: ReadPrec ListConfigurationSetsResponse
readList :: ReadS [ListConfigurationSetsResponse]
$creadList :: ReadS [ListConfigurationSetsResponse]
readsPrec :: Int -> ReadS ListConfigurationSetsResponse
$creadsPrec :: Int -> ReadS ListConfigurationSetsResponse
Prelude.Read, Int -> ListConfigurationSetsResponse -> ShowS
[ListConfigurationSetsResponse] -> ShowS
ListConfigurationSetsResponse -> String
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [ListConfigurationSetsResponse] -> ShowS
$cshowList :: [ListConfigurationSetsResponse] -> ShowS
show :: ListConfigurationSetsResponse -> String
$cshow :: ListConfigurationSetsResponse -> String
showsPrec :: Int -> ListConfigurationSetsResponse -> ShowS
$cshowsPrec :: Int -> ListConfigurationSetsResponse -> ShowS
Prelude.Show, forall x.
Rep ListConfigurationSetsResponse x
-> ListConfigurationSetsResponse
forall x.
ListConfigurationSetsResponse
-> Rep ListConfigurationSetsResponse x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cto :: forall x.
Rep ListConfigurationSetsResponse x
-> ListConfigurationSetsResponse
$cfrom :: forall x.
ListConfigurationSetsResponse
-> Rep ListConfigurationSetsResponse x
Prelude.Generic)

-- |
-- Create a value of 'ListConfigurationSetsResponse' 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:
--
-- 'configurationSets', 'listConfigurationSetsResponse_configurationSets' - A list of configuration sets.
--
-- 'nextToken', 'listConfigurationSetsResponse_nextToken' - A token indicating that there are additional configuration sets
-- available to be listed. Pass this token to successive calls of
-- @ListConfigurationSets@.
--
-- 'httpStatus', 'listConfigurationSetsResponse_httpStatus' - The response's http status code.
newListConfigurationSetsResponse ::
  -- | 'httpStatus'
  Prelude.Int ->
  ListConfigurationSetsResponse
newListConfigurationSetsResponse :: Int -> ListConfigurationSetsResponse
newListConfigurationSetsResponse Int
pHttpStatus_ =
  ListConfigurationSetsResponse'
    { $sel:configurationSets:ListConfigurationSetsResponse' :: Maybe [ConfigurationSet]
configurationSets =
        forall a. Maybe a
Prelude.Nothing,
      $sel:nextToken:ListConfigurationSetsResponse' :: Maybe Text
nextToken = forall a. Maybe a
Prelude.Nothing,
      $sel:httpStatus:ListConfigurationSetsResponse' :: Int
httpStatus = Int
pHttpStatus_
    }

-- | A list of configuration sets.
listConfigurationSetsResponse_configurationSets :: Lens.Lens' ListConfigurationSetsResponse (Prelude.Maybe [ConfigurationSet])
listConfigurationSetsResponse_configurationSets :: Lens' ListConfigurationSetsResponse (Maybe [ConfigurationSet])
listConfigurationSetsResponse_configurationSets = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\ListConfigurationSetsResponse' {Maybe [ConfigurationSet]
configurationSets :: Maybe [ConfigurationSet]
$sel:configurationSets:ListConfigurationSetsResponse' :: ListConfigurationSetsResponse -> Maybe [ConfigurationSet]
configurationSets} -> Maybe [ConfigurationSet]
configurationSets) (\s :: ListConfigurationSetsResponse
s@ListConfigurationSetsResponse' {} Maybe [ConfigurationSet]
a -> ListConfigurationSetsResponse
s {$sel:configurationSets:ListConfigurationSetsResponse' :: Maybe [ConfigurationSet]
configurationSets = Maybe [ConfigurationSet]
a} :: ListConfigurationSetsResponse) 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 token indicating that there are additional configuration sets
-- available to be listed. Pass this token to successive calls of
-- @ListConfigurationSets@.
listConfigurationSetsResponse_nextToken :: Lens.Lens' ListConfigurationSetsResponse (Prelude.Maybe Prelude.Text)
listConfigurationSetsResponse_nextToken :: Lens' ListConfigurationSetsResponse (Maybe Text)
listConfigurationSetsResponse_nextToken = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\ListConfigurationSetsResponse' {Maybe Text
nextToken :: Maybe Text
$sel:nextToken:ListConfigurationSetsResponse' :: ListConfigurationSetsResponse -> Maybe Text
nextToken} -> Maybe Text
nextToken) (\s :: ListConfigurationSetsResponse
s@ListConfigurationSetsResponse' {} Maybe Text
a -> ListConfigurationSetsResponse
s {$sel:nextToken:ListConfigurationSetsResponse' :: Maybe Text
nextToken = Maybe Text
a} :: ListConfigurationSetsResponse)

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

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