{-# 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.DescribeIdentityPool
-- Copyright   : (c) 2013-2023 Brendan Hay
-- License     : Mozilla Public License, v. 2.0.
-- Maintainer  : Brendan Hay
-- Stability   : auto-generated
-- Portability : non-portable (GHC extensions)
--
-- Gets details about a particular identity pool, including the pool name,
-- ID description, creation date, and current number of users.
--
-- You must use AWS Developer credentials to call this API.
module Amazonka.CognitoIdentity.DescribeIdentityPool
  ( -- * Creating a Request
    DescribeIdentityPool (..),
    newDescribeIdentityPool,

    -- * Request Lenses
    describeIdentityPool_identityPoolId,

    -- * Destructuring the Response
    IdentityPool (..),
    newIdentityPool,

    -- * Response Lenses
    identityPool_allowClassicFlow,
    identityPool_cognitoIdentityProviders,
    identityPool_developerProviderName,
    identityPool_identityPoolTags,
    identityPool_openIdConnectProviderARNs,
    identityPool_samlProviderARNs,
    identityPool_supportedLoginProviders,
    identityPool_identityPoolId,
    identityPool_identityPoolName,
    identityPool_allowUnauthenticatedIdentities,
  )
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 DescribeIdentityPool action.
--
-- /See:/ 'newDescribeIdentityPool' smart constructor.
data DescribeIdentityPool = DescribeIdentityPool'
  { -- | An identity pool ID in the format REGION:GUID.
    DescribeIdentityPool -> Text
identityPoolId :: Prelude.Text
  }
  deriving (DescribeIdentityPool -> DescribeIdentityPool -> Bool
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: DescribeIdentityPool -> DescribeIdentityPool -> Bool
$c/= :: DescribeIdentityPool -> DescribeIdentityPool -> Bool
== :: DescribeIdentityPool -> DescribeIdentityPool -> Bool
$c== :: DescribeIdentityPool -> DescribeIdentityPool -> Bool
Prelude.Eq, ReadPrec [DescribeIdentityPool]
ReadPrec DescribeIdentityPool
Int -> ReadS DescribeIdentityPool
ReadS [DescribeIdentityPool]
forall a.
(Int -> ReadS a)
-> ReadS [a] -> ReadPrec a -> ReadPrec [a] -> Read a
readListPrec :: ReadPrec [DescribeIdentityPool]
$creadListPrec :: ReadPrec [DescribeIdentityPool]
readPrec :: ReadPrec DescribeIdentityPool
$creadPrec :: ReadPrec DescribeIdentityPool
readList :: ReadS [DescribeIdentityPool]
$creadList :: ReadS [DescribeIdentityPool]
readsPrec :: Int -> ReadS DescribeIdentityPool
$creadsPrec :: Int -> ReadS DescribeIdentityPool
Prelude.Read, Int -> DescribeIdentityPool -> ShowS
[DescribeIdentityPool] -> ShowS
DescribeIdentityPool -> String
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [DescribeIdentityPool] -> ShowS
$cshowList :: [DescribeIdentityPool] -> ShowS
show :: DescribeIdentityPool -> String
$cshow :: DescribeIdentityPool -> String
showsPrec :: Int -> DescribeIdentityPool -> ShowS
$cshowsPrec :: Int -> DescribeIdentityPool -> ShowS
Prelude.Show, forall x. Rep DescribeIdentityPool x -> DescribeIdentityPool
forall x. DescribeIdentityPool -> Rep DescribeIdentityPool x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cto :: forall x. Rep DescribeIdentityPool x -> DescribeIdentityPool
$cfrom :: forall x. DescribeIdentityPool -> Rep DescribeIdentityPool x
Prelude.Generic)

-- |
-- Create a value of 'DescribeIdentityPool' 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:
--
-- 'identityPoolId', 'describeIdentityPool_identityPoolId' - An identity pool ID in the format REGION:GUID.
newDescribeIdentityPool ::
  -- | 'identityPoolId'
  Prelude.Text ->
  DescribeIdentityPool
newDescribeIdentityPool :: Text -> DescribeIdentityPool
newDescribeIdentityPool Text
pIdentityPoolId_ =
  DescribeIdentityPool'
    { $sel:identityPoolId:DescribeIdentityPool' :: Text
identityPoolId =
        Text
pIdentityPoolId_
    }

-- | An identity pool ID in the format REGION:GUID.
describeIdentityPool_identityPoolId :: Lens.Lens' DescribeIdentityPool Prelude.Text
describeIdentityPool_identityPoolId :: Lens' DescribeIdentityPool Text
describeIdentityPool_identityPoolId = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\DescribeIdentityPool' {Text
identityPoolId :: Text
$sel:identityPoolId:DescribeIdentityPool' :: DescribeIdentityPool -> Text
identityPoolId} -> Text
identityPoolId) (\s :: DescribeIdentityPool
s@DescribeIdentityPool' {} Text
a -> DescribeIdentityPool
s {$sel:identityPoolId:DescribeIdentityPool' :: Text
identityPoolId = Text
a} :: DescribeIdentityPool)

instance Core.AWSRequest DescribeIdentityPool where
  type AWSResponse DescribeIdentityPool = IdentityPool
  request :: (Service -> Service)
-> DescribeIdentityPool -> Request DescribeIdentityPool
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 DescribeIdentityPool
-> ClientResponse ClientBody
-> m (Either
        Error (ClientResponse (AWSResponse DescribeIdentityPool)))
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 -> forall a. FromJSON a => Object -> Either String a
Data.eitherParseJSON Object
x)

instance Prelude.Hashable DescribeIdentityPool where
  hashWithSalt :: Int -> DescribeIdentityPool -> Int
hashWithSalt Int
_salt DescribeIdentityPool' {Text
identityPoolId :: Text
$sel:identityPoolId:DescribeIdentityPool' :: DescribeIdentityPool -> Text
..} =
    Int
_salt forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Text
identityPoolId

instance Prelude.NFData DescribeIdentityPool where
  rnf :: DescribeIdentityPool -> ()
rnf DescribeIdentityPool' {Text
identityPoolId :: Text
$sel:identityPoolId:DescribeIdentityPool' :: DescribeIdentityPool -> Text
..} =
    forall a. NFData a => a -> ()
Prelude.rnf Text
identityPoolId

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

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

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