{-# 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.UntagServerCertificate
-- 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 server certificate. 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/.
--
-- For certificates in a Region supported by Certificate Manager (ACM), we
-- recommend that you don\'t use IAM server certificates. Instead, use ACM
-- to provision, manage, and deploy your server certificates. For more
-- information about IAM server certificates,
-- <https://docs.aws.amazon.com/IAM/latest/UserGuide/id_credentials_server-certs.html Working with server certificates>
-- in the /IAM User Guide/.
module Amazonka.IAM.UntagServerCertificate
  ( -- * Creating a Request
    UntagServerCertificate (..),
    newUntagServerCertificate,

    -- * Request Lenses
    untagServerCertificate_serverCertificateName,
    untagServerCertificate_tagKeys,

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

-- |
-- Create a value of 'UntagServerCertificate' 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:
--
-- 'serverCertificateName', 'untagServerCertificate_serverCertificateName' - The name of the IAM server certificate 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', 'untagServerCertificate_tagKeys' - A list of key names as a simple array of strings. The tags with matching
-- keys are removed from the specified IAM server certificate.
newUntagServerCertificate ::
  -- | 'serverCertificateName'
  Prelude.Text ->
  UntagServerCertificate
newUntagServerCertificate :: Text -> UntagServerCertificate
newUntagServerCertificate Text
pServerCertificateName_ =
  UntagServerCertificate'
    { $sel:serverCertificateName:UntagServerCertificate' :: Text
serverCertificateName =
        Text
pServerCertificateName_,
      $sel:tagKeys:UntagServerCertificate' :: [Text]
tagKeys = forall a. Monoid a => a
Prelude.mempty
    }

-- | The name of the IAM server certificate 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: _+=,.\@-
untagServerCertificate_serverCertificateName :: Lens.Lens' UntagServerCertificate Prelude.Text
untagServerCertificate_serverCertificateName :: Lens' UntagServerCertificate Text
untagServerCertificate_serverCertificateName = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\UntagServerCertificate' {Text
serverCertificateName :: Text
$sel:serverCertificateName:UntagServerCertificate' :: UntagServerCertificate -> Text
serverCertificateName} -> Text
serverCertificateName) (\s :: UntagServerCertificate
s@UntagServerCertificate' {} Text
a -> UntagServerCertificate
s {$sel:serverCertificateName:UntagServerCertificate' :: Text
serverCertificateName = Text
a} :: UntagServerCertificate)

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

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

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

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

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

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

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

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