{-# 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.AMP.UpdateWorkspaceAlias
-- Copyright   : (c) 2013-2023 Brendan Hay
-- License     : Mozilla Public License, v. 2.0.
-- Maintainer  : Brendan Hay
-- Stability   : auto-generated
-- Portability : non-portable (GHC extensions)
--
-- Updates an AMP workspace alias.
module Amazonka.AMP.UpdateWorkspaceAlias
  ( -- * Creating a Request
    UpdateWorkspaceAlias (..),
    newUpdateWorkspaceAlias,

    -- * Request Lenses
    updateWorkspaceAlias_alias,
    updateWorkspaceAlias_clientToken,
    updateWorkspaceAlias_workspaceId,

    -- * Destructuring the Response
    UpdateWorkspaceAliasResponse (..),
    newUpdateWorkspaceAliasResponse,
  )
where

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

-- | Represents the input of an UpdateWorkspaceAlias operation.
--
-- /See:/ 'newUpdateWorkspaceAlias' smart constructor.
data UpdateWorkspaceAlias = UpdateWorkspaceAlias'
  { -- | The new alias of the workspace.
    UpdateWorkspaceAlias -> Maybe Text
alias :: Prelude.Maybe Prelude.Text,
    -- | Optional, unique, case-sensitive, user-provided identifier to ensure the
    -- idempotency of the request.
    UpdateWorkspaceAlias -> Maybe Text
clientToken :: Prelude.Maybe Prelude.Text,
    -- | The ID of the workspace being updated.
    UpdateWorkspaceAlias -> Text
workspaceId :: Prelude.Text
  }
  deriving (UpdateWorkspaceAlias -> UpdateWorkspaceAlias -> Bool
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: UpdateWorkspaceAlias -> UpdateWorkspaceAlias -> Bool
$c/= :: UpdateWorkspaceAlias -> UpdateWorkspaceAlias -> Bool
== :: UpdateWorkspaceAlias -> UpdateWorkspaceAlias -> Bool
$c== :: UpdateWorkspaceAlias -> UpdateWorkspaceAlias -> Bool
Prelude.Eq, ReadPrec [UpdateWorkspaceAlias]
ReadPrec UpdateWorkspaceAlias
Int -> ReadS UpdateWorkspaceAlias
ReadS [UpdateWorkspaceAlias]
forall a.
(Int -> ReadS a)
-> ReadS [a] -> ReadPrec a -> ReadPrec [a] -> Read a
readListPrec :: ReadPrec [UpdateWorkspaceAlias]
$creadListPrec :: ReadPrec [UpdateWorkspaceAlias]
readPrec :: ReadPrec UpdateWorkspaceAlias
$creadPrec :: ReadPrec UpdateWorkspaceAlias
readList :: ReadS [UpdateWorkspaceAlias]
$creadList :: ReadS [UpdateWorkspaceAlias]
readsPrec :: Int -> ReadS UpdateWorkspaceAlias
$creadsPrec :: Int -> ReadS UpdateWorkspaceAlias
Prelude.Read, Int -> UpdateWorkspaceAlias -> ShowS
[UpdateWorkspaceAlias] -> ShowS
UpdateWorkspaceAlias -> String
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [UpdateWorkspaceAlias] -> ShowS
$cshowList :: [UpdateWorkspaceAlias] -> ShowS
show :: UpdateWorkspaceAlias -> String
$cshow :: UpdateWorkspaceAlias -> String
showsPrec :: Int -> UpdateWorkspaceAlias -> ShowS
$cshowsPrec :: Int -> UpdateWorkspaceAlias -> ShowS
Prelude.Show, forall x. Rep UpdateWorkspaceAlias x -> UpdateWorkspaceAlias
forall x. UpdateWorkspaceAlias -> Rep UpdateWorkspaceAlias x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cto :: forall x. Rep UpdateWorkspaceAlias x -> UpdateWorkspaceAlias
$cfrom :: forall x. UpdateWorkspaceAlias -> Rep UpdateWorkspaceAlias x
Prelude.Generic)

-- |
-- Create a value of 'UpdateWorkspaceAlias' 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', 'updateWorkspaceAlias_alias' - The new alias of the workspace.
--
-- 'clientToken', 'updateWorkspaceAlias_clientToken' - Optional, unique, case-sensitive, user-provided identifier to ensure the
-- idempotency of the request.
--
-- 'workspaceId', 'updateWorkspaceAlias_workspaceId' - The ID of the workspace being updated.
newUpdateWorkspaceAlias ::
  -- | 'workspaceId'
  Prelude.Text ->
  UpdateWorkspaceAlias
newUpdateWorkspaceAlias :: Text -> UpdateWorkspaceAlias
newUpdateWorkspaceAlias Text
pWorkspaceId_ =
  UpdateWorkspaceAlias'
    { $sel:alias:UpdateWorkspaceAlias' :: Maybe Text
alias = forall a. Maybe a
Prelude.Nothing,
      $sel:clientToken:UpdateWorkspaceAlias' :: Maybe Text
clientToken = forall a. Maybe a
Prelude.Nothing,
      $sel:workspaceId:UpdateWorkspaceAlias' :: Text
workspaceId = Text
pWorkspaceId_
    }

-- | The new alias of the workspace.
updateWorkspaceAlias_alias :: Lens.Lens' UpdateWorkspaceAlias (Prelude.Maybe Prelude.Text)
updateWorkspaceAlias_alias :: Lens' UpdateWorkspaceAlias (Maybe Text)
updateWorkspaceAlias_alias = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\UpdateWorkspaceAlias' {Maybe Text
alias :: Maybe Text
$sel:alias:UpdateWorkspaceAlias' :: UpdateWorkspaceAlias -> Maybe Text
alias} -> Maybe Text
alias) (\s :: UpdateWorkspaceAlias
s@UpdateWorkspaceAlias' {} Maybe Text
a -> UpdateWorkspaceAlias
s {$sel:alias:UpdateWorkspaceAlias' :: Maybe Text
alias = Maybe Text
a} :: UpdateWorkspaceAlias)

-- | Optional, unique, case-sensitive, user-provided identifier to ensure the
-- idempotency of the request.
updateWorkspaceAlias_clientToken :: Lens.Lens' UpdateWorkspaceAlias (Prelude.Maybe Prelude.Text)
updateWorkspaceAlias_clientToken :: Lens' UpdateWorkspaceAlias (Maybe Text)
updateWorkspaceAlias_clientToken = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\UpdateWorkspaceAlias' {Maybe Text
clientToken :: Maybe Text
$sel:clientToken:UpdateWorkspaceAlias' :: UpdateWorkspaceAlias -> Maybe Text
clientToken} -> Maybe Text
clientToken) (\s :: UpdateWorkspaceAlias
s@UpdateWorkspaceAlias' {} Maybe Text
a -> UpdateWorkspaceAlias
s {$sel:clientToken:UpdateWorkspaceAlias' :: Maybe Text
clientToken = Maybe Text
a} :: UpdateWorkspaceAlias)

-- | The ID of the workspace being updated.
updateWorkspaceAlias_workspaceId :: Lens.Lens' UpdateWorkspaceAlias Prelude.Text
updateWorkspaceAlias_workspaceId :: Lens' UpdateWorkspaceAlias Text
updateWorkspaceAlias_workspaceId = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\UpdateWorkspaceAlias' {Text
workspaceId :: Text
$sel:workspaceId:UpdateWorkspaceAlias' :: UpdateWorkspaceAlias -> Text
workspaceId} -> Text
workspaceId) (\s :: UpdateWorkspaceAlias
s@UpdateWorkspaceAlias' {} Text
a -> UpdateWorkspaceAlias
s {$sel:workspaceId:UpdateWorkspaceAlias' :: Text
workspaceId = Text
a} :: UpdateWorkspaceAlias)

instance Core.AWSRequest UpdateWorkspaceAlias where
  type
    AWSResponse UpdateWorkspaceAlias =
      UpdateWorkspaceAliasResponse
  request :: (Service -> Service)
-> UpdateWorkspaceAlias -> Request UpdateWorkspaceAlias
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 UpdateWorkspaceAlias
-> ClientResponse ClientBody
-> m (Either
        Error (ClientResponse (AWSResponse UpdateWorkspaceAlias)))
response =
    forall (m :: * -> *) a.
MonadResource m =>
AWSResponse a
-> (ByteStringLazy -> IO ByteStringLazy)
-> Service
-> Proxy a
-> ClientResponse ClientBody
-> m (Either Error (ClientResponse (AWSResponse a)))
Response.receiveNull UpdateWorkspaceAliasResponse
UpdateWorkspaceAliasResponse'

instance Prelude.Hashable UpdateWorkspaceAlias where
  hashWithSalt :: Int -> UpdateWorkspaceAlias -> Int
hashWithSalt Int
_salt UpdateWorkspaceAlias' {Maybe Text
Text
workspaceId :: Text
clientToken :: Maybe Text
alias :: Maybe Text
$sel:workspaceId:UpdateWorkspaceAlias' :: UpdateWorkspaceAlias -> Text
$sel:clientToken:UpdateWorkspaceAlias' :: UpdateWorkspaceAlias -> Maybe Text
$sel:alias:UpdateWorkspaceAlias' :: UpdateWorkspaceAlias -> Maybe Text
..} =
    Int
_salt
      forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Maybe Text
alias
      forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Maybe Text
clientToken
      forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Text
workspaceId

instance Prelude.NFData UpdateWorkspaceAlias where
  rnf :: UpdateWorkspaceAlias -> ()
rnf UpdateWorkspaceAlias' {Maybe Text
Text
workspaceId :: Text
clientToken :: Maybe Text
alias :: Maybe Text
$sel:workspaceId:UpdateWorkspaceAlias' :: UpdateWorkspaceAlias -> Text
$sel:clientToken:UpdateWorkspaceAlias' :: UpdateWorkspaceAlias -> Maybe Text
$sel:alias:UpdateWorkspaceAlias' :: UpdateWorkspaceAlias -> 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
clientToken
      seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf Text
workspaceId

instance Data.ToHeaders UpdateWorkspaceAlias where
  toHeaders :: UpdateWorkspaceAlias -> [Header]
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 -> [Header]
Data.=# ( ByteString
"application/x-amz-json-1.1" ::
                          Prelude.ByteString
                      )
          ]
      )

instance Data.ToJSON UpdateWorkspaceAlias where
  toJSON :: UpdateWorkspaceAlias -> Value
toJSON UpdateWorkspaceAlias' {Maybe Text
Text
workspaceId :: Text
clientToken :: Maybe Text
alias :: Maybe Text
$sel:workspaceId:UpdateWorkspaceAlias' :: UpdateWorkspaceAlias -> Text
$sel:clientToken:UpdateWorkspaceAlias' :: UpdateWorkspaceAlias -> Maybe Text
$sel:alias:UpdateWorkspaceAlias' :: UpdateWorkspaceAlias -> Maybe Text
..} =
    [Pair] -> Value
Data.object
      ( forall a. [Maybe a] -> [a]
Prelude.catMaybes
          [ (Key
"alias" 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
alias,
            (Key
"clientToken" 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
clientToken
          ]
      )

instance Data.ToPath UpdateWorkspaceAlias where
  toPath :: UpdateWorkspaceAlias -> ByteString
toPath UpdateWorkspaceAlias' {Maybe Text
Text
workspaceId :: Text
clientToken :: Maybe Text
alias :: Maybe Text
$sel:workspaceId:UpdateWorkspaceAlias' :: UpdateWorkspaceAlias -> Text
$sel:clientToken:UpdateWorkspaceAlias' :: UpdateWorkspaceAlias -> Maybe Text
$sel:alias:UpdateWorkspaceAlias' :: UpdateWorkspaceAlias -> Maybe Text
..} =
    forall a. Monoid a => [a] -> a
Prelude.mconcat
      [ByteString
"/workspaces/", forall a. ToByteString a => a -> ByteString
Data.toBS Text
workspaceId, ByteString
"/alias"]

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

-- | /See:/ 'newUpdateWorkspaceAliasResponse' smart constructor.
data UpdateWorkspaceAliasResponse = UpdateWorkspaceAliasResponse'
  {
  }
  deriving (UpdateWorkspaceAliasResponse
-> UpdateWorkspaceAliasResponse -> Bool
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: UpdateWorkspaceAliasResponse
-> UpdateWorkspaceAliasResponse -> Bool
$c/= :: UpdateWorkspaceAliasResponse
-> UpdateWorkspaceAliasResponse -> Bool
== :: UpdateWorkspaceAliasResponse
-> UpdateWorkspaceAliasResponse -> Bool
$c== :: UpdateWorkspaceAliasResponse
-> UpdateWorkspaceAliasResponse -> Bool
Prelude.Eq, ReadPrec [UpdateWorkspaceAliasResponse]
ReadPrec UpdateWorkspaceAliasResponse
Int -> ReadS UpdateWorkspaceAliasResponse
ReadS [UpdateWorkspaceAliasResponse]
forall a.
(Int -> ReadS a)
-> ReadS [a] -> ReadPrec a -> ReadPrec [a] -> Read a
readListPrec :: ReadPrec [UpdateWorkspaceAliasResponse]
$creadListPrec :: ReadPrec [UpdateWorkspaceAliasResponse]
readPrec :: ReadPrec UpdateWorkspaceAliasResponse
$creadPrec :: ReadPrec UpdateWorkspaceAliasResponse
readList :: ReadS [UpdateWorkspaceAliasResponse]
$creadList :: ReadS [UpdateWorkspaceAliasResponse]
readsPrec :: Int -> ReadS UpdateWorkspaceAliasResponse
$creadsPrec :: Int -> ReadS UpdateWorkspaceAliasResponse
Prelude.Read, Int -> UpdateWorkspaceAliasResponse -> ShowS
[UpdateWorkspaceAliasResponse] -> ShowS
UpdateWorkspaceAliasResponse -> String
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [UpdateWorkspaceAliasResponse] -> ShowS
$cshowList :: [UpdateWorkspaceAliasResponse] -> ShowS
show :: UpdateWorkspaceAliasResponse -> String
$cshow :: UpdateWorkspaceAliasResponse -> String
showsPrec :: Int -> UpdateWorkspaceAliasResponse -> ShowS
$cshowsPrec :: Int -> UpdateWorkspaceAliasResponse -> ShowS
Prelude.Show, forall x.
Rep UpdateWorkspaceAliasResponse x -> UpdateWorkspaceAliasResponse
forall x.
UpdateWorkspaceAliasResponse -> Rep UpdateWorkspaceAliasResponse x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cto :: forall x.
Rep UpdateWorkspaceAliasResponse x -> UpdateWorkspaceAliasResponse
$cfrom :: forall x.
UpdateWorkspaceAliasResponse -> Rep UpdateWorkspaceAliasResponse x
Prelude.Generic)

-- |
-- Create a value of 'UpdateWorkspaceAliasResponse' 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.
newUpdateWorkspaceAliasResponse ::
  UpdateWorkspaceAliasResponse
newUpdateWorkspaceAliasResponse :: UpdateWorkspaceAliasResponse
newUpdateWorkspaceAliasResponse =
  UpdateWorkspaceAliasResponse
UpdateWorkspaceAliasResponse'

instance Prelude.NFData UpdateWorkspaceAliasResponse where
  rnf :: UpdateWorkspaceAliasResponse -> ()
rnf UpdateWorkspaceAliasResponse
_ = ()