{-# 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.DeleteRolePolicy
-- 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 role.
--
-- A role can also have managed policies attached to it. To detach a
-- managed policy from a role, use DetachRolePolicy. 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.DeleteRolePolicy
  ( -- * Creating a Request
    DeleteRolePolicy (..),
    newDeleteRolePolicy,

    -- * Request Lenses
    deleteRolePolicy_roleName,
    deleteRolePolicy_policyName,

    -- * Destructuring the Response
    DeleteRolePolicyResponse (..),
    newDeleteRolePolicyResponse,
  )
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:/ 'newDeleteRolePolicy' smart constructor.
data DeleteRolePolicy = DeleteRolePolicy'
  { -- | The name (friendly name, not ARN) identifying the role 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: _+=,.\@-
    DeleteRolePolicy -> Text
roleName :: Prelude.Text,
    -- | The name of the inline policy to delete from the specified IAM role.
    --
    -- 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: _+=,.\@-
    DeleteRolePolicy -> Text
policyName :: Prelude.Text
  }
  deriving (DeleteRolePolicy -> DeleteRolePolicy -> Bool
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: DeleteRolePolicy -> DeleteRolePolicy -> Bool
$c/= :: DeleteRolePolicy -> DeleteRolePolicy -> Bool
== :: DeleteRolePolicy -> DeleteRolePolicy -> Bool
$c== :: DeleteRolePolicy -> DeleteRolePolicy -> Bool
Prelude.Eq, ReadPrec [DeleteRolePolicy]
ReadPrec DeleteRolePolicy
Int -> ReadS DeleteRolePolicy
ReadS [DeleteRolePolicy]
forall a.
(Int -> ReadS a)
-> ReadS [a] -> ReadPrec a -> ReadPrec [a] -> Read a
readListPrec :: ReadPrec [DeleteRolePolicy]
$creadListPrec :: ReadPrec [DeleteRolePolicy]
readPrec :: ReadPrec DeleteRolePolicy
$creadPrec :: ReadPrec DeleteRolePolicy
readList :: ReadS [DeleteRolePolicy]
$creadList :: ReadS [DeleteRolePolicy]
readsPrec :: Int -> ReadS DeleteRolePolicy
$creadsPrec :: Int -> ReadS DeleteRolePolicy
Prelude.Read, Int -> DeleteRolePolicy -> ShowS
[DeleteRolePolicy] -> ShowS
DeleteRolePolicy -> String
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [DeleteRolePolicy] -> ShowS
$cshowList :: [DeleteRolePolicy] -> ShowS
show :: DeleteRolePolicy -> String
$cshow :: DeleteRolePolicy -> String
showsPrec :: Int -> DeleteRolePolicy -> ShowS
$cshowsPrec :: Int -> DeleteRolePolicy -> ShowS
Prelude.Show, forall x. Rep DeleteRolePolicy x -> DeleteRolePolicy
forall x. DeleteRolePolicy -> Rep DeleteRolePolicy x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cto :: forall x. Rep DeleteRolePolicy x -> DeleteRolePolicy
$cfrom :: forall x. DeleteRolePolicy -> Rep DeleteRolePolicy x
Prelude.Generic)

-- |
-- Create a value of 'DeleteRolePolicy' 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:
--
-- 'roleName', 'deleteRolePolicy_roleName' - The name (friendly name, not ARN) identifying the role 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', 'deleteRolePolicy_policyName' - The name of the inline policy to delete from the specified IAM role.
--
-- 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: _+=,.\@-
newDeleteRolePolicy ::
  -- | 'roleName'
  Prelude.Text ->
  -- | 'policyName'
  Prelude.Text ->
  DeleteRolePolicy
newDeleteRolePolicy :: Text -> Text -> DeleteRolePolicy
newDeleteRolePolicy Text
pRoleName_ Text
pPolicyName_ =
  DeleteRolePolicy'
    { $sel:roleName:DeleteRolePolicy' :: Text
roleName = Text
pRoleName_,
      $sel:policyName:DeleteRolePolicy' :: Text
policyName = Text
pPolicyName_
    }

-- | The name (friendly name, not ARN) identifying the role 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: _+=,.\@-
deleteRolePolicy_roleName :: Lens.Lens' DeleteRolePolicy Prelude.Text
deleteRolePolicy_roleName :: Lens' DeleteRolePolicy Text
deleteRolePolicy_roleName = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\DeleteRolePolicy' {Text
roleName :: Text
$sel:roleName:DeleteRolePolicy' :: DeleteRolePolicy -> Text
roleName} -> Text
roleName) (\s :: DeleteRolePolicy
s@DeleteRolePolicy' {} Text
a -> DeleteRolePolicy
s {$sel:roleName:DeleteRolePolicy' :: Text
roleName = Text
a} :: DeleteRolePolicy)

-- | The name of the inline policy to delete from the specified IAM role.
--
-- 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: _+=,.\@-
deleteRolePolicy_policyName :: Lens.Lens' DeleteRolePolicy Prelude.Text
deleteRolePolicy_policyName :: Lens' DeleteRolePolicy Text
deleteRolePolicy_policyName = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\DeleteRolePolicy' {Text
policyName :: Text
$sel:policyName:DeleteRolePolicy' :: DeleteRolePolicy -> Text
policyName} -> Text
policyName) (\s :: DeleteRolePolicy
s@DeleteRolePolicy' {} Text
a -> DeleteRolePolicy
s {$sel:policyName:DeleteRolePolicy' :: Text
policyName = Text
a} :: DeleteRolePolicy)

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

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

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

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

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

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

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

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

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