{-# 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.CognitoIdentity.ListIdentityPools
-- 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 all of the Cognito identity pools registered for your account.
--
-- You must use AWS Developer credentials to call this API.
--
-- This operation returns paginated results.
module Amazonka.CognitoIdentity.ListIdentityPools
  ( -- * Creating a Request
    ListIdentityPools (..),
    newListIdentityPools,

    -- * Request Lenses
    listIdentityPools_nextToken,
    listIdentityPools_maxResults,

    -- * Destructuring the Response
    ListIdentityPoolsResponse (..),
    newListIdentityPoolsResponse,

    -- * Response Lenses
    listIdentityPoolsResponse_identityPools,
    listIdentityPoolsResponse_nextToken,
    listIdentityPoolsResponse_httpStatus,
  )
where

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

-- | Input to the ListIdentityPools action.
--
-- /See:/ 'newListIdentityPools' smart constructor.
data ListIdentityPools = ListIdentityPools'
  { -- | A pagination token.
    ListIdentityPools -> Maybe Text
nextToken :: Prelude.Maybe Prelude.Text,
    -- | The maximum number of identities to return.
    ListIdentityPools -> Natural
maxResults :: Prelude.Natural
  }
  deriving (ListIdentityPools -> ListIdentityPools -> Bool
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: ListIdentityPools -> ListIdentityPools -> Bool
$c/= :: ListIdentityPools -> ListIdentityPools -> Bool
== :: ListIdentityPools -> ListIdentityPools -> Bool
$c== :: ListIdentityPools -> ListIdentityPools -> Bool
Prelude.Eq, ReadPrec [ListIdentityPools]
ReadPrec ListIdentityPools
Int -> ReadS ListIdentityPools
ReadS [ListIdentityPools]
forall a.
(Int -> ReadS a)
-> ReadS [a] -> ReadPrec a -> ReadPrec [a] -> Read a
readListPrec :: ReadPrec [ListIdentityPools]
$creadListPrec :: ReadPrec [ListIdentityPools]
readPrec :: ReadPrec ListIdentityPools
$creadPrec :: ReadPrec ListIdentityPools
readList :: ReadS [ListIdentityPools]
$creadList :: ReadS [ListIdentityPools]
readsPrec :: Int -> ReadS ListIdentityPools
$creadsPrec :: Int -> ReadS ListIdentityPools
Prelude.Read, Int -> ListIdentityPools -> ShowS
[ListIdentityPools] -> ShowS
ListIdentityPools -> String
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [ListIdentityPools] -> ShowS
$cshowList :: [ListIdentityPools] -> ShowS
show :: ListIdentityPools -> String
$cshow :: ListIdentityPools -> String
showsPrec :: Int -> ListIdentityPools -> ShowS
$cshowsPrec :: Int -> ListIdentityPools -> ShowS
Prelude.Show, forall x. Rep ListIdentityPools x -> ListIdentityPools
forall x. ListIdentityPools -> Rep ListIdentityPools x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cto :: forall x. Rep ListIdentityPools x -> ListIdentityPools
$cfrom :: forall x. ListIdentityPools -> Rep ListIdentityPools x
Prelude.Generic)

-- |
-- Create a value of 'ListIdentityPools' 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', 'listIdentityPools_nextToken' - A pagination token.
--
-- 'maxResults', 'listIdentityPools_maxResults' - The maximum number of identities to return.
newListIdentityPools ::
  -- | 'maxResults'
  Prelude.Natural ->
  ListIdentityPools
newListIdentityPools :: Natural -> ListIdentityPools
newListIdentityPools Natural
pMaxResults_ =
  ListIdentityPools'
    { $sel:nextToken:ListIdentityPools' :: Maybe Text
nextToken = forall a. Maybe a
Prelude.Nothing,
      $sel:maxResults:ListIdentityPools' :: Natural
maxResults = Natural
pMaxResults_
    }

-- | A pagination token.
listIdentityPools_nextToken :: Lens.Lens' ListIdentityPools (Prelude.Maybe Prelude.Text)
listIdentityPools_nextToken :: Lens' ListIdentityPools (Maybe Text)
listIdentityPools_nextToken = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\ListIdentityPools' {Maybe Text
nextToken :: Maybe Text
$sel:nextToken:ListIdentityPools' :: ListIdentityPools -> Maybe Text
nextToken} -> Maybe Text
nextToken) (\s :: ListIdentityPools
s@ListIdentityPools' {} Maybe Text
a -> ListIdentityPools
s {$sel:nextToken:ListIdentityPools' :: Maybe Text
nextToken = Maybe Text
a} :: ListIdentityPools)

-- | The maximum number of identities to return.
listIdentityPools_maxResults :: Lens.Lens' ListIdentityPools Prelude.Natural
listIdentityPools_maxResults :: Lens' ListIdentityPools Natural
listIdentityPools_maxResults = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\ListIdentityPools' {Natural
maxResults :: Natural
$sel:maxResults:ListIdentityPools' :: ListIdentityPools -> Natural
maxResults} -> Natural
maxResults) (\s :: ListIdentityPools
s@ListIdentityPools' {} Natural
a -> ListIdentityPools
s {$sel:maxResults:ListIdentityPools' :: Natural
maxResults = Natural
a} :: ListIdentityPools)

instance Core.AWSPager ListIdentityPools where
  page :: ListIdentityPools
-> AWSResponse ListIdentityPools -> Maybe ListIdentityPools
page ListIdentityPools
rq AWSResponse ListIdentityPools
rs
    | forall a. AWSTruncated a => a -> Bool
Core.stop
        ( AWSResponse ListIdentityPools
rs
            forall s a. s -> Getting (First a) s a -> Maybe a
Lens.^? Lens' ListIdentityPoolsResponse (Maybe Text)
listIdentityPoolsResponse_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 ListIdentityPools
rs
            forall s a. s -> Getting (First a) s a -> Maybe a
Lens.^? Lens'
  ListIdentityPoolsResponse (Maybe [IdentityPoolShortDescription])
listIdentityPoolsResponse_identityPools
            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.$ ListIdentityPools
rq
          forall a b. a -> (a -> b) -> b
Prelude.& Lens' ListIdentityPools (Maybe Text)
listIdentityPools_nextToken
          forall s t a b. ASetter s t a b -> b -> s -> t
Lens..~ AWSResponse ListIdentityPools
rs
          forall s a. s -> Getting (First a) s a -> Maybe a
Lens.^? Lens' ListIdentityPoolsResponse (Maybe Text)
listIdentityPoolsResponse_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 ListIdentityPools where
  type
    AWSResponse ListIdentityPools =
      ListIdentityPoolsResponse
  request :: (Service -> Service)
-> ListIdentityPools -> Request ListIdentityPools
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 ListIdentityPools
-> ClientResponse ClientBody
-> m (Either
        Error (ClientResponse (AWSResponse ListIdentityPools)))
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 [IdentityPoolShortDescription]
-> Maybe Text -> Int -> ListIdentityPoolsResponse
ListIdentityPoolsResponse'
            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
"IdentityPools" 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 ListIdentityPools where
  hashWithSalt :: Int -> ListIdentityPools -> Int
hashWithSalt Int
_salt ListIdentityPools' {Natural
Maybe Text
maxResults :: Natural
nextToken :: Maybe Text
$sel:maxResults:ListIdentityPools' :: ListIdentityPools -> Natural
$sel:nextToken:ListIdentityPools' :: ListIdentityPools -> 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 ListIdentityPools where
  rnf :: ListIdentityPools -> ()
rnf ListIdentityPools' {Natural
Maybe Text
maxResults :: Natural
nextToken :: Maybe Text
$sel:maxResults:ListIdentityPools' :: ListIdentityPools -> Natural
$sel:nextToken:ListIdentityPools' :: ListIdentityPools -> 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 ListIdentityPools where
  toHeaders :: ListIdentityPools -> 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
"AWSCognitoIdentityService.ListIdentityPools" ::
                          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 ListIdentityPools where
  toJSON :: ListIdentityPools -> Value
toJSON ListIdentityPools' {Natural
Maybe Text
maxResults :: Natural
nextToken :: Maybe Text
$sel:maxResults:ListIdentityPools' :: ListIdentityPools -> Natural
$sel:nextToken:ListIdentityPools' :: ListIdentityPools -> 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 ListIdentityPools where
  toPath :: ListIdentityPools -> ByteString
toPath = forall a b. a -> b -> a
Prelude.const ByteString
"/"

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

-- | The result of a successful ListIdentityPools action.
--
-- /See:/ 'newListIdentityPoolsResponse' smart constructor.
data ListIdentityPoolsResponse = ListIdentityPoolsResponse'
  { -- | The identity pools returned by the ListIdentityPools action.
    ListIdentityPoolsResponse -> Maybe [IdentityPoolShortDescription]
identityPools :: Prelude.Maybe [IdentityPoolShortDescription],
    -- | A pagination token.
    ListIdentityPoolsResponse -> Maybe Text
nextToken :: Prelude.Maybe Prelude.Text,
    -- | The response's http status code.
    ListIdentityPoolsResponse -> Int
httpStatus :: Prelude.Int
  }
  deriving (ListIdentityPoolsResponse -> ListIdentityPoolsResponse -> Bool
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: ListIdentityPoolsResponse -> ListIdentityPoolsResponse -> Bool
$c/= :: ListIdentityPoolsResponse -> ListIdentityPoolsResponse -> Bool
== :: ListIdentityPoolsResponse -> ListIdentityPoolsResponse -> Bool
$c== :: ListIdentityPoolsResponse -> ListIdentityPoolsResponse -> Bool
Prelude.Eq, ReadPrec [ListIdentityPoolsResponse]
ReadPrec ListIdentityPoolsResponse
Int -> ReadS ListIdentityPoolsResponse
ReadS [ListIdentityPoolsResponse]
forall a.
(Int -> ReadS a)
-> ReadS [a] -> ReadPrec a -> ReadPrec [a] -> Read a
readListPrec :: ReadPrec [ListIdentityPoolsResponse]
$creadListPrec :: ReadPrec [ListIdentityPoolsResponse]
readPrec :: ReadPrec ListIdentityPoolsResponse
$creadPrec :: ReadPrec ListIdentityPoolsResponse
readList :: ReadS [ListIdentityPoolsResponse]
$creadList :: ReadS [ListIdentityPoolsResponse]
readsPrec :: Int -> ReadS ListIdentityPoolsResponse
$creadsPrec :: Int -> ReadS ListIdentityPoolsResponse
Prelude.Read, Int -> ListIdentityPoolsResponse -> ShowS
[ListIdentityPoolsResponse] -> ShowS
ListIdentityPoolsResponse -> String
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [ListIdentityPoolsResponse] -> ShowS
$cshowList :: [ListIdentityPoolsResponse] -> ShowS
show :: ListIdentityPoolsResponse -> String
$cshow :: ListIdentityPoolsResponse -> String
showsPrec :: Int -> ListIdentityPoolsResponse -> ShowS
$cshowsPrec :: Int -> ListIdentityPoolsResponse -> ShowS
Prelude.Show, forall x.
Rep ListIdentityPoolsResponse x -> ListIdentityPoolsResponse
forall x.
ListIdentityPoolsResponse -> Rep ListIdentityPoolsResponse x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cto :: forall x.
Rep ListIdentityPoolsResponse x -> ListIdentityPoolsResponse
$cfrom :: forall x.
ListIdentityPoolsResponse -> Rep ListIdentityPoolsResponse x
Prelude.Generic)

-- |
-- Create a value of 'ListIdentityPoolsResponse' 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:
--
-- 'identityPools', 'listIdentityPoolsResponse_identityPools' - The identity pools returned by the ListIdentityPools action.
--
-- 'nextToken', 'listIdentityPoolsResponse_nextToken' - A pagination token.
--
-- 'httpStatus', 'listIdentityPoolsResponse_httpStatus' - The response's http status code.
newListIdentityPoolsResponse ::
  -- | 'httpStatus'
  Prelude.Int ->
  ListIdentityPoolsResponse
newListIdentityPoolsResponse :: Int -> ListIdentityPoolsResponse
newListIdentityPoolsResponse Int
pHttpStatus_ =
  ListIdentityPoolsResponse'
    { $sel:identityPools:ListIdentityPoolsResponse' :: Maybe [IdentityPoolShortDescription]
identityPools =
        forall a. Maybe a
Prelude.Nothing,
      $sel:nextToken:ListIdentityPoolsResponse' :: Maybe Text
nextToken = forall a. Maybe a
Prelude.Nothing,
      $sel:httpStatus:ListIdentityPoolsResponse' :: Int
httpStatus = Int
pHttpStatus_
    }

-- | The identity pools returned by the ListIdentityPools action.
listIdentityPoolsResponse_identityPools :: Lens.Lens' ListIdentityPoolsResponse (Prelude.Maybe [IdentityPoolShortDescription])
listIdentityPoolsResponse_identityPools :: Lens'
  ListIdentityPoolsResponse (Maybe [IdentityPoolShortDescription])
listIdentityPoolsResponse_identityPools = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\ListIdentityPoolsResponse' {Maybe [IdentityPoolShortDescription]
identityPools :: Maybe [IdentityPoolShortDescription]
$sel:identityPools:ListIdentityPoolsResponse' :: ListIdentityPoolsResponse -> Maybe [IdentityPoolShortDescription]
identityPools} -> Maybe [IdentityPoolShortDescription]
identityPools) (\s :: ListIdentityPoolsResponse
s@ListIdentityPoolsResponse' {} Maybe [IdentityPoolShortDescription]
a -> ListIdentityPoolsResponse
s {$sel:identityPools:ListIdentityPoolsResponse' :: Maybe [IdentityPoolShortDescription]
identityPools = Maybe [IdentityPoolShortDescription]
a} :: ListIdentityPoolsResponse) 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 pagination token.
listIdentityPoolsResponse_nextToken :: Lens.Lens' ListIdentityPoolsResponse (Prelude.Maybe Prelude.Text)
listIdentityPoolsResponse_nextToken :: Lens' ListIdentityPoolsResponse (Maybe Text)
listIdentityPoolsResponse_nextToken = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\ListIdentityPoolsResponse' {Maybe Text
nextToken :: Maybe Text
$sel:nextToken:ListIdentityPoolsResponse' :: ListIdentityPoolsResponse -> Maybe Text
nextToken} -> Maybe Text
nextToken) (\s :: ListIdentityPoolsResponse
s@ListIdentityPoolsResponse' {} Maybe Text
a -> ListIdentityPoolsResponse
s {$sel:nextToken:ListIdentityPoolsResponse' :: Maybe Text
nextToken = Maybe Text
a} :: ListIdentityPoolsResponse)

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

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