{-# 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.CertificateManagerPCA.GetCertificate
-- Copyright   : (c) 2013-2023 Brendan Hay
-- License     : Mozilla Public License, v. 2.0.
-- Maintainer  : Brendan Hay
-- Stability   : auto-generated
-- Portability : non-portable (GHC extensions)
--
-- Retrieves a certificate from your private CA or one that has been shared
-- with you. The ARN of the certificate is returned when you call the
-- <https://docs.aws.amazon.com/privateca/latest/APIReference/API_IssueCertificate.html IssueCertificate>
-- action. You must specify both the ARN of your private CA and the ARN of
-- the issued certificate when calling the __GetCertificate__ action. You
-- can retrieve the certificate if it is in the __ISSUED__ state. You can
-- call the
-- <https://docs.aws.amazon.com/privateca/latest/APIReference/API_CreateCertificateAuthorityAuditReport.html CreateCertificateAuthorityAuditReport>
-- action to create a report that contains information about all of the
-- certificates issued and revoked by your private CA.
module Amazonka.CertificateManagerPCA.GetCertificate
  ( -- * Creating a Request
    GetCertificate (..),
    newGetCertificate,

    -- * Request Lenses
    getCertificate_certificateAuthorityArn,
    getCertificate_certificateArn,

    -- * Destructuring the Response
    GetCertificateResponse (..),
    newGetCertificateResponse,

    -- * Response Lenses
    getCertificateResponse_certificate,
    getCertificateResponse_certificateChain,
    getCertificateResponse_httpStatus,
  )
where

import Amazonka.CertificateManagerPCA.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

-- | /See:/ 'newGetCertificate' smart constructor.
data GetCertificate = GetCertificate'
  { -- | The Amazon Resource Name (ARN) that was returned when you called
    -- <https://docs.aws.amazon.com/privateca/latest/APIReference/API_CreateCertificateAuthority.html CreateCertificateAuthority>.
    -- This must be of the form:
    --
    -- @arn:aws:acm-pca:@/@region@/@:@/@account@/@:certificate-authority\/@/@12345678-1234-1234-1234-123456789012@/@ @.
    GetCertificate -> Text
certificateAuthorityArn :: Prelude.Text,
    -- | The ARN of the issued certificate. The ARN contains the certificate
    -- serial number and must be in the following form:
    --
    -- @arn:aws:acm-pca:@/@region@/@:@/@account@/@:certificate-authority\/@/@12345678-1234-1234-1234-123456789012@/@\/certificate\/@/@286535153982981100925020015808220737245@/@ @
    GetCertificate -> Text
certificateArn :: Prelude.Text
  }
  deriving (GetCertificate -> GetCertificate -> Bool
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: GetCertificate -> GetCertificate -> Bool
$c/= :: GetCertificate -> GetCertificate -> Bool
== :: GetCertificate -> GetCertificate -> Bool
$c== :: GetCertificate -> GetCertificate -> Bool
Prelude.Eq, ReadPrec [GetCertificate]
ReadPrec GetCertificate
Int -> ReadS GetCertificate
ReadS [GetCertificate]
forall a.
(Int -> ReadS a)
-> ReadS [a] -> ReadPrec a -> ReadPrec [a] -> Read a
readListPrec :: ReadPrec [GetCertificate]
$creadListPrec :: ReadPrec [GetCertificate]
readPrec :: ReadPrec GetCertificate
$creadPrec :: ReadPrec GetCertificate
readList :: ReadS [GetCertificate]
$creadList :: ReadS [GetCertificate]
readsPrec :: Int -> ReadS GetCertificate
$creadsPrec :: Int -> ReadS GetCertificate
Prelude.Read, Int -> GetCertificate -> ShowS
[GetCertificate] -> ShowS
GetCertificate -> String
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [GetCertificate] -> ShowS
$cshowList :: [GetCertificate] -> ShowS
show :: GetCertificate -> String
$cshow :: GetCertificate -> String
showsPrec :: Int -> GetCertificate -> ShowS
$cshowsPrec :: Int -> GetCertificate -> ShowS
Prelude.Show, forall x. Rep GetCertificate x -> GetCertificate
forall x. GetCertificate -> Rep GetCertificate x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cto :: forall x. Rep GetCertificate x -> GetCertificate
$cfrom :: forall x. GetCertificate -> Rep GetCertificate x
Prelude.Generic)

-- |
-- Create a value of 'GetCertificate' 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:
--
-- 'certificateAuthorityArn', 'getCertificate_certificateAuthorityArn' - The Amazon Resource Name (ARN) that was returned when you called
-- <https://docs.aws.amazon.com/privateca/latest/APIReference/API_CreateCertificateAuthority.html CreateCertificateAuthority>.
-- This must be of the form:
--
-- @arn:aws:acm-pca:@/@region@/@:@/@account@/@:certificate-authority\/@/@12345678-1234-1234-1234-123456789012@/@ @.
--
-- 'certificateArn', 'getCertificate_certificateArn' - The ARN of the issued certificate. The ARN contains the certificate
-- serial number and must be in the following form:
--
-- @arn:aws:acm-pca:@/@region@/@:@/@account@/@:certificate-authority\/@/@12345678-1234-1234-1234-123456789012@/@\/certificate\/@/@286535153982981100925020015808220737245@/@ @
newGetCertificate ::
  -- | 'certificateAuthorityArn'
  Prelude.Text ->
  -- | 'certificateArn'
  Prelude.Text ->
  GetCertificate
newGetCertificate :: Text -> Text -> GetCertificate
newGetCertificate
  Text
pCertificateAuthorityArn_
  Text
pCertificateArn_ =
    GetCertificate'
      { $sel:certificateAuthorityArn:GetCertificate' :: Text
certificateAuthorityArn =
          Text
pCertificateAuthorityArn_,
        $sel:certificateArn:GetCertificate' :: Text
certificateArn = Text
pCertificateArn_
      }

-- | The Amazon Resource Name (ARN) that was returned when you called
-- <https://docs.aws.amazon.com/privateca/latest/APIReference/API_CreateCertificateAuthority.html CreateCertificateAuthority>.
-- This must be of the form:
--
-- @arn:aws:acm-pca:@/@region@/@:@/@account@/@:certificate-authority\/@/@12345678-1234-1234-1234-123456789012@/@ @.
getCertificate_certificateAuthorityArn :: Lens.Lens' GetCertificate Prelude.Text
getCertificate_certificateAuthorityArn :: Lens' GetCertificate Text
getCertificate_certificateAuthorityArn = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\GetCertificate' {Text
certificateAuthorityArn :: Text
$sel:certificateAuthorityArn:GetCertificate' :: GetCertificate -> Text
certificateAuthorityArn} -> Text
certificateAuthorityArn) (\s :: GetCertificate
s@GetCertificate' {} Text
a -> GetCertificate
s {$sel:certificateAuthorityArn:GetCertificate' :: Text
certificateAuthorityArn = Text
a} :: GetCertificate)

-- | The ARN of the issued certificate. The ARN contains the certificate
-- serial number and must be in the following form:
--
-- @arn:aws:acm-pca:@/@region@/@:@/@account@/@:certificate-authority\/@/@12345678-1234-1234-1234-123456789012@/@\/certificate\/@/@286535153982981100925020015808220737245@/@ @
getCertificate_certificateArn :: Lens.Lens' GetCertificate Prelude.Text
getCertificate_certificateArn :: Lens' GetCertificate Text
getCertificate_certificateArn = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\GetCertificate' {Text
certificateArn :: Text
$sel:certificateArn:GetCertificate' :: GetCertificate -> Text
certificateArn} -> Text
certificateArn) (\s :: GetCertificate
s@GetCertificate' {} Text
a -> GetCertificate
s {$sel:certificateArn:GetCertificate' :: Text
certificateArn = Text
a} :: GetCertificate)

instance Core.AWSRequest GetCertificate where
  type
    AWSResponse GetCertificate =
      GetCertificateResponse
  request :: (Service -> Service) -> GetCertificate -> Request GetCertificate
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 GetCertificate
-> ClientResponse ClientBody
-> m (Either Error (ClientResponse (AWSResponse GetCertificate)))
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 -> Maybe Text -> Int -> GetCertificateResponse
GetCertificateResponse'
            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.<*> (Object
x forall a. FromJSON a => Object -> Key -> Either String (Maybe a)
Data..?> Key
"CertificateChain")
            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 GetCertificate where
  hashWithSalt :: Int -> GetCertificate -> Int
hashWithSalt Int
_salt GetCertificate' {Text
certificateArn :: Text
certificateAuthorityArn :: Text
$sel:certificateArn:GetCertificate' :: GetCertificate -> Text
$sel:certificateAuthorityArn:GetCertificate' :: GetCertificate -> Text
..} =
    Int
_salt
      forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Text
certificateAuthorityArn
      forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Text
certificateArn

instance Prelude.NFData GetCertificate where
  rnf :: GetCertificate -> ()
rnf GetCertificate' {Text
certificateArn :: Text
certificateAuthorityArn :: Text
$sel:certificateArn:GetCertificate' :: GetCertificate -> Text
$sel:certificateAuthorityArn:GetCertificate' :: GetCertificate -> Text
..} =
    forall a. NFData a => a -> ()
Prelude.rnf Text
certificateAuthorityArn
      seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf Text
certificateArn

instance Data.ToHeaders GetCertificate where
  toHeaders :: GetCertificate -> 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
"ACMPrivateCA.GetCertificate" ::
                          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 GetCertificate where
  toJSON :: GetCertificate -> Value
toJSON GetCertificate' {Text
certificateArn :: Text
certificateAuthorityArn :: Text
$sel:certificateArn:GetCertificate' :: GetCertificate -> Text
$sel:certificateAuthorityArn:GetCertificate' :: GetCertificate -> Text
..} =
    [Pair] -> Value
Data.object
      ( forall a. [Maybe a] -> [a]
Prelude.catMaybes
          [ forall a. a -> Maybe a
Prelude.Just
              ( Key
"CertificateAuthorityArn"
                  forall kv v. (KeyValue kv, ToJSON v) => Key -> v -> kv
Data..= Text
certificateAuthorityArn
              ),
            forall a. a -> Maybe a
Prelude.Just
              (Key
"CertificateArn" forall kv v. (KeyValue kv, ToJSON v) => Key -> v -> kv
Data..= Text
certificateArn)
          ]
      )

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

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

-- | /See:/ 'newGetCertificateResponse' smart constructor.
data GetCertificateResponse = GetCertificateResponse'
  { -- | The base64 PEM-encoded certificate specified by the @CertificateArn@
    -- parameter.
    GetCertificateResponse -> Maybe Text
certificate :: Prelude.Maybe Prelude.Text,
    -- | The base64 PEM-encoded certificate chain that chains up to the root CA
    -- certificate that you used to sign your private CA certificate.
    GetCertificateResponse -> Maybe Text
certificateChain :: Prelude.Maybe Prelude.Text,
    -- | The response's http status code.
    GetCertificateResponse -> Int
httpStatus :: Prelude.Int
  }
  deriving (GetCertificateResponse -> GetCertificateResponse -> Bool
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: GetCertificateResponse -> GetCertificateResponse -> Bool
$c/= :: GetCertificateResponse -> GetCertificateResponse -> Bool
== :: GetCertificateResponse -> GetCertificateResponse -> Bool
$c== :: GetCertificateResponse -> GetCertificateResponse -> Bool
Prelude.Eq, ReadPrec [GetCertificateResponse]
ReadPrec GetCertificateResponse
Int -> ReadS GetCertificateResponse
ReadS [GetCertificateResponse]
forall a.
(Int -> ReadS a)
-> ReadS [a] -> ReadPrec a -> ReadPrec [a] -> Read a
readListPrec :: ReadPrec [GetCertificateResponse]
$creadListPrec :: ReadPrec [GetCertificateResponse]
readPrec :: ReadPrec GetCertificateResponse
$creadPrec :: ReadPrec GetCertificateResponse
readList :: ReadS [GetCertificateResponse]
$creadList :: ReadS [GetCertificateResponse]
readsPrec :: Int -> ReadS GetCertificateResponse
$creadsPrec :: Int -> ReadS GetCertificateResponse
Prelude.Read, Int -> GetCertificateResponse -> ShowS
[GetCertificateResponse] -> ShowS
GetCertificateResponse -> String
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [GetCertificateResponse] -> ShowS
$cshowList :: [GetCertificateResponse] -> ShowS
show :: GetCertificateResponse -> String
$cshow :: GetCertificateResponse -> String
showsPrec :: Int -> GetCertificateResponse -> ShowS
$cshowsPrec :: Int -> GetCertificateResponse -> ShowS
Prelude.Show, forall x. Rep GetCertificateResponse x -> GetCertificateResponse
forall x. GetCertificateResponse -> Rep GetCertificateResponse x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cto :: forall x. Rep GetCertificateResponse x -> GetCertificateResponse
$cfrom :: forall x. GetCertificateResponse -> Rep GetCertificateResponse x
Prelude.Generic)

-- |
-- Create a value of 'GetCertificateResponse' 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', 'getCertificateResponse_certificate' - The base64 PEM-encoded certificate specified by the @CertificateArn@
-- parameter.
--
-- 'certificateChain', 'getCertificateResponse_certificateChain' - The base64 PEM-encoded certificate chain that chains up to the root CA
-- certificate that you used to sign your private CA certificate.
--
-- 'httpStatus', 'getCertificateResponse_httpStatus' - The response's http status code.
newGetCertificateResponse ::
  -- | 'httpStatus'
  Prelude.Int ->
  GetCertificateResponse
newGetCertificateResponse :: Int -> GetCertificateResponse
newGetCertificateResponse Int
pHttpStatus_ =
  GetCertificateResponse'
    { $sel:certificate:GetCertificateResponse' :: Maybe Text
certificate =
        forall a. Maybe a
Prelude.Nothing,
      $sel:certificateChain:GetCertificateResponse' :: Maybe Text
certificateChain = forall a. Maybe a
Prelude.Nothing,
      $sel:httpStatus:GetCertificateResponse' :: Int
httpStatus = Int
pHttpStatus_
    }

-- | The base64 PEM-encoded certificate specified by the @CertificateArn@
-- parameter.
getCertificateResponse_certificate :: Lens.Lens' GetCertificateResponse (Prelude.Maybe Prelude.Text)
getCertificateResponse_certificate :: Lens' GetCertificateResponse (Maybe Text)
getCertificateResponse_certificate = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\GetCertificateResponse' {Maybe Text
certificate :: Maybe Text
$sel:certificate:GetCertificateResponse' :: GetCertificateResponse -> Maybe Text
certificate} -> Maybe Text
certificate) (\s :: GetCertificateResponse
s@GetCertificateResponse' {} Maybe Text
a -> GetCertificateResponse
s {$sel:certificate:GetCertificateResponse' :: Maybe Text
certificate = Maybe Text
a} :: GetCertificateResponse)

-- | The base64 PEM-encoded certificate chain that chains up to the root CA
-- certificate that you used to sign your private CA certificate.
getCertificateResponse_certificateChain :: Lens.Lens' GetCertificateResponse (Prelude.Maybe Prelude.Text)
getCertificateResponse_certificateChain :: Lens' GetCertificateResponse (Maybe Text)
getCertificateResponse_certificateChain = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\GetCertificateResponse' {Maybe Text
certificateChain :: Maybe Text
$sel:certificateChain:GetCertificateResponse' :: GetCertificateResponse -> Maybe Text
certificateChain} -> Maybe Text
certificateChain) (\s :: GetCertificateResponse
s@GetCertificateResponse' {} Maybe Text
a -> GetCertificateResponse
s {$sel:certificateChain:GetCertificateResponse' :: Maybe Text
certificateChain = Maybe Text
a} :: GetCertificateResponse)

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

instance Prelude.NFData GetCertificateResponse where
  rnf :: GetCertificateResponse -> ()
rnf GetCertificateResponse' {Int
Maybe Text
httpStatus :: Int
certificateChain :: Maybe Text
certificate :: Maybe Text
$sel:httpStatus:GetCertificateResponse' :: GetCertificateResponse -> Int
$sel:certificateChain:GetCertificateResponse' :: GetCertificateResponse -> Maybe Text
$sel:certificate:GetCertificateResponse' :: GetCertificateResponse -> 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 Maybe Text
certificateChain
      seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf Int
httpStatus