{-# 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.CognitoIdentityProvider.GetSigningCertificate
-- Copyright   : (c) 2013-2023 Brendan Hay
-- License     : Mozilla Public License, v. 2.0.
-- Maintainer  : Brendan Hay
-- Stability   : auto-generated
-- Portability : non-portable (GHC extensions)
--
-- This method takes a user pool ID, and returns the signing certificate.
-- The issued certificate is valid for 10 years from the date of issue.
--
-- Amazon Cognito issues and assigns a new signing certificate annually.
-- This process returns a new value in the response to
-- @GetSigningCertificate@, but doesn\'t invalidate the original
-- certificate.
module Amazonka.CognitoIdentityProvider.GetSigningCertificate
  ( -- * Creating a Request
    GetSigningCertificate (..),
    newGetSigningCertificate,

    -- * Request Lenses
    getSigningCertificate_userPoolId,

    -- * Destructuring the Response
    GetSigningCertificateResponse (..),
    newGetSigningCertificateResponse,

    -- * Response Lenses
    getSigningCertificateResponse_certificate,
    getSigningCertificateResponse_httpStatus,
  )
where

import Amazonka.CognitoIdentityProvider.Types
import qualified Amazonka.Core as Core
import qualified Amazonka.Core.Lens.Internal as Lens
import qualified Amazonka.Data as Data
import qualified Amazonka.Prelude as Prelude
import qualified Amazonka.Request as Request
import qualified Amazonka.Response as Response

-- | Request to get a signing certificate from Amazon Cognito.
--
-- /See:/ 'newGetSigningCertificate' smart constructor.
data GetSigningCertificate = GetSigningCertificate'
  { -- | The user pool ID.
    GetSigningCertificate -> Text
userPoolId :: Prelude.Text
  }
  deriving (GetSigningCertificate -> GetSigningCertificate -> Bool
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: GetSigningCertificate -> GetSigningCertificate -> Bool
$c/= :: GetSigningCertificate -> GetSigningCertificate -> Bool
== :: GetSigningCertificate -> GetSigningCertificate -> Bool
$c== :: GetSigningCertificate -> GetSigningCertificate -> Bool
Prelude.Eq, ReadPrec [GetSigningCertificate]
ReadPrec GetSigningCertificate
Int -> ReadS GetSigningCertificate
ReadS [GetSigningCertificate]
forall a.
(Int -> ReadS a)
-> ReadS [a] -> ReadPrec a -> ReadPrec [a] -> Read a
readListPrec :: ReadPrec [GetSigningCertificate]
$creadListPrec :: ReadPrec [GetSigningCertificate]
readPrec :: ReadPrec GetSigningCertificate
$creadPrec :: ReadPrec GetSigningCertificate
readList :: ReadS [GetSigningCertificate]
$creadList :: ReadS [GetSigningCertificate]
readsPrec :: Int -> ReadS GetSigningCertificate
$creadsPrec :: Int -> ReadS GetSigningCertificate
Prelude.Read, Int -> GetSigningCertificate -> ShowS
[GetSigningCertificate] -> ShowS
GetSigningCertificate -> String
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [GetSigningCertificate] -> ShowS
$cshowList :: [GetSigningCertificate] -> ShowS
show :: GetSigningCertificate -> String
$cshow :: GetSigningCertificate -> String
showsPrec :: Int -> GetSigningCertificate -> ShowS
$cshowsPrec :: Int -> GetSigningCertificate -> ShowS
Prelude.Show, forall x. Rep GetSigningCertificate x -> GetSigningCertificate
forall x. GetSigningCertificate -> Rep GetSigningCertificate x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cto :: forall x. Rep GetSigningCertificate x -> GetSigningCertificate
$cfrom :: forall x. GetSigningCertificate -> Rep GetSigningCertificate x
Prelude.Generic)

-- |
-- Create a value of 'GetSigningCertificate' 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:
--
-- 'userPoolId', 'getSigningCertificate_userPoolId' - The user pool ID.
newGetSigningCertificate ::
  -- | 'userPoolId'
  Prelude.Text ->
  GetSigningCertificate
newGetSigningCertificate :: Text -> GetSigningCertificate
newGetSigningCertificate Text
pUserPoolId_ =
  GetSigningCertificate' {$sel:userPoolId:GetSigningCertificate' :: Text
userPoolId = Text
pUserPoolId_}

-- | The user pool ID.
getSigningCertificate_userPoolId :: Lens.Lens' GetSigningCertificate Prelude.Text
getSigningCertificate_userPoolId :: Lens' GetSigningCertificate Text
getSigningCertificate_userPoolId = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\GetSigningCertificate' {Text
userPoolId :: Text
$sel:userPoolId:GetSigningCertificate' :: GetSigningCertificate -> Text
userPoolId} -> Text
userPoolId) (\s :: GetSigningCertificate
s@GetSigningCertificate' {} Text
a -> GetSigningCertificate
s {$sel:userPoolId:GetSigningCertificate' :: Text
userPoolId = Text
a} :: GetSigningCertificate)

instance Core.AWSRequest GetSigningCertificate where
  type
    AWSResponse GetSigningCertificate =
      GetSigningCertificateResponse
  request :: (Service -> Service)
-> GetSigningCertificate -> Request GetSigningCertificate
request Service -> Service
overrides =
    forall a. (ToRequest a, ToJSON a) => Service -> a -> Request a
Request.postJSON (Service -> Service
overrides Service
defaultService)
  response :: forall (m :: * -> *).
MonadResource m =>
(ByteStringLazy -> IO ByteStringLazy)
-> Service
-> Proxy GetSigningCertificate
-> ClientResponse ClientBody
-> m (Either
        Error (ClientResponse (AWSResponse GetSigningCertificate)))
response =
    forall (m :: * -> *) a.
MonadResource m =>
(Int -> ResponseHeaders -> Object -> Either String (AWSResponse a))
-> (ByteStringLazy -> IO ByteStringLazy)
-> Service
-> Proxy a
-> ClientResponse ClientBody
-> m (Either Error (ClientResponse (AWSResponse a)))
Response.receiveJSON
      ( \Int
s ResponseHeaders
h Object
x ->
          Maybe Text -> Int -> GetSigningCertificateResponse
GetSigningCertificateResponse'
            forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
Prelude.<$> (Object
x forall a. FromJSON a => Object -> Key -> Either String (Maybe a)
Data..?> Key
"Certificate")
            forall (f :: * -> *) a b. Applicative f => 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))
      )

instance Prelude.Hashable GetSigningCertificate where
  hashWithSalt :: Int -> GetSigningCertificate -> Int
hashWithSalt Int
_salt GetSigningCertificate' {Text
userPoolId :: Text
$sel:userPoolId:GetSigningCertificate' :: GetSigningCertificate -> Text
..} =
    Int
_salt forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Text
userPoolId

instance Prelude.NFData GetSigningCertificate where
  rnf :: GetSigningCertificate -> ()
rnf GetSigningCertificate' {Text
userPoolId :: Text
$sel:userPoolId:GetSigningCertificate' :: GetSigningCertificate -> Text
..} =
    forall a. NFData a => a -> ()
Prelude.rnf Text
userPoolId

instance Data.ToHeaders GetSigningCertificate where
  toHeaders :: GetSigningCertificate -> ResponseHeaders
toHeaders =
    forall a b. a -> b -> a
Prelude.const
      ( forall a. Monoid a => [a] -> a
Prelude.mconcat
          [ HeaderName
"X-Amz-Target"
              forall a. ToHeader a => HeaderName -> a -> ResponseHeaders
Data.=# ( ByteString
"AWSCognitoIdentityProviderService.GetSigningCertificate" ::
                          Prelude.ByteString
                      ),
            HeaderName
"Content-Type"
              forall a. ToHeader a => HeaderName -> a -> ResponseHeaders
Data.=# ( ByteString
"application/x-amz-json-1.1" ::
                          Prelude.ByteString
                      )
          ]
      )

instance Data.ToJSON GetSigningCertificate where
  toJSON :: GetSigningCertificate -> Value
toJSON GetSigningCertificate' {Text
userPoolId :: Text
$sel:userPoolId:GetSigningCertificate' :: GetSigningCertificate -> Text
..} =
    [Pair] -> Value
Data.object
      ( forall a. [Maybe a] -> [a]
Prelude.catMaybes
          [forall a. a -> Maybe a
Prelude.Just (Key
"UserPoolId" forall kv v. (KeyValue kv, ToJSON v) => Key -> v -> kv
Data..= Text
userPoolId)]
      )

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

instance Data.ToQuery GetSigningCertificate where
  toQuery :: GetSigningCertificate -> QueryString
toQuery = forall a b. a -> b -> a
Prelude.const forall a. Monoid a => a
Prelude.mempty

-- | Response from Amazon Cognito for a signing certificate request.
--
-- /See:/ 'newGetSigningCertificateResponse' smart constructor.
data GetSigningCertificateResponse = GetSigningCertificateResponse'
  { -- | The signing certificate.
    GetSigningCertificateResponse -> Maybe Text
certificate :: Prelude.Maybe Prelude.Text,
    -- | The response's http status code.
    GetSigningCertificateResponse -> Int
httpStatus :: Prelude.Int
  }
  deriving (GetSigningCertificateResponse
-> GetSigningCertificateResponse -> Bool
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: GetSigningCertificateResponse
-> GetSigningCertificateResponse -> Bool
$c/= :: GetSigningCertificateResponse
-> GetSigningCertificateResponse -> Bool
== :: GetSigningCertificateResponse
-> GetSigningCertificateResponse -> Bool
$c== :: GetSigningCertificateResponse
-> GetSigningCertificateResponse -> Bool
Prelude.Eq, ReadPrec [GetSigningCertificateResponse]
ReadPrec GetSigningCertificateResponse
Int -> ReadS GetSigningCertificateResponse
ReadS [GetSigningCertificateResponse]
forall a.
(Int -> ReadS a)
-> ReadS [a] -> ReadPrec a -> ReadPrec [a] -> Read a
readListPrec :: ReadPrec [GetSigningCertificateResponse]
$creadListPrec :: ReadPrec [GetSigningCertificateResponse]
readPrec :: ReadPrec GetSigningCertificateResponse
$creadPrec :: ReadPrec GetSigningCertificateResponse
readList :: ReadS [GetSigningCertificateResponse]
$creadList :: ReadS [GetSigningCertificateResponse]
readsPrec :: Int -> ReadS GetSigningCertificateResponse
$creadsPrec :: Int -> ReadS GetSigningCertificateResponse
Prelude.Read, Int -> GetSigningCertificateResponse -> ShowS
[GetSigningCertificateResponse] -> ShowS
GetSigningCertificateResponse -> String
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [GetSigningCertificateResponse] -> ShowS
$cshowList :: [GetSigningCertificateResponse] -> ShowS
show :: GetSigningCertificateResponse -> String
$cshow :: GetSigningCertificateResponse -> String
showsPrec :: Int -> GetSigningCertificateResponse -> ShowS
$cshowsPrec :: Int -> GetSigningCertificateResponse -> ShowS
Prelude.Show, forall x.
Rep GetSigningCertificateResponse x
-> GetSigningCertificateResponse
forall x.
GetSigningCertificateResponse
-> Rep GetSigningCertificateResponse x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cto :: forall x.
Rep GetSigningCertificateResponse x
-> GetSigningCertificateResponse
$cfrom :: forall x.
GetSigningCertificateResponse
-> Rep GetSigningCertificateResponse x
Prelude.Generic)

-- |
-- Create a value of 'GetSigningCertificateResponse' 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:
--
-- 'certificate', 'getSigningCertificateResponse_certificate' - The signing certificate.
--
-- 'httpStatus', 'getSigningCertificateResponse_httpStatus' - The response's http status code.
newGetSigningCertificateResponse ::
  -- | 'httpStatus'
  Prelude.Int ->
  GetSigningCertificateResponse
newGetSigningCertificateResponse :: Int -> GetSigningCertificateResponse
newGetSigningCertificateResponse Int
pHttpStatus_ =
  GetSigningCertificateResponse'
    { $sel:certificate:GetSigningCertificateResponse' :: Maybe Text
certificate =
        forall a. Maybe a
Prelude.Nothing,
      $sel:httpStatus:GetSigningCertificateResponse' :: Int
httpStatus = Int
pHttpStatus_
    }

-- | The signing certificate.
getSigningCertificateResponse_certificate :: Lens.Lens' GetSigningCertificateResponse (Prelude.Maybe Prelude.Text)
getSigningCertificateResponse_certificate :: Lens' GetSigningCertificateResponse (Maybe Text)
getSigningCertificateResponse_certificate = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\GetSigningCertificateResponse' {Maybe Text
certificate :: Maybe Text
$sel:certificate:GetSigningCertificateResponse' :: GetSigningCertificateResponse -> Maybe Text
certificate} -> Maybe Text
certificate) (\s :: GetSigningCertificateResponse
s@GetSigningCertificateResponse' {} Maybe Text
a -> GetSigningCertificateResponse
s {$sel:certificate:GetSigningCertificateResponse' :: Maybe Text
certificate = Maybe Text
a} :: GetSigningCertificateResponse)

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

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