{-# 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.CertificateManager.ExportCertificate
-- Copyright   : (c) 2013-2023 Brendan Hay
-- License     : Mozilla Public License, v. 2.0.
-- Maintainer  : Brendan Hay
-- Stability   : auto-generated
-- Portability : non-portable (GHC extensions)
--
-- Exports a private certificate issued by a private certificate authority
-- (CA) for use anywhere. The exported file contains the certificate, the
-- certificate chain, and the encrypted private 2048-bit RSA key associated
-- with the public key that is embedded in the certificate. For security,
-- you must assign a passphrase for the private key when exporting it.
--
-- For information about exporting and formatting a certificate using the
-- ACM console or CLI, see
-- <https://docs.aws.amazon.com/acm/latest/userguide/gs-acm-export-private.html Export a Private Certificate>.
module Amazonka.CertificateManager.ExportCertificate
  ( -- * Creating a Request
    ExportCertificate (..),
    newExportCertificate,

    -- * Request Lenses
    exportCertificate_certificateArn,
    exportCertificate_passphrase,

    -- * Destructuring the Response
    ExportCertificateResponse (..),
    newExportCertificateResponse,

    -- * Response Lenses
    exportCertificateResponse_certificate,
    exportCertificateResponse_certificateChain,
    exportCertificateResponse_privateKey,
    exportCertificateResponse_httpStatus,
  )
where

import Amazonka.CertificateManager.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:/ 'newExportCertificate' smart constructor.
data ExportCertificate = ExportCertificate'
  { -- | An Amazon Resource Name (ARN) of the issued certificate. This must be of
    -- the form:
    --
    -- @arn:aws:acm:region:account:certificate\/12345678-1234-1234-1234-123456789012@
    ExportCertificate -> Text
certificateArn :: Prelude.Text,
    -- | Passphrase to associate with the encrypted exported private key.
    --
    -- When creating your passphrase, you can use any ASCII character except #,
    -- \$, or %.
    --
    -- If you want to later decrypt the private key, you must have the
    -- passphrase. You can use the following OpenSSL command to decrypt a
    -- private key. After entering the command, you are prompted for the
    -- passphrase.
    --
    -- @openssl rsa -in encrypted_key.pem -out decrypted_key.pem@
    ExportCertificate -> Sensitive Base64
passphrase :: Data.Sensitive Data.Base64
  }
  deriving (ExportCertificate -> ExportCertificate -> Bool
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: ExportCertificate -> ExportCertificate -> Bool
$c/= :: ExportCertificate -> ExportCertificate -> Bool
== :: ExportCertificate -> ExportCertificate -> Bool
$c== :: ExportCertificate -> ExportCertificate -> Bool
Prelude.Eq, Int -> ExportCertificate -> ShowS
[ExportCertificate] -> ShowS
ExportCertificate -> String
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [ExportCertificate] -> ShowS
$cshowList :: [ExportCertificate] -> ShowS
show :: ExportCertificate -> String
$cshow :: ExportCertificate -> String
showsPrec :: Int -> ExportCertificate -> ShowS
$cshowsPrec :: Int -> ExportCertificate -> ShowS
Prelude.Show, forall x. Rep ExportCertificate x -> ExportCertificate
forall x. ExportCertificate -> Rep ExportCertificate x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cto :: forall x. Rep ExportCertificate x -> ExportCertificate
$cfrom :: forall x. ExportCertificate -> Rep ExportCertificate x
Prelude.Generic)

-- |
-- Create a value of 'ExportCertificate' 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:
--
-- 'certificateArn', 'exportCertificate_certificateArn' - An Amazon Resource Name (ARN) of the issued certificate. This must be of
-- the form:
--
-- @arn:aws:acm:region:account:certificate\/12345678-1234-1234-1234-123456789012@
--
-- 'passphrase', 'exportCertificate_passphrase' - Passphrase to associate with the encrypted exported private key.
--
-- When creating your passphrase, you can use any ASCII character except #,
-- \$, or %.
--
-- If you want to later decrypt the private key, you must have the
-- passphrase. You can use the following OpenSSL command to decrypt a
-- private key. After entering the command, you are prompted for the
-- passphrase.
--
-- @openssl rsa -in encrypted_key.pem -out decrypted_key.pem@--
-- -- /Note:/ This 'Lens' automatically encodes and decodes Base64 data.
-- -- The underlying isomorphism will encode to Base64 representation during
-- -- serialisation, and decode from Base64 representation during deserialisation.
-- -- This 'Lens' accepts and returns only raw unencoded data.
newExportCertificate ::
  -- | 'certificateArn'
  Prelude.Text ->
  -- | 'passphrase'
  Prelude.ByteString ->
  ExportCertificate
newExportCertificate :: Text -> ByteString -> ExportCertificate
newExportCertificate Text
pCertificateArn_ ByteString
pPassphrase_ =
  ExportCertificate'
    { $sel:certificateArn:ExportCertificate' :: Text
certificateArn =
        Text
pCertificateArn_,
      $sel:passphrase:ExportCertificate' :: Sensitive Base64
passphrase =
        forall a. Iso' (Sensitive a) a
Data._Sensitive
          forall b c a. (b -> c) -> (a -> b) -> a -> c
Prelude.. Iso' Base64 ByteString
Data._Base64
          forall t b. AReview t b -> b -> t
Lens.# ByteString
pPassphrase_
    }

-- | An Amazon Resource Name (ARN) of the issued certificate. This must be of
-- the form:
--
-- @arn:aws:acm:region:account:certificate\/12345678-1234-1234-1234-123456789012@
exportCertificate_certificateArn :: Lens.Lens' ExportCertificate Prelude.Text
exportCertificate_certificateArn :: Lens' ExportCertificate Text
exportCertificate_certificateArn = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\ExportCertificate' {Text
certificateArn :: Text
$sel:certificateArn:ExportCertificate' :: ExportCertificate -> Text
certificateArn} -> Text
certificateArn) (\s :: ExportCertificate
s@ExportCertificate' {} Text
a -> ExportCertificate
s {$sel:certificateArn:ExportCertificate' :: Text
certificateArn = Text
a} :: ExportCertificate)

-- | Passphrase to associate with the encrypted exported private key.
--
-- When creating your passphrase, you can use any ASCII character except #,
-- \$, or %.
--
-- If you want to later decrypt the private key, you must have the
-- passphrase. You can use the following OpenSSL command to decrypt a
-- private key. After entering the command, you are prompted for the
-- passphrase.
--
-- @openssl rsa -in encrypted_key.pem -out decrypted_key.pem@--
-- -- /Note:/ This 'Lens' automatically encodes and decodes Base64 data.
-- -- The underlying isomorphism will encode to Base64 representation during
-- -- serialisation, and decode from Base64 representation during deserialisation.
-- -- This 'Lens' accepts and returns only raw unencoded data.
exportCertificate_passphrase :: Lens.Lens' ExportCertificate Prelude.ByteString
exportCertificate_passphrase :: Lens' ExportCertificate ByteString
exportCertificate_passphrase = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\ExportCertificate' {Sensitive Base64
passphrase :: Sensitive Base64
$sel:passphrase:ExportCertificate' :: ExportCertificate -> Sensitive Base64
passphrase} -> Sensitive Base64
passphrase) (\s :: ExportCertificate
s@ExportCertificate' {} Sensitive Base64
a -> ExportCertificate
s {$sel:passphrase:ExportCertificate' :: Sensitive Base64
passphrase = Sensitive Base64
a} :: ExportCertificate) forall b c a. (b -> c) -> (a -> b) -> a -> c
Prelude.. forall a. Iso' (Sensitive a) a
Data._Sensitive forall b c a. (b -> c) -> (a -> b) -> a -> c
Prelude.. Iso' Base64 ByteString
Data._Base64

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

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

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

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

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

-- | /See:/ 'newExportCertificateResponse' smart constructor.
data ExportCertificateResponse = ExportCertificateResponse'
  { -- | The base64 PEM-encoded certificate.
    ExportCertificateResponse -> Maybe Text
certificate :: Prelude.Maybe Prelude.Text,
    -- | The base64 PEM-encoded certificate chain. This does not include the
    -- certificate that you are exporting.
    ExportCertificateResponse -> Maybe Text
certificateChain :: Prelude.Maybe Prelude.Text,
    -- | The encrypted private key associated with the public key in the
    -- certificate. The key is output in PKCS #8 format and is base64
    -- PEM-encoded.
    ExportCertificateResponse -> Maybe (Sensitive Text)
privateKey :: Prelude.Maybe (Data.Sensitive Prelude.Text),
    -- | The response's http status code.
    ExportCertificateResponse -> Int
httpStatus :: Prelude.Int
  }
  deriving (ExportCertificateResponse -> ExportCertificateResponse -> Bool
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: ExportCertificateResponse -> ExportCertificateResponse -> Bool
$c/= :: ExportCertificateResponse -> ExportCertificateResponse -> Bool
== :: ExportCertificateResponse -> ExportCertificateResponse -> Bool
$c== :: ExportCertificateResponse -> ExportCertificateResponse -> Bool
Prelude.Eq, Int -> ExportCertificateResponse -> ShowS
[ExportCertificateResponse] -> ShowS
ExportCertificateResponse -> String
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [ExportCertificateResponse] -> ShowS
$cshowList :: [ExportCertificateResponse] -> ShowS
show :: ExportCertificateResponse -> String
$cshow :: ExportCertificateResponse -> String
showsPrec :: Int -> ExportCertificateResponse -> ShowS
$cshowsPrec :: Int -> ExportCertificateResponse -> ShowS
Prelude.Show, forall x.
Rep ExportCertificateResponse x -> ExportCertificateResponse
forall x.
ExportCertificateResponse -> Rep ExportCertificateResponse x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cto :: forall x.
Rep ExportCertificateResponse x -> ExportCertificateResponse
$cfrom :: forall x.
ExportCertificateResponse -> Rep ExportCertificateResponse x
Prelude.Generic)

-- |
-- Create a value of 'ExportCertificateResponse' 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', 'exportCertificateResponse_certificate' - The base64 PEM-encoded certificate.
--
-- 'certificateChain', 'exportCertificateResponse_certificateChain' - The base64 PEM-encoded certificate chain. This does not include the
-- certificate that you are exporting.
--
-- 'privateKey', 'exportCertificateResponse_privateKey' - The encrypted private key associated with the public key in the
-- certificate. The key is output in PKCS #8 format and is base64
-- PEM-encoded.
--
-- 'httpStatus', 'exportCertificateResponse_httpStatus' - The response's http status code.
newExportCertificateResponse ::
  -- | 'httpStatus'
  Prelude.Int ->
  ExportCertificateResponse
newExportCertificateResponse :: Int -> ExportCertificateResponse
newExportCertificateResponse Int
pHttpStatus_ =
  ExportCertificateResponse'
    { $sel:certificate:ExportCertificateResponse' :: Maybe Text
certificate =
        forall a. Maybe a
Prelude.Nothing,
      $sel:certificateChain:ExportCertificateResponse' :: Maybe Text
certificateChain = forall a. Maybe a
Prelude.Nothing,
      $sel:privateKey:ExportCertificateResponse' :: Maybe (Sensitive Text)
privateKey = forall a. Maybe a
Prelude.Nothing,
      $sel:httpStatus:ExportCertificateResponse' :: Int
httpStatus = Int
pHttpStatus_
    }

-- | The base64 PEM-encoded certificate.
exportCertificateResponse_certificate :: Lens.Lens' ExportCertificateResponse (Prelude.Maybe Prelude.Text)
exportCertificateResponse_certificate :: Lens' ExportCertificateResponse (Maybe Text)
exportCertificateResponse_certificate = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\ExportCertificateResponse' {Maybe Text
certificate :: Maybe Text
$sel:certificate:ExportCertificateResponse' :: ExportCertificateResponse -> Maybe Text
certificate} -> Maybe Text
certificate) (\s :: ExportCertificateResponse
s@ExportCertificateResponse' {} Maybe Text
a -> ExportCertificateResponse
s {$sel:certificate:ExportCertificateResponse' :: Maybe Text
certificate = Maybe Text
a} :: ExportCertificateResponse)

-- | The base64 PEM-encoded certificate chain. This does not include the
-- certificate that you are exporting.
exportCertificateResponse_certificateChain :: Lens.Lens' ExportCertificateResponse (Prelude.Maybe Prelude.Text)
exportCertificateResponse_certificateChain :: Lens' ExportCertificateResponse (Maybe Text)
exportCertificateResponse_certificateChain = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\ExportCertificateResponse' {Maybe Text
certificateChain :: Maybe Text
$sel:certificateChain:ExportCertificateResponse' :: ExportCertificateResponse -> Maybe Text
certificateChain} -> Maybe Text
certificateChain) (\s :: ExportCertificateResponse
s@ExportCertificateResponse' {} Maybe Text
a -> ExportCertificateResponse
s {$sel:certificateChain:ExportCertificateResponse' :: Maybe Text
certificateChain = Maybe Text
a} :: ExportCertificateResponse)

-- | The encrypted private key associated with the public key in the
-- certificate. The key is output in PKCS #8 format and is base64
-- PEM-encoded.
exportCertificateResponse_privateKey :: Lens.Lens' ExportCertificateResponse (Prelude.Maybe Prelude.Text)
exportCertificateResponse_privateKey :: Lens' ExportCertificateResponse (Maybe Text)
exportCertificateResponse_privateKey = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\ExportCertificateResponse' {Maybe (Sensitive Text)
privateKey :: Maybe (Sensitive Text)
$sel:privateKey:ExportCertificateResponse' :: ExportCertificateResponse -> Maybe (Sensitive Text)
privateKey} -> Maybe (Sensitive Text)
privateKey) (\s :: ExportCertificateResponse
s@ExportCertificateResponse' {} Maybe (Sensitive Text)
a -> ExportCertificateResponse
s {$sel:privateKey:ExportCertificateResponse' :: Maybe (Sensitive Text)
privateKey = Maybe (Sensitive Text)
a} :: ExportCertificateResponse) forall b c a. (b -> c) -> (a -> b) -> a -> c
Prelude.. forall (f :: * -> *) (g :: * -> *) s t a b.
(Functor f, Functor g) =>
AnIso s t a b -> Iso (f s) (g t) (f a) (g b)
Lens.mapping forall a. Iso' (Sensitive a) a
Data._Sensitive

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

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