{-# 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.DetachLoadBalancerTargetGroups
-- Copyright   : (c) 2013-2023 Brendan Hay
-- License     : Mozilla Public License, v. 2.0.
-- Maintainer  : Brendan Hay
-- Stability   : auto-generated
-- Portability : non-portable (GHC extensions)
--
-- Detaches one or more target groups from the specified Auto Scaling
-- group.
--
-- When you detach a target group, it enters the @Removing@ state while
-- deregistering the instances in the group. When all instances are
-- deregistered, then you can no longer describe the target group using the
-- DescribeLoadBalancerTargetGroups API call. The instances remain running.
--
-- You can use this operation to detach target groups that were attached by
-- using AttachLoadBalancerTargetGroups, but not for target groups that
-- were attached by using AttachTrafficSources.
module Amazonka.AutoScaling.DetachLoadBalancerTargetGroups
  ( -- * Creating a Request
    DetachLoadBalancerTargetGroups (..),
    newDetachLoadBalancerTargetGroups,

    -- * Request Lenses
    detachLoadBalancerTargetGroups_autoScalingGroupName,
    detachLoadBalancerTargetGroups_targetGroupARNs,

    -- * Destructuring the Response
    DetachLoadBalancerTargetGroupsResponse (..),
    newDetachLoadBalancerTargetGroupsResponse,

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

-- |
-- Create a value of 'DetachLoadBalancerTargetGroups' 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', 'detachLoadBalancerTargetGroups_autoScalingGroupName' - The name of the Auto Scaling group.
--
-- 'targetGroupARNs', 'detachLoadBalancerTargetGroups_targetGroupARNs' - The Amazon Resource Names (ARN) of the target groups. You can specify up
-- to 10 target groups.
newDetachLoadBalancerTargetGroups ::
  -- | 'autoScalingGroupName'
  Prelude.Text ->
  DetachLoadBalancerTargetGroups
newDetachLoadBalancerTargetGroups :: Text -> DetachLoadBalancerTargetGroups
newDetachLoadBalancerTargetGroups
  Text
pAutoScalingGroupName_ =
    DetachLoadBalancerTargetGroups'
      { $sel:autoScalingGroupName:DetachLoadBalancerTargetGroups' :: Text
autoScalingGroupName =
          Text
pAutoScalingGroupName_,
        $sel:targetGroupARNs:DetachLoadBalancerTargetGroups' :: [Text]
targetGroupARNs = forall a. Monoid a => a
Prelude.mempty
      }

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

-- | The Amazon Resource Names (ARN) of the target groups. You can specify up
-- to 10 target groups.
detachLoadBalancerTargetGroups_targetGroupARNs :: Lens.Lens' DetachLoadBalancerTargetGroups [Prelude.Text]
detachLoadBalancerTargetGroups_targetGroupARNs :: Lens' DetachLoadBalancerTargetGroups [Text]
detachLoadBalancerTargetGroups_targetGroupARNs = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\DetachLoadBalancerTargetGroups' {[Text]
targetGroupARNs :: [Text]
$sel:targetGroupARNs:DetachLoadBalancerTargetGroups' :: DetachLoadBalancerTargetGroups -> [Text]
targetGroupARNs} -> [Text]
targetGroupARNs) (\s :: DetachLoadBalancerTargetGroups
s@DetachLoadBalancerTargetGroups' {} [Text]
a -> DetachLoadBalancerTargetGroups
s {$sel:targetGroupARNs:DetachLoadBalancerTargetGroups' :: [Text]
targetGroupARNs = [Text]
a} :: DetachLoadBalancerTargetGroups) 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
    DetachLoadBalancerTargetGroups
  where
  type
    AWSResponse DetachLoadBalancerTargetGroups =
      DetachLoadBalancerTargetGroupsResponse
  request :: (Service -> Service)
-> DetachLoadBalancerTargetGroups
-> Request DetachLoadBalancerTargetGroups
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 DetachLoadBalancerTargetGroups
-> ClientResponse ClientBody
-> m (Either
        Error
        (ClientResponse (AWSResponse DetachLoadBalancerTargetGroups)))
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
"DetachLoadBalancerTargetGroupsResult"
      ( \Int
s ResponseHeaders
h [Node]
x ->
          Int -> DetachLoadBalancerTargetGroupsResponse
DetachLoadBalancerTargetGroupsResponse'
            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
    DetachLoadBalancerTargetGroups
  where
  hashWithSalt :: Int -> DetachLoadBalancerTargetGroups -> Int
hashWithSalt
    Int
_salt
    DetachLoadBalancerTargetGroups' {[Text]
Text
targetGroupARNs :: [Text]
autoScalingGroupName :: Text
$sel:targetGroupARNs:DetachLoadBalancerTargetGroups' :: DetachLoadBalancerTargetGroups -> [Text]
$sel:autoScalingGroupName:DetachLoadBalancerTargetGroups' :: DetachLoadBalancerTargetGroups -> 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
    DetachLoadBalancerTargetGroups
  where
  rnf :: DetachLoadBalancerTargetGroups -> ()
rnf DetachLoadBalancerTargetGroups' {[Text]
Text
targetGroupARNs :: [Text]
autoScalingGroupName :: Text
$sel:targetGroupARNs:DetachLoadBalancerTargetGroups' :: DetachLoadBalancerTargetGroups -> [Text]
$sel:autoScalingGroupName:DetachLoadBalancerTargetGroups' :: DetachLoadBalancerTargetGroups -> 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
    DetachLoadBalancerTargetGroups
  where
  toHeaders :: DetachLoadBalancerTargetGroups -> ResponseHeaders
toHeaders = forall a b. a -> b -> a
Prelude.const forall a. Monoid a => a
Prelude.mempty

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

instance Data.ToQuery DetachLoadBalancerTargetGroups where
  toQuery :: DetachLoadBalancerTargetGroups -> QueryString
toQuery DetachLoadBalancerTargetGroups' {[Text]
Text
targetGroupARNs :: [Text]
autoScalingGroupName :: Text
$sel:targetGroupARNs:DetachLoadBalancerTargetGroups' :: DetachLoadBalancerTargetGroups -> [Text]
$sel:autoScalingGroupName:DetachLoadBalancerTargetGroups' :: DetachLoadBalancerTargetGroups -> Text
..} =
    forall a. Monoid a => [a] -> a
Prelude.mconcat
      [ ByteString
"Action"
          forall a. ToQuery a => ByteString -> a -> QueryString
Data.=: ( ByteString
"DetachLoadBalancerTargetGroups" ::
                      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:/ 'newDetachLoadBalancerTargetGroupsResponse' smart constructor.
data DetachLoadBalancerTargetGroupsResponse = DetachLoadBalancerTargetGroupsResponse'
  { -- | The response's http status code.
    DetachLoadBalancerTargetGroupsResponse -> Int
httpStatus :: Prelude.Int
  }
  deriving (DetachLoadBalancerTargetGroupsResponse
-> DetachLoadBalancerTargetGroupsResponse -> Bool
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: DetachLoadBalancerTargetGroupsResponse
-> DetachLoadBalancerTargetGroupsResponse -> Bool
$c/= :: DetachLoadBalancerTargetGroupsResponse
-> DetachLoadBalancerTargetGroupsResponse -> Bool
== :: DetachLoadBalancerTargetGroupsResponse
-> DetachLoadBalancerTargetGroupsResponse -> Bool
$c== :: DetachLoadBalancerTargetGroupsResponse
-> DetachLoadBalancerTargetGroupsResponse -> Bool
Prelude.Eq, ReadPrec [DetachLoadBalancerTargetGroupsResponse]
ReadPrec DetachLoadBalancerTargetGroupsResponse
Int -> ReadS DetachLoadBalancerTargetGroupsResponse
ReadS [DetachLoadBalancerTargetGroupsResponse]
forall a.
(Int -> ReadS a)
-> ReadS [a] -> ReadPrec a -> ReadPrec [a] -> Read a
readListPrec :: ReadPrec [DetachLoadBalancerTargetGroupsResponse]
$creadListPrec :: ReadPrec [DetachLoadBalancerTargetGroupsResponse]
readPrec :: ReadPrec DetachLoadBalancerTargetGroupsResponse
$creadPrec :: ReadPrec DetachLoadBalancerTargetGroupsResponse
readList :: ReadS [DetachLoadBalancerTargetGroupsResponse]
$creadList :: ReadS [DetachLoadBalancerTargetGroupsResponse]
readsPrec :: Int -> ReadS DetachLoadBalancerTargetGroupsResponse
$creadsPrec :: Int -> ReadS DetachLoadBalancerTargetGroupsResponse
Prelude.Read, Int -> DetachLoadBalancerTargetGroupsResponse -> ShowS
[DetachLoadBalancerTargetGroupsResponse] -> ShowS
DetachLoadBalancerTargetGroupsResponse -> String
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [DetachLoadBalancerTargetGroupsResponse] -> ShowS
$cshowList :: [DetachLoadBalancerTargetGroupsResponse] -> ShowS
show :: DetachLoadBalancerTargetGroupsResponse -> String
$cshow :: DetachLoadBalancerTargetGroupsResponse -> String
showsPrec :: Int -> DetachLoadBalancerTargetGroupsResponse -> ShowS
$cshowsPrec :: Int -> DetachLoadBalancerTargetGroupsResponse -> ShowS
Prelude.Show, forall x.
Rep DetachLoadBalancerTargetGroupsResponse x
-> DetachLoadBalancerTargetGroupsResponse
forall x.
DetachLoadBalancerTargetGroupsResponse
-> Rep DetachLoadBalancerTargetGroupsResponse x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cto :: forall x.
Rep DetachLoadBalancerTargetGroupsResponse x
-> DetachLoadBalancerTargetGroupsResponse
$cfrom :: forall x.
DetachLoadBalancerTargetGroupsResponse
-> Rep DetachLoadBalancerTargetGroupsResponse x
Prelude.Generic)

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

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

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