{-# 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.GroundStation.ListDataflowEndpointGroups
-- 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 a list of @DataflowEndpoint@ groups.
--
-- This operation returns paginated results.
module Amazonka.GroundStation.ListDataflowEndpointGroups
  ( -- * Creating a Request
    ListDataflowEndpointGroups (..),
    newListDataflowEndpointGroups,

    -- * Request Lenses
    listDataflowEndpointGroups_maxResults,
    listDataflowEndpointGroups_nextToken,

    -- * Destructuring the Response
    ListDataflowEndpointGroupsResponse (..),
    newListDataflowEndpointGroupsResponse,

    -- * Response Lenses
    listDataflowEndpointGroupsResponse_dataflowEndpointGroupList,
    listDataflowEndpointGroupsResponse_nextToken,
    listDataflowEndpointGroupsResponse_httpStatus,
  )
where

import qualified Amazonka.Core as Core
import qualified Amazonka.Core.Lens.Internal as Lens
import qualified Amazonka.Data as Data
import Amazonka.GroundStation.Types
import qualified Amazonka.Prelude as Prelude
import qualified Amazonka.Request as Request
import qualified Amazonka.Response as Response

-- |
--
-- /See:/ 'newListDataflowEndpointGroups' smart constructor.
data ListDataflowEndpointGroups = ListDataflowEndpointGroups'
  { -- | Maximum number of dataflow endpoint groups returned.
    ListDataflowEndpointGroups -> Maybe Natural
maxResults :: Prelude.Maybe Prelude.Natural,
    -- | Next token returned in the request of a previous
    -- @ListDataflowEndpointGroups@ call. Used to get the next page of results.
    ListDataflowEndpointGroups -> Maybe Text
nextToken :: Prelude.Maybe Prelude.Text
  }
  deriving (ListDataflowEndpointGroups -> ListDataflowEndpointGroups -> Bool
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: ListDataflowEndpointGroups -> ListDataflowEndpointGroups -> Bool
$c/= :: ListDataflowEndpointGroups -> ListDataflowEndpointGroups -> Bool
== :: ListDataflowEndpointGroups -> ListDataflowEndpointGroups -> Bool
$c== :: ListDataflowEndpointGroups -> ListDataflowEndpointGroups -> Bool
Prelude.Eq, ReadPrec [ListDataflowEndpointGroups]
ReadPrec ListDataflowEndpointGroups
Int -> ReadS ListDataflowEndpointGroups
ReadS [ListDataflowEndpointGroups]
forall a.
(Int -> ReadS a)
-> ReadS [a] -> ReadPrec a -> ReadPrec [a] -> Read a
readListPrec :: ReadPrec [ListDataflowEndpointGroups]
$creadListPrec :: ReadPrec [ListDataflowEndpointGroups]
readPrec :: ReadPrec ListDataflowEndpointGroups
$creadPrec :: ReadPrec ListDataflowEndpointGroups
readList :: ReadS [ListDataflowEndpointGroups]
$creadList :: ReadS [ListDataflowEndpointGroups]
readsPrec :: Int -> ReadS ListDataflowEndpointGroups
$creadsPrec :: Int -> ReadS ListDataflowEndpointGroups
Prelude.Read, Int -> ListDataflowEndpointGroups -> ShowS
[ListDataflowEndpointGroups] -> ShowS
ListDataflowEndpointGroups -> String
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [ListDataflowEndpointGroups] -> ShowS
$cshowList :: [ListDataflowEndpointGroups] -> ShowS
show :: ListDataflowEndpointGroups -> String
$cshow :: ListDataflowEndpointGroups -> String
showsPrec :: Int -> ListDataflowEndpointGroups -> ShowS
$cshowsPrec :: Int -> ListDataflowEndpointGroups -> ShowS
Prelude.Show, forall x.
Rep ListDataflowEndpointGroups x -> ListDataflowEndpointGroups
forall x.
ListDataflowEndpointGroups -> Rep ListDataflowEndpointGroups x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cto :: forall x.
Rep ListDataflowEndpointGroups x -> ListDataflowEndpointGroups
$cfrom :: forall x.
ListDataflowEndpointGroups -> Rep ListDataflowEndpointGroups x
Prelude.Generic)

-- |
-- Create a value of 'ListDataflowEndpointGroups' 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:
--
-- 'maxResults', 'listDataflowEndpointGroups_maxResults' - Maximum number of dataflow endpoint groups returned.
--
-- 'nextToken', 'listDataflowEndpointGroups_nextToken' - Next token returned in the request of a previous
-- @ListDataflowEndpointGroups@ call. Used to get the next page of results.
newListDataflowEndpointGroups ::
  ListDataflowEndpointGroups
newListDataflowEndpointGroups :: ListDataflowEndpointGroups
newListDataflowEndpointGroups =
  ListDataflowEndpointGroups'
    { $sel:maxResults:ListDataflowEndpointGroups' :: Maybe Natural
maxResults =
        forall a. Maybe a
Prelude.Nothing,
      $sel:nextToken:ListDataflowEndpointGroups' :: Maybe Text
nextToken = forall a. Maybe a
Prelude.Nothing
    }

-- | Maximum number of dataflow endpoint groups returned.
listDataflowEndpointGroups_maxResults :: Lens.Lens' ListDataflowEndpointGroups (Prelude.Maybe Prelude.Natural)
listDataflowEndpointGroups_maxResults :: Lens' ListDataflowEndpointGroups (Maybe Natural)
listDataflowEndpointGroups_maxResults = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\ListDataflowEndpointGroups' {Maybe Natural
maxResults :: Maybe Natural
$sel:maxResults:ListDataflowEndpointGroups' :: ListDataflowEndpointGroups -> Maybe Natural
maxResults} -> Maybe Natural
maxResults) (\s :: ListDataflowEndpointGroups
s@ListDataflowEndpointGroups' {} Maybe Natural
a -> ListDataflowEndpointGroups
s {$sel:maxResults:ListDataflowEndpointGroups' :: Maybe Natural
maxResults = Maybe Natural
a} :: ListDataflowEndpointGroups)

-- | Next token returned in the request of a previous
-- @ListDataflowEndpointGroups@ call. Used to get the next page of results.
listDataflowEndpointGroups_nextToken :: Lens.Lens' ListDataflowEndpointGroups (Prelude.Maybe Prelude.Text)
listDataflowEndpointGroups_nextToken :: Lens' ListDataflowEndpointGroups (Maybe Text)
listDataflowEndpointGroups_nextToken = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\ListDataflowEndpointGroups' {Maybe Text
nextToken :: Maybe Text
$sel:nextToken:ListDataflowEndpointGroups' :: ListDataflowEndpointGroups -> Maybe Text
nextToken} -> Maybe Text
nextToken) (\s :: ListDataflowEndpointGroups
s@ListDataflowEndpointGroups' {} Maybe Text
a -> ListDataflowEndpointGroups
s {$sel:nextToken:ListDataflowEndpointGroups' :: Maybe Text
nextToken = Maybe Text
a} :: ListDataflowEndpointGroups)

instance Core.AWSPager ListDataflowEndpointGroups where
  page :: ListDataflowEndpointGroups
-> AWSResponse ListDataflowEndpointGroups
-> Maybe ListDataflowEndpointGroups
page ListDataflowEndpointGroups
rq AWSResponse ListDataflowEndpointGroups
rs
    | forall a. AWSTruncated a => a -> Bool
Core.stop
        ( AWSResponse ListDataflowEndpointGroups
rs
            forall s a. s -> Getting (First a) s a -> Maybe a
Lens.^? Lens' ListDataflowEndpointGroupsResponse (Maybe Text)
listDataflowEndpointGroupsResponse_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 ListDataflowEndpointGroups
rs
            forall s a. s -> Getting (First a) s a -> Maybe a
Lens.^? Lens'
  ListDataflowEndpointGroupsResponse
  (Maybe [DataflowEndpointListItem])
listDataflowEndpointGroupsResponse_dataflowEndpointGroupList
            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.$ ListDataflowEndpointGroups
rq
          forall a b. a -> (a -> b) -> b
Prelude.& Lens' ListDataflowEndpointGroups (Maybe Text)
listDataflowEndpointGroups_nextToken
          forall s t a b. ASetter s t a b -> b -> s -> t
Lens..~ AWSResponse ListDataflowEndpointGroups
rs
          forall s a. s -> Getting (First a) s a -> Maybe a
Lens.^? Lens' ListDataflowEndpointGroupsResponse (Maybe Text)
listDataflowEndpointGroupsResponse_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 ListDataflowEndpointGroups where
  type
    AWSResponse ListDataflowEndpointGroups =
      ListDataflowEndpointGroupsResponse
  request :: (Service -> Service)
-> ListDataflowEndpointGroups -> Request ListDataflowEndpointGroups
request Service -> Service
overrides =
    forall a. ToRequest a => Service -> a -> Request a
Request.get (Service -> Service
overrides Service
defaultService)
  response :: forall (m :: * -> *).
MonadResource m =>
(ByteStringLazy -> IO ByteStringLazy)
-> Service
-> Proxy ListDataflowEndpointGroups
-> ClientResponse ClientBody
-> m (Either
        Error (ClientResponse (AWSResponse ListDataflowEndpointGroups)))
response =
    forall (m :: * -> *) a.
MonadResource m =>
(Int -> ResponseHeaders -> Object -> Either String (AWSResponse a))
-> (ByteStringLazy -> IO ByteStringLazy)
-> Service
-> Proxy a
-> ClientResponse ClientBody
-> m (Either Error (ClientResponse (AWSResponse a)))
Response.receiveJSON
      ( \Int
s ResponseHeaders
h Object
x ->
          Maybe [DataflowEndpointListItem]
-> Maybe Text -> Int -> ListDataflowEndpointGroupsResponse
ListDataflowEndpointGroupsResponse'
            forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
Prelude.<$> ( Object
x
                            forall a. FromJSON a => Object -> Key -> Either String (Maybe a)
Data..?> Key
"dataflowEndpointGroupList"
                            forall (f :: * -> *) a. Functor f => f (Maybe a) -> a -> f a
Core..!@ forall a. Monoid a => a
Prelude.mempty
                        )
            forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
Prelude.<*> (Object
x forall a. FromJSON a => Object -> Key -> Either String (Maybe a)
Data..?> Key
"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 ListDataflowEndpointGroups where
  hashWithSalt :: Int -> ListDataflowEndpointGroups -> Int
hashWithSalt Int
_salt ListDataflowEndpointGroups' {Maybe Natural
Maybe Text
nextToken :: Maybe Text
maxResults :: Maybe Natural
$sel:nextToken:ListDataflowEndpointGroups' :: ListDataflowEndpointGroups -> Maybe Text
$sel:maxResults:ListDataflowEndpointGroups' :: ListDataflowEndpointGroups -> Maybe Natural
..} =
    Int
_salt
      forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Maybe Natural
maxResults
      forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Maybe Text
nextToken

instance Prelude.NFData ListDataflowEndpointGroups where
  rnf :: ListDataflowEndpointGroups -> ()
rnf ListDataflowEndpointGroups' {Maybe Natural
Maybe Text
nextToken :: Maybe Text
maxResults :: Maybe Natural
$sel:nextToken:ListDataflowEndpointGroups' :: ListDataflowEndpointGroups -> Maybe Text
$sel:maxResults:ListDataflowEndpointGroups' :: ListDataflowEndpointGroups -> Maybe Natural
..} =
    forall a. NFData a => a -> ()
Prelude.rnf Maybe Natural
maxResults
      seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf Maybe Text
nextToken

instance Data.ToHeaders ListDataflowEndpointGroups where
  toHeaders :: ListDataflowEndpointGroups -> ResponseHeaders
toHeaders =
    forall a b. a -> b -> a
Prelude.const
      ( forall a. Monoid a => [a] -> a
Prelude.mconcat
          [ HeaderName
"Content-Type"
              forall a. ToHeader a => HeaderName -> a -> ResponseHeaders
Data.=# ( ByteString
"application/x-amz-json-1.1" ::
                          Prelude.ByteString
                      )
          ]
      )

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

instance Data.ToQuery ListDataflowEndpointGroups where
  toQuery :: ListDataflowEndpointGroups -> QueryString
toQuery ListDataflowEndpointGroups' {Maybe Natural
Maybe Text
nextToken :: Maybe Text
maxResults :: Maybe Natural
$sel:nextToken:ListDataflowEndpointGroups' :: ListDataflowEndpointGroups -> Maybe Text
$sel:maxResults:ListDataflowEndpointGroups' :: ListDataflowEndpointGroups -> Maybe Natural
..} =
    forall a. Monoid a => [a] -> a
Prelude.mconcat
      [ ByteString
"maxResults" forall a. ToQuery a => ByteString -> a -> QueryString
Data.=: Maybe Natural
maxResults,
        ByteString
"nextToken" forall a. ToQuery a => ByteString -> a -> QueryString
Data.=: Maybe Text
nextToken
      ]

-- |
--
-- /See:/ 'newListDataflowEndpointGroupsResponse' smart constructor.
data ListDataflowEndpointGroupsResponse = ListDataflowEndpointGroupsResponse'
  { -- | A list of dataflow endpoint groups.
    ListDataflowEndpointGroupsResponse
-> Maybe [DataflowEndpointListItem]
dataflowEndpointGroupList :: Prelude.Maybe [DataflowEndpointListItem],
    -- | Next token returned in the response of a previous
    -- @ListDataflowEndpointGroups@ call. Used to get the next page of results.
    ListDataflowEndpointGroupsResponse -> Maybe Text
nextToken :: Prelude.Maybe Prelude.Text,
    -- | The response's http status code.
    ListDataflowEndpointGroupsResponse -> Int
httpStatus :: Prelude.Int
  }
  deriving (ListDataflowEndpointGroupsResponse
-> ListDataflowEndpointGroupsResponse -> Bool
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: ListDataflowEndpointGroupsResponse
-> ListDataflowEndpointGroupsResponse -> Bool
$c/= :: ListDataflowEndpointGroupsResponse
-> ListDataflowEndpointGroupsResponse -> Bool
== :: ListDataflowEndpointGroupsResponse
-> ListDataflowEndpointGroupsResponse -> Bool
$c== :: ListDataflowEndpointGroupsResponse
-> ListDataflowEndpointGroupsResponse -> Bool
Prelude.Eq, ReadPrec [ListDataflowEndpointGroupsResponse]
ReadPrec ListDataflowEndpointGroupsResponse
Int -> ReadS ListDataflowEndpointGroupsResponse
ReadS [ListDataflowEndpointGroupsResponse]
forall a.
(Int -> ReadS a)
-> ReadS [a] -> ReadPrec a -> ReadPrec [a] -> Read a
readListPrec :: ReadPrec [ListDataflowEndpointGroupsResponse]
$creadListPrec :: ReadPrec [ListDataflowEndpointGroupsResponse]
readPrec :: ReadPrec ListDataflowEndpointGroupsResponse
$creadPrec :: ReadPrec ListDataflowEndpointGroupsResponse
readList :: ReadS [ListDataflowEndpointGroupsResponse]
$creadList :: ReadS [ListDataflowEndpointGroupsResponse]
readsPrec :: Int -> ReadS ListDataflowEndpointGroupsResponse
$creadsPrec :: Int -> ReadS ListDataflowEndpointGroupsResponse
Prelude.Read, Int -> ListDataflowEndpointGroupsResponse -> ShowS
[ListDataflowEndpointGroupsResponse] -> ShowS
ListDataflowEndpointGroupsResponse -> String
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [ListDataflowEndpointGroupsResponse] -> ShowS
$cshowList :: [ListDataflowEndpointGroupsResponse] -> ShowS
show :: ListDataflowEndpointGroupsResponse -> String
$cshow :: ListDataflowEndpointGroupsResponse -> String
showsPrec :: Int -> ListDataflowEndpointGroupsResponse -> ShowS
$cshowsPrec :: Int -> ListDataflowEndpointGroupsResponse -> ShowS
Prelude.Show, forall x.
Rep ListDataflowEndpointGroupsResponse x
-> ListDataflowEndpointGroupsResponse
forall x.
ListDataflowEndpointGroupsResponse
-> Rep ListDataflowEndpointGroupsResponse x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cto :: forall x.
Rep ListDataflowEndpointGroupsResponse x
-> ListDataflowEndpointGroupsResponse
$cfrom :: forall x.
ListDataflowEndpointGroupsResponse
-> Rep ListDataflowEndpointGroupsResponse x
Prelude.Generic)

-- |
-- Create a value of 'ListDataflowEndpointGroupsResponse' 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:
--
-- 'dataflowEndpointGroupList', 'listDataflowEndpointGroupsResponse_dataflowEndpointGroupList' - A list of dataflow endpoint groups.
--
-- 'nextToken', 'listDataflowEndpointGroupsResponse_nextToken' - Next token returned in the response of a previous
-- @ListDataflowEndpointGroups@ call. Used to get the next page of results.
--
-- 'httpStatus', 'listDataflowEndpointGroupsResponse_httpStatus' - The response's http status code.
newListDataflowEndpointGroupsResponse ::
  -- | 'httpStatus'
  Prelude.Int ->
  ListDataflowEndpointGroupsResponse
newListDataflowEndpointGroupsResponse :: Int -> ListDataflowEndpointGroupsResponse
newListDataflowEndpointGroupsResponse Int
pHttpStatus_ =
  ListDataflowEndpointGroupsResponse'
    { $sel:dataflowEndpointGroupList:ListDataflowEndpointGroupsResponse' :: Maybe [DataflowEndpointListItem]
dataflowEndpointGroupList =
        forall a. Maybe a
Prelude.Nothing,
      $sel:nextToken:ListDataflowEndpointGroupsResponse' :: Maybe Text
nextToken = forall a. Maybe a
Prelude.Nothing,
      $sel:httpStatus:ListDataflowEndpointGroupsResponse' :: Int
httpStatus = Int
pHttpStatus_
    }

-- | A list of dataflow endpoint groups.
listDataflowEndpointGroupsResponse_dataflowEndpointGroupList :: Lens.Lens' ListDataflowEndpointGroupsResponse (Prelude.Maybe [DataflowEndpointListItem])
listDataflowEndpointGroupsResponse_dataflowEndpointGroupList :: Lens'
  ListDataflowEndpointGroupsResponse
  (Maybe [DataflowEndpointListItem])
listDataflowEndpointGroupsResponse_dataflowEndpointGroupList = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\ListDataflowEndpointGroupsResponse' {Maybe [DataflowEndpointListItem]
dataflowEndpointGroupList :: Maybe [DataflowEndpointListItem]
$sel:dataflowEndpointGroupList:ListDataflowEndpointGroupsResponse' :: ListDataflowEndpointGroupsResponse
-> Maybe [DataflowEndpointListItem]
dataflowEndpointGroupList} -> Maybe [DataflowEndpointListItem]
dataflowEndpointGroupList) (\s :: ListDataflowEndpointGroupsResponse
s@ListDataflowEndpointGroupsResponse' {} Maybe [DataflowEndpointListItem]
a -> ListDataflowEndpointGroupsResponse
s {$sel:dataflowEndpointGroupList:ListDataflowEndpointGroupsResponse' :: Maybe [DataflowEndpointListItem]
dataflowEndpointGroupList = Maybe [DataflowEndpointListItem]
a} :: ListDataflowEndpointGroupsResponse) 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

-- | Next token returned in the response of a previous
-- @ListDataflowEndpointGroups@ call. Used to get the next page of results.
listDataflowEndpointGroupsResponse_nextToken :: Lens.Lens' ListDataflowEndpointGroupsResponse (Prelude.Maybe Prelude.Text)
listDataflowEndpointGroupsResponse_nextToken :: Lens' ListDataflowEndpointGroupsResponse (Maybe Text)
listDataflowEndpointGroupsResponse_nextToken = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\ListDataflowEndpointGroupsResponse' {Maybe Text
nextToken :: Maybe Text
$sel:nextToken:ListDataflowEndpointGroupsResponse' :: ListDataflowEndpointGroupsResponse -> Maybe Text
nextToken} -> Maybe Text
nextToken) (\s :: ListDataflowEndpointGroupsResponse
s@ListDataflowEndpointGroupsResponse' {} Maybe Text
a -> ListDataflowEndpointGroupsResponse
s {$sel:nextToken:ListDataflowEndpointGroupsResponse' :: Maybe Text
nextToken = Maybe Text
a} :: ListDataflowEndpointGroupsResponse)

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

instance
  Prelude.NFData
    ListDataflowEndpointGroupsResponse
  where
  rnf :: ListDataflowEndpointGroupsResponse -> ()
rnf ListDataflowEndpointGroupsResponse' {Int
Maybe [DataflowEndpointListItem]
Maybe Text
httpStatus :: Int
nextToken :: Maybe Text
dataflowEndpointGroupList :: Maybe [DataflowEndpointListItem]
$sel:httpStatus:ListDataflowEndpointGroupsResponse' :: ListDataflowEndpointGroupsResponse -> Int
$sel:nextToken:ListDataflowEndpointGroupsResponse' :: ListDataflowEndpointGroupsResponse -> Maybe Text
$sel:dataflowEndpointGroupList:ListDataflowEndpointGroupsResponse' :: ListDataflowEndpointGroupsResponse
-> Maybe [DataflowEndpointListItem]
..} =
    forall a. NFData a => a -> ()
Prelude.rnf Maybe [DataflowEndpointListItem]
dataflowEndpointGroupList
      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