{-# 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.DetachInstances
-- Copyright   : (c) 2013-2023 Brendan Hay
-- License     : Mozilla Public License, v. 2.0.
-- Maintainer  : Brendan Hay
-- Stability   : auto-generated
-- Portability : non-portable (GHC extensions)
--
-- Removes one or more instances from the specified Auto Scaling group.
--
-- After the instances are detached, you can manage them independent of the
-- Auto Scaling group.
--
-- If you do not specify the option to decrement the desired capacity,
-- Amazon EC2 Auto Scaling launches instances to replace the ones that are
-- detached.
--
-- If there is a Classic Load Balancer attached to the Auto Scaling group,
-- the instances are deregistered from the load balancer. If there are
-- target groups attached to the Auto Scaling group, the instances are
-- deregistered from the target groups.
--
-- For more information, see
-- <https://docs.aws.amazon.com/autoscaling/ec2/userguide/detach-instance-asg.html Detach EC2 instances from your Auto Scaling group>
-- in the /Amazon EC2 Auto Scaling User Guide/.
module Amazonka.AutoScaling.DetachInstances
  ( -- * Creating a Request
    DetachInstances (..),
    newDetachInstances,

    -- * Request Lenses
    detachInstances_instanceIds,
    detachInstances_autoScalingGroupName,
    detachInstances_shouldDecrementDesiredCapacity,

    -- * Destructuring the Response
    DetachInstancesResponse (..),
    newDetachInstancesResponse,

    -- * Response Lenses
    detachInstancesResponse_activities,
    detachInstancesResponse_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:/ 'newDetachInstances' smart constructor.
data DetachInstances = DetachInstances'
  { -- | The IDs of the instances. You can specify up to 20 instances.
    DetachInstances -> Maybe [Text]
instanceIds :: Prelude.Maybe [Prelude.Text],
    -- | The name of the Auto Scaling group.
    DetachInstances -> Text
autoScalingGroupName :: Prelude.Text,
    -- | Indicates whether the Auto Scaling group decrements the desired capacity
    -- value by the number of instances detached.
    DetachInstances -> Bool
shouldDecrementDesiredCapacity :: Prelude.Bool
  }
  deriving (DetachInstances -> DetachInstances -> Bool
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: DetachInstances -> DetachInstances -> Bool
$c/= :: DetachInstances -> DetachInstances -> Bool
== :: DetachInstances -> DetachInstances -> Bool
$c== :: DetachInstances -> DetachInstances -> Bool
Prelude.Eq, ReadPrec [DetachInstances]
ReadPrec DetachInstances
Int -> ReadS DetachInstances
ReadS [DetachInstances]
forall a.
(Int -> ReadS a)
-> ReadS [a] -> ReadPrec a -> ReadPrec [a] -> Read a
readListPrec :: ReadPrec [DetachInstances]
$creadListPrec :: ReadPrec [DetachInstances]
readPrec :: ReadPrec DetachInstances
$creadPrec :: ReadPrec DetachInstances
readList :: ReadS [DetachInstances]
$creadList :: ReadS [DetachInstances]
readsPrec :: Int -> ReadS DetachInstances
$creadsPrec :: Int -> ReadS DetachInstances
Prelude.Read, Int -> DetachInstances -> ShowS
[DetachInstances] -> ShowS
DetachInstances -> String
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [DetachInstances] -> ShowS
$cshowList :: [DetachInstances] -> ShowS
show :: DetachInstances -> String
$cshow :: DetachInstances -> String
showsPrec :: Int -> DetachInstances -> ShowS
$cshowsPrec :: Int -> DetachInstances -> ShowS
Prelude.Show, forall x. Rep DetachInstances x -> DetachInstances
forall x. DetachInstances -> Rep DetachInstances x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cto :: forall x. Rep DetachInstances x -> DetachInstances
$cfrom :: forall x. DetachInstances -> Rep DetachInstances x
Prelude.Generic)

-- |
-- Create a value of 'DetachInstances' 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', 'detachInstances_instanceIds' - The IDs of the instances. You can specify up to 20 instances.
--
-- 'autoScalingGroupName', 'detachInstances_autoScalingGroupName' - The name of the Auto Scaling group.
--
-- 'shouldDecrementDesiredCapacity', 'detachInstances_shouldDecrementDesiredCapacity' - Indicates whether the Auto Scaling group decrements the desired capacity
-- value by the number of instances detached.
newDetachInstances ::
  -- | 'autoScalingGroupName'
  Prelude.Text ->
  -- | 'shouldDecrementDesiredCapacity'
  Prelude.Bool ->
  DetachInstances
newDetachInstances :: Text -> Bool -> DetachInstances
newDetachInstances
  Text
pAutoScalingGroupName_
  Bool
pShouldDecrementDesiredCapacity_ =
    DetachInstances'
      { $sel:instanceIds:DetachInstances' :: Maybe [Text]
instanceIds = forall a. Maybe a
Prelude.Nothing,
        $sel:autoScalingGroupName:DetachInstances' :: Text
autoScalingGroupName = Text
pAutoScalingGroupName_,
        $sel:shouldDecrementDesiredCapacity:DetachInstances' :: Bool
shouldDecrementDesiredCapacity =
          Bool
pShouldDecrementDesiredCapacity_
      }

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

-- | Indicates whether the Auto Scaling group decrements the desired capacity
-- value by the number of instances detached.
detachInstances_shouldDecrementDesiredCapacity :: Lens.Lens' DetachInstances Prelude.Bool
detachInstances_shouldDecrementDesiredCapacity :: Lens' DetachInstances Bool
detachInstances_shouldDecrementDesiredCapacity = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\DetachInstances' {Bool
shouldDecrementDesiredCapacity :: Bool
$sel:shouldDecrementDesiredCapacity:DetachInstances' :: DetachInstances -> Bool
shouldDecrementDesiredCapacity} -> Bool
shouldDecrementDesiredCapacity) (\s :: DetachInstances
s@DetachInstances' {} Bool
a -> DetachInstances
s {$sel:shouldDecrementDesiredCapacity:DetachInstances' :: Bool
shouldDecrementDesiredCapacity = Bool
a} :: DetachInstances)

instance Core.AWSRequest DetachInstances where
  type
    AWSResponse DetachInstances =
      DetachInstancesResponse
  request :: (Service -> Service) -> DetachInstances -> Request DetachInstances
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 DetachInstances
-> ClientResponse ClientBody
-> m (Either Error (ClientResponse (AWSResponse DetachInstances)))
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
"DetachInstancesResult"
      ( \Int
s ResponseHeaders
h [Node]
x ->
          Maybe [Activity] -> Int -> DetachInstancesResponse
DetachInstancesResponse'
            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
"Activities"
                            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 DetachInstances where
  hashWithSalt :: Int -> DetachInstances -> Int
hashWithSalt Int
_salt DetachInstances' {Bool
Maybe [Text]
Text
shouldDecrementDesiredCapacity :: Bool
autoScalingGroupName :: Text
instanceIds :: Maybe [Text]
$sel:shouldDecrementDesiredCapacity:DetachInstances' :: DetachInstances -> Bool
$sel:autoScalingGroupName:DetachInstances' :: DetachInstances -> Text
$sel:instanceIds:DetachInstances' :: DetachInstances -> 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
      forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Bool
shouldDecrementDesiredCapacity

instance Prelude.NFData DetachInstances where
  rnf :: DetachInstances -> ()
rnf DetachInstances' {Bool
Maybe [Text]
Text
shouldDecrementDesiredCapacity :: Bool
autoScalingGroupName :: Text
instanceIds :: Maybe [Text]
$sel:shouldDecrementDesiredCapacity:DetachInstances' :: DetachInstances -> Bool
$sel:autoScalingGroupName:DetachInstances' :: DetachInstances -> Text
$sel:instanceIds:DetachInstances' :: DetachInstances -> 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
      seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf Bool
shouldDecrementDesiredCapacity

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

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

instance Data.ToQuery DetachInstances where
  toQuery :: DetachInstances -> QueryString
toQuery DetachInstances' {Bool
Maybe [Text]
Text
shouldDecrementDesiredCapacity :: Bool
autoScalingGroupName :: Text
instanceIds :: Maybe [Text]
$sel:shouldDecrementDesiredCapacity:DetachInstances' :: DetachInstances -> Bool
$sel:autoScalingGroupName:DetachInstances' :: DetachInstances -> Text
$sel:instanceIds:DetachInstances' :: DetachInstances -> Maybe [Text]
..} =
    forall a. Monoid a => [a] -> a
Prelude.mconcat
      [ ByteString
"Action"
          forall a. ToQuery a => ByteString -> a -> QueryString
Data.=: (ByteString
"DetachInstances" :: 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,
        ByteString
"ShouldDecrementDesiredCapacity"
          forall a. ToQuery a => ByteString -> a -> QueryString
Data.=: Bool
shouldDecrementDesiredCapacity
      ]

-- | /See:/ 'newDetachInstancesResponse' smart constructor.
data DetachInstancesResponse = DetachInstancesResponse'
  { -- | The activities related to detaching the instances from the Auto Scaling
    -- group.
    DetachInstancesResponse -> Maybe [Activity]
activities :: Prelude.Maybe [Activity],
    -- | The response's http status code.
    DetachInstancesResponse -> Int
httpStatus :: Prelude.Int
  }
  deriving (DetachInstancesResponse -> DetachInstancesResponse -> Bool
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: DetachInstancesResponse -> DetachInstancesResponse -> Bool
$c/= :: DetachInstancesResponse -> DetachInstancesResponse -> Bool
== :: DetachInstancesResponse -> DetachInstancesResponse -> Bool
$c== :: DetachInstancesResponse -> DetachInstancesResponse -> Bool
Prelude.Eq, ReadPrec [DetachInstancesResponse]
ReadPrec DetachInstancesResponse
Int -> ReadS DetachInstancesResponse
ReadS [DetachInstancesResponse]
forall a.
(Int -> ReadS a)
-> ReadS [a] -> ReadPrec a -> ReadPrec [a] -> Read a
readListPrec :: ReadPrec [DetachInstancesResponse]
$creadListPrec :: ReadPrec [DetachInstancesResponse]
readPrec :: ReadPrec DetachInstancesResponse
$creadPrec :: ReadPrec DetachInstancesResponse
readList :: ReadS [DetachInstancesResponse]
$creadList :: ReadS [DetachInstancesResponse]
readsPrec :: Int -> ReadS DetachInstancesResponse
$creadsPrec :: Int -> ReadS DetachInstancesResponse
Prelude.Read, Int -> DetachInstancesResponse -> ShowS
[DetachInstancesResponse] -> ShowS
DetachInstancesResponse -> String
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [DetachInstancesResponse] -> ShowS
$cshowList :: [DetachInstancesResponse] -> ShowS
show :: DetachInstancesResponse -> String
$cshow :: DetachInstancesResponse -> String
showsPrec :: Int -> DetachInstancesResponse -> ShowS
$cshowsPrec :: Int -> DetachInstancesResponse -> ShowS
Prelude.Show, forall x. Rep DetachInstancesResponse x -> DetachInstancesResponse
forall x. DetachInstancesResponse -> Rep DetachInstancesResponse x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cto :: forall x. Rep DetachInstancesResponse x -> DetachInstancesResponse
$cfrom :: forall x. DetachInstancesResponse -> Rep DetachInstancesResponse x
Prelude.Generic)

-- |
-- Create a value of 'DetachInstancesResponse' 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:
--
-- 'activities', 'detachInstancesResponse_activities' - The activities related to detaching the instances from the Auto Scaling
-- group.
--
-- 'httpStatus', 'detachInstancesResponse_httpStatus' - The response's http status code.
newDetachInstancesResponse ::
  -- | 'httpStatus'
  Prelude.Int ->
  DetachInstancesResponse
newDetachInstancesResponse :: Int -> DetachInstancesResponse
newDetachInstancesResponse Int
pHttpStatus_ =
  DetachInstancesResponse'
    { $sel:activities:DetachInstancesResponse' :: Maybe [Activity]
activities =
        forall a. Maybe a
Prelude.Nothing,
      $sel:httpStatus:DetachInstancesResponse' :: Int
httpStatus = Int
pHttpStatus_
    }

-- | The activities related to detaching the instances from the Auto Scaling
-- group.
detachInstancesResponse_activities :: Lens.Lens' DetachInstancesResponse (Prelude.Maybe [Activity])
detachInstancesResponse_activities :: Lens' DetachInstancesResponse (Maybe [Activity])
detachInstancesResponse_activities = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\DetachInstancesResponse' {Maybe [Activity]
activities :: Maybe [Activity]
$sel:activities:DetachInstancesResponse' :: DetachInstancesResponse -> Maybe [Activity]
activities} -> Maybe [Activity]
activities) (\s :: DetachInstancesResponse
s@DetachInstancesResponse' {} Maybe [Activity]
a -> DetachInstancesResponse
s {$sel:activities:DetachInstancesResponse' :: Maybe [Activity]
activities = Maybe [Activity]
a} :: DetachInstancesResponse) 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.
detachInstancesResponse_httpStatus :: Lens.Lens' DetachInstancesResponse Prelude.Int
detachInstancesResponse_httpStatus :: Lens' DetachInstancesResponse Int
detachInstancesResponse_httpStatus = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\DetachInstancesResponse' {Int
httpStatus :: Int
$sel:httpStatus:DetachInstancesResponse' :: DetachInstancesResponse -> Int
httpStatus} -> Int
httpStatus) (\s :: DetachInstancesResponse
s@DetachInstancesResponse' {} Int
a -> DetachInstancesResponse
s {$sel:httpStatus:DetachInstancesResponse' :: Int
httpStatus = Int
a} :: DetachInstancesResponse)

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