{-# 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.DeleteUserPolicy
-- 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 specified inline policy that is embedded in the specified
-- IAM user.
--
-- A user can also have managed policies attached to it. To detach a
-- managed policy from a user, use DetachUserPolicy. For more information
-- about policies, refer to
-- <https://docs.aws.amazon.com/IAM/latest/UserGuide/policies-managed-vs-inline.html Managed policies and inline policies>
-- in the /IAM User Guide/.
module Amazonka.IAM.DeleteUserPolicy
  ( -- * Creating a Request
    DeleteUserPolicy (..),
    newDeleteUserPolicy,

    -- * Request Lenses
    deleteUserPolicy_userName,
    deleteUserPolicy_policyName,

    -- * Destructuring the Response
    DeleteUserPolicyResponse (..),
    newDeleteUserPolicyResponse,
  )
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:/ 'newDeleteUserPolicy' smart constructor.
data DeleteUserPolicy = DeleteUserPolicy'
  { -- | The name (friendly name, not ARN) identifying the user that the policy
    -- is embedded in.
    --
    -- This parameter allows (through its
    -- <http://wikipedia.org/wiki/regex regex pattern>) a string of characters
    -- consisting of upper and lowercase alphanumeric characters with no
    -- spaces. You can also include any of the following characters: _+=,.\@-
    DeleteUserPolicy -> Text
userName :: Prelude.Text,
    -- | The name identifying the policy document to delete.
    --
    -- This parameter allows (through its
    -- <http://wikipedia.org/wiki/regex regex pattern>) a string of characters
    -- consisting of upper and lowercase alphanumeric characters with no
    -- spaces. You can also include any of the following characters: _+=,.\@-
    DeleteUserPolicy -> Text
policyName :: Prelude.Text
  }
  deriving (DeleteUserPolicy -> DeleteUserPolicy -> Bool
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: DeleteUserPolicy -> DeleteUserPolicy -> Bool
$c/= :: DeleteUserPolicy -> DeleteUserPolicy -> Bool
== :: DeleteUserPolicy -> DeleteUserPolicy -> Bool
$c== :: DeleteUserPolicy -> DeleteUserPolicy -> Bool
Prelude.Eq, ReadPrec [DeleteUserPolicy]
ReadPrec DeleteUserPolicy
Int -> ReadS DeleteUserPolicy
ReadS [DeleteUserPolicy]
forall a.
(Int -> ReadS a)
-> ReadS [a] -> ReadPrec a -> ReadPrec [a] -> Read a
readListPrec :: ReadPrec [DeleteUserPolicy]
$creadListPrec :: ReadPrec [DeleteUserPolicy]
readPrec :: ReadPrec DeleteUserPolicy
$creadPrec :: ReadPrec DeleteUserPolicy
readList :: ReadS [DeleteUserPolicy]
$creadList :: ReadS [DeleteUserPolicy]
readsPrec :: Int -> ReadS DeleteUserPolicy
$creadsPrec :: Int -> ReadS DeleteUserPolicy
Prelude.Read, Int -> DeleteUserPolicy -> ShowS
[DeleteUserPolicy] -> ShowS
DeleteUserPolicy -> String
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [DeleteUserPolicy] -> ShowS
$cshowList :: [DeleteUserPolicy] -> ShowS
show :: DeleteUserPolicy -> String
$cshow :: DeleteUserPolicy -> String
showsPrec :: Int -> DeleteUserPolicy -> ShowS
$cshowsPrec :: Int -> DeleteUserPolicy -> ShowS
Prelude.Show, forall x. Rep DeleteUserPolicy x -> DeleteUserPolicy
forall x. DeleteUserPolicy -> Rep DeleteUserPolicy x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cto :: forall x. Rep DeleteUserPolicy x -> DeleteUserPolicy
$cfrom :: forall x. DeleteUserPolicy -> Rep DeleteUserPolicy x
Prelude.Generic)

-- |
-- Create a value of 'DeleteUserPolicy' 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', 'deleteUserPolicy_userName' - The name (friendly name, not ARN) identifying the user that the policy
-- is embedded in.
--
-- This parameter allows (through its
-- <http://wikipedia.org/wiki/regex regex pattern>) a string of characters
-- consisting of upper and lowercase alphanumeric characters with no
-- spaces. You can also include any of the following characters: _+=,.\@-
--
-- 'policyName', 'deleteUserPolicy_policyName' - The name identifying the policy document to delete.
--
-- This parameter allows (through its
-- <http://wikipedia.org/wiki/regex regex pattern>) a string of characters
-- consisting of upper and lowercase alphanumeric characters with no
-- spaces. You can also include any of the following characters: _+=,.\@-
newDeleteUserPolicy ::
  -- | 'userName'
  Prelude.Text ->
  -- | 'policyName'
  Prelude.Text ->
  DeleteUserPolicy
newDeleteUserPolicy :: Text -> Text -> DeleteUserPolicy
newDeleteUserPolicy Text
pUserName_ Text
pPolicyName_ =
  DeleteUserPolicy'
    { $sel:userName:DeleteUserPolicy' :: Text
userName = Text
pUserName_,
      $sel:policyName:DeleteUserPolicy' :: Text
policyName = Text
pPolicyName_
    }

-- | The name (friendly name, not ARN) identifying the user that the policy
-- is embedded in.
--
-- This parameter allows (through its
-- <http://wikipedia.org/wiki/regex regex pattern>) a string of characters
-- consisting of upper and lowercase alphanumeric characters with no
-- spaces. You can also include any of the following characters: _+=,.\@-
deleteUserPolicy_userName :: Lens.Lens' DeleteUserPolicy Prelude.Text
deleteUserPolicy_userName :: Lens' DeleteUserPolicy Text
deleteUserPolicy_userName = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\DeleteUserPolicy' {Text
userName :: Text
$sel:userName:DeleteUserPolicy' :: DeleteUserPolicy -> Text
userName} -> Text
userName) (\s :: DeleteUserPolicy
s@DeleteUserPolicy' {} Text
a -> DeleteUserPolicy
s {$sel:userName:DeleteUserPolicy' :: Text
userName = Text
a} :: DeleteUserPolicy)

-- | The name identifying the policy document to delete.
--
-- This parameter allows (through its
-- <http://wikipedia.org/wiki/regex regex pattern>) a string of characters
-- consisting of upper and lowercase alphanumeric characters with no
-- spaces. You can also include any of the following characters: _+=,.\@-
deleteUserPolicy_policyName :: Lens.Lens' DeleteUserPolicy Prelude.Text
deleteUserPolicy_policyName :: Lens' DeleteUserPolicy Text
deleteUserPolicy_policyName = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\DeleteUserPolicy' {Text
policyName :: Text
$sel:policyName:DeleteUserPolicy' :: DeleteUserPolicy -> Text
policyName} -> Text
policyName) (\s :: DeleteUserPolicy
s@DeleteUserPolicy' {} Text
a -> DeleteUserPolicy
s {$sel:policyName:DeleteUserPolicy' :: Text
policyName = Text
a} :: DeleteUserPolicy)

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

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

instance Prelude.NFData DeleteUserPolicy where
  rnf :: DeleteUserPolicy -> ()
rnf DeleteUserPolicy' {Text
policyName :: Text
userName :: Text
$sel:policyName:DeleteUserPolicy' :: DeleteUserPolicy -> Text
$sel:userName:DeleteUserPolicy' :: DeleteUserPolicy -> Text
..} =
    forall a. NFData a => a -> ()
Prelude.rnf Text
userName
      seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf Text
policyName

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

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

instance Data.ToQuery DeleteUserPolicy where
  toQuery :: DeleteUserPolicy -> QueryString
toQuery DeleteUserPolicy' {Text
policyName :: Text
userName :: Text
$sel:policyName:DeleteUserPolicy' :: DeleteUserPolicy -> Text
$sel:userName:DeleteUserPolicy' :: DeleteUserPolicy -> Text
..} =
    forall a. Monoid a => [a] -> a
Prelude.mconcat
      [ ByteString
"Action"
          forall a. ToQuery a => ByteString -> a -> QueryString
Data.=: (ByteString
"DeleteUserPolicy" :: 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,
        ByteString
"PolicyName" forall a. ToQuery a => ByteString -> a -> QueryString
Data.=: Text
policyName
      ]

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

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

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