{-# 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.CodeDeploy.ListDeploymentGroups
-- Copyright   : (c) 2013-2023 Brendan Hay
-- License     : Mozilla Public License, v. 2.0.
-- Maintainer  : Brendan Hay
-- Stability   : auto-generated
-- Portability : non-portable (GHC extensions)
--
-- Lists the deployment groups for an application registered with the IAM
-- user or Amazon Web Services account.
--
-- This operation returns paginated results.
module Amazonka.CodeDeploy.ListDeploymentGroups
  ( -- * Creating a Request
    ListDeploymentGroups (..),
    newListDeploymentGroups,

    -- * Request Lenses
    listDeploymentGroups_nextToken,
    listDeploymentGroups_applicationName,

    -- * Destructuring the Response
    ListDeploymentGroupsResponse (..),
    newListDeploymentGroupsResponse,

    -- * Response Lenses
    listDeploymentGroupsResponse_applicationName,
    listDeploymentGroupsResponse_deploymentGroups,
    listDeploymentGroupsResponse_nextToken,
    listDeploymentGroupsResponse_httpStatus,
  )
where

import Amazonka.CodeDeploy.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

-- | Represents the input of a @ListDeploymentGroups@ operation.
--
-- /See:/ 'newListDeploymentGroups' smart constructor.
data ListDeploymentGroups = ListDeploymentGroups'
  { -- | An identifier returned from the previous list deployment groups call. It
    -- can be used to return the next set of deployment groups in the list.
    ListDeploymentGroups -> Maybe Text
nextToken :: Prelude.Maybe Prelude.Text,
    -- | The name of an CodeDeploy application associated with the IAM user or
    -- Amazon Web Services account.
    ListDeploymentGroups -> Text
applicationName :: Prelude.Text
  }
  deriving (ListDeploymentGroups -> ListDeploymentGroups -> Bool
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: ListDeploymentGroups -> ListDeploymentGroups -> Bool
$c/= :: ListDeploymentGroups -> ListDeploymentGroups -> Bool
== :: ListDeploymentGroups -> ListDeploymentGroups -> Bool
$c== :: ListDeploymentGroups -> ListDeploymentGroups -> Bool
Prelude.Eq, ReadPrec [ListDeploymentGroups]
ReadPrec ListDeploymentGroups
Int -> ReadS ListDeploymentGroups
ReadS [ListDeploymentGroups]
forall a.
(Int -> ReadS a)
-> ReadS [a] -> ReadPrec a -> ReadPrec [a] -> Read a
readListPrec :: ReadPrec [ListDeploymentGroups]
$creadListPrec :: ReadPrec [ListDeploymentGroups]
readPrec :: ReadPrec ListDeploymentGroups
$creadPrec :: ReadPrec ListDeploymentGroups
readList :: ReadS [ListDeploymentGroups]
$creadList :: ReadS [ListDeploymentGroups]
readsPrec :: Int -> ReadS ListDeploymentGroups
$creadsPrec :: Int -> ReadS ListDeploymentGroups
Prelude.Read, Int -> ListDeploymentGroups -> ShowS
[ListDeploymentGroups] -> ShowS
ListDeploymentGroups -> String
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [ListDeploymentGroups] -> ShowS
$cshowList :: [ListDeploymentGroups] -> ShowS
show :: ListDeploymentGroups -> String
$cshow :: ListDeploymentGroups -> String
showsPrec :: Int -> ListDeploymentGroups -> ShowS
$cshowsPrec :: Int -> ListDeploymentGroups -> ShowS
Prelude.Show, forall x. Rep ListDeploymentGroups x -> ListDeploymentGroups
forall x. ListDeploymentGroups -> Rep ListDeploymentGroups x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cto :: forall x. Rep ListDeploymentGroups x -> ListDeploymentGroups
$cfrom :: forall x. ListDeploymentGroups -> Rep ListDeploymentGroups x
Prelude.Generic)

-- |
-- Create a value of 'ListDeploymentGroups' 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:
--
-- 'nextToken', 'listDeploymentGroups_nextToken' - An identifier returned from the previous list deployment groups call. It
-- can be used to return the next set of deployment groups in the list.
--
-- 'applicationName', 'listDeploymentGroups_applicationName' - The name of an CodeDeploy application associated with the IAM user or
-- Amazon Web Services account.
newListDeploymentGroups ::
  -- | 'applicationName'
  Prelude.Text ->
  ListDeploymentGroups
newListDeploymentGroups :: Text -> ListDeploymentGroups
newListDeploymentGroups Text
pApplicationName_ =
  ListDeploymentGroups'
    { $sel:nextToken:ListDeploymentGroups' :: Maybe Text
nextToken = forall a. Maybe a
Prelude.Nothing,
      $sel:applicationName:ListDeploymentGroups' :: Text
applicationName = Text
pApplicationName_
    }

-- | An identifier returned from the previous list deployment groups call. It
-- can be used to return the next set of deployment groups in the list.
listDeploymentGroups_nextToken :: Lens.Lens' ListDeploymentGroups (Prelude.Maybe Prelude.Text)
listDeploymentGroups_nextToken :: Lens' ListDeploymentGroups (Maybe Text)
listDeploymentGroups_nextToken = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\ListDeploymentGroups' {Maybe Text
nextToken :: Maybe Text
$sel:nextToken:ListDeploymentGroups' :: ListDeploymentGroups -> Maybe Text
nextToken} -> Maybe Text
nextToken) (\s :: ListDeploymentGroups
s@ListDeploymentGroups' {} Maybe Text
a -> ListDeploymentGroups
s {$sel:nextToken:ListDeploymentGroups' :: Maybe Text
nextToken = Maybe Text
a} :: ListDeploymentGroups)

-- | The name of an CodeDeploy application associated with the IAM user or
-- Amazon Web Services account.
listDeploymentGroups_applicationName :: Lens.Lens' ListDeploymentGroups Prelude.Text
listDeploymentGroups_applicationName :: Lens' ListDeploymentGroups Text
listDeploymentGroups_applicationName = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\ListDeploymentGroups' {Text
applicationName :: Text
$sel:applicationName:ListDeploymentGroups' :: ListDeploymentGroups -> Text
applicationName} -> Text
applicationName) (\s :: ListDeploymentGroups
s@ListDeploymentGroups' {} Text
a -> ListDeploymentGroups
s {$sel:applicationName:ListDeploymentGroups' :: Text
applicationName = Text
a} :: ListDeploymentGroups)

instance Core.AWSPager ListDeploymentGroups where
  page :: ListDeploymentGroups
-> AWSResponse ListDeploymentGroups -> Maybe ListDeploymentGroups
page ListDeploymentGroups
rq AWSResponse ListDeploymentGroups
rs
    | forall a. AWSTruncated a => a -> Bool
Core.stop
        ( AWSResponse ListDeploymentGroups
rs
            forall s a. s -> Getting (First a) s a -> Maybe a
Lens.^? Lens' ListDeploymentGroupsResponse (Maybe Text)
listDeploymentGroupsResponse_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 ListDeploymentGroups
rs
            forall s a. s -> Getting (First a) s a -> Maybe a
Lens.^? Lens' ListDeploymentGroupsResponse (Maybe [Text])
listDeploymentGroupsResponse_deploymentGroups
            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.$ ListDeploymentGroups
rq
          forall a b. a -> (a -> b) -> b
Prelude.& Lens' ListDeploymentGroups (Maybe Text)
listDeploymentGroups_nextToken
          forall s t a b. ASetter s t a b -> b -> s -> t
Lens..~ AWSResponse ListDeploymentGroups
rs
          forall s a. s -> Getting (First a) s a -> Maybe a
Lens.^? Lens' ListDeploymentGroupsResponse (Maybe Text)
listDeploymentGroupsResponse_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 ListDeploymentGroups where
  type
    AWSResponse ListDeploymentGroups =
      ListDeploymentGroupsResponse
  request :: (Service -> Service)
-> ListDeploymentGroups -> Request ListDeploymentGroups
request Service -> Service
overrides =
    forall a. (ToRequest a, ToJSON a) => Service -> a -> Request a
Request.postJSON (Service -> Service
overrides Service
defaultService)
  response :: forall (m :: * -> *).
MonadResource m =>
(ByteStringLazy -> IO ByteStringLazy)
-> Service
-> Proxy ListDeploymentGroups
-> ClientResponse ClientBody
-> m (Either
        Error (ClientResponse (AWSResponse ListDeploymentGroups)))
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 Text
-> Maybe [Text]
-> Maybe Text
-> Int
-> ListDeploymentGroupsResponse
ListDeploymentGroupsResponse'
            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
"applicationName")
            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
"deploymentGroups"
                            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 ListDeploymentGroups where
  hashWithSalt :: Int -> ListDeploymentGroups -> Int
hashWithSalt Int
_salt ListDeploymentGroups' {Maybe Text
Text
applicationName :: Text
nextToken :: Maybe Text
$sel:applicationName:ListDeploymentGroups' :: ListDeploymentGroups -> Text
$sel:nextToken:ListDeploymentGroups' :: ListDeploymentGroups -> Maybe Text
..} =
    Int
_salt
      forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Maybe Text
nextToken
      forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Text
applicationName

instance Prelude.NFData ListDeploymentGroups where
  rnf :: ListDeploymentGroups -> ()
rnf ListDeploymentGroups' {Maybe Text
Text
applicationName :: Text
nextToken :: Maybe Text
$sel:applicationName:ListDeploymentGroups' :: ListDeploymentGroups -> Text
$sel:nextToken:ListDeploymentGroups' :: ListDeploymentGroups -> Maybe Text
..} =
    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
applicationName

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

instance Data.ToJSON ListDeploymentGroups where
  toJSON :: ListDeploymentGroups -> Value
toJSON ListDeploymentGroups' {Maybe Text
Text
applicationName :: Text
nextToken :: Maybe Text
$sel:applicationName:ListDeploymentGroups' :: ListDeploymentGroups -> Text
$sel:nextToken:ListDeploymentGroups' :: ListDeploymentGroups -> Maybe Text
..} =
    [Pair] -> Value
Data.object
      ( forall a. [Maybe a] -> [a]
Prelude.catMaybes
          [ (Key
"nextToken" forall kv v. (KeyValue kv, ToJSON v) => Key -> v -> kv
Data..=) forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
Prelude.<$> Maybe Text
nextToken,
            forall a. a -> Maybe a
Prelude.Just
              (Key
"applicationName" forall kv v. (KeyValue kv, ToJSON v) => Key -> v -> kv
Data..= Text
applicationName)
          ]
      )

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

instance Data.ToQuery ListDeploymentGroups where
  toQuery :: ListDeploymentGroups -> QueryString
toQuery = forall a b. a -> b -> a
Prelude.const forall a. Monoid a => a
Prelude.mempty

-- | Represents the output of a @ListDeploymentGroups@ operation.
--
-- /See:/ 'newListDeploymentGroupsResponse' smart constructor.
data ListDeploymentGroupsResponse = ListDeploymentGroupsResponse'
  { -- | The application name.
    ListDeploymentGroupsResponse -> Maybe Text
applicationName :: Prelude.Maybe Prelude.Text,
    -- | A list of deployment group names.
    ListDeploymentGroupsResponse -> Maybe [Text]
deploymentGroups :: Prelude.Maybe [Prelude.Text],
    -- | If a large amount of information is returned, an identifier is also
    -- returned. It can be used in a subsequent list deployment groups call to
    -- return the next set of deployment groups in the list.
    ListDeploymentGroupsResponse -> Maybe Text
nextToken :: Prelude.Maybe Prelude.Text,
    -- | The response's http status code.
    ListDeploymentGroupsResponse -> Int
httpStatus :: Prelude.Int
  }
  deriving (ListDeploymentGroupsResponse
-> ListDeploymentGroupsResponse -> Bool
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: ListDeploymentGroupsResponse
-> ListDeploymentGroupsResponse -> Bool
$c/= :: ListDeploymentGroupsResponse
-> ListDeploymentGroupsResponse -> Bool
== :: ListDeploymentGroupsResponse
-> ListDeploymentGroupsResponse -> Bool
$c== :: ListDeploymentGroupsResponse
-> ListDeploymentGroupsResponse -> Bool
Prelude.Eq, ReadPrec [ListDeploymentGroupsResponse]
ReadPrec ListDeploymentGroupsResponse
Int -> ReadS ListDeploymentGroupsResponse
ReadS [ListDeploymentGroupsResponse]
forall a.
(Int -> ReadS a)
-> ReadS [a] -> ReadPrec a -> ReadPrec [a] -> Read a
readListPrec :: ReadPrec [ListDeploymentGroupsResponse]
$creadListPrec :: ReadPrec [ListDeploymentGroupsResponse]
readPrec :: ReadPrec ListDeploymentGroupsResponse
$creadPrec :: ReadPrec ListDeploymentGroupsResponse
readList :: ReadS [ListDeploymentGroupsResponse]
$creadList :: ReadS [ListDeploymentGroupsResponse]
readsPrec :: Int -> ReadS ListDeploymentGroupsResponse
$creadsPrec :: Int -> ReadS ListDeploymentGroupsResponse
Prelude.Read, Int -> ListDeploymentGroupsResponse -> ShowS
[ListDeploymentGroupsResponse] -> ShowS
ListDeploymentGroupsResponse -> String
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [ListDeploymentGroupsResponse] -> ShowS
$cshowList :: [ListDeploymentGroupsResponse] -> ShowS
show :: ListDeploymentGroupsResponse -> String
$cshow :: ListDeploymentGroupsResponse -> String
showsPrec :: Int -> ListDeploymentGroupsResponse -> ShowS
$cshowsPrec :: Int -> ListDeploymentGroupsResponse -> ShowS
Prelude.Show, forall x.
Rep ListDeploymentGroupsResponse x -> ListDeploymentGroupsResponse
forall x.
ListDeploymentGroupsResponse -> Rep ListDeploymentGroupsResponse x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cto :: forall x.
Rep ListDeploymentGroupsResponse x -> ListDeploymentGroupsResponse
$cfrom :: forall x.
ListDeploymentGroupsResponse -> Rep ListDeploymentGroupsResponse x
Prelude.Generic)

-- |
-- Create a value of 'ListDeploymentGroupsResponse' 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:
--
-- 'applicationName', 'listDeploymentGroupsResponse_applicationName' - The application name.
--
-- 'deploymentGroups', 'listDeploymentGroupsResponse_deploymentGroups' - A list of deployment group names.
--
-- 'nextToken', 'listDeploymentGroupsResponse_nextToken' - If a large amount of information is returned, an identifier is also
-- returned. It can be used in a subsequent list deployment groups call to
-- return the next set of deployment groups in the list.
--
-- 'httpStatus', 'listDeploymentGroupsResponse_httpStatus' - The response's http status code.
newListDeploymentGroupsResponse ::
  -- | 'httpStatus'
  Prelude.Int ->
  ListDeploymentGroupsResponse
newListDeploymentGroupsResponse :: Int -> ListDeploymentGroupsResponse
newListDeploymentGroupsResponse Int
pHttpStatus_ =
  ListDeploymentGroupsResponse'
    { $sel:applicationName:ListDeploymentGroupsResponse' :: Maybe Text
applicationName =
        forall a. Maybe a
Prelude.Nothing,
      $sel:deploymentGroups:ListDeploymentGroupsResponse' :: Maybe [Text]
deploymentGroups = forall a. Maybe a
Prelude.Nothing,
      $sel:nextToken:ListDeploymentGroupsResponse' :: Maybe Text
nextToken = forall a. Maybe a
Prelude.Nothing,
      $sel:httpStatus:ListDeploymentGroupsResponse' :: Int
httpStatus = Int
pHttpStatus_
    }

-- | The application name.
listDeploymentGroupsResponse_applicationName :: Lens.Lens' ListDeploymentGroupsResponse (Prelude.Maybe Prelude.Text)
listDeploymentGroupsResponse_applicationName :: Lens' ListDeploymentGroupsResponse (Maybe Text)
listDeploymentGroupsResponse_applicationName = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\ListDeploymentGroupsResponse' {Maybe Text
applicationName :: Maybe Text
$sel:applicationName:ListDeploymentGroupsResponse' :: ListDeploymentGroupsResponse -> Maybe Text
applicationName} -> Maybe Text
applicationName) (\s :: ListDeploymentGroupsResponse
s@ListDeploymentGroupsResponse' {} Maybe Text
a -> ListDeploymentGroupsResponse
s {$sel:applicationName:ListDeploymentGroupsResponse' :: Maybe Text
applicationName = Maybe Text
a} :: ListDeploymentGroupsResponse)

-- | A list of deployment group names.
listDeploymentGroupsResponse_deploymentGroups :: Lens.Lens' ListDeploymentGroupsResponse (Prelude.Maybe [Prelude.Text])
listDeploymentGroupsResponse_deploymentGroups :: Lens' ListDeploymentGroupsResponse (Maybe [Text])
listDeploymentGroupsResponse_deploymentGroups = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\ListDeploymentGroupsResponse' {Maybe [Text]
deploymentGroups :: Maybe [Text]
$sel:deploymentGroups:ListDeploymentGroupsResponse' :: ListDeploymentGroupsResponse -> Maybe [Text]
deploymentGroups} -> Maybe [Text]
deploymentGroups) (\s :: ListDeploymentGroupsResponse
s@ListDeploymentGroupsResponse' {} Maybe [Text]
a -> ListDeploymentGroupsResponse
s {$sel:deploymentGroups:ListDeploymentGroupsResponse' :: Maybe [Text]
deploymentGroups = Maybe [Text]
a} :: ListDeploymentGroupsResponse) 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

-- | If a large amount of information is returned, an identifier is also
-- returned. It can be used in a subsequent list deployment groups call to
-- return the next set of deployment groups in the list.
listDeploymentGroupsResponse_nextToken :: Lens.Lens' ListDeploymentGroupsResponse (Prelude.Maybe Prelude.Text)
listDeploymentGroupsResponse_nextToken :: Lens' ListDeploymentGroupsResponse (Maybe Text)
listDeploymentGroupsResponse_nextToken = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\ListDeploymentGroupsResponse' {Maybe Text
nextToken :: Maybe Text
$sel:nextToken:ListDeploymentGroupsResponse' :: ListDeploymentGroupsResponse -> Maybe Text
nextToken} -> Maybe Text
nextToken) (\s :: ListDeploymentGroupsResponse
s@ListDeploymentGroupsResponse' {} Maybe Text
a -> ListDeploymentGroupsResponse
s {$sel:nextToken:ListDeploymentGroupsResponse' :: Maybe Text
nextToken = Maybe Text
a} :: ListDeploymentGroupsResponse)

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

instance Prelude.NFData ListDeploymentGroupsResponse where
  rnf :: ListDeploymentGroupsResponse -> ()
rnf ListDeploymentGroupsResponse' {Int
Maybe [Text]
Maybe Text
httpStatus :: Int
nextToken :: Maybe Text
deploymentGroups :: Maybe [Text]
applicationName :: Maybe Text
$sel:httpStatus:ListDeploymentGroupsResponse' :: ListDeploymentGroupsResponse -> Int
$sel:nextToken:ListDeploymentGroupsResponse' :: ListDeploymentGroupsResponse -> Maybe Text
$sel:deploymentGroups:ListDeploymentGroupsResponse' :: ListDeploymentGroupsResponse -> Maybe [Text]
$sel:applicationName:ListDeploymentGroupsResponse' :: ListDeploymentGroupsResponse -> Maybe Text
..} =
    forall a. NFData a => a -> ()
Prelude.rnf Maybe Text
applicationName
      seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf Maybe [Text]
deploymentGroups
      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