{-# 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.UntagOpenIDConnectProvider
-- 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 specified OpenID Connect
-- (OIDC)-compatible identity provider in IAM. For more information about
-- OIDC providers, see
-- <https://docs.aws.amazon.com/IAM/latest/UserGuide/id_roles_providers_oidc.html About web identity federation>.
-- 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.UntagOpenIDConnectProvider
  ( -- * Creating a Request
    UntagOpenIDConnectProvider (..),
    newUntagOpenIDConnectProvider,

    -- * Request Lenses
    untagOpenIDConnectProvider_openIDConnectProviderArn,
    untagOpenIDConnectProvider_tagKeys,

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

-- |
-- Create a value of 'UntagOpenIDConnectProvider' 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:
--
-- 'openIDConnectProviderArn', 'untagOpenIDConnectProvider_openIDConnectProviderArn' - The ARN of the OIDC provider in IAM 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', 'untagOpenIDConnectProvider_tagKeys' - A list of key names as a simple array of strings. The tags with matching
-- keys are removed from the specified OIDC provider.
newUntagOpenIDConnectProvider ::
  -- | 'openIDConnectProviderArn'
  Prelude.Text ->
  UntagOpenIDConnectProvider
newUntagOpenIDConnectProvider :: Text -> UntagOpenIDConnectProvider
newUntagOpenIDConnectProvider
  Text
pOpenIDConnectProviderArn_ =
    UntagOpenIDConnectProvider'
      { $sel:openIDConnectProviderArn:UntagOpenIDConnectProvider' :: Text
openIDConnectProviderArn =
          Text
pOpenIDConnectProviderArn_,
        $sel:tagKeys:UntagOpenIDConnectProvider' :: [Text]
tagKeys = forall a. Monoid a => a
Prelude.mempty
      }

-- | The ARN of the OIDC provider in IAM 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: _+=,.\@-
untagOpenIDConnectProvider_openIDConnectProviderArn :: Lens.Lens' UntagOpenIDConnectProvider Prelude.Text
untagOpenIDConnectProvider_openIDConnectProviderArn :: Lens' UntagOpenIDConnectProvider Text
untagOpenIDConnectProvider_openIDConnectProviderArn = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\UntagOpenIDConnectProvider' {Text
openIDConnectProviderArn :: Text
$sel:openIDConnectProviderArn:UntagOpenIDConnectProvider' :: UntagOpenIDConnectProvider -> Text
openIDConnectProviderArn} -> Text
openIDConnectProviderArn) (\s :: UntagOpenIDConnectProvider
s@UntagOpenIDConnectProvider' {} Text
a -> UntagOpenIDConnectProvider
s {$sel:openIDConnectProviderArn:UntagOpenIDConnectProvider' :: Text
openIDConnectProviderArn = Text
a} :: UntagOpenIDConnectProvider)

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

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

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

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

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

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

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

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