{-# 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.BillingConductor.UpdateCustomLineItem
-- Copyright   : (c) 2013-2023 Brendan Hay
-- License     : Mozilla Public License, v. 2.0.
-- Maintainer  : Brendan Hay
-- Stability   : auto-generated
-- Portability : non-portable (GHC extensions)
--
-- Update an existing custom line item in the current or previous billing
-- period.
module Amazonka.BillingConductor.UpdateCustomLineItem
  ( -- * Creating a Request
    UpdateCustomLineItem (..),
    newUpdateCustomLineItem,

    -- * Request Lenses
    updateCustomLineItem_billingPeriodRange,
    updateCustomLineItem_chargeDetails,
    updateCustomLineItem_description,
    updateCustomLineItem_name,
    updateCustomLineItem_arn,

    -- * Destructuring the Response
    UpdateCustomLineItemResponse (..),
    newUpdateCustomLineItemResponse,

    -- * Response Lenses
    updateCustomLineItemResponse_arn,
    updateCustomLineItemResponse_associationSize,
    updateCustomLineItemResponse_billingGroupArn,
    updateCustomLineItemResponse_chargeDetails,
    updateCustomLineItemResponse_description,
    updateCustomLineItemResponse_lastModifiedTime,
    updateCustomLineItemResponse_name,
    updateCustomLineItemResponse_httpStatus,
  )
where

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

-- | /See:/ 'newUpdateCustomLineItem' smart constructor.
data UpdateCustomLineItem = UpdateCustomLineItem'
  { UpdateCustomLineItem -> Maybe CustomLineItemBillingPeriodRange
billingPeriodRange :: Prelude.Maybe CustomLineItemBillingPeriodRange,
    -- | A @ListCustomLineItemChargeDetails@ containing the new charge details
    -- for the custom line item.
    UpdateCustomLineItem -> Maybe UpdateCustomLineItemChargeDetails
chargeDetails :: Prelude.Maybe UpdateCustomLineItemChargeDetails,
    -- | The new line item description of the custom line item.
    UpdateCustomLineItem -> Maybe (Sensitive Text)
description :: Prelude.Maybe (Data.Sensitive Prelude.Text),
    -- | The new name for the custom line item.
    UpdateCustomLineItem -> Maybe (Sensitive Text)
name :: Prelude.Maybe (Data.Sensitive Prelude.Text),
    -- | The ARN of the custom line item to be updated.
    UpdateCustomLineItem -> Text
arn :: Prelude.Text
  }
  deriving (UpdateCustomLineItem -> UpdateCustomLineItem -> Bool
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: UpdateCustomLineItem -> UpdateCustomLineItem -> Bool
$c/= :: UpdateCustomLineItem -> UpdateCustomLineItem -> Bool
== :: UpdateCustomLineItem -> UpdateCustomLineItem -> Bool
$c== :: UpdateCustomLineItem -> UpdateCustomLineItem -> Bool
Prelude.Eq, Int -> UpdateCustomLineItem -> ShowS
[UpdateCustomLineItem] -> ShowS
UpdateCustomLineItem -> String
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [UpdateCustomLineItem] -> ShowS
$cshowList :: [UpdateCustomLineItem] -> ShowS
show :: UpdateCustomLineItem -> String
$cshow :: UpdateCustomLineItem -> String
showsPrec :: Int -> UpdateCustomLineItem -> ShowS
$cshowsPrec :: Int -> UpdateCustomLineItem -> ShowS
Prelude.Show, forall x. Rep UpdateCustomLineItem x -> UpdateCustomLineItem
forall x. UpdateCustomLineItem -> Rep UpdateCustomLineItem x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cto :: forall x. Rep UpdateCustomLineItem x -> UpdateCustomLineItem
$cfrom :: forall x. UpdateCustomLineItem -> Rep UpdateCustomLineItem x
Prelude.Generic)

-- |
-- Create a value of 'UpdateCustomLineItem' 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:
--
-- 'billingPeriodRange', 'updateCustomLineItem_billingPeriodRange' - Undocumented member.
--
-- 'chargeDetails', 'updateCustomLineItem_chargeDetails' - A @ListCustomLineItemChargeDetails@ containing the new charge details
-- for the custom line item.
--
-- 'description', 'updateCustomLineItem_description' - The new line item description of the custom line item.
--
-- 'name', 'updateCustomLineItem_name' - The new name for the custom line item.
--
-- 'arn', 'updateCustomLineItem_arn' - The ARN of the custom line item to be updated.
newUpdateCustomLineItem ::
  -- | 'arn'
  Prelude.Text ->
  UpdateCustomLineItem
newUpdateCustomLineItem :: Text -> UpdateCustomLineItem
newUpdateCustomLineItem Text
pArn_ =
  UpdateCustomLineItem'
    { $sel:billingPeriodRange:UpdateCustomLineItem' :: Maybe CustomLineItemBillingPeriodRange
billingPeriodRange =
        forall a. Maybe a
Prelude.Nothing,
      $sel:chargeDetails:UpdateCustomLineItem' :: Maybe UpdateCustomLineItemChargeDetails
chargeDetails = forall a. Maybe a
Prelude.Nothing,
      $sel:description:UpdateCustomLineItem' :: Maybe (Sensitive Text)
description = forall a. Maybe a
Prelude.Nothing,
      $sel:name:UpdateCustomLineItem' :: Maybe (Sensitive Text)
name = forall a. Maybe a
Prelude.Nothing,
      $sel:arn:UpdateCustomLineItem' :: Text
arn = Text
pArn_
    }

-- | Undocumented member.
updateCustomLineItem_billingPeriodRange :: Lens.Lens' UpdateCustomLineItem (Prelude.Maybe CustomLineItemBillingPeriodRange)
updateCustomLineItem_billingPeriodRange :: Lens' UpdateCustomLineItem (Maybe CustomLineItemBillingPeriodRange)
updateCustomLineItem_billingPeriodRange = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\UpdateCustomLineItem' {Maybe CustomLineItemBillingPeriodRange
billingPeriodRange :: Maybe CustomLineItemBillingPeriodRange
$sel:billingPeriodRange:UpdateCustomLineItem' :: UpdateCustomLineItem -> Maybe CustomLineItemBillingPeriodRange
billingPeriodRange} -> Maybe CustomLineItemBillingPeriodRange
billingPeriodRange) (\s :: UpdateCustomLineItem
s@UpdateCustomLineItem' {} Maybe CustomLineItemBillingPeriodRange
a -> UpdateCustomLineItem
s {$sel:billingPeriodRange:UpdateCustomLineItem' :: Maybe CustomLineItemBillingPeriodRange
billingPeriodRange = Maybe CustomLineItemBillingPeriodRange
a} :: UpdateCustomLineItem)

-- | A @ListCustomLineItemChargeDetails@ containing the new charge details
-- for the custom line item.
updateCustomLineItem_chargeDetails :: Lens.Lens' UpdateCustomLineItem (Prelude.Maybe UpdateCustomLineItemChargeDetails)
updateCustomLineItem_chargeDetails :: Lens'
  UpdateCustomLineItem (Maybe UpdateCustomLineItemChargeDetails)
updateCustomLineItem_chargeDetails = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\UpdateCustomLineItem' {Maybe UpdateCustomLineItemChargeDetails
chargeDetails :: Maybe UpdateCustomLineItemChargeDetails
$sel:chargeDetails:UpdateCustomLineItem' :: UpdateCustomLineItem -> Maybe UpdateCustomLineItemChargeDetails
chargeDetails} -> Maybe UpdateCustomLineItemChargeDetails
chargeDetails) (\s :: UpdateCustomLineItem
s@UpdateCustomLineItem' {} Maybe UpdateCustomLineItemChargeDetails
a -> UpdateCustomLineItem
s {$sel:chargeDetails:UpdateCustomLineItem' :: Maybe UpdateCustomLineItemChargeDetails
chargeDetails = Maybe UpdateCustomLineItemChargeDetails
a} :: UpdateCustomLineItem)

-- | The new line item description of the custom line item.
updateCustomLineItem_description :: Lens.Lens' UpdateCustomLineItem (Prelude.Maybe Prelude.Text)
updateCustomLineItem_description :: Lens' UpdateCustomLineItem (Maybe Text)
updateCustomLineItem_description = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\UpdateCustomLineItem' {Maybe (Sensitive Text)
description :: Maybe (Sensitive Text)
$sel:description:UpdateCustomLineItem' :: UpdateCustomLineItem -> Maybe (Sensitive Text)
description} -> Maybe (Sensitive Text)
description) (\s :: UpdateCustomLineItem
s@UpdateCustomLineItem' {} Maybe (Sensitive Text)
a -> UpdateCustomLineItem
s {$sel:description:UpdateCustomLineItem' :: Maybe (Sensitive Text)
description = Maybe (Sensitive Text)
a} :: UpdateCustomLineItem) 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 a. Iso' (Sensitive a) a
Data._Sensitive

-- | The new name for the custom line item.
updateCustomLineItem_name :: Lens.Lens' UpdateCustomLineItem (Prelude.Maybe Prelude.Text)
updateCustomLineItem_name :: Lens' UpdateCustomLineItem (Maybe Text)
updateCustomLineItem_name = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\UpdateCustomLineItem' {Maybe (Sensitive Text)
name :: Maybe (Sensitive Text)
$sel:name:UpdateCustomLineItem' :: UpdateCustomLineItem -> Maybe (Sensitive Text)
name} -> Maybe (Sensitive Text)
name) (\s :: UpdateCustomLineItem
s@UpdateCustomLineItem' {} Maybe (Sensitive Text)
a -> UpdateCustomLineItem
s {$sel:name:UpdateCustomLineItem' :: Maybe (Sensitive Text)
name = Maybe (Sensitive Text)
a} :: UpdateCustomLineItem) 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 a. Iso' (Sensitive a) a
Data._Sensitive

-- | The ARN of the custom line item to be updated.
updateCustomLineItem_arn :: Lens.Lens' UpdateCustomLineItem Prelude.Text
updateCustomLineItem_arn :: Lens' UpdateCustomLineItem Text
updateCustomLineItem_arn = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\UpdateCustomLineItem' {Text
arn :: Text
$sel:arn:UpdateCustomLineItem' :: UpdateCustomLineItem -> Text
arn} -> Text
arn) (\s :: UpdateCustomLineItem
s@UpdateCustomLineItem' {} Text
a -> UpdateCustomLineItem
s {$sel:arn:UpdateCustomLineItem' :: Text
arn = Text
a} :: UpdateCustomLineItem)

instance Core.AWSRequest UpdateCustomLineItem where
  type
    AWSResponse UpdateCustomLineItem =
      UpdateCustomLineItemResponse
  request :: (Service -> Service)
-> UpdateCustomLineItem -> Request UpdateCustomLineItem
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 UpdateCustomLineItem
-> ClientResponse ClientBody
-> m (Either
        Error (ClientResponse (AWSResponse UpdateCustomLineItem)))
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 Natural
-> Maybe Text
-> Maybe ListCustomLineItemChargeDetails
-> Maybe (Sensitive Text)
-> Maybe Integer
-> Maybe (Sensitive Text)
-> Int
-> UpdateCustomLineItemResponse
UpdateCustomLineItemResponse'
            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
"Arn")
            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
"AssociationSize")
            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
"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
"ChargeDetails")
            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
"Description")
            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
"LastModifiedTime")
            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
"Name")
            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 UpdateCustomLineItem where
  hashWithSalt :: Int -> UpdateCustomLineItem -> Int
hashWithSalt Int
_salt UpdateCustomLineItem' {Maybe (Sensitive Text)
Maybe CustomLineItemBillingPeriodRange
Maybe UpdateCustomLineItemChargeDetails
Text
arn :: Text
name :: Maybe (Sensitive Text)
description :: Maybe (Sensitive Text)
chargeDetails :: Maybe UpdateCustomLineItemChargeDetails
billingPeriodRange :: Maybe CustomLineItemBillingPeriodRange
$sel:arn:UpdateCustomLineItem' :: UpdateCustomLineItem -> Text
$sel:name:UpdateCustomLineItem' :: UpdateCustomLineItem -> Maybe (Sensitive Text)
$sel:description:UpdateCustomLineItem' :: UpdateCustomLineItem -> Maybe (Sensitive Text)
$sel:chargeDetails:UpdateCustomLineItem' :: UpdateCustomLineItem -> Maybe UpdateCustomLineItemChargeDetails
$sel:billingPeriodRange:UpdateCustomLineItem' :: UpdateCustomLineItem -> Maybe CustomLineItemBillingPeriodRange
..} =
    Int
_salt
      forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Maybe CustomLineItemBillingPeriodRange
billingPeriodRange
      forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Maybe UpdateCustomLineItemChargeDetails
chargeDetails
      forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Maybe (Sensitive Text)
description
      forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Maybe (Sensitive Text)
name
      forall a. Hashable a => Int -> a -> Int
`Prelude.hashWithSalt` Text
arn

instance Prelude.NFData UpdateCustomLineItem where
  rnf :: UpdateCustomLineItem -> ()
rnf UpdateCustomLineItem' {Maybe (Sensitive Text)
Maybe CustomLineItemBillingPeriodRange
Maybe UpdateCustomLineItemChargeDetails
Text
arn :: Text
name :: Maybe (Sensitive Text)
description :: Maybe (Sensitive Text)
chargeDetails :: Maybe UpdateCustomLineItemChargeDetails
billingPeriodRange :: Maybe CustomLineItemBillingPeriodRange
$sel:arn:UpdateCustomLineItem' :: UpdateCustomLineItem -> Text
$sel:name:UpdateCustomLineItem' :: UpdateCustomLineItem -> Maybe (Sensitive Text)
$sel:description:UpdateCustomLineItem' :: UpdateCustomLineItem -> Maybe (Sensitive Text)
$sel:chargeDetails:UpdateCustomLineItem' :: UpdateCustomLineItem -> Maybe UpdateCustomLineItemChargeDetails
$sel:billingPeriodRange:UpdateCustomLineItem' :: UpdateCustomLineItem -> Maybe CustomLineItemBillingPeriodRange
..} =
    forall a. NFData a => a -> ()
Prelude.rnf Maybe CustomLineItemBillingPeriodRange
billingPeriodRange
      seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf Maybe UpdateCustomLineItemChargeDetails
chargeDetails
      seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf Maybe (Sensitive Text)
description
      seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf Maybe (Sensitive Text)
name
      seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf Text
arn

instance Data.ToHeaders UpdateCustomLineItem where
  toHeaders :: UpdateCustomLineItem -> 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.ToJSON UpdateCustomLineItem where
  toJSON :: UpdateCustomLineItem -> Value
toJSON UpdateCustomLineItem' {Maybe (Sensitive Text)
Maybe CustomLineItemBillingPeriodRange
Maybe UpdateCustomLineItemChargeDetails
Text
arn :: Text
name :: Maybe (Sensitive Text)
description :: Maybe (Sensitive Text)
chargeDetails :: Maybe UpdateCustomLineItemChargeDetails
billingPeriodRange :: Maybe CustomLineItemBillingPeriodRange
$sel:arn:UpdateCustomLineItem' :: UpdateCustomLineItem -> Text
$sel:name:UpdateCustomLineItem' :: UpdateCustomLineItem -> Maybe (Sensitive Text)
$sel:description:UpdateCustomLineItem' :: UpdateCustomLineItem -> Maybe (Sensitive Text)
$sel:chargeDetails:UpdateCustomLineItem' :: UpdateCustomLineItem -> Maybe UpdateCustomLineItemChargeDetails
$sel:billingPeriodRange:UpdateCustomLineItem' :: UpdateCustomLineItem -> Maybe CustomLineItemBillingPeriodRange
..} =
    [Pair] -> Value
Data.object
      ( forall a. [Maybe a] -> [a]
Prelude.catMaybes
          [ (Key
"BillingPeriodRange" 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 CustomLineItemBillingPeriodRange
billingPeriodRange,
            (Key
"ChargeDetails" 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 UpdateCustomLineItemChargeDetails
chargeDetails,
            (Key
"Description" 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 (Sensitive Text)
description,
            (Key
"Name" 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 (Sensitive Text)
name,
            forall a. a -> Maybe a
Prelude.Just (Key
"Arn" forall kv v. (KeyValue kv, ToJSON v) => Key -> v -> kv
Data..= Text
arn)
          ]
      )

instance Data.ToPath UpdateCustomLineItem where
  toPath :: UpdateCustomLineItem -> ByteString
toPath = forall a b. a -> b -> a
Prelude.const ByteString
"/update-custom-line-item"

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

-- | /See:/ 'newUpdateCustomLineItemResponse' smart constructor.
data UpdateCustomLineItemResponse = UpdateCustomLineItemResponse'
  { -- | The ARN of the successfully updated custom line item.
    UpdateCustomLineItemResponse -> Maybe Text
arn :: Prelude.Maybe Prelude.Text,
    -- | The number of resources that are associated to the custom line item.
    UpdateCustomLineItemResponse -> Maybe Natural
associationSize :: Prelude.Maybe Prelude.Natural,
    -- | The ARN of the billing group that the custom line item is applied to.
    UpdateCustomLineItemResponse -> Maybe Text
billingGroupArn :: Prelude.Maybe Prelude.Text,
    -- | A @ListCustomLineItemChargeDetails@ containing the charge details of the
    -- successfully updated custom line item.
    UpdateCustomLineItemResponse
-> Maybe ListCustomLineItemChargeDetails
chargeDetails :: Prelude.Maybe ListCustomLineItemChargeDetails,
    -- | The description of the successfully updated custom line item.
    UpdateCustomLineItemResponse -> Maybe (Sensitive Text)
description :: Prelude.Maybe (Data.Sensitive Prelude.Text),
    -- | The most recent time when the custom line item was modified.
    UpdateCustomLineItemResponse -> Maybe Integer
lastModifiedTime :: Prelude.Maybe Prelude.Integer,
    -- | The name of the successfully updated custom line item.
    UpdateCustomLineItemResponse -> Maybe (Sensitive Text)
name :: Prelude.Maybe (Data.Sensitive Prelude.Text),
    -- | The response's http status code.
    UpdateCustomLineItemResponse -> Int
httpStatus :: Prelude.Int
  }
  deriving (UpdateCustomLineItemResponse
-> UpdateCustomLineItemResponse -> Bool
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: UpdateCustomLineItemResponse
-> UpdateCustomLineItemResponse -> Bool
$c/= :: UpdateCustomLineItemResponse
-> UpdateCustomLineItemResponse -> Bool
== :: UpdateCustomLineItemResponse
-> UpdateCustomLineItemResponse -> Bool
$c== :: UpdateCustomLineItemResponse
-> UpdateCustomLineItemResponse -> Bool
Prelude.Eq, Int -> UpdateCustomLineItemResponse -> ShowS
[UpdateCustomLineItemResponse] -> ShowS
UpdateCustomLineItemResponse -> String
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [UpdateCustomLineItemResponse] -> ShowS
$cshowList :: [UpdateCustomLineItemResponse] -> ShowS
show :: UpdateCustomLineItemResponse -> String
$cshow :: UpdateCustomLineItemResponse -> String
showsPrec :: Int -> UpdateCustomLineItemResponse -> ShowS
$cshowsPrec :: Int -> UpdateCustomLineItemResponse -> ShowS
Prelude.Show, forall x.
Rep UpdateCustomLineItemResponse x -> UpdateCustomLineItemResponse
forall x.
UpdateCustomLineItemResponse -> Rep UpdateCustomLineItemResponse x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cto :: forall x.
Rep UpdateCustomLineItemResponse x -> UpdateCustomLineItemResponse
$cfrom :: forall x.
UpdateCustomLineItemResponse -> Rep UpdateCustomLineItemResponse x
Prelude.Generic)

-- |
-- Create a value of 'UpdateCustomLineItemResponse' 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:
--
-- 'arn', 'updateCustomLineItemResponse_arn' - The ARN of the successfully updated custom line item.
--
-- 'associationSize', 'updateCustomLineItemResponse_associationSize' - The number of resources that are associated to the custom line item.
--
-- 'billingGroupArn', 'updateCustomLineItemResponse_billingGroupArn' - The ARN of the billing group that the custom line item is applied to.
--
-- 'chargeDetails', 'updateCustomLineItemResponse_chargeDetails' - A @ListCustomLineItemChargeDetails@ containing the charge details of the
-- successfully updated custom line item.
--
-- 'description', 'updateCustomLineItemResponse_description' - The description of the successfully updated custom line item.
--
-- 'lastModifiedTime', 'updateCustomLineItemResponse_lastModifiedTime' - The most recent time when the custom line item was modified.
--
-- 'name', 'updateCustomLineItemResponse_name' - The name of the successfully updated custom line item.
--
-- 'httpStatus', 'updateCustomLineItemResponse_httpStatus' - The response's http status code.
newUpdateCustomLineItemResponse ::
  -- | 'httpStatus'
  Prelude.Int ->
  UpdateCustomLineItemResponse
newUpdateCustomLineItemResponse :: Int -> UpdateCustomLineItemResponse
newUpdateCustomLineItemResponse Int
pHttpStatus_ =
  UpdateCustomLineItemResponse'
    { $sel:arn:UpdateCustomLineItemResponse' :: Maybe Text
arn =
        forall a. Maybe a
Prelude.Nothing,
      $sel:associationSize:UpdateCustomLineItemResponse' :: Maybe Natural
associationSize = forall a. Maybe a
Prelude.Nothing,
      $sel:billingGroupArn:UpdateCustomLineItemResponse' :: Maybe Text
billingGroupArn = forall a. Maybe a
Prelude.Nothing,
      $sel:chargeDetails:UpdateCustomLineItemResponse' :: Maybe ListCustomLineItemChargeDetails
chargeDetails = forall a. Maybe a
Prelude.Nothing,
      $sel:description:UpdateCustomLineItemResponse' :: Maybe (Sensitive Text)
description = forall a. Maybe a
Prelude.Nothing,
      $sel:lastModifiedTime:UpdateCustomLineItemResponse' :: Maybe Integer
lastModifiedTime = forall a. Maybe a
Prelude.Nothing,
      $sel:name:UpdateCustomLineItemResponse' :: Maybe (Sensitive Text)
name = forall a. Maybe a
Prelude.Nothing,
      $sel:httpStatus:UpdateCustomLineItemResponse' :: Int
httpStatus = Int
pHttpStatus_
    }

-- | The ARN of the successfully updated custom line item.
updateCustomLineItemResponse_arn :: Lens.Lens' UpdateCustomLineItemResponse (Prelude.Maybe Prelude.Text)
updateCustomLineItemResponse_arn :: Lens' UpdateCustomLineItemResponse (Maybe Text)
updateCustomLineItemResponse_arn = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\UpdateCustomLineItemResponse' {Maybe Text
arn :: Maybe Text
$sel:arn:UpdateCustomLineItemResponse' :: UpdateCustomLineItemResponse -> Maybe Text
arn} -> Maybe Text
arn) (\s :: UpdateCustomLineItemResponse
s@UpdateCustomLineItemResponse' {} Maybe Text
a -> UpdateCustomLineItemResponse
s {$sel:arn:UpdateCustomLineItemResponse' :: Maybe Text
arn = Maybe Text
a} :: UpdateCustomLineItemResponse)

-- | The number of resources that are associated to the custom line item.
updateCustomLineItemResponse_associationSize :: Lens.Lens' UpdateCustomLineItemResponse (Prelude.Maybe Prelude.Natural)
updateCustomLineItemResponse_associationSize :: Lens' UpdateCustomLineItemResponse (Maybe Natural)
updateCustomLineItemResponse_associationSize = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\UpdateCustomLineItemResponse' {Maybe Natural
associationSize :: Maybe Natural
$sel:associationSize:UpdateCustomLineItemResponse' :: UpdateCustomLineItemResponse -> Maybe Natural
associationSize} -> Maybe Natural
associationSize) (\s :: UpdateCustomLineItemResponse
s@UpdateCustomLineItemResponse' {} Maybe Natural
a -> UpdateCustomLineItemResponse
s {$sel:associationSize:UpdateCustomLineItemResponse' :: Maybe Natural
associationSize = Maybe Natural
a} :: UpdateCustomLineItemResponse)

-- | The ARN of the billing group that the custom line item is applied to.
updateCustomLineItemResponse_billingGroupArn :: Lens.Lens' UpdateCustomLineItemResponse (Prelude.Maybe Prelude.Text)
updateCustomLineItemResponse_billingGroupArn :: Lens' UpdateCustomLineItemResponse (Maybe Text)
updateCustomLineItemResponse_billingGroupArn = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\UpdateCustomLineItemResponse' {Maybe Text
billingGroupArn :: Maybe Text
$sel:billingGroupArn:UpdateCustomLineItemResponse' :: UpdateCustomLineItemResponse -> Maybe Text
billingGroupArn} -> Maybe Text
billingGroupArn) (\s :: UpdateCustomLineItemResponse
s@UpdateCustomLineItemResponse' {} Maybe Text
a -> UpdateCustomLineItemResponse
s {$sel:billingGroupArn:UpdateCustomLineItemResponse' :: Maybe Text
billingGroupArn = Maybe Text
a} :: UpdateCustomLineItemResponse)

-- | A @ListCustomLineItemChargeDetails@ containing the charge details of the
-- successfully updated custom line item.
updateCustomLineItemResponse_chargeDetails :: Lens.Lens' UpdateCustomLineItemResponse (Prelude.Maybe ListCustomLineItemChargeDetails)
updateCustomLineItemResponse_chargeDetails :: Lens'
  UpdateCustomLineItemResponse
  (Maybe ListCustomLineItemChargeDetails)
updateCustomLineItemResponse_chargeDetails = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\UpdateCustomLineItemResponse' {Maybe ListCustomLineItemChargeDetails
chargeDetails :: Maybe ListCustomLineItemChargeDetails
$sel:chargeDetails:UpdateCustomLineItemResponse' :: UpdateCustomLineItemResponse
-> Maybe ListCustomLineItemChargeDetails
chargeDetails} -> Maybe ListCustomLineItemChargeDetails
chargeDetails) (\s :: UpdateCustomLineItemResponse
s@UpdateCustomLineItemResponse' {} Maybe ListCustomLineItemChargeDetails
a -> UpdateCustomLineItemResponse
s {$sel:chargeDetails:UpdateCustomLineItemResponse' :: Maybe ListCustomLineItemChargeDetails
chargeDetails = Maybe ListCustomLineItemChargeDetails
a} :: UpdateCustomLineItemResponse)

-- | The description of the successfully updated custom line item.
updateCustomLineItemResponse_description :: Lens.Lens' UpdateCustomLineItemResponse (Prelude.Maybe Prelude.Text)
updateCustomLineItemResponse_description :: Lens' UpdateCustomLineItemResponse (Maybe Text)
updateCustomLineItemResponse_description = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\UpdateCustomLineItemResponse' {Maybe (Sensitive Text)
description :: Maybe (Sensitive Text)
$sel:description:UpdateCustomLineItemResponse' :: UpdateCustomLineItemResponse -> Maybe (Sensitive Text)
description} -> Maybe (Sensitive Text)
description) (\s :: UpdateCustomLineItemResponse
s@UpdateCustomLineItemResponse' {} Maybe (Sensitive Text)
a -> UpdateCustomLineItemResponse
s {$sel:description:UpdateCustomLineItemResponse' :: Maybe (Sensitive Text)
description = Maybe (Sensitive Text)
a} :: UpdateCustomLineItemResponse) 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 a. Iso' (Sensitive a) a
Data._Sensitive

-- | The most recent time when the custom line item was modified.
updateCustomLineItemResponse_lastModifiedTime :: Lens.Lens' UpdateCustomLineItemResponse (Prelude.Maybe Prelude.Integer)
updateCustomLineItemResponse_lastModifiedTime :: Lens' UpdateCustomLineItemResponse (Maybe Integer)
updateCustomLineItemResponse_lastModifiedTime = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\UpdateCustomLineItemResponse' {Maybe Integer
lastModifiedTime :: Maybe Integer
$sel:lastModifiedTime:UpdateCustomLineItemResponse' :: UpdateCustomLineItemResponse -> Maybe Integer
lastModifiedTime} -> Maybe Integer
lastModifiedTime) (\s :: UpdateCustomLineItemResponse
s@UpdateCustomLineItemResponse' {} Maybe Integer
a -> UpdateCustomLineItemResponse
s {$sel:lastModifiedTime:UpdateCustomLineItemResponse' :: Maybe Integer
lastModifiedTime = Maybe Integer
a} :: UpdateCustomLineItemResponse)

-- | The name of the successfully updated custom line item.
updateCustomLineItemResponse_name :: Lens.Lens' UpdateCustomLineItemResponse (Prelude.Maybe Prelude.Text)
updateCustomLineItemResponse_name :: Lens' UpdateCustomLineItemResponse (Maybe Text)
updateCustomLineItemResponse_name = forall s a b t. (s -> a) -> (s -> b -> t) -> Lens s t a b
Lens.lens (\UpdateCustomLineItemResponse' {Maybe (Sensitive Text)
name :: Maybe (Sensitive Text)
$sel:name:UpdateCustomLineItemResponse' :: UpdateCustomLineItemResponse -> Maybe (Sensitive Text)
name} -> Maybe (Sensitive Text)
name) (\s :: UpdateCustomLineItemResponse
s@UpdateCustomLineItemResponse' {} Maybe (Sensitive Text)
a -> UpdateCustomLineItemResponse
s {$sel:name:UpdateCustomLineItemResponse' :: Maybe (Sensitive Text)
name = Maybe (Sensitive Text)
a} :: UpdateCustomLineItemResponse) 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 a. Iso' (Sensitive a) a
Data._Sensitive

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

instance Prelude.NFData UpdateCustomLineItemResponse where
  rnf :: UpdateCustomLineItemResponse -> ()
rnf UpdateCustomLineItemResponse' {Int
Maybe Integer
Maybe Natural
Maybe Text
Maybe (Sensitive Text)
Maybe ListCustomLineItemChargeDetails
httpStatus :: Int
name :: Maybe (Sensitive Text)
lastModifiedTime :: Maybe Integer
description :: Maybe (Sensitive Text)
chargeDetails :: Maybe ListCustomLineItemChargeDetails
billingGroupArn :: Maybe Text
associationSize :: Maybe Natural
arn :: Maybe Text
$sel:httpStatus:UpdateCustomLineItemResponse' :: UpdateCustomLineItemResponse -> Int
$sel:name:UpdateCustomLineItemResponse' :: UpdateCustomLineItemResponse -> Maybe (Sensitive Text)
$sel:lastModifiedTime:UpdateCustomLineItemResponse' :: UpdateCustomLineItemResponse -> Maybe Integer
$sel:description:UpdateCustomLineItemResponse' :: UpdateCustomLineItemResponse -> Maybe (Sensitive Text)
$sel:chargeDetails:UpdateCustomLineItemResponse' :: UpdateCustomLineItemResponse
-> Maybe ListCustomLineItemChargeDetails
$sel:billingGroupArn:UpdateCustomLineItemResponse' :: UpdateCustomLineItemResponse -> Maybe Text
$sel:associationSize:UpdateCustomLineItemResponse' :: UpdateCustomLineItemResponse -> Maybe Natural
$sel:arn:UpdateCustomLineItemResponse' :: UpdateCustomLineItemResponse -> Maybe Text
..} =
    forall a. NFData a => a -> ()
Prelude.rnf Maybe Text
arn
      seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf Maybe Natural
associationSize
      seq :: forall a b. a -> b -> b
`Prelude.seq` 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 ListCustomLineItemChargeDetails
chargeDetails
      seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf Maybe (Sensitive Text)
description
      seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf Maybe Integer
lastModifiedTime
      seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf Maybe (Sensitive Text)
name
      seq :: forall a b. a -> b -> b
`Prelude.seq` forall a. NFData a => a -> ()
Prelude.rnf Int
httpStatus