{-# 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.IoT.ListBillingGroups
-- 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 billing groups you have created.
--
-- Requires permission to access the
-- <https://docs.aws.amazon.com/service-authorization/latest/reference/list_awsiot.html#awsiot-actions-as-permissions ListBillingGroups>
-- action.
--
-- This operation returns paginated results.
module Amazonka.IoT.ListBillingGroups
  ( -- * Creating a Request
    ListBillingGroups (..),
    newListBillingGroups,

    -- * Request Lenses
    listBillingGroups_maxResults,
    listBillingGroups_namePrefixFilter,
    listBillingGroups_nextToken,

    -- * Destructuring the Response
    ListBillingGroupsResponse (..),
    newListBillingGroupsResponse,

    -- * Response Lenses
    listBillingGroupsResponse_billingGroups,
    listBillingGroupsResponse_nextToken,
    listBillingGroupsResponse_httpStatus,
  )
where

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

-- | /See:/ 'newListBillingGroups' smart constructor.
data ListBillingGroups = ListBillingGroups'
  { -- | The maximum number of results to return per request.
    ListBillingGroups -> Maybe Natural
maxResults :: Prelude.Maybe Prelude.Natural,
    -- | Limit the results to billing groups whose names have the given prefix.
    ListBillingGroups -> Maybe Text
namePrefixFilter :: Prelude.Maybe Prelude.Text,
    -- | To retrieve the next set of results, the @nextToken@ value from a
    -- previous response; otherwise __null__ to receive the first set of
    -- results.
    ListBillingGroups -> Maybe Text
nextToken :: Prelude.Maybe Prelude.Text
  }
  deriving (ListBillingGroups -> ListBillingGroups -> Bool
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: ListBillingGroups -> ListBillingGroups -> Bool
$c/= :: ListBillingGroups -> ListBillingGroups -> Bool
== :: ListBillingGroups -> ListBillingGroups -> Bool
$c== :: ListBillingGroups -> ListBillingGroups -> Bool
Prelude.Eq, ReadPrec [ListBillingGroups]
ReadPrec ListBillingGroups
Int -> ReadS ListBillingGroups
ReadS [ListBillingGroups]
forall a.
(Int -> ReadS a)
-> ReadS [a] -> ReadPrec a -> ReadPrec [a] -> Read a
readListPrec :: ReadPrec [ListBillingGroups]
$creadListPrec :: ReadPrec [ListBillingGroups]
readPrec :: ReadPrec ListBillingGroups
$creadPrec :: ReadPrec ListBillingGroups
readList :: ReadS [ListBillingGroups]
$creadList :: ReadS [ListBillingGroups]
readsPrec :: Int -> ReadS ListBillingGroups
$creadsPrec :: Int -> ReadS ListBillingGroups
Prelude.Read, Int -> ListBillingGroups -> ShowS
[ListBillingGroups] -> ShowS
ListBillingGroups -> String
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [ListBillingGroups] -> ShowS
$cshowList :: [ListBillingGroups] -> ShowS
show :: ListBillingGroups -> String
$cshow :: ListBillingGroups -> String
showsPrec :: Int -> ListBillingGroups -> ShowS
$cshowsPrec :: Int -> ListBillingGroups -> ShowS
Prelude.Show, forall x. Rep ListBillingGroups x -> ListBillingGroups
forall x. ListBillingGroups -> Rep ListBillingGroups x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cto :: forall x. Rep ListBillingGroups x -> ListBillingGroups
$cfrom :: forall x. ListBillingGroups -> Rep ListBillingGroups x
Prelude.Generic)

-- |
-- Create a value of 'ListBillingGroups' 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', 'listBillingGroups_maxResults' - The maximum number of results to return per request.
--
-- 'namePrefixFilter', 'listBillingGroups_namePrefixFilter' - Limit the results to billing groups whose names have the given prefix.
--
-- 'nextToken', 'listBillingGroups_nextToken' - To retrieve the next set of results, the @nextToken@ value from a
-- previous response; otherwise __null__ to receive the first set of
-- results.
newListBillingGroups ::
  ListBillingGroups
newListBillingGroups :: ListBillingGroups
newListBillingGroups =
  ListBillingGroups'
    { $sel:maxResults:ListBillingGroups' :: Maybe Natural
maxResults = forall a. Maybe a
Prelude.Nothing,
      $sel:namePrefixFilter:ListBillingGroups' :: Maybe Text
namePrefixFilter = forall a. Maybe a
Prelude.Nothing,
      $sel:nextToken:ListBillingGroups' :: Maybe Text
nextToken = forall a. Maybe a
Prelude.Nothing
    }

-- | The maximum number of results to return per request.
listBillingGroups_maxResults :: Lens.Lens' ListBillingGroups (Prelude.Maybe Prelude.Natural)
listBillingGroups_maxResults :: Lens' ListBillingGroups (Maybe Natural)
listBillingGroups_maxResults = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\ListBillingGroups' {Maybe Natural
maxResults :: Maybe Natural
$sel:maxResults:ListBillingGroups' :: ListBillingGroups -> Maybe Natural
maxResults} -> Maybe Natural
maxResults) (\s :: ListBillingGroups
s@ListBillingGroups' {} Maybe Natural
a -> ListBillingGroups
s {$sel:maxResults:ListBillingGroups' :: Maybe Natural
maxResults = Maybe Natural
a} :: ListBillingGroups)

-- | Limit the results to billing groups whose names have the given prefix.
listBillingGroups_namePrefixFilter :: Lens.Lens' ListBillingGroups (Prelude.Maybe Prelude.Text)
listBillingGroups_namePrefixFilter :: Lens' ListBillingGroups (Maybe Text)
listBillingGroups_namePrefixFilter = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\ListBillingGroups' {Maybe Text
namePrefixFilter :: Maybe Text
$sel:namePrefixFilter:ListBillingGroups' :: ListBillingGroups -> Maybe Text
namePrefixFilter} -> Maybe Text
namePrefixFilter) (\s :: ListBillingGroups
s@ListBillingGroups' {} Maybe Text
a -> ListBillingGroups
s {$sel:namePrefixFilter:ListBillingGroups' :: Maybe Text
namePrefixFilter = Maybe Text
a} :: ListBillingGroups)

-- | To retrieve the next set of results, the @nextToken@ value from a
-- previous response; otherwise __null__ to receive the first set of
-- results.
listBillingGroups_nextToken :: Lens.Lens' ListBillingGroups (Prelude.Maybe Prelude.Text)
listBillingGroups_nextToken :: Lens' ListBillingGroups (Maybe Text)
listBillingGroups_nextToken = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\ListBillingGroups' {Maybe Text
nextToken :: Maybe Text
$sel:nextToken:ListBillingGroups' :: ListBillingGroups -> Maybe Text
nextToken} -> Maybe Text
nextToken) (\s :: ListBillingGroups
s@ListBillingGroups' {} Maybe Text
a -> ListBillingGroups
s {$sel:nextToken:ListBillingGroups' :: Maybe Text
nextToken = Maybe Text
a} :: ListBillingGroups)

instance Core.AWSPager ListBillingGroups where
  page :: ListBillingGroups
-> AWSResponse ListBillingGroups -> Maybe ListBillingGroups
page ListBillingGroups
rq AWSResponse ListBillingGroups
rs
    | forall a. AWSTruncated a => a -> Bool
Core.stop
        ( AWSResponse ListBillingGroups
rs
            forall s a. s -> Getting (First a) s a -> Maybe a
Lens.^? Lens' ListBillingGroupsResponse (Maybe Text)
listBillingGroupsResponse_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 ListBillingGroups
rs
            forall s a. s -> Getting (First a) s a -> Maybe a
Lens.^? Lens' ListBillingGroupsResponse (Maybe [GroupNameAndArn])
listBillingGroupsResponse_billingGroups
            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.$ ListBillingGroups
rq
          forall a b. a -> (a -> b) -> b
Prelude.& Lens' ListBillingGroups (Maybe Text)
listBillingGroups_nextToken
          forall s t a b. ASetter s t a b -> b -> s -> t
Lens..~ AWSResponse ListBillingGroups
rs
          forall s a. s -> Getting (First a) s a -> Maybe a
Lens.^? Lens' ListBillingGroupsResponse (Maybe Text)
listBillingGroupsResponse_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 ListBillingGroups where
  type
    AWSResponse ListBillingGroups =
      ListBillingGroupsResponse
  request :: (Service -> Service)
-> ListBillingGroups -> Request ListBillingGroups
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 ListBillingGroups
-> ClientResponse ClientBody
-> m (Either
        Error (ClientResponse (AWSResponse ListBillingGroups)))
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 [GroupNameAndArn]
-> Maybe Text -> Int -> ListBillingGroupsResponse
ListBillingGroupsResponse'
            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
"billingGroups" 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 ListBillingGroups where
  hashWithSalt :: Int -> ListBillingGroups -> Int
hashWithSalt Int
_salt ListBillingGroups' {Maybe Natural
Maybe Text
nextToken :: Maybe Text
namePrefixFilter :: Maybe Text
maxResults :: Maybe Natural
$sel:nextToken:ListBillingGroups' :: ListBillingGroups -> Maybe Text
$sel:namePrefixFilter:ListBillingGroups' :: ListBillingGroups -> Maybe Text
$sel:maxResults:ListBillingGroups' :: ListBillingGroups -> 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
namePrefixFilter
      forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Maybe Text
nextToken

instance Prelude.NFData ListBillingGroups where
  rnf :: ListBillingGroups -> ()
rnf ListBillingGroups' {Maybe Natural
Maybe Text
nextToken :: Maybe Text
namePrefixFilter :: Maybe Text
maxResults :: Maybe Natural
$sel:nextToken:ListBillingGroups' :: ListBillingGroups -> Maybe Text
$sel:namePrefixFilter:ListBillingGroups' :: ListBillingGroups -> Maybe Text
$sel:maxResults:ListBillingGroups' :: ListBillingGroups -> 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
namePrefixFilter
      seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf Maybe Text
nextToken

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

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

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

-- | /See:/ 'newListBillingGroupsResponse' smart constructor.
data ListBillingGroupsResponse = ListBillingGroupsResponse'
  { -- | The list of billing groups.
    ListBillingGroupsResponse -> Maybe [GroupNameAndArn]
billingGroups :: Prelude.Maybe [GroupNameAndArn],
    -- | The token to use to get the next set of results, or __null__ if there
    -- are no additional results.
    ListBillingGroupsResponse -> Maybe Text
nextToken :: Prelude.Maybe Prelude.Text,
    -- | The response's http status code.
    ListBillingGroupsResponse -> Int
httpStatus :: Prelude.Int
  }
  deriving (ListBillingGroupsResponse -> ListBillingGroupsResponse -> Bool
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: ListBillingGroupsResponse -> ListBillingGroupsResponse -> Bool
$c/= :: ListBillingGroupsResponse -> ListBillingGroupsResponse -> Bool
== :: ListBillingGroupsResponse -> ListBillingGroupsResponse -> Bool
$c== :: ListBillingGroupsResponse -> ListBillingGroupsResponse -> Bool
Prelude.Eq, ReadPrec [ListBillingGroupsResponse]
ReadPrec ListBillingGroupsResponse
Int -> ReadS ListBillingGroupsResponse
ReadS [ListBillingGroupsResponse]
forall a.
(Int -> ReadS a)
-> ReadS [a] -> ReadPrec a -> ReadPrec [a] -> Read a
readListPrec :: ReadPrec [ListBillingGroupsResponse]
$creadListPrec :: ReadPrec [ListBillingGroupsResponse]
readPrec :: ReadPrec ListBillingGroupsResponse
$creadPrec :: ReadPrec ListBillingGroupsResponse
readList :: ReadS [ListBillingGroupsResponse]
$creadList :: ReadS [ListBillingGroupsResponse]
readsPrec :: Int -> ReadS ListBillingGroupsResponse
$creadsPrec :: Int -> ReadS ListBillingGroupsResponse
Prelude.Read, Int -> ListBillingGroupsResponse -> ShowS
[ListBillingGroupsResponse] -> ShowS
ListBillingGroupsResponse -> String
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [ListBillingGroupsResponse] -> ShowS
$cshowList :: [ListBillingGroupsResponse] -> ShowS
show :: ListBillingGroupsResponse -> String
$cshow :: ListBillingGroupsResponse -> String
showsPrec :: Int -> ListBillingGroupsResponse -> ShowS
$cshowsPrec :: Int -> ListBillingGroupsResponse -> ShowS
Prelude.Show, forall x.
Rep ListBillingGroupsResponse x -> ListBillingGroupsResponse
forall x.
ListBillingGroupsResponse -> Rep ListBillingGroupsResponse x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cto :: forall x.
Rep ListBillingGroupsResponse x -> ListBillingGroupsResponse
$cfrom :: forall x.
ListBillingGroupsResponse -> Rep ListBillingGroupsResponse x
Prelude.Generic)

-- |
-- Create a value of 'ListBillingGroupsResponse' 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:
--
-- 'billingGroups', 'listBillingGroupsResponse_billingGroups' - The list of billing groups.
--
-- 'nextToken', 'listBillingGroupsResponse_nextToken' - The token to use to get the next set of results, or __null__ if there
-- are no additional results.
--
-- 'httpStatus', 'listBillingGroupsResponse_httpStatus' - The response's http status code.
newListBillingGroupsResponse ::
  -- | 'httpStatus'
  Prelude.Int ->
  ListBillingGroupsResponse
newListBillingGroupsResponse :: Int -> ListBillingGroupsResponse
newListBillingGroupsResponse Int
pHttpStatus_ =
  ListBillingGroupsResponse'
    { $sel:billingGroups:ListBillingGroupsResponse' :: Maybe [GroupNameAndArn]
billingGroups =
        forall a. Maybe a
Prelude.Nothing,
      $sel:nextToken:ListBillingGroupsResponse' :: Maybe Text
nextToken = forall a. Maybe a
Prelude.Nothing,
      $sel:httpStatus:ListBillingGroupsResponse' :: Int
httpStatus = Int
pHttpStatus_
    }

-- | The list of billing groups.
listBillingGroupsResponse_billingGroups :: Lens.Lens' ListBillingGroupsResponse (Prelude.Maybe [GroupNameAndArn])
listBillingGroupsResponse_billingGroups :: Lens' ListBillingGroupsResponse (Maybe [GroupNameAndArn])
listBillingGroupsResponse_billingGroups = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\ListBillingGroupsResponse' {Maybe [GroupNameAndArn]
billingGroups :: Maybe [GroupNameAndArn]
$sel:billingGroups:ListBillingGroupsResponse' :: ListBillingGroupsResponse -> Maybe [GroupNameAndArn]
billingGroups} -> Maybe [GroupNameAndArn]
billingGroups) (\s :: ListBillingGroupsResponse
s@ListBillingGroupsResponse' {} Maybe [GroupNameAndArn]
a -> ListBillingGroupsResponse
s {$sel:billingGroups:ListBillingGroupsResponse' :: Maybe [GroupNameAndArn]
billingGroups = Maybe [GroupNameAndArn]
a} :: ListBillingGroupsResponse) 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 token to use to get the next set of results, or __null__ if there
-- are no additional results.
listBillingGroupsResponse_nextToken :: Lens.Lens' ListBillingGroupsResponse (Prelude.Maybe Prelude.Text)
listBillingGroupsResponse_nextToken :: Lens' ListBillingGroupsResponse (Maybe Text)
listBillingGroupsResponse_nextToken = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\ListBillingGroupsResponse' {Maybe Text
nextToken :: Maybe Text
$sel:nextToken:ListBillingGroupsResponse' :: ListBillingGroupsResponse -> Maybe Text
nextToken} -> Maybe Text
nextToken) (\s :: ListBillingGroupsResponse
s@ListBillingGroupsResponse' {} Maybe Text
a -> ListBillingGroupsResponse
s {$sel:nextToken:ListBillingGroupsResponse' :: Maybe Text
nextToken = Maybe Text
a} :: ListBillingGroupsResponse)

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

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