{-# 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.UploadSigningCertificate
-- Copyright   : (c) 2013-2023 Brendan Hay
-- License     : Mozilla Public License, v. 2.0.
-- Maintainer  : Brendan Hay
-- Stability   : auto-generated
-- Portability : non-portable (GHC extensions)
--
-- Uploads an X.509 signing certificate and associates it with the
-- specified IAM user. Some Amazon Web Services services require you to use
-- certificates to validate requests that are signed with a corresponding
-- private key. When you upload the certificate, its default status is
-- @Active@.
--
-- For information about when you would use an X.509 signing certificate,
-- see
-- <https://docs.aws.amazon.com/IAM/latest/UserGuide/id_credentials_server-certs.html Managing server certificates in IAM>
-- in the /IAM User Guide/.
--
-- If the @UserName@ is not specified, the IAM user name is determined
-- implicitly based on the Amazon Web Services access key ID used to sign
-- the request. This operation works for access keys under the Amazon Web
-- Services account. Consequently, you can use this operation to manage
-- Amazon Web Services account root user credentials even if the Amazon Web
-- Services account has no associated users.
--
-- Because the body of an X.509 certificate can be large, you should use
-- POST rather than GET when calling @UploadSigningCertificate@. For
-- information about setting up signatures and authorization through the
-- API, see
-- <https://docs.aws.amazon.com/general/latest/gr/signing_aws_api_requests.html Signing Amazon Web Services API requests>
-- in the /Amazon Web Services General Reference/. For general information
-- about using the Query API with IAM, see
-- <https://docs.aws.amazon.com/IAM/latest/UserGuide/IAM_UsingQueryAPI.html Making query requests>
-- in the /IAM User Guide/.
module Amazonka.IAM.UploadSigningCertificate
  ( -- * Creating a Request
    UploadSigningCertificate (..),
    newUploadSigningCertificate,

    -- * Request Lenses
    uploadSigningCertificate_userName,
    uploadSigningCertificate_certificateBody,

    -- * Destructuring the Response
    UploadSigningCertificateResponse (..),
    newUploadSigningCertificateResponse,

    -- * Response Lenses
    uploadSigningCertificateResponse_httpStatus,
    uploadSigningCertificateResponse_certificate,
  )
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:/ 'newUploadSigningCertificate' smart constructor.
data UploadSigningCertificate = UploadSigningCertificate'
  { -- | The name of the user the signing certificate is for.
    --
    -- 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: _+=,.\@-
    UploadSigningCertificate -> Maybe Text
userName :: Prelude.Maybe Prelude.Text,
    -- | The contents of the signing certificate.
    --
    -- The <http://wikipedia.org/wiki/regex regex pattern> used to validate
    -- this parameter is a string of characters consisting of the following:
    --
    -- -   Any printable ASCII character ranging from the space character
    --     (@\\u0020@) through the end of the ASCII character range
    --
    -- -   The printable characters in the Basic Latin and Latin-1 Supplement
    --     character set (through @\\u00FF@)
    --
    -- -   The special characters tab (@\\u0009@), line feed (@\\u000A@), and
    --     carriage return (@\\u000D@)
    UploadSigningCertificate -> Text
certificateBody :: Prelude.Text
  }
  deriving (UploadSigningCertificate -> UploadSigningCertificate -> Bool
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: UploadSigningCertificate -> UploadSigningCertificate -> Bool
$c/= :: UploadSigningCertificate -> UploadSigningCertificate -> Bool
== :: UploadSigningCertificate -> UploadSigningCertificate -> Bool
$c== :: UploadSigningCertificate -> UploadSigningCertificate -> Bool
Prelude.Eq, ReadPrec [UploadSigningCertificate]
ReadPrec UploadSigningCertificate
Int -> ReadS UploadSigningCertificate
ReadS [UploadSigningCertificate]
forall a.
(Int -> ReadS a)
-> ReadS [a] -> ReadPrec a -> ReadPrec [a] -> Read a
readListPrec :: ReadPrec [UploadSigningCertificate]
$creadListPrec :: ReadPrec [UploadSigningCertificate]
readPrec :: ReadPrec UploadSigningCertificate
$creadPrec :: ReadPrec UploadSigningCertificate
readList :: ReadS [UploadSigningCertificate]
$creadList :: ReadS [UploadSigningCertificate]
readsPrec :: Int -> ReadS UploadSigningCertificate
$creadsPrec :: Int -> ReadS UploadSigningCertificate
Prelude.Read, Int -> UploadSigningCertificate -> ShowS
[UploadSigningCertificate] -> ShowS
UploadSigningCertificate -> String
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [UploadSigningCertificate] -> ShowS
$cshowList :: [UploadSigningCertificate] -> ShowS
show :: UploadSigningCertificate -> String
$cshow :: UploadSigningCertificate -> String
showsPrec :: Int -> UploadSigningCertificate -> ShowS
$cshowsPrec :: Int -> UploadSigningCertificate -> ShowS
Prelude.Show, forall x.
Rep UploadSigningCertificate x -> UploadSigningCertificate
forall x.
UploadSigningCertificate -> Rep UploadSigningCertificate x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cto :: forall x.
Rep UploadSigningCertificate x -> UploadSigningCertificate
$cfrom :: forall x.
UploadSigningCertificate -> Rep UploadSigningCertificate x
Prelude.Generic)

-- |
-- Create a value of 'UploadSigningCertificate' 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:
--
-- 'userName', 'uploadSigningCertificate_userName' - The name of the user the signing certificate is for.
--
-- 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: _+=,.\@-
--
-- 'certificateBody', 'uploadSigningCertificate_certificateBody' - The contents of the signing certificate.
--
-- The <http://wikipedia.org/wiki/regex regex pattern> used to validate
-- this parameter is a string of characters consisting of the following:
--
-- -   Any printable ASCII character ranging from the space character
--     (@\\u0020@) through the end of the ASCII character range
--
-- -   The printable characters in the Basic Latin and Latin-1 Supplement
--     character set (through @\\u00FF@)
--
-- -   The special characters tab (@\\u0009@), line feed (@\\u000A@), and
--     carriage return (@\\u000D@)
newUploadSigningCertificate ::
  -- | 'certificateBody'
  Prelude.Text ->
  UploadSigningCertificate
newUploadSigningCertificate :: Text -> UploadSigningCertificate
newUploadSigningCertificate Text
pCertificateBody_ =
  UploadSigningCertificate'
    { $sel:userName:UploadSigningCertificate' :: Maybe Text
userName =
        forall a. Maybe a
Prelude.Nothing,
      $sel:certificateBody:UploadSigningCertificate' :: Text
certificateBody = Text
pCertificateBody_
    }

-- | The name of the user the signing certificate is for.
--
-- 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: _+=,.\@-
uploadSigningCertificate_userName :: Lens.Lens' UploadSigningCertificate (Prelude.Maybe Prelude.Text)
uploadSigningCertificate_userName :: Lens' UploadSigningCertificate (Maybe Text)
uploadSigningCertificate_userName = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\UploadSigningCertificate' {Maybe Text
userName :: Maybe Text
$sel:userName:UploadSigningCertificate' :: UploadSigningCertificate -> Maybe Text
userName} -> Maybe Text
userName) (\s :: UploadSigningCertificate
s@UploadSigningCertificate' {} Maybe Text
a -> UploadSigningCertificate
s {$sel:userName:UploadSigningCertificate' :: Maybe Text
userName = Maybe Text
a} :: UploadSigningCertificate)

-- | The contents of the signing certificate.
--
-- The <http://wikipedia.org/wiki/regex regex pattern> used to validate
-- this parameter is a string of characters consisting of the following:
--
-- -   Any printable ASCII character ranging from the space character
--     (@\\u0020@) through the end of the ASCII character range
--
-- -   The printable characters in the Basic Latin and Latin-1 Supplement
--     character set (through @\\u00FF@)
--
-- -   The special characters tab (@\\u0009@), line feed (@\\u000A@), and
--     carriage return (@\\u000D@)
uploadSigningCertificate_certificateBody :: Lens.Lens' UploadSigningCertificate Prelude.Text
uploadSigningCertificate_certificateBody :: Lens' UploadSigningCertificate Text
uploadSigningCertificate_certificateBody = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\UploadSigningCertificate' {Text
certificateBody :: Text
$sel:certificateBody:UploadSigningCertificate' :: UploadSigningCertificate -> Text
certificateBody} -> Text
certificateBody) (\s :: UploadSigningCertificate
s@UploadSigningCertificate' {} Text
a -> UploadSigningCertificate
s {$sel:certificateBody:UploadSigningCertificate' :: Text
certificateBody = Text
a} :: UploadSigningCertificate)

instance Core.AWSRequest UploadSigningCertificate where
  type
    AWSResponse UploadSigningCertificate =
      UploadSigningCertificateResponse
  request :: (Service -> Service)
-> UploadSigningCertificate -> Request UploadSigningCertificate
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 UploadSigningCertificate
-> ClientResponse ClientBody
-> m (Either
        Error (ClientResponse (AWSResponse UploadSigningCertificate)))
response =
    forall (m :: * -> *) a.
MonadResource m =>
Text
-> (Int
    -> ResponseHeaders -> [Node] -> Either String (AWSResponse a))
-> (ByteStringLazy -> IO ByteStringLazy)
-> Service
-> Proxy a
-> ClientResponse ClientBody
-> m (Either Error (ClientResponse (AWSResponse a)))
Response.receiveXMLWrapper
      Text
"UploadSigningCertificateResult"
      ( \Int
s ResponseHeaders
h [Node]
x ->
          Int -> SigningCertificate -> UploadSigningCertificateResponse
UploadSigningCertificateResponse'
            forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
Prelude.<$> (forall (f :: * -> *) a. Applicative f => a -> f a
Prelude.pure (forall a. Enum a => a -> Int
Prelude.fromEnum Int
s))
            forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
Prelude.<*> ([Node]
x forall a. FromXML a => [Node] -> Text -> Either String a
Data..@ Text
"Certificate")
      )

instance Prelude.Hashable UploadSigningCertificate where
  hashWithSalt :: Int -> UploadSigningCertificate -> Int
hashWithSalt Int
_salt UploadSigningCertificate' {Maybe Text
Text
certificateBody :: Text
userName :: Maybe Text
$sel:certificateBody:UploadSigningCertificate' :: UploadSigningCertificate -> Text
$sel:userName:UploadSigningCertificate' :: UploadSigningCertificate -> Maybe Text
..} =
    Int
_salt
      forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Maybe Text
userName
      forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Text
certificateBody

instance Prelude.NFData UploadSigningCertificate where
  rnf :: UploadSigningCertificate -> ()
rnf UploadSigningCertificate' {Maybe Text
Text
certificateBody :: Text
userName :: Maybe Text
$sel:certificateBody:UploadSigningCertificate' :: UploadSigningCertificate -> Text
$sel:userName:UploadSigningCertificate' :: UploadSigningCertificate -> Maybe Text
..} =
    forall a. NFData a => a -> ()
Prelude.rnf Maybe Text
userName
      seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf Text
certificateBody

instance Data.ToHeaders UploadSigningCertificate where
  toHeaders :: UploadSigningCertificate -> ResponseHeaders
toHeaders = forall a b. a -> b -> a
Prelude.const forall a. Monoid a => a
Prelude.mempty

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

instance Data.ToQuery UploadSigningCertificate where
  toQuery :: UploadSigningCertificate -> QueryString
toQuery UploadSigningCertificate' {Maybe Text
Text
certificateBody :: Text
userName :: Maybe Text
$sel:certificateBody:UploadSigningCertificate' :: UploadSigningCertificate -> Text
$sel:userName:UploadSigningCertificate' :: UploadSigningCertificate -> Maybe Text
..} =
    forall a. Monoid a => [a] -> a
Prelude.mconcat
      [ ByteString
"Action"
          forall a. ToQuery a => ByteString -> a -> QueryString
Data.=: (ByteString
"UploadSigningCertificate" :: Prelude.ByteString),
        ByteString
"Version"
          forall a. ToQuery a => ByteString -> a -> QueryString
Data.=: (ByteString
"2010-05-08" :: Prelude.ByteString),
        ByteString
"UserName" forall a. ToQuery a => ByteString -> a -> QueryString
Data.=: Maybe Text
userName,
        ByteString
"CertificateBody" forall a. ToQuery a => ByteString -> a -> QueryString
Data.=: Text
certificateBody
      ]

-- | Contains the response to a successful UploadSigningCertificate request.
--
-- /See:/ 'newUploadSigningCertificateResponse' smart constructor.
data UploadSigningCertificateResponse = UploadSigningCertificateResponse'
  { -- | The response's http status code.
    UploadSigningCertificateResponse -> Int
httpStatus :: Prelude.Int,
    -- | Information about the certificate.
    UploadSigningCertificateResponse -> SigningCertificate
certificate :: SigningCertificate
  }
  deriving (UploadSigningCertificateResponse
-> UploadSigningCertificateResponse -> Bool
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: UploadSigningCertificateResponse
-> UploadSigningCertificateResponse -> Bool
$c/= :: UploadSigningCertificateResponse
-> UploadSigningCertificateResponse -> Bool
== :: UploadSigningCertificateResponse
-> UploadSigningCertificateResponse -> Bool
$c== :: UploadSigningCertificateResponse
-> UploadSigningCertificateResponse -> Bool
Prelude.Eq, ReadPrec [UploadSigningCertificateResponse]
ReadPrec UploadSigningCertificateResponse
Int -> ReadS UploadSigningCertificateResponse
ReadS [UploadSigningCertificateResponse]
forall a.
(Int -> ReadS a)
-> ReadS [a] -> ReadPrec a -> ReadPrec [a] -> Read a
readListPrec :: ReadPrec [UploadSigningCertificateResponse]
$creadListPrec :: ReadPrec [UploadSigningCertificateResponse]
readPrec :: ReadPrec UploadSigningCertificateResponse
$creadPrec :: ReadPrec UploadSigningCertificateResponse
readList :: ReadS [UploadSigningCertificateResponse]
$creadList :: ReadS [UploadSigningCertificateResponse]
readsPrec :: Int -> ReadS UploadSigningCertificateResponse
$creadsPrec :: Int -> ReadS UploadSigningCertificateResponse
Prelude.Read, Int -> UploadSigningCertificateResponse -> ShowS
[UploadSigningCertificateResponse] -> ShowS
UploadSigningCertificateResponse -> String
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [UploadSigningCertificateResponse] -> ShowS
$cshowList :: [UploadSigningCertificateResponse] -> ShowS
show :: UploadSigningCertificateResponse -> String
$cshow :: UploadSigningCertificateResponse -> String
showsPrec :: Int -> UploadSigningCertificateResponse -> ShowS
$cshowsPrec :: Int -> UploadSigningCertificateResponse -> ShowS
Prelude.Show, forall x.
Rep UploadSigningCertificateResponse x
-> UploadSigningCertificateResponse
forall x.
UploadSigningCertificateResponse
-> Rep UploadSigningCertificateResponse x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cto :: forall x.
Rep UploadSigningCertificateResponse x
-> UploadSigningCertificateResponse
$cfrom :: forall x.
UploadSigningCertificateResponse
-> Rep UploadSigningCertificateResponse x
Prelude.Generic)

-- |
-- Create a value of 'UploadSigningCertificateResponse' 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:
--
-- 'httpStatus', 'uploadSigningCertificateResponse_httpStatus' - The response's http status code.
--
-- 'certificate', 'uploadSigningCertificateResponse_certificate' - Information about the certificate.
newUploadSigningCertificateResponse ::
  -- | 'httpStatus'
  Prelude.Int ->
  -- | 'certificate'
  SigningCertificate ->
  UploadSigningCertificateResponse
newUploadSigningCertificateResponse :: Int -> SigningCertificate -> UploadSigningCertificateResponse
newUploadSigningCertificateResponse
  Int
pHttpStatus_
  SigningCertificate
pCertificate_ =
    UploadSigningCertificateResponse'
      { $sel:httpStatus:UploadSigningCertificateResponse' :: Int
httpStatus =
          Int
pHttpStatus_,
        $sel:certificate:UploadSigningCertificateResponse' :: SigningCertificate
certificate = SigningCertificate
pCertificate_
      }

-- | The response's http status code.
uploadSigningCertificateResponse_httpStatus :: Lens.Lens' UploadSigningCertificateResponse Prelude.Int
uploadSigningCertificateResponse_httpStatus :: Lens' UploadSigningCertificateResponse Int
uploadSigningCertificateResponse_httpStatus = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\UploadSigningCertificateResponse' {Int
httpStatus :: Int
$sel:httpStatus:UploadSigningCertificateResponse' :: UploadSigningCertificateResponse -> Int
httpStatus} -> Int
httpStatus) (\s :: UploadSigningCertificateResponse
s@UploadSigningCertificateResponse' {} Int
a -> UploadSigningCertificateResponse
s {$sel:httpStatus:UploadSigningCertificateResponse' :: Int
httpStatus = Int
a} :: UploadSigningCertificateResponse)

-- | Information about the certificate.
uploadSigningCertificateResponse_certificate :: Lens.Lens' UploadSigningCertificateResponse SigningCertificate
uploadSigningCertificateResponse_certificate :: Lens' UploadSigningCertificateResponse SigningCertificate
uploadSigningCertificateResponse_certificate = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\UploadSigningCertificateResponse' {SigningCertificate
certificate :: SigningCertificate
$sel:certificate:UploadSigningCertificateResponse' :: UploadSigningCertificateResponse -> SigningCertificate
certificate} -> SigningCertificate
certificate) (\s :: UploadSigningCertificateResponse
s@UploadSigningCertificateResponse' {} SigningCertificate
a -> UploadSigningCertificateResponse
s {$sel:certificate:UploadSigningCertificateResponse' :: SigningCertificate
certificate = SigningCertificate
a} :: UploadSigningCertificateResponse)

instance
  Prelude.NFData
    UploadSigningCertificateResponse
  where
  rnf :: UploadSigningCertificateResponse -> ()
rnf UploadSigningCertificateResponse' {Int
SigningCertificate
certificate :: SigningCertificate
httpStatus :: Int
$sel:certificate:UploadSigningCertificateResponse' :: UploadSigningCertificateResponse -> SigningCertificate
$sel:httpStatus:UploadSigningCertificateResponse' :: UploadSigningCertificateResponse -> Int
..} =
    forall a. NFData a => a -> ()
Prelude.rnf Int
httpStatus
      seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf SigningCertificate
certificate