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

    -- * Request Lenses
    deleteGroupPolicy_groupName,
    deleteGroupPolicy_policyName,

    -- * Destructuring the Response
    DeleteGroupPolicyResponse (..),
    newDeleteGroupPolicyResponse,
  )
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:/ 'newDeleteGroupPolicy' smart constructor.
data DeleteGroupPolicy = DeleteGroupPolicy'
  { -- | The name (friendly name, not ARN) identifying the group 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: _+=,.\@-
    DeleteGroupPolicy -> Text
groupName :: 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: _+=,.\@-
    DeleteGroupPolicy -> Text
policyName :: Prelude.Text
  }
  deriving (DeleteGroupPolicy -> DeleteGroupPolicy -> Bool
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: DeleteGroupPolicy -> DeleteGroupPolicy -> Bool
$c/= :: DeleteGroupPolicy -> DeleteGroupPolicy -> Bool
== :: DeleteGroupPolicy -> DeleteGroupPolicy -> Bool
$c== :: DeleteGroupPolicy -> DeleteGroupPolicy -> Bool
Prelude.Eq, ReadPrec [DeleteGroupPolicy]
ReadPrec DeleteGroupPolicy
Int -> ReadS DeleteGroupPolicy
ReadS [DeleteGroupPolicy]
forall a.
(Int -> ReadS a)
-> ReadS [a] -> ReadPrec a -> ReadPrec [a] -> Read a
readListPrec :: ReadPrec [DeleteGroupPolicy]
$creadListPrec :: ReadPrec [DeleteGroupPolicy]
readPrec :: ReadPrec DeleteGroupPolicy
$creadPrec :: ReadPrec DeleteGroupPolicy
readList :: ReadS [DeleteGroupPolicy]
$creadList :: ReadS [DeleteGroupPolicy]
readsPrec :: Int -> ReadS DeleteGroupPolicy
$creadsPrec :: Int -> ReadS DeleteGroupPolicy
Prelude.Read, Int -> DeleteGroupPolicy -> ShowS
[DeleteGroupPolicy] -> ShowS
DeleteGroupPolicy -> String
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [DeleteGroupPolicy] -> ShowS
$cshowList :: [DeleteGroupPolicy] -> ShowS
show :: DeleteGroupPolicy -> String
$cshow :: DeleteGroupPolicy -> String
showsPrec :: Int -> DeleteGroupPolicy -> ShowS
$cshowsPrec :: Int -> DeleteGroupPolicy -> ShowS
Prelude.Show, forall x. Rep DeleteGroupPolicy x -> DeleteGroupPolicy
forall x. DeleteGroupPolicy -> Rep DeleteGroupPolicy x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cto :: forall x. Rep DeleteGroupPolicy x -> DeleteGroupPolicy
$cfrom :: forall x. DeleteGroupPolicy -> Rep DeleteGroupPolicy x
Prelude.Generic)

-- |
-- Create a value of 'DeleteGroupPolicy' 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:
--
-- 'groupName', 'deleteGroupPolicy_groupName' - The name (friendly name, not ARN) identifying the group 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', 'deleteGroupPolicy_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: _+=,.\@-
newDeleteGroupPolicy ::
  -- | 'groupName'
  Prelude.Text ->
  -- | 'policyName'
  Prelude.Text ->
  DeleteGroupPolicy
newDeleteGroupPolicy :: Text -> Text -> DeleteGroupPolicy
newDeleteGroupPolicy Text
pGroupName_ Text
pPolicyName_ =
  DeleteGroupPolicy'
    { $sel:groupName:DeleteGroupPolicy' :: Text
groupName = Text
pGroupName_,
      $sel:policyName:DeleteGroupPolicy' :: Text
policyName = Text
pPolicyName_
    }

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

-- | 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: _+=,.\@-
deleteGroupPolicy_policyName :: Lens.Lens' DeleteGroupPolicy Prelude.Text
deleteGroupPolicy_policyName :: Lens' DeleteGroupPolicy Text
deleteGroupPolicy_policyName = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\DeleteGroupPolicy' {Text
policyName :: Text
$sel:policyName:DeleteGroupPolicy' :: DeleteGroupPolicy -> Text
policyName} -> Text
policyName) (\s :: DeleteGroupPolicy
s@DeleteGroupPolicy' {} Text
a -> DeleteGroupPolicy
s {$sel:policyName:DeleteGroupPolicy' :: Text
policyName = Text
a} :: DeleteGroupPolicy)

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

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

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

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

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

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

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

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

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