{-# 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.ELBV2.AddListenerCertificates
-- Copyright   : (c) 2013-2023 Brendan Hay
-- License     : Mozilla Public License, v. 2.0.
-- Maintainer  : Brendan Hay
-- Stability   : auto-generated
-- Portability : non-portable (GHC extensions)
--
-- Adds the specified SSL server certificate to the certificate list for
-- the specified HTTPS or TLS listener.
--
-- If the certificate in already in the certificate list, the call is
-- successful but the certificate is not added again.
--
-- For more information, see
-- <https://docs.aws.amazon.com/elasticloadbalancing/latest/application/create-https-listener.html HTTPS listeners>
-- in the /Application Load Balancers Guide/ or
-- <https://docs.aws.amazon.com/elasticloadbalancing/latest/network/create-tls-listener.html TLS listeners>
-- in the /Network Load Balancers Guide/.
module Amazonka.ELBV2.AddListenerCertificates
  ( -- * Creating a Request
    AddListenerCertificates (..),
    newAddListenerCertificates,

    -- * Request Lenses
    addListenerCertificates_listenerArn,
    addListenerCertificates_certificates,

    -- * Destructuring the Response
    AddListenerCertificatesResponse (..),
    newAddListenerCertificatesResponse,

    -- * Response Lenses
    addListenerCertificatesResponse_certificates,
    addListenerCertificatesResponse_httpStatus,
  )
where

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

-- | /See:/ 'newAddListenerCertificates' smart constructor.
data AddListenerCertificates = AddListenerCertificates'
  { -- | The Amazon Resource Name (ARN) of the listener.
    AddListenerCertificates -> Text
listenerArn :: Prelude.Text,
    -- | The certificate to add. You can specify one certificate per call. Set
    -- @CertificateArn@ to the certificate ARN but do not set @IsDefault@.
    AddListenerCertificates -> [Certificate]
certificates :: [Certificate]
  }
  deriving (AddListenerCertificates -> AddListenerCertificates -> Bool
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: AddListenerCertificates -> AddListenerCertificates -> Bool
$c/= :: AddListenerCertificates -> AddListenerCertificates -> Bool
== :: AddListenerCertificates -> AddListenerCertificates -> Bool
$c== :: AddListenerCertificates -> AddListenerCertificates -> Bool
Prelude.Eq, ReadPrec [AddListenerCertificates]
ReadPrec AddListenerCertificates
Int -> ReadS AddListenerCertificates
ReadS [AddListenerCertificates]
forall a.
(Int -> ReadS a)
-> ReadS [a] -> ReadPrec a -> ReadPrec [a] -> Read a
readListPrec :: ReadPrec [AddListenerCertificates]
$creadListPrec :: ReadPrec [AddListenerCertificates]
readPrec :: ReadPrec AddListenerCertificates
$creadPrec :: ReadPrec AddListenerCertificates
readList :: ReadS [AddListenerCertificates]
$creadList :: ReadS [AddListenerCertificates]
readsPrec :: Int -> ReadS AddListenerCertificates
$creadsPrec :: Int -> ReadS AddListenerCertificates
Prelude.Read, Int -> AddListenerCertificates -> ShowS
[AddListenerCertificates] -> ShowS
AddListenerCertificates -> String
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [AddListenerCertificates] -> ShowS
$cshowList :: [AddListenerCertificates] -> ShowS
show :: AddListenerCertificates -> String
$cshow :: AddListenerCertificates -> String
showsPrec :: Int -> AddListenerCertificates -> ShowS
$cshowsPrec :: Int -> AddListenerCertificates -> ShowS
Prelude.Show, forall x. Rep AddListenerCertificates x -> AddListenerCertificates
forall x. AddListenerCertificates -> Rep AddListenerCertificates x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cto :: forall x. Rep AddListenerCertificates x -> AddListenerCertificates
$cfrom :: forall x. AddListenerCertificates -> Rep AddListenerCertificates x
Prelude.Generic)

-- |
-- Create a value of 'AddListenerCertificates' 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:
--
-- 'listenerArn', 'addListenerCertificates_listenerArn' - The Amazon Resource Name (ARN) of the listener.
--
-- 'certificates', 'addListenerCertificates_certificates' - The certificate to add. You can specify one certificate per call. Set
-- @CertificateArn@ to the certificate ARN but do not set @IsDefault@.
newAddListenerCertificates ::
  -- | 'listenerArn'
  Prelude.Text ->
  AddListenerCertificates
newAddListenerCertificates :: Text -> AddListenerCertificates
newAddListenerCertificates Text
pListenerArn_ =
  AddListenerCertificates'
    { $sel:listenerArn:AddListenerCertificates' :: Text
listenerArn =
        Text
pListenerArn_,
      $sel:certificates:AddListenerCertificates' :: [Certificate]
certificates = forall a. Monoid a => a
Prelude.mempty
    }

-- | The Amazon Resource Name (ARN) of the listener.
addListenerCertificates_listenerArn :: Lens.Lens' AddListenerCertificates Prelude.Text
addListenerCertificates_listenerArn :: Lens' AddListenerCertificates Text
addListenerCertificates_listenerArn = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\AddListenerCertificates' {Text
listenerArn :: Text
$sel:listenerArn:AddListenerCertificates' :: AddListenerCertificates -> Text
listenerArn} -> Text
listenerArn) (\s :: AddListenerCertificates
s@AddListenerCertificates' {} Text
a -> AddListenerCertificates
s {$sel:listenerArn:AddListenerCertificates' :: Text
listenerArn = Text
a} :: AddListenerCertificates)

-- | The certificate to add. You can specify one certificate per call. Set
-- @CertificateArn@ to the certificate ARN but do not set @IsDefault@.
addListenerCertificates_certificates :: Lens.Lens' AddListenerCertificates [Certificate]
addListenerCertificates_certificates :: Lens' AddListenerCertificates [Certificate]
addListenerCertificates_certificates = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\AddListenerCertificates' {[Certificate]
certificates :: [Certificate]
$sel:certificates:AddListenerCertificates' :: AddListenerCertificates -> [Certificate]
certificates} -> [Certificate]
certificates) (\s :: AddListenerCertificates
s@AddListenerCertificates' {} [Certificate]
a -> AddListenerCertificates
s {$sel:certificates:AddListenerCertificates' :: [Certificate]
certificates = [Certificate]
a} :: AddListenerCertificates) forall b c a. (b -> c) -> (a -> b) -> a -> c
Prelude.. forall s t a b. (Coercible s a, Coercible t b) => Iso s t a b
Lens.coerced

instance Core.AWSRequest AddListenerCertificates where
  type
    AWSResponse AddListenerCertificates =
      AddListenerCertificatesResponse
  request :: (Service -> Service)
-> AddListenerCertificates -> Request AddListenerCertificates
request Service -> Service
overrides =
    forall a. ToRequest a => Service -> a -> Request a
Request.postQuery (Service -> Service
overrides Service
defaultService)
  response :: forall (m :: * -> *).
MonadResource m =>
(ByteStringLazy -> IO ByteStringLazy)
-> Service
-> Proxy AddListenerCertificates
-> ClientResponse ClientBody
-> m (Either
        Error (ClientResponse (AWSResponse AddListenerCertificates)))
response =
    forall (m :: * -> *) a.
MonadResource m =>
Text
-> (Int
    -> ResponseHeaders -> [Node] -> Either String (AWSResponse a))
-> (ByteStringLazy -> IO ByteStringLazy)
-> Service
-> Proxy a
-> ClientResponse ClientBody
-> m (Either Error (ClientResponse (AWSResponse a)))
Response.receiveXMLWrapper
      Text
"AddListenerCertificatesResult"
      ( \Int
s ResponseHeaders
h [Node]
x ->
          Maybe [Certificate] -> Int -> AddListenerCertificatesResponse
AddListenerCertificatesResponse'
            forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
Prelude.<$> ( [Node]
x
                            forall a. FromXML a => [Node] -> Text -> Either String (Maybe a)
Data..@? Text
"Certificates"
                            forall (f :: * -> *) a. Functor f => f (Maybe a) -> a -> f a
Core..!@ forall a. Monoid a => a
Prelude.mempty
                            forall (m :: * -> *) a b. Monad m => m a -> (a -> m b) -> m b
Prelude.>>= forall (f :: * -> *) a b.
Applicative f =>
([a] -> f b) -> [a] -> f (Maybe b)
Core.may (forall a. FromXML a => Text -> [Node] -> Either String [a]
Data.parseXMLList Text
"member")
                        )
            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 AddListenerCertificates where
  hashWithSalt :: Int -> AddListenerCertificates -> Int
hashWithSalt Int
_salt AddListenerCertificates' {[Certificate]
Text
certificates :: [Certificate]
listenerArn :: Text
$sel:certificates:AddListenerCertificates' :: AddListenerCertificates -> [Certificate]
$sel:listenerArn:AddListenerCertificates' :: AddListenerCertificates -> Text
..} =
    Int
_salt
      forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Text
listenerArn
      forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` [Certificate]
certificates

instance Prelude.NFData AddListenerCertificates where
  rnf :: AddListenerCertificates -> ()
rnf AddListenerCertificates' {[Certificate]
Text
certificates :: [Certificate]
listenerArn :: Text
$sel:certificates:AddListenerCertificates' :: AddListenerCertificates -> [Certificate]
$sel:listenerArn:AddListenerCertificates' :: AddListenerCertificates -> Text
..} =
    forall a. NFData a => a -> ()
Prelude.rnf Text
listenerArn
      seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf [Certificate]
certificates

instance Data.ToHeaders AddListenerCertificates where
  toHeaders :: AddListenerCertificates -> ResponseHeaders
toHeaders = forall a b. a -> b -> a
Prelude.const forall a. Monoid a => a
Prelude.mempty

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

instance Data.ToQuery AddListenerCertificates where
  toQuery :: AddListenerCertificates -> QueryString
toQuery AddListenerCertificates' {[Certificate]
Text
certificates :: [Certificate]
listenerArn :: Text
$sel:certificates:AddListenerCertificates' :: AddListenerCertificates -> [Certificate]
$sel:listenerArn:AddListenerCertificates' :: AddListenerCertificates -> Text
..} =
    forall a. Monoid a => [a] -> a
Prelude.mconcat
      [ ByteString
"Action"
          forall a. ToQuery a => ByteString -> a -> QueryString
Data.=: (ByteString
"AddListenerCertificates" :: Prelude.ByteString),
        ByteString
"Version"
          forall a. ToQuery a => ByteString -> a -> QueryString
Data.=: (ByteString
"2015-12-01" :: Prelude.ByteString),
        ByteString
"ListenerArn" forall a. ToQuery a => ByteString -> a -> QueryString
Data.=: Text
listenerArn,
        ByteString
"Certificates"
          forall a. ToQuery a => ByteString -> a -> QueryString
Data.=: forall a.
(IsList a, ToQuery (Item a)) =>
ByteString -> a -> QueryString
Data.toQueryList ByteString
"member" [Certificate]
certificates
      ]

-- | /See:/ 'newAddListenerCertificatesResponse' smart constructor.
data AddListenerCertificatesResponse = AddListenerCertificatesResponse'
  { -- | Information about the certificates in the certificate list.
    AddListenerCertificatesResponse -> Maybe [Certificate]
certificates :: Prelude.Maybe [Certificate],
    -- | The response's http status code.
    AddListenerCertificatesResponse -> Int
httpStatus :: Prelude.Int
  }
  deriving (AddListenerCertificatesResponse
-> AddListenerCertificatesResponse -> Bool
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: AddListenerCertificatesResponse
-> AddListenerCertificatesResponse -> Bool
$c/= :: AddListenerCertificatesResponse
-> AddListenerCertificatesResponse -> Bool
== :: AddListenerCertificatesResponse
-> AddListenerCertificatesResponse -> Bool
$c== :: AddListenerCertificatesResponse
-> AddListenerCertificatesResponse -> Bool
Prelude.Eq, ReadPrec [AddListenerCertificatesResponse]
ReadPrec AddListenerCertificatesResponse
Int -> ReadS AddListenerCertificatesResponse
ReadS [AddListenerCertificatesResponse]
forall a.
(Int -> ReadS a)
-> ReadS [a] -> ReadPrec a -> ReadPrec [a] -> Read a
readListPrec :: ReadPrec [AddListenerCertificatesResponse]
$creadListPrec :: ReadPrec [AddListenerCertificatesResponse]
readPrec :: ReadPrec AddListenerCertificatesResponse
$creadPrec :: ReadPrec AddListenerCertificatesResponse
readList :: ReadS [AddListenerCertificatesResponse]
$creadList :: ReadS [AddListenerCertificatesResponse]
readsPrec :: Int -> ReadS AddListenerCertificatesResponse
$creadsPrec :: Int -> ReadS AddListenerCertificatesResponse
Prelude.Read, Int -> AddListenerCertificatesResponse -> ShowS
[AddListenerCertificatesResponse] -> ShowS
AddListenerCertificatesResponse -> String
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [AddListenerCertificatesResponse] -> ShowS
$cshowList :: [AddListenerCertificatesResponse] -> ShowS
show :: AddListenerCertificatesResponse -> String
$cshow :: AddListenerCertificatesResponse -> String
showsPrec :: Int -> AddListenerCertificatesResponse -> ShowS
$cshowsPrec :: Int -> AddListenerCertificatesResponse -> ShowS
Prelude.Show, forall x.
Rep AddListenerCertificatesResponse x
-> AddListenerCertificatesResponse
forall x.
AddListenerCertificatesResponse
-> Rep AddListenerCertificatesResponse x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cto :: forall x.
Rep AddListenerCertificatesResponse x
-> AddListenerCertificatesResponse
$cfrom :: forall x.
AddListenerCertificatesResponse
-> Rep AddListenerCertificatesResponse x
Prelude.Generic)

-- |
-- Create a value of 'AddListenerCertificatesResponse' 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:
--
-- 'certificates', 'addListenerCertificatesResponse_certificates' - Information about the certificates in the certificate list.
--
-- 'httpStatus', 'addListenerCertificatesResponse_httpStatus' - The response's http status code.
newAddListenerCertificatesResponse ::
  -- | 'httpStatus'
  Prelude.Int ->
  AddListenerCertificatesResponse
newAddListenerCertificatesResponse :: Int -> AddListenerCertificatesResponse
newAddListenerCertificatesResponse Int
pHttpStatus_ =
  AddListenerCertificatesResponse'
    { $sel:certificates:AddListenerCertificatesResponse' :: Maybe [Certificate]
certificates =
        forall a. Maybe a
Prelude.Nothing,
      $sel:httpStatus:AddListenerCertificatesResponse' :: Int
httpStatus = Int
pHttpStatus_
    }

-- | Information about the certificates in the certificate list.
addListenerCertificatesResponse_certificates :: Lens.Lens' AddListenerCertificatesResponse (Prelude.Maybe [Certificate])
addListenerCertificatesResponse_certificates :: Lens' AddListenerCertificatesResponse (Maybe [Certificate])
addListenerCertificatesResponse_certificates = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\AddListenerCertificatesResponse' {Maybe [Certificate]
certificates :: Maybe [Certificate]
$sel:certificates:AddListenerCertificatesResponse' :: AddListenerCertificatesResponse -> Maybe [Certificate]
certificates} -> Maybe [Certificate]
certificates) (\s :: AddListenerCertificatesResponse
s@AddListenerCertificatesResponse' {} Maybe [Certificate]
a -> AddListenerCertificatesResponse
s {$sel:certificates:AddListenerCertificatesResponse' :: Maybe [Certificate]
certificates = Maybe [Certificate]
a} :: AddListenerCertificatesResponse) 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 s t a b. (Coercible s a, Coercible t b) => Iso s t a b
Lens.coerced

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

instance
  Prelude.NFData
    AddListenerCertificatesResponse
  where
  rnf :: AddListenerCertificatesResponse -> ()
rnf AddListenerCertificatesResponse' {Int
Maybe [Certificate]
httpStatus :: Int
certificates :: Maybe [Certificate]
$sel:httpStatus:AddListenerCertificatesResponse' :: AddListenerCertificatesResponse -> Int
$sel:certificates:AddListenerCertificatesResponse' :: AddListenerCertificatesResponse -> Maybe [Certificate]
..} =
    forall a. NFData a => a -> ()
Prelude.rnf Maybe [Certificate]
certificates
      seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf Int
httpStatus