{-# 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.SupportApp.PutAccountAlias
-- 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 or updates an individual alias for each Amazon Web Services
-- account ID. The alias appears in the Amazon Web Services Support App
-- page of the Amazon Web Services Support Center. The alias also appears
-- in Slack messages from the Amazon Web Services Support App.
module Amazonka.SupportApp.PutAccountAlias
  ( -- * Creating a Request
    PutAccountAlias (..),
    newPutAccountAlias,

    -- * Request Lenses
    putAccountAlias_accountAlias,

    -- * Destructuring the Response
    PutAccountAliasResponse (..),
    newPutAccountAliasResponse,

    -- * Response Lenses
    putAccountAliasResponse_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.SupportApp.Types

-- | /See:/ 'newPutAccountAlias' smart constructor.
data PutAccountAlias = PutAccountAlias'
  { -- | An alias or short name for an Amazon Web Services account.
    PutAccountAlias -> Text
accountAlias :: Prelude.Text
  }
  deriving (PutAccountAlias -> PutAccountAlias -> Bool
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: PutAccountAlias -> PutAccountAlias -> Bool
$c/= :: PutAccountAlias -> PutAccountAlias -> Bool
== :: PutAccountAlias -> PutAccountAlias -> Bool
$c== :: PutAccountAlias -> PutAccountAlias -> Bool
Prelude.Eq, ReadPrec [PutAccountAlias]
ReadPrec PutAccountAlias
Int -> ReadS PutAccountAlias
ReadS [PutAccountAlias]
forall a.
(Int -> ReadS a)
-> ReadS [a] -> ReadPrec a -> ReadPrec [a] -> Read a
readListPrec :: ReadPrec [PutAccountAlias]
$creadListPrec :: ReadPrec [PutAccountAlias]
readPrec :: ReadPrec PutAccountAlias
$creadPrec :: ReadPrec PutAccountAlias
readList :: ReadS [PutAccountAlias]
$creadList :: ReadS [PutAccountAlias]
readsPrec :: Int -> ReadS PutAccountAlias
$creadsPrec :: Int -> ReadS PutAccountAlias
Prelude.Read, Int -> PutAccountAlias -> ShowS
[PutAccountAlias] -> ShowS
PutAccountAlias -> String
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [PutAccountAlias] -> ShowS
$cshowList :: [PutAccountAlias] -> ShowS
show :: PutAccountAlias -> String
$cshow :: PutAccountAlias -> String
showsPrec :: Int -> PutAccountAlias -> ShowS
$cshowsPrec :: Int -> PutAccountAlias -> ShowS
Prelude.Show, forall x. Rep PutAccountAlias x -> PutAccountAlias
forall x. PutAccountAlias -> Rep PutAccountAlias x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cto :: forall x. Rep PutAccountAlias x -> PutAccountAlias
$cfrom :: forall x. PutAccountAlias -> Rep PutAccountAlias x
Prelude.Generic)

-- |
-- Create a value of 'PutAccountAlias' 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:
--
-- 'accountAlias', 'putAccountAlias_accountAlias' - An alias or short name for an Amazon Web Services account.
newPutAccountAlias ::
  -- | 'accountAlias'
  Prelude.Text ->
  PutAccountAlias
newPutAccountAlias :: Text -> PutAccountAlias
newPutAccountAlias Text
pAccountAlias_ =
  PutAccountAlias' {$sel:accountAlias:PutAccountAlias' :: Text
accountAlias = Text
pAccountAlias_}

-- | An alias or short name for an Amazon Web Services account.
putAccountAlias_accountAlias :: Lens.Lens' PutAccountAlias Prelude.Text
putAccountAlias_accountAlias :: Lens' PutAccountAlias Text
putAccountAlias_accountAlias = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\PutAccountAlias' {Text
accountAlias :: Text
$sel:accountAlias:PutAccountAlias' :: PutAccountAlias -> Text
accountAlias} -> Text
accountAlias) (\s :: PutAccountAlias
s@PutAccountAlias' {} Text
a -> PutAccountAlias
s {$sel:accountAlias:PutAccountAlias' :: Text
accountAlias = Text
a} :: PutAccountAlias)

instance Core.AWSRequest PutAccountAlias where
  type
    AWSResponse PutAccountAlias =
      PutAccountAliasResponse
  request :: (Service -> Service) -> PutAccountAlias -> Request PutAccountAlias
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 PutAccountAlias
-> ClientResponse ClientBody
-> m (Either Error (ClientResponse (AWSResponse PutAccountAlias)))
response =
    forall (m :: * -> *) a.
MonadResource m =>
(Int -> ResponseHeaders -> () -> Either String (AWSResponse a))
-> (ByteStringLazy -> IO ByteStringLazy)
-> Service
-> Proxy a
-> ClientResponse ClientBody
-> m (Either Error (ClientResponse (AWSResponse a)))
Response.receiveEmpty
      ( \Int
s ResponseHeaders
h ()
x ->
          Int -> PutAccountAliasResponse
PutAccountAliasResponse'
            forall (f :: * -> *) a b. Functor 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 PutAccountAlias where
  hashWithSalt :: Int -> PutAccountAlias -> Int
hashWithSalt Int
_salt PutAccountAlias' {Text
accountAlias :: Text
$sel:accountAlias:PutAccountAlias' :: PutAccountAlias -> Text
..} =
    Int
_salt forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Text
accountAlias

instance Prelude.NFData PutAccountAlias where
  rnf :: PutAccountAlias -> ()
rnf PutAccountAlias' {Text
accountAlias :: Text
$sel:accountAlias:PutAccountAlias' :: PutAccountAlias -> Text
..} = forall a. NFData a => a -> ()
Prelude.rnf Text
accountAlias

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

instance Data.ToPath PutAccountAlias where
  toPath :: PutAccountAlias -> ByteString
toPath = forall a b. a -> b -> a
Prelude.const ByteString
"/control/put-account-alias"

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

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

-- |
-- Create a value of 'PutAccountAliasResponse' 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:
--
-- 'httpStatus', 'putAccountAliasResponse_httpStatus' - The response's http status code.
newPutAccountAliasResponse ::
  -- | 'httpStatus'
  Prelude.Int ->
  PutAccountAliasResponse
newPutAccountAliasResponse :: Int -> PutAccountAliasResponse
newPutAccountAliasResponse Int
pHttpStatus_ =
  PutAccountAliasResponse' {$sel:httpStatus:PutAccountAliasResponse' :: Int
httpStatus = Int
pHttpStatus_}

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

instance Prelude.NFData PutAccountAliasResponse where
  rnf :: PutAccountAliasResponse -> ()
rnf PutAccountAliasResponse' {Int
httpStatus :: Int
$sel:httpStatus:PutAccountAliasResponse' :: PutAccountAliasResponse -> Int
..} =
    forall a. NFData a => a -> ()
Prelude.rnf Int
httpStatus