{-# 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.UntagInstanceProfile
-- 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 IAM instance profile. 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.UntagInstanceProfile
  ( -- * Creating a Request
    UntagInstanceProfile (..),
    newUntagInstanceProfile,

    -- * Request Lenses
    untagInstanceProfile_instanceProfileName,
    untagInstanceProfile_tagKeys,

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

-- |
-- Create a value of 'UntagInstanceProfile' 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:
--
-- 'instanceProfileName', 'untagInstanceProfile_instanceProfileName' - The name of the IAM instance profile 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', 'untagInstanceProfile_tagKeys' - A list of key names as a simple array of strings. The tags with matching
-- keys are removed from the specified instance profile.
newUntagInstanceProfile ::
  -- | 'instanceProfileName'
  Prelude.Text ->
  UntagInstanceProfile
newUntagInstanceProfile :: Text -> UntagInstanceProfile
newUntagInstanceProfile Text
pInstanceProfileName_ =
  UntagInstanceProfile'
    { $sel:instanceProfileName:UntagInstanceProfile' :: Text
instanceProfileName =
        Text
pInstanceProfileName_,
      $sel:tagKeys:UntagInstanceProfile' :: [Text]
tagKeys = forall a. Monoid a => a
Prelude.mempty
    }

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

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

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

instance Prelude.NFData UntagInstanceProfile where
  rnf :: UntagInstanceProfile -> ()
rnf UntagInstanceProfile' {[Text]
Text
tagKeys :: [Text]
instanceProfileName :: Text
$sel:tagKeys:UntagInstanceProfile' :: UntagInstanceProfile -> [Text]
$sel:instanceProfileName:UntagInstanceProfile' :: UntagInstanceProfile -> Text
..} =
    forall a. NFData a => a -> ()
Prelude.rnf Text
instanceProfileName
      seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf [Text]
tagKeys

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

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

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

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

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