{-# 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.IoT.DeleteRoleAlias
-- 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 a role alias
--
-- Requires permission to access the
-- <https://docs.aws.amazon.com/service-authorization/latest/reference/list_awsiot.html#awsiot-actions-as-permissions DeleteRoleAlias>
-- action.
module Amazonka.IoT.DeleteRoleAlias
  ( -- * Creating a Request
    DeleteRoleAlias (..),
    newDeleteRoleAlias,

    -- * Request Lenses
    deleteRoleAlias_roleAlias,

    -- * Destructuring the Response
    DeleteRoleAliasResponse (..),
    newDeleteRoleAliasResponse,

    -- * Response Lenses
    deleteRoleAliasResponse_httpStatus,
  )
where

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

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

-- |
-- Create a value of 'DeleteRoleAlias' 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:
--
-- 'roleAlias', 'deleteRoleAlias_roleAlias' - The role alias to delete.
newDeleteRoleAlias ::
  -- | 'roleAlias'
  Prelude.Text ->
  DeleteRoleAlias
newDeleteRoleAlias :: Text -> DeleteRoleAlias
newDeleteRoleAlias Text
pRoleAlias_ =
  DeleteRoleAlias' {$sel:roleAlias:DeleteRoleAlias' :: Text
roleAlias = Text
pRoleAlias_}

-- | The role alias to delete.
deleteRoleAlias_roleAlias :: Lens.Lens' DeleteRoleAlias Prelude.Text
deleteRoleAlias_roleAlias :: Lens' DeleteRoleAlias Text
deleteRoleAlias_roleAlias = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\DeleteRoleAlias' {Text
roleAlias :: Text
$sel:roleAlias:DeleteRoleAlias' :: DeleteRoleAlias -> Text
roleAlias} -> Text
roleAlias) (\s :: DeleteRoleAlias
s@DeleteRoleAlias' {} Text
a -> DeleteRoleAlias
s {$sel:roleAlias:DeleteRoleAlias' :: Text
roleAlias = Text
a} :: DeleteRoleAlias)

instance Core.AWSRequest DeleteRoleAlias where
  type
    AWSResponse DeleteRoleAlias =
      DeleteRoleAliasResponse
  request :: (Service -> Service) -> DeleteRoleAlias -> Request DeleteRoleAlias
request Service -> Service
overrides =
    forall a. ToRequest a => Service -> a -> Request a
Request.delete (Service -> Service
overrides Service
defaultService)
  response :: forall (m :: * -> *).
MonadResource m =>
(ByteStringLazy -> IO ByteStringLazy)
-> Service
-> Proxy DeleteRoleAlias
-> ClientResponse ClientBody
-> m (Either Error (ClientResponse (AWSResponse DeleteRoleAlias)))
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 -> DeleteRoleAliasResponse
DeleteRoleAliasResponse'
            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 DeleteRoleAlias where
  hashWithSalt :: Int -> DeleteRoleAlias -> Int
hashWithSalt Int
_salt DeleteRoleAlias' {Text
roleAlias :: Text
$sel:roleAlias:DeleteRoleAlias' :: DeleteRoleAlias -> Text
..} =
    Int
_salt forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Text
roleAlias

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

instance Data.ToHeaders DeleteRoleAlias where
  toHeaders :: DeleteRoleAlias -> ResponseHeaders
toHeaders = forall a b. a -> b -> a
Prelude.const forall a. Monoid a => a
Prelude.mempty

instance Data.ToPath DeleteRoleAlias where
  toPath :: DeleteRoleAlias -> ByteString
toPath DeleteRoleAlias' {Text
roleAlias :: Text
$sel:roleAlias:DeleteRoleAlias' :: DeleteRoleAlias -> Text
..} =
    forall a. Monoid a => [a] -> a
Prelude.mconcat
      [ByteString
"/role-aliases/", forall a. ToByteString a => a -> ByteString
Data.toBS Text
roleAlias]

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

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

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

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

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