{-# 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.AttachLoadBalancers
-- Copyright   : (c) 2013-2023 Brendan Hay
-- License     : Mozilla Public License, v. 2.0.
-- Maintainer  : Brendan Hay
-- Stability   : auto-generated
-- Portability : non-portable (GHC extensions)
--
-- To attach an Application Load Balancer, Network Load Balancer, or
-- Gateway Load Balancer, use the AttachLoadBalancerTargetGroups API
-- operation instead.
--
-- Attaches one or more Classic Load Balancers to the specified Auto
-- Scaling group. Amazon EC2 Auto Scaling registers the running instances
-- with these Classic Load Balancers.
--
-- To describe the load balancers for an Auto Scaling group, call the
-- DescribeLoadBalancers API. To detach a load balancer from the Auto
-- Scaling group, call the DetachLoadBalancers API.
--
-- This operation is additive and does not detach existing Classic Load
-- Balancers or target groups 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.AttachLoadBalancers
  ( -- * Creating a Request
    AttachLoadBalancers (..),
    newAttachLoadBalancers,

    -- * Request Lenses
    attachLoadBalancers_autoScalingGroupName,
    attachLoadBalancers_loadBalancerNames,

    -- * Destructuring the Response
    AttachLoadBalancersResponse (..),
    newAttachLoadBalancersResponse,

    -- * Response Lenses
    attachLoadBalancersResponse_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:/ 'newAttachLoadBalancers' smart constructor.
data AttachLoadBalancers = AttachLoadBalancers'
  { -- | The name of the Auto Scaling group.
    AttachLoadBalancers -> Text
autoScalingGroupName :: Prelude.Text,
    -- | The names of the load balancers. You can specify up to 10 load
    -- balancers.
    AttachLoadBalancers -> [Text]
loadBalancerNames :: [Prelude.Text]
  }
  deriving (AttachLoadBalancers -> AttachLoadBalancers -> Bool
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: AttachLoadBalancers -> AttachLoadBalancers -> Bool
$c/= :: AttachLoadBalancers -> AttachLoadBalancers -> Bool
== :: AttachLoadBalancers -> AttachLoadBalancers -> Bool
$c== :: AttachLoadBalancers -> AttachLoadBalancers -> Bool
Prelude.Eq, ReadPrec [AttachLoadBalancers]
ReadPrec AttachLoadBalancers
Int -> ReadS AttachLoadBalancers
ReadS [AttachLoadBalancers]
forall a.
(Int -> ReadS a)
-> ReadS [a] -> ReadPrec a -> ReadPrec [a] -> Read a
readListPrec :: ReadPrec [AttachLoadBalancers]
$creadListPrec :: ReadPrec [AttachLoadBalancers]
readPrec :: ReadPrec AttachLoadBalancers
$creadPrec :: ReadPrec AttachLoadBalancers
readList :: ReadS [AttachLoadBalancers]
$creadList :: ReadS [AttachLoadBalancers]
readsPrec :: Int -> ReadS AttachLoadBalancers
$creadsPrec :: Int -> ReadS AttachLoadBalancers
Prelude.Read, Int -> AttachLoadBalancers -> ShowS
[AttachLoadBalancers] -> ShowS
AttachLoadBalancers -> String
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [AttachLoadBalancers] -> ShowS
$cshowList :: [AttachLoadBalancers] -> ShowS
show :: AttachLoadBalancers -> String
$cshow :: AttachLoadBalancers -> String
showsPrec :: Int -> AttachLoadBalancers -> ShowS
$cshowsPrec :: Int -> AttachLoadBalancers -> ShowS
Prelude.Show, forall x. Rep AttachLoadBalancers x -> AttachLoadBalancers
forall x. AttachLoadBalancers -> Rep AttachLoadBalancers x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cto :: forall x. Rep AttachLoadBalancers x -> AttachLoadBalancers
$cfrom :: forall x. AttachLoadBalancers -> Rep AttachLoadBalancers x
Prelude.Generic)

-- |
-- Create a value of 'AttachLoadBalancers' 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', 'attachLoadBalancers_autoScalingGroupName' - The name of the Auto Scaling group.
--
-- 'loadBalancerNames', 'attachLoadBalancers_loadBalancerNames' - The names of the load balancers. You can specify up to 10 load
-- balancers.
newAttachLoadBalancers ::
  -- | 'autoScalingGroupName'
  Prelude.Text ->
  AttachLoadBalancers
newAttachLoadBalancers :: Text -> AttachLoadBalancers
newAttachLoadBalancers Text
pAutoScalingGroupName_ =
  AttachLoadBalancers'
    { $sel:autoScalingGroupName:AttachLoadBalancers' :: Text
autoScalingGroupName =
        Text
pAutoScalingGroupName_,
      $sel:loadBalancerNames:AttachLoadBalancers' :: [Text]
loadBalancerNames = forall a. Monoid a => a
Prelude.mempty
    }

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

-- | The names of the load balancers. You can specify up to 10 load
-- balancers.
attachLoadBalancers_loadBalancerNames :: Lens.Lens' AttachLoadBalancers [Prelude.Text]
attachLoadBalancers_loadBalancerNames :: Lens' AttachLoadBalancers [Text]
attachLoadBalancers_loadBalancerNames = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\AttachLoadBalancers' {[Text]
loadBalancerNames :: [Text]
$sel:loadBalancerNames:AttachLoadBalancers' :: AttachLoadBalancers -> [Text]
loadBalancerNames} -> [Text]
loadBalancerNames) (\s :: AttachLoadBalancers
s@AttachLoadBalancers' {} [Text]
a -> AttachLoadBalancers
s {$sel:loadBalancerNames:AttachLoadBalancers' :: [Text]
loadBalancerNames = [Text]
a} :: AttachLoadBalancers) 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 AttachLoadBalancers where
  type
    AWSResponse AttachLoadBalancers =
      AttachLoadBalancersResponse
  request :: (Service -> Service)
-> AttachLoadBalancers -> Request AttachLoadBalancers
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 AttachLoadBalancers
-> ClientResponse ClientBody
-> m (Either
        Error (ClientResponse (AWSResponse AttachLoadBalancers)))
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
"AttachLoadBalancersResult"
      ( \Int
s ResponseHeaders
h [Node]
x ->
          Int -> AttachLoadBalancersResponse
AttachLoadBalancersResponse'
            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 AttachLoadBalancers where
  hashWithSalt :: Int -> AttachLoadBalancers -> Int
hashWithSalt Int
_salt AttachLoadBalancers' {[Text]
Text
loadBalancerNames :: [Text]
autoScalingGroupName :: Text
$sel:loadBalancerNames:AttachLoadBalancers' :: AttachLoadBalancers -> [Text]
$sel:autoScalingGroupName:AttachLoadBalancers' :: AttachLoadBalancers -> Text
..} =
    Int
_salt
      forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Text
autoScalingGroupName
      forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` [Text]
loadBalancerNames

instance Prelude.NFData AttachLoadBalancers where
  rnf :: AttachLoadBalancers -> ()
rnf AttachLoadBalancers' {[Text]
Text
loadBalancerNames :: [Text]
autoScalingGroupName :: Text
$sel:loadBalancerNames:AttachLoadBalancers' :: AttachLoadBalancers -> [Text]
$sel:autoScalingGroupName:AttachLoadBalancers' :: AttachLoadBalancers -> 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]
loadBalancerNames

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

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

instance Data.ToQuery AttachLoadBalancers where
  toQuery :: AttachLoadBalancers -> QueryString
toQuery AttachLoadBalancers' {[Text]
Text
loadBalancerNames :: [Text]
autoScalingGroupName :: Text
$sel:loadBalancerNames:AttachLoadBalancers' :: AttachLoadBalancers -> [Text]
$sel:autoScalingGroupName:AttachLoadBalancers' :: AttachLoadBalancers -> Text
..} =
    forall a. Monoid a => [a] -> a
Prelude.mconcat
      [ ByteString
"Action"
          forall a. ToQuery a => ByteString -> a -> QueryString
Data.=: (ByteString
"AttachLoadBalancers" :: 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
"LoadBalancerNames"
          forall a. ToQuery a => ByteString -> a -> QueryString
Data.=: forall a.
(IsList a, ToQuery (Item a)) =>
ByteString -> a -> QueryString
Data.toQueryList ByteString
"member" [Text]
loadBalancerNames
      ]

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

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

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

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