{-# 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.DeleteAccountAlias
-- Copyright   : (c) 2013-2023 Brendan Hay
-- License     : Mozilla Public License, v. 2.0.
-- Maintainer  : Brendan Hay
-- Stability   : auto-generated
-- Portability : non-portable (GHC extensions)
--
-- Deletes an alias for an 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.DeleteAccountAlias
  ( -- * Creating a Request
    DeleteAccountAlias (..),
    newDeleteAccountAlias,

    -- * Destructuring the Response
    DeleteAccountAliasResponse (..),
    newDeleteAccountAliasResponse,

    -- * Response Lenses
    deleteAccountAliasResponse_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:/ 'newDeleteAccountAlias' smart constructor.
data DeleteAccountAlias = DeleteAccountAlias'
  {
  }
  deriving (DeleteAccountAlias -> DeleteAccountAlias -> Bool
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: DeleteAccountAlias -> DeleteAccountAlias -> Bool
$c/= :: DeleteAccountAlias -> DeleteAccountAlias -> Bool
== :: DeleteAccountAlias -> DeleteAccountAlias -> Bool
$c== :: DeleteAccountAlias -> DeleteAccountAlias -> Bool
Prelude.Eq, ReadPrec [DeleteAccountAlias]
ReadPrec DeleteAccountAlias
Int -> ReadS DeleteAccountAlias
ReadS [DeleteAccountAlias]
forall a.
(Int -> ReadS a)
-> ReadS [a] -> ReadPrec a -> ReadPrec [a] -> Read a
readListPrec :: ReadPrec [DeleteAccountAlias]
$creadListPrec :: ReadPrec [DeleteAccountAlias]
readPrec :: ReadPrec DeleteAccountAlias
$creadPrec :: ReadPrec DeleteAccountAlias
readList :: ReadS [DeleteAccountAlias]
$creadList :: ReadS [DeleteAccountAlias]
readsPrec :: Int -> ReadS DeleteAccountAlias
$creadsPrec :: Int -> ReadS DeleteAccountAlias
Prelude.Read, Int -> DeleteAccountAlias -> ShowS
[DeleteAccountAlias] -> ShowS
DeleteAccountAlias -> String
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [DeleteAccountAlias] -> ShowS
$cshowList :: [DeleteAccountAlias] -> ShowS
show :: DeleteAccountAlias -> String
$cshow :: DeleteAccountAlias -> String
showsPrec :: Int -> DeleteAccountAlias -> ShowS
$cshowsPrec :: Int -> DeleteAccountAlias -> ShowS
Prelude.Show, forall x. Rep DeleteAccountAlias x -> DeleteAccountAlias
forall x. DeleteAccountAlias -> Rep DeleteAccountAlias x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cto :: forall x. Rep DeleteAccountAlias x -> DeleteAccountAlias
$cfrom :: forall x. DeleteAccountAlias -> Rep DeleteAccountAlias x
Prelude.Generic)

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

instance Core.AWSRequest DeleteAccountAlias where
  type
    AWSResponse DeleteAccountAlias =
      DeleteAccountAliasResponse
  request :: (Service -> Service)
-> DeleteAccountAlias -> Request DeleteAccountAlias
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 DeleteAccountAlias
-> ClientResponse ClientBody
-> m (Either
        Error (ClientResponse (AWSResponse DeleteAccountAlias)))
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 -> DeleteAccountAliasResponse
DeleteAccountAliasResponse'
            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 DeleteAccountAlias where
  hashWithSalt :: Int -> DeleteAccountAlias -> Int
hashWithSalt Int
_salt DeleteAccountAlias
_ =
    Int
_salt forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` ()

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

instance Data.ToHeaders DeleteAccountAlias where
  toHeaders :: DeleteAccountAlias -> 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 DeleteAccountAlias where
  toJSON :: DeleteAccountAlias -> Value
toJSON = forall a b. a -> b -> a
Prelude.const (Object -> Value
Data.Object forall a. Monoid a => a
Prelude.mempty)

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

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

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

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

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

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