{-# 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.DescribeCertificateAuthority
-- Copyright   : (c) 2013-2023 Brendan Hay
-- License     : Mozilla Public License, v. 2.0.
-- Maintainer  : Brendan Hay
-- Stability   : auto-generated
-- Portability : non-portable (GHC extensions)
--
-- Lists information about your private certificate authority (CA) or one
-- that has been shared with you. You specify the private CA on input by
-- its ARN (Amazon Resource Name). The output contains the status of your
-- CA. This can be any of the following:
--
-- -   @CREATING@ - Amazon Web Services Private CA is creating your private
--     certificate authority.
--
-- -   @PENDING_CERTIFICATE@ - The certificate is pending. You must use
--     your Amazon Web Services Private CA-hosted or on-premises root or
--     subordinate CA to sign your private CA CSR and then import it into
--     Amazon Web Services Private CA.
--
-- -   @ACTIVE@ - Your private CA is active.
--
-- -   @DISABLED@ - Your private CA has been disabled.
--
-- -   @EXPIRED@ - Your private CA certificate has expired.
--
-- -   @FAILED@ - Your private CA has failed. Your CA can fail because of
--     problems such a network outage or back-end Amazon Web Services
--     failure or other errors. A failed CA can never return to the pending
--     state. You must create a new CA.
--
-- -   @DELETED@ - Your private CA is within the restoration period, after
--     which it is permanently deleted. The length of time remaining in the
--     CA\'s restoration period is also included in this action\'s output.
module Amazonka.CertificateManagerPCA.DescribeCertificateAuthority
  ( -- * Creating a Request
    DescribeCertificateAuthority (..),
    newDescribeCertificateAuthority,

    -- * Request Lenses
    describeCertificateAuthority_certificateAuthorityArn,

    -- * Destructuring the Response
    DescribeCertificateAuthorityResponse (..),
    newDescribeCertificateAuthorityResponse,

    -- * Response Lenses
    describeCertificateAuthorityResponse_certificateAuthority,
    describeCertificateAuthorityResponse_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:/ 'newDescribeCertificateAuthority' smart constructor.
data DescribeCertificateAuthority = DescribeCertificateAuthority'
  { -- | 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@/@ @.
    DescribeCertificateAuthority -> Text
certificateAuthorityArn :: Prelude.Text
  }
  deriving (DescribeCertificateAuthority
-> DescribeCertificateAuthority -> Bool
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: DescribeCertificateAuthority
-> DescribeCertificateAuthority -> Bool
$c/= :: DescribeCertificateAuthority
-> DescribeCertificateAuthority -> Bool
== :: DescribeCertificateAuthority
-> DescribeCertificateAuthority -> Bool
$c== :: DescribeCertificateAuthority
-> DescribeCertificateAuthority -> Bool
Prelude.Eq, ReadPrec [DescribeCertificateAuthority]
ReadPrec DescribeCertificateAuthority
Int -> ReadS DescribeCertificateAuthority
ReadS [DescribeCertificateAuthority]
forall a.
(Int -> ReadS a)
-> ReadS [a] -> ReadPrec a -> ReadPrec [a] -> Read a
readListPrec :: ReadPrec [DescribeCertificateAuthority]
$creadListPrec :: ReadPrec [DescribeCertificateAuthority]
readPrec :: ReadPrec DescribeCertificateAuthority
$creadPrec :: ReadPrec DescribeCertificateAuthority
readList :: ReadS [DescribeCertificateAuthority]
$creadList :: ReadS [DescribeCertificateAuthority]
readsPrec :: Int -> ReadS DescribeCertificateAuthority
$creadsPrec :: Int -> ReadS DescribeCertificateAuthority
Prelude.Read, Int -> DescribeCertificateAuthority -> ShowS
[DescribeCertificateAuthority] -> ShowS
DescribeCertificateAuthority -> String
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [DescribeCertificateAuthority] -> ShowS
$cshowList :: [DescribeCertificateAuthority] -> ShowS
show :: DescribeCertificateAuthority -> String
$cshow :: DescribeCertificateAuthority -> String
showsPrec :: Int -> DescribeCertificateAuthority -> ShowS
$cshowsPrec :: Int -> DescribeCertificateAuthority -> ShowS
Prelude.Show, forall x.
Rep DescribeCertificateAuthority x -> DescribeCertificateAuthority
forall x.
DescribeCertificateAuthority -> Rep DescribeCertificateAuthority x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cto :: forall x.
Rep DescribeCertificateAuthority x -> DescribeCertificateAuthority
$cfrom :: forall x.
DescribeCertificateAuthority -> Rep DescribeCertificateAuthority x
Prelude.Generic)

-- |
-- Create a value of 'DescribeCertificateAuthority' 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', 'describeCertificateAuthority_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@/@ @.
newDescribeCertificateAuthority ::
  -- | 'certificateAuthorityArn'
  Prelude.Text ->
  DescribeCertificateAuthority
newDescribeCertificateAuthority :: Text -> DescribeCertificateAuthority
newDescribeCertificateAuthority
  Text
pCertificateAuthorityArn_ =
    DescribeCertificateAuthority'
      { $sel:certificateAuthorityArn:DescribeCertificateAuthority' :: Text
certificateAuthorityArn =
          Text
pCertificateAuthorityArn_
      }

-- | 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@/@ @.
describeCertificateAuthority_certificateAuthorityArn :: Lens.Lens' DescribeCertificateAuthority Prelude.Text
describeCertificateAuthority_certificateAuthorityArn :: Lens' DescribeCertificateAuthority Text
describeCertificateAuthority_certificateAuthorityArn = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\DescribeCertificateAuthority' {Text
certificateAuthorityArn :: Text
$sel:certificateAuthorityArn:DescribeCertificateAuthority' :: DescribeCertificateAuthority -> Text
certificateAuthorityArn} -> Text
certificateAuthorityArn) (\s :: DescribeCertificateAuthority
s@DescribeCertificateAuthority' {} Text
a -> DescribeCertificateAuthority
s {$sel:certificateAuthorityArn:DescribeCertificateAuthority' :: Text
certificateAuthorityArn = Text
a} :: DescribeCertificateAuthority)

instance Core.AWSRequest DescribeCertificateAuthority where
  type
    AWSResponse DescribeCertificateAuthority =
      DescribeCertificateAuthorityResponse
  request :: (Service -> Service)
-> DescribeCertificateAuthority
-> Request DescribeCertificateAuthority
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 DescribeCertificateAuthority
-> ClientResponse ClientBody
-> m (Either
        Error (ClientResponse (AWSResponse DescribeCertificateAuthority)))
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 CertificateAuthority
-> Int -> DescribeCertificateAuthorityResponse
DescribeCertificateAuthorityResponse'
            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
"CertificateAuthority")
            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
    DescribeCertificateAuthority
  where
  hashWithSalt :: Int -> DescribeCertificateAuthority -> Int
hashWithSalt Int
_salt DescribeCertificateAuthority' {Text
certificateAuthorityArn :: Text
$sel:certificateAuthorityArn:DescribeCertificateAuthority' :: DescribeCertificateAuthority -> Text
..} =
    Int
_salt
      forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Text
certificateAuthorityArn

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

instance Data.ToHeaders DescribeCertificateAuthority where
  toHeaders :: DescribeCertificateAuthority -> 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.DescribeCertificateAuthority" ::
                          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 DescribeCertificateAuthority where
  toJSON :: DescribeCertificateAuthority -> Value
toJSON DescribeCertificateAuthority' {Text
certificateAuthorityArn :: Text
$sel:certificateAuthorityArn:DescribeCertificateAuthority' :: DescribeCertificateAuthority -> 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
              )
          ]
      )

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

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

-- | /See:/ 'newDescribeCertificateAuthorityResponse' smart constructor.
data DescribeCertificateAuthorityResponse = DescribeCertificateAuthorityResponse'
  { -- | A
    -- <https://docs.aws.amazon.com/privateca/latest/APIReference/API_CertificateAuthority.html CertificateAuthority>
    -- structure that contains information about your private CA.
    DescribeCertificateAuthorityResponse -> Maybe CertificateAuthority
certificateAuthority :: Prelude.Maybe CertificateAuthority,
    -- | The response's http status code.
    DescribeCertificateAuthorityResponse -> Int
httpStatus :: Prelude.Int
  }
  deriving (DescribeCertificateAuthorityResponse
-> DescribeCertificateAuthorityResponse -> Bool
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: DescribeCertificateAuthorityResponse
-> DescribeCertificateAuthorityResponse -> Bool
$c/= :: DescribeCertificateAuthorityResponse
-> DescribeCertificateAuthorityResponse -> Bool
== :: DescribeCertificateAuthorityResponse
-> DescribeCertificateAuthorityResponse -> Bool
$c== :: DescribeCertificateAuthorityResponse
-> DescribeCertificateAuthorityResponse -> Bool
Prelude.Eq, ReadPrec [DescribeCertificateAuthorityResponse]
ReadPrec DescribeCertificateAuthorityResponse
Int -> ReadS DescribeCertificateAuthorityResponse
ReadS [DescribeCertificateAuthorityResponse]
forall a.
(Int -> ReadS a)
-> ReadS [a] -> ReadPrec a -> ReadPrec [a] -> Read a
readListPrec :: ReadPrec [DescribeCertificateAuthorityResponse]
$creadListPrec :: ReadPrec [DescribeCertificateAuthorityResponse]
readPrec :: ReadPrec DescribeCertificateAuthorityResponse
$creadPrec :: ReadPrec DescribeCertificateAuthorityResponse
readList :: ReadS [DescribeCertificateAuthorityResponse]
$creadList :: ReadS [DescribeCertificateAuthorityResponse]
readsPrec :: Int -> ReadS DescribeCertificateAuthorityResponse
$creadsPrec :: Int -> ReadS DescribeCertificateAuthorityResponse
Prelude.Read, Int -> DescribeCertificateAuthorityResponse -> ShowS
[DescribeCertificateAuthorityResponse] -> ShowS
DescribeCertificateAuthorityResponse -> String
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [DescribeCertificateAuthorityResponse] -> ShowS
$cshowList :: [DescribeCertificateAuthorityResponse] -> ShowS
show :: DescribeCertificateAuthorityResponse -> String
$cshow :: DescribeCertificateAuthorityResponse -> String
showsPrec :: Int -> DescribeCertificateAuthorityResponse -> ShowS
$cshowsPrec :: Int -> DescribeCertificateAuthorityResponse -> ShowS
Prelude.Show, forall x.
Rep DescribeCertificateAuthorityResponse x
-> DescribeCertificateAuthorityResponse
forall x.
DescribeCertificateAuthorityResponse
-> Rep DescribeCertificateAuthorityResponse x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cto :: forall x.
Rep DescribeCertificateAuthorityResponse x
-> DescribeCertificateAuthorityResponse
$cfrom :: forall x.
DescribeCertificateAuthorityResponse
-> Rep DescribeCertificateAuthorityResponse x
Prelude.Generic)

-- |
-- Create a value of 'DescribeCertificateAuthorityResponse' 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:
--
-- 'certificateAuthority', 'describeCertificateAuthorityResponse_certificateAuthority' - A
-- <https://docs.aws.amazon.com/privateca/latest/APIReference/API_CertificateAuthority.html CertificateAuthority>
-- structure that contains information about your private CA.
--
-- 'httpStatus', 'describeCertificateAuthorityResponse_httpStatus' - The response's http status code.
newDescribeCertificateAuthorityResponse ::
  -- | 'httpStatus'
  Prelude.Int ->
  DescribeCertificateAuthorityResponse
newDescribeCertificateAuthorityResponse :: Int -> DescribeCertificateAuthorityResponse
newDescribeCertificateAuthorityResponse Int
pHttpStatus_ =
  DescribeCertificateAuthorityResponse'
    { $sel:certificateAuthority:DescribeCertificateAuthorityResponse' :: Maybe CertificateAuthority
certificateAuthority =
        forall a. Maybe a
Prelude.Nothing,
      $sel:httpStatus:DescribeCertificateAuthorityResponse' :: Int
httpStatus = Int
pHttpStatus_
    }

-- | A
-- <https://docs.aws.amazon.com/privateca/latest/APIReference/API_CertificateAuthority.html CertificateAuthority>
-- structure that contains information about your private CA.
describeCertificateAuthorityResponse_certificateAuthority :: Lens.Lens' DescribeCertificateAuthorityResponse (Prelude.Maybe CertificateAuthority)
describeCertificateAuthorityResponse_certificateAuthority :: Lens'
  DescribeCertificateAuthorityResponse (Maybe CertificateAuthority)
describeCertificateAuthorityResponse_certificateAuthority = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\DescribeCertificateAuthorityResponse' {Maybe CertificateAuthority
certificateAuthority :: Maybe CertificateAuthority
$sel:certificateAuthority:DescribeCertificateAuthorityResponse' :: DescribeCertificateAuthorityResponse -> Maybe CertificateAuthority
certificateAuthority} -> Maybe CertificateAuthority
certificateAuthority) (\s :: DescribeCertificateAuthorityResponse
s@DescribeCertificateAuthorityResponse' {} Maybe CertificateAuthority
a -> DescribeCertificateAuthorityResponse
s {$sel:certificateAuthority:DescribeCertificateAuthorityResponse' :: Maybe CertificateAuthority
certificateAuthority = Maybe CertificateAuthority
a} :: DescribeCertificateAuthorityResponse)

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

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