{-# 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.AttachGroupPolicy
-- Copyright   : (c) 2013-2023 Brendan Hay
-- License     : Mozilla Public License, v. 2.0.
-- Maintainer  : Brendan Hay
-- Stability   : auto-generated
-- Portability : non-portable (GHC extensions)
--
-- Attaches the specified managed policy to the specified IAM group.
--
-- You use this operation to attach a managed policy to a group. To embed
-- an inline policy in a group, use PutGroupPolicy.
--
-- As a best practice, you can validate your IAM policies. To learn more,
-- see
-- <https://docs.aws.amazon.com/IAM/latest/UserGuide/access_policies_policy-validator.html Validating IAM policies>
-- in the /IAM User Guide/.
--
-- For more 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.AttachGroupPolicy
  ( -- * Creating a Request
    AttachGroupPolicy (..),
    newAttachGroupPolicy,

    -- * Request Lenses
    attachGroupPolicy_groupName,
    attachGroupPolicy_policyArn,

    -- * Destructuring the Response
    AttachGroupPolicyResponse (..),
    newAttachGroupPolicyResponse,
  )
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:/ 'newAttachGroupPolicy' smart constructor.
data AttachGroupPolicy = AttachGroupPolicy'
  { -- | The name (friendly name, not ARN) of the group to attach the policy to.
    --
    -- 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: _+=,.\@-
    AttachGroupPolicy -> Text
groupName :: Prelude.Text,
    -- | The Amazon Resource Name (ARN) of the IAM policy you want to attach.
    --
    -- 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/.
    AttachGroupPolicy -> Text
policyArn :: Prelude.Text
  }
  deriving (AttachGroupPolicy -> AttachGroupPolicy -> Bool
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: AttachGroupPolicy -> AttachGroupPolicy -> Bool
$c/= :: AttachGroupPolicy -> AttachGroupPolicy -> Bool
== :: AttachGroupPolicy -> AttachGroupPolicy -> Bool
$c== :: AttachGroupPolicy -> AttachGroupPolicy -> Bool
Prelude.Eq, ReadPrec [AttachGroupPolicy]
ReadPrec AttachGroupPolicy
Int -> ReadS AttachGroupPolicy
ReadS [AttachGroupPolicy]
forall a.
(Int -> ReadS a)
-> ReadS [a] -> ReadPrec a -> ReadPrec [a] -> Read a
readListPrec :: ReadPrec [AttachGroupPolicy]
$creadListPrec :: ReadPrec [AttachGroupPolicy]
readPrec :: ReadPrec AttachGroupPolicy
$creadPrec :: ReadPrec AttachGroupPolicy
readList :: ReadS [AttachGroupPolicy]
$creadList :: ReadS [AttachGroupPolicy]
readsPrec :: Int -> ReadS AttachGroupPolicy
$creadsPrec :: Int -> ReadS AttachGroupPolicy
Prelude.Read, Int -> AttachGroupPolicy -> ShowS
[AttachGroupPolicy] -> ShowS
AttachGroupPolicy -> String
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [AttachGroupPolicy] -> ShowS
$cshowList :: [AttachGroupPolicy] -> ShowS
show :: AttachGroupPolicy -> String
$cshow :: AttachGroupPolicy -> String
showsPrec :: Int -> AttachGroupPolicy -> ShowS
$cshowsPrec :: Int -> AttachGroupPolicy -> ShowS
Prelude.Show, forall x. Rep AttachGroupPolicy x -> AttachGroupPolicy
forall x. AttachGroupPolicy -> Rep AttachGroupPolicy x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cto :: forall x. Rep AttachGroupPolicy x -> AttachGroupPolicy
$cfrom :: forall x. AttachGroupPolicy -> Rep AttachGroupPolicy x
Prelude.Generic)

-- |
-- Create a value of 'AttachGroupPolicy' 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', 'attachGroupPolicy_groupName' - The name (friendly name, not ARN) of the group to attach the policy to.
--
-- 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', 'attachGroupPolicy_policyArn' - The Amazon Resource Name (ARN) of the IAM policy you want to attach.
--
-- 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/.
newAttachGroupPolicy ::
  -- | 'groupName'
  Prelude.Text ->
  -- | 'policyArn'
  Prelude.Text ->
  AttachGroupPolicy
newAttachGroupPolicy :: Text -> Text -> AttachGroupPolicy
newAttachGroupPolicy Text
pGroupName_ Text
pPolicyArn_ =
  AttachGroupPolicy'
    { $sel:groupName:AttachGroupPolicy' :: Text
groupName = Text
pGroupName_,
      $sel:policyArn:AttachGroupPolicy' :: Text
policyArn = Text
pPolicyArn_
    }

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

-- | The Amazon Resource Name (ARN) of the IAM policy you want to attach.
--
-- 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/.
attachGroupPolicy_policyArn :: Lens.Lens' AttachGroupPolicy Prelude.Text
attachGroupPolicy_policyArn :: Lens' AttachGroupPolicy Text
attachGroupPolicy_policyArn = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\AttachGroupPolicy' {Text
policyArn :: Text
$sel:policyArn:AttachGroupPolicy' :: AttachGroupPolicy -> Text
policyArn} -> Text
policyArn) (\s :: AttachGroupPolicy
s@AttachGroupPolicy' {} Text
a -> AttachGroupPolicy
s {$sel:policyArn:AttachGroupPolicy' :: Text
policyArn = Text
a} :: AttachGroupPolicy)

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

instance Prelude.Hashable AttachGroupPolicy where
  hashWithSalt :: Int -> AttachGroupPolicy -> Int
hashWithSalt Int
_salt AttachGroupPolicy' {Text
policyArn :: Text
groupName :: Text
$sel:policyArn:AttachGroupPolicy' :: AttachGroupPolicy -> Text
$sel:groupName:AttachGroupPolicy' :: AttachGroupPolicy -> 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 AttachGroupPolicy where
  rnf :: AttachGroupPolicy -> ()
rnf AttachGroupPolicy' {Text
policyArn :: Text
groupName :: Text
$sel:policyArn:AttachGroupPolicy' :: AttachGroupPolicy -> Text
$sel:groupName:AttachGroupPolicy' :: AttachGroupPolicy -> 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 AttachGroupPolicy where
  toHeaders :: AttachGroupPolicy -> [Header]
toHeaders = forall a b. a -> b -> a
Prelude.const forall a. Monoid a => a
Prelude.mempty

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

instance Data.ToQuery AttachGroupPolicy where
  toQuery :: AttachGroupPolicy -> QueryString
toQuery AttachGroupPolicy' {Text
policyArn :: Text
groupName :: Text
$sel:policyArn:AttachGroupPolicy' :: AttachGroupPolicy -> Text
$sel:groupName:AttachGroupPolicy' :: AttachGroupPolicy -> Text
..} =
    forall a. Monoid a => [a] -> a
Prelude.mconcat
      [ ByteString
"Action"
          forall a. ToQuery a => ByteString -> a -> QueryString
Data.=: (ByteString
"AttachGroupPolicy" :: 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:/ 'newAttachGroupPolicyResponse' smart constructor.
data AttachGroupPolicyResponse = AttachGroupPolicyResponse'
  {
  }
  deriving (AttachGroupPolicyResponse -> AttachGroupPolicyResponse -> Bool
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: AttachGroupPolicyResponse -> AttachGroupPolicyResponse -> Bool
$c/= :: AttachGroupPolicyResponse -> AttachGroupPolicyResponse -> Bool
== :: AttachGroupPolicyResponse -> AttachGroupPolicyResponse -> Bool
$c== :: AttachGroupPolicyResponse -> AttachGroupPolicyResponse -> Bool
Prelude.Eq, ReadPrec [AttachGroupPolicyResponse]
ReadPrec AttachGroupPolicyResponse
Int -> ReadS AttachGroupPolicyResponse
ReadS [AttachGroupPolicyResponse]
forall a.
(Int -> ReadS a)
-> ReadS [a] -> ReadPrec a -> ReadPrec [a] -> Read a
readListPrec :: ReadPrec [AttachGroupPolicyResponse]
$creadListPrec :: ReadPrec [AttachGroupPolicyResponse]
readPrec :: ReadPrec AttachGroupPolicyResponse
$creadPrec :: ReadPrec AttachGroupPolicyResponse
readList :: ReadS [AttachGroupPolicyResponse]
$creadList :: ReadS [AttachGroupPolicyResponse]
readsPrec :: Int -> ReadS AttachGroupPolicyResponse
$creadsPrec :: Int -> ReadS AttachGroupPolicyResponse
Prelude.Read, Int -> AttachGroupPolicyResponse -> ShowS
[AttachGroupPolicyResponse] -> ShowS
AttachGroupPolicyResponse -> String
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [AttachGroupPolicyResponse] -> ShowS
$cshowList :: [AttachGroupPolicyResponse] -> ShowS
show :: AttachGroupPolicyResponse -> String
$cshow :: AttachGroupPolicyResponse -> String
showsPrec :: Int -> AttachGroupPolicyResponse -> ShowS
$cshowsPrec :: Int -> AttachGroupPolicyResponse -> ShowS
Prelude.Show, forall x.
Rep AttachGroupPolicyResponse x -> AttachGroupPolicyResponse
forall x.
AttachGroupPolicyResponse -> Rep AttachGroupPolicyResponse x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cto :: forall x.
Rep AttachGroupPolicyResponse x -> AttachGroupPolicyResponse
$cfrom :: forall x.
AttachGroupPolicyResponse -> Rep AttachGroupPolicyResponse x
Prelude.Generic)

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

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