{-# 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.RDS.DescribeDBProxyTargetGroups
-- Copyright   : (c) 2013-2023 Brendan Hay
-- License     : Mozilla Public License, v. 2.0.
-- Maintainer  : Brendan Hay
-- Stability   : auto-generated
-- Portability : non-portable (GHC extensions)
--
-- Returns information about DB proxy target groups, represented by
-- @DBProxyTargetGroup@ data structures.
--
-- This operation returns paginated results.
module Amazonka.RDS.DescribeDBProxyTargetGroups
  ( -- * Creating a Request
    DescribeDBProxyTargetGroups (..),
    newDescribeDBProxyTargetGroups,

    -- * Request Lenses
    describeDBProxyTargetGroups_filters,
    describeDBProxyTargetGroups_marker,
    describeDBProxyTargetGroups_maxRecords,
    describeDBProxyTargetGroups_targetGroupName,
    describeDBProxyTargetGroups_dbProxyName,

    -- * Destructuring the Response
    DescribeDBProxyTargetGroupsResponse (..),
    newDescribeDBProxyTargetGroupsResponse,

    -- * Response Lenses
    describeDBProxyTargetGroupsResponse_marker,
    describeDBProxyTargetGroupsResponse_targetGroups,
    describeDBProxyTargetGroupsResponse_httpStatus,
  )
where

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 Amazonka.RDS.Types
import qualified Amazonka.Request as Request
import qualified Amazonka.Response as Response

-- | /See:/ 'newDescribeDBProxyTargetGroups' smart constructor.
data DescribeDBProxyTargetGroups = DescribeDBProxyTargetGroups'
  { -- | This parameter is not currently supported.
    DescribeDBProxyTargetGroups -> Maybe [Filter]
filters :: Prelude.Maybe [Filter],
    -- | An optional pagination token provided by a previous request. If this
    -- parameter is specified, the response includes only records beyond the
    -- marker, up to the value specified by @MaxRecords@.
    DescribeDBProxyTargetGroups -> Maybe Text
marker :: Prelude.Maybe Prelude.Text,
    -- | The maximum number of records to include in the response. If more
    -- records exist than the specified @MaxRecords@ value, a pagination token
    -- called a marker is included in the response so that the remaining
    -- results can be retrieved.
    --
    -- Default: 100
    --
    -- Constraints: Minimum 20, maximum 100.
    DescribeDBProxyTargetGroups -> Maybe Natural
maxRecords :: Prelude.Maybe Prelude.Natural,
    -- | The identifier of the @DBProxyTargetGroup@ to describe.
    DescribeDBProxyTargetGroups -> Maybe Text
targetGroupName :: Prelude.Maybe Prelude.Text,
    -- | The identifier of the @DBProxy@ associated with the target group.
    DescribeDBProxyTargetGroups -> Text
dbProxyName :: Prelude.Text
  }
  deriving (DescribeDBProxyTargetGroups -> DescribeDBProxyTargetGroups -> Bool
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: DescribeDBProxyTargetGroups -> DescribeDBProxyTargetGroups -> Bool
$c/= :: DescribeDBProxyTargetGroups -> DescribeDBProxyTargetGroups -> Bool
== :: DescribeDBProxyTargetGroups -> DescribeDBProxyTargetGroups -> Bool
$c== :: DescribeDBProxyTargetGroups -> DescribeDBProxyTargetGroups -> Bool
Prelude.Eq, ReadPrec [DescribeDBProxyTargetGroups]
ReadPrec DescribeDBProxyTargetGroups
Int -> ReadS DescribeDBProxyTargetGroups
ReadS [DescribeDBProxyTargetGroups]
forall a.
(Int -> ReadS a)
-> ReadS [a] -> ReadPrec a -> ReadPrec [a] -> Read a
readListPrec :: ReadPrec [DescribeDBProxyTargetGroups]
$creadListPrec :: ReadPrec [DescribeDBProxyTargetGroups]
readPrec :: ReadPrec DescribeDBProxyTargetGroups
$creadPrec :: ReadPrec DescribeDBProxyTargetGroups
readList :: ReadS [DescribeDBProxyTargetGroups]
$creadList :: ReadS [DescribeDBProxyTargetGroups]
readsPrec :: Int -> ReadS DescribeDBProxyTargetGroups
$creadsPrec :: Int -> ReadS DescribeDBProxyTargetGroups
Prelude.Read, Int -> DescribeDBProxyTargetGroups -> ShowS
[DescribeDBProxyTargetGroups] -> ShowS
DescribeDBProxyTargetGroups -> String
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [DescribeDBProxyTargetGroups] -> ShowS
$cshowList :: [DescribeDBProxyTargetGroups] -> ShowS
show :: DescribeDBProxyTargetGroups -> String
$cshow :: DescribeDBProxyTargetGroups -> String
showsPrec :: Int -> DescribeDBProxyTargetGroups -> ShowS
$cshowsPrec :: Int -> DescribeDBProxyTargetGroups -> ShowS
Prelude.Show, forall x.
Rep DescribeDBProxyTargetGroups x -> DescribeDBProxyTargetGroups
forall x.
DescribeDBProxyTargetGroups -> Rep DescribeDBProxyTargetGroups x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cto :: forall x.
Rep DescribeDBProxyTargetGroups x -> DescribeDBProxyTargetGroups
$cfrom :: forall x.
DescribeDBProxyTargetGroups -> Rep DescribeDBProxyTargetGroups x
Prelude.Generic)

-- |
-- Create a value of 'DescribeDBProxyTargetGroups' 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:
--
-- 'filters', 'describeDBProxyTargetGroups_filters' - This parameter is not currently supported.
--
-- 'marker', 'describeDBProxyTargetGroups_marker' - An optional pagination token provided by a previous request. If this
-- parameter is specified, the response includes only records beyond the
-- marker, up to the value specified by @MaxRecords@.
--
-- 'maxRecords', 'describeDBProxyTargetGroups_maxRecords' - The maximum number of records to include in the response. If more
-- records exist than the specified @MaxRecords@ value, a pagination token
-- called a marker is included in the response so that the remaining
-- results can be retrieved.
--
-- Default: 100
--
-- Constraints: Minimum 20, maximum 100.
--
-- 'targetGroupName', 'describeDBProxyTargetGroups_targetGroupName' - The identifier of the @DBProxyTargetGroup@ to describe.
--
-- 'dbProxyName', 'describeDBProxyTargetGroups_dbProxyName' - The identifier of the @DBProxy@ associated with the target group.
newDescribeDBProxyTargetGroups ::
  -- | 'dbProxyName'
  Prelude.Text ->
  DescribeDBProxyTargetGroups
newDescribeDBProxyTargetGroups :: Text -> DescribeDBProxyTargetGroups
newDescribeDBProxyTargetGroups Text
pDBProxyName_ =
  DescribeDBProxyTargetGroups'
    { $sel:filters:DescribeDBProxyTargetGroups' :: Maybe [Filter]
filters =
        forall a. Maybe a
Prelude.Nothing,
      $sel:marker:DescribeDBProxyTargetGroups' :: Maybe Text
marker = forall a. Maybe a
Prelude.Nothing,
      $sel:maxRecords:DescribeDBProxyTargetGroups' :: Maybe Natural
maxRecords = forall a. Maybe a
Prelude.Nothing,
      $sel:targetGroupName:DescribeDBProxyTargetGroups' :: Maybe Text
targetGroupName = forall a. Maybe a
Prelude.Nothing,
      $sel:dbProxyName:DescribeDBProxyTargetGroups' :: Text
dbProxyName = Text
pDBProxyName_
    }

-- | This parameter is not currently supported.
describeDBProxyTargetGroups_filters :: Lens.Lens' DescribeDBProxyTargetGroups (Prelude.Maybe [Filter])
describeDBProxyTargetGroups_filters :: Lens' DescribeDBProxyTargetGroups (Maybe [Filter])
describeDBProxyTargetGroups_filters = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\DescribeDBProxyTargetGroups' {Maybe [Filter]
filters :: Maybe [Filter]
$sel:filters:DescribeDBProxyTargetGroups' :: DescribeDBProxyTargetGroups -> Maybe [Filter]
filters} -> Maybe [Filter]
filters) (\s :: DescribeDBProxyTargetGroups
s@DescribeDBProxyTargetGroups' {} Maybe [Filter]
a -> DescribeDBProxyTargetGroups
s {$sel:filters:DescribeDBProxyTargetGroups' :: Maybe [Filter]
filters = Maybe [Filter]
a} :: DescribeDBProxyTargetGroups) 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

-- | An optional pagination token provided by a previous request. If this
-- parameter is specified, the response includes only records beyond the
-- marker, up to the value specified by @MaxRecords@.
describeDBProxyTargetGroups_marker :: Lens.Lens' DescribeDBProxyTargetGroups (Prelude.Maybe Prelude.Text)
describeDBProxyTargetGroups_marker :: Lens' DescribeDBProxyTargetGroups (Maybe Text)
describeDBProxyTargetGroups_marker = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\DescribeDBProxyTargetGroups' {Maybe Text
marker :: Maybe Text
$sel:marker:DescribeDBProxyTargetGroups' :: DescribeDBProxyTargetGroups -> Maybe Text
marker} -> Maybe Text
marker) (\s :: DescribeDBProxyTargetGroups
s@DescribeDBProxyTargetGroups' {} Maybe Text
a -> DescribeDBProxyTargetGroups
s {$sel:marker:DescribeDBProxyTargetGroups' :: Maybe Text
marker = Maybe Text
a} :: DescribeDBProxyTargetGroups)

-- | The maximum number of records to include in the response. If more
-- records exist than the specified @MaxRecords@ value, a pagination token
-- called a marker is included in the response so that the remaining
-- results can be retrieved.
--
-- Default: 100
--
-- Constraints: Minimum 20, maximum 100.
describeDBProxyTargetGroups_maxRecords :: Lens.Lens' DescribeDBProxyTargetGroups (Prelude.Maybe Prelude.Natural)
describeDBProxyTargetGroups_maxRecords :: Lens' DescribeDBProxyTargetGroups (Maybe Natural)
describeDBProxyTargetGroups_maxRecords = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\DescribeDBProxyTargetGroups' {Maybe Natural
maxRecords :: Maybe Natural
$sel:maxRecords:DescribeDBProxyTargetGroups' :: DescribeDBProxyTargetGroups -> Maybe Natural
maxRecords} -> Maybe Natural
maxRecords) (\s :: DescribeDBProxyTargetGroups
s@DescribeDBProxyTargetGroups' {} Maybe Natural
a -> DescribeDBProxyTargetGroups
s {$sel:maxRecords:DescribeDBProxyTargetGroups' :: Maybe Natural
maxRecords = Maybe Natural
a} :: DescribeDBProxyTargetGroups)

-- | The identifier of the @DBProxyTargetGroup@ to describe.
describeDBProxyTargetGroups_targetGroupName :: Lens.Lens' DescribeDBProxyTargetGroups (Prelude.Maybe Prelude.Text)
describeDBProxyTargetGroups_targetGroupName :: Lens' DescribeDBProxyTargetGroups (Maybe Text)
describeDBProxyTargetGroups_targetGroupName = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\DescribeDBProxyTargetGroups' {Maybe Text
targetGroupName :: Maybe Text
$sel:targetGroupName:DescribeDBProxyTargetGroups' :: DescribeDBProxyTargetGroups -> Maybe Text
targetGroupName} -> Maybe Text
targetGroupName) (\s :: DescribeDBProxyTargetGroups
s@DescribeDBProxyTargetGroups' {} Maybe Text
a -> DescribeDBProxyTargetGroups
s {$sel:targetGroupName:DescribeDBProxyTargetGroups' :: Maybe Text
targetGroupName = Maybe Text
a} :: DescribeDBProxyTargetGroups)

-- | The identifier of the @DBProxy@ associated with the target group.
describeDBProxyTargetGroups_dbProxyName :: Lens.Lens' DescribeDBProxyTargetGroups Prelude.Text
describeDBProxyTargetGroups_dbProxyName :: Lens' DescribeDBProxyTargetGroups Text
describeDBProxyTargetGroups_dbProxyName = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\DescribeDBProxyTargetGroups' {Text
dbProxyName :: Text
$sel:dbProxyName:DescribeDBProxyTargetGroups' :: DescribeDBProxyTargetGroups -> Text
dbProxyName} -> Text
dbProxyName) (\s :: DescribeDBProxyTargetGroups
s@DescribeDBProxyTargetGroups' {} Text
a -> DescribeDBProxyTargetGroups
s {$sel:dbProxyName:DescribeDBProxyTargetGroups' :: Text
dbProxyName = Text
a} :: DescribeDBProxyTargetGroups)

instance Core.AWSPager DescribeDBProxyTargetGroups where
  page :: DescribeDBProxyTargetGroups
-> AWSResponse DescribeDBProxyTargetGroups
-> Maybe DescribeDBProxyTargetGroups
page DescribeDBProxyTargetGroups
rq AWSResponse DescribeDBProxyTargetGroups
rs
    | forall a. AWSTruncated a => a -> Bool
Core.stop
        ( AWSResponse DescribeDBProxyTargetGroups
rs
            forall s a. s -> Getting (First a) s a -> Maybe a
Lens.^? Lens' DescribeDBProxyTargetGroupsResponse (Maybe Text)
describeDBProxyTargetGroupsResponse_marker
            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 DescribeDBProxyTargetGroups
rs
            forall s a. s -> Getting (First a) s a -> Maybe a
Lens.^? Lens'
  DescribeDBProxyTargetGroupsResponse (Maybe [DBProxyTargetGroup])
describeDBProxyTargetGroupsResponse_targetGroups
            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.$ DescribeDBProxyTargetGroups
rq
          forall a b. a -> (a -> b) -> b
Prelude.& Lens' DescribeDBProxyTargetGroups (Maybe Text)
describeDBProxyTargetGroups_marker
          forall s t a b. ASetter s t a b -> b -> s -> t
Lens..~ AWSResponse DescribeDBProxyTargetGroups
rs
          forall s a. s -> Getting (First a) s a -> Maybe a
Lens.^? Lens' DescribeDBProxyTargetGroupsResponse (Maybe Text)
describeDBProxyTargetGroupsResponse_marker
          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 DescribeDBProxyTargetGroups where
  type
    AWSResponse DescribeDBProxyTargetGroups =
      DescribeDBProxyTargetGroupsResponse
  request :: (Service -> Service)
-> DescribeDBProxyTargetGroups
-> Request DescribeDBProxyTargetGroups
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 DescribeDBProxyTargetGroups
-> ClientResponse ClientBody
-> m (Either
        Error (ClientResponse (AWSResponse DescribeDBProxyTargetGroups)))
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
"DescribeDBProxyTargetGroupsResult"
      ( \Int
s ResponseHeaders
h [Node]
x ->
          Maybe Text
-> Maybe [DBProxyTargetGroup]
-> Int
-> DescribeDBProxyTargetGroupsResponse
DescribeDBProxyTargetGroupsResponse'
            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
"Marker")
            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
"TargetGroups"
                            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 DescribeDBProxyTargetGroups where
  hashWithSalt :: Int -> DescribeDBProxyTargetGroups -> Int
hashWithSalt Int
_salt DescribeDBProxyTargetGroups' {Maybe Natural
Maybe [Filter]
Maybe Text
Text
dbProxyName :: Text
targetGroupName :: Maybe Text
maxRecords :: Maybe Natural
marker :: Maybe Text
filters :: Maybe [Filter]
$sel:dbProxyName:DescribeDBProxyTargetGroups' :: DescribeDBProxyTargetGroups -> Text
$sel:targetGroupName:DescribeDBProxyTargetGroups' :: DescribeDBProxyTargetGroups -> Maybe Text
$sel:maxRecords:DescribeDBProxyTargetGroups' :: DescribeDBProxyTargetGroups -> Maybe Natural
$sel:marker:DescribeDBProxyTargetGroups' :: DescribeDBProxyTargetGroups -> Maybe Text
$sel:filters:DescribeDBProxyTargetGroups' :: DescribeDBProxyTargetGroups -> Maybe [Filter]
..} =
    Int
_salt
      forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Maybe [Filter]
filters
      forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Maybe Text
marker
      forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Maybe Natural
maxRecords
      forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Maybe Text
targetGroupName
      forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Text
dbProxyName

instance Prelude.NFData DescribeDBProxyTargetGroups where
  rnf :: DescribeDBProxyTargetGroups -> ()
rnf DescribeDBProxyTargetGroups' {Maybe Natural
Maybe [Filter]
Maybe Text
Text
dbProxyName :: Text
targetGroupName :: Maybe Text
maxRecords :: Maybe Natural
marker :: Maybe Text
filters :: Maybe [Filter]
$sel:dbProxyName:DescribeDBProxyTargetGroups' :: DescribeDBProxyTargetGroups -> Text
$sel:targetGroupName:DescribeDBProxyTargetGroups' :: DescribeDBProxyTargetGroups -> Maybe Text
$sel:maxRecords:DescribeDBProxyTargetGroups' :: DescribeDBProxyTargetGroups -> Maybe Natural
$sel:marker:DescribeDBProxyTargetGroups' :: DescribeDBProxyTargetGroups -> Maybe Text
$sel:filters:DescribeDBProxyTargetGroups' :: DescribeDBProxyTargetGroups -> Maybe [Filter]
..} =
    forall a. NFData a => a -> ()
Prelude.rnf Maybe [Filter]
filters
      seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf Maybe Text
marker
      seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf Maybe Natural
maxRecords
      seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf Maybe Text
targetGroupName
      seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf Text
dbProxyName

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

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

instance Data.ToQuery DescribeDBProxyTargetGroups where
  toQuery :: DescribeDBProxyTargetGroups -> QueryString
toQuery DescribeDBProxyTargetGroups' {Maybe Natural
Maybe [Filter]
Maybe Text
Text
dbProxyName :: Text
targetGroupName :: Maybe Text
maxRecords :: Maybe Natural
marker :: Maybe Text
filters :: Maybe [Filter]
$sel:dbProxyName:DescribeDBProxyTargetGroups' :: DescribeDBProxyTargetGroups -> Text
$sel:targetGroupName:DescribeDBProxyTargetGroups' :: DescribeDBProxyTargetGroups -> Maybe Text
$sel:maxRecords:DescribeDBProxyTargetGroups' :: DescribeDBProxyTargetGroups -> Maybe Natural
$sel:marker:DescribeDBProxyTargetGroups' :: DescribeDBProxyTargetGroups -> Maybe Text
$sel:filters:DescribeDBProxyTargetGroups' :: DescribeDBProxyTargetGroups -> Maybe [Filter]
..} =
    forall a. Monoid a => [a] -> a
Prelude.mconcat
      [ ByteString
"Action"
          forall a. ToQuery a => ByteString -> a -> QueryString
Data.=: ( ByteString
"DescribeDBProxyTargetGroups" ::
                      Prelude.ByteString
                  ),
        ByteString
"Version"
          forall a. ToQuery a => ByteString -> a -> QueryString
Data.=: (ByteString
"2014-10-31" :: Prelude.ByteString),
        ByteString
"Filters"
          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
"Filter" forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
Prelude.<$> Maybe [Filter]
filters),
        ByteString
"Marker" forall a. ToQuery a => ByteString -> a -> QueryString
Data.=: Maybe Text
marker,
        ByteString
"MaxRecords" forall a. ToQuery a => ByteString -> a -> QueryString
Data.=: Maybe Natural
maxRecords,
        ByteString
"TargetGroupName" forall a. ToQuery a => ByteString -> a -> QueryString
Data.=: Maybe Text
targetGroupName,
        ByteString
"DBProxyName" forall a. ToQuery a => ByteString -> a -> QueryString
Data.=: Text
dbProxyName
      ]

-- | /See:/ 'newDescribeDBProxyTargetGroupsResponse' smart constructor.
data DescribeDBProxyTargetGroupsResponse = DescribeDBProxyTargetGroupsResponse'
  { -- | An optional pagination token provided by a previous request. If this
    -- parameter is specified, the response includes only records beyond the
    -- marker, up to the value specified by @MaxRecords@.
    DescribeDBProxyTargetGroupsResponse -> Maybe Text
marker :: Prelude.Maybe Prelude.Text,
    -- | An arbitrary number of @DBProxyTargetGroup@ objects, containing details
    -- of the corresponding target groups.
    DescribeDBProxyTargetGroupsResponse -> Maybe [DBProxyTargetGroup]
targetGroups :: Prelude.Maybe [DBProxyTargetGroup],
    -- | The response's http status code.
    DescribeDBProxyTargetGroupsResponse -> Int
httpStatus :: Prelude.Int
  }
  deriving (DescribeDBProxyTargetGroupsResponse
-> DescribeDBProxyTargetGroupsResponse -> Bool
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: DescribeDBProxyTargetGroupsResponse
-> DescribeDBProxyTargetGroupsResponse -> Bool
$c/= :: DescribeDBProxyTargetGroupsResponse
-> DescribeDBProxyTargetGroupsResponse -> Bool
== :: DescribeDBProxyTargetGroupsResponse
-> DescribeDBProxyTargetGroupsResponse -> Bool
$c== :: DescribeDBProxyTargetGroupsResponse
-> DescribeDBProxyTargetGroupsResponse -> Bool
Prelude.Eq, ReadPrec [DescribeDBProxyTargetGroupsResponse]
ReadPrec DescribeDBProxyTargetGroupsResponse
Int -> ReadS DescribeDBProxyTargetGroupsResponse
ReadS [DescribeDBProxyTargetGroupsResponse]
forall a.
(Int -> ReadS a)
-> ReadS [a] -> ReadPrec a -> ReadPrec [a] -> Read a
readListPrec :: ReadPrec [DescribeDBProxyTargetGroupsResponse]
$creadListPrec :: ReadPrec [DescribeDBProxyTargetGroupsResponse]
readPrec :: ReadPrec DescribeDBProxyTargetGroupsResponse
$creadPrec :: ReadPrec DescribeDBProxyTargetGroupsResponse
readList :: ReadS [DescribeDBProxyTargetGroupsResponse]
$creadList :: ReadS [DescribeDBProxyTargetGroupsResponse]
readsPrec :: Int -> ReadS DescribeDBProxyTargetGroupsResponse
$creadsPrec :: Int -> ReadS DescribeDBProxyTargetGroupsResponse
Prelude.Read, Int -> DescribeDBProxyTargetGroupsResponse -> ShowS
[DescribeDBProxyTargetGroupsResponse] -> ShowS
DescribeDBProxyTargetGroupsResponse -> String
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [DescribeDBProxyTargetGroupsResponse] -> ShowS
$cshowList :: [DescribeDBProxyTargetGroupsResponse] -> ShowS
show :: DescribeDBProxyTargetGroupsResponse -> String
$cshow :: DescribeDBProxyTargetGroupsResponse -> String
showsPrec :: Int -> DescribeDBProxyTargetGroupsResponse -> ShowS
$cshowsPrec :: Int -> DescribeDBProxyTargetGroupsResponse -> ShowS
Prelude.Show, forall x.
Rep DescribeDBProxyTargetGroupsResponse x
-> DescribeDBProxyTargetGroupsResponse
forall x.
DescribeDBProxyTargetGroupsResponse
-> Rep DescribeDBProxyTargetGroupsResponse x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cto :: forall x.
Rep DescribeDBProxyTargetGroupsResponse x
-> DescribeDBProxyTargetGroupsResponse
$cfrom :: forall x.
DescribeDBProxyTargetGroupsResponse
-> Rep DescribeDBProxyTargetGroupsResponse x
Prelude.Generic)

-- |
-- Create a value of 'DescribeDBProxyTargetGroupsResponse' 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:
--
-- 'marker', 'describeDBProxyTargetGroupsResponse_marker' - An optional pagination token provided by a previous request. If this
-- parameter is specified, the response includes only records beyond the
-- marker, up to the value specified by @MaxRecords@.
--
-- 'targetGroups', 'describeDBProxyTargetGroupsResponse_targetGroups' - An arbitrary number of @DBProxyTargetGroup@ objects, containing details
-- of the corresponding target groups.
--
-- 'httpStatus', 'describeDBProxyTargetGroupsResponse_httpStatus' - The response's http status code.
newDescribeDBProxyTargetGroupsResponse ::
  -- | 'httpStatus'
  Prelude.Int ->
  DescribeDBProxyTargetGroupsResponse
newDescribeDBProxyTargetGroupsResponse :: Int -> DescribeDBProxyTargetGroupsResponse
newDescribeDBProxyTargetGroupsResponse Int
pHttpStatus_ =
  DescribeDBProxyTargetGroupsResponse'
    { $sel:marker:DescribeDBProxyTargetGroupsResponse' :: Maybe Text
marker =
        forall a. Maybe a
Prelude.Nothing,
      $sel:targetGroups:DescribeDBProxyTargetGroupsResponse' :: Maybe [DBProxyTargetGroup]
targetGroups = forall a. Maybe a
Prelude.Nothing,
      $sel:httpStatus:DescribeDBProxyTargetGroupsResponse' :: Int
httpStatus = Int
pHttpStatus_
    }

-- | An optional pagination token provided by a previous request. If this
-- parameter is specified, the response includes only records beyond the
-- marker, up to the value specified by @MaxRecords@.
describeDBProxyTargetGroupsResponse_marker :: Lens.Lens' DescribeDBProxyTargetGroupsResponse (Prelude.Maybe Prelude.Text)
describeDBProxyTargetGroupsResponse_marker :: Lens' DescribeDBProxyTargetGroupsResponse (Maybe Text)
describeDBProxyTargetGroupsResponse_marker = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\DescribeDBProxyTargetGroupsResponse' {Maybe Text
marker :: Maybe Text
$sel:marker:DescribeDBProxyTargetGroupsResponse' :: DescribeDBProxyTargetGroupsResponse -> Maybe Text
marker} -> Maybe Text
marker) (\s :: DescribeDBProxyTargetGroupsResponse
s@DescribeDBProxyTargetGroupsResponse' {} Maybe Text
a -> DescribeDBProxyTargetGroupsResponse
s {$sel:marker:DescribeDBProxyTargetGroupsResponse' :: Maybe Text
marker = Maybe Text
a} :: DescribeDBProxyTargetGroupsResponse)

-- | An arbitrary number of @DBProxyTargetGroup@ objects, containing details
-- of the corresponding target groups.
describeDBProxyTargetGroupsResponse_targetGroups :: Lens.Lens' DescribeDBProxyTargetGroupsResponse (Prelude.Maybe [DBProxyTargetGroup])
describeDBProxyTargetGroupsResponse_targetGroups :: Lens'
  DescribeDBProxyTargetGroupsResponse (Maybe [DBProxyTargetGroup])
describeDBProxyTargetGroupsResponse_targetGroups = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\DescribeDBProxyTargetGroupsResponse' {Maybe [DBProxyTargetGroup]
targetGroups :: Maybe [DBProxyTargetGroup]
$sel:targetGroups:DescribeDBProxyTargetGroupsResponse' :: DescribeDBProxyTargetGroupsResponse -> Maybe [DBProxyTargetGroup]
targetGroups} -> Maybe [DBProxyTargetGroup]
targetGroups) (\s :: DescribeDBProxyTargetGroupsResponse
s@DescribeDBProxyTargetGroupsResponse' {} Maybe [DBProxyTargetGroup]
a -> DescribeDBProxyTargetGroupsResponse
s {$sel:targetGroups:DescribeDBProxyTargetGroupsResponse' :: Maybe [DBProxyTargetGroup]
targetGroups = Maybe [DBProxyTargetGroup]
a} :: DescribeDBProxyTargetGroupsResponse) 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.
describeDBProxyTargetGroupsResponse_httpStatus :: Lens.Lens' DescribeDBProxyTargetGroupsResponse Prelude.Int
describeDBProxyTargetGroupsResponse_httpStatus :: Lens' DescribeDBProxyTargetGroupsResponse Int
describeDBProxyTargetGroupsResponse_httpStatus = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\DescribeDBProxyTargetGroupsResponse' {Int
httpStatus :: Int
$sel:httpStatus:DescribeDBProxyTargetGroupsResponse' :: DescribeDBProxyTargetGroupsResponse -> Int
httpStatus} -> Int
httpStatus) (\s :: DescribeDBProxyTargetGroupsResponse
s@DescribeDBProxyTargetGroupsResponse' {} Int
a -> DescribeDBProxyTargetGroupsResponse
s {$sel:httpStatus:DescribeDBProxyTargetGroupsResponse' :: Int
httpStatus = Int
a} :: DescribeDBProxyTargetGroupsResponse)

instance
  Prelude.NFData
    DescribeDBProxyTargetGroupsResponse
  where
  rnf :: DescribeDBProxyTargetGroupsResponse -> ()
rnf DescribeDBProxyTargetGroupsResponse' {Int
Maybe [DBProxyTargetGroup]
Maybe Text
httpStatus :: Int
targetGroups :: Maybe [DBProxyTargetGroup]
marker :: Maybe Text
$sel:httpStatus:DescribeDBProxyTargetGroupsResponse' :: DescribeDBProxyTargetGroupsResponse -> Int
$sel:targetGroups:DescribeDBProxyTargetGroupsResponse' :: DescribeDBProxyTargetGroupsResponse -> Maybe [DBProxyTargetGroup]
$sel:marker:DescribeDBProxyTargetGroupsResponse' :: DescribeDBProxyTargetGroupsResponse -> Maybe Text
..} =
    forall a. NFData a => a -> ()
Prelude.rnf Maybe Text
marker
      seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf Maybe [DBProxyTargetGroup]
targetGroups
      seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf Int
httpStatus