{-# 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.AttachInstances
-- 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 EC2 instances to the specified Auto Scaling group.
--
-- When you attach instances, Amazon EC2 Auto Scaling increases the desired
-- capacity of the group by the number of instances being attached. If the
-- number of instances being attached plus the desired capacity of the
-- group exceeds the maximum size of the group, the operation fails.
--
-- If there is a Classic Load Balancer attached to your Auto Scaling group,
-- the instances are also registered with the load balancer. If there are
-- target groups attached to your Auto Scaling group, the instances are
-- also registered with the target groups.
--
-- For more information, see
-- <https://docs.aws.amazon.com/autoscaling/ec2/userguide/attach-instance-asg.html Attach EC2 instances to your Auto Scaling group>
-- in the /Amazon EC2 Auto Scaling User Guide/.
module Amazonka.AutoScaling.AttachInstances
  ( -- * Creating a Request
    AttachInstances (..),
    newAttachInstances,

    -- * Request Lenses
    attachInstances_instanceIds,
    attachInstances_autoScalingGroupName,

    -- * Destructuring the Response
    AttachInstancesResponse (..),
    newAttachInstancesResponse,
  )
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:/ 'newAttachInstances' smart constructor.
data AttachInstances = AttachInstances'
  { -- | The IDs of the instances. You can specify up to 20 instances.
    AttachInstances -> Maybe [Text]
instanceIds :: Prelude.Maybe [Prelude.Text],
    -- | The name of the Auto Scaling group.
    AttachInstances -> Text
autoScalingGroupName :: Prelude.Text
  }
  deriving (AttachInstances -> AttachInstances -> Bool
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: AttachInstances -> AttachInstances -> Bool
$c/= :: AttachInstances -> AttachInstances -> Bool
== :: AttachInstances -> AttachInstances -> Bool
$c== :: AttachInstances -> AttachInstances -> Bool
Prelude.Eq, ReadPrec [AttachInstances]
ReadPrec AttachInstances
Int -> ReadS AttachInstances
ReadS [AttachInstances]
forall a.
(Int -> ReadS a)
-> ReadS [a] -> ReadPrec a -> ReadPrec [a] -> Read a
readListPrec :: ReadPrec [AttachInstances]
$creadListPrec :: ReadPrec [AttachInstances]
readPrec :: ReadPrec AttachInstances
$creadPrec :: ReadPrec AttachInstances
readList :: ReadS [AttachInstances]
$creadList :: ReadS [AttachInstances]
readsPrec :: Int -> ReadS AttachInstances
$creadsPrec :: Int -> ReadS AttachInstances
Prelude.Read, Int -> AttachInstances -> ShowS
[AttachInstances] -> ShowS
AttachInstances -> String
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [AttachInstances] -> ShowS
$cshowList :: [AttachInstances] -> ShowS
show :: AttachInstances -> String
$cshow :: AttachInstances -> String
showsPrec :: Int -> AttachInstances -> ShowS
$cshowsPrec :: Int -> AttachInstances -> ShowS
Prelude.Show, forall x. Rep AttachInstances x -> AttachInstances
forall x. AttachInstances -> Rep AttachInstances x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cto :: forall x. Rep AttachInstances x -> AttachInstances
$cfrom :: forall x. AttachInstances -> Rep AttachInstances x
Prelude.Generic)

-- |
-- Create a value of 'AttachInstances' 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:
--
-- 'instanceIds', 'attachInstances_instanceIds' - The IDs of the instances. You can specify up to 20 instances.
--
-- 'autoScalingGroupName', 'attachInstances_autoScalingGroupName' - The name of the Auto Scaling group.
newAttachInstances ::
  -- | 'autoScalingGroupName'
  Prelude.Text ->
  AttachInstances
newAttachInstances :: Text -> AttachInstances
newAttachInstances Text
pAutoScalingGroupName_ =
  AttachInstances'
    { $sel:instanceIds:AttachInstances' :: Maybe [Text]
instanceIds = forall a. Maybe a
Prelude.Nothing,
      $sel:autoScalingGroupName:AttachInstances' :: Text
autoScalingGroupName = Text
pAutoScalingGroupName_
    }

-- | The IDs of the instances. You can specify up to 20 instances.
attachInstances_instanceIds :: Lens.Lens' AttachInstances (Prelude.Maybe [Prelude.Text])
attachInstances_instanceIds :: Lens' AttachInstances (Maybe [Text])
attachInstances_instanceIds = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\AttachInstances' {Maybe [Text]
instanceIds :: Maybe [Text]
$sel:instanceIds:AttachInstances' :: AttachInstances -> Maybe [Text]
instanceIds} -> Maybe [Text]
instanceIds) (\s :: AttachInstances
s@AttachInstances' {} Maybe [Text]
a -> AttachInstances
s {$sel:instanceIds:AttachInstances' :: Maybe [Text]
instanceIds = Maybe [Text]
a} :: AttachInstances) 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 name of the Auto Scaling group.
attachInstances_autoScalingGroupName :: Lens.Lens' AttachInstances Prelude.Text
attachInstances_autoScalingGroupName :: Lens' AttachInstances Text
attachInstances_autoScalingGroupName = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\AttachInstances' {Text
autoScalingGroupName :: Text
$sel:autoScalingGroupName:AttachInstances' :: AttachInstances -> Text
autoScalingGroupName} -> Text
autoScalingGroupName) (\s :: AttachInstances
s@AttachInstances' {} Text
a -> AttachInstances
s {$sel:autoScalingGroupName:AttachInstances' :: Text
autoScalingGroupName = Text
a} :: AttachInstances)

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

instance Prelude.Hashable AttachInstances where
  hashWithSalt :: Int -> AttachInstances -> Int
hashWithSalt Int
_salt AttachInstances' {Maybe [Text]
Text
autoScalingGroupName :: Text
instanceIds :: Maybe [Text]
$sel:autoScalingGroupName:AttachInstances' :: AttachInstances -> Text
$sel:instanceIds:AttachInstances' :: AttachInstances -> Maybe [Text]
..} =
    Int
_salt
      forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Maybe [Text]
instanceIds
      forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Text
autoScalingGroupName

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

instance Data.ToHeaders AttachInstances where
  toHeaders :: AttachInstances -> [Header]
toHeaders = forall a b. a -> b -> a
Prelude.const forall a. Monoid a => a
Prelude.mempty

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

instance Data.ToQuery AttachInstances where
  toQuery :: AttachInstances -> QueryString
toQuery AttachInstances' {Maybe [Text]
Text
autoScalingGroupName :: Text
instanceIds :: Maybe [Text]
$sel:autoScalingGroupName:AttachInstances' :: AttachInstances -> Text
$sel:instanceIds:AttachInstances' :: AttachInstances -> Maybe [Text]
..} =
    forall a. Monoid a => [a] -> a
Prelude.mconcat
      [ ByteString
"Action"
          forall a. ToQuery a => ByteString -> a -> QueryString
Data.=: (ByteString
"AttachInstances" :: Prelude.ByteString),
        ByteString
"Version"
          forall a. ToQuery a => ByteString -> a -> QueryString
Data.=: (ByteString
"2011-01-01" :: Prelude.ByteString),
        ByteString
"InstanceIds"
          forall a. ToQuery a => ByteString -> a -> QueryString
Data.=: forall a. ToQuery a => a -> QueryString
Data.toQuery
            (forall a.
(IsList a, ToQuery (Item a)) =>
ByteString -> a -> QueryString
Data.toQueryList ByteString
"member" forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
Prelude.<$> Maybe [Text]
instanceIds),
        ByteString
"AutoScalingGroupName" forall a. ToQuery a => ByteString -> a -> QueryString
Data.=: Text
autoScalingGroupName
      ]

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

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

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