{-# 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.IAM.DeleteUserPermissionsBoundary
-- 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 the permissions boundary for the specified IAM user.
--
-- Deleting the permissions boundary for a user might increase its
-- permissions by allowing the user to perform all the actions granted in
-- its permissions policies.
module Amazonka.IAM.DeleteUserPermissionsBoundary
  ( -- * Creating a Request
    DeleteUserPermissionsBoundary (..),
    newDeleteUserPermissionsBoundary,

    -- * Request Lenses
    deleteUserPermissionsBoundary_userName,

    -- * Destructuring the Response
    DeleteUserPermissionsBoundaryResponse (..),
    newDeleteUserPermissionsBoundaryResponse,
  )
where

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

-- | /See:/ 'newDeleteUserPermissionsBoundary' smart constructor.
data DeleteUserPermissionsBoundary = DeleteUserPermissionsBoundary'
  { -- | The name (friendly name, not ARN) of the IAM user from which you want to
    -- remove the permissions boundary.
    DeleteUserPermissionsBoundary -> Text
userName :: Prelude.Text
  }
  deriving (DeleteUserPermissionsBoundary
-> DeleteUserPermissionsBoundary -> Bool
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: DeleteUserPermissionsBoundary
-> DeleteUserPermissionsBoundary -> Bool
$c/= :: DeleteUserPermissionsBoundary
-> DeleteUserPermissionsBoundary -> Bool
== :: DeleteUserPermissionsBoundary
-> DeleteUserPermissionsBoundary -> Bool
$c== :: DeleteUserPermissionsBoundary
-> DeleteUserPermissionsBoundary -> Bool
Prelude.Eq, ReadPrec [DeleteUserPermissionsBoundary]
ReadPrec DeleteUserPermissionsBoundary
Int -> ReadS DeleteUserPermissionsBoundary
ReadS [DeleteUserPermissionsBoundary]
forall a.
(Int -> ReadS a)
-> ReadS [a] -> ReadPrec a -> ReadPrec [a] -> Read a
readListPrec :: ReadPrec [DeleteUserPermissionsBoundary]
$creadListPrec :: ReadPrec [DeleteUserPermissionsBoundary]
readPrec :: ReadPrec DeleteUserPermissionsBoundary
$creadPrec :: ReadPrec DeleteUserPermissionsBoundary
readList :: ReadS [DeleteUserPermissionsBoundary]
$creadList :: ReadS [DeleteUserPermissionsBoundary]
readsPrec :: Int -> ReadS DeleteUserPermissionsBoundary
$creadsPrec :: Int -> ReadS DeleteUserPermissionsBoundary
Prelude.Read, Int -> DeleteUserPermissionsBoundary -> ShowS
[DeleteUserPermissionsBoundary] -> ShowS
DeleteUserPermissionsBoundary -> String
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [DeleteUserPermissionsBoundary] -> ShowS
$cshowList :: [DeleteUserPermissionsBoundary] -> ShowS
show :: DeleteUserPermissionsBoundary -> String
$cshow :: DeleteUserPermissionsBoundary -> String
showsPrec :: Int -> DeleteUserPermissionsBoundary -> ShowS
$cshowsPrec :: Int -> DeleteUserPermissionsBoundary -> ShowS
Prelude.Show, forall x.
Rep DeleteUserPermissionsBoundary x
-> DeleteUserPermissionsBoundary
forall x.
DeleteUserPermissionsBoundary
-> Rep DeleteUserPermissionsBoundary x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cto :: forall x.
Rep DeleteUserPermissionsBoundary x
-> DeleteUserPermissionsBoundary
$cfrom :: forall x.
DeleteUserPermissionsBoundary
-> Rep DeleteUserPermissionsBoundary x
Prelude.Generic)

-- |
-- Create a value of 'DeleteUserPermissionsBoundary' 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:
--
-- 'userName', 'deleteUserPermissionsBoundary_userName' - The name (friendly name, not ARN) of the IAM user from which you want to
-- remove the permissions boundary.
newDeleteUserPermissionsBoundary ::
  -- | 'userName'
  Prelude.Text ->
  DeleteUserPermissionsBoundary
newDeleteUserPermissionsBoundary :: Text -> DeleteUserPermissionsBoundary
newDeleteUserPermissionsBoundary Text
pUserName_ =
  DeleteUserPermissionsBoundary'
    { $sel:userName:DeleteUserPermissionsBoundary' :: Text
userName =
        Text
pUserName_
    }

-- | The name (friendly name, not ARN) of the IAM user from which you want to
-- remove the permissions boundary.
deleteUserPermissionsBoundary_userName :: Lens.Lens' DeleteUserPermissionsBoundary Prelude.Text
deleteUserPermissionsBoundary_userName :: Lens' DeleteUserPermissionsBoundary Text
deleteUserPermissionsBoundary_userName = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\DeleteUserPermissionsBoundary' {Text
userName :: Text
$sel:userName:DeleteUserPermissionsBoundary' :: DeleteUserPermissionsBoundary -> Text
userName} -> Text
userName) (\s :: DeleteUserPermissionsBoundary
s@DeleteUserPermissionsBoundary' {} Text
a -> DeleteUserPermissionsBoundary
s {$sel:userName:DeleteUserPermissionsBoundary' :: Text
userName = Text
a} :: DeleteUserPermissionsBoundary)

instance
  Core.AWSRequest
    DeleteUserPermissionsBoundary
  where
  type
    AWSResponse DeleteUserPermissionsBoundary =
      DeleteUserPermissionsBoundaryResponse
  request :: (Service -> Service)
-> DeleteUserPermissionsBoundary
-> Request DeleteUserPermissionsBoundary
request Service -> Service
overrides =
    forall a. ToRequest a => Service -> a -> Request a
Request.postQuery (Service -> Service
overrides Service
defaultService)
  response :: forall (m :: * -> *).
MonadResource m =>
(ByteStringLazy -> IO ByteStringLazy)
-> Service
-> Proxy DeleteUserPermissionsBoundary
-> ClientResponse ClientBody
-> m (Either
        Error (ClientResponse (AWSResponse DeleteUserPermissionsBoundary)))
response =
    forall (m :: * -> *) a.
MonadResource m =>
AWSResponse a
-> (ByteStringLazy -> IO ByteStringLazy)
-> Service
-> Proxy a
-> ClientResponse ClientBody
-> m (Either Error (ClientResponse (AWSResponse a)))
Response.receiveNull
      DeleteUserPermissionsBoundaryResponse
DeleteUserPermissionsBoundaryResponse'

instance
  Prelude.Hashable
    DeleteUserPermissionsBoundary
  where
  hashWithSalt :: Int -> DeleteUserPermissionsBoundary -> Int
hashWithSalt Int
_salt DeleteUserPermissionsBoundary' {Text
userName :: Text
$sel:userName:DeleteUserPermissionsBoundary' :: DeleteUserPermissionsBoundary -> Text
..} =
    Int
_salt forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Text
userName

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

instance Data.ToHeaders DeleteUserPermissionsBoundary where
  toHeaders :: DeleteUserPermissionsBoundary -> [Header]
toHeaders = forall a b. a -> b -> a
Prelude.const forall a. Monoid a => a
Prelude.mempty

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

instance Data.ToQuery DeleteUserPermissionsBoundary where
  toQuery :: DeleteUserPermissionsBoundary -> QueryString
toQuery DeleteUserPermissionsBoundary' {Text
userName :: Text
$sel:userName:DeleteUserPermissionsBoundary' :: DeleteUserPermissionsBoundary -> Text
..} =
    forall a. Monoid a => [a] -> a
Prelude.mconcat
      [ ByteString
"Action"
          forall a. ToQuery a => ByteString -> a -> QueryString
Data.=: ( ByteString
"DeleteUserPermissionsBoundary" ::
                      Prelude.ByteString
                  ),
        ByteString
"Version"
          forall a. ToQuery a => ByteString -> a -> QueryString
Data.=: (ByteString
"2010-05-08" :: Prelude.ByteString),
        ByteString
"UserName" forall a. ToQuery a => ByteString -> a -> QueryString
Data.=: Text
userName
      ]

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

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

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