{-# 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.CognitoIdentityProvider.ListUserPools
-- Copyright   : (c) 2013-2023 Brendan Hay
-- License     : Mozilla Public License, v. 2.0.
-- Maintainer  : Brendan Hay
-- Stability   : auto-generated
-- Portability : non-portable (GHC extensions)
--
-- Lists the user pools associated with an Amazon Web Services account.
--
-- This operation returns paginated results.
module Amazonka.CognitoIdentityProvider.ListUserPools
  ( -- * Creating a Request
    ListUserPools (..),
    newListUserPools,

    -- * Request Lenses
    listUserPools_nextToken,
    listUserPools_maxResults,

    -- * Destructuring the Response
    ListUserPoolsResponse (..),
    newListUserPoolsResponse,

    -- * Response Lenses
    listUserPoolsResponse_nextToken,
    listUserPoolsResponse_userPools,
    listUserPoolsResponse_httpStatus,
  )
where

import Amazonka.CognitoIdentityProvider.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

-- | Represents the request to list user pools.
--
-- /See:/ 'newListUserPools' smart constructor.
data ListUserPools = ListUserPools'
  { -- | An identifier that was returned from the previous call to this
    -- operation, which can be used to return the next set of items in the
    -- list.
    ListUserPools -> Maybe Text
nextToken :: Prelude.Maybe Prelude.Text,
    -- | The maximum number of results you want the request to return when
    -- listing the user pools.
    ListUserPools -> Natural
maxResults :: Prelude.Natural
  }
  deriving (ListUserPools -> ListUserPools -> Bool
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: ListUserPools -> ListUserPools -> Bool
$c/= :: ListUserPools -> ListUserPools -> Bool
== :: ListUserPools -> ListUserPools -> Bool
$c== :: ListUserPools -> ListUserPools -> Bool
Prelude.Eq, ReadPrec [ListUserPools]
ReadPrec ListUserPools
Int -> ReadS ListUserPools
ReadS [ListUserPools]
forall a.
(Int -> ReadS a)
-> ReadS [a] -> ReadPrec a -> ReadPrec [a] -> Read a
readListPrec :: ReadPrec [ListUserPools]
$creadListPrec :: ReadPrec [ListUserPools]
readPrec :: ReadPrec ListUserPools
$creadPrec :: ReadPrec ListUserPools
readList :: ReadS [ListUserPools]
$creadList :: ReadS [ListUserPools]
readsPrec :: Int -> ReadS ListUserPools
$creadsPrec :: Int -> ReadS ListUserPools
Prelude.Read, Int -> ListUserPools -> ShowS
[ListUserPools] -> ShowS
ListUserPools -> String
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [ListUserPools] -> ShowS
$cshowList :: [ListUserPools] -> ShowS
show :: ListUserPools -> String
$cshow :: ListUserPools -> String
showsPrec :: Int -> ListUserPools -> ShowS
$cshowsPrec :: Int -> ListUserPools -> ShowS
Prelude.Show, forall x. Rep ListUserPools x -> ListUserPools
forall x. ListUserPools -> Rep ListUserPools x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cto :: forall x. Rep ListUserPools x -> ListUserPools
$cfrom :: forall x. ListUserPools -> Rep ListUserPools x
Prelude.Generic)

-- |
-- Create a value of 'ListUserPools' 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:
--
-- 'nextToken', 'listUserPools_nextToken' - An identifier that was returned from the previous call to this
-- operation, which can be used to return the next set of items in the
-- list.
--
-- 'maxResults', 'listUserPools_maxResults' - The maximum number of results you want the request to return when
-- listing the user pools.
newListUserPools ::
  -- | 'maxResults'
  Prelude.Natural ->
  ListUserPools
newListUserPools :: Natural -> ListUserPools
newListUserPools Natural
pMaxResults_ =
  ListUserPools'
    { $sel:nextToken:ListUserPools' :: Maybe Text
nextToken = forall a. Maybe a
Prelude.Nothing,
      $sel:maxResults:ListUserPools' :: Natural
maxResults = Natural
pMaxResults_
    }

-- | An identifier that was returned from the previous call to this
-- operation, which can be used to return the next set of items in the
-- list.
listUserPools_nextToken :: Lens.Lens' ListUserPools (Prelude.Maybe Prelude.Text)
listUserPools_nextToken :: Lens' ListUserPools (Maybe Text)
listUserPools_nextToken = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\ListUserPools' {Maybe Text
nextToken :: Maybe Text
$sel:nextToken:ListUserPools' :: ListUserPools -> Maybe Text
nextToken} -> Maybe Text
nextToken) (\s :: ListUserPools
s@ListUserPools' {} Maybe Text
a -> ListUserPools
s {$sel:nextToken:ListUserPools' :: Maybe Text
nextToken = Maybe Text
a} :: ListUserPools)

-- | The maximum number of results you want the request to return when
-- listing the user pools.
listUserPools_maxResults :: Lens.Lens' ListUserPools Prelude.Natural
listUserPools_maxResults :: Lens' ListUserPools Natural
listUserPools_maxResults = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\ListUserPools' {Natural
maxResults :: Natural
$sel:maxResults:ListUserPools' :: ListUserPools -> Natural
maxResults} -> Natural
maxResults) (\s :: ListUserPools
s@ListUserPools' {} Natural
a -> ListUserPools
s {$sel:maxResults:ListUserPools' :: Natural
maxResults = Natural
a} :: ListUserPools)

instance Core.AWSPager ListUserPools where
  page :: ListUserPools -> AWSResponse ListUserPools -> Maybe ListUserPools
page ListUserPools
rq AWSResponse ListUserPools
rs
    | forall a. AWSTruncated a => a -> Bool
Core.stop
        ( AWSResponse ListUserPools
rs
            forall s a. s -> Getting (First a) s a -> Maybe a
Lens.^? Lens' ListUserPoolsResponse (Maybe Text)
listUserPoolsResponse_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 ListUserPools
rs
            forall s a. s -> Getting (First a) s a -> Maybe a
Lens.^? Lens' ListUserPoolsResponse (Maybe [UserPoolDescriptionType])
listUserPoolsResponse_userPools
            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.$ ListUserPools
rq
          forall a b. a -> (a -> b) -> b
Prelude.& Lens' ListUserPools (Maybe Text)
listUserPools_nextToken
          forall s t a b. ASetter s t a b -> b -> s -> t
Lens..~ AWSResponse ListUserPools
rs
          forall s a. s -> Getting (First a) s a -> Maybe a
Lens.^? Lens' ListUserPoolsResponse (Maybe Text)
listUserPoolsResponse_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 ListUserPools where
  type
    AWSResponse ListUserPools =
      ListUserPoolsResponse
  request :: (Service -> Service) -> ListUserPools -> Request ListUserPools
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 ListUserPools
-> ClientResponse ClientBody
-> m (Either Error (ClientResponse (AWSResponse ListUserPools)))
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 Text
-> Maybe [UserPoolDescriptionType] -> Int -> ListUserPoolsResponse
ListUserPoolsResponse'
            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
"NextToken")
            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
"UserPools" forall (f :: * -> *) a. Functor f => f (Maybe a) -> a -> f a
Core..!@ forall a. Monoid a => a
Prelude.mempty)
            forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
Prelude.<*> (forall (f :: * -> *) a. Applicative f => a -> f a
Prelude.pure (forall a. Enum a => a -> Int
Prelude.fromEnum Int
s))
      )

instance Prelude.Hashable ListUserPools where
  hashWithSalt :: Int -> ListUserPools -> Int
hashWithSalt Int
_salt ListUserPools' {Natural
Maybe Text
maxResults :: Natural
nextToken :: Maybe Text
$sel:maxResults:ListUserPools' :: ListUserPools -> Natural
$sel:nextToken:ListUserPools' :: ListUserPools -> Maybe Text
..} =
    Int
_salt
      forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Maybe Text
nextToken
      forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Natural
maxResults

instance Prelude.NFData ListUserPools where
  rnf :: ListUserPools -> ()
rnf ListUserPools' {Natural
Maybe Text
maxResults :: Natural
nextToken :: Maybe Text
$sel:maxResults:ListUserPools' :: ListUserPools -> Natural
$sel:nextToken:ListUserPools' :: ListUserPools -> Maybe Text
..} =
    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 Natural
maxResults

instance Data.ToHeaders ListUserPools where
  toHeaders :: ListUserPools -> 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
"AWSCognitoIdentityProviderService.ListUserPools" ::
                          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 ListUserPools where
  toJSON :: ListUserPools -> Value
toJSON ListUserPools' {Natural
Maybe Text
maxResults :: Natural
nextToken :: Maybe Text
$sel:maxResults:ListUserPools' :: ListUserPools -> Natural
$sel:nextToken:ListUserPools' :: ListUserPools -> Maybe Text
..} =
    [Pair] -> Value
Data.object
      ( forall a. [Maybe a] -> [a]
Prelude.catMaybes
          [ (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,
            forall a. a -> Maybe a
Prelude.Just (Key
"MaxResults" forall kv v. (KeyValue kv, ToJSON v) => Key -> v -> kv
Data..= Natural
maxResults)
          ]
      )

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

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

-- | Represents the response to list user pools.
--
-- /See:/ 'newListUserPoolsResponse' smart constructor.
data ListUserPoolsResponse = ListUserPoolsResponse'
  { -- | An identifier that was returned from the previous call to this
    -- operation, which can be used to return the next set of items in the
    -- list.
    ListUserPoolsResponse -> Maybe Text
nextToken :: Prelude.Maybe Prelude.Text,
    -- | The user pools from the response to list users.
    ListUserPoolsResponse -> Maybe [UserPoolDescriptionType]
userPools :: Prelude.Maybe [UserPoolDescriptionType],
    -- | The response's http status code.
    ListUserPoolsResponse -> Int
httpStatus :: Prelude.Int
  }
  deriving (ListUserPoolsResponse -> ListUserPoolsResponse -> Bool
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: ListUserPoolsResponse -> ListUserPoolsResponse -> Bool
$c/= :: ListUserPoolsResponse -> ListUserPoolsResponse -> Bool
== :: ListUserPoolsResponse -> ListUserPoolsResponse -> Bool
$c== :: ListUserPoolsResponse -> ListUserPoolsResponse -> Bool
Prelude.Eq, ReadPrec [ListUserPoolsResponse]
ReadPrec ListUserPoolsResponse
Int -> ReadS ListUserPoolsResponse
ReadS [ListUserPoolsResponse]
forall a.
(Int -> ReadS a)
-> ReadS [a] -> ReadPrec a -> ReadPrec [a] -> Read a
readListPrec :: ReadPrec [ListUserPoolsResponse]
$creadListPrec :: ReadPrec [ListUserPoolsResponse]
readPrec :: ReadPrec ListUserPoolsResponse
$creadPrec :: ReadPrec ListUserPoolsResponse
readList :: ReadS [ListUserPoolsResponse]
$creadList :: ReadS [ListUserPoolsResponse]
readsPrec :: Int -> ReadS ListUserPoolsResponse
$creadsPrec :: Int -> ReadS ListUserPoolsResponse
Prelude.Read, Int -> ListUserPoolsResponse -> ShowS
[ListUserPoolsResponse] -> ShowS
ListUserPoolsResponse -> String
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [ListUserPoolsResponse] -> ShowS
$cshowList :: [ListUserPoolsResponse] -> ShowS
show :: ListUserPoolsResponse -> String
$cshow :: ListUserPoolsResponse -> String
showsPrec :: Int -> ListUserPoolsResponse -> ShowS
$cshowsPrec :: Int -> ListUserPoolsResponse -> ShowS
Prelude.Show, forall x. Rep ListUserPoolsResponse x -> ListUserPoolsResponse
forall x. ListUserPoolsResponse -> Rep ListUserPoolsResponse x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cto :: forall x. Rep ListUserPoolsResponse x -> ListUserPoolsResponse
$cfrom :: forall x. ListUserPoolsResponse -> Rep ListUserPoolsResponse x
Prelude.Generic)

-- |
-- Create a value of 'ListUserPoolsResponse' 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:
--
-- 'nextToken', 'listUserPoolsResponse_nextToken' - An identifier that was returned from the previous call to this
-- operation, which can be used to return the next set of items in the
-- list.
--
-- 'userPools', 'listUserPoolsResponse_userPools' - The user pools from the response to list users.
--
-- 'httpStatus', 'listUserPoolsResponse_httpStatus' - The response's http status code.
newListUserPoolsResponse ::
  -- | 'httpStatus'
  Prelude.Int ->
  ListUserPoolsResponse
newListUserPoolsResponse :: Int -> ListUserPoolsResponse
newListUserPoolsResponse Int
pHttpStatus_ =
  ListUserPoolsResponse'
    { $sel:nextToken:ListUserPoolsResponse' :: Maybe Text
nextToken = forall a. Maybe a
Prelude.Nothing,
      $sel:userPools:ListUserPoolsResponse' :: Maybe [UserPoolDescriptionType]
userPools = forall a. Maybe a
Prelude.Nothing,
      $sel:httpStatus:ListUserPoolsResponse' :: Int
httpStatus = Int
pHttpStatus_
    }

-- | An identifier that was returned from the previous call to this
-- operation, which can be used to return the next set of items in the
-- list.
listUserPoolsResponse_nextToken :: Lens.Lens' ListUserPoolsResponse (Prelude.Maybe Prelude.Text)
listUserPoolsResponse_nextToken :: Lens' ListUserPoolsResponse (Maybe Text)
listUserPoolsResponse_nextToken = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\ListUserPoolsResponse' {Maybe Text
nextToken :: Maybe Text
$sel:nextToken:ListUserPoolsResponse' :: ListUserPoolsResponse -> Maybe Text
nextToken} -> Maybe Text
nextToken) (\s :: ListUserPoolsResponse
s@ListUserPoolsResponse' {} Maybe Text
a -> ListUserPoolsResponse
s {$sel:nextToken:ListUserPoolsResponse' :: Maybe Text
nextToken = Maybe Text
a} :: ListUserPoolsResponse)

-- | The user pools from the response to list users.
listUserPoolsResponse_userPools :: Lens.Lens' ListUserPoolsResponse (Prelude.Maybe [UserPoolDescriptionType])
listUserPoolsResponse_userPools :: Lens' ListUserPoolsResponse (Maybe [UserPoolDescriptionType])
listUserPoolsResponse_userPools = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\ListUserPoolsResponse' {Maybe [UserPoolDescriptionType]
userPools :: Maybe [UserPoolDescriptionType]
$sel:userPools:ListUserPoolsResponse' :: ListUserPoolsResponse -> Maybe [UserPoolDescriptionType]
userPools} -> Maybe [UserPoolDescriptionType]
userPools) (\s :: ListUserPoolsResponse
s@ListUserPoolsResponse' {} Maybe [UserPoolDescriptionType]
a -> ListUserPoolsResponse
s {$sel:userPools:ListUserPoolsResponse' :: Maybe [UserPoolDescriptionType]
userPools = Maybe [UserPoolDescriptionType]
a} :: ListUserPoolsResponse) 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.
listUserPoolsResponse_httpStatus :: Lens.Lens' ListUserPoolsResponse Prelude.Int
listUserPoolsResponse_httpStatus :: Lens' ListUserPoolsResponse Int
listUserPoolsResponse_httpStatus = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\ListUserPoolsResponse' {Int
httpStatus :: Int
$sel:httpStatus:ListUserPoolsResponse' :: ListUserPoolsResponse -> Int
httpStatus} -> Int
httpStatus) (\s :: ListUserPoolsResponse
s@ListUserPoolsResponse' {} Int
a -> ListUserPoolsResponse
s {$sel:httpStatus:ListUserPoolsResponse' :: Int
httpStatus = Int
a} :: ListUserPoolsResponse)

instance Prelude.NFData ListUserPoolsResponse where
  rnf :: ListUserPoolsResponse -> ()
rnf ListUserPoolsResponse' {Int
Maybe [UserPoolDescriptionType]
Maybe Text
httpStatus :: Int
userPools :: Maybe [UserPoolDescriptionType]
nextToken :: Maybe Text
$sel:httpStatus:ListUserPoolsResponse' :: ListUserPoolsResponse -> Int
$sel:userPools:ListUserPoolsResponse' :: ListUserPoolsResponse -> Maybe [UserPoolDescriptionType]
$sel:nextToken:ListUserPoolsResponse' :: ListUserPoolsResponse -> Maybe Text
..} =
    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 [UserPoolDescriptionType]
userPools
      seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf Int
httpStatus