{-# 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.DescribeBillingGroup
-- 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 a billing group.
--
-- Requires permission to access the
-- <https://docs.aws.amazon.com/service-authorization/latest/reference/list_awsiot.html#awsiot-actions-as-permissions DescribeBillingGroup>
-- action.
module Amazonka.IoT.DescribeBillingGroup
  ( -- * Creating a Request
    DescribeBillingGroup (..),
    newDescribeBillingGroup,

    -- * Request Lenses
    describeBillingGroup_billingGroupName,

    -- * Destructuring the Response
    DescribeBillingGroupResponse (..),
    newDescribeBillingGroupResponse,

    -- * Response Lenses
    describeBillingGroupResponse_billingGroupArn,
    describeBillingGroupResponse_billingGroupId,
    describeBillingGroupResponse_billingGroupMetadata,
    describeBillingGroupResponse_billingGroupName,
    describeBillingGroupResponse_billingGroupProperties,
    describeBillingGroupResponse_version,
    describeBillingGroupResponse_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:/ 'newDescribeBillingGroup' smart constructor.
data DescribeBillingGroup = DescribeBillingGroup'
  { -- | The name of the billing group.
    DescribeBillingGroup -> Text
billingGroupName :: Prelude.Text
  }
  deriving (DescribeBillingGroup -> DescribeBillingGroup -> Bool
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: DescribeBillingGroup -> DescribeBillingGroup -> Bool
$c/= :: DescribeBillingGroup -> DescribeBillingGroup -> Bool
== :: DescribeBillingGroup -> DescribeBillingGroup -> Bool
$c== :: DescribeBillingGroup -> DescribeBillingGroup -> Bool
Prelude.Eq, ReadPrec [DescribeBillingGroup]
ReadPrec DescribeBillingGroup
Int -> ReadS DescribeBillingGroup
ReadS [DescribeBillingGroup]
forall a.
(Int -> ReadS a)
-> ReadS [a] -> ReadPrec a -> ReadPrec [a] -> Read a
readListPrec :: ReadPrec [DescribeBillingGroup]
$creadListPrec :: ReadPrec [DescribeBillingGroup]
readPrec :: ReadPrec DescribeBillingGroup
$creadPrec :: ReadPrec DescribeBillingGroup
readList :: ReadS [DescribeBillingGroup]
$creadList :: ReadS [DescribeBillingGroup]
readsPrec :: Int -> ReadS DescribeBillingGroup
$creadsPrec :: Int -> ReadS DescribeBillingGroup
Prelude.Read, Int -> DescribeBillingGroup -> ShowS
[DescribeBillingGroup] -> ShowS
DescribeBillingGroup -> String
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [DescribeBillingGroup] -> ShowS
$cshowList :: [DescribeBillingGroup] -> ShowS
show :: DescribeBillingGroup -> String
$cshow :: DescribeBillingGroup -> String
showsPrec :: Int -> DescribeBillingGroup -> ShowS
$cshowsPrec :: Int -> DescribeBillingGroup -> ShowS
Prelude.Show, forall x. Rep DescribeBillingGroup x -> DescribeBillingGroup
forall x. DescribeBillingGroup -> Rep DescribeBillingGroup x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cto :: forall x. Rep DescribeBillingGroup x -> DescribeBillingGroup
$cfrom :: forall x. DescribeBillingGroup -> Rep DescribeBillingGroup x
Prelude.Generic)

-- |
-- Create a value of 'DescribeBillingGroup' 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:
--
-- 'billingGroupName', 'describeBillingGroup_billingGroupName' - The name of the billing group.
newDescribeBillingGroup ::
  -- | 'billingGroupName'
  Prelude.Text ->
  DescribeBillingGroup
newDescribeBillingGroup :: Text -> DescribeBillingGroup
newDescribeBillingGroup Text
pBillingGroupName_ =
  DescribeBillingGroup'
    { $sel:billingGroupName:DescribeBillingGroup' :: Text
billingGroupName =
        Text
pBillingGroupName_
    }

-- | The name of the billing group.
describeBillingGroup_billingGroupName :: Lens.Lens' DescribeBillingGroup Prelude.Text
describeBillingGroup_billingGroupName :: Lens' DescribeBillingGroup Text
describeBillingGroup_billingGroupName = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\DescribeBillingGroup' {Text
billingGroupName :: Text
$sel:billingGroupName:DescribeBillingGroup' :: DescribeBillingGroup -> Text
billingGroupName} -> Text
billingGroupName) (\s :: DescribeBillingGroup
s@DescribeBillingGroup' {} Text
a -> DescribeBillingGroup
s {$sel:billingGroupName:DescribeBillingGroup' :: Text
billingGroupName = Text
a} :: DescribeBillingGroup)

instance Core.AWSRequest DescribeBillingGroup where
  type
    AWSResponse DescribeBillingGroup =
      DescribeBillingGroupResponse
  request :: (Service -> Service)
-> DescribeBillingGroup -> Request DescribeBillingGroup
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 DescribeBillingGroup
-> ClientResponse ClientBody
-> m (Either
        Error (ClientResponse (AWSResponse DescribeBillingGroup)))
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 BillingGroupMetadata
-> Maybe Text
-> Maybe BillingGroupProperties
-> Maybe Integer
-> Int
-> DescribeBillingGroupResponse
DescribeBillingGroupResponse'
            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
"billingGroupArn")
            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
"billingGroupId")
            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
"billingGroupMetadata")
            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
"billingGroupName")
            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
"billingGroupProperties")
            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
"version")
            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 DescribeBillingGroup where
  hashWithSalt :: Int -> DescribeBillingGroup -> Int
hashWithSalt Int
_salt DescribeBillingGroup' {Text
billingGroupName :: Text
$sel:billingGroupName:DescribeBillingGroup' :: DescribeBillingGroup -> Text
..} =
    Int
_salt forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Text
billingGroupName

instance Prelude.NFData DescribeBillingGroup where
  rnf :: DescribeBillingGroup -> ()
rnf DescribeBillingGroup' {Text
billingGroupName :: Text
$sel:billingGroupName:DescribeBillingGroup' :: DescribeBillingGroup -> Text
..} =
    forall a. NFData a => a -> ()
Prelude.rnf Text
billingGroupName

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

instance Data.ToPath DescribeBillingGroup where
  toPath :: DescribeBillingGroup -> ByteString
toPath DescribeBillingGroup' {Text
billingGroupName :: Text
$sel:billingGroupName:DescribeBillingGroup' :: DescribeBillingGroup -> Text
..} =
    forall a. Monoid a => [a] -> a
Prelude.mconcat
      [ByteString
"/billing-groups/", forall a. ToByteString a => a -> ByteString
Data.toBS Text
billingGroupName]

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

-- | /See:/ 'newDescribeBillingGroupResponse' smart constructor.
data DescribeBillingGroupResponse = DescribeBillingGroupResponse'
  { -- | The ARN of the billing group.
    DescribeBillingGroupResponse -> Maybe Text
billingGroupArn :: Prelude.Maybe Prelude.Text,
    -- | The ID of the billing group.
    DescribeBillingGroupResponse -> Maybe Text
billingGroupId :: Prelude.Maybe Prelude.Text,
    -- | Additional information about the billing group.
    DescribeBillingGroupResponse -> Maybe BillingGroupMetadata
billingGroupMetadata :: Prelude.Maybe BillingGroupMetadata,
    -- | The name of the billing group.
    DescribeBillingGroupResponse -> Maybe Text
billingGroupName :: Prelude.Maybe Prelude.Text,
    -- | The properties of the billing group.
    DescribeBillingGroupResponse -> Maybe BillingGroupProperties
billingGroupProperties :: Prelude.Maybe BillingGroupProperties,
    -- | The version of the billing group.
    DescribeBillingGroupResponse -> Maybe Integer
version :: Prelude.Maybe Prelude.Integer,
    -- | The response's http status code.
    DescribeBillingGroupResponse -> Int
httpStatus :: Prelude.Int
  }
  deriving (DescribeBillingGroupResponse
-> DescribeBillingGroupResponse -> Bool
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: DescribeBillingGroupResponse
-> DescribeBillingGroupResponse -> Bool
$c/= :: DescribeBillingGroupResponse
-> DescribeBillingGroupResponse -> Bool
== :: DescribeBillingGroupResponse
-> DescribeBillingGroupResponse -> Bool
$c== :: DescribeBillingGroupResponse
-> DescribeBillingGroupResponse -> Bool
Prelude.Eq, ReadPrec [DescribeBillingGroupResponse]
ReadPrec DescribeBillingGroupResponse
Int -> ReadS DescribeBillingGroupResponse
ReadS [DescribeBillingGroupResponse]
forall a.
(Int -> ReadS a)
-> ReadS [a] -> ReadPrec a -> ReadPrec [a] -> Read a
readListPrec :: ReadPrec [DescribeBillingGroupResponse]
$creadListPrec :: ReadPrec [DescribeBillingGroupResponse]
readPrec :: ReadPrec DescribeBillingGroupResponse
$creadPrec :: ReadPrec DescribeBillingGroupResponse
readList :: ReadS [DescribeBillingGroupResponse]
$creadList :: ReadS [DescribeBillingGroupResponse]
readsPrec :: Int -> ReadS DescribeBillingGroupResponse
$creadsPrec :: Int -> ReadS DescribeBillingGroupResponse
Prelude.Read, Int -> DescribeBillingGroupResponse -> ShowS
[DescribeBillingGroupResponse] -> ShowS
DescribeBillingGroupResponse -> String
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [DescribeBillingGroupResponse] -> ShowS
$cshowList :: [DescribeBillingGroupResponse] -> ShowS
show :: DescribeBillingGroupResponse -> String
$cshow :: DescribeBillingGroupResponse -> String
showsPrec :: Int -> DescribeBillingGroupResponse -> ShowS
$cshowsPrec :: Int -> DescribeBillingGroupResponse -> ShowS
Prelude.Show, forall x.
Rep DescribeBillingGroupResponse x -> DescribeBillingGroupResponse
forall x.
DescribeBillingGroupResponse -> Rep DescribeBillingGroupResponse x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cto :: forall x.
Rep DescribeBillingGroupResponse x -> DescribeBillingGroupResponse
$cfrom :: forall x.
DescribeBillingGroupResponse -> Rep DescribeBillingGroupResponse x
Prelude.Generic)

-- |
-- Create a value of 'DescribeBillingGroupResponse' 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:
--
-- 'billingGroupArn', 'describeBillingGroupResponse_billingGroupArn' - The ARN of the billing group.
--
-- 'billingGroupId', 'describeBillingGroupResponse_billingGroupId' - The ID of the billing group.
--
-- 'billingGroupMetadata', 'describeBillingGroupResponse_billingGroupMetadata' - Additional information about the billing group.
--
-- 'billingGroupName', 'describeBillingGroupResponse_billingGroupName' - The name of the billing group.
--
-- 'billingGroupProperties', 'describeBillingGroupResponse_billingGroupProperties' - The properties of the billing group.
--
-- 'version', 'describeBillingGroupResponse_version' - The version of the billing group.
--
-- 'httpStatus', 'describeBillingGroupResponse_httpStatus' - The response's http status code.
newDescribeBillingGroupResponse ::
  -- | 'httpStatus'
  Prelude.Int ->
  DescribeBillingGroupResponse
newDescribeBillingGroupResponse :: Int -> DescribeBillingGroupResponse
newDescribeBillingGroupResponse Int
pHttpStatus_ =
  DescribeBillingGroupResponse'
    { $sel:billingGroupArn:DescribeBillingGroupResponse' :: Maybe Text
billingGroupArn =
        forall a. Maybe a
Prelude.Nothing,
      $sel:billingGroupId:DescribeBillingGroupResponse' :: Maybe Text
billingGroupId = forall a. Maybe a
Prelude.Nothing,
      $sel:billingGroupMetadata:DescribeBillingGroupResponse' :: Maybe BillingGroupMetadata
billingGroupMetadata = forall a. Maybe a
Prelude.Nothing,
      $sel:billingGroupName:DescribeBillingGroupResponse' :: Maybe Text
billingGroupName = forall a. Maybe a
Prelude.Nothing,
      $sel:billingGroupProperties:DescribeBillingGroupResponse' :: Maybe BillingGroupProperties
billingGroupProperties = forall a. Maybe a
Prelude.Nothing,
      $sel:version:DescribeBillingGroupResponse' :: Maybe Integer
version = forall a. Maybe a
Prelude.Nothing,
      $sel:httpStatus:DescribeBillingGroupResponse' :: Int
httpStatus = Int
pHttpStatus_
    }

-- | The ARN of the billing group.
describeBillingGroupResponse_billingGroupArn :: Lens.Lens' DescribeBillingGroupResponse (Prelude.Maybe Prelude.Text)
describeBillingGroupResponse_billingGroupArn :: Lens' DescribeBillingGroupResponse (Maybe Text)
describeBillingGroupResponse_billingGroupArn = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\DescribeBillingGroupResponse' {Maybe Text
billingGroupArn :: Maybe Text
$sel:billingGroupArn:DescribeBillingGroupResponse' :: DescribeBillingGroupResponse -> Maybe Text
billingGroupArn} -> Maybe Text
billingGroupArn) (\s :: DescribeBillingGroupResponse
s@DescribeBillingGroupResponse' {} Maybe Text
a -> DescribeBillingGroupResponse
s {$sel:billingGroupArn:DescribeBillingGroupResponse' :: Maybe Text
billingGroupArn = Maybe Text
a} :: DescribeBillingGroupResponse)

-- | The ID of the billing group.
describeBillingGroupResponse_billingGroupId :: Lens.Lens' DescribeBillingGroupResponse (Prelude.Maybe Prelude.Text)
describeBillingGroupResponse_billingGroupId :: Lens' DescribeBillingGroupResponse (Maybe Text)
describeBillingGroupResponse_billingGroupId = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\DescribeBillingGroupResponse' {Maybe Text
billingGroupId :: Maybe Text
$sel:billingGroupId:DescribeBillingGroupResponse' :: DescribeBillingGroupResponse -> Maybe Text
billingGroupId} -> Maybe Text
billingGroupId) (\s :: DescribeBillingGroupResponse
s@DescribeBillingGroupResponse' {} Maybe Text
a -> DescribeBillingGroupResponse
s {$sel:billingGroupId:DescribeBillingGroupResponse' :: Maybe Text
billingGroupId = Maybe Text
a} :: DescribeBillingGroupResponse)

-- | Additional information about the billing group.
describeBillingGroupResponse_billingGroupMetadata :: Lens.Lens' DescribeBillingGroupResponse (Prelude.Maybe BillingGroupMetadata)
describeBillingGroupResponse_billingGroupMetadata :: Lens' DescribeBillingGroupResponse (Maybe BillingGroupMetadata)
describeBillingGroupResponse_billingGroupMetadata = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\DescribeBillingGroupResponse' {Maybe BillingGroupMetadata
billingGroupMetadata :: Maybe BillingGroupMetadata
$sel:billingGroupMetadata:DescribeBillingGroupResponse' :: DescribeBillingGroupResponse -> Maybe BillingGroupMetadata
billingGroupMetadata} -> Maybe BillingGroupMetadata
billingGroupMetadata) (\s :: DescribeBillingGroupResponse
s@DescribeBillingGroupResponse' {} Maybe BillingGroupMetadata
a -> DescribeBillingGroupResponse
s {$sel:billingGroupMetadata:DescribeBillingGroupResponse' :: Maybe BillingGroupMetadata
billingGroupMetadata = Maybe BillingGroupMetadata
a} :: DescribeBillingGroupResponse)

-- | The name of the billing group.
describeBillingGroupResponse_billingGroupName :: Lens.Lens' DescribeBillingGroupResponse (Prelude.Maybe Prelude.Text)
describeBillingGroupResponse_billingGroupName :: Lens' DescribeBillingGroupResponse (Maybe Text)
describeBillingGroupResponse_billingGroupName = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\DescribeBillingGroupResponse' {Maybe Text
billingGroupName :: Maybe Text
$sel:billingGroupName:DescribeBillingGroupResponse' :: DescribeBillingGroupResponse -> Maybe Text
billingGroupName} -> Maybe Text
billingGroupName) (\s :: DescribeBillingGroupResponse
s@DescribeBillingGroupResponse' {} Maybe Text
a -> DescribeBillingGroupResponse
s {$sel:billingGroupName:DescribeBillingGroupResponse' :: Maybe Text
billingGroupName = Maybe Text
a} :: DescribeBillingGroupResponse)

-- | The properties of the billing group.
describeBillingGroupResponse_billingGroupProperties :: Lens.Lens' DescribeBillingGroupResponse (Prelude.Maybe BillingGroupProperties)
describeBillingGroupResponse_billingGroupProperties :: Lens' DescribeBillingGroupResponse (Maybe BillingGroupProperties)
describeBillingGroupResponse_billingGroupProperties = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\DescribeBillingGroupResponse' {Maybe BillingGroupProperties
billingGroupProperties :: Maybe BillingGroupProperties
$sel:billingGroupProperties:DescribeBillingGroupResponse' :: DescribeBillingGroupResponse -> Maybe BillingGroupProperties
billingGroupProperties} -> Maybe BillingGroupProperties
billingGroupProperties) (\s :: DescribeBillingGroupResponse
s@DescribeBillingGroupResponse' {} Maybe BillingGroupProperties
a -> DescribeBillingGroupResponse
s {$sel:billingGroupProperties:DescribeBillingGroupResponse' :: Maybe BillingGroupProperties
billingGroupProperties = Maybe BillingGroupProperties
a} :: DescribeBillingGroupResponse)

-- | The version of the billing group.
describeBillingGroupResponse_version :: Lens.Lens' DescribeBillingGroupResponse (Prelude.Maybe Prelude.Integer)
describeBillingGroupResponse_version :: Lens' DescribeBillingGroupResponse (Maybe Integer)
describeBillingGroupResponse_version = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\DescribeBillingGroupResponse' {Maybe Integer
version :: Maybe Integer
$sel:version:DescribeBillingGroupResponse' :: DescribeBillingGroupResponse -> Maybe Integer
version} -> Maybe Integer
version) (\s :: DescribeBillingGroupResponse
s@DescribeBillingGroupResponse' {} Maybe Integer
a -> DescribeBillingGroupResponse
s {$sel:version:DescribeBillingGroupResponse' :: Maybe Integer
version = Maybe Integer
a} :: DescribeBillingGroupResponse)

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

instance Prelude.NFData DescribeBillingGroupResponse where
  rnf :: DescribeBillingGroupResponse -> ()
rnf DescribeBillingGroupResponse' {Int
Maybe Integer
Maybe Text
Maybe BillingGroupMetadata
Maybe BillingGroupProperties
httpStatus :: Int
version :: Maybe Integer
billingGroupProperties :: Maybe BillingGroupProperties
billingGroupName :: Maybe Text
billingGroupMetadata :: Maybe BillingGroupMetadata
billingGroupId :: Maybe Text
billingGroupArn :: Maybe Text
$sel:httpStatus:DescribeBillingGroupResponse' :: DescribeBillingGroupResponse -> Int
$sel:version:DescribeBillingGroupResponse' :: DescribeBillingGroupResponse -> Maybe Integer
$sel:billingGroupProperties:DescribeBillingGroupResponse' :: DescribeBillingGroupResponse -> Maybe BillingGroupProperties
$sel:billingGroupName:DescribeBillingGroupResponse' :: DescribeBillingGroupResponse -> Maybe Text
$sel:billingGroupMetadata:DescribeBillingGroupResponse' :: DescribeBillingGroupResponse -> Maybe BillingGroupMetadata
$sel:billingGroupId:DescribeBillingGroupResponse' :: DescribeBillingGroupResponse -> Maybe Text
$sel:billingGroupArn:DescribeBillingGroupResponse' :: DescribeBillingGroupResponse -> Maybe Text
..} =
    forall a. NFData a => a -> ()
Prelude.rnf Maybe Text
billingGroupArn
      seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf Maybe Text
billingGroupId
      seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf Maybe BillingGroupMetadata
billingGroupMetadata
      seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf Maybe Text
billingGroupName
      seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf Maybe BillingGroupProperties
billingGroupProperties
      seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf Maybe Integer
version
      seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf Int
httpStatus