{-# 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.DirectoryService.CreateAlias
-- 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 an alias for a directory and assigns the alias to the directory.
-- The alias is used to construct the access URL for the directory, such as
-- @http:\/\/\<alias>.awsapps.com@.
--
-- After an alias has been created, it cannot be deleted or reused, so this
-- operation should only be used when absolutely necessary.
module Amazonka.DirectoryService.CreateAlias
  ( -- * Creating a Request
    CreateAlias (..),
    newCreateAlias,

    -- * Request Lenses
    createAlias_directoryId,
    createAlias_alias,

    -- * Destructuring the Response
    CreateAliasResponse (..),
    newCreateAliasResponse,

    -- * Response Lenses
    createAliasResponse_alias,
    createAliasResponse_directoryId,
    createAliasResponse_httpStatus,
  )
where

import qualified Amazonka.Core as Core
import qualified Amazonka.Core.Lens.Internal as Lens
import qualified Amazonka.Data as Data
import Amazonka.DirectoryService.Types
import qualified Amazonka.Prelude as Prelude
import qualified Amazonka.Request as Request
import qualified Amazonka.Response as Response

-- | Contains the inputs for the CreateAlias operation.
--
-- /See:/ 'newCreateAlias' smart constructor.
data CreateAlias = CreateAlias'
  { -- | The identifier of the directory for which to create the alias.
    CreateAlias -> Text
directoryId :: Prelude.Text,
    -- | The requested alias.
    --
    -- The alias must be unique amongst all aliases in Amazon Web Services.
    -- This operation throws an @EntityAlreadyExistsException@ error if the
    -- alias already exists.
    CreateAlias -> Text
alias :: Prelude.Text
  }
  deriving (CreateAlias -> CreateAlias -> Bool
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: CreateAlias -> CreateAlias -> Bool
$c/= :: CreateAlias -> CreateAlias -> Bool
== :: CreateAlias -> CreateAlias -> Bool
$c== :: CreateAlias -> CreateAlias -> Bool
Prelude.Eq, ReadPrec [CreateAlias]
ReadPrec CreateAlias
Int -> ReadS CreateAlias
ReadS [CreateAlias]
forall a.
(Int -> ReadS a)
-> ReadS [a] -> ReadPrec a -> ReadPrec [a] -> Read a
readListPrec :: ReadPrec [CreateAlias]
$creadListPrec :: ReadPrec [CreateAlias]
readPrec :: ReadPrec CreateAlias
$creadPrec :: ReadPrec CreateAlias
readList :: ReadS [CreateAlias]
$creadList :: ReadS [CreateAlias]
readsPrec :: Int -> ReadS CreateAlias
$creadsPrec :: Int -> ReadS CreateAlias
Prelude.Read, Int -> CreateAlias -> ShowS
[CreateAlias] -> ShowS
CreateAlias -> String
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [CreateAlias] -> ShowS
$cshowList :: [CreateAlias] -> ShowS
show :: CreateAlias -> String
$cshow :: CreateAlias -> String
showsPrec :: Int -> CreateAlias -> ShowS
$cshowsPrec :: Int -> CreateAlias -> ShowS
Prelude.Show, forall x. Rep CreateAlias x -> CreateAlias
forall x. CreateAlias -> Rep CreateAlias x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cto :: forall x. Rep CreateAlias x -> CreateAlias
$cfrom :: forall x. CreateAlias -> Rep CreateAlias x
Prelude.Generic)

-- |
-- Create a value of 'CreateAlias' 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:
--
-- 'directoryId', 'createAlias_directoryId' - The identifier of the directory for which to create the alias.
--
-- 'alias', 'createAlias_alias' - The requested alias.
--
-- The alias must be unique amongst all aliases in Amazon Web Services.
-- This operation throws an @EntityAlreadyExistsException@ error if the
-- alias already exists.
newCreateAlias ::
  -- | 'directoryId'
  Prelude.Text ->
  -- | 'alias'
  Prelude.Text ->
  CreateAlias
newCreateAlias :: Text -> Text -> CreateAlias
newCreateAlias Text
pDirectoryId_ Text
pAlias_ =
  CreateAlias'
    { $sel:directoryId:CreateAlias' :: Text
directoryId = Text
pDirectoryId_,
      $sel:alias:CreateAlias' :: Text
alias = Text
pAlias_
    }

-- | The identifier of the directory for which to create the alias.
createAlias_directoryId :: Lens.Lens' CreateAlias Prelude.Text
createAlias_directoryId :: Lens' CreateAlias Text
createAlias_directoryId = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\CreateAlias' {Text
directoryId :: Text
$sel:directoryId:CreateAlias' :: CreateAlias -> Text
directoryId} -> Text
directoryId) (\s :: CreateAlias
s@CreateAlias' {} Text
a -> CreateAlias
s {$sel:directoryId:CreateAlias' :: Text
directoryId = Text
a} :: CreateAlias)

-- | The requested alias.
--
-- The alias must be unique amongst all aliases in Amazon Web Services.
-- This operation throws an @EntityAlreadyExistsException@ error if the
-- alias already exists.
createAlias_alias :: Lens.Lens' CreateAlias Prelude.Text
createAlias_alias :: Lens' CreateAlias Text
createAlias_alias = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\CreateAlias' {Text
alias :: Text
$sel:alias:CreateAlias' :: CreateAlias -> Text
alias} -> Text
alias) (\s :: CreateAlias
s@CreateAlias' {} Text
a -> CreateAlias
s {$sel:alias:CreateAlias' :: Text
alias = Text
a} :: CreateAlias)

instance Core.AWSRequest CreateAlias where
  type AWSResponse CreateAlias = CreateAliasResponse
  request :: (Service -> Service) -> CreateAlias -> Request CreateAlias
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 CreateAlias
-> ClientResponse ClientBody
-> m (Either Error (ClientResponse (AWSResponse CreateAlias)))
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 -> Int -> CreateAliasResponse
CreateAliasResponse'
            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
"Alias")
            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
"DirectoryId")
            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 CreateAlias where
  hashWithSalt :: Int -> CreateAlias -> Int
hashWithSalt Int
_salt CreateAlias' {Text
alias :: Text
directoryId :: Text
$sel:alias:CreateAlias' :: CreateAlias -> Text
$sel:directoryId:CreateAlias' :: CreateAlias -> Text
..} =
    Int
_salt
      forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Text
directoryId
      forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Text
alias

instance Prelude.NFData CreateAlias where
  rnf :: CreateAlias -> ()
rnf CreateAlias' {Text
alias :: Text
directoryId :: Text
$sel:alias:CreateAlias' :: CreateAlias -> Text
$sel:directoryId:CreateAlias' :: CreateAlias -> Text
..} =
    forall a. NFData a => a -> ()
Prelude.rnf Text
directoryId
      seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf Text
alias

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

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

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

-- | Contains the results of the CreateAlias operation.
--
-- /See:/ 'newCreateAliasResponse' smart constructor.
data CreateAliasResponse = CreateAliasResponse'
  { -- | The alias for the directory.
    CreateAliasResponse -> Maybe Text
alias :: Prelude.Maybe Prelude.Text,
    -- | The identifier of the directory.
    CreateAliasResponse -> Maybe Text
directoryId :: Prelude.Maybe Prelude.Text,
    -- | The response's http status code.
    CreateAliasResponse -> Int
httpStatus :: Prelude.Int
  }
  deriving (CreateAliasResponse -> CreateAliasResponse -> Bool
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: CreateAliasResponse -> CreateAliasResponse -> Bool
$c/= :: CreateAliasResponse -> CreateAliasResponse -> Bool
== :: CreateAliasResponse -> CreateAliasResponse -> Bool
$c== :: CreateAliasResponse -> CreateAliasResponse -> Bool
Prelude.Eq, ReadPrec [CreateAliasResponse]
ReadPrec CreateAliasResponse
Int -> ReadS CreateAliasResponse
ReadS [CreateAliasResponse]
forall a.
(Int -> ReadS a)
-> ReadS [a] -> ReadPrec a -> ReadPrec [a] -> Read a
readListPrec :: ReadPrec [CreateAliasResponse]
$creadListPrec :: ReadPrec [CreateAliasResponse]
readPrec :: ReadPrec CreateAliasResponse
$creadPrec :: ReadPrec CreateAliasResponse
readList :: ReadS [CreateAliasResponse]
$creadList :: ReadS [CreateAliasResponse]
readsPrec :: Int -> ReadS CreateAliasResponse
$creadsPrec :: Int -> ReadS CreateAliasResponse
Prelude.Read, Int -> CreateAliasResponse -> ShowS
[CreateAliasResponse] -> ShowS
CreateAliasResponse -> String
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [CreateAliasResponse] -> ShowS
$cshowList :: [CreateAliasResponse] -> ShowS
show :: CreateAliasResponse -> String
$cshow :: CreateAliasResponse -> String
showsPrec :: Int -> CreateAliasResponse -> ShowS
$cshowsPrec :: Int -> CreateAliasResponse -> ShowS
Prelude.Show, forall x. Rep CreateAliasResponse x -> CreateAliasResponse
forall x. CreateAliasResponse -> Rep CreateAliasResponse x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cto :: forall x. Rep CreateAliasResponse x -> CreateAliasResponse
$cfrom :: forall x. CreateAliasResponse -> Rep CreateAliasResponse x
Prelude.Generic)

-- |
-- Create a value of 'CreateAliasResponse' 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:
--
-- 'alias', 'createAliasResponse_alias' - The alias for the directory.
--
-- 'directoryId', 'createAliasResponse_directoryId' - The identifier of the directory.
--
-- 'httpStatus', 'createAliasResponse_httpStatus' - The response's http status code.
newCreateAliasResponse ::
  -- | 'httpStatus'
  Prelude.Int ->
  CreateAliasResponse
newCreateAliasResponse :: Int -> CreateAliasResponse
newCreateAliasResponse Int
pHttpStatus_ =
  CreateAliasResponse'
    { $sel:alias:CreateAliasResponse' :: Maybe Text
alias = forall a. Maybe a
Prelude.Nothing,
      $sel:directoryId:CreateAliasResponse' :: Maybe Text
directoryId = forall a. Maybe a
Prelude.Nothing,
      $sel:httpStatus:CreateAliasResponse' :: Int
httpStatus = Int
pHttpStatus_
    }

-- | The alias for the directory.
createAliasResponse_alias :: Lens.Lens' CreateAliasResponse (Prelude.Maybe Prelude.Text)
createAliasResponse_alias :: Lens' CreateAliasResponse (Maybe Text)
createAliasResponse_alias = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\CreateAliasResponse' {Maybe Text
alias :: Maybe Text
$sel:alias:CreateAliasResponse' :: CreateAliasResponse -> Maybe Text
alias} -> Maybe Text
alias) (\s :: CreateAliasResponse
s@CreateAliasResponse' {} Maybe Text
a -> CreateAliasResponse
s {$sel:alias:CreateAliasResponse' :: Maybe Text
alias = Maybe Text
a} :: CreateAliasResponse)

-- | The identifier of the directory.
createAliasResponse_directoryId :: Lens.Lens' CreateAliasResponse (Prelude.Maybe Prelude.Text)
createAliasResponse_directoryId :: Lens' CreateAliasResponse (Maybe Text)
createAliasResponse_directoryId = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\CreateAliasResponse' {Maybe Text
directoryId :: Maybe Text
$sel:directoryId:CreateAliasResponse' :: CreateAliasResponse -> Maybe Text
directoryId} -> Maybe Text
directoryId) (\s :: CreateAliasResponse
s@CreateAliasResponse' {} Maybe Text
a -> CreateAliasResponse
s {$sel:directoryId:CreateAliasResponse' :: Maybe Text
directoryId = Maybe Text
a} :: CreateAliasResponse)

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

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