{-# 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.CreateUserPoolDomain
-- Copyright   : (c) 2013-2023 Brendan Hay
-- License     : Mozilla Public License, v. 2.0.
-- Maintainer  : Brendan Hay
-- Stability   : auto-generated
-- Portability : non-portable (GHC extensions)
--
-- Creates a new domain for a user pool.
module Amazonka.CognitoIdentityProvider.CreateUserPoolDomain
  ( -- * Creating a Request
    CreateUserPoolDomain (..),
    newCreateUserPoolDomain,

    -- * Request Lenses
    createUserPoolDomain_customDomainConfig,
    createUserPoolDomain_domain,
    createUserPoolDomain_userPoolId,

    -- * Destructuring the Response
    CreateUserPoolDomainResponse (..),
    newCreateUserPoolDomainResponse,

    -- * Response Lenses
    createUserPoolDomainResponse_cloudFrontDomain,
    createUserPoolDomainResponse_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

-- | /See:/ 'newCreateUserPoolDomain' smart constructor.
data CreateUserPoolDomain = CreateUserPoolDomain'
  { -- | The configuration for a custom domain that hosts the sign-up and sign-in
    -- webpages for your application.
    --
    -- Provide this parameter only if you want to use a custom domain for your
    -- user pool. Otherwise, you can exclude this parameter and use the Amazon
    -- Cognito hosted domain instead.
    --
    -- For more information about the hosted domain and custom domains, see
    -- <https://docs.aws.amazon.com/cognito/latest/developerguide/cognito-user-pools-assign-domain.html Configuring a User Pool Domain>.
    CreateUserPoolDomain -> Maybe CustomDomainConfigType
customDomainConfig :: Prelude.Maybe CustomDomainConfigType,
    -- | The domain string. For custom domains, this is the fully-qualified
    -- domain name, such as @auth.example.com@. For Amazon Cognito prefix
    -- domains, this is the prefix alone, such as @auth@.
    CreateUserPoolDomain -> Text
domain :: Prelude.Text,
    -- | The user pool ID.
    CreateUserPoolDomain -> Text
userPoolId :: Prelude.Text
  }
  deriving (CreateUserPoolDomain -> CreateUserPoolDomain -> Bool
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: CreateUserPoolDomain -> CreateUserPoolDomain -> Bool
$c/= :: CreateUserPoolDomain -> CreateUserPoolDomain -> Bool
== :: CreateUserPoolDomain -> CreateUserPoolDomain -> Bool
$c== :: CreateUserPoolDomain -> CreateUserPoolDomain -> Bool
Prelude.Eq, ReadPrec [CreateUserPoolDomain]
ReadPrec CreateUserPoolDomain
Int -> ReadS CreateUserPoolDomain
ReadS [CreateUserPoolDomain]
forall a.
(Int -> ReadS a)
-> ReadS [a] -> ReadPrec a -> ReadPrec [a] -> Read a
readListPrec :: ReadPrec [CreateUserPoolDomain]
$creadListPrec :: ReadPrec [CreateUserPoolDomain]
readPrec :: ReadPrec CreateUserPoolDomain
$creadPrec :: ReadPrec CreateUserPoolDomain
readList :: ReadS [CreateUserPoolDomain]
$creadList :: ReadS [CreateUserPoolDomain]
readsPrec :: Int -> ReadS CreateUserPoolDomain
$creadsPrec :: Int -> ReadS CreateUserPoolDomain
Prelude.Read, Int -> CreateUserPoolDomain -> ShowS
[CreateUserPoolDomain] -> ShowS
CreateUserPoolDomain -> String
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [CreateUserPoolDomain] -> ShowS
$cshowList :: [CreateUserPoolDomain] -> ShowS
show :: CreateUserPoolDomain -> String
$cshow :: CreateUserPoolDomain -> String
showsPrec :: Int -> CreateUserPoolDomain -> ShowS
$cshowsPrec :: Int -> CreateUserPoolDomain -> ShowS
Prelude.Show, forall x. Rep CreateUserPoolDomain x -> CreateUserPoolDomain
forall x. CreateUserPoolDomain -> Rep CreateUserPoolDomain x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cto :: forall x. Rep CreateUserPoolDomain x -> CreateUserPoolDomain
$cfrom :: forall x. CreateUserPoolDomain -> Rep CreateUserPoolDomain x
Prelude.Generic)

-- |
-- Create a value of 'CreateUserPoolDomain' 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:
--
-- 'customDomainConfig', 'createUserPoolDomain_customDomainConfig' - The configuration for a custom domain that hosts the sign-up and sign-in
-- webpages for your application.
--
-- Provide this parameter only if you want to use a custom domain for your
-- user pool. Otherwise, you can exclude this parameter and use the Amazon
-- Cognito hosted domain instead.
--
-- For more information about the hosted domain and custom domains, see
-- <https://docs.aws.amazon.com/cognito/latest/developerguide/cognito-user-pools-assign-domain.html Configuring a User Pool Domain>.
--
-- 'domain', 'createUserPoolDomain_domain' - The domain string. For custom domains, this is the fully-qualified
-- domain name, such as @auth.example.com@. For Amazon Cognito prefix
-- domains, this is the prefix alone, such as @auth@.
--
-- 'userPoolId', 'createUserPoolDomain_userPoolId' - The user pool ID.
newCreateUserPoolDomain ::
  -- | 'domain'
  Prelude.Text ->
  -- | 'userPoolId'
  Prelude.Text ->
  CreateUserPoolDomain
newCreateUserPoolDomain :: Text -> Text -> CreateUserPoolDomain
newCreateUserPoolDomain Text
pDomain_ Text
pUserPoolId_ =
  CreateUserPoolDomain'
    { $sel:customDomainConfig:CreateUserPoolDomain' :: Maybe CustomDomainConfigType
customDomainConfig =
        forall a. Maybe a
Prelude.Nothing,
      $sel:domain:CreateUserPoolDomain' :: Text
domain = Text
pDomain_,
      $sel:userPoolId:CreateUserPoolDomain' :: Text
userPoolId = Text
pUserPoolId_
    }

-- | The configuration for a custom domain that hosts the sign-up and sign-in
-- webpages for your application.
--
-- Provide this parameter only if you want to use a custom domain for your
-- user pool. Otherwise, you can exclude this parameter and use the Amazon
-- Cognito hosted domain instead.
--
-- For more information about the hosted domain and custom domains, see
-- <https://docs.aws.amazon.com/cognito/latest/developerguide/cognito-user-pools-assign-domain.html Configuring a User Pool Domain>.
createUserPoolDomain_customDomainConfig :: Lens.Lens' CreateUserPoolDomain (Prelude.Maybe CustomDomainConfigType)
createUserPoolDomain_customDomainConfig :: Lens' CreateUserPoolDomain (Maybe CustomDomainConfigType)
createUserPoolDomain_customDomainConfig = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\CreateUserPoolDomain' {Maybe CustomDomainConfigType
customDomainConfig :: Maybe CustomDomainConfigType
$sel:customDomainConfig:CreateUserPoolDomain' :: CreateUserPoolDomain -> Maybe CustomDomainConfigType
customDomainConfig} -> Maybe CustomDomainConfigType
customDomainConfig) (\s :: CreateUserPoolDomain
s@CreateUserPoolDomain' {} Maybe CustomDomainConfigType
a -> CreateUserPoolDomain
s {$sel:customDomainConfig:CreateUserPoolDomain' :: Maybe CustomDomainConfigType
customDomainConfig = Maybe CustomDomainConfigType
a} :: CreateUserPoolDomain)

-- | The domain string. For custom domains, this is the fully-qualified
-- domain name, such as @auth.example.com@. For Amazon Cognito prefix
-- domains, this is the prefix alone, such as @auth@.
createUserPoolDomain_domain :: Lens.Lens' CreateUserPoolDomain Prelude.Text
createUserPoolDomain_domain :: Lens' CreateUserPoolDomain Text
createUserPoolDomain_domain = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\CreateUserPoolDomain' {Text
domain :: Text
$sel:domain:CreateUserPoolDomain' :: CreateUserPoolDomain -> Text
domain} -> Text
domain) (\s :: CreateUserPoolDomain
s@CreateUserPoolDomain' {} Text
a -> CreateUserPoolDomain
s {$sel:domain:CreateUserPoolDomain' :: Text
domain = Text
a} :: CreateUserPoolDomain)

-- | The user pool ID.
createUserPoolDomain_userPoolId :: Lens.Lens' CreateUserPoolDomain Prelude.Text
createUserPoolDomain_userPoolId :: Lens' CreateUserPoolDomain Text
createUserPoolDomain_userPoolId = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\CreateUserPoolDomain' {Text
userPoolId :: Text
$sel:userPoolId:CreateUserPoolDomain' :: CreateUserPoolDomain -> Text
userPoolId} -> Text
userPoolId) (\s :: CreateUserPoolDomain
s@CreateUserPoolDomain' {} Text
a -> CreateUserPoolDomain
s {$sel:userPoolId:CreateUserPoolDomain' :: Text
userPoolId = Text
a} :: CreateUserPoolDomain)

instance Core.AWSRequest CreateUserPoolDomain where
  type
    AWSResponse CreateUserPoolDomain =
      CreateUserPoolDomainResponse
  request :: (Service -> Service)
-> CreateUserPoolDomain -> Request CreateUserPoolDomain
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 CreateUserPoolDomain
-> ClientResponse ClientBody
-> m (Either
        Error (ClientResponse (AWSResponse CreateUserPoolDomain)))
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 -> Int -> CreateUserPoolDomainResponse
CreateUserPoolDomainResponse'
            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
"CloudFrontDomain")
            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 CreateUserPoolDomain where
  hashWithSalt :: Int -> CreateUserPoolDomain -> Int
hashWithSalt Int
_salt CreateUserPoolDomain' {Maybe CustomDomainConfigType
Text
userPoolId :: Text
domain :: Text
customDomainConfig :: Maybe CustomDomainConfigType
$sel:userPoolId:CreateUserPoolDomain' :: CreateUserPoolDomain -> Text
$sel:domain:CreateUserPoolDomain' :: CreateUserPoolDomain -> Text
$sel:customDomainConfig:CreateUserPoolDomain' :: CreateUserPoolDomain -> Maybe CustomDomainConfigType
..} =
    Int
_salt
      forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Maybe CustomDomainConfigType
customDomainConfig
      forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Text
domain
      forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Text
userPoolId

instance Prelude.NFData CreateUserPoolDomain where
  rnf :: CreateUserPoolDomain -> ()
rnf CreateUserPoolDomain' {Maybe CustomDomainConfigType
Text
userPoolId :: Text
domain :: Text
customDomainConfig :: Maybe CustomDomainConfigType
$sel:userPoolId:CreateUserPoolDomain' :: CreateUserPoolDomain -> Text
$sel:domain:CreateUserPoolDomain' :: CreateUserPoolDomain -> Text
$sel:customDomainConfig:CreateUserPoolDomain' :: CreateUserPoolDomain -> Maybe CustomDomainConfigType
..} =
    forall a. NFData a => a -> ()
Prelude.rnf Maybe CustomDomainConfigType
customDomainConfig
      seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf Text
domain
      seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf Text
userPoolId

instance Data.ToHeaders CreateUserPoolDomain where
  toHeaders :: CreateUserPoolDomain -> 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.CreateUserPoolDomain" ::
                          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 CreateUserPoolDomain where
  toJSON :: CreateUserPoolDomain -> Value
toJSON CreateUserPoolDomain' {Maybe CustomDomainConfigType
Text
userPoolId :: Text
domain :: Text
customDomainConfig :: Maybe CustomDomainConfigType
$sel:userPoolId:CreateUserPoolDomain' :: CreateUserPoolDomain -> Text
$sel:domain:CreateUserPoolDomain' :: CreateUserPoolDomain -> Text
$sel:customDomainConfig:CreateUserPoolDomain' :: CreateUserPoolDomain -> Maybe CustomDomainConfigType
..} =
    [Pair] -> Value
Data.object
      ( forall a. [Maybe a] -> [a]
Prelude.catMaybes
          [ (Key
"CustomDomainConfig" 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 CustomDomainConfigType
customDomainConfig,
            forall a. a -> Maybe a
Prelude.Just (Key
"Domain" forall kv v. (KeyValue kv, ToJSON v) => Key -> v -> kv
Data..= Text
domain),
            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 CreateUserPoolDomain where
  toPath :: CreateUserPoolDomain -> ByteString
toPath = forall a b. a -> b -> a
Prelude.const ByteString
"/"

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

-- | /See:/ 'newCreateUserPoolDomainResponse' smart constructor.
data CreateUserPoolDomainResponse = CreateUserPoolDomainResponse'
  { -- | The Amazon CloudFront endpoint that you use as the target of the alias
    -- that you set up with your Domain Name Service (DNS) provider.
    CreateUserPoolDomainResponse -> Maybe Text
cloudFrontDomain :: Prelude.Maybe Prelude.Text,
    -- | The response's http status code.
    CreateUserPoolDomainResponse -> Int
httpStatus :: Prelude.Int
  }
  deriving (CreateUserPoolDomainResponse
-> CreateUserPoolDomainResponse -> Bool
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: CreateUserPoolDomainResponse
-> CreateUserPoolDomainResponse -> Bool
$c/= :: CreateUserPoolDomainResponse
-> CreateUserPoolDomainResponse -> Bool
== :: CreateUserPoolDomainResponse
-> CreateUserPoolDomainResponse -> Bool
$c== :: CreateUserPoolDomainResponse
-> CreateUserPoolDomainResponse -> Bool
Prelude.Eq, ReadPrec [CreateUserPoolDomainResponse]
ReadPrec CreateUserPoolDomainResponse
Int -> ReadS CreateUserPoolDomainResponse
ReadS [CreateUserPoolDomainResponse]
forall a.
(Int -> ReadS a)
-> ReadS [a] -> ReadPrec a -> ReadPrec [a] -> Read a
readListPrec :: ReadPrec [CreateUserPoolDomainResponse]
$creadListPrec :: ReadPrec [CreateUserPoolDomainResponse]
readPrec :: ReadPrec CreateUserPoolDomainResponse
$creadPrec :: ReadPrec CreateUserPoolDomainResponse
readList :: ReadS [CreateUserPoolDomainResponse]
$creadList :: ReadS [CreateUserPoolDomainResponse]
readsPrec :: Int -> ReadS CreateUserPoolDomainResponse
$creadsPrec :: Int -> ReadS CreateUserPoolDomainResponse
Prelude.Read, Int -> CreateUserPoolDomainResponse -> ShowS
[CreateUserPoolDomainResponse] -> ShowS
CreateUserPoolDomainResponse -> String
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [CreateUserPoolDomainResponse] -> ShowS
$cshowList :: [CreateUserPoolDomainResponse] -> ShowS
show :: CreateUserPoolDomainResponse -> String
$cshow :: CreateUserPoolDomainResponse -> String
showsPrec :: Int -> CreateUserPoolDomainResponse -> ShowS
$cshowsPrec :: Int -> CreateUserPoolDomainResponse -> ShowS
Prelude.Show, forall x.
Rep CreateUserPoolDomainResponse x -> CreateUserPoolDomainResponse
forall x.
CreateUserPoolDomainResponse -> Rep CreateUserPoolDomainResponse x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cto :: forall x.
Rep CreateUserPoolDomainResponse x -> CreateUserPoolDomainResponse
$cfrom :: forall x.
CreateUserPoolDomainResponse -> Rep CreateUserPoolDomainResponse x
Prelude.Generic)

-- |
-- Create a value of 'CreateUserPoolDomainResponse' 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:
--
-- 'cloudFrontDomain', 'createUserPoolDomainResponse_cloudFrontDomain' - The Amazon CloudFront endpoint that you use as the target of the alias
-- that you set up with your Domain Name Service (DNS) provider.
--
-- 'httpStatus', 'createUserPoolDomainResponse_httpStatus' - The response's http status code.
newCreateUserPoolDomainResponse ::
  -- | 'httpStatus'
  Prelude.Int ->
  CreateUserPoolDomainResponse
newCreateUserPoolDomainResponse :: Int -> CreateUserPoolDomainResponse
newCreateUserPoolDomainResponse Int
pHttpStatus_ =
  CreateUserPoolDomainResponse'
    { $sel:cloudFrontDomain:CreateUserPoolDomainResponse' :: Maybe Text
cloudFrontDomain =
        forall a. Maybe a
Prelude.Nothing,
      $sel:httpStatus:CreateUserPoolDomainResponse' :: Int
httpStatus = Int
pHttpStatus_
    }

-- | The Amazon CloudFront endpoint that you use as the target of the alias
-- that you set up with your Domain Name Service (DNS) provider.
createUserPoolDomainResponse_cloudFrontDomain :: Lens.Lens' CreateUserPoolDomainResponse (Prelude.Maybe Prelude.Text)
createUserPoolDomainResponse_cloudFrontDomain :: Lens' CreateUserPoolDomainResponse (Maybe Text)
createUserPoolDomainResponse_cloudFrontDomain = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\CreateUserPoolDomainResponse' {Maybe Text
cloudFrontDomain :: Maybe Text
$sel:cloudFrontDomain:CreateUserPoolDomainResponse' :: CreateUserPoolDomainResponse -> Maybe Text
cloudFrontDomain} -> Maybe Text
cloudFrontDomain) (\s :: CreateUserPoolDomainResponse
s@CreateUserPoolDomainResponse' {} Maybe Text
a -> CreateUserPoolDomainResponse
s {$sel:cloudFrontDomain:CreateUserPoolDomainResponse' :: Maybe Text
cloudFrontDomain = Maybe Text
a} :: CreateUserPoolDomainResponse)

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

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