{-# 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.RenewCertificate
-- Copyright   : (c) 2013-2023 Brendan Hay
-- License     : Mozilla Public License, v. 2.0.
-- Maintainer  : Brendan Hay
-- Stability   : auto-generated
-- Portability : non-portable (GHC extensions)
--
-- Renews an eligible ACM certificate. At this time, only exported private
-- certificates can be renewed with this operation. In order to renew your
-- Amazon Web Services Private CA certificates with ACM, you must first
-- <https://docs.aws.amazon.com/privateca/latest/userguide/PcaPermissions.html grant the ACM service principal permission to do so>.
-- For more information, see
-- <https://docs.aws.amazon.com/acm/latest/userguide/manual-renewal.html Testing Managed Renewal>
-- in the ACM User Guide.
module Amazonka.CertificateManager.RenewCertificate
  ( -- * Creating a Request
    RenewCertificate (..),
    newRenewCertificate,

    -- * Request Lenses
    renewCertificate_certificateArn,

    -- * Destructuring the Response
    RenewCertificateResponse (..),
    newRenewCertificateResponse,
  )
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:/ 'newRenewCertificate' smart constructor.
data RenewCertificate = RenewCertificate'
  { -- | String that contains the ARN of the ACM certificate to be renewed. This
    -- must be of the form:
    --
    -- @arn:aws:acm:region:123456789012:certificate\/12345678-1234-1234-1234-123456789012@
    --
    -- For more information about ARNs, see
    -- <https://docs.aws.amazon.com/general/latest/gr/aws-arns-and-namespaces.html Amazon Resource Names (ARNs)>.
    RenewCertificate -> Text
certificateArn :: Prelude.Text
  }
  deriving (RenewCertificate -> RenewCertificate -> Bool
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: RenewCertificate -> RenewCertificate -> Bool
$c/= :: RenewCertificate -> RenewCertificate -> Bool
== :: RenewCertificate -> RenewCertificate -> Bool
$c== :: RenewCertificate -> RenewCertificate -> Bool
Prelude.Eq, ReadPrec [RenewCertificate]
ReadPrec RenewCertificate
Int -> ReadS RenewCertificate
ReadS [RenewCertificate]
forall a.
(Int -> ReadS a)
-> ReadS [a] -> ReadPrec a -> ReadPrec [a] -> Read a
readListPrec :: ReadPrec [RenewCertificate]
$creadListPrec :: ReadPrec [RenewCertificate]
readPrec :: ReadPrec RenewCertificate
$creadPrec :: ReadPrec RenewCertificate
readList :: ReadS [RenewCertificate]
$creadList :: ReadS [RenewCertificate]
readsPrec :: Int -> ReadS RenewCertificate
$creadsPrec :: Int -> ReadS RenewCertificate
Prelude.Read, Int -> RenewCertificate -> ShowS
[RenewCertificate] -> ShowS
RenewCertificate -> String
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [RenewCertificate] -> ShowS
$cshowList :: [RenewCertificate] -> ShowS
show :: RenewCertificate -> String
$cshow :: RenewCertificate -> String
showsPrec :: Int -> RenewCertificate -> ShowS
$cshowsPrec :: Int -> RenewCertificate -> ShowS
Prelude.Show, forall x. Rep RenewCertificate x -> RenewCertificate
forall x. RenewCertificate -> Rep RenewCertificate x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cto :: forall x. Rep RenewCertificate x -> RenewCertificate
$cfrom :: forall x. RenewCertificate -> Rep RenewCertificate x
Prelude.Generic)

-- |
-- Create a value of 'RenewCertificate' 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', 'renewCertificate_certificateArn' - String that contains the ARN of the ACM certificate to be renewed. This
-- must be of the form:
--
-- @arn:aws:acm:region:123456789012:certificate\/12345678-1234-1234-1234-123456789012@
--
-- For more information about ARNs, see
-- <https://docs.aws.amazon.com/general/latest/gr/aws-arns-and-namespaces.html Amazon Resource Names (ARNs)>.
newRenewCertificate ::
  -- | 'certificateArn'
  Prelude.Text ->
  RenewCertificate
newRenewCertificate :: Text -> RenewCertificate
newRenewCertificate Text
pCertificateArn_ =
  RenewCertificate'
    { $sel:certificateArn:RenewCertificate' :: Text
certificateArn =
        Text
pCertificateArn_
    }

-- | String that contains the ARN of the ACM certificate to be renewed. This
-- must be of the form:
--
-- @arn:aws:acm:region:123456789012:certificate\/12345678-1234-1234-1234-123456789012@
--
-- For more information about ARNs, see
-- <https://docs.aws.amazon.com/general/latest/gr/aws-arns-and-namespaces.html Amazon Resource Names (ARNs)>.
renewCertificate_certificateArn :: Lens.Lens' RenewCertificate Prelude.Text
renewCertificate_certificateArn :: Lens' RenewCertificate Text
renewCertificate_certificateArn = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\RenewCertificate' {Text
certificateArn :: Text
$sel:certificateArn:RenewCertificate' :: RenewCertificate -> Text
certificateArn} -> Text
certificateArn) (\s :: RenewCertificate
s@RenewCertificate' {} Text
a -> RenewCertificate
s {$sel:certificateArn:RenewCertificate' :: Text
certificateArn = Text
a} :: RenewCertificate)

instance Core.AWSRequest RenewCertificate where
  type
    AWSResponse RenewCertificate =
      RenewCertificateResponse
  request :: (Service -> Service)
-> RenewCertificate -> Request RenewCertificate
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 RenewCertificate
-> ClientResponse ClientBody
-> m (Either Error (ClientResponse (AWSResponse RenewCertificate)))
response =
    forall (m :: * -> *) a.
MonadResource m =>
AWSResponse a
-> (ByteStringLazy -> IO ByteStringLazy)
-> Service
-> Proxy a
-> ClientResponse ClientBody
-> m (Either Error (ClientResponse (AWSResponse a)))
Response.receiveNull RenewCertificateResponse
RenewCertificateResponse'

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

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

instance Data.ToHeaders RenewCertificate where
  toHeaders :: RenewCertificate -> [Header]
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 -> [Header]
Data.=# ( ByteString
"CertificateManager.RenewCertificate" ::
                          Prelude.ByteString
                      ),
            HeaderName
"Content-Type"
              forall a. ToHeader a => HeaderName -> a -> [Header]
Data.=# ( ByteString
"application/x-amz-json-1.1" ::
                          Prelude.ByteString
                      )
          ]
      )

instance Data.ToJSON RenewCertificate where
  toJSON :: RenewCertificate -> Value
toJSON RenewCertificate' {Text
certificateArn :: Text
$sel:certificateArn:RenewCertificate' :: RenewCertificate -> 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)
          ]
      )

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

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

-- | /See:/ 'newRenewCertificateResponse' smart constructor.
data RenewCertificateResponse = RenewCertificateResponse'
  {
  }
  deriving (RenewCertificateResponse -> RenewCertificateResponse -> Bool
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: RenewCertificateResponse -> RenewCertificateResponse -> Bool
$c/= :: RenewCertificateResponse -> RenewCertificateResponse -> Bool
== :: RenewCertificateResponse -> RenewCertificateResponse -> Bool
$c== :: RenewCertificateResponse -> RenewCertificateResponse -> Bool
Prelude.Eq, ReadPrec [RenewCertificateResponse]
ReadPrec RenewCertificateResponse
Int -> ReadS RenewCertificateResponse
ReadS [RenewCertificateResponse]
forall a.
(Int -> ReadS a)
-> ReadS [a] -> ReadPrec a -> ReadPrec [a] -> Read a
readListPrec :: ReadPrec [RenewCertificateResponse]
$creadListPrec :: ReadPrec [RenewCertificateResponse]
readPrec :: ReadPrec RenewCertificateResponse
$creadPrec :: ReadPrec RenewCertificateResponse
readList :: ReadS [RenewCertificateResponse]
$creadList :: ReadS [RenewCertificateResponse]
readsPrec :: Int -> ReadS RenewCertificateResponse
$creadsPrec :: Int -> ReadS RenewCertificateResponse
Prelude.Read, Int -> RenewCertificateResponse -> ShowS
[RenewCertificateResponse] -> ShowS
RenewCertificateResponse -> String
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [RenewCertificateResponse] -> ShowS
$cshowList :: [RenewCertificateResponse] -> ShowS
show :: RenewCertificateResponse -> String
$cshow :: RenewCertificateResponse -> String
showsPrec :: Int -> RenewCertificateResponse -> ShowS
$cshowsPrec :: Int -> RenewCertificateResponse -> ShowS
Prelude.Show, forall x.
Rep RenewCertificateResponse x -> RenewCertificateResponse
forall x.
RenewCertificateResponse -> Rep RenewCertificateResponse x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cto :: forall x.
Rep RenewCertificateResponse x -> RenewCertificateResponse
$cfrom :: forall x.
RenewCertificateResponse -> Rep RenewCertificateResponse x
Prelude.Generic)

-- |
-- Create a value of 'RenewCertificateResponse' 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.
newRenewCertificateResponse ::
  RenewCertificateResponse
newRenewCertificateResponse :: RenewCertificateResponse
newRenewCertificateResponse =
  RenewCertificateResponse
RenewCertificateResponse'

instance Prelude.NFData RenewCertificateResponse where
  rnf :: RenewCertificateResponse -> ()
rnf RenewCertificateResponse
_ = ()