{-# 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.AppSync.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 custom @DomainName@ object.
module Amazonka.AppSync.CreateDomainName
  ( -- * Creating a Request
    CreateDomainName (..),
    newCreateDomainName,

    -- * Request Lenses
    createDomainName_description,
    createDomainName_domainName,
    createDomainName_certificateArn,

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

    -- * Response Lenses
    createDomainNameResponse_domainNameConfig,
    createDomainNameResponse_httpStatus,
  )
where

import Amazonka.AppSync.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:/ 'newCreateDomainName' smart constructor.
data CreateDomainName = CreateDomainName'
  { -- | A description of the @DomainName@.
    CreateDomainName -> Maybe Text
description :: Prelude.Maybe Prelude.Text,
    -- | The domain name.
    CreateDomainName -> Text
domainName :: Prelude.Text,
    -- | The Amazon Resource Name (ARN) of the certificate. This can be an
    -- Certificate Manager (ACM) certificate or an Identity and Access
    -- Management (IAM) server certificate.
    CreateDomainName -> Text
certificateArn :: 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:
--
-- 'description', 'createDomainName_description' - A description of the @DomainName@.
--
-- 'domainName', 'createDomainName_domainName' - The domain name.
--
-- 'certificateArn', 'createDomainName_certificateArn' - The Amazon Resource Name (ARN) of the certificate. This can be an
-- Certificate Manager (ACM) certificate or an Identity and Access
-- Management (IAM) server certificate.
newCreateDomainName ::
  -- | 'domainName'
  Prelude.Text ->
  -- | 'certificateArn'
  Prelude.Text ->
  CreateDomainName
newCreateDomainName :: Text -> Text -> CreateDomainName
newCreateDomainName Text
pDomainName_ Text
pCertificateArn_ =
  CreateDomainName'
    { $sel:description:CreateDomainName' :: Maybe Text
description = forall a. Maybe a
Prelude.Nothing,
      $sel:domainName:CreateDomainName' :: Text
domainName = Text
pDomainName_,
      $sel:certificateArn:CreateDomainName' :: Text
certificateArn = Text
pCertificateArn_
    }

-- | A description of the @DomainName@.
createDomainName_description :: Lens.Lens' CreateDomainName (Prelude.Maybe Prelude.Text)
createDomainName_description :: Lens' CreateDomainName (Maybe Text)
createDomainName_description = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\CreateDomainName' {Maybe Text
description :: Maybe Text
$sel:description:CreateDomainName' :: CreateDomainName -> Maybe Text
description} -> Maybe Text
description) (\s :: CreateDomainName
s@CreateDomainName' {} Maybe Text
a -> CreateDomainName
s {$sel:description:CreateDomainName' :: Maybe Text
description = Maybe Text
a} :: CreateDomainName)

-- | 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)

-- | The Amazon Resource Name (ARN) of the certificate. This can be an
-- Certificate Manager (ACM) certificate or an Identity and Access
-- Management (IAM) server certificate.
createDomainName_certificateArn :: Lens.Lens' CreateDomainName Prelude.Text
createDomainName_certificateArn :: Lens' CreateDomainName Text
createDomainName_certificateArn = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\CreateDomainName' {Text
certificateArn :: Text
$sel:certificateArn:CreateDomainName' :: CreateDomainName -> Text
certificateArn} -> Text
certificateArn) (\s :: CreateDomainName
s@CreateDomainName' {} Text
a -> CreateDomainName
s {$sel:certificateArn:CreateDomainName' :: Text
certificateArn = 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 DomainNameConfig -> 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
"domainNameConfig")
            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 Text
Text
certificateArn :: Text
domainName :: Text
description :: Maybe Text
$sel:certificateArn:CreateDomainName' :: CreateDomainName -> Text
$sel:domainName:CreateDomainName' :: CreateDomainName -> Text
$sel:description:CreateDomainName' :: CreateDomainName -> Maybe Text
..} =
    Int
_salt
      forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Maybe Text
description
      forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Text
domainName
      forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Text
certificateArn

instance Prelude.NFData CreateDomainName where
  rnf :: CreateDomainName -> ()
rnf CreateDomainName' {Maybe Text
Text
certificateArn :: Text
domainName :: Text
description :: Maybe Text
$sel:certificateArn:CreateDomainName' :: CreateDomainName -> Text
$sel:domainName:CreateDomainName' :: CreateDomainName -> Text
$sel:description:CreateDomainName' :: CreateDomainName -> Maybe Text
..} =
    forall a. NFData a => a -> ()
Prelude.rnf Maybe Text
description
      seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf Text
domainName
      seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf Text
certificateArn

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 Text
Text
certificateArn :: Text
domainName :: Text
description :: Maybe Text
$sel:certificateArn:CreateDomainName' :: CreateDomainName -> Text
$sel:domainName:CreateDomainName' :: CreateDomainName -> Text
$sel:description:CreateDomainName' :: CreateDomainName -> Maybe Text
..} =
    [Pair] -> Value
Data.object
      ( forall a. [Maybe a] -> [a]
Prelude.catMaybes
          [ (Key
"description" 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
description,
            forall a. a -> Maybe a
Prelude.Just (Key
"domainName" forall kv v. (KeyValue kv, ToJSON v) => Key -> v -> kv
Data..= Text
domainName),
            forall a. a -> Maybe a
Prelude.Just
              (Key
"certificateArn" forall kv v. (KeyValue kv, ToJSON v) => Key -> v -> kv
Data..= Text
certificateArn)
          ]
      )

instance Data.ToPath CreateDomainName where
  toPath :: CreateDomainName -> ByteString
toPath = forall a b. a -> b -> a
Prelude.const ByteString
"/v1/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 configuration for the @DomainName@.
    CreateDomainNameResponse -> Maybe DomainNameConfig
domainNameConfig :: Prelude.Maybe DomainNameConfig,
    -- | 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:
--
-- 'domainNameConfig', 'createDomainNameResponse_domainNameConfig' - The configuration for the @DomainName@.
--
-- 'httpStatus', 'createDomainNameResponse_httpStatus' - The response's http status code.
newCreateDomainNameResponse ::
  -- | 'httpStatus'
  Prelude.Int ->
  CreateDomainNameResponse
newCreateDomainNameResponse :: Int -> CreateDomainNameResponse
newCreateDomainNameResponse Int
pHttpStatus_ =
  CreateDomainNameResponse'
    { $sel:domainNameConfig:CreateDomainNameResponse' :: Maybe DomainNameConfig
domainNameConfig =
        forall a. Maybe a
Prelude.Nothing,
      $sel:httpStatus:CreateDomainNameResponse' :: Int
httpStatus = Int
pHttpStatus_
    }

-- | The configuration for the @DomainName@.
createDomainNameResponse_domainNameConfig :: Lens.Lens' CreateDomainNameResponse (Prelude.Maybe DomainNameConfig)
createDomainNameResponse_domainNameConfig :: Lens' CreateDomainNameResponse (Maybe DomainNameConfig)
createDomainNameResponse_domainNameConfig = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\CreateDomainNameResponse' {Maybe DomainNameConfig
domainNameConfig :: Maybe DomainNameConfig
$sel:domainNameConfig:CreateDomainNameResponse' :: CreateDomainNameResponse -> Maybe DomainNameConfig
domainNameConfig} -> Maybe DomainNameConfig
domainNameConfig) (\s :: CreateDomainNameResponse
s@CreateDomainNameResponse' {} Maybe DomainNameConfig
a -> CreateDomainNameResponse
s {$sel:domainNameConfig:CreateDomainNameResponse' :: Maybe DomainNameConfig
domainNameConfig = Maybe DomainNameConfig
a} :: CreateDomainNameResponse)

-- | 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 DomainNameConfig
httpStatus :: Int
domainNameConfig :: Maybe DomainNameConfig
$sel:httpStatus:CreateDomainNameResponse' :: CreateDomainNameResponse -> Int
$sel:domainNameConfig:CreateDomainNameResponse' :: CreateDomainNameResponse -> Maybe DomainNameConfig
..} =
    forall a. NFData a => a -> ()
Prelude.rnf Maybe DomainNameConfig
domainNameConfig
      seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf Int
httpStatus