{-# 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.ApiGatewayV2.CreateDomainName
-- 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 domain name.
module Amazonka.ApiGatewayV2.CreateDomainName
  ( -- * Creating a Request
    CreateDomainName (..),
    newCreateDomainName,

    -- * Request Lenses
    createDomainName_domainNameConfigurations,
    createDomainName_mutualTlsAuthentication,
    createDomainName_tags,
    createDomainName_domainName,

    -- * Destructuring the Response
    CreateDomainNameResponse (..),
    newCreateDomainNameResponse,

    -- * Response Lenses
    createDomainNameResponse_apiMappingSelectionExpression,
    createDomainNameResponse_domainName,
    createDomainNameResponse_domainNameConfigurations,
    createDomainNameResponse_mutualTlsAuthentication,
    createDomainNameResponse_tags,
    createDomainNameResponse_httpStatus,
  )
where

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

-- | Creates a new DomainName resource to represent a domain name.
--
-- /See:/ 'newCreateDomainName' smart constructor.
data CreateDomainName = CreateDomainName'
  { -- | The domain name configurations.
    CreateDomainName -> Maybe [DomainNameConfiguration]
domainNameConfigurations :: Prelude.Maybe [DomainNameConfiguration],
    -- | The mutual TLS authentication configuration for a custom domain name.
    CreateDomainName -> Maybe MutualTlsAuthenticationInput
mutualTlsAuthentication :: Prelude.Maybe MutualTlsAuthenticationInput,
    -- | The collection of tags associated with a domain name.
    CreateDomainName -> Maybe (HashMap Text Text)
tags :: Prelude.Maybe (Prelude.HashMap Prelude.Text Prelude.Text),
    -- | The domain name.
    CreateDomainName -> Text
domainName :: Prelude.Text
  }
  deriving (CreateDomainName -> CreateDomainName -> Bool
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: CreateDomainName -> CreateDomainName -> Bool
$c/= :: CreateDomainName -> CreateDomainName -> Bool
== :: CreateDomainName -> CreateDomainName -> Bool
$c== :: CreateDomainName -> CreateDomainName -> Bool
Prelude.Eq, ReadPrec [CreateDomainName]
ReadPrec CreateDomainName
Int -> ReadS CreateDomainName
ReadS [CreateDomainName]
forall a.
(Int -> ReadS a)
-> ReadS [a] -> ReadPrec a -> ReadPrec [a] -> Read a
readListPrec :: ReadPrec [CreateDomainName]
$creadListPrec :: ReadPrec [CreateDomainName]
readPrec :: ReadPrec CreateDomainName
$creadPrec :: ReadPrec CreateDomainName
readList :: ReadS [CreateDomainName]
$creadList :: ReadS [CreateDomainName]
readsPrec :: Int -> ReadS CreateDomainName
$creadsPrec :: Int -> ReadS CreateDomainName
Prelude.Read, Int -> CreateDomainName -> ShowS
[CreateDomainName] -> ShowS
CreateDomainName -> String
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [CreateDomainName] -> ShowS
$cshowList :: [CreateDomainName] -> ShowS
show :: CreateDomainName -> String
$cshow :: CreateDomainName -> String
showsPrec :: Int -> CreateDomainName -> ShowS
$cshowsPrec :: Int -> CreateDomainName -> ShowS
Prelude.Show, forall x. Rep CreateDomainName x -> CreateDomainName
forall x. CreateDomainName -> Rep CreateDomainName x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cto :: forall x. Rep CreateDomainName x -> CreateDomainName
$cfrom :: forall x. CreateDomainName -> Rep CreateDomainName x
Prelude.Generic)

-- |
-- Create a value of 'CreateDomainName' 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:
--
-- 'domainNameConfigurations', 'createDomainName_domainNameConfigurations' - The domain name configurations.
--
-- 'mutualTlsAuthentication', 'createDomainName_mutualTlsAuthentication' - The mutual TLS authentication configuration for a custom domain name.
--
-- 'tags', 'createDomainName_tags' - The collection of tags associated with a domain name.
--
-- 'domainName', 'createDomainName_domainName' - The domain name.
newCreateDomainName ::
  -- | 'domainName'
  Prelude.Text ->
  CreateDomainName
newCreateDomainName :: Text -> CreateDomainName
newCreateDomainName Text
pDomainName_ =
  CreateDomainName'
    { $sel:domainNameConfigurations:CreateDomainName' :: Maybe [DomainNameConfiguration]
domainNameConfigurations =
        forall a. Maybe a
Prelude.Nothing,
      $sel:mutualTlsAuthentication:CreateDomainName' :: Maybe MutualTlsAuthenticationInput
mutualTlsAuthentication = forall a. Maybe a
Prelude.Nothing,
      $sel:tags:CreateDomainName' :: Maybe (HashMap Text Text)
tags = forall a. Maybe a
Prelude.Nothing,
      $sel:domainName:CreateDomainName' :: Text
domainName = Text
pDomainName_
    }

-- | The domain name configurations.
createDomainName_domainNameConfigurations :: Lens.Lens' CreateDomainName (Prelude.Maybe [DomainNameConfiguration])
createDomainName_domainNameConfigurations :: Lens' CreateDomainName (Maybe [DomainNameConfiguration])
createDomainName_domainNameConfigurations = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\CreateDomainName' {Maybe [DomainNameConfiguration]
domainNameConfigurations :: Maybe [DomainNameConfiguration]
$sel:domainNameConfigurations:CreateDomainName' :: CreateDomainName -> Maybe [DomainNameConfiguration]
domainNameConfigurations} -> Maybe [DomainNameConfiguration]
domainNameConfigurations) (\s :: CreateDomainName
s@CreateDomainName' {} Maybe [DomainNameConfiguration]
a -> CreateDomainName
s {$sel:domainNameConfigurations:CreateDomainName' :: Maybe [DomainNameConfiguration]
domainNameConfigurations = Maybe [DomainNameConfiguration]
a} :: CreateDomainName) 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 mutual TLS authentication configuration for a custom domain name.
createDomainName_mutualTlsAuthentication :: Lens.Lens' CreateDomainName (Prelude.Maybe MutualTlsAuthenticationInput)
createDomainName_mutualTlsAuthentication :: Lens' CreateDomainName (Maybe MutualTlsAuthenticationInput)
createDomainName_mutualTlsAuthentication = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\CreateDomainName' {Maybe MutualTlsAuthenticationInput
mutualTlsAuthentication :: Maybe MutualTlsAuthenticationInput
$sel:mutualTlsAuthentication:CreateDomainName' :: CreateDomainName -> Maybe MutualTlsAuthenticationInput
mutualTlsAuthentication} -> Maybe MutualTlsAuthenticationInput
mutualTlsAuthentication) (\s :: CreateDomainName
s@CreateDomainName' {} Maybe MutualTlsAuthenticationInput
a -> CreateDomainName
s {$sel:mutualTlsAuthentication:CreateDomainName' :: Maybe MutualTlsAuthenticationInput
mutualTlsAuthentication = Maybe MutualTlsAuthenticationInput
a} :: CreateDomainName)

-- | The collection of tags associated with a domain name.
createDomainName_tags :: Lens.Lens' CreateDomainName (Prelude.Maybe (Prelude.HashMap Prelude.Text Prelude.Text))
createDomainName_tags :: Lens' CreateDomainName (Maybe (HashMap Text Text))
createDomainName_tags = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\CreateDomainName' {Maybe (HashMap Text Text)
tags :: Maybe (HashMap Text Text)
$sel:tags:CreateDomainName' :: CreateDomainName -> Maybe (HashMap Text Text)
tags} -> Maybe (HashMap Text Text)
tags) (\s :: CreateDomainName
s@CreateDomainName' {} Maybe (HashMap Text Text)
a -> CreateDomainName
s {$sel:tags:CreateDomainName' :: Maybe (HashMap Text Text)
tags = Maybe (HashMap Text Text)
a} :: CreateDomainName) 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 domain name.
createDomainName_domainName :: Lens.Lens' CreateDomainName Prelude.Text
createDomainName_domainName :: Lens' CreateDomainName Text
createDomainName_domainName = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\CreateDomainName' {Text
domainName :: Text
$sel:domainName:CreateDomainName' :: CreateDomainName -> Text
domainName} -> Text
domainName) (\s :: CreateDomainName
s@CreateDomainName' {} Text
a -> CreateDomainName
s {$sel:domainName:CreateDomainName' :: Text
domainName = Text
a} :: CreateDomainName)

instance Core.AWSRequest CreateDomainName where
  type
    AWSResponse CreateDomainName =
      CreateDomainNameResponse
  request :: (Service -> Service)
-> CreateDomainName -> Request CreateDomainName
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 CreateDomainName
-> ClientResponse ClientBody
-> m (Either Error (ClientResponse (AWSResponse CreateDomainName)))
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 Text
-> Maybe [DomainNameConfiguration]
-> Maybe MutualTlsAuthentication
-> Maybe (HashMap Text Text)
-> Int
-> CreateDomainNameResponse
CreateDomainNameResponse'
            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
"apiMappingSelectionExpression")
            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
"domainName")
            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
"domainNameConfigurations"
                            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
"mutualTlsAuthentication")
            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
"tags" 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 CreateDomainName where
  hashWithSalt :: Int -> CreateDomainName -> Int
hashWithSalt Int
_salt CreateDomainName' {Maybe [DomainNameConfiguration]
Maybe (HashMap Text Text)
Maybe MutualTlsAuthenticationInput
Text
domainName :: Text
tags :: Maybe (HashMap Text Text)
mutualTlsAuthentication :: Maybe MutualTlsAuthenticationInput
domainNameConfigurations :: Maybe [DomainNameConfiguration]
$sel:domainName:CreateDomainName' :: CreateDomainName -> Text
$sel:tags:CreateDomainName' :: CreateDomainName -> Maybe (HashMap Text Text)
$sel:mutualTlsAuthentication:CreateDomainName' :: CreateDomainName -> Maybe MutualTlsAuthenticationInput
$sel:domainNameConfigurations:CreateDomainName' :: CreateDomainName -> Maybe [DomainNameConfiguration]
..} =
    Int
_salt
      forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Maybe [DomainNameConfiguration]
domainNameConfigurations
      forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Maybe MutualTlsAuthenticationInput
mutualTlsAuthentication
      forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Maybe (HashMap Text Text)
tags
      forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Text
domainName

instance Prelude.NFData CreateDomainName where
  rnf :: CreateDomainName -> ()
rnf CreateDomainName' {Maybe [DomainNameConfiguration]
Maybe (HashMap Text Text)
Maybe MutualTlsAuthenticationInput
Text
domainName :: Text
tags :: Maybe (HashMap Text Text)
mutualTlsAuthentication :: Maybe MutualTlsAuthenticationInput
domainNameConfigurations :: Maybe [DomainNameConfiguration]
$sel:domainName:CreateDomainName' :: CreateDomainName -> Text
$sel:tags:CreateDomainName' :: CreateDomainName -> Maybe (HashMap Text Text)
$sel:mutualTlsAuthentication:CreateDomainName' :: CreateDomainName -> Maybe MutualTlsAuthenticationInput
$sel:domainNameConfigurations:CreateDomainName' :: CreateDomainName -> Maybe [DomainNameConfiguration]
..} =
    forall a. NFData a => a -> ()
Prelude.rnf Maybe [DomainNameConfiguration]
domainNameConfigurations
      seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf Maybe MutualTlsAuthenticationInput
mutualTlsAuthentication
      seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf Maybe (HashMap Text Text)
tags
      seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf Text
domainName

instance Data.ToHeaders CreateDomainName where
  toHeaders :: CreateDomainName -> ResponseHeaders
toHeaders =
    forall a b. a -> b -> a
Prelude.const
      ( forall a. Monoid a => [a] -> a
Prelude.mconcat
          [ HeaderName
"Content-Type"
              forall a. ToHeader a => HeaderName -> a -> ResponseHeaders
Data.=# ( ByteString
"application/x-amz-json-1.1" ::
                          Prelude.ByteString
                      )
          ]
      )

instance Data.ToJSON CreateDomainName where
  toJSON :: CreateDomainName -> Value
toJSON CreateDomainName' {Maybe [DomainNameConfiguration]
Maybe (HashMap Text Text)
Maybe MutualTlsAuthenticationInput
Text
domainName :: Text
tags :: Maybe (HashMap Text Text)
mutualTlsAuthentication :: Maybe MutualTlsAuthenticationInput
domainNameConfigurations :: Maybe [DomainNameConfiguration]
$sel:domainName:CreateDomainName' :: CreateDomainName -> Text
$sel:tags:CreateDomainName' :: CreateDomainName -> Maybe (HashMap Text Text)
$sel:mutualTlsAuthentication:CreateDomainName' :: CreateDomainName -> Maybe MutualTlsAuthenticationInput
$sel:domainNameConfigurations:CreateDomainName' :: CreateDomainName -> Maybe [DomainNameConfiguration]
..} =
    [Pair] -> Value
Data.object
      ( forall a. [Maybe a] -> [a]
Prelude.catMaybes
          [ (Key
"domainNameConfigurations" 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 [DomainNameConfiguration]
domainNameConfigurations,
            (Key
"mutualTlsAuthentication" 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 MutualTlsAuthenticationInput
mutualTlsAuthentication,
            (Key
"tags" 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 (HashMap Text Text)
tags,
            forall a. a -> Maybe a
Prelude.Just (Key
"domainName" forall kv v. (KeyValue kv, ToJSON v) => Key -> v -> kv
Data..= Text
domainName)
          ]
      )

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

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

-- | /See:/ 'newCreateDomainNameResponse' smart constructor.
data CreateDomainNameResponse = CreateDomainNameResponse'
  { -- | The API mapping selection expression.
    CreateDomainNameResponse -> Maybe Text
apiMappingSelectionExpression :: Prelude.Maybe Prelude.Text,
    -- | The name of the DomainName resource.
    CreateDomainNameResponse -> Maybe Text
domainName :: Prelude.Maybe Prelude.Text,
    -- | The domain name configurations.
    CreateDomainNameResponse -> Maybe [DomainNameConfiguration]
domainNameConfigurations :: Prelude.Maybe [DomainNameConfiguration],
    -- | The mutual TLS authentication configuration for a custom domain name.
    CreateDomainNameResponse -> Maybe MutualTlsAuthentication
mutualTlsAuthentication :: Prelude.Maybe MutualTlsAuthentication,
    -- | The collection of tags associated with a domain name.
    CreateDomainNameResponse -> Maybe (HashMap Text Text)
tags :: Prelude.Maybe (Prelude.HashMap Prelude.Text Prelude.Text),
    -- | The response's http status code.
    CreateDomainNameResponse -> Int
httpStatus :: Prelude.Int
  }
  deriving (CreateDomainNameResponse -> CreateDomainNameResponse -> Bool
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: CreateDomainNameResponse -> CreateDomainNameResponse -> Bool
$c/= :: CreateDomainNameResponse -> CreateDomainNameResponse -> Bool
== :: CreateDomainNameResponse -> CreateDomainNameResponse -> Bool
$c== :: CreateDomainNameResponse -> CreateDomainNameResponse -> Bool
Prelude.Eq, ReadPrec [CreateDomainNameResponse]
ReadPrec CreateDomainNameResponse
Int -> ReadS CreateDomainNameResponse
ReadS [CreateDomainNameResponse]
forall a.
(Int -> ReadS a)
-> ReadS [a] -> ReadPrec a -> ReadPrec [a] -> Read a
readListPrec :: ReadPrec [CreateDomainNameResponse]
$creadListPrec :: ReadPrec [CreateDomainNameResponse]
readPrec :: ReadPrec CreateDomainNameResponse
$creadPrec :: ReadPrec CreateDomainNameResponse
readList :: ReadS [CreateDomainNameResponse]
$creadList :: ReadS [CreateDomainNameResponse]
readsPrec :: Int -> ReadS CreateDomainNameResponse
$creadsPrec :: Int -> ReadS CreateDomainNameResponse
Prelude.Read, Int -> CreateDomainNameResponse -> ShowS
[CreateDomainNameResponse] -> ShowS
CreateDomainNameResponse -> String
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [CreateDomainNameResponse] -> ShowS
$cshowList :: [CreateDomainNameResponse] -> ShowS
show :: CreateDomainNameResponse -> String
$cshow :: CreateDomainNameResponse -> String
showsPrec :: Int -> CreateDomainNameResponse -> ShowS
$cshowsPrec :: Int -> CreateDomainNameResponse -> ShowS
Prelude.Show, forall x.
Rep CreateDomainNameResponse x -> CreateDomainNameResponse
forall x.
CreateDomainNameResponse -> Rep CreateDomainNameResponse x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cto :: forall x.
Rep CreateDomainNameResponse x -> CreateDomainNameResponse
$cfrom :: forall x.
CreateDomainNameResponse -> Rep CreateDomainNameResponse x
Prelude.Generic)

-- |
-- Create a value of 'CreateDomainNameResponse' 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:
--
-- 'apiMappingSelectionExpression', 'createDomainNameResponse_apiMappingSelectionExpression' - The API mapping selection expression.
--
-- 'domainName', 'createDomainNameResponse_domainName' - The name of the DomainName resource.
--
-- 'domainNameConfigurations', 'createDomainNameResponse_domainNameConfigurations' - The domain name configurations.
--
-- 'mutualTlsAuthentication', 'createDomainNameResponse_mutualTlsAuthentication' - The mutual TLS authentication configuration for a custom domain name.
--
-- 'tags', 'createDomainNameResponse_tags' - The collection of tags associated with a domain name.
--
-- 'httpStatus', 'createDomainNameResponse_httpStatus' - The response's http status code.
newCreateDomainNameResponse ::
  -- | 'httpStatus'
  Prelude.Int ->
  CreateDomainNameResponse
newCreateDomainNameResponse :: Int -> CreateDomainNameResponse
newCreateDomainNameResponse Int
pHttpStatus_ =
  CreateDomainNameResponse'
    { $sel:apiMappingSelectionExpression:CreateDomainNameResponse' :: Maybe Text
apiMappingSelectionExpression =
        forall a. Maybe a
Prelude.Nothing,
      $sel:domainName:CreateDomainNameResponse' :: Maybe Text
domainName = forall a. Maybe a
Prelude.Nothing,
      $sel:domainNameConfigurations:CreateDomainNameResponse' :: Maybe [DomainNameConfiguration]
domainNameConfigurations = forall a. Maybe a
Prelude.Nothing,
      $sel:mutualTlsAuthentication:CreateDomainNameResponse' :: Maybe MutualTlsAuthentication
mutualTlsAuthentication = forall a. Maybe a
Prelude.Nothing,
      $sel:tags:CreateDomainNameResponse' :: Maybe (HashMap Text Text)
tags = forall a. Maybe a
Prelude.Nothing,
      $sel:httpStatus:CreateDomainNameResponse' :: Int
httpStatus = Int
pHttpStatus_
    }

-- | The API mapping selection expression.
createDomainNameResponse_apiMappingSelectionExpression :: Lens.Lens' CreateDomainNameResponse (Prelude.Maybe Prelude.Text)
createDomainNameResponse_apiMappingSelectionExpression :: Lens' CreateDomainNameResponse (Maybe Text)
createDomainNameResponse_apiMappingSelectionExpression = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\CreateDomainNameResponse' {Maybe Text
apiMappingSelectionExpression :: Maybe Text
$sel:apiMappingSelectionExpression:CreateDomainNameResponse' :: CreateDomainNameResponse -> Maybe Text
apiMappingSelectionExpression} -> Maybe Text
apiMappingSelectionExpression) (\s :: CreateDomainNameResponse
s@CreateDomainNameResponse' {} Maybe Text
a -> CreateDomainNameResponse
s {$sel:apiMappingSelectionExpression:CreateDomainNameResponse' :: Maybe Text
apiMappingSelectionExpression = Maybe Text
a} :: CreateDomainNameResponse)

-- | The name of the DomainName resource.
createDomainNameResponse_domainName :: Lens.Lens' CreateDomainNameResponse (Prelude.Maybe Prelude.Text)
createDomainNameResponse_domainName :: Lens' CreateDomainNameResponse (Maybe Text)
createDomainNameResponse_domainName = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\CreateDomainNameResponse' {Maybe Text
domainName :: Maybe Text
$sel:domainName:CreateDomainNameResponse' :: CreateDomainNameResponse -> Maybe Text
domainName} -> Maybe Text
domainName) (\s :: CreateDomainNameResponse
s@CreateDomainNameResponse' {} Maybe Text
a -> CreateDomainNameResponse
s {$sel:domainName:CreateDomainNameResponse' :: Maybe Text
domainName = Maybe Text
a} :: CreateDomainNameResponse)

-- | The domain name configurations.
createDomainNameResponse_domainNameConfigurations :: Lens.Lens' CreateDomainNameResponse (Prelude.Maybe [DomainNameConfiguration])
createDomainNameResponse_domainNameConfigurations :: Lens' CreateDomainNameResponse (Maybe [DomainNameConfiguration])
createDomainNameResponse_domainNameConfigurations = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\CreateDomainNameResponse' {Maybe [DomainNameConfiguration]
domainNameConfigurations :: Maybe [DomainNameConfiguration]
$sel:domainNameConfigurations:CreateDomainNameResponse' :: CreateDomainNameResponse -> Maybe [DomainNameConfiguration]
domainNameConfigurations} -> Maybe [DomainNameConfiguration]
domainNameConfigurations) (\s :: CreateDomainNameResponse
s@CreateDomainNameResponse' {} Maybe [DomainNameConfiguration]
a -> CreateDomainNameResponse
s {$sel:domainNameConfigurations:CreateDomainNameResponse' :: Maybe [DomainNameConfiguration]
domainNameConfigurations = Maybe [DomainNameConfiguration]
a} :: CreateDomainNameResponse) 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 mutual TLS authentication configuration for a custom domain name.
createDomainNameResponse_mutualTlsAuthentication :: Lens.Lens' CreateDomainNameResponse (Prelude.Maybe MutualTlsAuthentication)
createDomainNameResponse_mutualTlsAuthentication :: Lens' CreateDomainNameResponse (Maybe MutualTlsAuthentication)
createDomainNameResponse_mutualTlsAuthentication = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\CreateDomainNameResponse' {Maybe MutualTlsAuthentication
mutualTlsAuthentication :: Maybe MutualTlsAuthentication
$sel:mutualTlsAuthentication:CreateDomainNameResponse' :: CreateDomainNameResponse -> Maybe MutualTlsAuthentication
mutualTlsAuthentication} -> Maybe MutualTlsAuthentication
mutualTlsAuthentication) (\s :: CreateDomainNameResponse
s@CreateDomainNameResponse' {} Maybe MutualTlsAuthentication
a -> CreateDomainNameResponse
s {$sel:mutualTlsAuthentication:CreateDomainNameResponse' :: Maybe MutualTlsAuthentication
mutualTlsAuthentication = Maybe MutualTlsAuthentication
a} :: CreateDomainNameResponse)

-- | The collection of tags associated with a domain name.
createDomainNameResponse_tags :: Lens.Lens' CreateDomainNameResponse (Prelude.Maybe (Prelude.HashMap Prelude.Text Prelude.Text))
createDomainNameResponse_tags :: Lens' CreateDomainNameResponse (Maybe (HashMap Text Text))
createDomainNameResponse_tags = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\CreateDomainNameResponse' {Maybe (HashMap Text Text)
tags :: Maybe (HashMap Text Text)
$sel:tags:CreateDomainNameResponse' :: CreateDomainNameResponse -> Maybe (HashMap Text Text)
tags} -> Maybe (HashMap Text Text)
tags) (\s :: CreateDomainNameResponse
s@CreateDomainNameResponse' {} Maybe (HashMap Text Text)
a -> CreateDomainNameResponse
s {$sel:tags:CreateDomainNameResponse' :: Maybe (HashMap Text Text)
tags = Maybe (HashMap Text Text)
a} :: CreateDomainNameResponse) 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.
createDomainNameResponse_httpStatus :: Lens.Lens' CreateDomainNameResponse Prelude.Int
createDomainNameResponse_httpStatus :: Lens' CreateDomainNameResponse Int
createDomainNameResponse_httpStatus = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\CreateDomainNameResponse' {Int
httpStatus :: Int
$sel:httpStatus:CreateDomainNameResponse' :: CreateDomainNameResponse -> Int
httpStatus} -> Int
httpStatus) (\s :: CreateDomainNameResponse
s@CreateDomainNameResponse' {} Int
a -> CreateDomainNameResponse
s {$sel:httpStatus:CreateDomainNameResponse' :: Int
httpStatus = Int
a} :: CreateDomainNameResponse)

instance Prelude.NFData CreateDomainNameResponse where
  rnf :: CreateDomainNameResponse -> ()
rnf CreateDomainNameResponse' {Int
Maybe [DomainNameConfiguration]
Maybe Text
Maybe (HashMap Text Text)
Maybe MutualTlsAuthentication
httpStatus :: Int
tags :: Maybe (HashMap Text Text)
mutualTlsAuthentication :: Maybe MutualTlsAuthentication
domainNameConfigurations :: Maybe [DomainNameConfiguration]
domainName :: Maybe Text
apiMappingSelectionExpression :: Maybe Text
$sel:httpStatus:CreateDomainNameResponse' :: CreateDomainNameResponse -> Int
$sel:tags:CreateDomainNameResponse' :: CreateDomainNameResponse -> Maybe (HashMap Text Text)
$sel:mutualTlsAuthentication:CreateDomainNameResponse' :: CreateDomainNameResponse -> Maybe MutualTlsAuthentication
$sel:domainNameConfigurations:CreateDomainNameResponse' :: CreateDomainNameResponse -> Maybe [DomainNameConfiguration]
$sel:domainName:CreateDomainNameResponse' :: CreateDomainNameResponse -> Maybe Text
$sel:apiMappingSelectionExpression:CreateDomainNameResponse' :: CreateDomainNameResponse -> Maybe Text
..} =
    forall a. NFData a => a -> ()
Prelude.rnf Maybe Text
apiMappingSelectionExpression
      seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf Maybe Text
domainName
      seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf Maybe [DomainNameConfiguration]
domainNameConfigurations
      seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf Maybe MutualTlsAuthentication
mutualTlsAuthentication
      seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf Maybe (HashMap Text Text)
tags
      seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf Int
httpStatus