{-# 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.UntagUser
-- 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 tags from the user. 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/.
module Amazonka.IAM.UntagUser
  ( -- * Creating a Request
    UntagUser (..),
    newUntagUser,

    -- * Request Lenses
    untagUser_userName,
    untagUser_tagKeys,

    -- * Destructuring the Response
    UntagUserResponse (..),
    newUntagUserResponse,
  )
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:/ 'newUntagUser' smart constructor.
data UntagUser = UntagUser'
  { -- | The name of the IAM user from which you want to remove 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: _+=,.\@-
    UntagUser -> Text
userName :: Prelude.Text,
    -- | A list of key names as a simple array of strings. The tags with matching
    -- keys are removed from the specified user.
    UntagUser -> [Text]
tagKeys :: [Prelude.Text]
  }
  deriving (UntagUser -> UntagUser -> Bool
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: UntagUser -> UntagUser -> Bool
$c/= :: UntagUser -> UntagUser -> Bool
== :: UntagUser -> UntagUser -> Bool
$c== :: UntagUser -> UntagUser -> Bool
Prelude.Eq, ReadPrec [UntagUser]
ReadPrec UntagUser
Int -> ReadS UntagUser
ReadS [UntagUser]
forall a.
(Int -> ReadS a)
-> ReadS [a] -> ReadPrec a -> ReadPrec [a] -> Read a
readListPrec :: ReadPrec [UntagUser]
$creadListPrec :: ReadPrec [UntagUser]
readPrec :: ReadPrec UntagUser
$creadPrec :: ReadPrec UntagUser
readList :: ReadS [UntagUser]
$creadList :: ReadS [UntagUser]
readsPrec :: Int -> ReadS UntagUser
$creadsPrec :: Int -> ReadS UntagUser
Prelude.Read, Int -> UntagUser -> ShowS
[UntagUser] -> ShowS
UntagUser -> String
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [UntagUser] -> ShowS
$cshowList :: [UntagUser] -> ShowS
show :: UntagUser -> String
$cshow :: UntagUser -> String
showsPrec :: Int -> UntagUser -> ShowS
$cshowsPrec :: Int -> UntagUser -> ShowS
Prelude.Show, forall x. Rep UntagUser x -> UntagUser
forall x. UntagUser -> Rep UntagUser x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cto :: forall x. Rep UntagUser x -> UntagUser
$cfrom :: forall x. UntagUser -> Rep UntagUser x
Prelude.Generic)

-- |
-- Create a value of 'UntagUser' 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', 'untagUser_userName' - The name of the IAM user from which you want to remove 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: _+=,.\@-
--
-- 'tagKeys', 'untagUser_tagKeys' - A list of key names as a simple array of strings. The tags with matching
-- keys are removed from the specified user.
newUntagUser ::
  -- | 'userName'
  Prelude.Text ->
  UntagUser
newUntagUser :: Text -> UntagUser
newUntagUser Text
pUserName_ =
  UntagUser'
    { $sel:userName:UntagUser' :: Text
userName = Text
pUserName_,
      $sel:tagKeys:UntagUser' :: [Text]
tagKeys = forall a. Monoid a => a
Prelude.mempty
    }

-- | The name of the IAM user from which you want to remove 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: _+=,.\@-
untagUser_userName :: Lens.Lens' UntagUser Prelude.Text
untagUser_userName :: Lens' UntagUser Text
untagUser_userName = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\UntagUser' {Text
userName :: Text
$sel:userName:UntagUser' :: UntagUser -> Text
userName} -> Text
userName) (\s :: UntagUser
s@UntagUser' {} Text
a -> UntagUser
s {$sel:userName:UntagUser' :: Text
userName = Text
a} :: UntagUser)

-- | A list of key names as a simple array of strings. The tags with matching
-- keys are removed from the specified user.
untagUser_tagKeys :: Lens.Lens' UntagUser [Prelude.Text]
untagUser_tagKeys :: Lens' UntagUser [Text]
untagUser_tagKeys = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\UntagUser' {[Text]
tagKeys :: [Text]
$sel:tagKeys:UntagUser' :: UntagUser -> [Text]
tagKeys} -> [Text]
tagKeys) (\s :: UntagUser
s@UntagUser' {} [Text]
a -> UntagUser
s {$sel:tagKeys:UntagUser' :: [Text]
tagKeys = [Text]
a} :: UntagUser) 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 UntagUser where
  type AWSResponse UntagUser = UntagUserResponse
  request :: (Service -> Service) -> UntagUser -> Request UntagUser
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 UntagUser
-> ClientResponse ClientBody
-> m (Either Error (ClientResponse (AWSResponse UntagUser)))
response = forall (m :: * -> *) a.
MonadResource m =>
AWSResponse a
-> (ByteStringLazy -> IO ByteStringLazy)
-> Service
-> Proxy a
-> ClientResponse ClientBody
-> m (Either Error (ClientResponse (AWSResponse a)))
Response.receiveNull UntagUserResponse
UntagUserResponse'

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

instance Prelude.NFData UntagUser where
  rnf :: UntagUser -> ()
rnf UntagUser' {[Text]
Text
tagKeys :: [Text]
userName :: Text
$sel:tagKeys:UntagUser' :: UntagUser -> [Text]
$sel:userName:UntagUser' :: UntagUser -> 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 [Text]
tagKeys

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

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

instance Data.ToQuery UntagUser where
  toQuery :: UntagUser -> QueryString
toQuery UntagUser' {[Text]
Text
tagKeys :: [Text]
userName :: Text
$sel:tagKeys:UntagUser' :: UntagUser -> [Text]
$sel:userName:UntagUser' :: UntagUser -> Text
..} =
    forall a. Monoid a => [a] -> a
Prelude.mconcat
      [ ByteString
"Action"
          forall a. ToQuery a => ByteString -> a -> QueryString
Data.=: (ByteString
"UntagUser" :: 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
"TagKeys" forall a. ToQuery a => ByteString -> a -> QueryString
Data.=: forall a.
(IsList a, ToQuery (Item a)) =>
ByteString -> a -> QueryString
Data.toQueryList ByteString
"member" [Text]
tagKeys
      ]

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

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

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