{-# 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.WorkSpaces.CreateConnectionAlias
-- 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 the specified connection alias for use with cross-Region
-- redirection. For more information, see
-- <https://docs.aws.amazon.com/workspaces/latest/adminguide/cross-region-redirection.html Cross-Region Redirection for Amazon WorkSpaces>.
module Amazonka.WorkSpaces.CreateConnectionAlias
  ( -- * Creating a Request
    CreateConnectionAlias (..),
    newCreateConnectionAlias,

    -- * Request Lenses
    createConnectionAlias_tags,
    createConnectionAlias_connectionString,

    -- * Destructuring the Response
    CreateConnectionAliasResponse (..),
    newCreateConnectionAliasResponse,

    -- * Response Lenses
    createConnectionAliasResponse_aliasId,
    createConnectionAliasResponse_httpStatus,
  )
where

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
import Amazonka.WorkSpaces.Types

-- | /See:/ 'newCreateConnectionAlias' smart constructor.
data CreateConnectionAlias = CreateConnectionAlias'
  { -- | The tags to associate with the connection alias.
    CreateConnectionAlias -> Maybe [Tag]
tags :: Prelude.Maybe [Tag],
    -- | A connection string in the form of a fully qualified domain name (FQDN),
    -- such as @www.example.com@.
    --
    -- After you create a connection string, it is always associated to your
    -- Amazon Web Services account. You cannot recreate the same connection
    -- string with a different account, even if you delete all instances of it
    -- from the original account. The connection string is globally reserved
    -- for your account.
    CreateConnectionAlias -> Text
connectionString :: Prelude.Text
  }
  deriving (CreateConnectionAlias -> CreateConnectionAlias -> Bool
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: CreateConnectionAlias -> CreateConnectionAlias -> Bool
$c/= :: CreateConnectionAlias -> CreateConnectionAlias -> Bool
== :: CreateConnectionAlias -> CreateConnectionAlias -> Bool
$c== :: CreateConnectionAlias -> CreateConnectionAlias -> Bool
Prelude.Eq, ReadPrec [CreateConnectionAlias]
ReadPrec CreateConnectionAlias
Int -> ReadS CreateConnectionAlias
ReadS [CreateConnectionAlias]
forall a.
(Int -> ReadS a)
-> ReadS [a] -> ReadPrec a -> ReadPrec [a] -> Read a
readListPrec :: ReadPrec [CreateConnectionAlias]
$creadListPrec :: ReadPrec [CreateConnectionAlias]
readPrec :: ReadPrec CreateConnectionAlias
$creadPrec :: ReadPrec CreateConnectionAlias
readList :: ReadS [CreateConnectionAlias]
$creadList :: ReadS [CreateConnectionAlias]
readsPrec :: Int -> ReadS CreateConnectionAlias
$creadsPrec :: Int -> ReadS CreateConnectionAlias
Prelude.Read, Int -> CreateConnectionAlias -> ShowS
[CreateConnectionAlias] -> ShowS
CreateConnectionAlias -> String
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [CreateConnectionAlias] -> ShowS
$cshowList :: [CreateConnectionAlias] -> ShowS
show :: CreateConnectionAlias -> String
$cshow :: CreateConnectionAlias -> String
showsPrec :: Int -> CreateConnectionAlias -> ShowS
$cshowsPrec :: Int -> CreateConnectionAlias -> ShowS
Prelude.Show, forall x. Rep CreateConnectionAlias x -> CreateConnectionAlias
forall x. CreateConnectionAlias -> Rep CreateConnectionAlias x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cto :: forall x. Rep CreateConnectionAlias x -> CreateConnectionAlias
$cfrom :: forall x. CreateConnectionAlias -> Rep CreateConnectionAlias x
Prelude.Generic)

-- |
-- Create a value of 'CreateConnectionAlias' 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:
--
-- 'tags', 'createConnectionAlias_tags' - The tags to associate with the connection alias.
--
-- 'connectionString', 'createConnectionAlias_connectionString' - A connection string in the form of a fully qualified domain name (FQDN),
-- such as @www.example.com@.
--
-- After you create a connection string, it is always associated to your
-- Amazon Web Services account. You cannot recreate the same connection
-- string with a different account, even if you delete all instances of it
-- from the original account. The connection string is globally reserved
-- for your account.
newCreateConnectionAlias ::
  -- | 'connectionString'
  Prelude.Text ->
  CreateConnectionAlias
newCreateConnectionAlias :: Text -> CreateConnectionAlias
newCreateConnectionAlias Text
pConnectionString_ =
  CreateConnectionAlias'
    { $sel:tags:CreateConnectionAlias' :: Maybe [Tag]
tags = forall a. Maybe a
Prelude.Nothing,
      $sel:connectionString:CreateConnectionAlias' :: Text
connectionString = Text
pConnectionString_
    }

-- | The tags to associate with the connection alias.
createConnectionAlias_tags :: Lens.Lens' CreateConnectionAlias (Prelude.Maybe [Tag])
createConnectionAlias_tags :: Lens' CreateConnectionAlias (Maybe [Tag])
createConnectionAlias_tags = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\CreateConnectionAlias' {Maybe [Tag]
tags :: Maybe [Tag]
$sel:tags:CreateConnectionAlias' :: CreateConnectionAlias -> Maybe [Tag]
tags} -> Maybe [Tag]
tags) (\s :: CreateConnectionAlias
s@CreateConnectionAlias' {} Maybe [Tag]
a -> CreateConnectionAlias
s {$sel:tags:CreateConnectionAlias' :: Maybe [Tag]
tags = Maybe [Tag]
a} :: CreateConnectionAlias) 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

-- | A connection string in the form of a fully qualified domain name (FQDN),
-- such as @www.example.com@.
--
-- After you create a connection string, it is always associated to your
-- Amazon Web Services account. You cannot recreate the same connection
-- string with a different account, even if you delete all instances of it
-- from the original account. The connection string is globally reserved
-- for your account.
createConnectionAlias_connectionString :: Lens.Lens' CreateConnectionAlias Prelude.Text
createConnectionAlias_connectionString :: Lens' CreateConnectionAlias Text
createConnectionAlias_connectionString = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\CreateConnectionAlias' {Text
connectionString :: Text
$sel:connectionString:CreateConnectionAlias' :: CreateConnectionAlias -> Text
connectionString} -> Text
connectionString) (\s :: CreateConnectionAlias
s@CreateConnectionAlias' {} Text
a -> CreateConnectionAlias
s {$sel:connectionString:CreateConnectionAlias' :: Text
connectionString = Text
a} :: CreateConnectionAlias)

instance Core.AWSRequest CreateConnectionAlias where
  type
    AWSResponse CreateConnectionAlias =
      CreateConnectionAliasResponse
  request :: (Service -> Service)
-> CreateConnectionAlias -> Request CreateConnectionAlias
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 CreateConnectionAlias
-> ClientResponse ClientBody
-> m (Either
        Error (ClientResponse (AWSResponse CreateConnectionAlias)))
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 -> CreateConnectionAliasResponse
CreateConnectionAliasResponse'
            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
"AliasId")
            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 CreateConnectionAlias where
  hashWithSalt :: Int -> CreateConnectionAlias -> Int
hashWithSalt Int
_salt CreateConnectionAlias' {Maybe [Tag]
Text
connectionString :: Text
tags :: Maybe [Tag]
$sel:connectionString:CreateConnectionAlias' :: CreateConnectionAlias -> Text
$sel:tags:CreateConnectionAlias' :: CreateConnectionAlias -> Maybe [Tag]
..} =
    Int
_salt
      forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Maybe [Tag]
tags
      forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Text
connectionString

instance Prelude.NFData CreateConnectionAlias where
  rnf :: CreateConnectionAlias -> ()
rnf CreateConnectionAlias' {Maybe [Tag]
Text
connectionString :: Text
tags :: Maybe [Tag]
$sel:connectionString:CreateConnectionAlias' :: CreateConnectionAlias -> Text
$sel:tags:CreateConnectionAlias' :: CreateConnectionAlias -> Maybe [Tag]
..} =
    forall a. NFData a => a -> ()
Prelude.rnf Maybe [Tag]
tags
      seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf Text
connectionString

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

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

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

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

-- |
-- Create a value of 'CreateConnectionAliasResponse' 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:
--
-- 'aliasId', 'createConnectionAliasResponse_aliasId' - The identifier of the connection alias.
--
-- 'httpStatus', 'createConnectionAliasResponse_httpStatus' - The response's http status code.
newCreateConnectionAliasResponse ::
  -- | 'httpStatus'
  Prelude.Int ->
  CreateConnectionAliasResponse
newCreateConnectionAliasResponse :: Int -> CreateConnectionAliasResponse
newCreateConnectionAliasResponse Int
pHttpStatus_ =
  CreateConnectionAliasResponse'
    { $sel:aliasId:CreateConnectionAliasResponse' :: Maybe Text
aliasId =
        forall a. Maybe a
Prelude.Nothing,
      $sel:httpStatus:CreateConnectionAliasResponse' :: Int
httpStatus = Int
pHttpStatus_
    }

-- | The identifier of the connection alias.
createConnectionAliasResponse_aliasId :: Lens.Lens' CreateConnectionAliasResponse (Prelude.Maybe Prelude.Text)
createConnectionAliasResponse_aliasId :: Lens' CreateConnectionAliasResponse (Maybe Text)
createConnectionAliasResponse_aliasId = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\CreateConnectionAliasResponse' {Maybe Text
aliasId :: Maybe Text
$sel:aliasId:CreateConnectionAliasResponse' :: CreateConnectionAliasResponse -> Maybe Text
aliasId} -> Maybe Text
aliasId) (\s :: CreateConnectionAliasResponse
s@CreateConnectionAliasResponse' {} Maybe Text
a -> CreateConnectionAliasResponse
s {$sel:aliasId:CreateConnectionAliasResponse' :: Maybe Text
aliasId = Maybe Text
a} :: CreateConnectionAliasResponse)

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

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