{-# 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.TagUser
-- 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 user. 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 requesting user that has a specified tag attached. You can
--     also restrict access to only those resources that have a certain 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/.
--
-- -   __Cost allocation__ - Use tags to help track which individuals and
--     teams are using which Amazon Web Services resources.
--
-- -   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.
--
-- For more information about tagging, see
-- <https://docs.aws.amazon.com/IAM/latest/UserGuide/id_tags.html Tagging IAM identities>
-- in the /IAM User Guide/.
module Amazonka.IAM.TagUser
  ( -- * Creating a Request
    TagUser (..),
    newTagUser,

    -- * Request Lenses
    tagUser_userName,
    tagUser_tags,

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

-- |
-- Create a value of 'TagUser' 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:
--
-- 'userName', 'tagUser_userName' - The name of the IAM user 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', 'tagUser_tags' - The list of tags that you want to attach to the IAM user. Each tag
-- consists of a key name and an associated value.
newTagUser ::
  -- | 'userName'
  Prelude.Text ->
  TagUser
newTagUser :: Text -> TagUser
newTagUser Text
pUserName_ =
  TagUser'
    { $sel:userName:TagUser' :: Text
userName = Text
pUserName_,
      $sel:tags:TagUser' :: [Tag]
tags = forall a. Monoid a => a
Prelude.mempty
    }

-- | The name of the IAM user 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: _+=,.\@-
tagUser_userName :: Lens.Lens' TagUser Prelude.Text
tagUser_userName :: Lens' TagUser Text
tagUser_userName = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\TagUser' {Text
userName :: Text
$sel:userName:TagUser' :: TagUser -> Text
userName} -> Text
userName) (\s :: TagUser
s@TagUser' {} Text
a -> TagUser
s {$sel:userName:TagUser' :: Text
userName = Text
a} :: TagUser)

-- | The list of tags that you want to attach to the IAM user. Each tag
-- consists of a key name and an associated value.
tagUser_tags :: Lens.Lens' TagUser [Tag]
tagUser_tags :: Lens' TagUser [Tag]
tagUser_tags = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\TagUser' {[Tag]
tags :: [Tag]
$sel:tags:TagUser' :: TagUser -> [Tag]
tags} -> [Tag]
tags) (\s :: TagUser
s@TagUser' {} [Tag]
a -> TagUser
s {$sel:tags:TagUser' :: [Tag]
tags = [Tag]
a} :: TagUser) 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 TagUser where
  type AWSResponse TagUser = TagUserResponse
  request :: (Service -> Service) -> TagUser -> Request TagUser
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 TagUser
-> ClientResponse ClientBody
-> m (Either Error (ClientResponse (AWSResponse TagUser)))
response = forall (m :: * -> *) a.
MonadResource m =>
AWSResponse a
-> (ByteStringLazy -> IO ByteStringLazy)
-> Service
-> Proxy a
-> ClientResponse ClientBody
-> m (Either Error (ClientResponse (AWSResponse a)))
Response.receiveNull TagUserResponse
TagUserResponse'

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

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

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

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

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

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

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