{-# 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.DescribeUserPool
-- Copyright   : (c) 2013-2023 Brendan Hay
-- License     : Mozilla Public License, v. 2.0.
-- Maintainer  : Brendan Hay
-- Stability   : auto-generated
-- Portability : non-portable (GHC extensions)
--
-- Returns the configuration information and metadata of the specified user
-- pool.
module Amazonka.CognitoIdentityProvider.DescribeUserPool
  ( -- * Creating a Request
    DescribeUserPool (..),
    newDescribeUserPool,

    -- * Request Lenses
    describeUserPool_userPoolId,

    -- * Destructuring the Response
    DescribeUserPoolResponse (..),
    newDescribeUserPoolResponse,

    -- * Response Lenses
    describeUserPoolResponse_userPool,
    describeUserPoolResponse_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 describe the user pool.
--
-- /See:/ 'newDescribeUserPool' smart constructor.
data DescribeUserPool = DescribeUserPool'
  { -- | The user pool ID for the user pool you want to describe.
    DescribeUserPool -> Text
userPoolId :: Prelude.Text
  }
  deriving (DescribeUserPool -> DescribeUserPool -> Bool
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: DescribeUserPool -> DescribeUserPool -> Bool
$c/= :: DescribeUserPool -> DescribeUserPool -> Bool
== :: DescribeUserPool -> DescribeUserPool -> Bool
$c== :: DescribeUserPool -> DescribeUserPool -> Bool
Prelude.Eq, ReadPrec [DescribeUserPool]
ReadPrec DescribeUserPool
Int -> ReadS DescribeUserPool
ReadS [DescribeUserPool]
forall a.
(Int -> ReadS a)
-> ReadS [a] -> ReadPrec a -> ReadPrec [a] -> Read a
readListPrec :: ReadPrec [DescribeUserPool]
$creadListPrec :: ReadPrec [DescribeUserPool]
readPrec :: ReadPrec DescribeUserPool
$creadPrec :: ReadPrec DescribeUserPool
readList :: ReadS [DescribeUserPool]
$creadList :: ReadS [DescribeUserPool]
readsPrec :: Int -> ReadS DescribeUserPool
$creadsPrec :: Int -> ReadS DescribeUserPool
Prelude.Read, Int -> DescribeUserPool -> ShowS
[DescribeUserPool] -> ShowS
DescribeUserPool -> String
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [DescribeUserPool] -> ShowS
$cshowList :: [DescribeUserPool] -> ShowS
show :: DescribeUserPool -> String
$cshow :: DescribeUserPool -> String
showsPrec :: Int -> DescribeUserPool -> ShowS
$cshowsPrec :: Int -> DescribeUserPool -> ShowS
Prelude.Show, forall x. Rep DescribeUserPool x -> DescribeUserPool
forall x. DescribeUserPool -> Rep DescribeUserPool x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cto :: forall x. Rep DescribeUserPool x -> DescribeUserPool
$cfrom :: forall x. DescribeUserPool -> Rep DescribeUserPool x
Prelude.Generic)

-- |
-- Create a value of 'DescribeUserPool' 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:
--
-- 'userPoolId', 'describeUserPool_userPoolId' - The user pool ID for the user pool you want to describe.
newDescribeUserPool ::
  -- | 'userPoolId'
  Prelude.Text ->
  DescribeUserPool
newDescribeUserPool :: Text -> DescribeUserPool
newDescribeUserPool Text
pUserPoolId_ =
  DescribeUserPool' {$sel:userPoolId:DescribeUserPool' :: Text
userPoolId = Text
pUserPoolId_}

-- | The user pool ID for the user pool you want to describe.
describeUserPool_userPoolId :: Lens.Lens' DescribeUserPool Prelude.Text
describeUserPool_userPoolId :: Lens' DescribeUserPool Text
describeUserPool_userPoolId = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\DescribeUserPool' {Text
userPoolId :: Text
$sel:userPoolId:DescribeUserPool' :: DescribeUserPool -> Text
userPoolId} -> Text
userPoolId) (\s :: DescribeUserPool
s@DescribeUserPool' {} Text
a -> DescribeUserPool
s {$sel:userPoolId:DescribeUserPool' :: Text
userPoolId = Text
a} :: DescribeUserPool)

instance Core.AWSRequest DescribeUserPool where
  type
    AWSResponse DescribeUserPool =
      DescribeUserPoolResponse
  request :: (Service -> Service)
-> DescribeUserPool -> Request DescribeUserPool
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 DescribeUserPool
-> ClientResponse ClientBody
-> m (Either Error (ClientResponse (AWSResponse DescribeUserPool)))
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 UserPoolType -> Int -> DescribeUserPoolResponse
DescribeUserPoolResponse'
            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
"UserPool")
            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 DescribeUserPool where
  hashWithSalt :: Int -> DescribeUserPool -> Int
hashWithSalt Int
_salt DescribeUserPool' {Text
userPoolId :: Text
$sel:userPoolId:DescribeUserPool' :: DescribeUserPool -> Text
..} =
    Int
_salt forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Text
userPoolId

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

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

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

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

-- | Represents the response to describe the user pool.
--
-- /See:/ 'newDescribeUserPoolResponse' smart constructor.
data DescribeUserPoolResponse = DescribeUserPoolResponse'
  { -- | The container of metadata returned by the server to describe the pool.
    DescribeUserPoolResponse -> Maybe UserPoolType
userPool :: Prelude.Maybe UserPoolType,
    -- | The response's http status code.
    DescribeUserPoolResponse -> Int
httpStatus :: Prelude.Int
  }
  deriving (DescribeUserPoolResponse -> DescribeUserPoolResponse -> Bool
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: DescribeUserPoolResponse -> DescribeUserPoolResponse -> Bool
$c/= :: DescribeUserPoolResponse -> DescribeUserPoolResponse -> Bool
== :: DescribeUserPoolResponse -> DescribeUserPoolResponse -> Bool
$c== :: DescribeUserPoolResponse -> DescribeUserPoolResponse -> Bool
Prelude.Eq, ReadPrec [DescribeUserPoolResponse]
ReadPrec DescribeUserPoolResponse
Int -> ReadS DescribeUserPoolResponse
ReadS [DescribeUserPoolResponse]
forall a.
(Int -> ReadS a)
-> ReadS [a] -> ReadPrec a -> ReadPrec [a] -> Read a
readListPrec :: ReadPrec [DescribeUserPoolResponse]
$creadListPrec :: ReadPrec [DescribeUserPoolResponse]
readPrec :: ReadPrec DescribeUserPoolResponse
$creadPrec :: ReadPrec DescribeUserPoolResponse
readList :: ReadS [DescribeUserPoolResponse]
$creadList :: ReadS [DescribeUserPoolResponse]
readsPrec :: Int -> ReadS DescribeUserPoolResponse
$creadsPrec :: Int -> ReadS DescribeUserPoolResponse
Prelude.Read, Int -> DescribeUserPoolResponse -> ShowS
[DescribeUserPoolResponse] -> ShowS
DescribeUserPoolResponse -> String
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [DescribeUserPoolResponse] -> ShowS
$cshowList :: [DescribeUserPoolResponse] -> ShowS
show :: DescribeUserPoolResponse -> String
$cshow :: DescribeUserPoolResponse -> String
showsPrec :: Int -> DescribeUserPoolResponse -> ShowS
$cshowsPrec :: Int -> DescribeUserPoolResponse -> ShowS
Prelude.Show, forall x.
Rep DescribeUserPoolResponse x -> DescribeUserPoolResponse
forall x.
DescribeUserPoolResponse -> Rep DescribeUserPoolResponse x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cto :: forall x.
Rep DescribeUserPoolResponse x -> DescribeUserPoolResponse
$cfrom :: forall x.
DescribeUserPoolResponse -> Rep DescribeUserPoolResponse x
Prelude.Generic)

-- |
-- Create a value of 'DescribeUserPoolResponse' 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:
--
-- 'userPool', 'describeUserPoolResponse_userPool' - The container of metadata returned by the server to describe the pool.
--
-- 'httpStatus', 'describeUserPoolResponse_httpStatus' - The response's http status code.
newDescribeUserPoolResponse ::
  -- | 'httpStatus'
  Prelude.Int ->
  DescribeUserPoolResponse
newDescribeUserPoolResponse :: Int -> DescribeUserPoolResponse
newDescribeUserPoolResponse Int
pHttpStatus_ =
  DescribeUserPoolResponse'
    { $sel:userPool:DescribeUserPoolResponse' :: Maybe UserPoolType
userPool =
        forall a. Maybe a
Prelude.Nothing,
      $sel:httpStatus:DescribeUserPoolResponse' :: Int
httpStatus = Int
pHttpStatus_
    }

-- | The container of metadata returned by the server to describe the pool.
describeUserPoolResponse_userPool :: Lens.Lens' DescribeUserPoolResponse (Prelude.Maybe UserPoolType)
describeUserPoolResponse_userPool :: Lens' DescribeUserPoolResponse (Maybe UserPoolType)
describeUserPoolResponse_userPool = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\DescribeUserPoolResponse' {Maybe UserPoolType
userPool :: Maybe UserPoolType
$sel:userPool:DescribeUserPoolResponse' :: DescribeUserPoolResponse -> Maybe UserPoolType
userPool} -> Maybe UserPoolType
userPool) (\s :: DescribeUserPoolResponse
s@DescribeUserPoolResponse' {} Maybe UserPoolType
a -> DescribeUserPoolResponse
s {$sel:userPool:DescribeUserPoolResponse' :: Maybe UserPoolType
userPool = Maybe UserPoolType
a} :: DescribeUserPoolResponse)

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

instance Prelude.NFData DescribeUserPoolResponse where
  rnf :: DescribeUserPoolResponse -> ()
rnf DescribeUserPoolResponse' {Int
Maybe UserPoolType
httpStatus :: Int
userPool :: Maybe UserPoolType
$sel:httpStatus:DescribeUserPoolResponse' :: DescribeUserPoolResponse -> Int
$sel:userPool:DescribeUserPoolResponse' :: DescribeUserPoolResponse -> Maybe UserPoolType
..} =
    forall a. NFData a => a -> ()
Prelude.rnf Maybe UserPoolType
userPool
      seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf Int
httpStatus