{-# 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.Lightsail.AttachCertificateToDistribution
-- Copyright   : (c) 2013-2023 Brendan Hay
-- License     : Mozilla Public License, v. 2.0.
-- Maintainer  : Brendan Hay
-- Stability   : auto-generated
-- Portability : non-portable (GHC extensions)
--
-- Attaches an SSL\/TLS certificate to your Amazon Lightsail content
-- delivery network (CDN) distribution.
--
-- After the certificate is attached, your distribution accepts HTTPS
-- traffic for all of the domains that are associated with the certificate.
--
-- Use the @CreateCertificate@ action to create a certificate that you can
-- attach to your distribution.
--
-- Only certificates created in the @us-east-1@ Amazon Web Services Region
-- can be attached to Lightsail distributions. Lightsail distributions are
-- global resources that can reference an origin in any Amazon Web Services
-- Region, and distribute its content globally. However, all distributions
-- are located in the @us-east-1@ Region.
module Amazonka.Lightsail.AttachCertificateToDistribution
  ( -- * Creating a Request
    AttachCertificateToDistribution (..),
    newAttachCertificateToDistribution,

    -- * Request Lenses
    attachCertificateToDistribution_distributionName,
    attachCertificateToDistribution_certificateName,

    -- * Destructuring the Response
    AttachCertificateToDistributionResponse (..),
    newAttachCertificateToDistributionResponse,

    -- * Response Lenses
    attachCertificateToDistributionResponse_operation,
    attachCertificateToDistributionResponse_httpStatus,
  )
where

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

-- | /See:/ 'newAttachCertificateToDistribution' smart constructor.
data AttachCertificateToDistribution = AttachCertificateToDistribution'
  { -- | The name of the distribution that the certificate will be attached to.
    --
    -- Use the @GetDistributions@ action to get a list of distribution names
    -- that you can specify.
    AttachCertificateToDistribution -> Text
distributionName :: Prelude.Text,
    -- | The name of the certificate to attach to a distribution.
    --
    -- Only certificates with a status of @ISSUED@ can be attached to a
    -- distribution.
    --
    -- Use the @GetCertificates@ action to get a list of certificate names that
    -- you can specify.
    --
    -- This is the name of the certificate resource type and is used only to
    -- reference the certificate in other API actions. It can be different than
    -- the domain name of the certificate. For example, your certificate name
    -- might be @WordPress-Blog-Certificate@ and the domain name of the
    -- certificate might be @example.com@.
    AttachCertificateToDistribution -> Text
certificateName :: Prelude.Text
  }
  deriving (AttachCertificateToDistribution
-> AttachCertificateToDistribution -> Bool
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: AttachCertificateToDistribution
-> AttachCertificateToDistribution -> Bool
$c/= :: AttachCertificateToDistribution
-> AttachCertificateToDistribution -> Bool
== :: AttachCertificateToDistribution
-> AttachCertificateToDistribution -> Bool
$c== :: AttachCertificateToDistribution
-> AttachCertificateToDistribution -> Bool
Prelude.Eq, ReadPrec [AttachCertificateToDistribution]
ReadPrec AttachCertificateToDistribution
Int -> ReadS AttachCertificateToDistribution
ReadS [AttachCertificateToDistribution]
forall a.
(Int -> ReadS a)
-> ReadS [a] -> ReadPrec a -> ReadPrec [a] -> Read a
readListPrec :: ReadPrec [AttachCertificateToDistribution]
$creadListPrec :: ReadPrec [AttachCertificateToDistribution]
readPrec :: ReadPrec AttachCertificateToDistribution
$creadPrec :: ReadPrec AttachCertificateToDistribution
readList :: ReadS [AttachCertificateToDistribution]
$creadList :: ReadS [AttachCertificateToDistribution]
readsPrec :: Int -> ReadS AttachCertificateToDistribution
$creadsPrec :: Int -> ReadS AttachCertificateToDistribution
Prelude.Read, Int -> AttachCertificateToDistribution -> ShowS
[AttachCertificateToDistribution] -> ShowS
AttachCertificateToDistribution -> String
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [AttachCertificateToDistribution] -> ShowS
$cshowList :: [AttachCertificateToDistribution] -> ShowS
show :: AttachCertificateToDistribution -> String
$cshow :: AttachCertificateToDistribution -> String
showsPrec :: Int -> AttachCertificateToDistribution -> ShowS
$cshowsPrec :: Int -> AttachCertificateToDistribution -> ShowS
Prelude.Show, forall x.
Rep AttachCertificateToDistribution x
-> AttachCertificateToDistribution
forall x.
AttachCertificateToDistribution
-> Rep AttachCertificateToDistribution x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cto :: forall x.
Rep AttachCertificateToDistribution x
-> AttachCertificateToDistribution
$cfrom :: forall x.
AttachCertificateToDistribution
-> Rep AttachCertificateToDistribution x
Prelude.Generic)

-- |
-- Create a value of 'AttachCertificateToDistribution' 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:
--
-- 'distributionName', 'attachCertificateToDistribution_distributionName' - The name of the distribution that the certificate will be attached to.
--
-- Use the @GetDistributions@ action to get a list of distribution names
-- that you can specify.
--
-- 'certificateName', 'attachCertificateToDistribution_certificateName' - The name of the certificate to attach to a distribution.
--
-- Only certificates with a status of @ISSUED@ can be attached to a
-- distribution.
--
-- Use the @GetCertificates@ action to get a list of certificate names that
-- you can specify.
--
-- This is the name of the certificate resource type and is used only to
-- reference the certificate in other API actions. It can be different than
-- the domain name of the certificate. For example, your certificate name
-- might be @WordPress-Blog-Certificate@ and the domain name of the
-- certificate might be @example.com@.
newAttachCertificateToDistribution ::
  -- | 'distributionName'
  Prelude.Text ->
  -- | 'certificateName'
  Prelude.Text ->
  AttachCertificateToDistribution
newAttachCertificateToDistribution :: Text -> Text -> AttachCertificateToDistribution
newAttachCertificateToDistribution
  Text
pDistributionName_
  Text
pCertificateName_ =
    AttachCertificateToDistribution'
      { $sel:distributionName:AttachCertificateToDistribution' :: Text
distributionName =
          Text
pDistributionName_,
        $sel:certificateName:AttachCertificateToDistribution' :: Text
certificateName = Text
pCertificateName_
      }

-- | The name of the distribution that the certificate will be attached to.
--
-- Use the @GetDistributions@ action to get a list of distribution names
-- that you can specify.
attachCertificateToDistribution_distributionName :: Lens.Lens' AttachCertificateToDistribution Prelude.Text
attachCertificateToDistribution_distributionName :: Lens' AttachCertificateToDistribution Text
attachCertificateToDistribution_distributionName = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\AttachCertificateToDistribution' {Text
distributionName :: Text
$sel:distributionName:AttachCertificateToDistribution' :: AttachCertificateToDistribution -> Text
distributionName} -> Text
distributionName) (\s :: AttachCertificateToDistribution
s@AttachCertificateToDistribution' {} Text
a -> AttachCertificateToDistribution
s {$sel:distributionName:AttachCertificateToDistribution' :: Text
distributionName = Text
a} :: AttachCertificateToDistribution)

-- | The name of the certificate to attach to a distribution.
--
-- Only certificates with a status of @ISSUED@ can be attached to a
-- distribution.
--
-- Use the @GetCertificates@ action to get a list of certificate names that
-- you can specify.
--
-- This is the name of the certificate resource type and is used only to
-- reference the certificate in other API actions. It can be different than
-- the domain name of the certificate. For example, your certificate name
-- might be @WordPress-Blog-Certificate@ and the domain name of the
-- certificate might be @example.com@.
attachCertificateToDistribution_certificateName :: Lens.Lens' AttachCertificateToDistribution Prelude.Text
attachCertificateToDistribution_certificateName :: Lens' AttachCertificateToDistribution Text
attachCertificateToDistribution_certificateName = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\AttachCertificateToDistribution' {Text
certificateName :: Text
$sel:certificateName:AttachCertificateToDistribution' :: AttachCertificateToDistribution -> Text
certificateName} -> Text
certificateName) (\s :: AttachCertificateToDistribution
s@AttachCertificateToDistribution' {} Text
a -> AttachCertificateToDistribution
s {$sel:certificateName:AttachCertificateToDistribution' :: Text
certificateName = Text
a} :: AttachCertificateToDistribution)

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

instance
  Prelude.NFData
    AttachCertificateToDistribution
  where
  rnf :: AttachCertificateToDistribution -> ()
rnf AttachCertificateToDistribution' {Text
certificateName :: Text
distributionName :: Text
$sel:certificateName:AttachCertificateToDistribution' :: AttachCertificateToDistribution -> Text
$sel:distributionName:AttachCertificateToDistribution' :: AttachCertificateToDistribution -> Text
..} =
    forall a. NFData a => a -> ()
Prelude.rnf Text
distributionName
      seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf Text
certificateName

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

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

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

-- | /See:/ 'newAttachCertificateToDistributionResponse' smart constructor.
data AttachCertificateToDistributionResponse = AttachCertificateToDistributionResponse'
  { -- | An object that describes the result of the action, such as the status of
    -- the request, the timestamp of the request, and the resources affected by
    -- the request.
    AttachCertificateToDistributionResponse -> Maybe Operation
operation :: Prelude.Maybe Operation,
    -- | The response's http status code.
    AttachCertificateToDistributionResponse -> Int
httpStatus :: Prelude.Int
  }
  deriving (AttachCertificateToDistributionResponse
-> AttachCertificateToDistributionResponse -> Bool
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: AttachCertificateToDistributionResponse
-> AttachCertificateToDistributionResponse -> Bool
$c/= :: AttachCertificateToDistributionResponse
-> AttachCertificateToDistributionResponse -> Bool
== :: AttachCertificateToDistributionResponse
-> AttachCertificateToDistributionResponse -> Bool
$c== :: AttachCertificateToDistributionResponse
-> AttachCertificateToDistributionResponse -> Bool
Prelude.Eq, ReadPrec [AttachCertificateToDistributionResponse]
ReadPrec AttachCertificateToDistributionResponse
Int -> ReadS AttachCertificateToDistributionResponse
ReadS [AttachCertificateToDistributionResponse]
forall a.
(Int -> ReadS a)
-> ReadS [a] -> ReadPrec a -> ReadPrec [a] -> Read a
readListPrec :: ReadPrec [AttachCertificateToDistributionResponse]
$creadListPrec :: ReadPrec [AttachCertificateToDistributionResponse]
readPrec :: ReadPrec AttachCertificateToDistributionResponse
$creadPrec :: ReadPrec AttachCertificateToDistributionResponse
readList :: ReadS [AttachCertificateToDistributionResponse]
$creadList :: ReadS [AttachCertificateToDistributionResponse]
readsPrec :: Int -> ReadS AttachCertificateToDistributionResponse
$creadsPrec :: Int -> ReadS AttachCertificateToDistributionResponse
Prelude.Read, Int -> AttachCertificateToDistributionResponse -> ShowS
[AttachCertificateToDistributionResponse] -> ShowS
AttachCertificateToDistributionResponse -> String
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [AttachCertificateToDistributionResponse] -> ShowS
$cshowList :: [AttachCertificateToDistributionResponse] -> ShowS
show :: AttachCertificateToDistributionResponse -> String
$cshow :: AttachCertificateToDistributionResponse -> String
showsPrec :: Int -> AttachCertificateToDistributionResponse -> ShowS
$cshowsPrec :: Int -> AttachCertificateToDistributionResponse -> ShowS
Prelude.Show, forall x.
Rep AttachCertificateToDistributionResponse x
-> AttachCertificateToDistributionResponse
forall x.
AttachCertificateToDistributionResponse
-> Rep AttachCertificateToDistributionResponse x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cto :: forall x.
Rep AttachCertificateToDistributionResponse x
-> AttachCertificateToDistributionResponse
$cfrom :: forall x.
AttachCertificateToDistributionResponse
-> Rep AttachCertificateToDistributionResponse x
Prelude.Generic)

-- |
-- Create a value of 'AttachCertificateToDistributionResponse' 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:
--
-- 'operation', 'attachCertificateToDistributionResponse_operation' - An object that describes the result of the action, such as the status of
-- the request, the timestamp of the request, and the resources affected by
-- the request.
--
-- 'httpStatus', 'attachCertificateToDistributionResponse_httpStatus' - The response's http status code.
newAttachCertificateToDistributionResponse ::
  -- | 'httpStatus'
  Prelude.Int ->
  AttachCertificateToDistributionResponse
newAttachCertificateToDistributionResponse :: Int -> AttachCertificateToDistributionResponse
newAttachCertificateToDistributionResponse
  Int
pHttpStatus_ =
    AttachCertificateToDistributionResponse'
      { $sel:operation:AttachCertificateToDistributionResponse' :: Maybe Operation
operation =
          forall a. Maybe a
Prelude.Nothing,
        $sel:httpStatus:AttachCertificateToDistributionResponse' :: Int
httpStatus = Int
pHttpStatus_
      }

-- | An object that describes the result of the action, such as the status of
-- the request, the timestamp of the request, and the resources affected by
-- the request.
attachCertificateToDistributionResponse_operation :: Lens.Lens' AttachCertificateToDistributionResponse (Prelude.Maybe Operation)
attachCertificateToDistributionResponse_operation :: Lens' AttachCertificateToDistributionResponse (Maybe Operation)
attachCertificateToDistributionResponse_operation = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\AttachCertificateToDistributionResponse' {Maybe Operation
operation :: Maybe Operation
$sel:operation:AttachCertificateToDistributionResponse' :: AttachCertificateToDistributionResponse -> Maybe Operation
operation} -> Maybe Operation
operation) (\s :: AttachCertificateToDistributionResponse
s@AttachCertificateToDistributionResponse' {} Maybe Operation
a -> AttachCertificateToDistributionResponse
s {$sel:operation:AttachCertificateToDistributionResponse' :: Maybe Operation
operation = Maybe Operation
a} :: AttachCertificateToDistributionResponse)

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

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