{-# 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.TagSAMLProvider
-- 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 a Security Assertion Markup Language (SAML)
-- identity provider. For more information about these providers, see
-- <https://docs.aws.amazon.com/IAM/latest/UserGuide/id_roles_providers_saml.html About SAML 2.0-based federation>
-- . 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
--     a SAML identity provider that has a specified 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/.
--
-- -   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.
module Amazonka.IAM.TagSAMLProvider
  ( -- * Creating a Request
    TagSAMLProvider (..),
    newTagSAMLProvider,

    -- * Request Lenses
    tagSAMLProvider_sAMLProviderArn,
    tagSAMLProvider_tags,

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

-- |
-- Create a value of 'TagSAMLProvider' 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:
--
-- 'sAMLProviderArn', 'tagSAMLProvider_sAMLProviderArn' - The ARN of the SAML identity provider in IAM 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', 'tagSAMLProvider_tags' - The list of tags that you want to attach to the SAML identity provider
-- in IAM. Each tag consists of a key name and an associated value.
newTagSAMLProvider ::
  -- | 'sAMLProviderArn'
  Prelude.Text ->
  TagSAMLProvider
newTagSAMLProvider :: Text -> TagSAMLProvider
newTagSAMLProvider Text
pSAMLProviderArn_ =
  TagSAMLProvider'
    { $sel:sAMLProviderArn:TagSAMLProvider' :: Text
sAMLProviderArn =
        Text
pSAMLProviderArn_,
      $sel:tags:TagSAMLProvider' :: [Tag]
tags = forall a. Monoid a => a
Prelude.mempty
    }

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

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

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

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

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

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

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

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

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