{-# 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.DescribeLoadBalancerTargetGroups
-- Copyright   : (c) 2013-2023 Brendan Hay
-- License     : Mozilla Public License, v. 2.0.
-- Maintainer  : Brendan Hay
-- Stability   : auto-generated
-- Portability : non-portable (GHC extensions)
--
-- Gets information about the Elastic Load Balancing target groups for the
-- specified Auto Scaling group.
--
-- To determine the attachment status of the target group, use the @State@
-- element in the response. When you attach a target group to an Auto
-- Scaling group, the initial @State@ value is @Adding@. The state
-- transitions to @Added@ after all Auto Scaling instances are registered
-- with the target group. If Elastic Load Balancing health checks are
-- enabled for the Auto Scaling group, the state transitions to @InService@
-- after at least one Auto Scaling instance passes the health check. When
-- the target group is in the @InService@ state, Amazon EC2 Auto Scaling
-- can terminate and replace any instances that are reported as unhealthy.
-- If no registered instances pass the health checks, the target group
-- doesn\'t enter the @InService@ state.
--
-- Target groups also have an @InService@ state if you attach them in the
-- CreateAutoScalingGroup API call. If your target group state is
-- @InService@, but it is not working properly, check the scaling
-- activities by calling DescribeScalingActivities and take any corrective
-- actions necessary.
--
-- For help with failed health checks, see
-- <https://docs.aws.amazon.com/autoscaling/ec2/userguide/ts-as-healthchecks.html Troubleshooting Amazon EC2 Auto Scaling: Health checks>
-- in the /Amazon EC2 Auto Scaling User Guide/. 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/.
--
-- You can use this operation to describe target groups that were attached
-- by using AttachLoadBalancerTargetGroups, but not for target groups that
-- were attached by using AttachTrafficSources.
--
-- This operation returns paginated results.
module Amazonka.AutoScaling.DescribeLoadBalancerTargetGroups
  ( -- * Creating a Request
    DescribeLoadBalancerTargetGroups (..),
    newDescribeLoadBalancerTargetGroups,

    -- * Request Lenses
    describeLoadBalancerTargetGroups_maxRecords,
    describeLoadBalancerTargetGroups_nextToken,
    describeLoadBalancerTargetGroups_autoScalingGroupName,

    -- * Destructuring the Response
    DescribeLoadBalancerTargetGroupsResponse (..),
    newDescribeLoadBalancerTargetGroupsResponse,

    -- * Response Lenses
    describeLoadBalancerTargetGroupsResponse_loadBalancerTargetGroups,
    describeLoadBalancerTargetGroupsResponse_nextToken,
    describeLoadBalancerTargetGroupsResponse_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:/ 'newDescribeLoadBalancerTargetGroups' smart constructor.
data DescribeLoadBalancerTargetGroups = DescribeLoadBalancerTargetGroups'
  { -- | The maximum number of items to return with this call. The default value
    -- is @100@ and the maximum value is @100@.
    DescribeLoadBalancerTargetGroups -> Maybe Int
maxRecords :: Prelude.Maybe Prelude.Int,
    -- | The token for the next set of items to return. (You received this token
    -- from a previous call.)
    DescribeLoadBalancerTargetGroups -> Maybe Text
nextToken :: Prelude.Maybe Prelude.Text,
    -- | The name of the Auto Scaling group.
    DescribeLoadBalancerTargetGroups -> Text
autoScalingGroupName :: Prelude.Text
  }
  deriving (DescribeLoadBalancerTargetGroups
-> DescribeLoadBalancerTargetGroups -> Bool
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: DescribeLoadBalancerTargetGroups
-> DescribeLoadBalancerTargetGroups -> Bool
$c/= :: DescribeLoadBalancerTargetGroups
-> DescribeLoadBalancerTargetGroups -> Bool
== :: DescribeLoadBalancerTargetGroups
-> DescribeLoadBalancerTargetGroups -> Bool
$c== :: DescribeLoadBalancerTargetGroups
-> DescribeLoadBalancerTargetGroups -> Bool
Prelude.Eq, ReadPrec [DescribeLoadBalancerTargetGroups]
ReadPrec DescribeLoadBalancerTargetGroups
Int -> ReadS DescribeLoadBalancerTargetGroups
ReadS [DescribeLoadBalancerTargetGroups]
forall a.
(Int -> ReadS a)
-> ReadS [a] -> ReadPrec a -> ReadPrec [a] -> Read a
readListPrec :: ReadPrec [DescribeLoadBalancerTargetGroups]
$creadListPrec :: ReadPrec [DescribeLoadBalancerTargetGroups]
readPrec :: ReadPrec DescribeLoadBalancerTargetGroups
$creadPrec :: ReadPrec DescribeLoadBalancerTargetGroups
readList :: ReadS [DescribeLoadBalancerTargetGroups]
$creadList :: ReadS [DescribeLoadBalancerTargetGroups]
readsPrec :: Int -> ReadS DescribeLoadBalancerTargetGroups
$creadsPrec :: Int -> ReadS DescribeLoadBalancerTargetGroups
Prelude.Read, Int -> DescribeLoadBalancerTargetGroups -> ShowS
[DescribeLoadBalancerTargetGroups] -> ShowS
DescribeLoadBalancerTargetGroups -> String
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [DescribeLoadBalancerTargetGroups] -> ShowS
$cshowList :: [DescribeLoadBalancerTargetGroups] -> ShowS
show :: DescribeLoadBalancerTargetGroups -> String
$cshow :: DescribeLoadBalancerTargetGroups -> String
showsPrec :: Int -> DescribeLoadBalancerTargetGroups -> ShowS
$cshowsPrec :: Int -> DescribeLoadBalancerTargetGroups -> ShowS
Prelude.Show, forall x.
Rep DescribeLoadBalancerTargetGroups x
-> DescribeLoadBalancerTargetGroups
forall x.
DescribeLoadBalancerTargetGroups
-> Rep DescribeLoadBalancerTargetGroups x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cto :: forall x.
Rep DescribeLoadBalancerTargetGroups x
-> DescribeLoadBalancerTargetGroups
$cfrom :: forall x.
DescribeLoadBalancerTargetGroups
-> Rep DescribeLoadBalancerTargetGroups x
Prelude.Generic)

-- |
-- Create a value of 'DescribeLoadBalancerTargetGroups' 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:
--
-- 'maxRecords', 'describeLoadBalancerTargetGroups_maxRecords' - The maximum number of items to return with this call. The default value
-- is @100@ and the maximum value is @100@.
--
-- 'nextToken', 'describeLoadBalancerTargetGroups_nextToken' - The token for the next set of items to return. (You received this token
-- from a previous call.)
--
-- 'autoScalingGroupName', 'describeLoadBalancerTargetGroups_autoScalingGroupName' - The name of the Auto Scaling group.
newDescribeLoadBalancerTargetGroups ::
  -- | 'autoScalingGroupName'
  Prelude.Text ->
  DescribeLoadBalancerTargetGroups
newDescribeLoadBalancerTargetGroups :: Text -> DescribeLoadBalancerTargetGroups
newDescribeLoadBalancerTargetGroups
  Text
pAutoScalingGroupName_ =
    DescribeLoadBalancerTargetGroups'
      { $sel:maxRecords:DescribeLoadBalancerTargetGroups' :: Maybe Int
maxRecords =
          forall a. Maybe a
Prelude.Nothing,
        $sel:nextToken:DescribeLoadBalancerTargetGroups' :: Maybe Text
nextToken = forall a. Maybe a
Prelude.Nothing,
        $sel:autoScalingGroupName:DescribeLoadBalancerTargetGroups' :: Text
autoScalingGroupName =
          Text
pAutoScalingGroupName_
      }

-- | The maximum number of items to return with this call. The default value
-- is @100@ and the maximum value is @100@.
describeLoadBalancerTargetGroups_maxRecords :: Lens.Lens' DescribeLoadBalancerTargetGroups (Prelude.Maybe Prelude.Int)
describeLoadBalancerTargetGroups_maxRecords :: Lens' DescribeLoadBalancerTargetGroups (Maybe Int)
describeLoadBalancerTargetGroups_maxRecords = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\DescribeLoadBalancerTargetGroups' {Maybe Int
maxRecords :: Maybe Int
$sel:maxRecords:DescribeLoadBalancerTargetGroups' :: DescribeLoadBalancerTargetGroups -> Maybe Int
maxRecords} -> Maybe Int
maxRecords) (\s :: DescribeLoadBalancerTargetGroups
s@DescribeLoadBalancerTargetGroups' {} Maybe Int
a -> DescribeLoadBalancerTargetGroups
s {$sel:maxRecords:DescribeLoadBalancerTargetGroups' :: Maybe Int
maxRecords = Maybe Int
a} :: DescribeLoadBalancerTargetGroups)

-- | The token for the next set of items to return. (You received this token
-- from a previous call.)
describeLoadBalancerTargetGroups_nextToken :: Lens.Lens' DescribeLoadBalancerTargetGroups (Prelude.Maybe Prelude.Text)
describeLoadBalancerTargetGroups_nextToken :: Lens' DescribeLoadBalancerTargetGroups (Maybe Text)
describeLoadBalancerTargetGroups_nextToken = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\DescribeLoadBalancerTargetGroups' {Maybe Text
nextToken :: Maybe Text
$sel:nextToken:DescribeLoadBalancerTargetGroups' :: DescribeLoadBalancerTargetGroups -> Maybe Text
nextToken} -> Maybe Text
nextToken) (\s :: DescribeLoadBalancerTargetGroups
s@DescribeLoadBalancerTargetGroups' {} Maybe Text
a -> DescribeLoadBalancerTargetGroups
s {$sel:nextToken:DescribeLoadBalancerTargetGroups' :: Maybe Text
nextToken = Maybe Text
a} :: DescribeLoadBalancerTargetGroups)

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

instance
  Core.AWSPager
    DescribeLoadBalancerTargetGroups
  where
  page :: DescribeLoadBalancerTargetGroups
-> AWSResponse DescribeLoadBalancerTargetGroups
-> Maybe DescribeLoadBalancerTargetGroups
page DescribeLoadBalancerTargetGroups
rq AWSResponse DescribeLoadBalancerTargetGroups
rs
    | forall a. AWSTruncated a => a -> Bool
Core.stop
        ( AWSResponse DescribeLoadBalancerTargetGroups
rs
            forall s a. s -> Getting (First a) s a -> Maybe a
Lens.^? Lens' DescribeLoadBalancerTargetGroupsResponse (Maybe Text)
describeLoadBalancerTargetGroupsResponse_nextToken
            forall b c a. (b -> c) -> (a -> b) -> a -> c
Prelude.. forall a b. Prism (Maybe a) (Maybe b) a b
Lens._Just
        ) =
        forall a. Maybe a
Prelude.Nothing
    | forall a. AWSTruncated a => a -> Bool
Core.stop
        ( AWSResponse DescribeLoadBalancerTargetGroups
rs
            forall s a. s -> Getting (First a) s a -> Maybe a
Lens.^? Lens'
  DescribeLoadBalancerTargetGroupsResponse
  (Maybe [LoadBalancerTargetGroupState])
describeLoadBalancerTargetGroupsResponse_loadBalancerTargetGroups
            forall b c a. (b -> c) -> (a -> b) -> a -> c
Prelude.. forall a b. Prism (Maybe a) (Maybe b) a b
Lens._Just
        ) =
        forall a. Maybe a
Prelude.Nothing
    | Bool
Prelude.otherwise =
        forall a. a -> Maybe a
Prelude.Just
          forall a b. (a -> b) -> a -> b
Prelude.$ DescribeLoadBalancerTargetGroups
rq
          forall a b. a -> (a -> b) -> b
Prelude.& Lens' DescribeLoadBalancerTargetGroups (Maybe Text)
describeLoadBalancerTargetGroups_nextToken
          forall s t a b. ASetter s t a b -> b -> s -> t
Lens..~ AWSResponse DescribeLoadBalancerTargetGroups
rs
          forall s a. s -> Getting (First a) s a -> Maybe a
Lens.^? Lens' DescribeLoadBalancerTargetGroupsResponse (Maybe Text)
describeLoadBalancerTargetGroupsResponse_nextToken
          forall b c a. (b -> c) -> (a -> b) -> a -> c
Prelude.. forall a b. Prism (Maybe a) (Maybe b) a b
Lens._Just

instance
  Core.AWSRequest
    DescribeLoadBalancerTargetGroups
  where
  type
    AWSResponse DescribeLoadBalancerTargetGroups =
      DescribeLoadBalancerTargetGroupsResponse
  request :: (Service -> Service)
-> DescribeLoadBalancerTargetGroups
-> Request DescribeLoadBalancerTargetGroups
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 DescribeLoadBalancerTargetGroups
-> ClientResponse ClientBody
-> m (Either
        Error
        (ClientResponse (AWSResponse DescribeLoadBalancerTargetGroups)))
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
"DescribeLoadBalancerTargetGroupsResult"
      ( \Int
s ResponseHeaders
h [Node]
x ->
          Maybe [LoadBalancerTargetGroupState]
-> Maybe Text -> Int -> DescribeLoadBalancerTargetGroupsResponse
DescribeLoadBalancerTargetGroupsResponse'
            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
"LoadBalancerTargetGroups"
                            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.<*> ([Node]
x forall a. FromXML a => [Node] -> Text -> Either String (Maybe a)
Data..@? Text
"NextToken")
            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
    DescribeLoadBalancerTargetGroups
  where
  hashWithSalt :: Int -> DescribeLoadBalancerTargetGroups -> Int
hashWithSalt
    Int
_salt
    DescribeLoadBalancerTargetGroups' {Maybe Int
Maybe Text
Text
autoScalingGroupName :: Text
nextToken :: Maybe Text
maxRecords :: Maybe Int
$sel:autoScalingGroupName:DescribeLoadBalancerTargetGroups' :: DescribeLoadBalancerTargetGroups -> Text
$sel:nextToken:DescribeLoadBalancerTargetGroups' :: DescribeLoadBalancerTargetGroups -> Maybe Text
$sel:maxRecords:DescribeLoadBalancerTargetGroups' :: DescribeLoadBalancerTargetGroups -> Maybe Int
..} =
      Int
_salt
        forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Maybe Int
maxRecords
        forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Maybe Text
nextToken
        forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Text
autoScalingGroupName

instance
  Prelude.NFData
    DescribeLoadBalancerTargetGroups
  where
  rnf :: DescribeLoadBalancerTargetGroups -> ()
rnf DescribeLoadBalancerTargetGroups' {Maybe Int
Maybe Text
Text
autoScalingGroupName :: Text
nextToken :: Maybe Text
maxRecords :: Maybe Int
$sel:autoScalingGroupName:DescribeLoadBalancerTargetGroups' :: DescribeLoadBalancerTargetGroups -> Text
$sel:nextToken:DescribeLoadBalancerTargetGroups' :: DescribeLoadBalancerTargetGroups -> Maybe Text
$sel:maxRecords:DescribeLoadBalancerTargetGroups' :: DescribeLoadBalancerTargetGroups -> Maybe Int
..} =
    forall a. NFData a => a -> ()
Prelude.rnf Maybe Int
maxRecords
      seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf Maybe Text
nextToken
      seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf Text
autoScalingGroupName

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

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

instance
  Data.ToQuery
    DescribeLoadBalancerTargetGroups
  where
  toQuery :: DescribeLoadBalancerTargetGroups -> QueryString
toQuery DescribeLoadBalancerTargetGroups' {Maybe Int
Maybe Text
Text
autoScalingGroupName :: Text
nextToken :: Maybe Text
maxRecords :: Maybe Int
$sel:autoScalingGroupName:DescribeLoadBalancerTargetGroups' :: DescribeLoadBalancerTargetGroups -> Text
$sel:nextToken:DescribeLoadBalancerTargetGroups' :: DescribeLoadBalancerTargetGroups -> Maybe Text
$sel:maxRecords:DescribeLoadBalancerTargetGroups' :: DescribeLoadBalancerTargetGroups -> Maybe Int
..} =
    forall a. Monoid a => [a] -> a
Prelude.mconcat
      [ ByteString
"Action"
          forall a. ToQuery a => ByteString -> a -> QueryString
Data.=: ( ByteString
"DescribeLoadBalancerTargetGroups" ::
                      Prelude.ByteString
                  ),
        ByteString
"Version"
          forall a. ToQuery a => ByteString -> a -> QueryString
Data.=: (ByteString
"2011-01-01" :: Prelude.ByteString),
        ByteString
"MaxRecords" forall a. ToQuery a => ByteString -> a -> QueryString
Data.=: Maybe Int
maxRecords,
        ByteString
"NextToken" forall a. ToQuery a => ByteString -> a -> QueryString
Data.=: Maybe Text
nextToken,
        ByteString
"AutoScalingGroupName" forall a. ToQuery a => ByteString -> a -> QueryString
Data.=: Text
autoScalingGroupName
      ]

-- | /See:/ 'newDescribeLoadBalancerTargetGroupsResponse' smart constructor.
data DescribeLoadBalancerTargetGroupsResponse = DescribeLoadBalancerTargetGroupsResponse'
  { -- | Information about the target groups.
    DescribeLoadBalancerTargetGroupsResponse
-> Maybe [LoadBalancerTargetGroupState]
loadBalancerTargetGroups :: Prelude.Maybe [LoadBalancerTargetGroupState],
    -- | A string that indicates that the response contains more items than can
    -- be returned in a single response. To receive additional items, specify
    -- this string for the @NextToken@ value when requesting the next set of
    -- items. This value is null when there are no more items to return.
    DescribeLoadBalancerTargetGroupsResponse -> Maybe Text
nextToken :: Prelude.Maybe Prelude.Text,
    -- | The response's http status code.
    DescribeLoadBalancerTargetGroupsResponse -> Int
httpStatus :: Prelude.Int
  }
  deriving (DescribeLoadBalancerTargetGroupsResponse
-> DescribeLoadBalancerTargetGroupsResponse -> Bool
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: DescribeLoadBalancerTargetGroupsResponse
-> DescribeLoadBalancerTargetGroupsResponse -> Bool
$c/= :: DescribeLoadBalancerTargetGroupsResponse
-> DescribeLoadBalancerTargetGroupsResponse -> Bool
== :: DescribeLoadBalancerTargetGroupsResponse
-> DescribeLoadBalancerTargetGroupsResponse -> Bool
$c== :: DescribeLoadBalancerTargetGroupsResponse
-> DescribeLoadBalancerTargetGroupsResponse -> Bool
Prelude.Eq, ReadPrec [DescribeLoadBalancerTargetGroupsResponse]
ReadPrec DescribeLoadBalancerTargetGroupsResponse
Int -> ReadS DescribeLoadBalancerTargetGroupsResponse
ReadS [DescribeLoadBalancerTargetGroupsResponse]
forall a.
(Int -> ReadS a)
-> ReadS [a] -> ReadPrec a -> ReadPrec [a] -> Read a
readListPrec :: ReadPrec [DescribeLoadBalancerTargetGroupsResponse]
$creadListPrec :: ReadPrec [DescribeLoadBalancerTargetGroupsResponse]
readPrec :: ReadPrec DescribeLoadBalancerTargetGroupsResponse
$creadPrec :: ReadPrec DescribeLoadBalancerTargetGroupsResponse
readList :: ReadS [DescribeLoadBalancerTargetGroupsResponse]
$creadList :: ReadS [DescribeLoadBalancerTargetGroupsResponse]
readsPrec :: Int -> ReadS DescribeLoadBalancerTargetGroupsResponse
$creadsPrec :: Int -> ReadS DescribeLoadBalancerTargetGroupsResponse
Prelude.Read, Int -> DescribeLoadBalancerTargetGroupsResponse -> ShowS
[DescribeLoadBalancerTargetGroupsResponse] -> ShowS
DescribeLoadBalancerTargetGroupsResponse -> String
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [DescribeLoadBalancerTargetGroupsResponse] -> ShowS
$cshowList :: [DescribeLoadBalancerTargetGroupsResponse] -> ShowS
show :: DescribeLoadBalancerTargetGroupsResponse -> String
$cshow :: DescribeLoadBalancerTargetGroupsResponse -> String
showsPrec :: Int -> DescribeLoadBalancerTargetGroupsResponse -> ShowS
$cshowsPrec :: Int -> DescribeLoadBalancerTargetGroupsResponse -> ShowS
Prelude.Show, forall x.
Rep DescribeLoadBalancerTargetGroupsResponse x
-> DescribeLoadBalancerTargetGroupsResponse
forall x.
DescribeLoadBalancerTargetGroupsResponse
-> Rep DescribeLoadBalancerTargetGroupsResponse x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cto :: forall x.
Rep DescribeLoadBalancerTargetGroupsResponse x
-> DescribeLoadBalancerTargetGroupsResponse
$cfrom :: forall x.
DescribeLoadBalancerTargetGroupsResponse
-> Rep DescribeLoadBalancerTargetGroupsResponse x
Prelude.Generic)

-- |
-- Create a value of 'DescribeLoadBalancerTargetGroupsResponse' 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:
--
-- 'loadBalancerTargetGroups', 'describeLoadBalancerTargetGroupsResponse_loadBalancerTargetGroups' - Information about the target groups.
--
-- 'nextToken', 'describeLoadBalancerTargetGroupsResponse_nextToken' - A string that indicates that the response contains more items than can
-- be returned in a single response. To receive additional items, specify
-- this string for the @NextToken@ value when requesting the next set of
-- items. This value is null when there are no more items to return.
--
-- 'httpStatus', 'describeLoadBalancerTargetGroupsResponse_httpStatus' - The response's http status code.
newDescribeLoadBalancerTargetGroupsResponse ::
  -- | 'httpStatus'
  Prelude.Int ->
  DescribeLoadBalancerTargetGroupsResponse
newDescribeLoadBalancerTargetGroupsResponse :: Int -> DescribeLoadBalancerTargetGroupsResponse
newDescribeLoadBalancerTargetGroupsResponse
  Int
pHttpStatus_ =
    DescribeLoadBalancerTargetGroupsResponse'
      { $sel:loadBalancerTargetGroups:DescribeLoadBalancerTargetGroupsResponse' :: Maybe [LoadBalancerTargetGroupState]
loadBalancerTargetGroups =
          forall a. Maybe a
Prelude.Nothing,
        $sel:nextToken:DescribeLoadBalancerTargetGroupsResponse' :: Maybe Text
nextToken = forall a. Maybe a
Prelude.Nothing,
        $sel:httpStatus:DescribeLoadBalancerTargetGroupsResponse' :: Int
httpStatus = Int
pHttpStatus_
      }

-- | Information about the target groups.
describeLoadBalancerTargetGroupsResponse_loadBalancerTargetGroups :: Lens.Lens' DescribeLoadBalancerTargetGroupsResponse (Prelude.Maybe [LoadBalancerTargetGroupState])
describeLoadBalancerTargetGroupsResponse_loadBalancerTargetGroups :: Lens'
  DescribeLoadBalancerTargetGroupsResponse
  (Maybe [LoadBalancerTargetGroupState])
describeLoadBalancerTargetGroupsResponse_loadBalancerTargetGroups = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\DescribeLoadBalancerTargetGroupsResponse' {Maybe [LoadBalancerTargetGroupState]
loadBalancerTargetGroups :: Maybe [LoadBalancerTargetGroupState]
$sel:loadBalancerTargetGroups:DescribeLoadBalancerTargetGroupsResponse' :: DescribeLoadBalancerTargetGroupsResponse
-> Maybe [LoadBalancerTargetGroupState]
loadBalancerTargetGroups} -> Maybe [LoadBalancerTargetGroupState]
loadBalancerTargetGroups) (\s :: DescribeLoadBalancerTargetGroupsResponse
s@DescribeLoadBalancerTargetGroupsResponse' {} Maybe [LoadBalancerTargetGroupState]
a -> DescribeLoadBalancerTargetGroupsResponse
s {$sel:loadBalancerTargetGroups:DescribeLoadBalancerTargetGroupsResponse' :: Maybe [LoadBalancerTargetGroupState]
loadBalancerTargetGroups = Maybe [LoadBalancerTargetGroupState]
a} :: DescribeLoadBalancerTargetGroupsResponse) 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

-- | A string that indicates that the response contains more items than can
-- be returned in a single response. To receive additional items, specify
-- this string for the @NextToken@ value when requesting the next set of
-- items. This value is null when there are no more items to return.
describeLoadBalancerTargetGroupsResponse_nextToken :: Lens.Lens' DescribeLoadBalancerTargetGroupsResponse (Prelude.Maybe Prelude.Text)
describeLoadBalancerTargetGroupsResponse_nextToken :: Lens' DescribeLoadBalancerTargetGroupsResponse (Maybe Text)
describeLoadBalancerTargetGroupsResponse_nextToken = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\DescribeLoadBalancerTargetGroupsResponse' {Maybe Text
nextToken :: Maybe Text
$sel:nextToken:DescribeLoadBalancerTargetGroupsResponse' :: DescribeLoadBalancerTargetGroupsResponse -> Maybe Text
nextToken} -> Maybe Text
nextToken) (\s :: DescribeLoadBalancerTargetGroupsResponse
s@DescribeLoadBalancerTargetGroupsResponse' {} Maybe Text
a -> DescribeLoadBalancerTargetGroupsResponse
s {$sel:nextToken:DescribeLoadBalancerTargetGroupsResponse' :: Maybe Text
nextToken = Maybe Text
a} :: DescribeLoadBalancerTargetGroupsResponse)

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

instance
  Prelude.NFData
    DescribeLoadBalancerTargetGroupsResponse
  where
  rnf :: DescribeLoadBalancerTargetGroupsResponse -> ()
rnf DescribeLoadBalancerTargetGroupsResponse' {Int
Maybe [LoadBalancerTargetGroupState]
Maybe Text
httpStatus :: Int
nextToken :: Maybe Text
loadBalancerTargetGroups :: Maybe [LoadBalancerTargetGroupState]
$sel:httpStatus:DescribeLoadBalancerTargetGroupsResponse' :: DescribeLoadBalancerTargetGroupsResponse -> Int
$sel:nextToken:DescribeLoadBalancerTargetGroupsResponse' :: DescribeLoadBalancerTargetGroupsResponse -> Maybe Text
$sel:loadBalancerTargetGroups:DescribeLoadBalancerTargetGroupsResponse' :: DescribeLoadBalancerTargetGroupsResponse
-> Maybe [LoadBalancerTargetGroupState]
..} =
    forall a. NFData a => a -> ()
Prelude.rnf Maybe [LoadBalancerTargetGroupState]
loadBalancerTargetGroups
      seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf Maybe Text
nextToken
      seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf Int
httpStatus