{-# 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.AutoScaling.AttachLoadBalancerTargetGroups
-- 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 one or more target groups to the specified Auto Scaling group.
--
-- This operation is used with the following load balancer types:
--
-- -   Application Load Balancer - Operates at the application layer (layer
--     7) and supports HTTP and HTTPS.
--
-- -   Network Load Balancer - Operates at the transport layer (layer 4)
--     and supports TCP, TLS, and UDP.
--
-- -   Gateway Load Balancer - Operates at the network layer (layer 3).
--
-- To describe the target groups for an Auto Scaling group, call the
-- DescribeLoadBalancerTargetGroups API. To detach the target group from
-- the Auto Scaling group, call the DetachLoadBalancerTargetGroups API.
--
-- This operation is additive and does not detach existing target groups or
-- Classic Load Balancers from the Auto Scaling group.
--
-- For more information, see
-- <https://docs.aws.amazon.com/autoscaling/ec2/userguide/autoscaling-load-balancer.html Use Elastic Load Balancing to distribute traffic across the instances in your Auto Scaling group>
-- in the /Amazon EC2 Auto Scaling User Guide/.
module Amazonka.AutoScaling.AttachLoadBalancerTargetGroups
  ( -- * Creating a Request
    AttachLoadBalancerTargetGroups (..),
    newAttachLoadBalancerTargetGroups,

    -- * Request Lenses
    attachLoadBalancerTargetGroups_autoScalingGroupName,
    attachLoadBalancerTargetGroups_targetGroupARNs,

    -- * Destructuring the Response
    AttachLoadBalancerTargetGroupsResponse (..),
    newAttachLoadBalancerTargetGroupsResponse,

    -- * Response Lenses
    attachLoadBalancerTargetGroupsResponse_httpStatus,
  )
where

import Amazonka.AutoScaling.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:/ 'newAttachLoadBalancerTargetGroups' smart constructor.
data AttachLoadBalancerTargetGroups = AttachLoadBalancerTargetGroups'
  { -- | The name of the Auto Scaling group.
    AttachLoadBalancerTargetGroups -> Text
autoScalingGroupName :: Prelude.Text,
    -- | The Amazon Resource Names (ARNs) of the target groups. You can specify
    -- up to 10 target groups. To get the ARN of a target group, use the
    -- Elastic Load Balancing
    -- <https://docs.aws.amazon.com/elasticloadbalancing/latest/APIReference/API_DescribeTargetGroups.html DescribeTargetGroups>
    -- API operation.
    AttachLoadBalancerTargetGroups -> [Text]
targetGroupARNs :: [Prelude.Text]
  }
  deriving (AttachLoadBalancerTargetGroups
-> AttachLoadBalancerTargetGroups -> Bool
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: AttachLoadBalancerTargetGroups
-> AttachLoadBalancerTargetGroups -> Bool
$c/= :: AttachLoadBalancerTargetGroups
-> AttachLoadBalancerTargetGroups -> Bool
== :: AttachLoadBalancerTargetGroups
-> AttachLoadBalancerTargetGroups -> Bool
$c== :: AttachLoadBalancerTargetGroups
-> AttachLoadBalancerTargetGroups -> Bool
Prelude.Eq, ReadPrec [AttachLoadBalancerTargetGroups]
ReadPrec AttachLoadBalancerTargetGroups
Int -> ReadS AttachLoadBalancerTargetGroups
ReadS [AttachLoadBalancerTargetGroups]
forall a.
(Int -> ReadS a)
-> ReadS [a] -> ReadPrec a -> ReadPrec [a] -> Read a
readListPrec :: ReadPrec [AttachLoadBalancerTargetGroups]
$creadListPrec :: ReadPrec [AttachLoadBalancerTargetGroups]
readPrec :: ReadPrec AttachLoadBalancerTargetGroups
$creadPrec :: ReadPrec AttachLoadBalancerTargetGroups
readList :: ReadS [AttachLoadBalancerTargetGroups]
$creadList :: ReadS [AttachLoadBalancerTargetGroups]
readsPrec :: Int -> ReadS AttachLoadBalancerTargetGroups
$creadsPrec :: Int -> ReadS AttachLoadBalancerTargetGroups
Prelude.Read, Int -> AttachLoadBalancerTargetGroups -> ShowS
[AttachLoadBalancerTargetGroups] -> ShowS
AttachLoadBalancerTargetGroups -> String
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [AttachLoadBalancerTargetGroups] -> ShowS
$cshowList :: [AttachLoadBalancerTargetGroups] -> ShowS
show :: AttachLoadBalancerTargetGroups -> String
$cshow :: AttachLoadBalancerTargetGroups -> String
showsPrec :: Int -> AttachLoadBalancerTargetGroups -> ShowS
$cshowsPrec :: Int -> AttachLoadBalancerTargetGroups -> ShowS
Prelude.Show, forall x.
Rep AttachLoadBalancerTargetGroups x
-> AttachLoadBalancerTargetGroups
forall x.
AttachLoadBalancerTargetGroups
-> Rep AttachLoadBalancerTargetGroups x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cto :: forall x.
Rep AttachLoadBalancerTargetGroups x
-> AttachLoadBalancerTargetGroups
$cfrom :: forall x.
AttachLoadBalancerTargetGroups
-> Rep AttachLoadBalancerTargetGroups x
Prelude.Generic)

-- |
-- Create a value of 'AttachLoadBalancerTargetGroups' 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:
--
-- 'autoScalingGroupName', 'attachLoadBalancerTargetGroups_autoScalingGroupName' - The name of the Auto Scaling group.
--
-- 'targetGroupARNs', 'attachLoadBalancerTargetGroups_targetGroupARNs' - The Amazon Resource Names (ARNs) of the target groups. You can specify
-- up to 10 target groups. To get the ARN of a target group, use the
-- Elastic Load Balancing
-- <https://docs.aws.amazon.com/elasticloadbalancing/latest/APIReference/API_DescribeTargetGroups.html DescribeTargetGroups>
-- API operation.
newAttachLoadBalancerTargetGroups ::
  -- | 'autoScalingGroupName'
  Prelude.Text ->
  AttachLoadBalancerTargetGroups
newAttachLoadBalancerTargetGroups :: Text -> AttachLoadBalancerTargetGroups
newAttachLoadBalancerTargetGroups
  Text
pAutoScalingGroupName_ =
    AttachLoadBalancerTargetGroups'
      { $sel:autoScalingGroupName:AttachLoadBalancerTargetGroups' :: Text
autoScalingGroupName =
          Text
pAutoScalingGroupName_,
        $sel:targetGroupARNs:AttachLoadBalancerTargetGroups' :: [Text]
targetGroupARNs = forall a. Monoid a => a
Prelude.mempty
      }

-- | The name of the Auto Scaling group.
attachLoadBalancerTargetGroups_autoScalingGroupName :: Lens.Lens' AttachLoadBalancerTargetGroups Prelude.Text
attachLoadBalancerTargetGroups_autoScalingGroupName :: Lens' AttachLoadBalancerTargetGroups Text
attachLoadBalancerTargetGroups_autoScalingGroupName = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\AttachLoadBalancerTargetGroups' {Text
autoScalingGroupName :: Text
$sel:autoScalingGroupName:AttachLoadBalancerTargetGroups' :: AttachLoadBalancerTargetGroups -> Text
autoScalingGroupName} -> Text
autoScalingGroupName) (\s :: AttachLoadBalancerTargetGroups
s@AttachLoadBalancerTargetGroups' {} Text
a -> AttachLoadBalancerTargetGroups
s {$sel:autoScalingGroupName:AttachLoadBalancerTargetGroups' :: Text
autoScalingGroupName = Text
a} :: AttachLoadBalancerTargetGroups)

-- | The Amazon Resource Names (ARNs) of the target groups. You can specify
-- up to 10 target groups. To get the ARN of a target group, use the
-- Elastic Load Balancing
-- <https://docs.aws.amazon.com/elasticloadbalancing/latest/APIReference/API_DescribeTargetGroups.html DescribeTargetGroups>
-- API operation.
attachLoadBalancerTargetGroups_targetGroupARNs :: Lens.Lens' AttachLoadBalancerTargetGroups [Prelude.Text]
attachLoadBalancerTargetGroups_targetGroupARNs :: Lens' AttachLoadBalancerTargetGroups [Text]
attachLoadBalancerTargetGroups_targetGroupARNs = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\AttachLoadBalancerTargetGroups' {[Text]
targetGroupARNs :: [Text]
$sel:targetGroupARNs:AttachLoadBalancerTargetGroups' :: AttachLoadBalancerTargetGroups -> [Text]
targetGroupARNs} -> [Text]
targetGroupARNs) (\s :: AttachLoadBalancerTargetGroups
s@AttachLoadBalancerTargetGroups' {} [Text]
a -> AttachLoadBalancerTargetGroups
s {$sel:targetGroupARNs:AttachLoadBalancerTargetGroups' :: [Text]
targetGroupARNs = [Text]
a} :: AttachLoadBalancerTargetGroups) 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
    AttachLoadBalancerTargetGroups
  where
  type
    AWSResponse AttachLoadBalancerTargetGroups =
      AttachLoadBalancerTargetGroupsResponse
  request :: (Service -> Service)
-> AttachLoadBalancerTargetGroups
-> Request AttachLoadBalancerTargetGroups
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 AttachLoadBalancerTargetGroups
-> ClientResponse ClientBody
-> m (Either
        Error
        (ClientResponse (AWSResponse AttachLoadBalancerTargetGroups)))
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
"AttachLoadBalancerTargetGroupsResult"
      ( \Int
s ResponseHeaders
h [Node]
x ->
          Int -> AttachLoadBalancerTargetGroupsResponse
AttachLoadBalancerTargetGroupsResponse'
            forall (f :: * -> *) a b. Functor 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
    AttachLoadBalancerTargetGroups
  where
  hashWithSalt :: Int -> AttachLoadBalancerTargetGroups -> Int
hashWithSalt
    Int
_salt
    AttachLoadBalancerTargetGroups' {[Text]
Text
targetGroupARNs :: [Text]
autoScalingGroupName :: Text
$sel:targetGroupARNs:AttachLoadBalancerTargetGroups' :: AttachLoadBalancerTargetGroups -> [Text]
$sel:autoScalingGroupName:AttachLoadBalancerTargetGroups' :: AttachLoadBalancerTargetGroups -> Text
..} =
      Int
_salt
        forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Text
autoScalingGroupName
        forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` [Text]
targetGroupARNs

instance
  Prelude.NFData
    AttachLoadBalancerTargetGroups
  where
  rnf :: AttachLoadBalancerTargetGroups -> ()
rnf AttachLoadBalancerTargetGroups' {[Text]
Text
targetGroupARNs :: [Text]
autoScalingGroupName :: Text
$sel:targetGroupARNs:AttachLoadBalancerTargetGroups' :: AttachLoadBalancerTargetGroups -> [Text]
$sel:autoScalingGroupName:AttachLoadBalancerTargetGroups' :: AttachLoadBalancerTargetGroups -> Text
..} =
    forall a. NFData a => a -> ()
Prelude.rnf Text
autoScalingGroupName
      seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf [Text]
targetGroupARNs

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

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

instance Data.ToQuery AttachLoadBalancerTargetGroups where
  toQuery :: AttachLoadBalancerTargetGroups -> QueryString
toQuery AttachLoadBalancerTargetGroups' {[Text]
Text
targetGroupARNs :: [Text]
autoScalingGroupName :: Text
$sel:targetGroupARNs:AttachLoadBalancerTargetGroups' :: AttachLoadBalancerTargetGroups -> [Text]
$sel:autoScalingGroupName:AttachLoadBalancerTargetGroups' :: AttachLoadBalancerTargetGroups -> Text
..} =
    forall a. Monoid a => [a] -> a
Prelude.mconcat
      [ ByteString
"Action"
          forall a. ToQuery a => ByteString -> a -> QueryString
Data.=: ( ByteString
"AttachLoadBalancerTargetGroups" ::
                      Prelude.ByteString
                  ),
        ByteString
"Version"
          forall a. ToQuery a => ByteString -> a -> QueryString
Data.=: (ByteString
"2011-01-01" :: Prelude.ByteString),
        ByteString
"AutoScalingGroupName" forall a. ToQuery a => ByteString -> a -> QueryString
Data.=: Text
autoScalingGroupName,
        ByteString
"TargetGroupARNs"
          forall a. ToQuery a => ByteString -> a -> QueryString
Data.=: forall a.
(IsList a, ToQuery (Item a)) =>
ByteString -> a -> QueryString
Data.toQueryList ByteString
"member" [Text]
targetGroupARNs
      ]

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

-- |
-- Create a value of 'AttachLoadBalancerTargetGroupsResponse' 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:
--
-- 'httpStatus', 'attachLoadBalancerTargetGroupsResponse_httpStatus' - The response's http status code.
newAttachLoadBalancerTargetGroupsResponse ::
  -- | 'httpStatus'
  Prelude.Int ->
  AttachLoadBalancerTargetGroupsResponse
newAttachLoadBalancerTargetGroupsResponse :: Int -> AttachLoadBalancerTargetGroupsResponse
newAttachLoadBalancerTargetGroupsResponse
  Int
pHttpStatus_ =
    AttachLoadBalancerTargetGroupsResponse'
      { $sel:httpStatus:AttachLoadBalancerTargetGroupsResponse' :: Int
httpStatus =
          Int
pHttpStatus_
      }

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

instance
  Prelude.NFData
    AttachLoadBalancerTargetGroupsResponse
  where
  rnf :: AttachLoadBalancerTargetGroupsResponse -> ()
rnf AttachLoadBalancerTargetGroupsResponse' {Int
httpStatus :: Int
$sel:httpStatus:AttachLoadBalancerTargetGroupsResponse' :: AttachLoadBalancerTargetGroupsResponse -> Int
..} =
    forall a. NFData a => a -> ()
Prelude.rnf Int
httpStatus