{-# 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.Route53.ListReusableDelegationSets
-- 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 the reusable delegation sets that are associated
-- with the current Amazon Web Services account.
module Amazonka.Route53.ListReusableDelegationSets
  ( -- * Creating a Request
    ListReusableDelegationSets (..),
    newListReusableDelegationSets,

    -- * Request Lenses
    listReusableDelegationSets_marker,
    listReusableDelegationSets_maxItems,

    -- * Destructuring the Response
    ListReusableDelegationSetsResponse (..),
    newListReusableDelegationSetsResponse,

    -- * Response Lenses
    listReusableDelegationSetsResponse_nextMarker,
    listReusableDelegationSetsResponse_httpStatus,
    listReusableDelegationSetsResponse_delegationSets,
    listReusableDelegationSetsResponse_marker,
    listReusableDelegationSetsResponse_isTruncated,
    listReusableDelegationSetsResponse_maxItems,
  )
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.Route53.Types

-- | A request to get a list of the reusable delegation sets that are
-- associated with the current Amazon Web Services account.
--
-- /See:/ 'newListReusableDelegationSets' smart constructor.
data ListReusableDelegationSets = ListReusableDelegationSets'
  { -- | If the value of @IsTruncated@ in the previous response was @true@, you
    -- have more reusable delegation sets. To get another group, submit another
    -- @ListReusableDelegationSets@ request.
    --
    -- For the value of @marker@, specify the value of @NextMarker@ from the
    -- previous response, which is the ID of the first reusable delegation set
    -- that Amazon Route 53 will return if you submit another request.
    --
    -- If the value of @IsTruncated@ in the previous response was @false@,
    -- there are no more reusable delegation sets to get.
    ListReusableDelegationSets -> Maybe Text
marker :: Prelude.Maybe Prelude.Text,
    -- | The number of reusable delegation sets that you want Amazon Route 53 to
    -- return in the response to this request. If you specify a value greater
    -- than 100, Route 53 returns only the first 100 reusable delegation sets.
    ListReusableDelegationSets -> Maybe Text
maxItems :: Prelude.Maybe Prelude.Text
  }
  deriving (ListReusableDelegationSets -> ListReusableDelegationSets -> Bool
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: ListReusableDelegationSets -> ListReusableDelegationSets -> Bool
$c/= :: ListReusableDelegationSets -> ListReusableDelegationSets -> Bool
== :: ListReusableDelegationSets -> ListReusableDelegationSets -> Bool
$c== :: ListReusableDelegationSets -> ListReusableDelegationSets -> Bool
Prelude.Eq, ReadPrec [ListReusableDelegationSets]
ReadPrec ListReusableDelegationSets
Int -> ReadS ListReusableDelegationSets
ReadS [ListReusableDelegationSets]
forall a.
(Int -> ReadS a)
-> ReadS [a] -> ReadPrec a -> ReadPrec [a] -> Read a
readListPrec :: ReadPrec [ListReusableDelegationSets]
$creadListPrec :: ReadPrec [ListReusableDelegationSets]
readPrec :: ReadPrec ListReusableDelegationSets
$creadPrec :: ReadPrec ListReusableDelegationSets
readList :: ReadS [ListReusableDelegationSets]
$creadList :: ReadS [ListReusableDelegationSets]
readsPrec :: Int -> ReadS ListReusableDelegationSets
$creadsPrec :: Int -> ReadS ListReusableDelegationSets
Prelude.Read, Int -> ListReusableDelegationSets -> ShowS
[ListReusableDelegationSets] -> ShowS
ListReusableDelegationSets -> String
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [ListReusableDelegationSets] -> ShowS
$cshowList :: [ListReusableDelegationSets] -> ShowS
show :: ListReusableDelegationSets -> String
$cshow :: ListReusableDelegationSets -> String
showsPrec :: Int -> ListReusableDelegationSets -> ShowS
$cshowsPrec :: Int -> ListReusableDelegationSets -> ShowS
Prelude.Show, forall x.
Rep ListReusableDelegationSets x -> ListReusableDelegationSets
forall x.
ListReusableDelegationSets -> Rep ListReusableDelegationSets x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cto :: forall x.
Rep ListReusableDelegationSets x -> ListReusableDelegationSets
$cfrom :: forall x.
ListReusableDelegationSets -> Rep ListReusableDelegationSets x
Prelude.Generic)

-- |
-- Create a value of 'ListReusableDelegationSets' 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:
--
-- 'marker', 'listReusableDelegationSets_marker' - If the value of @IsTruncated@ in the previous response was @true@, you
-- have more reusable delegation sets. To get another group, submit another
-- @ListReusableDelegationSets@ request.
--
-- For the value of @marker@, specify the value of @NextMarker@ from the
-- previous response, which is the ID of the first reusable delegation set
-- that Amazon Route 53 will return if you submit another request.
--
-- If the value of @IsTruncated@ in the previous response was @false@,
-- there are no more reusable delegation sets to get.
--
-- 'maxItems', 'listReusableDelegationSets_maxItems' - The number of reusable delegation sets that you want Amazon Route 53 to
-- return in the response to this request. If you specify a value greater
-- than 100, Route 53 returns only the first 100 reusable delegation sets.
newListReusableDelegationSets ::
  ListReusableDelegationSets
newListReusableDelegationSets :: ListReusableDelegationSets
newListReusableDelegationSets =
  ListReusableDelegationSets'
    { $sel:marker:ListReusableDelegationSets' :: Maybe Text
marker =
        forall a. Maybe a
Prelude.Nothing,
      $sel:maxItems:ListReusableDelegationSets' :: Maybe Text
maxItems = forall a. Maybe a
Prelude.Nothing
    }

-- | If the value of @IsTruncated@ in the previous response was @true@, you
-- have more reusable delegation sets. To get another group, submit another
-- @ListReusableDelegationSets@ request.
--
-- For the value of @marker@, specify the value of @NextMarker@ from the
-- previous response, which is the ID of the first reusable delegation set
-- that Amazon Route 53 will return if you submit another request.
--
-- If the value of @IsTruncated@ in the previous response was @false@,
-- there are no more reusable delegation sets to get.
listReusableDelegationSets_marker :: Lens.Lens' ListReusableDelegationSets (Prelude.Maybe Prelude.Text)
listReusableDelegationSets_marker :: Lens' ListReusableDelegationSets (Maybe Text)
listReusableDelegationSets_marker = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\ListReusableDelegationSets' {Maybe Text
marker :: Maybe Text
$sel:marker:ListReusableDelegationSets' :: ListReusableDelegationSets -> Maybe Text
marker} -> Maybe Text
marker) (\s :: ListReusableDelegationSets
s@ListReusableDelegationSets' {} Maybe Text
a -> ListReusableDelegationSets
s {$sel:marker:ListReusableDelegationSets' :: Maybe Text
marker = Maybe Text
a} :: ListReusableDelegationSets)

-- | The number of reusable delegation sets that you want Amazon Route 53 to
-- return in the response to this request. If you specify a value greater
-- than 100, Route 53 returns only the first 100 reusable delegation sets.
listReusableDelegationSets_maxItems :: Lens.Lens' ListReusableDelegationSets (Prelude.Maybe Prelude.Text)
listReusableDelegationSets_maxItems :: Lens' ListReusableDelegationSets (Maybe Text)
listReusableDelegationSets_maxItems = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\ListReusableDelegationSets' {Maybe Text
maxItems :: Maybe Text
$sel:maxItems:ListReusableDelegationSets' :: ListReusableDelegationSets -> Maybe Text
maxItems} -> Maybe Text
maxItems) (\s :: ListReusableDelegationSets
s@ListReusableDelegationSets' {} Maybe Text
a -> ListReusableDelegationSets
s {$sel:maxItems:ListReusableDelegationSets' :: Maybe Text
maxItems = Maybe Text
a} :: ListReusableDelegationSets)

instance Core.AWSRequest ListReusableDelegationSets where
  type
    AWSResponse ListReusableDelegationSets =
      ListReusableDelegationSetsResponse
  request :: (Service -> Service)
-> ListReusableDelegationSets -> Request ListReusableDelegationSets
request Service -> Service
overrides =
    forall a. ToRequest a => Service -> a -> Request a
Request.get (Service -> Service
overrides Service
defaultService)
  response :: forall (m :: * -> *).
MonadResource m =>
(ByteStringLazy -> IO ByteStringLazy)
-> Service
-> Proxy ListReusableDelegationSets
-> ClientResponse ClientBody
-> m (Either
        Error (ClientResponse (AWSResponse ListReusableDelegationSets)))
response =
    forall (m :: * -> *) a.
MonadResource m =>
(Int -> ResponseHeaders -> [Node] -> Either String (AWSResponse a))
-> (ByteStringLazy -> IO ByteStringLazy)
-> Service
-> Proxy a
-> ClientResponse ClientBody
-> m (Either Error (ClientResponse (AWSResponse a)))
Response.receiveXML
      ( \Int
s ResponseHeaders
h [Node]
x ->
          Maybe Text
-> Int
-> [DelegationSet]
-> Text
-> Bool
-> Text
-> ListReusableDelegationSetsResponse
ListReusableDelegationSetsResponse'
            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
"NextMarker")
            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))
            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
"DelegationSets"
                            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 a. FromXML a => Text -> [Node] -> Either String [a]
Data.parseXMLList Text
"DelegationSet"
                        )
            forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
Prelude.<*> ([Node]
x forall a. FromXML a => [Node] -> Text -> Either String a
Data..@ Text
"Marker")
            forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
Prelude.<*> ([Node]
x forall a. FromXML a => [Node] -> Text -> Either String a
Data..@ Text
"IsTruncated")
            forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
Prelude.<*> ([Node]
x forall a. FromXML a => [Node] -> Text -> Either String a
Data..@ Text
"MaxItems")
      )

instance Prelude.Hashable ListReusableDelegationSets where
  hashWithSalt :: Int -> ListReusableDelegationSets -> Int
hashWithSalt Int
_salt ListReusableDelegationSets' {Maybe Text
maxItems :: Maybe Text
marker :: Maybe Text
$sel:maxItems:ListReusableDelegationSets' :: ListReusableDelegationSets -> Maybe Text
$sel:marker:ListReusableDelegationSets' :: ListReusableDelegationSets -> Maybe Text
..} =
    Int
_salt
      forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Maybe Text
marker
      forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Maybe Text
maxItems

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

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

instance Data.ToPath ListReusableDelegationSets where
  toPath :: ListReusableDelegationSets -> ByteString
toPath = forall a b. a -> b -> a
Prelude.const ByteString
"/2013-04-01/delegationset"

instance Data.ToQuery ListReusableDelegationSets where
  toQuery :: ListReusableDelegationSets -> QueryString
toQuery ListReusableDelegationSets' {Maybe Text
maxItems :: Maybe Text
marker :: Maybe Text
$sel:maxItems:ListReusableDelegationSets' :: ListReusableDelegationSets -> Maybe Text
$sel:marker:ListReusableDelegationSets' :: ListReusableDelegationSets -> Maybe Text
..} =
    forall a. Monoid a => [a] -> a
Prelude.mconcat
      [ ByteString
"marker" forall a. ToQuery a => ByteString -> a -> QueryString
Data.=: Maybe Text
marker,
        ByteString
"maxitems" forall a. ToQuery a => ByteString -> a -> QueryString
Data.=: Maybe Text
maxItems
      ]

-- | A complex type that contains information about the reusable delegation
-- sets that are associated with the current Amazon Web Services account.
--
-- /See:/ 'newListReusableDelegationSetsResponse' smart constructor.
data ListReusableDelegationSetsResponse = ListReusableDelegationSetsResponse'
  { -- | If @IsTruncated@ is @true@, the value of @NextMarker@ identifies the
    -- next reusable delegation set that Amazon Route 53 will return if you
    -- submit another @ListReusableDelegationSets@ request and specify the
    -- value of @NextMarker@ in the @marker@ parameter.
    ListReusableDelegationSetsResponse -> Maybe Text
nextMarker :: Prelude.Maybe Prelude.Text,
    -- | The response's http status code.
    ListReusableDelegationSetsResponse -> Int
httpStatus :: Prelude.Int,
    -- | A complex type that contains one @DelegationSet@ element for each
    -- reusable delegation set that was created by the current Amazon Web
    -- Services account.
    ListReusableDelegationSetsResponse -> [DelegationSet]
delegationSets :: [DelegationSet],
    -- | For the second and subsequent calls to @ListReusableDelegationSets@,
    -- @Marker@ is the value that you specified for the @marker@ parameter in
    -- the request that produced the current response.
    ListReusableDelegationSetsResponse -> Text
marker :: Prelude.Text,
    -- | A flag that indicates whether there are more reusable delegation sets to
    -- be listed.
    ListReusableDelegationSetsResponse -> Bool
isTruncated :: Prelude.Bool,
    -- | The value that you specified for the @maxitems@ parameter in the call to
    -- @ListReusableDelegationSets@ that produced the current response.
    ListReusableDelegationSetsResponse -> Text
maxItems :: Prelude.Text
  }
  deriving (ListReusableDelegationSetsResponse
-> ListReusableDelegationSetsResponse -> Bool
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: ListReusableDelegationSetsResponse
-> ListReusableDelegationSetsResponse -> Bool
$c/= :: ListReusableDelegationSetsResponse
-> ListReusableDelegationSetsResponse -> Bool
== :: ListReusableDelegationSetsResponse
-> ListReusableDelegationSetsResponse -> Bool
$c== :: ListReusableDelegationSetsResponse
-> ListReusableDelegationSetsResponse -> Bool
Prelude.Eq, ReadPrec [ListReusableDelegationSetsResponse]
ReadPrec ListReusableDelegationSetsResponse
Int -> ReadS ListReusableDelegationSetsResponse
ReadS [ListReusableDelegationSetsResponse]
forall a.
(Int -> ReadS a)
-> ReadS [a] -> ReadPrec a -> ReadPrec [a] -> Read a
readListPrec :: ReadPrec [ListReusableDelegationSetsResponse]
$creadListPrec :: ReadPrec [ListReusableDelegationSetsResponse]
readPrec :: ReadPrec ListReusableDelegationSetsResponse
$creadPrec :: ReadPrec ListReusableDelegationSetsResponse
readList :: ReadS [ListReusableDelegationSetsResponse]
$creadList :: ReadS [ListReusableDelegationSetsResponse]
readsPrec :: Int -> ReadS ListReusableDelegationSetsResponse
$creadsPrec :: Int -> ReadS ListReusableDelegationSetsResponse
Prelude.Read, Int -> ListReusableDelegationSetsResponse -> ShowS
[ListReusableDelegationSetsResponse] -> ShowS
ListReusableDelegationSetsResponse -> String
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [ListReusableDelegationSetsResponse] -> ShowS
$cshowList :: [ListReusableDelegationSetsResponse] -> ShowS
show :: ListReusableDelegationSetsResponse -> String
$cshow :: ListReusableDelegationSetsResponse -> String
showsPrec :: Int -> ListReusableDelegationSetsResponse -> ShowS
$cshowsPrec :: Int -> ListReusableDelegationSetsResponse -> ShowS
Prelude.Show, forall x.
Rep ListReusableDelegationSetsResponse x
-> ListReusableDelegationSetsResponse
forall x.
ListReusableDelegationSetsResponse
-> Rep ListReusableDelegationSetsResponse x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cto :: forall x.
Rep ListReusableDelegationSetsResponse x
-> ListReusableDelegationSetsResponse
$cfrom :: forall x.
ListReusableDelegationSetsResponse
-> Rep ListReusableDelegationSetsResponse x
Prelude.Generic)

-- |
-- Create a value of 'ListReusableDelegationSetsResponse' 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:
--
-- 'nextMarker', 'listReusableDelegationSetsResponse_nextMarker' - If @IsTruncated@ is @true@, the value of @NextMarker@ identifies the
-- next reusable delegation set that Amazon Route 53 will return if you
-- submit another @ListReusableDelegationSets@ request and specify the
-- value of @NextMarker@ in the @marker@ parameter.
--
-- 'httpStatus', 'listReusableDelegationSetsResponse_httpStatus' - The response's http status code.
--
-- 'delegationSets', 'listReusableDelegationSetsResponse_delegationSets' - A complex type that contains one @DelegationSet@ element for each
-- reusable delegation set that was created by the current Amazon Web
-- Services account.
--
-- 'marker', 'listReusableDelegationSetsResponse_marker' - For the second and subsequent calls to @ListReusableDelegationSets@,
-- @Marker@ is the value that you specified for the @marker@ parameter in
-- the request that produced the current response.
--
-- 'isTruncated', 'listReusableDelegationSetsResponse_isTruncated' - A flag that indicates whether there are more reusable delegation sets to
-- be listed.
--
-- 'maxItems', 'listReusableDelegationSetsResponse_maxItems' - The value that you specified for the @maxitems@ parameter in the call to
-- @ListReusableDelegationSets@ that produced the current response.
newListReusableDelegationSetsResponse ::
  -- | 'httpStatus'
  Prelude.Int ->
  -- | 'marker'
  Prelude.Text ->
  -- | 'isTruncated'
  Prelude.Bool ->
  -- | 'maxItems'
  Prelude.Text ->
  ListReusableDelegationSetsResponse
newListReusableDelegationSetsResponse :: Int -> Text -> Bool -> Text -> ListReusableDelegationSetsResponse
newListReusableDelegationSetsResponse
  Int
pHttpStatus_
  Text
pMarker_
  Bool
pIsTruncated_
  Text
pMaxItems_ =
    ListReusableDelegationSetsResponse'
      { $sel:nextMarker:ListReusableDelegationSetsResponse' :: Maybe Text
nextMarker =
          forall a. Maybe a
Prelude.Nothing,
        $sel:httpStatus:ListReusableDelegationSetsResponse' :: Int
httpStatus = Int
pHttpStatus_,
        $sel:delegationSets:ListReusableDelegationSetsResponse' :: [DelegationSet]
delegationSets = forall a. Monoid a => a
Prelude.mempty,
        $sel:marker:ListReusableDelegationSetsResponse' :: Text
marker = Text
pMarker_,
        $sel:isTruncated:ListReusableDelegationSetsResponse' :: Bool
isTruncated = Bool
pIsTruncated_,
        $sel:maxItems:ListReusableDelegationSetsResponse' :: Text
maxItems = Text
pMaxItems_
      }

-- | If @IsTruncated@ is @true@, the value of @NextMarker@ identifies the
-- next reusable delegation set that Amazon Route 53 will return if you
-- submit another @ListReusableDelegationSets@ request and specify the
-- value of @NextMarker@ in the @marker@ parameter.
listReusableDelegationSetsResponse_nextMarker :: Lens.Lens' ListReusableDelegationSetsResponse (Prelude.Maybe Prelude.Text)
listReusableDelegationSetsResponse_nextMarker :: Lens' ListReusableDelegationSetsResponse (Maybe Text)
listReusableDelegationSetsResponse_nextMarker = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\ListReusableDelegationSetsResponse' {Maybe Text
nextMarker :: Maybe Text
$sel:nextMarker:ListReusableDelegationSetsResponse' :: ListReusableDelegationSetsResponse -> Maybe Text
nextMarker} -> Maybe Text
nextMarker) (\s :: ListReusableDelegationSetsResponse
s@ListReusableDelegationSetsResponse' {} Maybe Text
a -> ListReusableDelegationSetsResponse
s {$sel:nextMarker:ListReusableDelegationSetsResponse' :: Maybe Text
nextMarker = Maybe Text
a} :: ListReusableDelegationSetsResponse)

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

-- | A complex type that contains one @DelegationSet@ element for each
-- reusable delegation set that was created by the current Amazon Web
-- Services account.
listReusableDelegationSetsResponse_delegationSets :: Lens.Lens' ListReusableDelegationSetsResponse [DelegationSet]
listReusableDelegationSetsResponse_delegationSets :: Lens' ListReusableDelegationSetsResponse [DelegationSet]
listReusableDelegationSetsResponse_delegationSets = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\ListReusableDelegationSetsResponse' {[DelegationSet]
delegationSets :: [DelegationSet]
$sel:delegationSets:ListReusableDelegationSetsResponse' :: ListReusableDelegationSetsResponse -> [DelegationSet]
delegationSets} -> [DelegationSet]
delegationSets) (\s :: ListReusableDelegationSetsResponse
s@ListReusableDelegationSetsResponse' {} [DelegationSet]
a -> ListReusableDelegationSetsResponse
s {$sel:delegationSets:ListReusableDelegationSetsResponse' :: [DelegationSet]
delegationSets = [DelegationSet]
a} :: ListReusableDelegationSetsResponse) 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

-- | For the second and subsequent calls to @ListReusableDelegationSets@,
-- @Marker@ is the value that you specified for the @marker@ parameter in
-- the request that produced the current response.
listReusableDelegationSetsResponse_marker :: Lens.Lens' ListReusableDelegationSetsResponse Prelude.Text
listReusableDelegationSetsResponse_marker :: Lens' ListReusableDelegationSetsResponse Text
listReusableDelegationSetsResponse_marker = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\ListReusableDelegationSetsResponse' {Text
marker :: Text
$sel:marker:ListReusableDelegationSetsResponse' :: ListReusableDelegationSetsResponse -> Text
marker} -> Text
marker) (\s :: ListReusableDelegationSetsResponse
s@ListReusableDelegationSetsResponse' {} Text
a -> ListReusableDelegationSetsResponse
s {$sel:marker:ListReusableDelegationSetsResponse' :: Text
marker = Text
a} :: ListReusableDelegationSetsResponse)

-- | A flag that indicates whether there are more reusable delegation sets to
-- be listed.
listReusableDelegationSetsResponse_isTruncated :: Lens.Lens' ListReusableDelegationSetsResponse Prelude.Bool
listReusableDelegationSetsResponse_isTruncated :: Lens' ListReusableDelegationSetsResponse Bool
listReusableDelegationSetsResponse_isTruncated = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\ListReusableDelegationSetsResponse' {Bool
isTruncated :: Bool
$sel:isTruncated:ListReusableDelegationSetsResponse' :: ListReusableDelegationSetsResponse -> Bool
isTruncated} -> Bool
isTruncated) (\s :: ListReusableDelegationSetsResponse
s@ListReusableDelegationSetsResponse' {} Bool
a -> ListReusableDelegationSetsResponse
s {$sel:isTruncated:ListReusableDelegationSetsResponse' :: Bool
isTruncated = Bool
a} :: ListReusableDelegationSetsResponse)

-- | The value that you specified for the @maxitems@ parameter in the call to
-- @ListReusableDelegationSets@ that produced the current response.
listReusableDelegationSetsResponse_maxItems :: Lens.Lens' ListReusableDelegationSetsResponse Prelude.Text
listReusableDelegationSetsResponse_maxItems :: Lens' ListReusableDelegationSetsResponse Text
listReusableDelegationSetsResponse_maxItems = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\ListReusableDelegationSetsResponse' {Text
maxItems :: Text
$sel:maxItems:ListReusableDelegationSetsResponse' :: ListReusableDelegationSetsResponse -> Text
maxItems} -> Text
maxItems) (\s :: ListReusableDelegationSetsResponse
s@ListReusableDelegationSetsResponse' {} Text
a -> ListReusableDelegationSetsResponse
s {$sel:maxItems:ListReusableDelegationSetsResponse' :: Text
maxItems = Text
a} :: ListReusableDelegationSetsResponse)

instance
  Prelude.NFData
    ListReusableDelegationSetsResponse
  where
  rnf :: ListReusableDelegationSetsResponse -> ()
rnf ListReusableDelegationSetsResponse' {Bool
Int
[DelegationSet]
Maybe Text
Text
maxItems :: Text
isTruncated :: Bool
marker :: Text
delegationSets :: [DelegationSet]
httpStatus :: Int
nextMarker :: Maybe Text
$sel:maxItems:ListReusableDelegationSetsResponse' :: ListReusableDelegationSetsResponse -> Text
$sel:isTruncated:ListReusableDelegationSetsResponse' :: ListReusableDelegationSetsResponse -> Bool
$sel:marker:ListReusableDelegationSetsResponse' :: ListReusableDelegationSetsResponse -> Text
$sel:delegationSets:ListReusableDelegationSetsResponse' :: ListReusableDelegationSetsResponse -> [DelegationSet]
$sel:httpStatus:ListReusableDelegationSetsResponse' :: ListReusableDelegationSetsResponse -> Int
$sel:nextMarker:ListReusableDelegationSetsResponse' :: ListReusableDelegationSetsResponse -> Maybe Text
..} =
    forall a. NFData a => a -> ()
Prelude.rnf Maybe Text
nextMarker
      seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf Int
httpStatus
      seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf [DelegationSet]
delegationSets
      seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf Text
marker
      seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf Bool
isTruncated
      seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf Text
maxItems