{-# 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.PutGroupPolicy
-- Copyright   : (c) 2013-2023 Brendan Hay
-- License     : Mozilla Public License, v. 2.0.
-- Maintainer  : Brendan Hay
-- Stability   : auto-generated
-- Portability : non-portable (GHC extensions)
--
-- Adds or updates an inline policy document that is embedded in the
-- specified IAM group.
--
-- A user can also have managed policies attached to it. To attach a
-- managed policy to a group, use AttachGroupPolicy. To create a new
-- managed policy, use CreatePolicy. 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/.
--
-- For information about the maximum number of inline policies that you can
-- embed in a group, see
-- <https://docs.aws.amazon.com/IAM/latest/UserGuide/reference_iam-quotas.html IAM and STS quotas>
-- in the /IAM User Guide/.
--
-- Because policy documents can be large, you should use POST rather than
-- GET when calling @PutGroupPolicy@. For general information about using
-- the Query API with IAM, see
-- <https://docs.aws.amazon.com/IAM/latest/UserGuide/IAM_UsingQueryAPI.html Making query requests>
-- in the /IAM User Guide/.
module Amazonka.IAM.PutGroupPolicy
  ( -- * Creating a Request
    PutGroupPolicy (..),
    newPutGroupPolicy,

    -- * Request Lenses
    putGroupPolicy_groupName,
    putGroupPolicy_policyName,
    putGroupPolicy_policyDocument,

    -- * Destructuring the Response
    PutGroupPolicyResponse (..),
    newPutGroupPolicyResponse,
  )
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:/ 'newPutGroupPolicy' smart constructor.
data PutGroupPolicy = PutGroupPolicy'
  { -- | The name of the group to associate the policy with.
    --
    -- 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: _+=,.\@-.
    PutGroupPolicy -> Text
groupName :: Prelude.Text,
    -- | The name of the policy document.
    --
    -- 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: _+=,.\@-
    PutGroupPolicy -> Text
policyName :: Prelude.Text,
    -- | The policy document.
    --
    -- You must provide policies in JSON format in IAM. However, for
    -- CloudFormation templates formatted in YAML, you can provide the policy
    -- in JSON or YAML format. CloudFormation always converts a YAML policy to
    -- JSON format before submitting it to = IAM.
    --
    -- The <http://wikipedia.org/wiki/regex regex pattern> used to validate
    -- this parameter is a string of characters consisting of the following:
    --
    -- -   Any printable ASCII character ranging from the space character
    --     (@\\u0020@) through the end of the ASCII character range
    --
    -- -   The printable characters in the Basic Latin and Latin-1 Supplement
    --     character set (through @\\u00FF@)
    --
    -- -   The special characters tab (@\\u0009@), line feed (@\\u000A@), and
    --     carriage return (@\\u000D@)
    PutGroupPolicy -> Text
policyDocument :: Prelude.Text
  }
  deriving (PutGroupPolicy -> PutGroupPolicy -> Bool
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: PutGroupPolicy -> PutGroupPolicy -> Bool
$c/= :: PutGroupPolicy -> PutGroupPolicy -> Bool
== :: PutGroupPolicy -> PutGroupPolicy -> Bool
$c== :: PutGroupPolicy -> PutGroupPolicy -> Bool
Prelude.Eq, ReadPrec [PutGroupPolicy]
ReadPrec PutGroupPolicy
Int -> ReadS PutGroupPolicy
ReadS [PutGroupPolicy]
forall a.
(Int -> ReadS a)
-> ReadS [a] -> ReadPrec a -> ReadPrec [a] -> Read a
readListPrec :: ReadPrec [PutGroupPolicy]
$creadListPrec :: ReadPrec [PutGroupPolicy]
readPrec :: ReadPrec PutGroupPolicy
$creadPrec :: ReadPrec PutGroupPolicy
readList :: ReadS [PutGroupPolicy]
$creadList :: ReadS [PutGroupPolicy]
readsPrec :: Int -> ReadS PutGroupPolicy
$creadsPrec :: Int -> ReadS PutGroupPolicy
Prelude.Read, Int -> PutGroupPolicy -> ShowS
[PutGroupPolicy] -> ShowS
PutGroupPolicy -> String
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [PutGroupPolicy] -> ShowS
$cshowList :: [PutGroupPolicy] -> ShowS
show :: PutGroupPolicy -> String
$cshow :: PutGroupPolicy -> String
showsPrec :: Int -> PutGroupPolicy -> ShowS
$cshowsPrec :: Int -> PutGroupPolicy -> ShowS
Prelude.Show, forall x. Rep PutGroupPolicy x -> PutGroupPolicy
forall x. PutGroupPolicy -> Rep PutGroupPolicy x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cto :: forall x. Rep PutGroupPolicy x -> PutGroupPolicy
$cfrom :: forall x. PutGroupPolicy -> Rep PutGroupPolicy x
Prelude.Generic)

-- |
-- Create a value of 'PutGroupPolicy' 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', 'putGroupPolicy_groupName' - The name of the group to associate the policy with.
--
-- 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', 'putGroupPolicy_policyName' - The name of the policy document.
--
-- 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: _+=,.\@-
--
-- 'policyDocument', 'putGroupPolicy_policyDocument' - The policy document.
--
-- You must provide policies in JSON format in IAM. However, for
-- CloudFormation templates formatted in YAML, you can provide the policy
-- in JSON or YAML format. CloudFormation always converts a YAML policy to
-- JSON format before submitting it to = IAM.
--
-- The <http://wikipedia.org/wiki/regex regex pattern> used to validate
-- this parameter is a string of characters consisting of the following:
--
-- -   Any printable ASCII character ranging from the space character
--     (@\\u0020@) through the end of the ASCII character range
--
-- -   The printable characters in the Basic Latin and Latin-1 Supplement
--     character set (through @\\u00FF@)
--
-- -   The special characters tab (@\\u0009@), line feed (@\\u000A@), and
--     carriage return (@\\u000D@)
newPutGroupPolicy ::
  -- | 'groupName'
  Prelude.Text ->
  -- | 'policyName'
  Prelude.Text ->
  -- | 'policyDocument'
  Prelude.Text ->
  PutGroupPolicy
newPutGroupPolicy :: Text -> Text -> Text -> PutGroupPolicy
newPutGroupPolicy
  Text
pGroupName_
  Text
pPolicyName_
  Text
pPolicyDocument_ =
    PutGroupPolicy'
      { $sel:groupName:PutGroupPolicy' :: Text
groupName = Text
pGroupName_,
        $sel:policyName:PutGroupPolicy' :: Text
policyName = Text
pPolicyName_,
        $sel:policyDocument:PutGroupPolicy' :: Text
policyDocument = Text
pPolicyDocument_
      }

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

-- | The name of the policy document.
--
-- 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: _+=,.\@-
putGroupPolicy_policyName :: Lens.Lens' PutGroupPolicy Prelude.Text
putGroupPolicy_policyName :: Lens' PutGroupPolicy Text
putGroupPolicy_policyName = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\PutGroupPolicy' {Text
policyName :: Text
$sel:policyName:PutGroupPolicy' :: PutGroupPolicy -> Text
policyName} -> Text
policyName) (\s :: PutGroupPolicy
s@PutGroupPolicy' {} Text
a -> PutGroupPolicy
s {$sel:policyName:PutGroupPolicy' :: Text
policyName = Text
a} :: PutGroupPolicy)

-- | The policy document.
--
-- You must provide policies in JSON format in IAM. However, for
-- CloudFormation templates formatted in YAML, you can provide the policy
-- in JSON or YAML format. CloudFormation always converts a YAML policy to
-- JSON format before submitting it to = IAM.
--
-- The <http://wikipedia.org/wiki/regex regex pattern> used to validate
-- this parameter is a string of characters consisting of the following:
--
-- -   Any printable ASCII character ranging from the space character
--     (@\\u0020@) through the end of the ASCII character range
--
-- -   The printable characters in the Basic Latin and Latin-1 Supplement
--     character set (through @\\u00FF@)
--
-- -   The special characters tab (@\\u0009@), line feed (@\\u000A@), and
--     carriage return (@\\u000D@)
putGroupPolicy_policyDocument :: Lens.Lens' PutGroupPolicy Prelude.Text
putGroupPolicy_policyDocument :: Lens' PutGroupPolicy Text
putGroupPolicy_policyDocument = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\PutGroupPolicy' {Text
policyDocument :: Text
$sel:policyDocument:PutGroupPolicy' :: PutGroupPolicy -> Text
policyDocument} -> Text
policyDocument) (\s :: PutGroupPolicy
s@PutGroupPolicy' {} Text
a -> PutGroupPolicy
s {$sel:policyDocument:PutGroupPolicy' :: Text
policyDocument = Text
a} :: PutGroupPolicy)

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

instance Prelude.Hashable PutGroupPolicy where
  hashWithSalt :: Int -> PutGroupPolicy -> Int
hashWithSalt Int
_salt PutGroupPolicy' {Text
policyDocument :: Text
policyName :: Text
groupName :: Text
$sel:policyDocument:PutGroupPolicy' :: PutGroupPolicy -> Text
$sel:policyName:PutGroupPolicy' :: PutGroupPolicy -> Text
$sel:groupName:PutGroupPolicy' :: PutGroupPolicy -> 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
      forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Text
policyDocument

instance Prelude.NFData PutGroupPolicy where
  rnf :: PutGroupPolicy -> ()
rnf PutGroupPolicy' {Text
policyDocument :: Text
policyName :: Text
groupName :: Text
$sel:policyDocument:PutGroupPolicy' :: PutGroupPolicy -> Text
$sel:policyName:PutGroupPolicy' :: PutGroupPolicy -> Text
$sel:groupName:PutGroupPolicy' :: PutGroupPolicy -> 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
      seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf Text
policyDocument

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

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

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

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

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

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