{-# 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.UntagPolicy
-- 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 customer managed policy. 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.UntagPolicy
  ( -- * Creating a Request
    UntagPolicy (..),
    newUntagPolicy,

    -- * Request Lenses
    untagPolicy_policyArn,
    untagPolicy_tagKeys,

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

-- |
-- Create a value of 'UntagPolicy' 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', 'untagPolicy_policyArn' - The ARN of the IAM customer managed policy 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', 'untagPolicy_tagKeys' - A list of key names as a simple array of strings. The tags with matching
-- keys are removed from the specified policy.
newUntagPolicy ::
  -- | 'policyArn'
  Prelude.Text ->
  UntagPolicy
newUntagPolicy :: Text -> UntagPolicy
newUntagPolicy Text
pPolicyArn_ =
  UntagPolicy'
    { $sel:policyArn:UntagPolicy' :: Text
policyArn = Text
pPolicyArn_,
      $sel:tagKeys:UntagPolicy' :: [Text]
tagKeys = forall a. Monoid a => a
Prelude.mempty
    }

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

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

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

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

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

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

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

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

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