{-# 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.DetachGroupPolicy
-- Copyright   : (c) 2013-2023 Brendan Hay
-- License     : Mozilla Public License, v. 2.0.
-- Maintainer  : Brendan Hay
-- Stability   : auto-generated
-- Portability : non-portable (GHC extensions)
--
-- Removes the specified managed policy from the specified IAM group.
--
-- A group can also have inline policies embedded with it. To delete an
-- inline policy, use DeleteGroupPolicy. For information about policies,
-- see
-- <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.DetachGroupPolicy
  ( -- * Creating a Request
    DetachGroupPolicy (..),
    newDetachGroupPolicy,

    -- * Request Lenses
    detachGroupPolicy_groupName,
    detachGroupPolicy_policyArn,

    -- * Destructuring the Response
    DetachGroupPolicyResponse (..),
    newDetachGroupPolicyResponse,
  )
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:/ 'newDetachGroupPolicy' smart constructor.
data DetachGroupPolicy = DetachGroupPolicy'
  { -- | The name (friendly name, not ARN) of the IAM group to detach the policy
    -- from.
    --
    -- 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: _+=,.\@-
    DetachGroupPolicy -> Text
groupName :: Prelude.Text,
    -- | The Amazon Resource Name (ARN) of the IAM policy you want to detach.
    --
    -- For more information about ARNs, see
    -- <https://docs.aws.amazon.com/general/latest/gr/aws-arns-and-namespaces.html Amazon Resource Names (ARNs)>
    -- in the /Amazon Web Services General Reference/.
    DetachGroupPolicy -> Text
policyArn :: Prelude.Text
  }
  deriving (DetachGroupPolicy -> DetachGroupPolicy -> Bool
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: DetachGroupPolicy -> DetachGroupPolicy -> Bool
$c/= :: DetachGroupPolicy -> DetachGroupPolicy -> Bool
== :: DetachGroupPolicy -> DetachGroupPolicy -> Bool
$c== :: DetachGroupPolicy -> DetachGroupPolicy -> Bool
Prelude.Eq, ReadPrec [DetachGroupPolicy]
ReadPrec DetachGroupPolicy
Int -> ReadS DetachGroupPolicy
ReadS [DetachGroupPolicy]
forall a.
(Int -> ReadS a)
-> ReadS [a] -> ReadPrec a -> ReadPrec [a] -> Read a
readListPrec :: ReadPrec [DetachGroupPolicy]
$creadListPrec :: ReadPrec [DetachGroupPolicy]
readPrec :: ReadPrec DetachGroupPolicy
$creadPrec :: ReadPrec DetachGroupPolicy
readList :: ReadS [DetachGroupPolicy]
$creadList :: ReadS [DetachGroupPolicy]
readsPrec :: Int -> ReadS DetachGroupPolicy
$creadsPrec :: Int -> ReadS DetachGroupPolicy
Prelude.Read, Int -> DetachGroupPolicy -> ShowS
[DetachGroupPolicy] -> ShowS
DetachGroupPolicy -> String
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [DetachGroupPolicy] -> ShowS
$cshowList :: [DetachGroupPolicy] -> ShowS
show :: DetachGroupPolicy -> String
$cshow :: DetachGroupPolicy -> String
showsPrec :: Int -> DetachGroupPolicy -> ShowS
$cshowsPrec :: Int -> DetachGroupPolicy -> ShowS
Prelude.Show, forall x. Rep DetachGroupPolicy x -> DetachGroupPolicy
forall x. DetachGroupPolicy -> Rep DetachGroupPolicy x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cto :: forall x. Rep DetachGroupPolicy x -> DetachGroupPolicy
$cfrom :: forall x. DetachGroupPolicy -> Rep DetachGroupPolicy x
Prelude.Generic)

-- |
-- Create a value of 'DetachGroupPolicy' 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', 'detachGroupPolicy_groupName' - The name (friendly name, not ARN) of the IAM group to detach the policy
-- from.
--
-- 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: _+=,.\@-
--
-- 'policyArn', 'detachGroupPolicy_policyArn' - The Amazon Resource Name (ARN) of the IAM policy you want to detach.
--
-- For more information about ARNs, see
-- <https://docs.aws.amazon.com/general/latest/gr/aws-arns-and-namespaces.html Amazon Resource Names (ARNs)>
-- in the /Amazon Web Services General Reference/.
newDetachGroupPolicy ::
  -- | 'groupName'
  Prelude.Text ->
  -- | 'policyArn'
  Prelude.Text ->
  DetachGroupPolicy
newDetachGroupPolicy :: Text -> Text -> DetachGroupPolicy
newDetachGroupPolicy Text
pGroupName_ Text
pPolicyArn_ =
  DetachGroupPolicy'
    { $sel:groupName:DetachGroupPolicy' :: Text
groupName = Text
pGroupName_,
      $sel:policyArn:DetachGroupPolicy' :: Text
policyArn = Text
pPolicyArn_
    }

-- | The name (friendly name, not ARN) of the IAM group to detach the policy
-- from.
--
-- 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: _+=,.\@-
detachGroupPolicy_groupName :: Lens.Lens' DetachGroupPolicy Prelude.Text
detachGroupPolicy_groupName :: Lens' DetachGroupPolicy Text
detachGroupPolicy_groupName = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\DetachGroupPolicy' {Text
groupName :: Text
$sel:groupName:DetachGroupPolicy' :: DetachGroupPolicy -> Text
groupName} -> Text
groupName) (\s :: DetachGroupPolicy
s@DetachGroupPolicy' {} Text
a -> DetachGroupPolicy
s {$sel:groupName:DetachGroupPolicy' :: Text
groupName = Text
a} :: DetachGroupPolicy)

-- | The Amazon Resource Name (ARN) of the IAM policy you want to detach.
--
-- For more information about ARNs, see
-- <https://docs.aws.amazon.com/general/latest/gr/aws-arns-and-namespaces.html Amazon Resource Names (ARNs)>
-- in the /Amazon Web Services General Reference/.
detachGroupPolicy_policyArn :: Lens.Lens' DetachGroupPolicy Prelude.Text
detachGroupPolicy_policyArn :: Lens' DetachGroupPolicy Text
detachGroupPolicy_policyArn = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\DetachGroupPolicy' {Text
policyArn :: Text
$sel:policyArn:DetachGroupPolicy' :: DetachGroupPolicy -> Text
policyArn} -> Text
policyArn) (\s :: DetachGroupPolicy
s@DetachGroupPolicy' {} Text
a -> DetachGroupPolicy
s {$sel:policyArn:DetachGroupPolicy' :: Text
policyArn = Text
a} :: DetachGroupPolicy)

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

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

instance Prelude.NFData DetachGroupPolicy where
  rnf :: DetachGroupPolicy -> ()
rnf DetachGroupPolicy' {Text
policyArn :: Text
groupName :: Text
$sel:policyArn:DetachGroupPolicy' :: DetachGroupPolicy -> Text
$sel:groupName:DetachGroupPolicy' :: DetachGroupPolicy -> 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
policyArn

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

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

instance Data.ToQuery DetachGroupPolicy where
  toQuery :: DetachGroupPolicy -> QueryString
toQuery DetachGroupPolicy' {Text
policyArn :: Text
groupName :: Text
$sel:policyArn:DetachGroupPolicy' :: DetachGroupPolicy -> Text
$sel:groupName:DetachGroupPolicy' :: DetachGroupPolicy -> Text
..} =
    forall a. Monoid a => [a] -> a
Prelude.mconcat
      [ ByteString
"Action"
          forall a. ToQuery a => ByteString -> a -> QueryString
Data.=: (ByteString
"DetachGroupPolicy" :: 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
"PolicyArn" forall a. ToQuery a => ByteString -> a -> QueryString
Data.=: Text
policyArn
      ]

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

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

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