{-# 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.TagPolicy
-- 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 one or more tags to an IAM customer managed policy. If a tag with
-- the same key name already exists, then that tag is overwritten with the
-- new value.
--
-- A tag consists of a key name and an associated value. By assigning tags
-- to your resources, you can do the following:
--
-- -   __Administrative grouping and discovery__ - Attach tags to resources
--     to aid in organization and search. For example, you could search for
--     all resources with the key name /Project/ and the value
--     /MyImportantProject/. Or search for all resources with the key name
--     /Cost Center/ and the value /41200/.
--
-- -   __Access control__ - Include tags in IAM user-based and
--     resource-based policies. You can use tags to restrict access to only
--     an IAM customer managed policy that has a specified tag attached.
--     For examples of policies that show how to use tags to control
--     access, see
--     <https://docs.aws.amazon.com/IAM/latest/UserGuide/access_tags.html Control access using IAM tags>
--     in the /IAM User Guide/.
--
-- -   If any one of the tags is invalid or if you exceed the allowed
--     maximum number of tags, then the entire request fails and the
--     resource is not created. For more information about tagging, see
--     <https://docs.aws.amazon.com/IAM/latest/UserGuide/id_tags.html Tagging IAM resources>
--     in the /IAM User Guide/.
--
-- -   Amazon Web Services always interprets the tag @Value@ as a single
--     string. If you need to store an array, you can store comma-separated
--     values in the string. However, you must interpret the value in your
--     code.
module Amazonka.IAM.TagPolicy
  ( -- * Creating a Request
    TagPolicy (..),
    newTagPolicy,

    -- * Request Lenses
    tagPolicy_policyArn,
    tagPolicy_tags,

    -- * Destructuring the Response
    TagPolicyResponse (..),
    newTagPolicyResponse,
  )
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:/ 'newTagPolicy' smart constructor.
data TagPolicy = TagPolicy'
  { -- | The ARN of the IAM customer managed policy to which you want to add
    -- tags.
    --
    -- 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: _+=,.\@-
    TagPolicy -> Text
policyArn :: Prelude.Text,
    -- | The list of tags that you want to attach to the IAM customer managed
    -- policy. Each tag consists of a key name and an associated value.
    TagPolicy -> [Tag]
tags :: [Tag]
  }
  deriving (TagPolicy -> TagPolicy -> Bool
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: TagPolicy -> TagPolicy -> Bool
$c/= :: TagPolicy -> TagPolicy -> Bool
== :: TagPolicy -> TagPolicy -> Bool
$c== :: TagPolicy -> TagPolicy -> Bool
Prelude.Eq, ReadPrec [TagPolicy]
ReadPrec TagPolicy
Int -> ReadS TagPolicy
ReadS [TagPolicy]
forall a.
(Int -> ReadS a)
-> ReadS [a] -> ReadPrec a -> ReadPrec [a] -> Read a
readListPrec :: ReadPrec [TagPolicy]
$creadListPrec :: ReadPrec [TagPolicy]
readPrec :: ReadPrec TagPolicy
$creadPrec :: ReadPrec TagPolicy
readList :: ReadS [TagPolicy]
$creadList :: ReadS [TagPolicy]
readsPrec :: Int -> ReadS TagPolicy
$creadsPrec :: Int -> ReadS TagPolicy
Prelude.Read, Int -> TagPolicy -> ShowS
[TagPolicy] -> ShowS
TagPolicy -> String
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [TagPolicy] -> ShowS
$cshowList :: [TagPolicy] -> ShowS
show :: TagPolicy -> String
$cshow :: TagPolicy -> String
showsPrec :: Int -> TagPolicy -> ShowS
$cshowsPrec :: Int -> TagPolicy -> ShowS
Prelude.Show, forall x. Rep TagPolicy x -> TagPolicy
forall x. TagPolicy -> Rep TagPolicy x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cto :: forall x. Rep TagPolicy x -> TagPolicy
$cfrom :: forall x. TagPolicy -> Rep TagPolicy x
Prelude.Generic)

-- |
-- Create a value of 'TagPolicy' 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:
--
-- 'policyArn', 'tagPolicy_policyArn' - The ARN of the IAM customer managed policy to which you want to add
-- tags.
--
-- 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: _+=,.\@-
--
-- 'tags', 'tagPolicy_tags' - The list of tags that you want to attach to the IAM customer managed
-- policy. Each tag consists of a key name and an associated value.
newTagPolicy ::
  -- | 'policyArn'
  Prelude.Text ->
  TagPolicy
newTagPolicy :: Text -> TagPolicy
newTagPolicy Text
pPolicyArn_ =
  TagPolicy'
    { $sel:policyArn:TagPolicy' :: Text
policyArn = Text
pPolicyArn_,
      $sel:tags:TagPolicy' :: [Tag]
tags = forall a. Monoid a => a
Prelude.mempty
    }

-- | The ARN of the IAM customer managed policy to which you want to add
-- tags.
--
-- 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: _+=,.\@-
tagPolicy_policyArn :: Lens.Lens' TagPolicy Prelude.Text
tagPolicy_policyArn :: Lens' TagPolicy Text
tagPolicy_policyArn = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\TagPolicy' {Text
policyArn :: Text
$sel:policyArn:TagPolicy' :: TagPolicy -> Text
policyArn} -> Text
policyArn) (\s :: TagPolicy
s@TagPolicy' {} Text
a -> TagPolicy
s {$sel:policyArn:TagPolicy' :: Text
policyArn = Text
a} :: TagPolicy)

-- | The list of tags that you want to attach to the IAM customer managed
-- policy. Each tag consists of a key name and an associated value.
tagPolicy_tags :: Lens.Lens' TagPolicy [Tag]
tagPolicy_tags :: Lens' TagPolicy [Tag]
tagPolicy_tags = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\TagPolicy' {[Tag]
tags :: [Tag]
$sel:tags:TagPolicy' :: TagPolicy -> [Tag]
tags} -> [Tag]
tags) (\s :: TagPolicy
s@TagPolicy' {} [Tag]
a -> TagPolicy
s {$sel:tags:TagPolicy' :: [Tag]
tags = [Tag]
a} :: TagPolicy) forall b c a. (b -> c) -> (a -> b) -> a -> c
Prelude.. forall s t a b. (Coercible s a, Coercible t b) => Iso s t a b
Lens.coerced

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

instance Prelude.Hashable TagPolicy where
  hashWithSalt :: Int -> TagPolicy -> Int
hashWithSalt Int
_salt TagPolicy' {[Tag]
Text
tags :: [Tag]
policyArn :: Text
$sel:tags:TagPolicy' :: TagPolicy -> [Tag]
$sel:policyArn:TagPolicy' :: TagPolicy -> Text
..} =
    Int
_salt
      forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Text
policyArn
      forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` [Tag]
tags

instance Prelude.NFData TagPolicy where
  rnf :: TagPolicy -> ()
rnf TagPolicy' {[Tag]
Text
tags :: [Tag]
policyArn :: Text
$sel:tags:TagPolicy' :: TagPolicy -> [Tag]
$sel:policyArn:TagPolicy' :: TagPolicy -> Text
..} =
    forall a. NFData a => a -> ()
Prelude.rnf Text
policyArn
      seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf [Tag]
tags

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

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

instance Data.ToQuery TagPolicy where
  toQuery :: TagPolicy -> QueryString
toQuery TagPolicy' {[Tag]
Text
tags :: [Tag]
policyArn :: Text
$sel:tags:TagPolicy' :: TagPolicy -> [Tag]
$sel:policyArn:TagPolicy' :: TagPolicy -> Text
..} =
    forall a. Monoid a => [a] -> a
Prelude.mconcat
      [ ByteString
"Action"
          forall a. ToQuery a => ByteString -> a -> QueryString
Data.=: (ByteString
"TagPolicy" :: Prelude.ByteString),
        ByteString
"Version"
          forall a. ToQuery a => ByteString -> a -> QueryString
Data.=: (ByteString
"2010-05-08" :: Prelude.ByteString),
        ByteString
"PolicyArn" forall a. ToQuery a => ByteString -> a -> QueryString
Data.=: Text
policyArn,
        ByteString
"Tags" forall a. ToQuery a => ByteString -> a -> QueryString
Data.=: forall a.
(IsList a, ToQuery (Item a)) =>
ByteString -> a -> QueryString
Data.toQueryList ByteString
"member" [Tag]
tags
      ]

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

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

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